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.
nemogcm.F90 in NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/SAO – NEMO

source: NEMO/branches/2020/dev_r12563_ASINTER-06_ABL_improvement/src/SAO/nemogcm.F90 @ 12587

Last change on this file since 12587 was 12377, checked in by acc, 4 years ago

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

  • Property svn:keywords set to Id
File size: 22.1 KB
Line 
1MODULE nemogcm
2   !!======================================================================
3   !!                       ***  MODULE nemogcm   ***
4   !! Ocean system   : NEMO GCM (ocean dynamics, on-line tracers, biochemistry and sea-ice)
5   !!======================================================================
6   !! History :  3.6  ! 2015-12  (A. Ryan) Original code   (from OCE/)
7   !!            4.0  ! 2016-11  (G. Madec, S. Flavoni)  domain configuration / user defined interface
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   nemo_gcm      : solve ocean dynamics, tracer, biogeochemistry and/or sea-ice
12   !!   nemo_init     : initialization of the NEMO system
13   !!   nemo_ctl      : initialisation of the contol print
14   !!   nemo_closefile: close remaining open files
15   !!   nemo_alloc    : dynamical allocation
16   !!----------------------------------------------------------------------
17   USE step_oce       ! module used in the ocean time stepping module (step.F90)
18   USE domain         ! domain initialization   (dom_init & dom_cfg routines)
19   USE istate         ! initial state setting          (istate_init routine)
20   USE phycst         ! physical constant                  (par_cst routine)
21   USE step           ! NEMO time-stepping                 (stp     routine)
22   USE cpl_oasis3     ! OASIS3 coupling
23   USE diaobs         ! Observation diagnostics       (dia_obs_init routine)
24#if defined key_nemocice_decomp
25   USE ice_domain_size, only: nx_global, ny_global
26#endif
27   !           ! Stand Alone Observation operator modules
28   USE sao_data
29   USE sao_intp
30   !
31   USE lib_mpp        ! distributed memory computing
32   USE mppini         ! shared/distributed memory setting (mpp_init routine)
33   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges
34   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
35#if defined key_iomput
36   USE xios           ! xIOserver
37#endif
38
39   IMPLICIT NONE
40   PRIVATE
41
42   PUBLIC   nemo_gcm    ! called by model.F90
43   PUBLIC   nemo_init   ! needed by AGRIF
44   PUBLIC   nemo_alloc  ! needed by TAM
45
46   CHARACTER(lc) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
47
48   !!----------------------------------------------------------------------
49   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
50   !! $Id$
51   !! Software governed by the CeCILL license (see ./LICENSE)
52   !!----------------------------------------------------------------------
53CONTAINS
54
55   SUBROUTINE nemo_gcm
56         !!----------------------------------------------------------------------
57         !!                    ***  SUBROUTINE offline_obs_oper ***
58         !!
59         !! ** Purpose : To use NEMO components to interpolate model fields
60         !!              to observation space.
61         !!
62         !! ** Method : 1. Initialise NEMO
63         !!             2. Initialise offline obs_oper
64         !!             3. Cycle through match ups
65         !!             4. Write results to file
66         !!----------------------------------------------------------------------
67         !
68         CALL nemo_init       ! Initialise NEMO
69         !
70         CALL sao_data_init   ! Initialise Stand Alone Observation operator data
71         !
72         CALL dia_obs_init    ! Initialise obs_operator
73         !
74         CALL sao_interp      ! Interpolate to observation space
75         !
76         CALL dia_obs_wri     ! Pipe to output files
77         !
78         CALL dia_obs_dealloc ! Reset the obs_oper between
79         !
80         IF(lk_mpp)   CALL mppstop  ! Safely stop MPI (end mpp communications)
81         !
82   END SUBROUTINE nemo_gcm
83
84
85   SUBROUTINE nemo_init
86      !!----------------------------------------------------------------------
87      !!                     ***  ROUTINE nemo_init  ***
88      !!
89      !! ** Purpose :   initialization of the NEMO GCM
90      !!----------------------------------------------------------------------
91      INTEGER ::   ios, ilocal_comm   ! local integer
92      !
93      NAMELIST/namctl/ sn_cfctl,  nn_print, nn_ictls, nn_ictle,             &
94         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             &
95         &             ln_timing, ln_diacfl
96      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr
97      !!----------------------------------------------------------------------
98      !
99      cxios_context = 'nemo'
100      !
101      !                             !-------------------------------------------------!
102      !                             !     set communicator & select the local rank    !
103      !                             !  must be done as soon as possible to get narea  !
104      !                             !-------------------------------------------------!
105      !
106#if defined key_iomput
107      IF( Agrif_Root() ) THEN
108         IF( lk_oasis ) THEN
109            CALL cpl_init( "oceanx", ilocal_comm )                               ! nemo local communicator given by oasis
110            CALL xios_initialize( "not used"       , local_comm =ilocal_comm )   ! send nemo communicator to xios
111         ELSE
112            CALL xios_initialize( "for_xios_mpi_id", return_comm=ilocal_comm )   ! nemo local communicator given by xios
113         ENDIF
114      ENDIF
115      CALL mpp_start( ilocal_comm )
116#else
117      IF( lk_oasis ) THEN
118         IF( Agrif_Root() ) THEN
119            CALL cpl_init( "oceanx", ilocal_comm )          ! nemo local communicator given by oasis
120         ENDIF
121         CALL mpp_start( ilocal_comm )
122      ELSE
123         CALL mpp_start( )
124      ENDIF
125#endif
126      !
127      narea = mpprank + 1               ! mpprank: the rank of proc (0 --> mppsize -1 )
128      lwm = (narea == 1)                ! control of output namelists
129      !
130      !                             !---------------------------------------------------------------!
131      !                             ! Open output files, reference and configuration namelist files !
132      !                             !---------------------------------------------------------------!
133      !
134      ! open ocean.output as soon as possible to get all output prints (including errors messages)
135      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. )
136      ! open reference and configuration namelist files
137                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm )
138                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm )
139      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. )
140      ! open /dev/null file to be able to supress output write easily
141                  CALL ctl_opn(     numnul,           '/dev/null', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. )
142      !
143      !                             !--------------------!
144      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp
145      !                             !--------------------!
146      !
147      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 )
148901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' )
149      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 )
150902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' )
151      !
152      ! finalize the definition of namctl variables
153      IF( sn_cfctl%l_allon ) THEN
154         ! Turn on all options.
155         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. )
156         ! Ensure all processors are active
157         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1
158      ELSEIF( sn_cfctl%l_config ) THEN
159         ! Activate finer control of report outputs
160         ! optionally switch off output from selected areas (note this only
161         ! applies to output which does not involve global communications)
162         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. &
163           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    &
164           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. )
165      ELSE
166         ! turn off all options.
167         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. )
168      ENDIF
169      !
170      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print
171      !
172      IF(lwp) THEN                      ! open listing units
173         !
174         IF( .NOT. lwm )   &            ! alreay opened for narea == 1
175            &            CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE., narea )
176         !
177         WRITE(numout,*)
178         WRITE(numout,*) '   CNRS - NERC - Met OFFICE - MERCATOR-ocean - CMCC'
179         WRITE(numout,*) '                       NEMO team'
180         WRITE(numout,*) '            Stand Alone Observation operator'
181         WRITE(numout,*) '                NEMO version 4.0  (2019) '
182         WRITE(numout,*)
183         WRITE(numout,*) "           ._      ._      ._      ._      ._    "
184         WRITE(numout,*) "       _.-._)`\_.-._)`\_.-._)`\_.-._)`\_.-._)`\_ "
185         WRITE(numout,*)
186         WRITE(numout,*) "           o         _,           _,             "
187         WRITE(numout,*) "            o      .' (        .-' /             "
188         WRITE(numout,*) "           o     _/..._'.    .'   /              "
189         WRITE(numout,*) "      (    o .-'`      ` '-./  _.'               "
190         WRITE(numout,*) "       )    ( o)           ;= <_         (       "
191         WRITE(numout,*) "      (      '-.,\\__ __.-;`\   '.        )      "
192         WRITE(numout,*) "       )  )       \) |`\ \)  '.   \      (   (   "
193         WRITE(numout,*) "      (  (           \_/       '-._\      )   )  "
194         WRITE(numout,*) "       )  ) jgs                     `    (   (   "
195         WRITE(numout,*) "     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ "
196         WRITE(numout,*)
197         !
198         WRITE(numout,cform_aaa)                                        ! Flag AAAAAAA
199         !
200      ENDIF
201      !
202      IF(lwm) WRITE( numond, namctl )
203      !
204      !                             !------------------------------------!
205      !                             !  Set global domain size parameters !
206      !                             !------------------------------------!
207      !
208      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 )
209903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' )
210      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 )
211904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )   
212      !
213      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file
214         CALL domain_cfg ( cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio )
215      ELSE                              ! user-defined namelist
216         CALL usr_def_nam( cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio )
217      ENDIF
218      !
219      IF(lwm)   WRITE( numond, namcfg )
220      !
221      !                             !-----------------------------------------!
222      !                             ! mpp parameters and domain decomposition !
223      !                             !-----------------------------------------!
224      CALL mpp_init
225
226      ! Now we know the dimensions of the grid and numout has been set: we can allocate arrays
227      CALL nemo_alloc()
228
229      !                             !-------------------------------!
230      !                             !  NEMO general initialization  !
231      !                             !-------------------------------!
232
233      CALL nemo_ctl                          ! Control prints
234      !
235      !                                         ! General initialization
236      IF( ln_timing    )   CALL timing_init     ! timing
237      IF( ln_timing    )   CALL timing_start( 'nemo_init')
238      !
239                           CALL phy_cst            ! Physical constants
240                           CALL eos_init           ! Equation of state
241                           CALL dom_init( Nbb, Nnn, Naa, 'SAO')    ! Domain
242
243
244      IF( sn_cfctl%l_prtctl )   &
245         &                 CALL prt_ctl_init       ! Print control
246
247                           CALL istate_init        ! ocean initial state (Dynamics and tracers)
248   END SUBROUTINE nemo_init
249
250
251   SUBROUTINE nemo_ctl
252      !!----------------------------------------------------------------------
253      !!                     ***  ROUTINE nemo_ctl  ***
254      !!
255      !! ** Purpose :   control print setting
256      !!
257      !! ** Method  : - print namctl and namcfg information and check some consistencies
258      !!----------------------------------------------------------------------
259      !
260      IF(lwp) THEN                  ! control print
261         WRITE(numout,*)
262         WRITE(numout,*) 'nemo_ctl: Control prints'
263         WRITE(numout,*) '~~~~~~~~'
264         WRITE(numout,*) '   Namelist namctl'
265         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk
266         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon
267         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config
268         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat
269         WRITE(numout,*) '                              sn_cfctl%l_trcstat = ', sn_cfctl%l_trcstat
270         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout
271         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout
272         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl
273         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc
274         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout
275         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin 
276         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax 
277         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr 
278         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr 
279         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print
280         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls
281         WRITE(numout,*) '      End i indice for SUM control    nn_ictle   = ', nn_ictle
282         WRITE(numout,*) '      Start j indice for SUM control  nn_jctls   = ', nn_jctls
283         WRITE(numout,*) '      End j indice for SUM control    nn_jctle   = ', nn_jctle
284         WRITE(numout,*) '      number of proc. following i     nn_isplt   = ', nn_isplt
285         WRITE(numout,*) '      number of proc. following j     nn_jsplt   = ', nn_jsplt
286         WRITE(numout,*) '      timing by routine               ln_timing  = ', ln_timing
287         WRITE(numout,*) '      CFL diagnostics                 ln_diacfl  = ', ln_diacfl
288      ENDIF
289      !
290      nprint    = nn_print          ! convert DOCTOR namelist names into OLD names
291      nictls    = nn_ictls
292      nictle    = nn_ictle
293      njctls    = nn_jctls
294      njctle    = nn_jctle
295      isplt     = nn_isplt
296      jsplt     = nn_jsplt
297
298      IF(lwp) THEN                  ! control print
299         WRITE(numout,*)
300         WRITE(numout,*) '   Namelist namcfg'
301         WRITE(numout,*) '      read domain configuration file                ln_read_cfg      = ', ln_read_cfg
302         WRITE(numout,*) '         filename to be read                           cn_domcfg     = ', TRIM(cn_domcfg)
303         WRITE(numout,*) '         keep closed seas in the domain (if exist)     ln_closea     = ', ln_closea
304         WRITE(numout,*) '      create a configuration definition file        ln_write_cfg     = ', ln_write_cfg
305         WRITE(numout,*) '         filename to be written                        cn_domcfg_out = ', TRIM(cn_domcfg_out)
306         WRITE(numout,*) '      use file attribute if exists as i/p j-start   ln_use_jattr     = ', ln_use_jattr
307      ENDIF
308      IF( .NOT.ln_read_cfg )   ln_closea = .false.   ! dealing possible only with a domcfg file
309      !
310      !                             ! Parameter control
311      !
312      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints
313         IF( lk_mpp .AND. jpnij > 1 ) THEN
314            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain
315         ELSE
316            IF( isplt == 1 .AND. jsplt == 1  ) THEN
317               CALL ctl_warn( ' - isplt & jsplt are equal to 1',   &
318                  &           ' - the print control will be done over the whole domain' )
319            ENDIF
320            ijsplt = isplt * jsplt            ! total number of processors ijsplt
321         ENDIF
322         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
323         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
324         !
325         !                              ! indices used for the SUM control
326         IF( nictls+nictle+njctls+njctle == 0 )   THEN    ! print control done over the default area
327            lsp_area = .FALSE.
328         ELSE                                             ! print control done over a specific  area
329            lsp_area = .TRUE.
330            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
331               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
332               nictls = 1
333            ENDIF
334            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
335               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
336               nictle = jpiglo
337            ENDIF
338            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
339               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
340               njctls = 1
341            ENDIF
342            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
343               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
344               njctle = jpjglo
345            ENDIF
346         ENDIF
347      ENDIF
348      !
349      IF( 1._wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows f2003 standard.',  &
350         &                                                'Compile with key_nosignedzero enabled:',   &
351         &                                                '--> add -Dkey_nosignedzero to the definition of %CPP in your arch file' )
352      !
353   END SUBROUTINE nemo_ctl
354
355
356   SUBROUTINE nemo_closefile
357      !!----------------------------------------------------------------------
358      !!                     ***  ROUTINE nemo_closefile  ***
359      !!
360      !! ** Purpose :   Close the files
361      !!----------------------------------------------------------------------
362      !
363      IF( lk_mpp )   CALL mppsync
364      !
365      CALL iom_close                                 ! close all input/output files managed by iom_*
366      !
367      IF( numstp          /= -1 )   CLOSE( numstp          )   ! time-step file
368      IF( numrun          /= -1 )   CLOSE( numrun          )   ! run statistics file
369      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist
370      IF( lwm.AND.numoni  /= -1 )   CLOSE( numoni          )   ! ice output namelist
371      IF( numevo_ice      /= -1 )   CLOSE( numevo_ice      )   ! ice variables (temp. evolution)
372      IF( numout          /=  6 )   CLOSE( numout          )   ! standard model output file
373      IF( numdct_vol      /= -1 )   CLOSE( numdct_vol      )   ! volume transports
374      IF( numdct_heat     /= -1 )   CLOSE( numdct_heat     )   ! heat transports
375      IF( numdct_salt     /= -1 )   CLOSE( numdct_salt     )   ! salt transports
376      !
377      numout = 6                                     ! redefine numout in case it is used after this point...
378      !
379   END SUBROUTINE nemo_closefile
380
381
382   SUBROUTINE nemo_alloc
383      !!----------------------------------------------------------------------
384      !!                     ***  ROUTINE nemo_alloc  ***
385      !!
386      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules
387      !!
388      !! ** Method  :
389      !!----------------------------------------------------------------------
390      USE diawri    , ONLY: dia_wri_alloc
391      USE dom_oce   , ONLY: dom_oce_alloc
392      !
393      INTEGER :: ierr
394      !!----------------------------------------------------------------------
395      !
396      ierr =        oce_alloc       ()          ! ocean
397      ierr = ierr + dia_wri_alloc   ()
398      ierr = ierr + dom_oce_alloc   ()          ! ocean domain
399      !
400      CALL mpp_sum( 'nemogcm', ierr )
401      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'nemo_alloc : unable to allocate standard ocean arrays' )
402      !
403   END SUBROUTINE nemo_alloc
404
405   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto, for_all )
406      !!----------------------------------------------------------------------
407      !!                     ***  ROUTINE nemo_set_cfctl  ***
408      !!
409      !! ** Purpose :   Set elements of the output control structure to setto.
410      !!                for_all should be .false. unless all areas are to be
411      !!                treated identically.
412      !!
413      !! ** Method  :   Note this routine can be used to switch on/off some
414      !!                types of output for selected areas but any output types
415      !!                that involve global communications (e.g. mpp_max, glob_sum)
416      !!                should be protected from selective switching by the
417      !!                for_all argument
418      !!----------------------------------------------------------------------
419      LOGICAL :: setto, for_all
420      TYPE(sn_ctl) :: sn_cfctl
421      !!----------------------------------------------------------------------
422      IF( for_all ) THEN
423         sn_cfctl%l_runstat = setto
424         sn_cfctl%l_trcstat = setto
425      ENDIF
426      sn_cfctl%l_oceout  = setto
427      sn_cfctl%l_layout  = setto
428      sn_cfctl%l_prtctl  = setto
429      sn_cfctl%l_prttrc  = setto
430      sn_cfctl%l_oasout  = setto
431   END SUBROUTINE nemo_set_cfctl
432
433   !!======================================================================
434END MODULE nemogcm
435
Note: See TracBrowser for help on using the repository browser.