sol_oce.F90 5.2 KB

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