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 @ 503

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

nemo_v1_update_064 : CT : general trends update including the addition of mean windows analysis possibility in the mixed layer

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