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 trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/opa.F90 @ 392

Last change on this file since 392 was 392, checked in by opalod, 18 years ago

RB:nemo_v1_update_038: first integration of Agrif :

  • add agrif to dynspg_flt_jki.F90
  • cosmetic change of key_AGRIF in key_agrif
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 14.8 KB
RevLine 
[3]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   !!   opa_flg        : initialisation of algorithm flag
[300]10   !!   opa_closefile  : close remaining files
[3]11   !!----------------------------------------------------------------------
12   !! * Modules used
[145]13   USE cpl_oce         ! ocean-atmosphere-sea ice coupled exchanges
[3]14   USE dom_oce         ! ocean space domain variables
15   USE oce             ! dynamics and tracers variables
[216]16   USE trdmod_oce      ! ocean variables trends
[3]17   USE daymod          ! calendar
18   USE in_out_manager  ! I/O manager
19   USE lib_mpp         ! distributed memory computing
20
21   USE domcfg          ! domain configuration               (dom_cfg routine)
22   USE mppini          ! shared/distributed memory setting (mpp_init routine)
23   USE domain          ! domain initialization             (dom_init routine)
24   USE obc_par         ! open boundary cond. parameters
25   USE obcini          ! open boundary cond. initialization (obc_ini routine)
26   USE solver          ! solver initialization          (solver_init routine)
27   USE istate          ! initial state setting          (istate_init routine)
28   USE eosbn2          ! equation of state            (eos bn2 routine)
29   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
30
31   ! ocean physics
32   USE traqsr          ! solar radiation penetration   (tra_qsr_init routine)
33   USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine)
34   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine)
35   USE zdfini
36
37   USE phycst          ! physical constant                  (par_cst routine)
38   USE iceini          ! initialization of sea-ice         (ice_init routine)
39   USE cpl             ! coupled ocean/atmos.              (cpl_init routine)
40   USE ocfzpt          ! ocean freezing point              (oc_fz_pt routine)
[216]41   USE trdicp          ! momentum/tracers trends       (trd_icp_init routine)
42   USE trdvor          ! vorticity trends              (trd_vor_init routine)
43   USE trdmld          ! tracer mixed layer trends     (trd_mld_init routine)
[3]44   USE flxfwb          !
45
[132]46   USE diaptr          ! poleward transports           (dia_ptr_init routine)
[3]47
48   USE step            ! OPA time-stepping                  (stp     routine)
[367]49   USE dynspg_oce      ! Control choice of surface pressure gradient schemes
[258]50   USE prtctl          ! Print control                 (prt_ctl_init routine)
[253]51   USE ini1d           ! re-initialization of u-v mask for the 1D configuration
52   USE dyncor1d        ! Coriolis factor at T-point
53   USE step1d          ! Time stepping loop for the 1D configuration
[3]54
[268]55   USE initrc          ! Initialization of the passive tracers
56
[3]57   IMPLICIT NONE
58   PRIVATE
59
60   !! * Routine accessibility
61   PUBLIC opa_model      ! called by model.F90
[389]62   PUBLIC opa_init
[3]63   !!----------------------------------------------------------------------
[247]64   !!  OPA 9.0 , LOCEAN-IPSL (2005)
65   !! $Header$
66   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
[3]67   !!----------------------------------------------------------------------
68
69CONTAINS
70
71   SUBROUTINE opa_model
72      !!----------------------------------------------------------------------
73      !!                     ***  ROUTINE opa  ***
74      !!
75      !! ** Purpose :   opa solves the primitive equations on an orthogonal
76      !!      curvilinear mesh on the sphere.
77      !!
78      !! ** Method  : - model general initialization
79      !!              - launch the time-stepping (stp routine)
80      !!
81      !! References :
82      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
83      !!              internal report, IPSL.
84      !!
85      !! History :
86      !!   4.0  !  90-10  (C. Levy, G. Madec)  Original code
87      !!   7.0  !  91-11  (M. Imbard, C. Levy, G. Madec)
88      !!   7.1  !  93-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
89      !!                   M. Guyon, A. Lazar, P. Delecluse, C. Perigaud,
90      !!                   G. Caniaux, B. Colot, C. Maes ) release 7.1
91      !!        !  92-06  (L.Terray) coupling implementation
92      !!        !  93-11  (M.A. Filiberti) IGLOO sea-ice
93      !!   8.0  !  96-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
94      !!                   M. Guyon, A. Lazar, P. Delecluse, L.Terray,
95      !!                   M.A. Filiberti, J. Vialar, A.M. Treguier,
96      !!                   M. Levy)  release 8.0
97      !!   8.1  !  97-06  (M. Imbard, G. Madec)
98      !!   8.2  !  99-11  (M. Imbard, H. Goosse)  LIM sea-ice model
99      !!        !  99-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
100      !!        !  00-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
101      !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules
[216]102      !!    "   !  04-08  (C. Talandier) New trends organization
[253]103      !!    "   !  05-06  (C. Ethe) Add the 1D configuration possibility
[359]104      !!    "   !  05-11  (V. Garnier) Surface pressure gradient organization
[3]105      !!----------------------------------------------------------------------
106      !! * Local declarations
107      INTEGER ::   istp       ! time step index
[389]108      CHARACTER (len=64) ::        &
109         cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
110      !!----------------------------------------------------------------------
111
[392]112#if defined key_agrif
[389]113
114      Call Agrif_Init_Grids()
115#endif
116     
117      Call opa_init  ! Initializations
118
119      IF( lk_cfg_1d  )  THEN
120         istp = nit000
121         DO WHILE ( istp <= nitend .AND. nstop == 0 )
[392]122#if defined key_agrif
[389]123            CALL Agrif_Step(stp_1d)
124#else
125            CALL stp_1d( istp )
126#endif
127            istp = istp + 1
128         END DO
129      ELSE
130         istp = nit000
131         DO WHILE ( istp <= nitend .AND. nstop == 0 )
[392]132#if defined key_agrif
[389]133            CALL Agrif_Step(stp)
134#else
135            CALL stp( istp )
136#endif
137            istp = istp + 1
138         END DO
139      ENDIF
140      !                                     ! ========= !
141      !                                     !  Job end  !
142      !                                     ! ========= !
143
144      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
145
146      IF( nstop /= 0 ) THEN                 ! error print
147      IF(lwp) WRITE(numout,cform_err)
148      IF(lwp) WRITE(numout,*) nstop, ' error have been found' 
149      ENDIF
150
151      CALL opa_closefile
152      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
153
154   END SUBROUTINE opa_model
155
156
157   SUBROUTINE opa_flg
158      !!----------------------------------------------------------------------
159      !!                     ***  ROUTINE opa  ***
160      !!
161      !! ** Purpose :   Initialize logical flags that control the choice of
162      !!      some algorithm or control print
163      !!
164      !! ** Method  :    Read in namilist namflg logical flags
165      !!
166      !! History :
167      !!   9.0  !  03-11  (G. Madec)  Original code
168      !!----------------------------------------------------------------------
169      !! * Local declarations
170
171      NAMELIST/namflg/ ln_dynhpg_imp
172      !!----------------------------------------------------------------------
173
174      ! Read Namelist namflg : algorithm FLaG
175      ! --------------------
176      REWIND ( numnam )
177      READ   ( numnam, namflg )
178
179      ! Parameter control and print
180      ! ---------------------------
181      ! Control print
182      IF(lwp) THEN
183         WRITE(numout,*)
184         WRITE(numout,*) 'opa_flg : algorithm flag initialization'
185         WRITE(numout,*) '~~~~~~~'
186         WRITE(numout,*) '          Namelist namflg : set algorithm flags'
187         WRITE(numout,*)
188         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp
189         WRITE(numout,*) '             hydrostatic pressure gradient'
190      ENDIF
191
192   END SUBROUTINE opa_flg
193
194   SUBROUTINE opa_closefile
195      !!----------------------------------------------------------------------
196      !!                     ***  ROUTINE opa_closefile  ***
197      !!
198      !! ** Purpose :   Close the files
199      !!           
200      !! ** Method  :
201      !!
202      !! History :
203      !!   9.0  !  05-01  (O. Le Galloudec)  Original code
204      !!----------------------------------------------------------------------
205      !! * Modules used
206      USE dtatem        ! temperature data
207      USE dtasal        ! salinity data
208      USE dtasst        ! sea surface temperature data
209      !!----------------------------------------------------------------------
210
211      IF ( lk_mpp ) CALL mppsync
212
213      ! 1. Unit close
214      ! -------------
215
216      CLOSE( numnam )       ! namelist
217      CLOSE( numout )       ! standard model output file
218      CLOSE( numstp )       ! time-step file
219      CLOSE( numwrs )       ! ocean restart file
220
221      IF( lk_dtatem )   CLOSE( numtdt )
222      IF( lk_dtasal )   CLOSE( numsdt )
223      IF( lk_dtasst )   CLOSE( numsst )
224
225      IF(lwp) CLOSE( numsol )
226
227      IF( lk_cpl ) THEN
228         CLOSE( numlhf )
229         CLOSE( numlts )
230      ENDIF
231
232      CLOSE( numwri )
233
234   END SUBROUTINE opa_closefile
235
236   !!======================================================================
237   SUBROUTINE opa_init
238      !!----------------------------------------------------------------------
239      !!                     ***  ROUTINE opa_init  ***
240      !!
241      !! ** Purpose :   initialization of the opa model
242      !!
243      !! ** Method  :
244      !!
245      !! References :
246      !!----------------------------------------------------------------------
247      !! * Local declarations
248
[3]249#if defined key_coupled
250      INTEGER ::   itro, istp0        ! ???
251#endif
252      CHARACTER (len=64) ::        &
253         cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
[389]254      CHARACTER (len=20) :: namelistname
[231]255      CHARACTER (len=28) :: file_out
[3]256      !!----------------------------------------------------------------------
[389]257
[3]258      ! Initializations
259      ! ===============
[231]260
261      file_out = 'ocean.output'
[3]262     
263      ! open listing and namelist units
264      IF ( numout /= 0 .AND. numout /= 6 ) THEN
[389]265         CALL ctlopn(numout,file_out,'UNKNOWN', 'FORMATTED',   &
266                      'SEQUENTIAL',1,numout,.FALSE.,1)
267!         OPEN( UNIT=numout, FILE=TRIM(file_out), FORM='FORMATTED' )
[3]268      ENDIF
269
[389]270      namelistname = 'namelist'
271      CALL ctlopn(numnam,namelistname,'OLD', 'FORMATTED', 'SEQUENTIAL',   &
272                     1,numout,.FALSE.,1)
273!!!!      OPEN( UNIT=numnam, FILE='namelist', FORM='FORMATTED', STATUS='OLD' )
[3]274
[300]275      WRITE(numout,*)
276      WRITE(numout,*) '                 L O D Y C - I P S L'
277      WRITE(numout,*) '                     O P A model'
278      WRITE(numout,*) '            Ocean General Circulation Model'
279      WRITE(numout,*) '               version OPA 9.0  (2005) '
280      WRITE(numout,*)
281      WRITE(numout,*)
[231]282
[3]283      ! Nodes selection
284      narea = mynode()
285      narea = narea + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
286      lwp   = narea == 1
287
288      !                                     ! ============================== !
289      !                                     !  Model general initialization  !
290      !                                     ! ============================== !
291
292      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
293
294                                            ! Domain decomposition
295      IF( jpni*jpnj == jpnij ) THEN
296         CALL mpp_init                          ! standard cutting out
297      ELSE
298         CALL mpp_init2                         ! eliminate land processors
299      ENDIF
300     
301      CALL phy_cst                          ! Physical constants
302
303      CALL dom_cfg                          ! Domain configuration
304     
305      CALL dom_init                         ! Domain
[258]306      IF( ln_ctl )      CALL prt_ctl_init   ! Print control
307
[253]308      IF( lk_cfg_1d )   CALL fcorio_1d      ! redefine Coriolis at T-point
[3]309
[253]310      IF( lk_obc    )   CALL obc_init       ! Open boundaries
311
[359]312      IF( lk_dynspg_flt .OR. lk_dynspg_rl ) THEN
[389]313      CALL solver_init                      ! Elliptic solver
[359]314      ENDIF
[3]315
316      CALL day( nit000 )                    ! Calendar
317
318      CALL istate_init                      ! ocean initial state (Dynamics and tracers)
319!!add
320                       CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities
321
322                       CALL bn2( tb, sb, rn2 )              ! before Brunt-Vaisala frequency
323
[253]324      IF( lk_zps .AND. .NOT. lk_cfg_1d )   &
325         &             CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative
326                                            gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level
327                                            gtv, gsv, grv )
[3]328
329!!add
330
331      CALL oc_fz_pt                         ! Surface freezing point
332
333#if defined key_ice_lim
334      CALL ice_init                         ! Sea ice model
335#endif
336
[88]337      !                                     ! Ocean scheme
338
339      CALL opa_flg                              ! Choice of algorithms
340
[3]341      !                                     ! Ocean physics
342
[88]343      CALL tra_qsr_init                         ! Solar radiation penetration
[3]344
345      CALL ldf_dyn_init                         ! Lateral ocean momentum physics
346
347      CALL ldf_tra_init                         ! Lateral ocean tracer physics
348
349      CALL zdf_init                             ! Vertical ocean physics
350
351      !                                     ! Ocean trends
[216]352      ! Control parameters
353      IF( lk_trdtra .OR. lk_trdmld )   l_trdtra = .TRUE.
354      IF( lk_trddyn .OR. lk_trdvor )   l_trddyn = .TRUE.
355
356      IF( lk_trddyn .OR. lk_trdtra )   &
357         &            CALL trd_icp_init         ! active tracers and/or momentum
358
359      IF( lk_trdmld ) CALL trd_mld_init         ! mixed layer
360
361      IF( lk_trdvor ) CALL trd_vor_init         ! vorticity
362
[281]363#if defined key_passivetrc
364      CALL ini_trc                           ! Passive tracers
365#endif
366
[3]367#if defined key_coupled
368      itro  = nitend - nit000 + 1           ! Coupled
369      istp0 = NINT( rdt )
370      CALL cpl_init( itro, nexco, istp0 )   ! Signal processing and process id exchange
371#endif
372
373      CALL flx_fwb_init                     ! FreshWater Budget correction
374
[190]375      CALL dia_ptr_init                     ! Poleward TRansports initialization
[3]376
377      !                                     ! =============== !
378      !                                     !  time stepping  !
379      !                                     ! =============== !
380
381      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
382
[253]383      IF( lk_cfg_1d  )  THEN
384         CALL init_1d
385      ENDIF
[389]386   END SUBROUTINE opa_init
[3]387   !!======================================================================
388END MODULE opa
Note: See TracBrowser for help on using the repository browser.