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 @ 1057

Last change on this file since 1057 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.9 KB
Line 
1MODULE domwri
2   !!======================================================================
3   !!                       ***  MODULE domwri  ***
4   !! Ocean initialization : write the ocean domain mesh ask 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   USE iom
17
18   IMPLICIT NONE
19   PRIVATE
20
21   !! * Accessibility
22   PUBLIC dom_wri        ! routine called by inidom.F90
23   !!----------------------------------------------------------------------
24   !!   OPA 9.0 , LOCEAN-IPSL (2005)
25   !! $Header$
26   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
27   !!----------------------------------------------------------------------
28
29CONTAINS
30
31   SUBROUTINE dom_wri
32      !!----------------------------------------------------------------------
33      !!                  ***  ROUTINE dom_wri  ***
34      !!                   
35      !! ** Purpose :   Create the NetCDF file(s) which contain(s) all the
36      !!      ocean domain informations (mesh and mask arrays). This (these)
37      !!      file(s) is (are) used for visualisation (SAXO software) and
38      !!      diagnostic computation.
39      !!
40      !! ** Method  :   Write in a file all the arrays generated in routines
41      !!      domhgr, domzgr, and dommsk. Note: the file contain depends on
42      !!      the vertical coord. used (z-coord, partial steps, s-coord)
43      !!                    nmsh = 1  :   'mesh_mask.nc' file
44      !!                         = 2  :   'mesh.nc' and mask.nc' files
45      !!                         = 3  :   'mesh_hgr.nc', 'mesh_zgr.nc' and
46      !!                                  'mask.nc' files
47      !!      For huge size domain, use option 2 or 3 depending on your
48      !!      vertical coordinate.
49      !!
50      !! ** output file :
51      !!      meshmask.nc  : domain size, horizontal grid-point position,
52      !!                     masks, depth and vertical scale factors
53      !!
54      !! History :
55      !!        !  97-02  (G. Madec)  Original code
56      !!        !  99-11  (M. Imbard)  NetCDF FORMAT with IOIPSL
57      !!   9.0  !  02-08  (G. Madec)  F90 and several file
58      !!----------------------------------------------------------------------
59      INTEGER  ::   inum0   ! temprary units for 'mesh_mask.nc' file
60      INTEGER  ::   inum1   ! temprary units for 'mesh.nc'      file
61      INTEGER  ::   inum2   ! temprary units for 'mask.nc'      file
62      INTEGER  ::   inum3   ! temprary units for 'mesh_hgr.nc'  file
63      INTEGER  ::   inum4   ! temprary units for 'mesh_zgr.nc'  file
64      REAL(wp), DIMENSION(jpi,jpj) ::    zprt   ! temporary array for bathymetry
65      CHARACTER (len=21) ::   clnam0   ! filename (mesh and mask informations)
66      CHARACTER (len=21) ::   clnam1   ! filename (mesh informations)
67      CHARACTER (len=21) ::   clnam2   ! filename (mask informations)
68      CHARACTER (len=21) ::   clnam3   ! filename (horizontal mesh informations)
69      CHARACTER (len=21) ::   clnam4   ! filename (vertical   mesh informations)
70      !!----------------------------------------------------------------------
71
72       IF(lwp) WRITE(numout,*)
73       IF(lwp) WRITE(numout,*) 'dom_wri : create NetCDF mesh and mask information file(s)'
74       IF(lwp) WRITE(numout,*) '~~~~~~~'
75
76       clnam0 = 'mesh_mask'  ! filename (mesh and mask informations)
77       clnam1 = 'mesh'       ! filename (mesh informations)
78       clnam2 = 'mask'       ! filename (mask informations)
79       clnam3 = 'mesh_hgr'   ! filename (horizontal mesh informations)
80       clnam4 = 'mesh_zgr'   ! filename (vertical   mesh informations)
81
82!       note that mbathy has been modified in dommsk or in solver.
83!       it is the number of non-zero "w" levels in the water, and the minimum
84!       value (on land) is 2. We define zprt as the number of "T" points in the ocean
85!       at any location, and zero on land.
86!
87      zprt = tmask(:,:,1)*(mbathy-1)
88
89      SELECT CASE (nmsh)
90         !                                     ! ============================
91         CASE ( 1 )                            !  create 'mesh_mask.nc' file
92            !                                  ! ============================
93            CALL iom_open( TRIM(clnam0), inum0, ldwrt = .TRUE., kiolib = jprstlib )
94            inum2 = inum0                                            ! put all the informations
95            inum3 = inum0                                            ! in unit inum0
96            inum4 = inum0
97
98            !                                  ! ============================
99         CASE ( 2 )                            !  create 'mesh.nc' and
100            !                                  !         'mask.nc' files
101            !                                  ! ============================
102            CALL iom_open( TRIM(clnam1), inum1, ldwrt = .TRUE., kiolib = jprstlib )
103            CALL iom_open( TRIM(clnam2), inum2, ldwrt = .TRUE., kiolib = jprstlib )
104            inum3 = inum1                                            ! put mesh informations
105            inum4 = inum1                                            ! in unit inum1
106            !                                  ! ============================
107         CASE ( 3 )                            !  create 'mesh_hgr.nc'
108            !                                  !         'mesh_zgr.nc' and
109            !                                  !         'mask.nc'     files
110            !                                  ! ============================
111            CALL iom_open( TRIM(clnam2), inum2, ldwrt = .TRUE., kiolib = jprstlib )
112            CALL iom_open( TRIM(clnam3), inum3, ldwrt = .TRUE., kiolib = jprstlib )
113            CALL iom_open( TRIM(clnam4), inum4, ldwrt = .TRUE., kiolib = jprstlib )
114
115         END SELECT
116
117         !                                                         ! masks (inum2)
118         CALL iom_rstput( 0, 0, inum2, 'tmask', tmask, ktype = jp_i1 ) 
119         CALL iom_rstput( 0, 0, inum2, 'umask', umask, ktype = jp_i1 )
120         CALL iom_rstput( 0, 0, inum2, 'vmask', vmask, ktype = jp_i1 )
121         CALL iom_rstput( 0, 0, inum2, 'fmask', fmask, ktype = jp_i1 )
122
123         !                                                         ! horizontal mesh (inum3)
124         CALL iom_rstput( 0, 0, inum3, 'glamt', glamt, ktype = jp_r4 )     !    ! latitude
125         CALL iom_rstput( 0, 0, inum3, 'glamu', glamu, ktype = jp_r4 )
126         CALL iom_rstput( 0, 0, inum3, 'glamv', glamv, ktype = jp_r4 )
127         CALL iom_rstput( 0, 0, inum3, 'glamf', glamf, ktype = jp_r4 )
128
129         CALL iom_rstput( 0, 0, inum3, 'gphit', gphit, ktype = jp_r4 )     !    ! longitude
130         CALL iom_rstput( 0, 0, inum3, 'gphiu', gphiu, ktype = jp_r4 )
131         CALL iom_rstput( 0, 0, inum3, 'gphiv', gphiv, ktype = jp_r4 )
132         CALL iom_rstput( 0, 0, inum3, 'gphif', gphif, ktype = jp_r4 )
133
134         CALL iom_rstput( 0, 0, inum3, 'e1t', e1t, ktype = jp_r8 )         !    ! e1 scale factors
135         CALL iom_rstput( 0, 0, inum3, 'e1u', e1u, ktype = jp_r8 )
136         CALL iom_rstput( 0, 0, inum3, 'e1v', e1v, ktype = jp_r8 )
137         CALL iom_rstput( 0, 0, inum3, 'e1f', e1f, ktype = jp_r8 )
138
139         CALL iom_rstput( 0, 0, inum3, 'e2t', e2t, ktype = jp_r8 )         !    ! e2 scale factors
140         CALL iom_rstput( 0, 0, inum3, 'e2u', e2u, ktype = jp_r8 )
141         CALL iom_rstput( 0, 0, inum3, 'e2v', e2v, ktype = jp_r8 )
142         CALL iom_rstput( 0, 0, inum3, 'e2f', e2f, ktype = jp_r8 )
143
144         CALL iom_rstput( 0, 0, inum3, 'ff', ff, ktype = jp_r8 )           !    ! coriolis factor
145
146         CALL iom_rstput( 0, 0, inum4, 'mbathy', zprt, ktype = jp_i2 )
147
148#if ! defined key_zco
149         IF( ln_sco ) THEN                                         ! s-coordinate
150            CALL iom_rstput( 0, 0, inum4, 'hbatt', hbatt )      !    ! depth
151            CALL iom_rstput( 0, 0, inum4, 'hbatu', hbatu ) 
152            CALL iom_rstput( 0, 0, inum4, 'hbatv', hbatv )
153            CALL iom_rstput( 0, 0, inum4, 'hbatf', hbatf )
154   
155            CALL iom_rstput( 0, 0, inum4, 'gsigt', gsigt )        !    ! scaling coef.
156            CALL iom_rstput( 0, 0, inum4, 'gsigw', gsigw ) 
157            CALL iom_rstput( 0, 0, inum4, 'gsi3w', gsi3w )
158            CALL iom_rstput( 0, 0, inum4, 'esigt', esigt )
159            CALL iom_rstput( 0, 0, inum4, 'esigw', esigw )
160
161            CALL iom_rstput( 0, 0, inum4, 'e3t', e3t )       !    ! scale factors
162            CALL iom_rstput( 0, 0, inum4, 'e3u', e3u )
163            CALL iom_rstput( 0, 0, inum4, 'e3v', e3v )
164            CALL iom_rstput( 0, 0, inum4, 'e3w', e3w )
165
166            CALL iom_rstput( 0, 0, inum4, 'gdept_0' , gdept_0 )  !    ! stretched system
167            CALL iom_rstput( 0, 0, inum4, 'gdepw_0' , gdepw_0 )
168         ENDIF
169
170         IF( ln_zps ) THEN                                         ! z-coordinate - partial steps
171            CALL iom_rstput( 0, 0, inum4, 'hdept' , hdept  )    !    ! depth
172            CALL iom_rstput( 0, 0, inum4, 'hdepw' , hdepw  ) 
173
174            CALL iom_rstput( 0, 0, inum4, 'e3t' , e3t )      !    ! scale factors
175            CALL iom_rstput( 0, 0, inum4, 'e3u' , e3u )
176            CALL iom_rstput( 0, 0, inum4, 'e3v' , e3v )
177            CALL iom_rstput( 0, 0, inum4, 'e3w' , e3w )
178
179            CALL iom_rstput( 0, 0, inum4, 'gdept_0', gdept_0 )   !    ! reference z-coord.
180            CALL iom_rstput( 0, 0, inum4, 'gdepw_0', gdepw_0 )
181            CALL iom_rstput( 0, 0, inum4, 'e3t_0'  , e3t_0   )
182            CALL iom_rstput( 0, 0, inum4, 'e3w_0'  , e3w_0   )
183         ENDIF
184
185#endif
186
187         IF( ln_zco ) THEN
188         !                                                         ! z-coordinate - full steps
189            CALL iom_rstput( 0, 0, inum4, 'gdept_0', gdept_0 )   !    ! depth
190            CALL iom_rstput( 0, 0, inum4, 'gdepw_0', gdepw_0 )
191            CALL iom_rstput( 0, 0, inum4, 'e3t_0'  , e3t_0   )   !    ! scale factors
192            CALL iom_rstput( 0, 0, inum4, 'e3w_0'  , e3w_0   )
193         ENDIF
194         !                                     ! ============================
195         !                                     !        close the files
196         !                                     ! ============================
197         SELECT CASE ( nmsh )
198            CASE ( 1 )               
199               CALL iom_close( inum0 )
200            CASE ( 2 )
201               CALL iom_close( inum1 )
202               CALL iom_close( inum2 )
203            CASE ( 3 )
204               CALL iom_close( inum2 )
205               CALL iom_close( inum3 )
206               CALL iom_close( inum4 )
207         END SELECT
208
209   END SUBROUTINE dom_wri
210
211   !!======================================================================
212END MODULE domwri
Note: See TracBrowser for help on using the repository browser.