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.
opa.F90 in branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC – NEMO

source: branches/nemo_v3_3_beta/NEMOGCM/NEMO/OFF_SRC/opa.F90 @ 2431

Last change on this file since 2431 was 2431, checked in by cetlod, 13 years ago

Improve the Offline together with the 1D vertical configuration

  • Property svn:keywords set to Id
File size: 16.8 KB
Line 
1MODULE opa
2   !!==============================================================================
3   !!                       ***  MODULE opa   ***
4   !! Ocean system   : OPA ocean dynamics (including on-line tracers and sea-ice)
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   opa_model      : solve ocean dynamics, tracer and/or sea-ice
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE dom_oce         ! ocean space domain variables
12   USE oce             ! dynamics and tracers variables
13   USE in_out_manager  ! I/O manager
14   USE lib_mpp         ! distributed memory computing
15
16   USE domcfg          ! domain configuration               (dom_cfg routine)
17   USE mppini          ! shared/distributed memory setting (mpp_init routine)
18   USE domain          ! domain initialization             (dom_init routine)
19   USE istate          ! initial state setting          (istate_init routine)
20   USE eosbn2          ! equation of state            (eos bn2 routine)
21
22   ! ocean physics
23   USE ldftra          ! lateral diffusivity setting    (ldf_tra_init routine)
24   USE ldfslp          ! slopes of neutral surfaces     (ldf_slp_init routine)
25   USE traqsr          ! solar radiation penetration    (tra_qsr_init routine)
26   USE trabbl          ! bottom boundary layer          (tra_bbl_init routine)
27   USE zpshde          ! partial step: hor. derivative  (zps_hde_init routine)
28   USE zdfini
29   USE zdfddm
30   USE zdfkpp
31
32   USE phycst          ! physical constant                  (par_cst routine)
33   USE dtadyn          ! Lecture and Interpolation of the dynamical fields
34   USE trcini          ! Initilization of the passive tracers
35   USE stpctl
36   USE daymod          ! calendar                         (day     routine)
37   USE trcstp          ! passive tracer time-stepping      (trc_stp routine)
38   USE dtadyn          ! Lecture and interpolation of the dynamical fields
39   USE stpctl          ! time stepping control            (stp_ctl routine)
40
41   USE c1d             ! 1D configuration
42
43   USE iom
44#if defined key_iomput
45   USE  mod_ioclient
46#endif
47
48   IMPLICIT NONE
49   PRIVATE
50
51   !! * Module variables
52   CHARACTER (len=64) ::        &
53      cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
54
55   !! * Routine accessibility
56   PUBLIC opa_model      ! called by model.F90
57   PUBLIC opa_init
58   !!----------------------------------------------------------------------
59   !! NEMO/OFF 3.3 , NEMO Consortium (2010)
60   !! $Id$
61   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
62   !!----------------------------------------------------------------------
63
64CONTAINS
65
66   SUBROUTINE opa_model
67      !!----------------------------------------------------------------------
68      !!                     ***  ROUTINE opa  ***
69      !!
70      !! ** Purpose :   opa solves the primitive equations on an orthogonal
71      !!      curvilinear mesh on the sphere.
72      !!
73      !! ** Method  : - model general initialization
74      !!              - launch the time-stepping (stp routine)
75      !!
76      !! References :
77      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
78      !!              internal report, IPSL.
79      !!----------------------------------------------------------------------
80      INTEGER :: istp, indic       ! time step index
81      !!----------------------------------------------------------------------
82
83      CALL opa_init  ! Initializations
84
85      IF( lk_mpp )   CALL mpp_max( nstop )
86
87      ! check that all process are still there... If some process have an error,
88      ! they will never enter in step and other processes will wait until the end of the cpu time!
89      IF( lk_mpp )   CALL mpp_max( nstop )
90
91      istp = nit000
92         !
93      DO WHILE ( istp <= nitend .AND. nstop == 0 )
94         !
95         IF( istp /= nit000 )   CALL day      ( istp )   ! Calendar (day was already called at nit000 in day_init)
96                                CALL iom_setkt( istp )   ! say to iom that we are at time step kstp
97                                CALL dta_dyn  ( istp )   ! Interpolation of the dynamical fields
98                                CALL trc_stp  ( istp )   ! time-stepping
99                                CALL stp_ctl  ( istp, indic )   ! Time loop: control and print
100         istp = istp + 1
101         IF( lk_mpp )   CALL mpp_max( nstop )
102      END DO
103      !                                     ! ========= !
104      !                                     !  Job end  !
105      !                                     ! ========= !
106
107      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
108
109      IF( nstop /= 0 .AND. lwp ) THEN                 ! error print
110         WRITE(numout,cform_err)
111         WRITE(numout,*) nstop, ' error have been found'
112      ENDIF
113
114      CALL opa_closefile
115
116      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
117      !
118   END SUBROUTINE opa_model
119
120
121   SUBROUTINE opa_init
122      !!----------------------------------------------------------------------
123      !!                     ***  ROUTINE opa_init ***
124      !!
125      !! ** Purpose :   opa solves the primitive equations on an orthogonal
126      !!      curvilinear mesh on the sphere.
127      !!
128      !! ** Method  : - model general initialization
129      !!
130      !! References :
131      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
132      !!              internal report, IPSL.
133      !!
134      !! History :
135      !!   4.0  !  90-10  (C. Levy, G. Madec)  Original code
136      !!   7.0  !  91-11  (M. Imbard, C. Levy, G. Madec)
137      !!   7.1  !  93-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
138      !!                   M. Guyon, A. Lazar, P. Delecluse, C. Perigaud,
139      !!                   G. Caniaux, B. Colot, C. Maes ) release 7.1
140      !!        !  92-06  (L.Terray) coupling implementation
141      !!        !  93-11  (M.A. Filiberti) IGLOO sea-ice
142      !!   8.0  !  96-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
143      !!                   M. Guyon, A. Lazar, P. Delecluse, L.Terray,
144      !!                   M.A. Filiberti, J. Vialar, A.M. Treguier,
145      !!                   M. Levy)  release 8.0
146      !!   8.1  !  97-06  (M. Imbard, G. Madec)
147      !!   8.2  !  99-11  (M. Imbard, H. Goosse)  LIM sea-ice model
148      !!        !  99-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
149      !!        !  00-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
150      !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules
151      !!----------------------------------------------------------------------
152      !! * Local declarations
153#if defined key_oasis3 || defined key_oasis4 || defined key_iomput
154      INTEGER :: ilocal_comm
155#endif
156      CHARACTER(len=80),dimension(10) ::   cltxt = ''
157      INTEGER                         ::   ji   ! local loop indices
158      !!
159      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   &
160         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle, nn_bench
161      !!----------------------------------------------------------------------
162
163      !
164      !                             ! open Namelist file     
165      CALL ctl_opn( numnam, 'namelist', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. )
166      !
167      READ( numnam, namctl )        ! Namelist namctl : Control prints & Benchmark
168      !
169      !                             !--------------------------------------------!
170      !                             !  set communicator & select the local node  !
171      !                             !--------------------------------------------!
172#if defined key_iomput
173# if defined key_oasis3 || defined key_oasis4   
174      CALL cpl_prism_init( ilocal_comm )      ! nemo local communicator given by oasis
175      CALL init_ioclient()                    ! io_server will get its communicators (if needed) from oasis (we don't see it)
176# else
177      CALL init_ioclient( ilocal_comm )       ! nemo local communicator (used or not) given by the io_server
178# endif
179      narea = mynode( cltxt, ilocal_comm )    ! Nodes selection
180
181#else
182# if defined key_oasis3 || defined key_oasis4   
183      CALL cpl_prism_init( ilocal_comm )      ! nemo local communicator given by oasis
184      narea = mynode( cltxt, ilocal_comm )    ! Nodes selection (control print return in cltxt)
185# else
186      narea = mynode( cltxt )                 ! Nodes selection (control print return in cltxt)
187# endif
188#endif
189      narea = narea + 1                       ! mynode return the rank of proc (0 --> jpnij -1 )
190
191      lwp = (narea == 1) .OR. ln_ctl          ! control of all listing output print
192
193      IF(lwp) THEN                            ! open listing units
194         !
195         CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
196         !
197         WRITE(numout,*)
198         WRITE(numout,*) '         CNRS - NERC - Met OFFICE - MERCATOR-ocean'
199         WRITE(numout,*) '                       NEMO team'
200         WRITE(numout,*) '            Ocean General Circulation Model'
201         WRITE(numout,*) '                  version 3.2  (2009) '
202         WRITE(numout,*)
203         WRITE(numout,*)
204         DO ji = 1, SIZE(cltxt) 
205            IF( TRIM(cltxt(ji)) /= '' )   WRITE(numout,*) cltxt(ji)      ! control print of mynode
206         END DO
207         WRITE(numout,cform_aaa)                                         ! Flag AAAAAAA
208         !
209      ENDIF
210
211      CALL opa_flg                          ! Control prints & Benchmark
212
213      !                                     ! ============================== !
214      !                                     !  Model general initialization  !
215      !                                     ! ============================== !
216
217      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
218
219                                            ! Domain decomposition
220                                            ! Domain decomposition
221      IF( jpni*jpnj == jpnij ) THEN   ;   CALL mpp_init      ! standard cutting out
222      ELSE                            ;   CALL mpp_init2     ! eliminate land processors
223      ENDIF
224
225
226
227      !                                     ! General initialization
228                            CALL     phy_cst    ! Physical constants
229                            CALL     eos_init   ! Equation of state
230                            CALL     dom_cfg    ! Domain configuration
231                            CALL     dom_init   ! Domain
232
233      IF( ln_zps        )   CALL zps_hde_init   ! Partial steps:  horizontal derivative
234                            CALL  istate_init   ! ocean initial state (Dynamics and tracers)
235
236      !                                     ! Ocean physics
237      IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   &
238         &                  CALL zdf_ddm_init   ! double diffusive mixing
239#if ! defined key_degrad
240                            CALL ldf_tra_init   ! Lateral ocean tracer physics
241#endif
242      IF( lk_ldfslp )       CALL ldf_slp_init   ! slope of lateral mixing
243
244      !                                     ! Active tracers
245                            CALL tra_qsr_init   ! penetrative solar radiation qsr
246      IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme
247
248      !                                     ! Passive tracers
249                            CALL     trc_init   ! Passive tracers initialization
250      !                                     ! Dynamics
251                            CALL dta_dyn_init   ! Initialization for the dynamics
252                            CALL     iom_init       ! iom_put initialization
253
254      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
255
256   END SUBROUTINE opa_init
257
258   SUBROUTINE opa_flg
259      !!----------------------------------------------------------------------
260      !!                     ***  ROUTINE opa  ***
261      !!
262      !! ** Purpose :   Initialise logical flags that control the choice of
263      !!              some algorithm or control print
264      !!
265      !! ** Method  : - print namctl information
266      !!              - Read in namilist namflg logical flags
267      !!----------------------------------------------------------------------
268
269      IF(lwp) THEN                 ! Parameter print
270         WRITE(numout,*)
271         WRITE(numout,*) 'opa_flg: Control prints & Benchmark'
272         WRITE(numout,*) '~~~~~~~ '
273         WRITE(numout,*) '   Namelist namctl'
274         WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl
275         WRITE(numout,*) '      level of print                  nn_print   = ', nn_print
276         WRITE(numout,*) '      Start i indice for SUM control  nn_ictls   = ', nn_ictls
277         WRITE(numout,*) '      End i indice for SUM control    nn_ictle   = ', nn_ictle
278         WRITE(numout,*) '      Start j indice for SUM control  nn_jctls   = ', nn_jctls
279         WRITE(numout,*) '      End j indice for SUM control    nn_jctle   = ', nn_jctle
280         WRITE(numout,*) '      number of proc. following i     nn_isplt   = ', nn_isplt
281         WRITE(numout,*) '      number of proc. following j     nn_jsplt   = ', nn_jsplt
282         WRITE(numout,*) '      benchmark parameter (0/1)       nn_bench   = ', nn_bench
283      ENDIF
284
285      nprint    = nn_print          ! convert DOCTOR namelist names into OLD names
286      nictls    = nn_ictls
287      nictle    = nn_ictle
288      njctls    = nn_jctls
289      njctle    = nn_jctle
290      isplt     = nn_isplt
291      jsplt     = nn_jsplt
292      nbench    = nn_bench
293      !                           ! Parameter control
294      !
295      IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints
296         IF( lk_mpp ) THEN
297            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real splitted domain
298         ELSE
299            IF( isplt == 1 .AND. jsplt == 1  ) THEN
300               CALL ctl_warn( ' - isplt & jsplt are equal to 1',   &
301                  &           ' - the print control will be done over the whole domain' )
302            ENDIF
303            ijsplt = isplt * jsplt            ! total number of processors ijsplt
304         ENDIF
305         IF(lwp) WRITE(numout,*)'          - The total number of processors over which the'
306         IF(lwp) WRITE(numout,*)'            print control will be done is ijsplt : ', ijsplt
307         !
308         !                              ! indices used for the SUM control
309         IF( nictls+nictle+njctls+njctle == 0 )   THEN    ! print control done over the default area
310            lsp_area = .FALSE.
311         ELSE                                             ! print control done over a specific  area
312            lsp_area = .TRUE.
313            IF( nictls < 1 .OR. nictls > jpiglo )   THEN
314               CALL ctl_warn( '          - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
315               nictls = 1
316            ENDIF
317            IF( nictle < 1 .OR. nictle > jpiglo )   THEN
318               CALL ctl_warn( '          - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
319               nictle = jpiglo
320            ENDIF
321            IF( njctls < 1 .OR. njctls > jpjglo )   THEN
322               CALL ctl_warn( '          - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
323               njctls = 1
324            ENDIF
325            IF( njctle < 1 .OR. njctle > jpjglo )   THEN
326               CALL ctl_warn( '          - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
327               njctle = jpjglo
328            ENDIF
329         ENDIF
330      ENDIF
331
332      IF( nbench == 1 )   THEN            ! Benchmark
333         SELECT CASE ( cp_cfg )
334         CASE ( 'gyre' )   ;   CALL ctl_warn( ' The Benchmark is activated ' )
335         CASE DEFAULT      ;   CALL ctl_stop( ' The Benchmark is based on the GYRE configuration:',   &
336            &                                 ' key_gyre must be used or set nbench = 0' )
337         END SELECT
338      ENDIF
339      !
340      IF( lk_c1d .AND. .NOT. lk_iomput )  &
341        CALL ctl_stop( ' The 1D vertical configuration must be used in conjunction',   &
342            &          ' with the IOM Input/Output manager. Compile with key_iomput enabled' )
343      !
344
345   END SUBROUTINE opa_flg
346
347   SUBROUTINE opa_closefile
348      !!----------------------------------------------------------------------
349      !!                     ***  ROUTINE opa_closefile  ***
350      !!
351      !! ** Purpose :   Close the files
352      !!
353      !! ** Method  :
354      !!
355      !! History :
356      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
357      !!----------------------------------------------------------------------
358      !!----------------------------------------------------------------------
359
360      IF ( lk_mpp ) CALL mppsync
361
362      ! 1. Unit close
363      ! -------------
364
365      CLOSE( numnam )           ! namelist
366      CLOSE( numout )           ! standard model output file
367
368      IF(lwp) CLOSE( numstp )   ! time-step file
369
370      CALL iom_close            ! close all input/output files
371
372   END SUBROUTINE opa_closefile
373
374   !!======================================================================
375END MODULE opa
Note: See TracBrowser for help on using the repository browser.