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

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

nemo_v1_update_001 : Add the 1D configuration possibility

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