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.
sol_oce.F90 in branches/UKMO/dev_r5518_DMP_TOOLS/NEMOGCM/NEMO/OPA_SRC/SOL – NEMO

source: branches/UKMO/dev_r5518_DMP_TOOLS/NEMOGCM/NEMO/OPA_SRC/SOL/sol_oce.F90 @ 10198

Last change on this file since 10198 was 10198, checked in by jenniewaters, 5 years ago

Strip out SVN keywords.

File size: 5.2 KB
Line 
1MODULE sol_oce
2   !!======================================================================
3   !!                    ***  MODULE  sol_oce  ***
4   !! Ocean solver :  elliptic solver variables defined in memory
5   !!======================================================================
6   !! History :  1.0  ! 2002-11  (G. Madec)  F90: Free form and module
7   !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   sol_oce_alloc : allocate the solver arrays
12   !!----------------------------------------------------------------------
13   USE par_oce        ! ocean parameters
14   USE in_out_manager ! I/O manager
15   USE lib_mpp        ! distributed memory computing
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   sol_oce_alloc   ! routine called in solver.F90
21
22   !                                 !!* Namelist namsol : elliptic solver *
23   INTEGER , PUBLIC ::   nn_solv      !: = 1/2 type of elliptic solver
24   INTEGER , PUBLIC ::   nn_sol_arp   !: = 0/1 absolute/relative precision convergence test
25   INTEGER , PUBLIC ::   nn_nmin      !: minimum of iterations for the SOR solver
26   INTEGER , PUBLIC ::   nn_nmax      !: maximum of iterations for the SOR solver
27   INTEGER , PUBLIC ::   nn_nmod      !: frequency of test for the SOR solver
28   REAL(wp), PUBLIC ::   rn_eps       !: absolute precision of the solver
29   REAL(wp), PUBLIC ::   rn_resmax    !: absolute precision for the SOR solver
30   REAL(wp), PUBLIC ::   rn_sor       !: optimal coefficient for the SOR solver
31   REAL(wp), PUBLIC ::   rn_nu        !: strength of the additional force used in free surface
32
33   CHARACTER(len=1), PUBLIC ::   c_solver_pt = 'T'   !: nature of grid-points T (S) for free surface case
34
35   INTEGER , PUBLIC ::   ncut        !: indicator of solver convergence
36   INTEGER , PUBLIC ::   niter       !: number of iteration done by the solver
37
38   REAL(wp), PUBLIC ::   eps, epsr   !: relative precision for SOR & PCG solvers
39   REAL(wp), PUBLIC ::   rnorme      !: intermediate modulus
40   REAL(wp), PUBLIC ::   res         !: solver residu
41   REAL(wp), PUBLIC ::   alph        !: coefficient  =(gcr,gcr)/(gcx,gccd)
42   REAL(wp), PUBLIC ::   beta        !: coefficient  =(rn+1,rn+1)/(rn,rn)
43   REAL(wp), PUBLIC ::   radd        !: coefficient  =(gccd,gcdes)
44   REAL(wp), PUBLIC ::   rr          !: coefficient  =(rn,rn)
45
46   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   gcp     !: matrix extra-diagonal elements
47   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcx     !: now    solution of the elliptic eq.
48   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcxb    !: before solution of the elliptic eq.
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcdprc  !: inverse diagonal preconditioning matrix
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcdmat  !: diagonal preconditioning matrix
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcb     !: second member of the elliptic eq.
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcr     !: residu =b-a.x
53   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gcdes   !: vector descente
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gccd    !: gccd= gcdprc^-1.a.d
55
56#if defined key_agrif
57      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: laplacu, laplacv
58#endif
59
60   !!----------------------------------------------------------------------
61   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
62   !! $Id$
63   !! Software governed by the CeCILL licence    (NEMOGCM/NEMO_CeCILL.txt)
64   !!----------------------------------------------------------------------
65CONTAINS
66
67   INTEGER FUNCTION sol_oce_alloc()
68      !!----------------------------------------------------------------------
69      !!                ***  FUNCTION sol_oce_alloc  ***
70      !!----------------------------------------------------------------------
71      INTEGER  :: ierr(3)
72      !!----------------------------------------------------------------------
73      ierr(:) = 0
74      !
75      ALLOCATE( gcp (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj,4) ,     &
76         &      gcx (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj)   ,     &
77         &      gcxb(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj)   , STAT=ierr(1) )
78
79      ALLOCATE( gcdprc(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) ,     & 
80         &      gcdmat(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) ,     & 
81         &      gcb   (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) , STAT=ierr(2) )
82
83      ALLOCATE( gcr  (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) ,   & 
84         &      gcdes(1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) ,   & 
85         &      gccd (1-jpr2di:jpi+jpr2di,1-jpr2dj:jpj+jpr2dj) ,   &
86#if defined key_agrif
87         &      laplacu(jpi,jpj), laplacv(jpi,jpj),             &
88#endif
89         &      STAT=ierr(3) )
90         !
91      sol_oce_alloc = MAXVAL(ierr)
92      !
93      IF( lk_mpp            )   CALL mpp_sum ( sol_oce_alloc )
94      IF( sol_oce_alloc > 0 )   CALL ctl_warn('sol_oce_alloc: allocation of arrays failed')
95      !
96   END FUNCTION sol_oce_alloc
97
98   !!======================================================================
99END MODULE sol_oce
Note: See TracBrowser for help on using the repository browser.