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 branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90 @ 4479

Last change on this file since 4479 was 4479, checked in by trackstand2, 10 years ago

Remove jpkf as un-needed now we just reset jpk instead

  • Property svn:keywords set to Id
File size: 40.9 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 :  OPA  ! 1990-10  (C. Levy, G. Madec)  Original code
7   !!            7.0  ! 1991-11  (M. Imbard, C. Levy, G. Madec)
8   !!            7.1  ! 1993-03  (M. Imbard, C. Levy, G. Madec, O. Marti, M. Guyon, A. Lazar,
9   !!                             P. Delecluse, C. Perigaud, G. Caniaux, B. Colot, C. Maes) release 7.1
10   !!             -   ! 1992-06  (L.Terray)  coupling implementation
11   !!             -   ! 1993-11  (M.A. Filiberti) IGLOO sea-ice
12   !!            8.0  ! 1996-03  (M. Imbard, C. Levy, G. Madec, O. Marti, M. Guyon, A. Lazar,
13   !!                             P. Delecluse, L.Terray, M.A. Filiberti, J. Vialar, A.M. Treguier, M. Levy) release 8.0
14   !!            8.1  ! 1997-06  (M. Imbard, G. Madec)
15   !!            8.2  ! 1999-11  (M. Imbard, H. Goosse)  LIM sea-ice model
16   !!                 ! 1999-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
17   !!                 ! 2000-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
18   !!   NEMO     1.0  ! 2002-08  (G. Madec)  F90: Free form and modules
19   !!             -   ! 2004-06  (R. Redler, NEC CCRLE, Germany) add OASIS[3/4] coupled interfaces
20   !!             -   ! 2004-08  (C. Talandier) New trends organization
21   !!             -   ! 2005-06  (C. Ethe) Add the 1D configuration possibility
22   !!             -   ! 2005-11  (V. Garnier) Surface pressure gradient organization
23   !!             -   ! 2006-03  (L. Debreu, C. Mazauric)  Agrif implementation
24   !!             -   ! 2006-04  (G. Madec, R. Benshila)  Step reorganization
25   !!             -   ! 2007-07  (J. Chanut, A. Sellar) Unstructured open boundaries (BDY)
26   !!            3.2  ! 2009-08  (S. Masson)  open/write in the listing file in mpp
27   !!            3.3  ! 2010-05  (K. Mogensen, A. Weaver, M. Martin, D. Lea) Assimilation interface
28   !!             -   ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase
29   !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation
30   !!----------------------------------------------------------------------
31
32   !!----------------------------------------------------------------------
33   !!   nemo_gcm       : solve ocean dynamics, tracer, biogeochemistry and/or sea-ice
34   !!   nemo_init      : initialization of the NEMO system
35   !!   nemo_ctl       : initialisation of the contol print
36   !!   nemo_closefile : close remaining open files
37   !!   nemo_alloc     : dynamical allocation
38   !!   nemo_partition : calculate MPP domain decomposition
39   !!   sqfact         : calculate factors of the no. of MPI processes
40   !!----------------------------------------------------------------------
41   USE step_oce        ! module used in the ocean time stepping module
42   USE sbc_oce         ! surface boundary condition: ocean
43   USE cla             ! cross land advection               (tra_cla routine)
44   USE domcfg          ! domain configuration               (dom_cfg routine)
45   USE mppini          ! shared/distributed memory setting (mpp_init routine)
46   USE domain          ! domain initialization             (dom_init routine)
47   USE obcini          ! open boundary cond. initialization (obc_ini routine)
48   USE bdyini          ! unstructured open boundary cond. initialization (bdy_init routine)
49   USE istate          ! initial state setting          (istate_init routine)
50   USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine)
51   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine)
52   USE zdfini          ! vertical physics setting          (zdf_init routine)
53   USE phycst          ! physical constant                  (par_cst routine)
54   USE trdmod          ! momentum/tracers trends       (trd_mod_init routine)
55   USE asminc          ! assimilation increments       (asm_inc_init routine)
56   USE asmtrj          ! writing out state trajectory
57   USE sshwzv          ! vertical velocity used in asm
58   USE diaptr          ! poleward transports           (dia_ptr_init routine)
59   USE diaobs          ! Observation diagnostics       (dia_obs_init routine)
60   USE step            ! NEMO time-stepping                 (stp     routine)
61#if defined key_oasis3
62   USE cpl_oasis3      ! OASIS3 coupling
63#elif defined key_oasis4
64   USE cpl_oasis4      ! OASIS4 coupling (not working)
65#endif
66   USE c1d             ! 1D configuration
67   USE step_c1d        ! Time stepping loop for the 1D configuration
68#if defined key_top
69   USE trcini          ! passive tracer initialisation
70#endif
71   USE lib_mpp         ! distributed memory computing
72#if defined key_iomput
73   USE mod_ioclient
74#endif
75   USE partition_mod   ! irregular domain partitioning
76   USE timing, ONLY: timing_init, timing_finalize, timing_disable, timing_enable
77
78#define ARPDEBUG
79
80   IMPLICIT NONE
81   PRIVATE
82
83   PUBLIC   nemo_gcm    ! called by model.F90
84   PUBLIC   nemo_init   ! needed by AGRIF
85
86   CHARACTER(lc) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
87
88   !!----------------------------------------------------------------------
89   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
90   !! $Id$
91   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
92   !!----------------------------------------------------------------------
93CONTAINS
94
95   SUBROUTINE nemo_gcm
96      !!----------------------------------------------------------------------
97      !!                     ***  ROUTINE nemo_gcm  ***
98      !!
99      !! ** Purpose :   NEMO solves the primitive equations on an orthogonal
100      !!              curvilinear mesh on the sphere.
101      !!
102      !! ** Method  : - model general initialization
103      !!              - launch the time-stepping (stp routine)
104      !!              - finalize the run by closing files and communications
105      !!
106      !! References : Madec, Delecluse, Imbard, and Levy, 1997:  internal report, IPSL.
107      !!              Madec, 2008, internal report, IPSL.
108      !!----------------------------------------------------------------------
109      INTEGER ::   istp       ! time step index
110      !!----------------------------------------------------------------------
111      !
112#if defined key_agrif
113      CALL Agrif_Init_Grids()      ! AGRIF: set the meshes
114#endif
115
116      !                            !-----------------------!
117      CALL nemo_init               !==  Initialisations  ==!
118      !                            !-----------------------!
119#if defined key_agrif
120      CALL Agrif_Declare_Var       ! AGRIF: set the meshes
121# if defined key_top
122      CALL Agrif_Declare_Var_Top   ! AGRIF: set the meshes
123# endif
124#endif
125      ! check that all process are still there... If some process have an error,
126      ! they will never enter in step and other processes will wait until the end of the cpu time!
127      IF( lk_mpp )   CALL mpp_max( nstop )
128
129      IF(lwp) WRITE(numout,cform_aaa)   ! Flag AAAAAAA
130
131      CALL timing_enable()
132      !                            !-----------------------!
133      !                            !==   time stepping   ==!
134      !                            !-----------------------!
135      istp = nit000
136#if defined key_c1d
137         DO WHILE ( istp <= nitend .AND. nstop == 0 )
138            CALL stp_c1d( istp )
139            istp = istp + 1
140         END DO
141#else
142          IF( lk_asminc ) THEN
143             IF( ln_bkgwri ) CALL asm_bkg_wri( nit000 - 1 )    ! Output background fields
144             IF( ln_trjwri ) CALL asm_trj_wri( nit000 - 1 )    ! Output trajectory fields
145             IF( ln_asmdin ) THEN                        ! Direct initialization
146                IF( ln_trainc ) CALL tra_asm_inc( nit000 - 1 )    ! Tracers
147                IF( ln_dyninc ) THEN
148                   CALL dyn_asm_inc( nit000 - 1 )    ! Dynamics
149                   IF ( ln_asmdin ) CALL ssh_wzv ( nit000 - 1 )      ! update vertical velocity
150                ENDIF
151                IF( ln_sshinc ) CALL ssh_asm_inc( nit000 - 1 )    ! SSH
152             ENDIF
153          ENDIF
154       
155         DO WHILE ( istp <= nitend .AND. nstop == 0 )
156#if defined key_agrif
157            CALL Agrif_Step( stp )           ! AGRIF: time stepping
158#else
159            CALL stp( istp )                 ! standard time stepping
160#endif
161            istp = istp + 1
162            IF( lk_mpp )   CALL mpp_max( nstop )
163         END DO
164#endif
165
166      IF( lk_diaobs ) CALL dia_obs_wri
167       
168      !                            !------------------------!
169      !                            !==  finalize the run  ==!
170      !                            !------------------------!
171      IF(lwp) WRITE(numout,cform_aaa)   ! Flag AAAAAAA
172      !
173      IF( nstop /= 0 .AND. lwp ) THEN   ! error print
174         WRITE(numout,cform_err)
175         WRITE(numout,*) nstop, ' error have been found' 
176      ENDIF
177      !
178      CALL timing_finalize              ! Timing report
179
180      CALL nemo_closefile
181#if defined key_oasis3 || defined key_oasis4
182      CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS
183#else
184      IF( lk_mpp )   CALL mppstop       ! end mpp communications
185#endif
186      !
187   END SUBROUTINE nemo_gcm
188
189
190   SUBROUTINE nemo_init
191      !!----------------------------------------------------------------------
192      !!                     ***  ROUTINE nemo_init  ***
193      !!
194      !! ** Purpose :   initialization of the NEMO GCM
195      !!----------------------------------------------------------------------
196      INTEGER ::   ji            ! dummy loop indices
197      INTEGER ::   ilocal_comm   ! local integer
198      CHARACTER(len=80), DIMENSION(24) ::   cltxt
199      !!
200      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   &
201         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle, nn_bench
202      !!----------------------------------------------------------------------
203      !
204      cltxt(:) = ''
205      !
206      !                             ! open Namelist file
207      CALL ctl_opn( numnam, 'namelist', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. )
208      !
209      READ( numnam, namctl )        ! Namelist namctl : Control prints & Benchmark
210      !
211      !                             !--------------------------------------------!
212      !                             !  set communicator & select the local node  !
213      !                             !--------------------------------------------!
214#if defined key_iomput
215      IF( Agrif_Root() ) THEN
216# if defined key_oasis3 || defined key_oasis4
217         CALL cpl_prism_init( ilocal_comm )                 ! nemo local communicator given by oasis
218# endif
219         CALL  init_ioclient( ilocal_comm )                 ! exchange io_server nemo local communicator with the io_server
220      ENDIF
221      narea = mynode( cltxt, numnam, nstop, ilocal_comm )   ! Nodes selection
222#else
223# if defined key_oasis3 || defined key_oasis4
224      IF( Agrif_Root() ) THEN
225         CALL cpl_prism_init( ilocal_comm )                 ! nemo local communicator given by oasis
226      ENDIF
227      narea = mynode( cltxt, numnam, nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt)
228# else
229      ilocal_comm = 0
230      narea = mynode( cltxt, numnam, nstop )                 ! Nodes selection (control print return in cltxt)
231# endif
232#endif
233      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 )
234
235      lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print
236
237      ! Calculate domain z dimensions as needed when partitioning.
238      ! This used to be done in par_oce.F90 when they were parameters rather
239      ! than variables
240      IF( Agrif_Root() ) THEN
241         jpk = jpkdta                                             ! third dim
242         jpkm1 = jpk-1                                            ! inner domain indices
243         jpkorig = jpk                        ! Copy of jpk that is NOT modified
244      ENDIF
245
246      CALL timing_init                                      ! Init timing module
247      CALL timing_disable                                   ! but disable during startup
248
249      ! If dimensions of processor grid weren't specified in the namelist file
250      ! then we calculate them here now that we have our communicator size
251      IF( (jpni < 1) .OR. (jpnj < 1) )THEN
252#if   defined key_mpp_mpi
253#if   defined key_mpp_rkpart
254         IF( Agrif_Root() ) CALL nemo_recursive_partition(mppsize)
255#else
256         IF( Agrif_Root() ) CALL nemo_partition(mppsize)
257#endif
258#else
259         jpni  = 1
260         jpnj  = 1
261         jpnij = jpni*jpnj
262#endif
263
264#if   defined key_mpp_rkpart
265      ELSE
266         CALL ctl_stop( 'STOP', &
267                        'nemo_init : invalid inputs in namelist - cannot specify jpn{i,j}>0 &
268                        & when using recursive k-section paritioning!' )
269#endif
270      END IF
271
272      ! Calculate domain dimensions given calculated jpni and jpnj
273      ! This used to be done in par_oce.F90 when they were parameters rather
274      ! than variables
275      IF( Agrif_Root() ) THEN
276#if ! defined key_mpp_rkpart
277         jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   ! first  dim.
278         jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   ! second dim.
279         jpim1 = jpi-1                                            ! inner domain indices
280         jpjm1 = jpj-1                                            !   "           "
281         jpij  = jpi*jpj                                          !  jpi x j
282#endif
283      ENDIF
284
285      IF(lwp) THEN                            ! open listing units
286         !
287         CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
288         !
289         WRITE(numout,*)
290         WRITE(numout,*) '         CNRS - NERC - Met OFFICE - MERCATOR-ocean'
291         WRITE(numout,*) '                       NEMO team'
292         WRITE(numout,*) '            Ocean General Circulation Model'
293         WRITE(numout,*) '                  version 3.3  (2010) '
294         WRITE(numout,*)
295         WRITE(numout,*)
296         DO ji = 1, SIZE(cltxt,1) 
297            IF( TRIM(cltxt(ji)) /= '' )   WRITE(numout,*) cltxt(ji)      ! control print of mynode
298         END DO
299         WRITE(numout,cform_aaa)                                         ! Flag AAAAAAA
300         !
301      ENDIF
302
303      ! Now we know the dimensions of the grid and numout has been set we can
304      ! allocate arrays
305      CALL nemo_alloc()
306
307      !                             !-------------------------------!
308      !                             !  NEMO general initialization  !
309      !                             !-------------------------------!
310
311      CALL nemo_ctl                          ! Control prints & Benchmark
312
313      !                                      ! Domain decomposition
314#if defined key_mpp_rkpart
315                                          CALL mpp_init3     ! Remainder of set-up for
316                                                             ! recursive partitioning
317#else
318      IF( jpni*jpnj == jpnij ) THEN   ;   CALL mpp_init      ! standard cutting out
319      ELSE                            ;   CALL mpp_init2     ! eliminate land processors
320      ENDIF
321#endif
322      !
323      !                                      ! General initialization
324!                            CALL     timing_init! Timing module
325                            CALL     phy_cst    ! Physical constants
326                            CALL     eos_init   ! Equation of state
327                            CALL     dom_cfg    ! Domain configuration
328                            CALL     dom_init   ! Domain
329
330      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control
331
332      IF( lk_obc        )   CALL     obc_init   ! Open boundaries
333      IF( lk_bdy        )   CALL     bdy_init   ! Unstructured open boundaries
334
335                            CALL  istate_init   ! ocean initial state (Dynamics and tracers)
336
337      !                                     ! Ocean physics
338                            CALL     sbc_init   ! Forcings : surface module
339      !                                         ! Vertical physics
340                            CALL     zdf_init      ! namelist read
341                            CALL zdf_bfr_init      ! bottom friction
342      IF( lk_zdfric     )   CALL zdf_ric_init      ! Richardson number dependent Kz
343      IF( lk_zdftke     )   CALL zdf_tke_init      ! TKE closure scheme
344      IF( lk_zdfgls     )   CALL zdf_gls_init      ! GLS closure scheme
345      IF( lk_zdfkpp     )   CALL zdf_kpp_init      ! KPP closure scheme
346      IF( lk_zdftmx     )   CALL zdf_tmx_init      ! tidal vertical mixing
347      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
348         &                  CALL zdf_ddm_init      ! double diffusive mixing
349      !                                         ! Lateral physics
350                            CALL ldf_tra_init      ! Lateral ocean tracer physics
351                            CALL ldf_dyn_init      ! Lateral ocean momentum physics
352      IF( lk_ldfslp     )   CALL ldf_slp_init      ! slope of lateral mixing
353
354      !                                     ! Active tracers
355                            CALL tra_qsr_init   ! penetrative solar radiation qsr
356                            CALL tra_bbc_init   ! bottom heat flux
357      IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme
358      IF( lk_tradmp     )   CALL tra_dmp_init   ! internal damping trends
359                            CALL tra_adv_init   ! horizontal & vertical advection
360                            CALL tra_ldf_init   ! lateral mixing
361                            CALL tra_zdf_init   ! vertical mixing and after tracer fields
362
363      !                                     ! Dynamics
364                            CALL dyn_adv_init   ! advection (vector or flux form)
365                            CALL dyn_vor_init   ! vorticity term including Coriolis
366                            CALL dyn_ldf_init   ! lateral mixing
367                            CALL dyn_hpg_init   ! horizontal gradient of Hydrostatic pressure
368                            CALL dyn_zdf_init   ! vertical diffusion
369                            CALL dyn_spg_init   ! surface pressure gradient
370                           
371      !                                     ! Misc. options
372      IF( nn_cla == 1   )   CALL cla_init       ! Cross Land Advection
373     
374#if defined key_top
375      !                                     ! Passive tracers
376                            CALL     trc_init
377#endif
378      !                                     ! Diagnostics
379                            CALL     iom_init   ! iom_put initialization
380      IF( lk_floats     )   CALL     flo_init   ! drifting Floats
381      IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag
382                            CALL dia_ptr_init   ! Poleward TRansports initialization
383                            CALL dia_hsb_init   ! heat content, salt content and volume budgets
384                            CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends
385      IF( lk_diaobs     ) THEN                  ! Observation & model comparison
386                            CALL dia_obs_init            ! Initialize observational data
387                            CALL dia_obs( nit000 - 1 )   ! Observation operator for restart
388      ENDIF     
389      !                                     ! Assimilation increments
390      IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments
391      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler
392      !
393   END SUBROUTINE nemo_init
394
395
396   SUBROUTINE nemo_ctl
397      !!----------------------------------------------------------------------
398      !!                     ***  ROUTINE nemo_ctl  ***
399      !!
400      !! ** Purpose :   control print setting
401      !!
402      !! ** Method  : - print namctl information and check some consistencies
403      !!----------------------------------------------------------------------
404      !
405      IF(lwp) THEN                  ! control print
406         WRITE(numout,*)
407         WRITE(numout,*) 'nemo_ctl: Control prints & Benchmark'
408         WRITE(numout,*) '~~~~~~~ '
409         WRITE(numout,*) '   Namelist namctl'
410         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl
411         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print
412         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls
413         WRITE(numout,*) '      End i indice for SUM control    nn_ictle   = ', nn_ictle
414         WRITE(numout,*) '      Start j indice for SUM control  nn_jctls   = ', nn_jctls
415         WRITE(numout,*) '      End j indice for SUM control    nn_jctle   = ', nn_jctle
416         WRITE(numout,*) '      number of proc. following i     nn_isplt   = ', nn_isplt
417         WRITE(numout,*) '      number of proc. following j     nn_jsplt   = ', nn_jsplt
418         WRITE(numout,*) '      benchmark parameter (0/1)       nn_bench   = ', nn_bench
419      ENDIF
420      !
421      nprint    = nn_print          ! convert DOCTOR namelist names into OLD names
422      nictls    = nn_ictls
423      nictle    = nn_ictle
424      njctls    = nn_jctls
425      njctle    = nn_jctle
426      isplt     = nn_isplt
427      jsplt     = nn_jsplt
428      nbench    = nn_bench
429      !                             ! Parameter control
430      !
431      IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints
432         IF( lk_mpp ) THEN
433            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain
434         ELSE
435            IF( isplt == 1 .AND. jsplt == 1  ) THEN
436               CALL ctl_warn( ' - isplt & jsplt are equal to 1',   &
437                  &           ' - the print control will be done over the whole domain' )
438            ENDIF
439            ijsplt = isplt * jsplt            ! total number of processors ijsplt
440         ENDIF
441         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
442         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
443         !
444         !                              ! indices used for the SUM control
445         IF( nictls+nictle+njctls+njctle == 0 )   THEN    ! print control done over the default area
446            lsp_area = .FALSE.                       
447         ELSE                                             ! print control done over a specific  area
448            lsp_area = .TRUE.
449            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
450               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
451               nictls = 1
452            ENDIF
453            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
454               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
455               nictle = jpiglo
456            ENDIF
457            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
458               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
459               njctls = 1
460            ENDIF
461            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
462               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
463               njctle = jpjglo
464            ENDIF
465         ENDIF
466      ENDIF
467      !
468      IF( nbench == 1 ) THEN              ! Benchmark
469         SELECT CASE ( cp_cfg )
470         CASE ( 'gyre' )   ;   CALL ctl_warn( ' The Benchmark is activated ' )
471         CASE DEFAULT      ;   CALL ctl_stop( ' The Benchmark is based on the GYRE configuration:',   &
472            &                                 ' key_gyre must be used or set nbench = 0' )
473         END SELECT
474      ENDIF
475      !
476      IF( lk_c1d .AND. .NOT.lk_iomput )   CALL ctl_stop( 'nemo_ctl: The 1D configuration must be used ',   &
477         &                                               'with the IOM Input/Output manager. '         ,   &
478         &                                               'Compile with key_iomput enabled' )
479      !
480   END SUBROUTINE nemo_ctl
481
482
483   SUBROUTINE nemo_closefile
484      !!----------------------------------------------------------------------
485      !!                     ***  ROUTINE nemo_closefile  ***
486      !!
487      !! ** Purpose :   Close the files
488      !!----------------------------------------------------------------------
489      !
490      IF( lk_mpp )   CALL mppsync
491      !
492      CALL iom_close                                 ! close all input/output files managed by iom_*
493      !
494      IF( numstp     /= -1 )   CLOSE( numstp     )   ! time-step file
495      IF( numsol     /= -1 )   CLOSE( numsol     )   ! solver file
496      IF( numnam     /= -1 )   CLOSE( numnam     )   ! oce namelist
497      IF( numnam_ice /= -1 )   CLOSE( numnam_ice )   ! ice namelist
498      IF( numevo_ice /= -1 )   CLOSE( numevo_ice )   ! ice variables (temp. evolution)
499      IF( numout     /=  6 )   CLOSE( numout     )   ! standard model output file
500      !
501      numout = 6                                     ! redefine numout in case it is used after this point...
502      !
503   END SUBROUTINE nemo_closefile
504
505
506   SUBROUTINE nemo_alloc
507      !!----------------------------------------------------------------------
508      !!                     ***  ROUTINE nemo_alloc  ***
509      !!
510      !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules
511      !!
512      !! ** Method  :
513      !!----------------------------------------------------------------------
514      USE diawri    , ONLY: dia_wri_alloc
515      USE dom_oce   , ONLY: dom_oce_alloc
516      USE ldfdyn_oce, ONLY: ldfdyn_oce_alloc
517      USE ldftra_oce, ONLY: ldftra_oce_alloc
518      USE trc_oce   , ONLY: trc_oce_alloc
519      USE wrk_nemo  , ONLY: wrk_alloc
520      USE exchmod   , ONLY: exchmod_alloc
521      !
522      INTEGER :: ierr
523      !!----------------------------------------------------------------------
524      !
525      ierr =        oce_alloc       ()          ! ocean
526      ierr = ierr + dia_wri_alloc   ()
527      ierr = ierr + dom_oce_alloc   ()          ! ocean domain
528      ierr = ierr + ldfdyn_oce_alloc()          ! ocean lateral  physics : dynamics
529      ierr = ierr + ldftra_oce_alloc()          ! ocean lateral  physics : tracers
530      ierr = ierr + zdf_oce_alloc   ()          ! ocean vertical physics
531      !
532      ierr = ierr + lib_mpp_alloc   (numout)    ! mpp exchanges
533      ierr = ierr + trc_oce_alloc   ()          ! shared TRC / TRA arrays
534      !
535      ierr = ierr + wrk_alloc(numout, lwp)      ! workspace
536      !
537      ierr = ierr + exchmod_alloc()             ! New mpp msg framework
538      !
539      IF( lk_mpp    )   CALL mpp_sum( ierr )
540      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'nemo_alloc : unable to allocate standard ocean arrays' )
541      !
542   END SUBROUTINE nemo_alloc
543
544
545   SUBROUTINE nemo_partition( num_pes )
546      USE mapcomm_mod, ONLY: trimmed
547      !!----------------------------------------------------------------------
548      !!                 ***  ROUTINE nemo_partition  ***
549      !!
550      !! ** Purpose : Work out a sensible factorisation of the number of
551      !!              processors for the x and y dimensions.
552      !! ** Method  :
553      !!----------------------------------------------------------------------
554      INTEGER, INTENT(in) :: num_pes ! The number of MPI processes we have
555      !
556      INTEGER             :: ifact1, ifact2 ! factors of num_pes, ifact1 <= ifact2
557      !!----------------------------------------------------------------------
558
559      ! Factorise the number of processors into ifact1*ifact2, such that
560      ! ifact1 and ifact2 are as nearly equal as possible.
561
562      CALL sqfact( num_pes, ifact1, ifact2 )
563
564      ! Make sure that the smaller dimension of the processor grid
565      ! is given the smaller dimension of the global domain
566      IF( jpiglo <= jpjglo) THEN
567         jpni = ifact1
568         jpnj = ifact2
569      ELSE
570         jpni = ifact2
571         jpnj = ifact1
572      ENDIF
573
574      ! This should never happen
575      IF( (jpni*jpnj) /= num_pes) THEN
576         WRITE (numout, *) 'WARNING: internal error - factorisation of number of PEs failed'
577      ENDIF
578
579      ! This should only happen if num_pes is prime
580      IF( ifact1 <= 1 ) THEN
581         WRITE (numout, *) 'WARNING: factorisation of number of PEs failed'
582         WRITE (numout, *) '       : using grid of ',jpni,' x ',jpnj
583      ENDIF
584      !
585      jpnij = jpni*jpnj
586      !
587
588      ! Array that stores whether domain boundaries have been trimmed. Not used in
589      ! this case (regular domain decomp.) so set all to false.
590      ALLOCATE(trimmed(4,jpnij))
591      trimmed(:,:) = .FALSE.
592
593   END SUBROUTINE nemo_partition
594
595
596   SUBROUTINE nemo_recursive_partition( num_pes )
597      USE in_out_manager, ONLY: numnam
598      USE dom_oce,        ONLY: ln_zco
599      USE dom_oce,        ONLY: gdepw_0, gdept_0, e3w_0, e3t_0, &
600                                mig, mjg, mi0, mi1, mj0, mj1,  mbathy, bathy
601      USE domzgr,         ONLY: zgr_z, zgr_bat, namzgr, zgr_zco, zgr_zps
602      USE closea,         ONLY: dom_clo
603      USE domain,         ONLY: dom_nam
604      USE iom,            ONLY: jpiglo, jpjglo, wp, jpdom_unknown, &
605                                iom_open, iom_get, iom_close
606      USE mapcomm_mod, ONLY: ielb, ieub, pielb, pjelb, pieub, pjeub,          &
607                             iesub, jesub, jeub, ilbext, iubext, jubext,      &
608                             jlbext, pnactive, piesub, pjesub, jelb, pilbext, &
609                             piubext, pjlbext, pjubext, LAND, trimmed,        &
610                             msgtrim_z, set_num_subdomains
611      USE partition_mod, ONLY: partition_rk, partition_mca_rk, read_partition, &
612                               imask, ibotlevel, partition_mask_alloc,         &
613                               smooth_global_bathy, global_bot_level
614      USE par_oce,       ONLY: do_exchanges
615#if defined key_mpp_mpi
616      USE mpi
617#endif
618      !!----------------------------------------------------------------------
619      !!                 ***  ROUTINE nemo_recursive_partition  ***
620      !!
621      !! ** Purpose : Work out a sensible factorisation of the number of
622      !!              processors for the x and y dimensions.
623      !! ** Method  :
624      !!----------------------------------------------------------------------
625      IMPLICIT none
626      INTEGER, INTENT(in) :: num_pes ! The number of MPI processes we have
627      ! Local vars
628      INTEGER :: ierr                          ! Error flag
629      INTEGER :: ii,jj                         ! Loop index
630      CHARACTER(LEN=8) :: lstr                 ! Local string for reading env. var.
631      INTEGER          :: lztrim               ! Local int for      "      "    "
632      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zdta  ! temporary data workspace
633      !!----------------------------------------------------------------------
634
635      ! Allocate masking arrays used in partitioning
636      CALL partition_mask_alloc(jpiglo,jpjglo,ierr)
637      IF(ierr /= 0)THEN
638         CALL ctl_stop('nemo_recursive_partition: failed to allocate masking arrays')
639         RETURN
640      END IF
641
642      ! Allocate local workspace array for this routine
643      ALLOCATE(zdta(jpiglo,jpjglo), Stat=ierr)
644      IF(ierr /= 0)THEN
645         CALL ctl_stop('nemo_recursive_partition: failed to allocate workspace arrays')
646         RETURN
647      END IF
648
649      ! Check whether user has specified halo trimming in z via environment
650      ! variable.
651      ! Halo trimming in z is on by default
652      msgtrim_z = .TRUE.
653      CALL GET_ENVIRONMENT_VARIABLE(NAME='NEMO_MSGTRIM_Z', VALUE=lstr, &
654                                    STATUS=ierr)
655      IF( ierr == 0)THEN
656         READ(lstr,FMT="(I10)",IOSTAT=ierr) lztrim
657         IF(ierr == 0)THEN
658            IF (lztrim == 0) msgtrim_z = .FALSE.
659         ELSE
660            CALL ctl_warn('nemo_recursive_partition: failed to parse value of NEMO_MSGTRIM_Z environment variable: '//TRIM(lstr))
661         END IF
662      END IF
663
664      IF(lwp) WRITE(*,*) 'ARPDBG: msgtrim_z = ',msgtrim_z
665
666      ! ============================
667      ! Generate a global mask from the model bathymetry
668      ! ============================
669
670      ! Read the z-coordinate options from the namelist file
671      REWIND(numnam)
672      READ  (numnam, namzgr)
673
674      ! Read domain options from namelist file
675      CALL dom_nam()
676
677      ! Allocate these arrays so we can use domzgr::zgr_z routine; free them
678      ! when we're done so as not to upset the 'official' allocation once
679      ! the domain decomposition is done.
680      ALLOCATE(gdepw_0(jpk), gdept_0(jpk), e3w_0(jpk), e3t_0(jpk), &
681               mig(jpiglo), mjg(jpjglo), &
682               mbathy(jpiglo,jpjglo), bathy(jpiglo,jpjglo), Stat=ierr)
683      IF(ierr /= 0)THEN
684         CALL ctl_stop('STOP', &
685                       'nemo_recursive_partition: failed to allocate zgr_z() arrays')
686         RETURN
687      END IF
688
689      ! Set-up reference depth coordinates
690      CALL zgr_z()
691
692      ! Set-up sub-domain limits as global domain for zgr_bat()
693      nldi = 2 ; nlci = jpiglo - 1
694      nldj = 2 ; nlcj = jpjglo - 1
695      jpi = jpiglo
696      jpj = jpjglo
697
698      ! Set-up fake m{i,j}g arrays for zgr_bat() call
699      DO ii = 1, jpiglo, 1
700         mig(ii) = ii
701         mi0(ii) = ii
702         mi1(ii) = ii
703      END DO
704      DO jj = 1, jpjglo, 1
705         mjg(jj) = jj
706         mj0(jj) = jj
707         mj1(jj) = jj
708      END DO
709
710      ! Initialise closed seas so loop over closed seas in zgr_bat works
711      CALL dom_clo()
712
713      ! Read-in bathy (if required) of global domain
714      CALL zgr_bat(.TRUE.)
715
716      ! land/sea mask (zero on land, 1 otherwise) over the global/zoom domain
717      imask(:,:)=1
718
719      ! Copy bathymetry in case we need to smooth it
720      zdta(:,:) = bathy(:,:)
721
722      IF(ln_sco)THEN
723         ! If ln_sco defined then the bathymetry gets smoothed before the
724         ! simulation begins and that process can alter the coastlines (bug!)
725         ! therefore we do it here too before calculating our mask.
726         CALL smooth_global_bathy(zdta, mbathy)
727      ELSE IF(ln_zps)THEN
728         CALL zgr_zps(.TRUE.)
729      ELSE IF(ln_zco)THEN
730         ! Not certain this is required since mbathy computed in zgr_bat()
731         ! in this case.
732         !CALL zgr_zco()
733      END IF
734
735      ! Compute the deepest/last ocean level for every point on the grid
736      ibotlevel(:,:) = mbathy(:,:)
737      CALL global_bot_level(ibotlevel)
738
739      ! Comment-out line below to achieve a regular partition
740      WHERE ( zdta(:,:) <= 1.0E-20 ) imask = LAND
741
742      ! Allocate partitioning arrays.
743
744      IF ( .NOT. ALLOCATED(pielb) ) THEN
745         ALLOCATE (pielb(num_pes),   pieub(num_pes), piesub(num_pes),     &
746                   pilbext(num_pes), piubext(num_pes),                    &
747                   pjelb(num_pes),   pjeub(num_pes), pjesub(num_pes),     &
748                   pjlbext(num_pes), pjubext(num_pes), pnactive(num_pes), &
749                   trimmed(4,num_pes), Stat = ierr)
750         IF(ierr /= 0)THEN
751            CALL ctl_stop('STOP', &
752                          'nemo_recursive_partition: failed to allocate partitioning arrays')
753            RETURN
754         END IF
755      ENDIF
756
757      ! Set error flag so that we calculate domain decomp if not reading
758      ! existing decomposition or if read fails.
759      ierr = 1
760
761      IF( nn_readpart )THEN
762         ! Read the partitioning to use from disk
763         CALL read_partition(ierr)
764         IF ( ierr /= 0 ) THEN
765            CALL ctl_warn('Read of pre-calculated domain decomposition failed - will calculate one instead.')
766         END IF
767      END IF
768
769      ! Set the number of sub-domains for which we are to partition
770      ! (module var in mapcomm_mod)
771      CALL set_num_subdomains(num_pes)
772
773      IF(ierr /= 0)THEN
774         ! Multi-core aware version of recursive k-section partitioning.
775         ! Currently only accounts for whether a grid point is wet or dry.
776         ! It has no knowledge of the number of wet levels at a point.
777         CALL partition_mca_rk ( imask, 1, jpiglo, 1, jpjglo, ierr )
778
779         ! Now we can do recursive k-section partitioning
780         ! ARPDBG - BUG if limits on array below are set to anything other than
781         ! 1 and jp{i,j}glo then check for external boundaries in a few lines
782         ! time WILL FAIL!
783         ! CALL partition_rk ( imask, 1, jpiglo, 1, jpjglo, ierr )
784     END IF
785
786      ! Check the error code from partitioning.
787      IF ( ierr /= 0 ) THEN
788         CALL ctl_stop('STOP','nemo_recursive_partition: Partitioning failed')
789         RETURN
790      ENDIF
791
792      ! If we used generate_fake_land() above then we must set
793      ! the mask correctly now we've partitioned. This is only
794      ! necessary when testing.
795      !WHERE ( zdta(:,:) <= 0. ) imask = 0
796
797      ! ARPDBG Quick and dirty dump to stdout in gnuplot form
798      IF(narea == 1)THEN
799         OPEN(UNIT=998, FILE="imask.dat", &
800              STATUS='REPLACE', ACTION='WRITE', IOSTAT=jj)
801         IF( jj == 0 )THEN
802            WRITE (998,*) '# Depth map'
803            WRITE (998,*) '# i   j  bathy  imask   ibotlevel   mbathy'
804            DO jj = 1, jpjglo, 1
805               DO ii = 1, jpiglo, 1
806                  WRITE (998,"(I4,1x,I4,1x,E16.6,1x,I4,1x,I4,1x,I4)") &
807                  ii, jj, zdta(ii,jj), imask(ii,jj), ibotlevel(ii,jj), mbathy(ii,jj)
808               END DO
809               WRITE (998,*)
810            END DO
811            CLOSE(998)
812         END IF
813      END IF
814
815      jpkm1 = jpk - 1
816
817      ! This chunk taken directly from original mpp_ini - not sure why nbondi
818      ! is reset? However, if it isn't reset then bad things happen in dommsk
819      ! so I'm doing what the original code does...
820      nperio = 0
821      nbondi = 0
822      IF( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 ) THEN
823         IF( jpni == 1 )THEN
824            nbondi = 2
825            nperio = 1
826         END IF
827      END IF
828
829#if defined ARPDEBUG
830      ! This output is REQUIRED by the check_nemo_comms.pl test script
831      WRITE (*,FMT="(I4,' : ARPDBG: ielb, ieub, iesub = ',3I5)") narea-1,&
832            ielb, ieub, iesub
833      WRITE (*,FMT="(I4,' : ARPDBG: jelb, jeub, jesub = ',3I5)") narea-1,&
834            jelb, jeub, jesub
835      WRITE (*,FMT="(I4,' : ARPDBG: nldi, nlei, nlci = ',3I5)") narea-1, &
836            nldi, nlei, nlci
837      WRITE (*,FMT="(I4,' : ARPDBG: nldj, nlej, nlcj = ',3I5)") narea-1, &
838            nldj, nlej, nlcj
839      WRITE (*,FMT="(I4,' : ARPDBG: jpi, jpj = ',2I5)") narea-1, jpi, jpj
840      WRITE (*,FMT="(I4,' : ARPDBG: nimpp, njmpp = ',2I5)") narea-1, &
841            nimpp, njmpp
842#endif
843
844      ! Debugging option - can turn off all halo exchanges by setting this to
845      ! false.
846      do_exchanges = .TRUE.
847
848      ! Free the domzgr/_oce member arrays that we used earlier in zgr_z() and
849      ! zgr_bat().
850      DEALLOCATE(gdepw_0, gdept_0, e3w_0, e3t_0, mig, mjg,  &
851                 mbathy, bathy)
852
853   END SUBROUTINE nemo_recursive_partition
854
855
856   SUBROUTINE sqfact ( kn, kna, knb )
857      !!----------------------------------------------------------------------
858      !!                     ***  ROUTINE sqfact  ***
859      !!
860      !! ** Purpose :   return factors (kna, knb) of kn, such that
861      !!                (1) kna*knb=kn
862      !!                (2) kna and knb are as near equal as possible
863      !!                (3) kna < knb
864      !! ** Method  :   Search backwards from the square root of kn,
865      !!                until we find an integer that cleanly divides kn
866      !! ** Preconditions : kn must be positive
867      !!----------------------------------------------------------------------
868      INTEGER, INTENT(in   ) ::   kn
869      INTEGER, INTENT(  out) ::   kna, knb
870       
871      ! Search backwards from the square root of n.
872
873      fact_loop: DO kna=INT(SQRT(REAL(kn))),1,-1
874         IF ( kn/kna*kna == kn ) THEN
875            EXIT fact_loop
876         ENDIF
877      END DO fact_loop
878
879      IF( kna < 1 ) kna = 1 
880
881      ! kna divides kn cleanly. Work out the other factor.
882      knb = kn/kna
883
884   END SUBROUTINE sqfact
885
886
887   SUBROUTINE generate_fake_land(imask)
888      !!----------------------------------------------------------------------
889      !! Generate a fake land mass to test the decomposition code
890      !!----------------------------------------------------------------------
891      USE par_oce, ONLY: jpiglo, jpjglo
892      USE partition_mod, ONLY: write_partition_map
893      IMPLICIT none
894      INTEGER, DIMENSION(jpiglo,jpjglo), INTENT(inout) :: imask
895      ! Locals
896      INTEGER :: jj
897      INTEGER :: icentre, jcentre
898      INTEGER :: iwidth, iheight
899      INTEGER :: istart, istop
900
901      ! imask is zero on land points , unity on ocean points
902      iwidth = jpiglo/8
903      iheight = jpjglo/8
904
905      icentre = jpiglo/2
906      jcentre = jpjglo/2
907
908      istart = icentre - iwidth
909      istop = icentre + iwidth
910      DO jj = jcentre, jcentre - iheight, -1
911         imask(istart:istop,jj) = 0
912         istart = istart + 1
913         istop = istop - 1
914      END DO
915      istart = icentre - iwidth
916      istop = icentre + iwidth
917      DO jj = jcentre+1, jcentre + iheight, 1
918         imask(istart:istop,jj) = 0
919         istart = istart + 1
920         istop = istop - 1
921      END DO
922
923! Quick and dirty dump to stdout in gnuplot form
924!!$      WRITE (*,*) 'GNUPLOT MAP'
925!!$      DO jj = 1, jpjglo, 1
926!!$         DO ii = 1, jpiglo, 1
927!!$            WRITE (*,*) ii, jj, imask(ii,jj)
928!!$         END DO
929!!$         WRITE (*,*)
930!!$      END DO
931!!$      WRITE (*,*) 'END GNUPLOT MAP'
932
933   END SUBROUTINE generate_fake_land
934
935   !!======================================================================
936END MODULE nemogcm
Note: See TracBrowser for help on using the repository browser.