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 branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/SOL – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/SOL/solver.F90 @ 4460

Last change on this file since 4460 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 6.3 KB
Line 
1MODULE solver
2   !!======================================================================
3   !!                     ***  MODULE  solver  ***
4   !! Ocean solver :  initialization of ocean solver
5   !!=====================================================================
6   !! History :  OPA  ! 1990-10  (G. Madec)  Original code           
7   !!                 ! 1993-02  (O. Marti)                         
8   !!                 ! 1997-02  (G. Madec)  local depth inverse computation
9   !!                 ! 1998-10  (G. Roullet, G. Madec)  free surface
10   !!   NEMO     1.0  ! 2003-07  (G. Madec)  free form, F90
11   !!            3.2  ! 2009-07  (R. Benshila) suppression of rigid-lid & FETI solver
12   !!----------------------------------------------------------------------
13#if defined key_dynspg_flt   ||   defined key_esopa 
14   !!----------------------------------------------------------------------
15   !!   'key_dynspg_flt'                              filtered free surface
16   !!----------------------------------------------------------------------
17   !!   solver_init: solver initialization
18   !!----------------------------------------------------------------------
19   USE oce             ! ocean dynamics and tracers variables
20   USE dom_oce         ! ocean space and time domain variables
21   USE zdf_oce         ! ocean vertical physics variables
22   USE sol_oce         ! solver variables
23   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient
24   USE solmat          ! matrix of the solver
25   USE obc_oce         ! Lateral open boundary condition
26   USE in_out_manager  ! I/O manager
27   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
28   USE lib_mpp         ! MPP library
29
30   IMPLICIT NONE
31
32   !! * Control permutation of array indices
33#  include "oce_ftrans.h90"
34#  include "dom_oce_ftrans.h90"
35#  include "zdf_oce_ftrans.h90"
36#  include "obc_oce_ftrans.h90"
37
38   !!----------------------------------------------------------------------
39   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
40   !! $Id$
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44
45   SUBROUTINE solver_init( kt )
46      !!----------------------------------------------------------------------
47      !!                  ***  ROUTINE solver_init  ***
48      !!                   
49      !! ** Purpose :   Initialization of the elliptic solver
50      !!     
51      !! ** Method  :   a solver is required when using the filtered free
52      !!              surface.
53      !!
54      !! ** Action  : - c_solver_pt : nature of the gridpoint at which the solver is applied
55      !!
56      !! References : Jensen, 1986: Adv. Phys. Oceanogr. Num. Mod.,Ed. O Brien,87-110.
57      !!----------------------------------------------------------------------
58      INTEGER, INTENT(in) :: kt
59      !!
60      NAMELIST/namsol/ nn_solv, nn_sol_arp, nn_nmin, nn_nmax, nn_nmod, rn_eps, rn_resmax, rn_sor
61      !!----------------------------------------------------------------------
62
63      IF(lwp) THEN                  !* open elliptic solver statistics file (only on the printing processors)
64         CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
65      ENDIF
66
67      REWIND( numnam )              !* Namelist namsol : elliptic solver / free surface
68      READ  ( numnam, namsol )
69
70      IF(lwp) THEN                  !* Control print
71         WRITE(numout,*)
72         WRITE(numout,*) 'solver_init : solver to compute the surface pressure gradient'
73         WRITE(numout,*) '~~~~~~~~~~~'
74         WRITE(numout,*) '   Namelist namsol : set solver parameters'
75         WRITE(numout,*) '      type of elliptic solver            nn_solv    = ', nn_solv
76         WRITE(numout,*) '      absolute/relative (0/1) precision  nn_sol_arp = ', nn_sol_arp
77         WRITE(numout,*) '      minimum iterations for solver      nn_nmin    = ', nn_nmin
78         WRITE(numout,*) '      maximum iterations for solver      nn_nmax    = ', nn_nmax
79         WRITE(numout,*) '      frequency for test                 nn_nmod    = ', nn_nmod
80         WRITE(numout,*) '      absolute precision of solver       rn_eps     = ', rn_eps
81         WRITE(numout,*) '      absolute precision for SOR solver  rn_resmax  = ', rn_resmax
82         WRITE(numout,*) '      optimal coefficient of sor         rn_sor     = ', rn_sor
83         WRITE(numout,*)
84      ENDIF
85      eps = rn_eps
86
87      !                              ! allocate solver arrays
88      IF( sol_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'solver_init : unable to allocate sol_oce arrays' )
89
90      SELECT CASE( nn_solv )          !* parameter check
91      !
92      CASE ( 1 )                          ! preconditioned conjugate gradient solver
93         IF(lwp) WRITE(numout,*) '   a preconditioned conjugate gradient solver is used'
94         IF( jpr2di /= 0 .AND. jpr2dj /= 0 )   CALL ctl_stop( ' jpr2di and jpr2dj should be equal to zero' )
95         !
96      CASE ( 2 )                          ! successive-over-relaxation solver
97         IF(lwp) WRITE(numout,*) '   a successive-over-relaxation solver with extra outer halo is used'
98         IF(lwp) WRITE(numout,*) '   with jpr2di =', jpr2di, ' and  jpr2dj =', jpr2dj
99         IF( .NOT. lk_mpp .AND. jpr2di /= 0 .AND. jpr2dj /= 0 ) THEN
100             CALL ctl_stop( 'jpr2di and jpr2dj are not equal to zero',   &
101             &              'In this case the algorithm should be used only with the key_mpp_... option' )
102         ELSE
103            IF( ( ( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 ) .OR. ( jpni /= 1 ) ) &
104              &  .AND. ( jpr2di /= jpr2dj ) )   CALL ctl_stop( 'jpr2di should be equal to jpr2dj' )
105         ENDIF
106         !
107      CASE DEFAULT                        ! error in parameter
108         WRITE(ctmp1,*) '          bad flag value for nn_solv = ', nn_solv
109         CALL ctl_stop( ctmp1 )
110      END SELECT
111      !
112
113      !                             !* Grid-point at which the solver is applied
114!!gm  c_solver_pt should be removed: nomore bsf, only T-point is used
115      c_solver_pt = 'T'                   ! always T-point (ssh solver only, not anymore bsf)
116
117      CALL sol_mat( kt )            !* Construction of the elliptic system matrix
118      !
119   END SUBROUTINE solver_init
120#endif
121
122   !!======================================================================
123END MODULE solver
Note: See TracBrowser for help on using the repository browser.