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.
solver.F90 in trunk/NEMO/OPA_SRC/SOL – NEMO

source: trunk/NEMO/OPA_SRC/SOL/solver.F90 @ 3

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

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 8.1 KB
Line 
1MODULE solver
2   !!======================================================================
3   !!                     ***  MODULE  solver  ***
4   !! Ocean solver :  initialization of ocean solver
5   !!=====================================================================
6
7   !!----------------------------------------------------------------------
8   !!   solver_init: solver initialization
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce             ! ocean dynamics and tracers variables
12   USE dom_oce         ! ocean space and time domain variables
13   USE zdf_oce         ! ocean vertical physics variables
14   USE sol_oce         ! solver variables
15   USE solmat          ! ???
16   USE solisl          ! ???
17   USE obc_oce         ! Lateral open boundary condition
18   USE in_out_manager  ! I/O manager
19   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
20
21   IMPLICIT NONE
22
23   !!----------------------------------------------------------------------
24   !!   OPA 9.0 , LODYC-IPSL  (2003)
25   !!----------------------------------------------------------------------
26
27CONTAINS
28
29   SUBROUTINE solver_init
30      !!----------------------------------------------------------------------
31      !!                  ***  ROUTINE solver_init  ***
32      !!                   
33      !! ** Purpose :   Initialization for the solver of the elliptic equation:
34      !!       * default option: barotropic stream function system
35      !!         and islands initialization (if l_isl=T)
36      !!       * key_dynspg_fsc = T : transport divergence system. No specific
37      !!         treatment of islands.
38      !!     
39      !! ** Method :
40      !!       - Compute the local depth of the water column at u- and v-point
41      !!      (key_dynspg_fsc = T) or its inverse (key_dynspg_rl = T).
42      !!      The local depth of the water column is computed by summing
43      !!      the vertical scale factors. For its inverse, the thickness of
44      !!      the first model level is imposed as lower bound. The inverse of
45      !!      this depth is THEN taken and masked, so that the inverse of the
46      !!      local depth is zero when the local depth is zero.
47      !!       - Construct the matrix of the elliptic system by a call to
48      !!      solmat.F routine.
49      !!       - island (if l_isl=T)
50      !!            isl_dom: find islands from the bathymetry file
51      !!            isl_bsf: compute the island barotropic stream function
52      !!            isl_mat: compute the inverse island matrix
53      !!            set mbathy to the number of non-zero w-levels of a water
54      !!            column (the minimum value of mbathy is 2):
55      !!                  mbathy = min( mbathy, 1 ) + 1
56      !!
57      !! ** Action : - hur, hvr : masked inverse of the local depth at
58      !!                                u- and v-point. (key_dynspg_rl = T)
59      !!             - hu, hv   : masked local depth at u- and v- points
60      !!                                (key_dynspg_fsc = T)
61      !! References :
62      !!      Jensen, 1986: adv. phys. oceanogr. num. mod.,ed. o brien,87-110.
63      !!      Madec & Marti, 1990: internal rep. LODYC, 90/03., 29pp.
64      !!
65      !! History :
66      !!        !  90-10  (G. Madec)  Original code           
67      !!        !  93-02  (O. Marti)                         
68      !!        !  97-02  (G. Madec)  local depth inverse computation
69      !!        !  98-10  (G. Roullet, G. Madec)  free surface
70      !!   9.0  !  03-07  (G. Madec)  free form, F90
71      !!----------------------------------------------------------------------
72      !! * Local declarations
73      INTEGER :: ji, jj   ! dummy loop indices
74
75      NAMELIST/namsol/ nsolv, nmax, eps, sor, epsisl, nmisl, rnu
76      !!----------------------------------------------------------------------
77
78      IF(lwp) WRITE(numout,*)
79      IF(lwp) WRITE(numout,*) 'ini_sol : solver to compute the surface pressure gradient'
80      IF(lwp) WRITE(numout,*) '~~~~~~~'
81
82      ! open elliptic solver statistics file
83      CALL ctlopn( numsol, 'solver.stat', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL',   &
84                   1, numout, lwp, 1 )
85
86
87      ! 0. Define the solver parameters
88      !    ----------------------------
89      ! Namelist namsol : elliptic solver / islands / free surface
90      REWIND( numnam )
91      READ  ( numnam, namsol )
92
93#if defined key_feti
94      ! FETI algorithm, we force nsolv at 3
95      nsolv = 3
96#endif
97
98
99      ! 0. Parameter control and print
100      !    ---------------------------
101
102      ! Control print
103      IF(lwp) WRITE(numout,*) '          Namelist namsol : set solver parameters'
104
105      IF(lwp) THEN
106         WRITE(numout,*)
107         WRITE(numout,*) '             type of elliptic solver        nsolv  = ', nsolv
108         WRITE(numout,*) '             maximum iterations for solver  nmax   = ', nmax
109         WRITE(numout,*) '             absolute precision of solver   eps    = ', eps
110         WRITE(numout,*) '             optimal coefficient of sor     sor    = ', sor
111         IF(l_isl) WRITE(numout,*) '             absolute precision stream fct  epsisl = ', epsisl
112         IF(l_isl) WRITE(numout,*) '             maximum pcg iterations island  nmisl  = ', nmisl
113         WRITE(numout,*) '             free surface parameter         rnu    = ', rnu
114         WRITE(numout,*)
115      ENDIF
116
117#if defined key_dynspg_fsc 
118         IF(lwp) WRITE(numout,*)
119         IF(lwp) WRITE(numout,*) '          *** free surface formulation'
120         IF( l_isl ) THEN
121            IF(lwp) WRITE(numout,cform_err)
122            IF(lwp) WRITE(numout,*) ' key_islands inconsistent with key_dynspg_fsc'
123            nstop = nstop + 1
124         ENDIF
125#endif
126#if defined key_dynspg_rl
127         IF(lwp) WRITE(numout,*)
128         IF(lwp) WRITE(numout,*) '          *** Rigid lid formulation'
129#endif
130#if defined key_dynspg_fsc && defined key_dynspg_rl
131         IF(lwp) WRITE(numout,cform_err)
132         IF(lwp) WRITE(numout,*) '          Chose between free surface or rigid-lid, not both'
133         nstop = nstop + 1
134#endif
135
136      SELECT CASE ( nsolv )
137
138      CASE ( 1 )                ! preconditioned conjugate gradient solver
139         IF(lwp) WRITE(numout,*) '          use a preconditioned conjugate gradient solver'
140
141      CASE ( 2 )                ! successive-over-relaxation solver
142         IF(lwp) WRITE(numout,*) '          use a successive-over-relaxation solver'
143
144      CASE ( 3 )                ! FETI solver
145         IF(lwp) WRITE(numout,*) '          use the FETI solver'
146#if ! defined key_mpp
147         IF(lwp) WRITE(numout,*) ' The FETI algorithm is used only with the key_mpp option'
148         nstop = nstop + 1
149#else
150         IF( jpnij == 1 ) THEN
151            IF(lwp) WRITE(numout,*) ' The FETI algorithm needs more than one processor'
152            nstop = nstop + 1
153         ENDIF
154#endif
155         
156      CASE DEFAULT
157         IF(lwp) WRITE(numout,cform_err)
158         IF(lwp) WRITE(numout,*) '          bad flag value for nsolv = ', nsolv
159         nstop = nstop + 1
160         
161      END SELECT
162
163
164      ! Construction of the elliptic system matrix
165      ! ------------------------------------------
166
167      CALL sol_mat
168
169
170      IF( l_isl ) THEN
171     
172         ! Islands in the domain
173         ! ---------------------
174
175         IF ( jpisl == 0 ) THEN
176             IF(lwp)WRITE(numout,cform_err)
177             IF(lwp)WRITE(numout,*) ' bad islands parameter jpisl =', jpisl
178             nstop = nstop + 1
179         ENDIF
180
181         ! open Island streamfunction statistic file
182         CALL ctlopn( numisp, 'islands.stat', 'UNKNOWN', 'FORMATTED', 'SEQUENTIAL',   &
183            &         1     , numout        , lwp      , 1                         )
184   
185         CALL isl_dom       ! Island identification
186
187         CALL isl_bsf       ! Island barotropic stream function
188
189         CALL isl_mat       ! Comput and invert the island matrix
190
191         ! mbathy set to the number of w-level (minimum value 2)
192         DO jj = 1, jpj
193            DO ji = 1, jpi
194               mbathy(ji,jj) = MAX( 1, mbathy(ji,jj) ) + 1
195            END DO
196         END DO
197
198      ENDIF
199
200   END SUBROUTINE solver_init
201
202   !!======================================================================
203END MODULE solver
Note: See TracBrowser for help on using the repository browser.