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 6717 for branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/USR/usrdef_closea.F90 – NEMO

Ignore:
Timestamp:
2016-06-17T12:00:46+02:00 (8 years ago)
Author:
gm
Message:

#1692 - branch SIMPLIF_2_usrdef: numerous improvement in the user defined interface

Location:
branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/USR
Files:
1 added
1 moved

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r6409_SIMPLIF_2_usrdef/NEMOGCM/NEMO/OPA_SRC/USR/usrdef_closea.F90

    r6594 r6717  
    1 MODULE closea 
     1MODULE usrdef_closea 
    22   !!====================================================================== 
    3    !!                       ***  MODULE  closea  *** 
    4    !! Closed Seas : specific treatments associated with closed seas 
     3   !!                   ***  MODULE  usrdef_closea  *** 
     4   !! User define : specific treatments associated with closed seas 
    55   !!====================================================================== 
    6    !! History :   8.2  !  00-05  (O. Marti)  Original code 
    7    !!             8.5  !  02-06  (E. Durand, G. Madec)  F90 
    8    !!             9.0  !  06-07  (G. Madec)  add clo_rnf, clo_ups, clo_bat 
    9    !!        NEMO 3.4  !  03-12  (P.G. Fogli) sbc_clo bug fix & mpp reproducibility 
     6   !! History :   8.2  !  2000-05  (O. Marti)  Original code 
     7   !!   NEMO      1.0  !  2002-06  (E. Durand, G. Madec)  F90 
     8   !!             3.0  !  2006-07  (G. Madec)  add clo_rnf, clo_ups, clo_bat 
     9   !!             3.4  !  2014-12  (P.G. Fogli) sbc_clo bug fix & mpp reproducibility 
     10   !!             4.0  !  2016-06  (G. Madec)  move to usrdef_closea, remove clo_ups 
    1011   !!---------------------------------------------------------------------- 
    1112 
     
    1415   !!   sbc_clo    : Special handling of closed seas 
    1516   !!   clo_rnf    : set close sea outflows as river mouths (see sbcrnf) 
    16    !!   clo_ups    : set mixed centered/upstream scheme in closed sea (see traadv_cen2) 
    1717   !!   clo_bat    : set to zero a field over closed sea (see domzrg) 
    1818   !!---------------------------------------------------------------------- 
     
    2020   USE dom_oce         ! ocean space and time domain 
    2121   USE phycst          ! physical constants 
     22   USE sbc_oce         ! ocean surface boundary conditions 
     23   ! 
    2224   USE in_out_manager  ! I/O manager 
    23    USE sbc_oce         ! ocean surface boundary conditions 
    2425   USE lib_fortran,    ONLY: glob_sum, DDPDD 
    2526   USE lbclnk          ! lateral boundary condition - MPP exchanges 
     
    3334   PUBLIC sbc_clo      ! routine called by step module 
    3435   PUBLIC clo_rnf      ! routine called by sbcrnf module 
    35    PUBLIC clo_ups      ! routine called in traadv_cen2(_jki) module 
    3636   PUBLIC clo_bat      ! routine called in domzgr module 
    3737 
     
    4848#  include "vectopt_loop_substitute.h90" 
    4949   !!---------------------------------------------------------------------- 
    50    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     50   !! NEMO/OPA 4.0 , NEMO Consortium (2016) 
    5151   !! $Id$ 
    5252   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    5454CONTAINS 
    5555 
    56    SUBROUTINE dom_clo 
     56   SUBROUTINE dom_clo( cd_cfg, kcfg ) 
    5757      !!--------------------------------------------------------------------- 
    5858      !!                  ***  ROUTINE dom_clo  *** 
     
    7171      !!                                   =2 put at location runoff 
    7272      !!---------------------------------------------------------------------- 
     73      CHARACTER(len=1)          , INTENT(in   ) ::   cd_cfg   ! configuration name 
     74      INTEGER                   , INTENT(in   ) ::   kcfg     ! configuration identifier  
     75      ! 
    7376      INTEGER ::   jc      ! dummy loop indices 
    7477      INTEGER ::   isrow   ! local index 
     
    8689      ! ------------------- 
    8790      ! 
    88       IF( cp_cfg == "orca" ) THEN 
    89          ! 
    90          SELECT CASE ( jp_cfg ) 
     91      IF( cd_cfg == "orca" ) THEN      !==  ORCA configuration  ==! 
     92         ! 
     93         SELECT CASE ( kcfg ) 
    9194         !                                           ! ======================= 
    92          CASE ( 1 )                                  ! ORCA_R1 configuration 
     95         CASE ( 1 )                                  !  ORCA_R1 configuration 
    9396            !                                        ! ======================= 
     97            IF(lwp) WRITE(numout,*)'   ORCA_R1 closed seas :  only the Caspian Sea' 
    9498            ! This dirty section will be suppressed by simplification process: 
    9599            ! all this will come back in input files 
     
    98102            isrow = 332 - jpjglo 
    99103            ! 
    100             ncsnr(1)   = 1    ; ncstt(1)   = 0           ! Caspian Sea 
     104            ncsnr(1)   = 1    ; ncstt(1)   = 0           ! Caspian Sea  (spread over the globe) 
    101105            ncsi1(1)   = 332  ; ncsj1(1)   = 243 - isrow 
    102106            ncsi2(1)   = 344  ; ncsj2(1)   = 275 - isrow 
     
    106110         CASE ( 2 )                                  !  ORCA_R2 configuration 
    107111            !                                        ! ======================= 
     112            IF(lwp) WRITE(numout,*)'   ORCA_R2 closed seas and lakes : ' 
    108113            !                                            ! Caspian Sea 
     114            IF(lwp) WRITE(numout,*)'      Caspian Sea  ' 
    109115            ncsnr(1)   =   1  ;  ncstt(1)   =   0           ! spread over the globe 
    110116            ncsi1(1)   =  11  ;  ncsj1(1)   = 103 
     
    112118            ncsir(1,1) =   1  ;  ncsjr(1,1) =   1  
    113119            !                                            ! Great North American Lakes 
     120            IF(lwp) WRITE(numout,*)'      Great North American Lakes  ' 
    114121            ncsnr(2)   =   1  ;  ncstt(2)   =   2           ! put at St Laurent mouth 
    115122            ncsi1(2)   =  97  ;  ncsj1(2)   = 107 
     
    117124            ncsir(2,1) = 110  ;  ncsjr(2,1) = 111            
    118125            !                                            ! Black Sea (crossed by the cyclic boundary condition) 
     126            IF(lwp) WRITE(numout,*)'      Black Sea  ' 
    119127            ncsnr(3:4) =   4  ;  ncstt(3:4) =   2           ! put in Med Sea (north of Aegean Sea) 
    120128            ncsir(3:4,1) = 171;  ncsjr(3:4,1) = 106         ! 
     
    126134            ncsi1(4)   =   2  ;  ncsj1(4)   = 107           ! 2 : east part of the Black Sea  
    127135            ncsi2(4)   =   6  ;  ncsj2(4)   = 112           !           (ie east of the cyclic b.c.) 
    128               
    129            
    130  
    131             !                                        ! ======================= 
    132          CASE ( 4 )                                  !  ORCA_R4 configuration 
    133             !                                        ! ======================= 
     136            ! 
     137            !                                        ! ========================= 
     138         CASE ( 025 )                                !  ORCA_R025 configuration 
     139            !                                        ! ========================= 
     140            IF(lwp) WRITE(numout,*)'   ORCA_R025 closed seas : ' 
    134141            !                                            ! Caspian Sea 
    135             ncsnr(1)   =  1  ;  ncstt(1)   =  0   
    136             ncsi1(1)   =  4  ;  ncsj1(1)   = 53  
    137             ncsi2(1)   =  4  ;  ncsj2(1)   = 56 
    138             ncsir(1,1) =  1  ;  ncsjr(1,1) =  1 
    139             !                                            ! Great North American Lakes 
    140             ncsnr(2)   =  1  ;  ncstt(2)   =  2  
    141             ncsi1(2)   = 49  ;  ncsj1(2)   = 55 
    142             ncsi2(2)   = 51  ;  ncsj2(2)   = 56 
    143             ncsir(2,1) = 57  ;  ncsjr(2,1) = 55 
    144             !                                            ! Black Sea 
    145             ncsnr(3)   =  4  ;  ncstt(3)   =  2   
    146             ncsi1(3)   = 88  ;  ncsj1(3)   = 55  
    147             ncsi2(3)   = 91  ;  ncsj2(3)   = 56 
    148             ncsir(3,1) = 86  ;  ncsjr(3,1) = 53 
    149             ncsir(3,2) = 87  ;  ncsjr(3,2) = 53  
    150             ncsir(3,3) = 86  ;  ncsjr(3,3) = 52  
    151             ncsir(3,4) = 87  ;  ncsjr(3,4) = 52 
    152             !                                            ! Baltic Sea 
    153             ncsnr(4)   =  1  ;  ncstt(4)   =  2 
    154             ncsi1(4)   = 75  ;  ncsj1(4)   = 59 
    155             ncsi2(4)   = 76  ;  ncsj2(4)   = 61 
    156             ncsir(4,1) = 84  ;  ncsjr(4,1) = 59  
    157             !                                        ! ======================= 
    158          CASE ( 025 )                                ! ORCA_R025 configuration 
    159             !                                        ! ======================= 
     142            IF(lwp) WRITE(numout,*)'      Caspian Sea  ' 
    160143            ncsnr(1)   = 1    ; ncstt(1)   = 0               ! Caspian + Aral sea 
    161144            ncsi1(1)   = 1330 ; ncsj1(1)   = 645 
     
    163146            ncsir(1,1) = 1    ; ncsjr(1,1) = 1 
    164147            !                                         
     148            IF(lwp) WRITE(numout,*)'      Azov Sea  ' 
    165149            ncsnr(2)   = 1    ; ncstt(2)   = 0               ! Azov Sea  
    166150            ncsi1(2)   = 1284 ; ncsj1(2)   = 722 
     
    169153            ! 
    170154         END SELECT 
     155         ! 
     156      ELSE                             !==  No closed sea in the configuration  ==! 
     157         ! 
     158         IF(lwp) WRITE(numout,*)'   No closed seas or lakes in the configuration ' 
    171159         ! 
    172160      ENDIF 
     
    177165         ncsi1(jc)   = mi0( ncsi1(jc) ) 
    178166         ncsj1(jc)   = mj0( ncsj1(jc) ) 
    179  
     167         ! 
    180168         ncsi2(jc)   = mi1( ncsi2(jc) )    
    181169         ncsj2(jc)   = mj1( ncsj2(jc) )   
     
    215203         IF(lwp) WRITE(numout,*)'~~~~~~~' 
    216204 
    217          surf(:) = 0.e0_wp 
     205         surf(:) = 0._wp 
    218206         ! 
    219207         surf(jpncs+1) = glob_sum( e1e2t(:,:) )   ! surface of the global ocean 
     
    398386      ! 
    399387   END SUBROUTINE clo_rnf 
    400  
    401     
    402    SUBROUTINE clo_ups( p_upsmsk ) 
    403       !!--------------------------------------------------------------------- 
    404       !!                  ***  ROUTINE sbc_rnf  *** 
    405       !!                     
    406       !! ** Purpose :   allow the treatment of closed sea outflow grid-points 
    407       !!                to be the same as river mouth grid-points 
    408       !! 
    409       !! ** Method  :   set to 0.5 the upstream mask (upsmsk, see traadv_cen2  
    410       !!                module) over the closed seas. 
    411       !! 
    412       !! ** Action  :   update (p_)upsmsk (set 0.5 over closed seas) 
    413       !!---------------------------------------------------------------------- 
    414       REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   p_upsmsk   ! upstream mask (upsmsk array) 
    415       ! 
    416       INTEGER  ::   jc, ji, jj      ! dummy loop indices 
    417       !!---------------------------------------------------------------------- 
    418       ! 
    419       DO jc = 1, jpncs 
    420          DO jj = ncsj1(jc), ncsj2(jc) 
    421             DO ji = ncsi1(jc), ncsi2(jc) 
    422                p_upsmsk(ji,jj) = 0.5_wp         ! mixed upstream/centered scheme over closed seas 
    423             END DO  
    424          END DO  
    425        END DO  
    426        ! 
    427    END SUBROUTINE clo_ups 
    428388    
    429389       
    430    SUBROUTINE clo_bat( pbat, kbat ) 
     390   SUBROUTINE clo_bat( k_top, k_bot ) 
    431391      !!--------------------------------------------------------------------- 
    432392      !!                  ***  ROUTINE clo_bat  *** 
     
    434394      !! ** Purpose :   suppress closed sea from the domain 
    435395      !! 
    436       !! ** Method  :   set to 0 the meter and level bathymetry (given in  
    437       !!                arguments) over the closed seas. 
     396      !! ** Method  :   set first and last ocean level to 0 over the closed seas. 
    438397      !! 
    439398      !! ** Action  :   set pbat=0 and kbat=0 over closed seas 
    440399      !!---------------------------------------------------------------------- 
    441       REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   pbat   ! bathymetry in meters (bathy array) 
    442       INTEGER , DIMENSION(jpi,jpj), INTENT(inout) ::   kbat   ! bathymetry in levels (mbathy array) 
     400      INTEGER, DIMENSION(:,:), INTENT(inout) ::   k_top, k_bot   ! ocean first and last level indices 
    443401      ! 
    444402      INTEGER  ::   jc, ji, jj      ! dummy loop indices 
     
    448406         DO jj = ncsj1(jc), ncsj2(jc) 
    449407            DO ji = ncsi1(jc), ncsi2(jc) 
    450                pbat(ji,jj) = 0._wp    
    451                kbat(ji,jj) = 0    
     408               k_top(ji,jj) = 0    
     409               k_bot(ji,jj) = 0    
    452410            END DO  
    453411         END DO  
     
    457415 
    458416   !!====================================================================== 
    459 END MODULE closea 
    460  
     417END MODULE usrdef_closea 
     418 
Note: See TracChangeset for help on using the changeset viewer.