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/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OFF_SRC – NEMO

source: branches/2014/dev_r4650_UKMO7_STARTHOUR/NEMOGCM/NEMO/OFF_SRC/domain.F90 @ 5075

Last change on this file since 5075 was 5075, checked in by timgraham, 9 years ago

Upgraded branch to current head of trunk (r5072) so it can be used with the trunk

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