New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
domwri.F90 in trunk/NEMO/OPA_SRC/DOM – NEMO

source: trunk/NEMO/OPA_SRC/DOM/domwri.F90 @ 107

Last change on this file since 107 was 107, checked in by opalod, 20 years ago

CT : UPDATE068 : Add binary output possibilities with the dimg output format

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 12.0 KB
Line 
1MODULE domwri
2   !!======================================================================
3   !!                       ***  MODULE domwri  ***
4   !! Ocean initialization : write the ocean domain mesh and mask file(s)
5   !!======================================================================
6
7   !!----------------------------------------------------------------------
8   !!   dom_wri        : create and write mesh and mask file(s)
9   !!                    nmsh = 1  :   mesh_mask file
10   !!                         = 2  :   mesh and mask file
11   !!                         = 3  :   mesh_hgr, mesh_zgr and mask
12   !!----------------------------------------------------------------------
13   !! * Modules used
14   USE dom_oce         ! ocean space and time domain
15   USE in_out_manager
16
17   IMPLICIT NONE
18   PRIVATE
19
20   !! * Accessibility
21   PUBLIC dom_wri        ! routine called by inidom.F90
22   !!----------------------------------------------------------------------
23   !!   OPA 9.0 , LODYC-IPSL  (2003)
24   !!----------------------------------------------------------------------
25
26CONTAINS
27
28#if defined key_fdir
29   !!----------------------------------------------------------------------
30   !!   'key_fdir' :                                     direct access file
31   !!----------------------------------------------------------------------
32#  include "domwri_fdir.h90"
33
34#elif ( defined key_mpp_mpi || defined key_mpp_shmem ) && defined key_dimgout
35   !!----------------------------------------------------------------------
36   !!   'key_mpp_mpi'     OR
37   !!   'key_mpp_shmem'
38   !!   'key_dimgout' :         each processor makes its own direct access file
39   !!                      use build_nc_meshmask off line to retrieve
40   !!                      a ioipsl compliant meshmask file
41   !!----------------------------------------------------------------------
42#  include "domwri_dimg.h90"
43
44
45#else
46   !!----------------------------------------------------------------------
47   !!   Default option :                                        NetCDF file
48   !!----------------------------------------------------------------------
49
50   SUBROUTINE dom_wri
51      !!----------------------------------------------------------------------
52      !!                  ***  ROUTINE dom_wri  ***
53      !!                   
54      !! ** Purpose :   Create the NetCDF file(s) which contain(s) all the
55      !!      ocean domain informations (mesh and mask arrays). This (these)
56      !!      file(s) is (are) used for visualisation (SAXO software) and
57      !!      diagnostic computation.
58      !!
59      !! ** Method  :   Write in a file all the arrays generated in routines
60      !!      domhgr, domzgr, and dommsk. Note: the file contain depends on
61      !!      the vertical coord. used (z-coord, partial steps, s-coord)
62      !!                    nmsh = 1  :   'mesh_mask.nc' file
63      !!                         = 2  :   'mesh.nc' and mask.nc' files
64      !!                         = 3  :   'mesh_hgr.nc', 'mesh_zgr.nc' and
65      !!                                  'mask.nc' files
66      !!      For huge size domain, use option 2 or 3 depending on your
67      !!      vertical coordinate.
68      !!
69      !! ** output file :
70      !!      meshmask.nc  : domain size, horizontal grid-point position,
71      !!                     masks, depth and vertical scale factors
72      !!
73      !! History :
74      !!        !  97-02  (G. Madec)  Original code
75      !!        !  99-11  (M. Imbard)  NetCDF FORMAT with IOIPSL
76      !!   9.0  !  02-08  (G. Madec)  F90 and several file
77      !!----------------------------------------------------------------------
78      !! * Modules used
79      USE ioipsl
80
81      !! * Local declarations
82      INTEGER  ::                & !!! * temprary units for :
83         inum0 ,                 &  ! 'mesh_mask.nc' file
84         inum1 ,                 &  ! 'mesh.nc'      file
85         inum2 ,                 &  ! 'mask.nc'      file
86         inum3 ,                 &  ! 'mesh_hgr.nc'  file
87         inum4                      ! 'mesh_zgr.nc'  file
88      INTEGER  ::   itime           !  output from restini ???
89      REAL(wp) ::   zdate0
90      CHARACTER (len=21) ::      &
91         clnam0 = 'mesh_mask',   &  ! filename (mesh and mask informations)
92         clnam1 = 'mesh'     ,   &  ! filename (mesh informations)
93         clnam2 = 'mask'     ,   &  ! filename (mask informations)
94         clnam3 = 'mesh_hgr' ,   &  ! filename (horizontal mesh informations)
95         clnam4 = 'mesh_zgr'        ! filename (vertical   mesh informations)
96      !!----------------------------------------------------------------------
97
98       IF(lwp) WRITE(numout,*)
99       IF(lwp) WRITE(numout,*) 'dom_wri : create NetCDF mesh and mask information file(s)'
100       IF(lwp) WRITE(numout,*) '~~~~~~~'
101
102      CALL ymds2ju( 0, 1, 1, 0.e0, zdate0 )    ! calendar initialization
103
104
105      SELECT CASE (nmsh)
106         !                                     ! ============================
107         CASE ( 1 )                            !  create 'mesh_mask.nc' file
108            !                                  ! ============================
109
110            IF(lwp) WRITE(numout,*) '          one file in "mesh_mask.nc" '
111            CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh_mask.nc' file
112            &             jpk   , gdept , trim(clnam0)        ,  &   ! in unit inum0
113            &             itime , zdate0, rdt   , inum0          )
114            inum2 = inum0                                            ! put all the informations
115            inum3 = inum0                                            ! in unit inum0
116            inum4 = inum0
117
118            !                                  ! ============================
119         CASE ( 2 )                            !  create 'mesh.nc' and
120            !                                  !         'mask.nc' files
121            !                                  ! ============================
122
123            IF(lwp) WRITE(numout,*) '          two files in "mesh.nc" and "mask.nc" '
124            CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh.nc' file
125            &             jpk   , gdept , trim(clnam1)        ,  &   ! in unit inum1
126            &             itime , zdate0, rdt   , inum1          )
127            CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mask.nc' file
128            &             jpk   , gdept , trim(clnam2)        ,  &   ! in unit inum2
129            &             itime , zdate0, rdt   , inum2          )
130            inum3 = inum1                                            ! put mesh informations
131            inum4 = inum1                                            ! in unit inum1
132
133            !                                  ! ============================
134         CASE ( 3 )                            !  create 'mesh_hgr.nc'
135            !                                  !         'mesh_zgr.nc' and
136            !                                  !         'mask.nc'     files
137            !                                  ! ============================
138
139            IF(lwp) WRITE(numout,*) '          three files in "mesh_hgr.nc" , mesh_zgr.nc" and "mask.nc" '
140            CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh_hgr.nc' file
141            &             jpk   , gdept , trim(clnam3)        ,  &   ! in unit inum3
142            &             itime , zdate0, rdt   , inum3          )
143            CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh_zgr.nc' file
144            &             jpk   , gdept , trim(clnam4)        ,  &   ! in unit inum4
145            &             itime , zdate0, rdt   , inum4          )
146            CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mask.nc' file
147            &             jpk   , gdept , trim(clnam2)        ,  &   ! in unit inum2
148            &             itime , zdate0, rdt   , inum2          ) 
149
150         END SELECT
151
152         !                                                         ! masks (inum2)
153         CALL restput( inum2, 'tmask', jpi, jpj, jpk, 0, tmask ) 
154         CALL restput( inum2, 'umask', jpi, jpj, jpk, 0, umask )
155         CALL restput( inum2, 'vmask', jpi, jpj, jpk, 0, vmask )
156         CALL restput( inum2, 'fmask', jpi, jpj, jpk, 0, fmask )
157
158         !                                                         ! horizontal mesh (inum3)
159         CALL restput( inum3, 'glamt', jpi, jpj, 1, 0, glamt )     !    ! latitude
160         CALL restput( inum3, 'glamu', jpi, jpj, 1, 0, glamu )
161         CALL restput( inum3, 'glamv', jpi, jpj, 1, 0, glamv )
162         CALL restput( inum3, 'glamf', jpi, jpj, 1, 0, glamf )
163
164         CALL restput( inum3, 'gphit', jpi, jpj, 1, 0, gphit )     !    ! longitude
165         CALL restput( inum3, 'gphiu', jpi, jpj, 1, 0, gphiu )
166         CALL restput( inum3, 'gphiv', jpi, jpj, 1, 0, gphiv )
167         CALL restput( inum3, 'gphif', jpi, jpj, 1, 0, gphif )
168
169         CALL restput( inum3, 'e1t', jpi, jpj, 1, 0, e1t )         !    ! e1 scale factors
170         CALL restput( inum3, 'e1u', jpi, jpj, 1, 0, e1u )
171         CALL restput( inum3, 'e1v', jpi, jpj, 1, 0, e1v )
172         CALL restput( inum3, 'e1f', jpi, jpj, 1, 0, e1f )
173
174         CALL restput( inum3, 'e2t', jpi, jpj, 1, 0, e2t )         !    ! e2 scale factors
175         CALL restput( inum3, 'e2u', jpi, jpj, 1, 0, e2u )
176         CALL restput( inum3, 'e2v', jpi, jpj, 1, 0, e2v )
177         CALL restput( inum3, 'e2f', jpi, jpj, 1, 0, e2f )
178
179         CALL restput( inum3, 'ff', jpi, jpj, 1, 0, ff )           !    ! coriolis factor
180
181# if defined key_s_coord
182         !                                                         ! s-coordinate
183         CALL restput( inum4, 'hbatt', jpi, jpj, 1, 0, hbatt )      !    ! depth
184         CALL restput( inum4, 'hbatu', jpi, jpj, 1, 0, hbatu ) 
185         CALL restput( inum4, 'hbatv', jpi, jpj, 1, 0, hbatv )
186         CALL restput( inum4, 'hbatf', jpi, jpj, 1, 0, hbatf )
187
188         CALL restput( inum4, 'gsigt', 1, 1, jpk, 0, gsigt )        !    ! scaling coef.
189         CALL restput( inum4, 'gsigw', 1, 1, jpk, 0, gsigw ) 
190         CALL restput( inum4, 'gsi3w', 1, 1, jpk, 0, gsi3w )
191         CALL restput( inum4, 'esigt', 1, 1, jpk, 0, esigt )
192         CALL restput( inum4, 'esigw', 1, 1, jpk, 0, esigw )
193
194# elif defined key_partial_steps
195         !                                                          ! z-coordinate with partial steps
196         CALL restput( inum4, 'hdept' , jpi, jpj, 1, 0, hdept  )    !    ! depth
197         CALL restput( inum4, 'hdepw' , jpi, jpj, 1, 0, hdepw  ) 
198
199         CALL restput( inum4, 'e3tp'  , jpi, jpj, 1  , 0, e3tp   )  !    ! scale factors
200         CALL restput( inum4, 'e3wp'  , jpi, jpj, 1  , 0, e3wp   )
201         CALL restput( inum4, 'e3u_ps', jpi, jpj, jpk, 0, e3u_ps )
202         CALL restput( inum4, 'e3v_ps', jpi, jpj, jpk, 0, e3v_ps )
203
204         CALL restput( inum4, 'gdept' , 1, 1, jpk, 0, gdept )       !    ! reference z-coord.
205         CALL restput( inum4, 'gdepw' , 1, 1, jpk, 0, gdepw )
206         CALL restput( inum4, 'e3t'   , 1, 1, jpk, 0, e3t   )
207         CALL restput( inum4, 'e3w'   , 1, 1, jpk, 0, e3w   )
208
209# else
210         !                                                          ! z-coordinate
211         CALL restput( inum4, 'gdept', 1, 1, jpk, 0, gdept )        !    ! depth
212         CALL restput( inum4, 'gdepw', 1, 1, jpk, 0, gdepw )
213         CALL restput( inum4, 'e3t'  , 1, 1, jpk, 0, e3t   )        !    ! scale factors
214         CALL restput( inum4, 'e3w'  , 1, 1, jpk, 0, e3w   )
215# endif
216
217         !                                     ! ============================
218         !                                     !        close the files
219         !                                     ! ============================
220         SELECT CASE ( nmsh )
221            CASE ( 1 )               
222               CALL restclo( inum0 )
223            CASE ( 2 )
224               CALL restclo( inum1 )
225               CALL restclo( inum2 )
226            CASE ( 3 )
227               CALL restclo( inum2 )
228               CALL restclo( inum3 )
229               CALL restclo( inum4 )
230         END SELECT
231
232   END SUBROUTINE dom_wri
233
234#endif
235
236   !!======================================================================
237END MODULE domwri
Note: See TracBrowser for help on using the repository browser.