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/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SOL – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/SOL/solver.F90 @ 13321

Last change on this file since 13321 was 11101, checked in by frrh, 5 years ago

Merge changes from Met Office GMED ticket 450 to reduce unnecessary
text output from NEMO.
This output, which is typically not switchable, is rarely of interest
in normal (non-debugging) runs and simply redunantley consumes extra
file space.
Further, the presence of this text output has been shown to
significantly degrade performance of models which are run during
Met Office HPC RAID (disk) checks.
The new code introduces switches which are configurable via the
changes made in the associated Met Office MOCI ticket 399.

File size: 7.1 KB
RevLine 
[3]1MODULE solver
2   !!======================================================================
3   !!                     ***  MODULE  solver  ***
4   !! Ocean solver :  initialization of ocean solver
5   !!=====================================================================
[1601]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
[3]12   !!----------------------------------------------------------------------
[1601]13#if defined key_dynspg_flt   ||   defined key_esopa 
14   !!----------------------------------------------------------------------
15   !!   'key_dynspg_flt'                              filtered free surface
16   !!----------------------------------------------------------------------
[3]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
[1601]23   USE dynspg_oce      ! choice/control of key cpp for surface pressure gradient
24   USE solmat          ! matrix of the solver
[3]25   USE in_out_manager  ! I/O manager
26   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
[2715]27   USE lib_mpp         ! MPP library
[3294]28   USE timing          ! timing
[3]29
30   IMPLICIT NONE
31
32   !!----------------------------------------------------------------------
[2528]33   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[6486]34   !! $Id$
[2715]35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[3]36   !!----------------------------------------------------------------------
37CONTAINS
38
[413]39   SUBROUTINE solver_init( kt )
[3]40      !!----------------------------------------------------------------------
41      !!                  ***  ROUTINE solver_init  ***
42      !!                   
[1601]43      !! ** Purpose :   Initialization of the elliptic solver
[3]44      !!     
[1601]45      !! ** Method  :   a solver is required when using the filtered free
46      !!              surface.
[3]47      !!
[1601]48      !! ** Action  : - c_solver_pt : nature of the gridpoint at which the solver is applied
[3]49      !!
[1601]50      !! References : Jensen, 1986: Adv. Phys. Oceanogr. Num. Mod.,Ed. O Brien,87-110.
[3]51      !!----------------------------------------------------------------------
[413]52      INTEGER, INTENT(in) :: kt
[4147]53      INTEGER             ::   ios       ! Local integer output status for namelist read
[1601]54      !!
55      NAMELIST/namsol/ nn_solv, nn_sol_arp, nn_nmin, nn_nmax, nn_nmod, rn_eps, rn_resmax, rn_sor
[3]56      !!----------------------------------------------------------------------
[3294]57      !
58      IF( nn_timing == 1 )  CALL timing_start('solver_init')
59      !
[3]60
[11101]61      IF(lwp .AND. (ln_ctl .OR. sn_cfctl%l_runstat)) THEN  !* open elliptic solver statistics file (only on the printing processors)
[1581]62         CALL ctl_opn( numsol, 'solver.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
63      ENDIF
[3]64
[4147]65      REWIND( numnam_ref )              ! Namelist namsol in reference namelist : Elliptic solver / free surface
66      READ  ( numnam_ref, namsol, IOSTAT = ios, ERR = 901)
67901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsol in reference namelist', lwp )
[3]68
[4147]69      REWIND( numnam_cfg )              ! Namelist namsol in configuration namelist : Elliptic solver / free surface
70      READ  ( numnam_cfg, namsol, IOSTAT = ios, ERR = 902 )
71902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsol in configuration namelist', lwp )
[11101]72      IF(lwm .AND. nprint > 2) WRITE ( numond, namsol )
[4147]73
[1601]74      IF(lwp) THEN                  !* Control print
[3]75         WRITE(numout,*)
[1601]76         WRITE(numout,*) 'solver_init : solver to compute the surface pressure gradient'
77         WRITE(numout,*) '~~~~~~~~~~~'
78         WRITE(numout,*) '   Namelist namsol : set solver parameters'
79         WRITE(numout,*) '      type of elliptic solver            nn_solv    = ', nn_solv
80         WRITE(numout,*) '      absolute/relative (0/1) precision  nn_sol_arp = ', nn_sol_arp
81         WRITE(numout,*) '      minimum iterations for solver      nn_nmin    = ', nn_nmin
82         WRITE(numout,*) '      maximum iterations for solver      nn_nmax    = ', nn_nmax
83         WRITE(numout,*) '      frequency for test                 nn_nmod    = ', nn_nmod
84         WRITE(numout,*) '      absolute precision of solver       rn_eps     = ', rn_eps
85         WRITE(numout,*) '      absolute precision for SOR solver  rn_resmax  = ', rn_resmax
86         WRITE(numout,*) '      optimal coefficient of sor         rn_sor     = ', rn_sor
87         WRITE(numout,*)
[11101]88         IF(lflush) CALL flush(numout)
[3]89      ENDIF
[1601]90      eps = rn_eps
[3]91
[2715]92      !                              ! allocate solver arrays
[3764]93      IF( .NOT. lk_agrif .OR. .NOT. ln_rstart) THEN
94         IF( sol_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'solver_init : unable to allocate sol_oce arrays' )
[6498]95         gcx (:,:) = 0.e0
96         gcxb(:,:) = 0.e0
[3764]97      ENDIF
[2715]98
[1601]99      SELECT CASE( nn_solv )          !* parameter check
100      !
101      CASE ( 1 )                          ! preconditioned conjugate gradient solver
102         IF(lwp) WRITE(numout,*) '   a preconditioned conjugate gradient solver is used'
[11101]103         IF(lwp .AND. lflush) CALL flush(numout)
[1601]104         IF( jpr2di /= 0 .AND. jpr2dj /= 0 )   CALL ctl_stop( ' jpr2di and jpr2dj should be equal to zero' )
105         !
106      CASE ( 2 )                          ! successive-over-relaxation solver
107         IF(lwp) WRITE(numout,*) '   a successive-over-relaxation solver with extra outer halo is used'
108         IF(lwp) WRITE(numout,*) '   with jpr2di =', jpr2di, ' and  jpr2dj =', jpr2dj
[11101]109         IF(lwp .AND. lflush) CALL flush(numout)
[784]110         IF( .NOT. lk_mpp .AND. jpr2di /= 0 .AND. jpr2dj /= 0 ) THEN
[1601]111             CALL ctl_stop( 'jpr2di and jpr2dj are not equal to zero',   &
112             &              'In this case the algorithm should be used only with the key_mpp_... option' )
[784]113         ELSE
114            IF( ( ( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 ) .OR. ( jpni /= 1 ) ) &
[1601]115              &  .AND. ( jpr2di /= jpr2dj ) )   CALL ctl_stop( 'jpr2di should be equal to jpr2dj' )
[784]116         ENDIF
[1601]117         !
118      CASE DEFAULT                        ! error in parameter
119         WRITE(ctmp1,*) '          bad flag value for nn_solv = ', nn_solv
[474]120         CALL ctl_stop( ctmp1 )
[3]121      END SELECT
[1601]122      !
[531]123
[1601]124      !                             !* Grid-point at which the solver is applied
125!!gm  c_solver_pt should be removed: nomore bsf, only T-point is used
[2528]126      c_solver_pt = 'T'                   ! always T-point (ssh solver only, not anymore bsf)
[16]127
[1601]128      CALL sol_mat( kt )            !* Construction of the elliptic system matrix
[1556]129      !
[3294]130      IF( nn_timing == 1 )  CALL timing_stop('solver_init')
131      !
[3]132   END SUBROUTINE solver_init
[1601]133#endif
[3]134
135   !!======================================================================
136END MODULE solver
Note: See TracBrowser for help on using the repository browser.