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.
Changeset 2413 – NEMO

Changeset 2413


Ignore:
Timestamp:
2010-11-19T20:46:05+01:00 (13 years ago)
Author:
gm
Message:

v3.3beta: #763 remove grid-point types S and G from the North Fold treatment

Location:
branches/nemo_v3_3_beta/NEMOGCM
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SOL/solmat.F90

    r2287 r2413  
    333333         SELECT CASE ( cd_type ) 
    334334         !  
    335          CASE ( 'T', 'S', 'U', 'W' ) 
     335         CASE ( 'T' , 'U', 'W' ) 
    336336            DO jk = 1, 4 
    337337               DO ji = 1-jpr2di, nlci+jpr2di 
     
    347347            END DO 
    348348            ! 
    349          CASE ( 'F' ,'G' , 'I', 'V' ) 
     349         CASE ( 'F' , 'I', 'V' ) 
    350350            DO jk =1, 4 
    351351               DO ji = 1-jpr2di, nlci+jpr2di 
     
    361361         SELECT CASE (cd_type ) 
    362362         ! 
    363          CASE ( 'T'  ,'S', 'U', 'W') 
     363         CASE ( 'T' , 'U', 'W') 
    364364            DO jk =1, 4 
    365365               DO ji = 1-jpr2di, nlci+jpr2di 
     
    368368            END DO 
    369369            ! 
    370          CASE ( 'F' ,'G' , 'I', 'V' ) 
     370         CASE ( 'F' , 'I', 'V' ) 
    371371            DO jk =1, 4 
    372372               DO ji = 1-jpr2di, nlci+jpr2di 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/SOL/solver.F90

    r2287 r2413  
    105105      !                             !* Grid-point at which the solver is applied 
    106106!!gm  c_solver_pt should be removed: nomore bsf, only T-point is used 
    107       IF( lk_mpp ) THEN   ;    c_solver_pt = 'S'   ! S=T with special staff ??? which one? 
    108       ELSE                ;    c_solver_pt = 'T' 
    109       ENDIF 
     107      c_solver_pt = 'T'                   ! always T-point (ssh solver only, not anymore bsf) 
    110108 
    111109      CALL sol_mat( kt )            !* Construction of the elliptic system matrix 
  • branches/nemo_v3_3_beta/NEMOGCM/NEMO/OPA_SRC/lbcnfd.F90

    r2287 r2413  
    44   !! Ocean        : north fold  boundary conditions 
    55   !!====================================================================== 
    6    !!             9.0  !  09-03  (R. Benshila) Initial version  
    7    !!---------------------------------------------------------------------- 
    8    !! * Modules used 
    9    USE oce             ! ocean dynamics and tracers    
    10    USE dom_oce         ! ocean space and time domain  
    11    USE in_out_manager  ! I/O manager 
     6   !! History :  3.2  ! 2009-03  (R. Benshila)  Original code  
     7   !!---------------------------------------------------------------------- 
     8 
     9   !!---------------------------------------------------------------------- 
     10   !!   lbc_nfd       : generic interface for lbc_nfd_3d and lbc_nfd_2d routines 
     11   !!   lbc_nfd_3d    : lateral boundary condition: North fold treatment for a 3D arrays   (lbc_nfd) 
     12   !!   lbc_nfd_2d    : lateral boundary condition: North fold treatment for a 2D arrays   (lbc_nfd) 
     13   !!---------------------------------------------------------------------- 
     14   USE oce            ! ocean dynamics and tracers    
     15   USE dom_oce        ! ocean space and time domain  
     16   USE in_out_manager ! I/O manager 
    1217 
    1318   IMPLICIT NONE 
     
    1520 
    1621   INTERFACE lbc_nfd 
    17       MODULE PROCEDURE lbc_nfd_3d, lbc_nfd_2d 
     22      MODULE PROCEDURE   lbc_nfd_3d, lbc_nfd_2d 
    1823   END INTERFACE 
    1924 
    20    PUBLIC lbc_nfd       ! north fold conditions 
     25   PUBLIC   lbc_nfd   ! north fold conditions 
    2126 
    2227   !!---------------------------------------------------------------------- 
    2328   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    2429   !! $Id$ 
    25    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    26    !!---------------------------------------------------------------------- 
    27  
     30   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     31   !!---------------------------------------------------------------------- 
    2832CONTAINS 
    2933 
     
    3337      !! 
    3438      !! ** Purpose :   3D lateral boundary condition : North fold treatment 
    35       !!       without processor exchanges.  
     39      !!              without processor exchanges.  
    3640      !! 
    3741      !! ** Method  :    
    3842      !! 
    39       !! ** Action  :   pt3d with update value at its periphery 
    40       !! 
    41       !!---------------------------------------------------------------------- 
    42       !! * Arguments 
    43       CHARACTER(len=1) , INTENT( in ) ::   & 
    44          cd_type       ! define the nature of ptab array grid-points 
    45       !             ! = T , U , V , F , W points 
    46       !             ! = S : T-point, north fold treatment ??? 
    47       !             ! = G : F-point, north fold treatment ??? 
    48       REAL(wp), INTENT( in ) ::   & 
    49          psgn          ! control of the sign change 
    50       !             !   = -1. , the sign is changed if north fold boundary 
    51       !             !   =  1. , the sign is kept  if north fold boundary 
    52       REAL(wp), DIMENSION(:,:,:), INTENT( inout ) ::   & 
    53          pt3d          ! 3D array on which the boundary condition is applied 
    54  
    55       !! * Local declarations 
     43      !! ** Action  :   pt3d with updated values along the north fold 
     44      !!---------------------------------------------------------------------- 
     45      CHARACTER(len=1)          , INTENT(in   ) ::   cd_type   ! define the nature of ptab array grid-points 
     46      !                                                        !   = T , U , V , F , W points 
     47      REAL(wp)                  , INTENT(in   ) ::   psgn      ! control of the sign change 
     48      !                                                        !   = -1. , the sign is changed if north fold boundary 
     49      !                                                        !   =  1. , the sign is kept  if north fold boundary 
     50      REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   pt3d      ! 3D array on which the boundary condition is applied 
     51      ! 
    5652      INTEGER  ::   ji, jk 
    5753      INTEGER  ::   ijt, iju, ijpj, ijpjm1 
    58  
     54      !!---------------------------------------------------------------------- 
    5955 
    6056      SELECT CASE ( jpni ) 
    61       CASE ( 1 )  ! only one proc along I 
    62          ijpj = nlcj 
    63       CASE DEFAULT  
    64          ijpj   = 4 
     57      CASE ( 1 )     ;   ijpj = nlcj      ! 1 proc only  along the i-direction 
     58      CASE DEFAULT   ;   ijpj = 4         ! several proc along the i-direction 
    6559      END SELECT 
    6660      ijpjm1 = ijpj-1 
    6761 
    6862      DO jk = 1, jpk 
    69  
     63         ! 
    7064         SELECT CASE ( npolj ) 
    71  
     65         ! 
    7266         CASE ( 3 , 4 )                        ! *  North fold  T-point pivot 
    73  
     67            ! 
    7468            SELECT CASE ( cd_type ) 
    7569            CASE ( 'T' , 'W' )                         ! T-, W-point 
     
    10498               END DO 
    10599            END SELECT 
    106  
     100            ! 
    107101         CASE ( 5 , 6 )                        ! *  North fold  F-point pivot 
    108  
     102            ! 
    109103            SELECT CASE ( cd_type ) 
    110104            CASE ( 'T' , 'W' )                         ! T-, W-point 
     
    137131               END DO 
    138132            END SELECT 
    139  
     133            ! 
    140134         CASE DEFAULT                           ! *  closed : the code probably never go through 
    141  
     135            ! 
    142136            SELECT CASE ( cd_type) 
    143137            CASE ( 'T' , 'U' , 'V' , 'W' )             ! T-, U-, V-, W-points 
     
    147141               pt3d(:,ijpj,jk) = 0.e0 
    148142            END SELECT 
    149  
     143            ! 
    150144         END SELECT     !  npolj 
    151  
     145         ! 
    152146      END DO 
    153  
     147      ! 
    154148   END SUBROUTINE lbc_nfd_3d 
    155149 
     
    164158      !! ** Method  :    
    165159      !! 
    166       !! ** Action  :   pt2d with update value at its periphery 
    167       !! 
    168       !!---------------------------------------------------------------------- 
    169       !! * Arguments 
    170       CHARACTER(len=1) , INTENT( in ) ::   & 
    171          cd_type       ! define the nature of ptab array grid-points 
    172       !             ! = T , U , V , F , W points 
    173       !             ! = S : T-point, north fold treatment ??? 
    174       !             ! = G : F-point, north fold treatment ??? 
    175       REAL(wp), INTENT( in ) ::   & 
    176          psgn          ! control of the sign change 
    177       !             !   = -1. , the sign is changed if north fold boundary 
    178       !             !   =  1. , the sign is kept  if north fold boundary 
    179       REAL(wp), DIMENSION(:,:), INTENT( inout ) ::   & 
    180          pt2d          ! 3D array on which the boundary condition is applied 
    181       INTEGER, OPTIONAL, INTENT(in) :: pr2dj 
    182  
    183       !! * Local declarations 
     160      !! ** Action  :   pt2d with updated values along the north fold 
     161      !!---------------------------------------------------------------------- 
     162      CHARACTER(len=1)        , INTENT(in   ) ::   cd_type   ! define the nature of ptab array grid-points 
     163      !                                                      ! = T , U , V , F , W points 
     164      REAL(wp)                , INTENT(in   ) ::   psgn      ! control of the sign change 
     165      !                                                      !   = -1. , the sign is changed if north fold boundary 
     166      !                                                      !   =  1. , the sign is kept  if north fold boundary 
     167      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   pt2d      ! 2D array on which the boundary condition is applied 
     168      INTEGER , OPTIONAL      , INTENT(in   ) ::   pr2dj     ! number of additional halos 
     169      ! 
    184170      INTEGER  ::   ji, jl, ipr2dj 
    185171      INTEGER  ::   ijt, iju, ijpj, ijpjm1 
     172      !!---------------------------------------------------------------------- 
    186173 
    187174      SELECT CASE ( jpni ) 
    188       CASE ( 1 )  ! only one proc along I 
    189          ijpj = nlcj 
    190       CASE DEFAULT  
    191          ijpj = 4 
     175      CASE ( 1 )     ;   ijpj = nlcj      ! 1 proc only  along the i-direction 
     176      CASE DEFAULT   ;   ijpj = 4         ! several proc along the i-direction 
    192177      END SELECT 
    193  
    194  
    195       IF( PRESENT(pr2dj) ) THEN 
     178      ! 
     179      IF( PRESENT(pr2dj) ) THEN           ! use of additional halos 
    196180         ipr2dj = pr2dj 
    197          IF (jpni .GT. 1) ijpj = ijpj + ipr2dj 
     181         IF( jpni > 1 )  ijpj = ijpj + ipr2dj 
    198182      ELSE 
    199183         ipr2dj = 0  
    200184      ENDIF 
    201  
     185      ! 
    202186      ijpjm1 = ijpj-1 
    203187 
    204188 
    205189      SELECT CASE ( npolj ) 
    206  
     190      ! 
    207191      CASE ( 3, 4 )                       ! *  North fold  T-point pivot 
    208  
     192         ! 
    209193         SELECT CASE ( cd_type ) 
    210  
    211          CASE ( 'T', 'S', 'W' ) 
     194         ! 
     195         CASE ( 'T' , 'W' )                               ! T- , W-points 
    212196            DO jl = 0, ipr2dj 
    213197               DO ji = 2, jpiglo 
     
    221205            END DO 
    222206         CASE ( 'U' )                                     ! U-point 
    223             DO jl =0, ipr2dj 
     207            DO jl = 0, ipr2dj 
    224208               DO ji = 1, jpiglo-1 
    225209                  iju = jpiglo-ji+1 
     
    232216            END DO 
    233217         CASE ( 'V' )                                     ! V-point 
    234             DO jl =-1, ipr2dj 
     218            DO jl = -1, ipr2dj 
    235219               DO ji = 2, jpiglo 
    236220                  ijt = jpiglo-ji+2 
     
    238222               END DO 
    239223            END DO 
    240          CASE ( 'F' , 'G' )                               ! F-point 
    241             DO jl =-1, ipr2dj 
     224         CASE ( 'F' )                                     ! F-point 
     225            DO jl = -1, ipr2dj 
    242226               DO ji = 1, jpiglo-1 
    243227                  iju = jpiglo-ji+1 
     
    245229               END DO 
    246230            END DO 
    247          CASE ( 'I' )                                     ! ice U-V point 
    248             DO jl =0, ipr2dj 
     231         CASE ( 'I' )                                     ! ice U-V point (I-point) 
     232            DO jl = 0, ipr2dj 
    249233               pt2d(2,ijpj+jl) = psgn * pt2d(3,ijpj-1+jl) 
    250234               DO ji = 3, jpiglo 
     
    254238            END DO 
    255239         END SELECT 
    256  
     240         ! 
    257241      CASE ( 5, 6 )                        ! *  North fold  F-point pivot 
    258  
     242         ! 
    259243         SELECT CASE ( cd_type ) 
    260          CASE ( 'T' , 'W' ,'S' )                          ! T-, W-point 
     244         CASE ( 'T' , 'W' )                               ! T-, W-point 
    261245            DO jl = 0, ipr2dj 
    262246               DO ji = 1, jpiglo 
     
    283267               pt2d(ji,ijpjm1) = psgn * pt2d(ijt,ijpjm1) 
    284268            END DO 
    285          CASE ( 'F' , 'G' )                               ! F-point 
     269         CASE ( 'F' )                               ! F-point 
    286270            DO jl = 0, ipr2dj 
    287271               DO ji = 1, jpiglo-1 
     
    294278               pt2d(ji,ijpjm1) = psgn * pt2d(iju,ijpjm1) 
    295279            END DO 
    296          CASE ( 'I' )                                  ! ice U-V point 
     280         CASE ( 'I' )                                  ! ice U-V point (I-point) 
    297281            pt2d( 2 ,ijpj:ijpj+ipr2dj) = 0.e0 
    298282            DO jl = 0, ipr2dj 
     
    303287            END DO 
    304288         END SELECT 
    305  
     289         ! 
    306290      CASE DEFAULT                           ! *  closed : the code probably never go through 
    307  
     291         ! 
    308292         SELECT CASE ( cd_type) 
    309293         CASE ( 'T' , 'U' , 'V' , 'W' )                 ! T-, U-, V-, W-points 
     
    316300            pt2d(:,ijpj:ijpj+ipr2dj) = 0.e0 
    317301         END SELECT 
    318  
     302         ! 
    319303      END SELECT 
    320  
     304      ! 
    321305   END SUBROUTINE lbc_nfd_2d 
    322306 
  • branches/nemo_v3_3_beta/NEMOGCM/TOOLS/COMPILE/cfg.txt

    r2409 r2413  
    55POMME OPA_SRC NST_SRC 
    66ORCA2_LIM3 OPA_SRC LIM_SRC_3 
    7 ORCA2_LIM OPA_SRC LIM_SRC_2 NST_SRC  
     7ORCA2_LIM OPA_SRC LIM_SRC_2 NST_SRC 
Note: See TracChangeset for help on using the changeset viewer.