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

Last change on this file since 219 was 219, checked in by opalod, 19 years ago

CT : UPDATE154 : move the closing file step done in mppstop subroutine (in lib_mpp.F90) in the subroutine opa_closefile (in opa.F90)

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