solsor.F90 8.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178
  1. MODULE solsor
  2. !!======================================================================
  3. !! *** MODULE solsor ***
  4. !! Ocean solver : Successive Over-Relaxation solver
  5. !!=====================================================================
  6. !! History : OPA ! 1990-10 (G. Madec) Original code
  7. !! 7.1 ! 1993-04 (G. Madec) time filter
  8. !! ! 1996-05 (G. Madec) merge sor and pcg formulations
  9. !! ! 1996-11 (A. Weaver) correction to preconditioning
  10. !! NEMO 1.0 ! 2003-04 (C. Deltel, G. Madec) Red-Black SOR in free form
  11. !! 2.0 ! 2005-09 (R. Benshila, G. Madec) MPI optimization
  12. !!----------------------------------------------------------------------
  13. !!----------------------------------------------------------------------
  14. !! sol_sor : Red-Black Successive Over-Relaxation solver
  15. !!----------------------------------------------------------------------
  16. USE oce ! ocean dynamics and tracers variables
  17. USE dom_oce ! ocean space and time domain variables
  18. USE zdf_oce ! ocean vertical physics variables
  19. USE sol_oce ! solver variables
  20. USE in_out_manager ! I/O manager
  21. USE lib_mpp ! distributed memory computing
  22. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  23. USE lib_fortran ! Fortran routines library
  24. USE wrk_nemo ! Memory allocation
  25. USE timing ! Timing
  26. IMPLICIT NONE
  27. PRIVATE
  28. PUBLIC sol_sor !
  29. !!----------------------------------------------------------------------
  30. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  31. !! $Id: solsor.F90 3609 2012-11-19 15:51:17Z acc $
  32. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  33. !!----------------------------------------------------------------------
  34. CONTAINS
  35. SUBROUTINE sol_sor( kindic )
  36. !!----------------------------------------------------------------------
  37. !! *** ROUTINE sol_sor ***
  38. !!
  39. !! ** Purpose : Solve the ellipic equation for the transport
  40. !! divergence system using a red-black successive-over-
  41. !! relaxation method.
  42. !! This routine provides a MPI optimization to the existing solsor
  43. !! by reducing the number of call to lbc.
  44. !!
  45. !! ** Method : Successive-over-relaxation method using the red-black
  46. !! technique. The former technique used was not compatible with
  47. !! the north-fold boundary condition used in orca configurations.
  48. !! Compared to the classical sol_sor, this routine provides a
  49. !! mpp optimization by reducing the number of calls to lnc_lnk
  50. !! The solution is computed on a larger area and the boudary
  51. !! conditions only when the inside domain is reached.
  52. !!
  53. !! References : Madec et al. 1988, Ocean Modelling, issue 78, 1-6.
  54. !! Beare and Stevens 1997 Ann. Geophysicae 15, 1369-1377
  55. !!----------------------------------------------------------------------
  56. !!
  57. INTEGER, INTENT(inout) :: kindic ! solver indicator, < 0 if the convergence is not reached:
  58. ! ! the model is stopped in step (set to zero before the call of solsor)
  59. !!
  60. INTEGER :: ji, jj, jn ! dummy loop indices
  61. INTEGER :: ishift, icount, ijmppodd, ijmppeven, ijpr2d ! local integers
  62. REAL(wp) :: ztmp, zres, zres2 ! local scalars
  63. REAL(wp), POINTER, DIMENSION(:,:) :: ztab ! 2D workspace
  64. !!----------------------------------------------------------------------
  65. !
  66. IF( nn_timing == 1 ) CALL timing_start('sol_sor')
  67. !
  68. CALL wrk_alloc( jpi, jpj, ztab )
  69. !
  70. ijmppeven = MOD( nimpp+njmpp+jpr2di+jpr2dj , 2 )
  71. ijmppodd = MOD( nimpp+njmpp+jpr2di+jpr2dj+1 , 2 )
  72. ijpr2d = MAX( jpr2di , jpr2dj )
  73. icount = 0
  74. ! ! ==============
  75. DO jn = 1, nn_nmax ! Iterative loop
  76. ! ! ==============
  77. IF( MOD(icount,ijpr2d+1) == 0 ) CALL lbc_lnk_e( gcx, c_solver_pt, 1., jpr2di, jpr2dj ) ! lateral boundary conditions
  78. ! Residus
  79. ! -------
  80. ! Guess black update
  81. DO jj = 2-jpr2dj, nlcj-1+jpr2dj
  82. ishift = MOD( jj-ijmppodd-jpr2dj, 2 )
  83. DO ji = 2-jpr2di+ishift, nlci-1+jpr2di, 2
  84. ztmp = gcb(ji ,jj ) &
  85. & - gcp(ji,jj,1) * gcx(ji ,jj-1) &
  86. & - gcp(ji,jj,2) * gcx(ji-1,jj ) &
  87. & - gcp(ji,jj,3) * gcx(ji+1,jj ) &
  88. & - gcp(ji,jj,4) * gcx(ji ,jj+1)
  89. ! Estimate of the residual
  90. zres = ztmp - gcx(ji,jj)
  91. gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
  92. ! Guess update
  93. gcx(ji,jj) = rn_sor * ztmp + (1-rn_sor) * gcx(ji,jj)
  94. END DO
  95. END DO
  96. icount = icount + 1
  97. IF( MOD(icount,ijpr2d+1) == 0 ) CALL lbc_lnk_e( gcx, c_solver_pt, 1., jpr2di, jpr2dj ) ! lateral boundary conditions
  98. ! Guess red update
  99. DO jj = 2-jpr2dj, nlcj-1+jpr2dj
  100. ishift = MOD( jj-ijmppeven-jpr2dj, 2 )
  101. DO ji = 2-jpr2di+ishift, nlci-1+jpr2di, 2
  102. ztmp = gcb(ji ,jj ) &
  103. & - gcp(ji,jj,1) * gcx(ji ,jj-1) &
  104. & - gcp(ji,jj,2) * gcx(ji-1,jj ) &
  105. & - gcp(ji,jj,3) * gcx(ji+1,jj ) &
  106. & - gcp(ji,jj,4) * gcx(ji ,jj+1)
  107. ! Estimate of the residual
  108. zres = ztmp - gcx(ji,jj)
  109. gcr(ji,jj) = zres * gcdmat(ji,jj) * zres
  110. ! Guess update
  111. gcx(ji,jj) = rn_sor * ztmp + (1-rn_sor) * gcx(ji,jj)
  112. END DO
  113. END DO
  114. icount = icount + 1
  115. ! test of convergence
  116. IF ( jn > nn_nmin .AND. MOD( jn-nn_nmin, nn_nmod ) == 0 ) THEN
  117. SELECT CASE ( nn_sol_arp )
  118. CASE ( 0 ) ! absolute precision (maximum value of the residual)
  119. zres2 = MAXVAL( gcr(2:nlci-1,2:nlcj-1) )
  120. IF( lk_mpp ) CALL mpp_max( zres2 ) ! max over the global domain
  121. ! test of convergence
  122. IF( zres2 < rn_resmax .OR. jn == nn_nmax ) THEN
  123. res = SQRT( zres2 )
  124. niter = jn
  125. ncut = 999
  126. ENDIF
  127. CASE ( 1 ) ! relative precision
  128. ztab = 0.
  129. ztab(:,:) = gcr(2:nlci-1,2:nlcj-1)
  130. rnorme = glob_sum( ztab) ! sum over the global domain
  131. ! test of convergence
  132. IF( rnorme < epsr .OR. jn == nn_nmax ) THEN
  133. res = SQRT( rnorme )
  134. niter = jn
  135. ncut = 999
  136. ENDIF
  137. END SELECT
  138. !****
  139. ! IF(lwp)WRITE(numsol,9300) jn, res, sqrt( epsr ) / eps
  140. 9300 FORMAT(' niter :',i4,' res :',e20.10,' b :',e20.10)
  141. !****
  142. ENDIF
  143. ! indicator of non-convergence or explosion
  144. IF( jn == nn_nmax .OR. SQRT(epsr)/eps > 1.e+20 ) kindic = -2
  145. IF( ncut == 999 ) GOTO 999
  146. ! ! =====================
  147. END DO ! END of iterative loop
  148. ! ! =====================
  149. 999 CONTINUE
  150. ! Output in gcx
  151. ! -------------
  152. CALL lbc_lnk_e( gcx, c_solver_pt, 1._wp, jpr2di, jpr2dj ) ! boundary conditions
  153. !
  154. CALL wrk_dealloc( jpi, jpj, ztab )
  155. !
  156. IF( nn_timing == 1 ) CALL timing_stop('sol_sor')
  157. !
  158. END SUBROUTINE sol_sor
  159. !!=====================================================================
  160. END MODULE solsor