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.
domain.F90 in branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OFF_SRC – NEMO

source: branches/2013/dev_MERGE_2013/NEMOGCM/NEMO/OFF_SRC/domain.F90 @ 4322

Last change on this file since 4322 was 4322, checked in by cetlod, 10 years ago

v3.6_alpha : defines the surface cells in offline, see ticket #1191

  • Property svn:keywords set to Id
File size: 20.9 KB
RevLine 
[2053]1MODULE domain
2   !!==============================================================================
3   !!                       ***  MODULE domain   ***
4   !! Ocean initialization : domain initialization
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   dom_init       : initialize the space and time domain
9   !!   dom_nam        : read and contral domain namelists
10   !!   dom_ctl        : control print for the ocean domain
11   !!----------------------------------------------------------------------
12   !! * Modules used
13   USE oce             !
14   USE dom_oce         ! ocean space and time domain
15   USE phycst          ! physical constants
16   USE in_out_manager  ! I/O manager
17   USE lib_mpp         ! distributed memory computing library
18
19   USE domstp          ! domain: set the time-step
20   USE domrea          ! domain: write the meshmask file
21   USE dommsk          ! domain : mask
22
23   IMPLICIT NONE
24   PRIVATE
25
26   !! * Routine accessibility
27   PUBLIC dom_init       ! called by opa.F90
28
29   !! * Substitutions
30#  include "domzgr_substitute.h90"
31   !!----------------------------------------------------------------------
[2287]32   !! NEMO/OFF 3.3 , NEMO Consortium (2010)
33   !! $Id$
34   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[2053]35   !!----------------------------------------------------------------------
36
37CONTAINS
38
39   SUBROUTINE dom_init
40      !!----------------------------------------------------------------------
41      !!                  ***  ROUTINE dom_init  ***
42      !!                   
43      !! ** Purpose :   Domain initialization. Call the routines that are
44      !!      required to create the arrays which define the space and time
45      !!      domain of the ocean model.
46      !!
47      !! ** Method  :
48      !!      - dom_stp: defined the model time step
49      !!      - dom_rea: read the meshmask file if nmsh=1
50      !!
51      !! History :
52      !!        !  90-10  (C. Levy - G. Madec)  Original code
53      !!        !  91-11  (G. Madec)
54      !!        !  92-01  (M. Imbard) insert time step initialization
55      !!        !  96-06  (G. Madec) generalized vertical coordinate
56      !!        !  97-02  (G. Madec) creation of domwri.F
57      !!        !  01-05  (E.Durand - G. Madec) insert closed sea
58      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
59      !!----------------------------------------------------------------------
60      !! * Local declarations
61      INTEGER ::   iconf = 0         ! temporary integers
62      !!----------------------------------------------------------------------
63
64      IF(lwp) THEN
65         WRITE(numout,*)
66         WRITE(numout,*) 'dom_init : domain initialization'
67         WRITE(numout,*) '~~~~~~~~'
68      ENDIF
69
70      CALL dom_nam      ! read namelist ( namrun, namdom, namcla )
71      CALL dom_zgr      ! Vertical mesh and bathymetry option
72      CALL dom_rea      ! Create a domain file
[4322]73
74     !
75      ! - ML - Used in dom_vvl_sf_nxt and lateral diffusion routines
76      !        but could be usefull in many other routines
77      e12t    (:,:) = e1t(:,:) * e2t(:,:)
78      e1e2t   (:,:) = e1t(:,:) * e2t(:,:)
79      e12u    (:,:) = e1u(:,:) * e2u(:,:)
80      e12v    (:,:) = e1v(:,:) * e2v(:,:)
81      e12f    (:,:) = e1f(:,:) * e2f(:,:)
82      r1_e12t (:,:) = 1._wp    / e12t(:,:)
83      r1_e12u (:,:) = 1._wp    / e12u(:,:)
84      r1_e12v (:,:) = 1._wp    / e12v(:,:)
85      r1_e12f (:,:) = 1._wp    / e12f(:,:)
86      re2u_e1u(:,:) = e2u(:,:) / e1u(:,:)
87      re1v_e2v(:,:) = e1v(:,:) / e2v(:,:)
88      !
89      hu(:,:) = 0._wp                          ! Ocean depth at U- and V-points
90      hv(:,:) = 0._wp
91      DO jk = 1, jpk
92         hu(:,:) = hu(:,:) + fse3u_n(:,:,jk) * umask(:,:,jk)
93         hv(:,:) = hv(:,:) + fse3v_n(:,:,jk) * vmask(:,:,jk)
94      END DO
95      !                                        ! Inverse of the local depth
96      hur(:,:) = 1._wp / ( hu(:,:) + 1._wp - umask(:,:,1) ) * umask(:,:,1)
97      hvr(:,:) = 1._wp / ( hv(:,:) + 1._wp - vmask(:,:,1) ) * vmask(:,:,1)
98
[2053]99      CALL dom_stp      ! Time step
100      CALL dom_msk      ! Masks
101      CALL dom_ctl      ! Domain control
102
103   END SUBROUTINE dom_init
104
105   SUBROUTINE dom_nam
106      !!----------------------------------------------------------------------
107      !!                     ***  ROUTINE dom_nam  ***
108      !!                   
109      !! ** Purpose :   read domaine namelists and print the variables.
110      !!
111      !! ** input   : - namrun namelist
112      !!              - namdom namelist
113      !!              - namcla namelist
114      !!----------------------------------------------------------------------
115      USE ioipsl
[4147]116      INTEGER  ::   ios                 ! Local integer output status for namelist read
[2053]117      NAMELIST/namrun/ nn_no   , cn_exp    , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl,   &
118         &             nn_it000, nn_itend  , nn_date0    , nn_leapy     , nn_istate , nn_stock ,   &
119         &             nn_write, ln_dimgnnn, ln_mskland  , ln_clobber   , nn_chunksz
[4248]120      NAMELIST/namdom/ nn_bathy , rn_bathy, rn_e3zps_min, rn_e3zps_rat, nn_msh    , rn_hmin,   &
[4147]121         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,            &
[4159]122         &             rn_rdtmax, rn_rdth     , nn_baro     , nn_closea , ln_crs, &
[4147]123         &             jphgr_msh, &
124         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, &
125         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, &
126         &             ppa2, ppkth2, ppacr2
[2053]127      NAMELIST/namcla/ nn_cla
[2574]128#if defined key_netcdf4
129      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip
130#endif
[2053]131      !!----------------------------------------------------------------------
132
[4147]133      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run
134      READ  ( numnam_ref, namrun, IOSTAT = ios, ERR = 901)
135901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in reference namelist', lwp )
136
137      REWIND( numnam_cfg )              ! Namelist namrun in configuration namelist : Parameters of the run
138      READ  ( numnam_cfg, namrun, IOSTAT = ios, ERR = 902 )
139902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namrun in configuration namelist', lwp )
140      WRITE ( numond, namrun )
[2053]141      !
142      IF(lwp) THEN                  ! control print
143         WRITE(numout,*)
144         WRITE(numout,*) 'dom_nam  : domain initialization through namelist read'
145         WRITE(numout,*) '~~~~~~~ '
146         WRITE(numout,*) '   Namelist namrun' 
147         WRITE(numout,*) '      job number                      nn_no      = ', nn_no
148         WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp
149         WRITE(numout,*) '      restart logical                 ln_rstart  = ', ln_rstart
150         WRITE(numout,*) '      control of time step            nn_rstctl  = ', nn_rstctl
151         WRITE(numout,*) '      number of the first time step   nn_it000   = ', nn_it000
152         WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend
153         WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0
154         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy
155         WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate
156         WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock
157         WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write
158         WRITE(numout,*) '      multi file dimgout              ln_dimgnnn = ', ln_dimgnnn
159         WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland
160         WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber
161         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz
162      ENDIF
163      no = nn_no                    ! conversion DOCTOR names into model names (this should disappear soon)
164      cexper = cn_exp
165      nrstdt = nn_rstctl
166      nit000 = nn_it000
167      nitend = nn_itend
168      ndate0 = nn_date0
169      nleapy = nn_leapy
170      ninist = nn_istate
171      nstock = nn_stock
172      nwrite = nn_write
173
174
175      !                             ! control of output frequency
176      IF ( nstock == 0 .OR. nstock > nitend ) THEN
177         WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend
178         CALL ctl_warn( ctmp1 )
179         nstock = nitend
180      ENDIF
181      IF ( nwrite == 0 ) THEN
182         WRITE(ctmp1,*) 'nwrite = ', nwrite, ' it is forced to ', nitend
183         CALL ctl_warn( ctmp1 )
184         nwrite = nitend
185      ENDIF
186
187      ! parameters correspondting to nit000 - 1 (as we start the step loop with a call to day)
188      ndastp = ndate0 - 1        ! ndate0 read in the namelist in dom_nam, we assume that we start run at 00:00
189      adatrj = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday
190
191#if defined key_agrif
192      IF( Agrif_Root() ) THEN
193#endif
194      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL
195      CASE (  1 ) 
196         CALL ioconf_calendar('gregorian')
197         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "gregorian", i.e. leap year'
198      CASE (  0 )
199         CALL ioconf_calendar('noleap')
200         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "noleap", i.e. no leap year'
201      CASE ( 30 )
202         CALL ioconf_calendar('360d')
203         IF(lwp) WRITE(numout,*) '   The IOIPSL calendar is "360d", i.e. 360 days in a year'
204      END SELECT
205#if defined key_agrif
206      ENDIF
207#endif
208
[4147]209      REWIND( numnam_ref )              ! Namelist namdom in reference namelist : space & time domain (bathymetry, mesh, timestep)
210      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 903)
211903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in reference namelist', lwp )
[2053]212
[4147]213      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep)
214      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 )
215904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp )
216      WRITE ( numond, namdom )
217
[2053]218      IF(lwp) THEN
219         WRITE(numout,*) 
220         WRITE(numout,*) '   Namelist namdom : space & time domain'
221         WRITE(numout,*) '      flag read/compute bathymetry      nn_bathy     = ', nn_bathy
[4248]222         WRITE(numout,*) '      Depth (if =0 bathy=jpkm1)         rn_bathy     = ', rn_bathy
[2574]223         WRITE(numout,*) '      min depth of the ocean    (>0) or    rn_hmin   = ', rn_hmin
[2053]224         WRITE(numout,*) '      minimum thickness of partial      rn_e3zps_min = ', rn_e3zps_min, ' (m)'
225         WRITE(numout,*) '         step level                     rn_e3zps_rat = ', rn_e3zps_rat
226         WRITE(numout,*) '      create mesh/mask file(s)          nn_msh       = ', nn_msh
227         WRITE(numout,*) '           = 0   no file created                 '
228         WRITE(numout,*) '           = 1   mesh_mask                       '
229         WRITE(numout,*) '           = 2   mesh and mask                   '
230         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask      '
231         WRITE(numout,*) '      ocean time step                      rn_rdt    = ', rn_rdt
232         WRITE(numout,*) '      asselin time filter parameter        rn_atfp   = ', rn_atfp
233         WRITE(numout,*) '      time-splitting: nb of sub time-step  nn_baro   = ', nn_baro
234         WRITE(numout,*) '      acceleration of converge             nn_acc    = ', nn_acc
235         WRITE(numout,*) '        nn_acc=1: surface tracer rdt       rn_rdtmin = ', rn_rdtmin
236         WRITE(numout,*) '                  bottom  tracer rdt       rdtmax    = ', rn_rdtmax
237         WRITE(numout,*) '                  depth of transition      rn_rdth   = ', rn_rdth
238         WRITE(numout,*) '      suppression of closed seas (=0)      nn_closea = ', nn_closea
[4147]239         WRITE(numout,*) '      type of horizontal mesh jphgr_msh           = ', jphgr_msh
240         WRITE(numout,*) '      longitude of first raw and column T-point ppglam0 = ', ppglam0
241         WRITE(numout,*) '      latitude  of first raw and column T-point ppgphi0 = ', ppgphi0
242         WRITE(numout,*) '      zonal      grid-spacing (degrees) ppe1_deg        = ', ppe1_deg
243         WRITE(numout,*) '      meridional grid-spacing (degrees) ppe2_deg        = ', ppe2_deg
244         WRITE(numout,*) '      zonal      grid-spacing (degrees) ppe1_m          = ', ppe1_m
245         WRITE(numout,*) '      meridional grid-spacing (degrees) ppe2_m          = ', ppe2_m
246         WRITE(numout,*) '      ORCA r4, r2 and r05 coefficients  ppsur           = ', ppsur
247         WRITE(numout,*) '                                        ppa0            = ', ppa0
248         WRITE(numout,*) '                                        ppa1            = ', ppa1
249         WRITE(numout,*) '                                        ppkth           = ', ppkth
250         WRITE(numout,*) '                                        ppacr           = ', ppacr
251         WRITE(numout,*) '      Minimum vertical spacing ppdzmin                  = ', ppdzmin
252         WRITE(numout,*) '      Maximum depth pphmax                              = ', pphmax
253         WRITE(numout,*) '      Use double tanf function for vertical coordinates ldbletanh = ', ldbletanh
254         WRITE(numout,*) '      Double tanh function parameters ppa2              = ', ppa2
255         WRITE(numout,*) '                                      ppkth2            = ', ppkth2
256         WRITE(numout,*) '                                      ppacr2            = ', ppacr2
[2053]257      ENDIF
258
259      ntopo     = nn_bathy          ! conversion DOCTOR names into model names (this should disappear soon)
260      e3zps_min = rn_e3zps_min
261      e3zps_rat = rn_e3zps_rat
262      nmsh      = nn_msh
263      nacc      = nn_acc
264      atfp      = rn_atfp
265      rdt       = rn_rdt
266      rdtmin    = rn_rdtmin
267      rdtmax    = rn_rdtmin
268      rdth      = rn_rdth
269
[4147]270      REWIND( numnam_ref )              ! Namelist namcla in reference namelist : Cross land advection
271      READ  ( numnam_ref, namcla, IOSTAT = ios, ERR = 905)
272905   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in reference namelist', lwp )
273
274      REWIND( numnam_cfg )              ! Namelist namcla in configuration namelist : Cross land advection
275      READ  ( numnam_cfg, namcla, IOSTAT = ios, ERR = 906 )
276906   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcla in configuration namelist', lwp )
277      WRITE( numond, namcla )
278
[2053]279      IF(lwp) THEN
280         WRITE(numout,*)
281         WRITE(numout,*) '   Namelist namcla'
282         WRITE(numout,*) '      cross land advection                 nn_cla    = ', nn_cla
283      ENDIF
284
[2574]285#if defined key_netcdf4
286      !                             ! NetCDF 4 case   ("key_netcdf4" defined)
[4147]287      REWIND( numnam_ref )              ! Namelist namnc4 in reference namelist : NETCDF
288      READ  ( numnam_ref, namnc4, IOSTAT = ios, ERR = 907)
289907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in reference namelist', lwp )
290
291      REWIND( numnam_cfg )              ! Namelist namnc4 in configuration namelist : NETCDF
292      READ  ( numnam_cfg, namnc4, IOSTAT = ios, ERR = 908 )
293908   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in configuration namelist', lwp )
294      WRITE( numond, namnc4 )
[2574]295      IF(lwp) THEN                        ! control print
296         WRITE(numout,*)
297         WRITE(numout,*) '   Namelist namnc4 - Netcdf4 chunking parameters'
298         WRITE(numout,*) '      number of chunks in i-dimension      nn_nchunks_i   = ', nn_nchunks_i
299         WRITE(numout,*) '      number of chunks in j-dimension      nn_nchunks_j   = ', nn_nchunks_j
300         WRITE(numout,*) '      number of chunks in k-dimension      nn_nchunks_k   = ', nn_nchunks_k
301         WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression ln_nc4zip = ', ln_nc4zip
302      ENDIF
303
304      ! Put the netcdf4 settings into a simple structure (snc4set, defined in in_out_manager module)
305      ! Note the chunk size in the unlimited (time) dimension will be fixed at 1
306      snc4set%ni   = nn_nchunks_i
307      snc4set%nj   = nn_nchunks_j
308      snc4set%nk   = nn_nchunks_k
309      snc4set%luse = ln_nc4zip
310#else
311      snc4set%luse = .FALSE.        ! No NetCDF 4 case
312#endif
[2053]313      !
314   END SUBROUTINE dom_nam
315
316   SUBROUTINE dom_zgr
317      !!----------------------------------------------------------------------
318      !!                ***  ROUTINE dom_zgr  ***
319      !!                   
320      !! ** Purpose :  set the depth of model levels and the resulting
321      !!      vertical scale factors.
322      !!
[4292]323      !! ** Method  : - reference 1D vertical coordinate (gdep._1d, e3._1d)
[2053]324      !!              - read/set ocean depth and ocean levels (bathy, mbathy)
325      !!              - vertical coordinate (gdep., e3.) depending on the
326      !!                coordinate chosen :
[2240]327      !!                   ln_zco=T   z-coordinate 
[2053]328      !!                   ln_zps=T   z-coordinate with partial steps
329      !!                   ln_zco=T   s-coordinate
330      !!
331      !! ** Action  :   define gdep., e3., mbathy and bathy
332      !!----------------------------------------------------------------------
333      INTEGER ::   ioptio = 0   ! temporary integer
[4147]334      INTEGER ::   ios
[2053]335      !!
336      NAMELIST/namzgr/ ln_zco, ln_zps, ln_sco
337      !!----------------------------------------------------------------------
338
[4147]339      REWIND( numnam_ref )              ! Namelist namzgr in reference namelist : Vertical coordinate
340      READ  ( numnam_ref, namzgr, IOSTAT = ios, ERR = 901 )
341901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in reference namelist', lwp )
[2053]342
[4147]343      REWIND( numnam_cfg )              ! Namelist namzgr in configuration namelist : Vertical coordinate
344      READ  ( numnam_cfg, namzgr, IOSTAT = ios, ERR = 902 )
345902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namzgr in configuration namelist', lwp )
346      WRITE ( numond, namzgr )
347
[2053]348      IF(lwp) THEN                     ! Control print
349         WRITE(numout,*)
350         WRITE(numout,*) 'dom_zgr : vertical coordinate'
351         WRITE(numout,*) '~~~~~~~'
352         WRITE(numout,*) '          Namelist namzgr : set vertical coordinate'
353         WRITE(numout,*) '             z-coordinate - full steps      ln_zco = ', ln_zco
354         WRITE(numout,*) '             z-coordinate - partial steps   ln_zps = ', ln_zps
355         WRITE(numout,*) '             s- or hybrid z-s-coordinate    ln_sco = ', ln_sco
356      ENDIF
357
358      ioptio = 0                       ! Check Vertical coordinate options
359      IF( ln_zco ) ioptio = ioptio + 1
360      IF( ln_zps ) ioptio = ioptio + 1
361      IF( ln_sco ) ioptio = ioptio + 1
362      IF ( ioptio /= 1 )   CALL ctl_stop( ' none or several vertical coordinate options used' )
363
364   END SUBROUTINE dom_zgr
365
366   SUBROUTINE dom_ctl
367      !!----------------------------------------------------------------------
368      !!                     ***  ROUTINE dom_ctl  ***
369      !!
370      !! ** Purpose :   Domain control.
371      !!
372      !! ** Method  :   compute and print extrema of masked scale factors
373      !!
374      !! History :
375      !!   8.5  !  02-08  (G. Madec)    Original code
376      !!----------------------------------------------------------------------
377      !! * Local declarations
378      INTEGER ::   iimi1, ijmi1, iimi2, ijmi2, iima1, ijma1, iima2, ijma2
379      INTEGER, DIMENSION(2) ::   iloc      !
380      REAL(wp) ::   ze1min, ze1max, ze2min, ze2max
381      !!----------------------------------------------------------------------
382
383      ! Extrema of the scale factors
384
385      IF(lwp)WRITE(numout,*)
386      IF(lwp)WRITE(numout,*) 'dom_ctl : extrema of the masked scale factors'
387      IF(lwp)WRITE(numout,*) '~~~~~~~'
388
389      IF (lk_mpp) THEN
390         CALL mpp_minloc( e1t(:,:), tmask(:,:,1), ze1min, iimi1,ijmi1 )
391         CALL mpp_minloc( e2t(:,:), tmask(:,:,1), ze2min, iimi2,ijmi2 )
392         CALL mpp_maxloc( e1t(:,:), tmask(:,:,1), ze1max, iima1,ijma1 )
393         CALL mpp_maxloc( e2t(:,:), tmask(:,:,1), ze2max, iima2,ijma2 )
394      ELSE
395         ze1min = MINVAL( e1t(:,:), mask = tmask(:,:,1) == 1.e0 )   
396         ze2min = MINVAL( e2t(:,:), mask = tmask(:,:,1) == 1.e0 )   
397         ze1max = MAXVAL( e1t(:,:), mask = tmask(:,:,1) == 1.e0 )   
398         ze2max = MAXVAL( e2t(:,:), mask = tmask(:,:,1) == 1.e0 )   
399
400         iloc  = MINLOC( e1t(:,:), mask = tmask(:,:,1) == 1.e0 )
401         iimi1 = iloc(1) + nimpp - 1
402         ijmi1 = iloc(2) + njmpp - 1
403         iloc  = MINLOC( e2t(:,:), mask = tmask(:,:,1) == 1.e0 )
404         iimi2 = iloc(1) + nimpp - 1
405         ijmi2 = iloc(2) + njmpp - 1
406         iloc  = MAXLOC( e1t(:,:), mask = tmask(:,:,1) == 1.e0 )
407         iima1 = iloc(1) + nimpp - 1
408         ijma1 = iloc(2) + njmpp - 1
409         iloc  = MAXLOC( e2t(:,:), mask = tmask(:,:,1) == 1.e0 )
410         iima2 = iloc(1) + nimpp - 1
411         ijma2 = iloc(2) + njmpp - 1
412      ENDIF
413
414      IF(lwp) THEN
415         WRITE(numout,"(14x,'e1t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1max, iima1, ijma1
416         WRITE(numout,"(14x,'e1t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1min, iimi1, ijmi1
417         WRITE(numout,"(14x,'e2t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2max, iima2, ijma2
418         WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2
419      ENDIF
420
421   END SUBROUTINE dom_ctl
422
423   !!======================================================================
424END MODULE domain
Note: See TracBrowser for help on using the repository browser.