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

Last change on this file since 88 was 88, checked in by opalod, 20 years ago

CT : UPDATE057 : # General syntax, alignement, comments corrections

# l_ctl alone replace the set (l_ctl .AND. lwp)
# Add of diagnostics which are activated when using l_ctl logical

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 10.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   !!   opa_flg        : initialisation of algorithm flag
10   !!----------------------------------------------------------------------
11   !! * Modules used
12   USE dom_oce         ! ocean space domain variables
13   USE oce             ! dynamics and tracers variables
14   USE daymod          ! calendar
15   USE in_out_manager  ! I/O manager
16   USE lib_mpp         ! distributed memory computing
17
18   USE domcfg          ! domain configuration               (dom_cfg routine)
19   USE mppini          ! shared/distributed memory setting (mpp_init routine)
20   USE domain          ! domain initialization             (dom_init routine)
21   USE obc_par         ! open boundary cond. parameters
22   USE obcini          ! open boundary cond. initialization (obc_ini routine)
23   USE solver          ! solver initialization          (solver_init routine)
24   USE istate          ! initial state setting          (istate_init routine)
25   USE eosbn2          ! equation of state            (eos bn2 routine)
26   USE zpshde          ! partial step: hor. derivative (zps_hde routine)
27
28   ! ocean physics
29   USE traqsr          ! solar radiation penetration   (tra_qsr_init routine)
30   USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine)
31   USE ldftra          ! lateral diffusivity setting    (ldftra_init routine)
32   USE zdfini
33!!!USE zdf_oce         ! ocean vertical physics            (zdf_init routine)
34
35   USE phycst          ! physical constant                  (par_cst routine)
36   USE iceini          ! initialization of sea-ice         (ice_init routine)
37   USE cpl             ! coupled ocean/atmos.              (cpl_init routine)
38   USE ocfzpt          ! ocean freezing point              (oc_fz_pt routine)
39   USE trddyn          ! ocean momentum trends         (trd_dyn_init routine)
40   USE trdtra          ! ocean active tracer trends    (trd_tra_init routine)
41   USE trdmld          ! ocean active tracer mixed layer trend ???
42   USE flxfwb          !
43
44   USE ptr             ! poleward transports           (dia_ptr_init routine)
45
46   USE step            ! OPA time-stepping                  (stp     routine)
47
48   IMPLICIT NONE
49   PRIVATE
50
51   !! * Routine accessibility
52   PUBLIC opa_model      ! called by model.F90
53   !!----------------------------------------------------------------------
54   !!  OPA 9.0 , LODYC-IPSL (2003)
55   !!----------------------------------------------------------------------
56
57CONTAINS
58
59   SUBROUTINE opa_model
60      !!----------------------------------------------------------------------
61      !!                     ***  ROUTINE opa  ***
62      !!
63      !! ** Purpose :   opa solves the primitive equations on an orthogonal
64      !!      curvilinear mesh on the sphere.
65      !!
66      !! ** Method  : - model general initialization
67      !!              - launch the time-stepping (stp routine)
68      !!
69      !! References :
70      !!      Madec, Delecluse,Imbard, and Levy, 1997: reference manual.
71      !!              internal report, IPSL.
72      !!
73      !! History :
74      !!   4.0  !  90-10  (C. Levy, G. Madec)  Original code
75      !!   7.0  !  91-11  (M. Imbard, C. Levy, G. Madec)
76      !!   7.1  !  93-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
77      !!                   M. Guyon, A. Lazar, P. Delecluse, C. Perigaud,
78      !!                   G. Caniaux, B. Colot, C. Maes ) release 7.1
79      !!        !  92-06  (L.Terray) coupling implementation
80      !!        !  93-11  (M.A. Filiberti) IGLOO sea-ice
81      !!   8.0  !  96-03  (M. Imbard, C. Levy, G. Madec, O. Marti,
82      !!                   M. Guyon, A. Lazar, P. Delecluse, L.Terray,
83      !!                   M.A. Filiberti, J. Vialar, A.M. Treguier,
84      !!                   M. Levy)  release 8.0
85      !!   8.1  !  97-06  (M. Imbard, G. Madec)
86      !!   8.2  !  99-11  (M. Imbard, H. Goosse)  LIM sea-ice model
87      !!        !  99-12  (V. Thierry, A-M. Treguier, M. Imbard, M-A. Foujols)  OPEN-MP
88      !!        !  00-07  (J-M Molines, M. Imbard)  Open Boundary Conditions  (CLIPPER)
89      !!   9.0  !  02-08  (G. Madec)  F90: Free form and modules
90      !!----------------------------------------------------------------------
91      !! * Local declarations
92      INTEGER ::   istp       ! time step index
93#if defined key_coupled
94      INTEGER ::   itro, istp0        ! ???
95#endif
96      CHARACTER (len=64) ::        &
97         cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing
98      !!----------------------------------------------------------------------
99     
100     
101      ! Initializations
102      ! ===============
103     
104      ! open listing and namelist units
105      IF ( numout /= 0 .AND. numout /= 6 ) THEN
106         OPEN( UNIT=numout, FILE='ocean.output', FORM='FORMATTED' )
107      ENDIF
108      IF( lk_mpp )   OPEN( UNIT=nummpp, FILE='mpp.output', FORM='FORMATTED' )
109
110
111      ! Nodes selection
112      narea = mynode()
113      narea = narea + 1    ! mynode return the rank of proc (0 --> jpnij -1 )
114      lwp   = narea == 1
115
116      OPEN( UNIT=numnam, FILE='namelist', FORM='FORMATTED', STATUS='OLD' )
117
118      IF(lwp) THEN
119         WRITE(numout,*)
120         WRITE(numout,*) '                 L O D Y C - I P S L'
121         WRITE(numout,*) '                     O P A model'
122         WRITE(numout,*) '            Ocean General Circulation Model'
123         WRITE(numout,*) '               version OPA 9.0  (2003)'
124         WRITE(numout,*)
125      ENDIF
126
127      !                                     ! ============================== !
128      !                                     !  Model general initialization  !
129      !                                     ! ============================== !
130
131      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
132
133                                            ! Domain decomposition
134      IF( jpni*jpnj == jpnij ) THEN
135         CALL mpp_init                          ! standard cutting out
136      ELSE
137         CALL mpp_init2                         ! eliminate land processors
138      ENDIF
139     
140      CALL phy_cst                          ! Physical constants
141
142      CALL dom_cfg                          ! Domain configuration
143     
144      CALL dom_init                         ! Domain
145
146      IF( lk_obc    )   CALL obc_init        ! Open boundaries
147
148      CALL solver_init                      ! Elliptic solver
149
150      CALL day( nit000 )                    ! Calendar
151
152      CALL istate_init                      ! ocean initial state (Dynamics and tracers)
153!!add
154                       CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities
155
156                       CALL bn2( tb, sb, rn2 )              ! before Brunt-Vaisala frequency
157
158      IF( lk_zps    )   CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative
159                                          gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level
160                                          gtv, gsv, grv )
161
162!!add
163
164      CALL oc_fz_pt                         ! Surface freezing point
165
166#if defined key_ice_lim
167      CALL ice_init                         ! Sea ice model
168#endif
169
170#if defined key_passivetrc
171      CALL initrc                           ! Passive tracers
172#endif
173
174      !                                     ! Ocean scheme
175
176      CALL opa_flg                              ! Choice of algorithms
177
178      !                                     ! Ocean physics
179
180      CALL tra_qsr_init                         ! Solar radiation penetration
181
182      CALL ldf_dyn_init                         ! Lateral ocean momentum physics
183
184      CALL ldf_tra_init                         ! Lateral ocean tracer physics
185
186      CALL zdf_init                             ! Vertical ocean physics
187
188      !                                     ! Ocean trends
189      IF( lk_trddyn )   CALL trd_dyn_init        ! momentum     
190      IF( lk_trdtra .OR. lk_trdmld )   &
191         &             CALL trd_tra_init        ! active tracers
192#if defined key_coupled
193      itro  = nitend - nit000 + 1           ! Coupled
194      istp0 = NINT( rdt )
195      CALL cpl_init( itro, nexco, istp0 )   ! Signal processing and process id exchange
196#endif
197
198      CALL flx_fwb_init                     ! FreshWater Budget correction
199
200#if defined key_diaptr
201      CALL dia_ptr_init                     ! Poleward TRansports
202#endif
203
204      !                                     ! =============== !
205      !                                     !  time stepping  !
206      !                                     ! =============== !
207
208      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
209
210      istp = nit000
211      DO WHILE ( istp <= nitend .AND. nstop == 0 )
212         CALL stp( istp )
213         istp = istp + 1
214      END DO
215      !                                     ! ========= !
216      !                                     !  Job end  !
217      !                                     ! ========= !
218
219      IF(lwp) WRITE(numout,cform_aaa)       ! Flag AAAAAAA
220
221      IF( nstop /= 0 ) THEN                 ! error print
222      IF(lwp) WRITE(numout,cform_err)
223      IF(lwp) WRITE(numout,*) nstop, ' error have been found' 
224      ENDIF
225
226      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp)
227
228   END SUBROUTINE opa_model
229
230
231   SUBROUTINE opa_flg
232      !!----------------------------------------------------------------------
233      !!                     ***  ROUTINE opa  ***
234      !!
235      !! ** Purpose :   Initialize logical flags that control the choice of
236      !!      some algorithm or control print
237      !!
238      !! ** Method  :    Read in namilist namflg logical flags
239      !!
240      !! History :
241      !!   9.0  !  03-11  (G. Madec)  Original code
242      !!----------------------------------------------------------------------
243      !! * Local declarations
244
245      NAMELIST/namflg/ ln_dynhpg_imp
246      !!----------------------------------------------------------------------
247
248      ! Read Namelist namflg : algorithm FLaG
249      ! --------------------
250      REWIND ( numnam )
251      READ   ( numnam, namflg )
252
253      ! Parameter control and print
254      ! ---------------------------
255      ! Control print
256      IF(lwp) THEN
257         WRITE(numout,*)
258         WRITE(numout,*) 'opa_flg : algorithm flag initialization'
259         WRITE(numout,*) '~~~~~~~'
260         WRITE(numout,*) '          Namelist namflg : set algorithm flags'
261         WRITE(numout,*)
262         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp
263         WRITE(numout,*) '             hydrostatic pressure gradient'
264      ENDIF
265
266   END SUBROUTINE opa_flg
267
268   !!======================================================================
269END MODULE opa
Note: See TracBrowser for help on using the repository browser.