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 13056 for utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src/mppini.F90 – NEMO

Ignore:
Timestamp:
2020-06-07T18:26:09+02:00 (4 years ago)
Author:
rblod
Message:

ticket #2129 : cleaning domcfg

File:
1 edited

Legend:

Unmodified
Added
Removed
  • utils/tools_dev_r12970_AGRIF_CMEMS/DOMAINcfg/src/mppini.F90

    r13024 r13056  
    1717   !!  mpp_init          : Lay out the global domain over processors with/without land processor elimination 
    1818   !!  mpp_init_mask     : Read global bathymetric information to facilitate land suppression 
    19    !!  mpp_init_ioipsl   : IOIPSL initialization in mpp  
    2019   !!  mpp_init_partition: Calculate MPP domain decomposition 
    2120   !!  factorise         : Calculate the factors of the no. of MPI processes 
     
    2322   !!---------------------------------------------------------------------- 
    2423   USE dom_oce        ! ocean space and time domain 
    25    USE bdy_oce        ! open BounDarY   
    2624   ! 
    2725   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
     
    3735 
    3836   INTEGER :: numbot = -1  ! 'bottom_level' local logical unit 
    39    INTEGER :: numbdy = -1  ! 'bdy_msk'      local logical unit 
    4037    
    4138   !!---------------------------------------------------------------------- 
     
    8380      nbondi = 2 
    8481      nbondj = 2 
    85       nidom  = FLIO_DOM_NONE 
    8682      npolj = jperio 
    8783      l_Iperio = jpni == 1 .AND. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6 .OR. jperio == 7) 
     
    186182      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   ilej, ildj, ioso, iowe         !  -     - 
    187183      LOGICAL, ALLOCATABLE, DIMENSION(:,:) ::   llisoce                        !  -     - 
    188       NAMELIST/nambdy/ ln_bdy, nb_bdy, ln_coords_file, cn_coords_file,           & 
    189            &             ln_mask_file, cn_mask_file, cn_dyn2d, nn_dyn2d_dta,     & 
    190            &             cn_dyn3d, nn_dyn3d_dta, cn_tra, nn_tra_dta,             &   
    191            &             ln_tra_dmp, ln_dyn3d_dmp, rn_time_dmp, rn_time_dmp_out, & 
    192            &             cn_ice, nn_ice_dta,                                     & 
    193            &             rn_ice_tem, rn_ice_sal, rn_ice_age,                     & 
    194            &             ln_vol, nn_volctl, nn_rimwidth, nb_jpk_bdy 
    195       !!---------------------------------------------------------------------- 
    196  
    197       llwrtlay = lwp .OR. ln_ctl .OR. sn_cfctl%l_layout 
    198       ! do we need to take into account bdy_msk? 
    199       REWIND( numnam_ref )              ! Namelist nambdy in reference namelist : BDY 
    200       READ  ( numnam_ref, nambdy, IOSTAT = ios, ERR = 903) 
    201 903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy in reference namelist (mppini)', lwp ) 
    202       REWIND( numnam_cfg )              ! Namelist nambdy in configuration namelist : BDY 
    203       READ  ( numnam_cfg, nambdy, IOSTAT = ios, ERR = 904 ) 
    204 904   IF( ios >  0 )   CALL ctl_nam ( ios , 'nambdy in configuration namelist (mppini)', lwp ) 
     184      !!---------------------------------------------------------------------- 
     185 
     186      llwrtlay = lwp  
    205187      ! 
    206188      IF(               ln_read_cfg ) CALL iom_open( cn_domcfg,    numbot ) 
    207       IF( ln_bdy .AND. ln_mask_file ) CALL iom_open( cn_mask_file, numbdy ) 
    208189      ! 
    209190      !  1. Dimension arrays for subdomains 
     
    280261 
    281262      IF( numbot /= -1 )   CALL iom_close( numbot ) 
    282       IF( numbdy /= -1 )   CALL iom_close( numbdy ) 
    283263     
    284264      ALLOCATE(  nfiimpp(jpni,jpnj), nfipproc(jpni,jpnj), nfilcit(jpni,jpnj) ,    & 
     
    666646      ENDIF 
    667647      ! 
    668       CALL mpp_init_ioipsl       ! Prepare NetCDF output file (if necessary) 
    669       ! 
    670648      IF( ln_nnogather ) THEN 
    671649         CALL mpp_init_nfdcom     ! northfold neighbour lists 
     
    902880 
    903881      ! if therr is no land and no print 
    904       IF( .NOT. llist .AND. numbot == -1 .AND. numbdy == -1 ) THEN 
     882      IF( .NOT. llist .AND. numbot == -1 ) THEN 
    905883         ! get the smaller partition which gives the smallest subdomain size 
    906884         ii = MINLOC(inbij1, mask = iszij1 == MINVAL(iszij1), dim = 1) 
     
    997975      !!---------------------------------------------------------------------- 
    998976      ! do nothing if there is no land-sea mask 
    999       IF( numbot == -1 .and. numbdy == -1 ) THEN 
     977      IF( numbot == -1 ) THEN 
    1000978         propland = 0. 
    1001979         RETURN 
     
    10531031      !!---------------------------------------------------------------------- 
    10541032      ! do nothing if there is no land-sea mask 
    1055       IF( numbot == -1 .AND. numbdy == -1 ) THEN 
     1033      IF( numbot == -1 ) THEN 
    10561034         ldisoce(:,:) = .TRUE. 
    10571035         RETURN 
     
    11081086      ! 
    11091087      INTEGER                           ::   inumsave                ! local logical unit 
    1110       REAL(wp), DIMENSION(jpiglo,kjcnt) ::   zbot, zbdy  
     1088      REAL(wp), DIMENSION(jpiglo,kjcnt) ::   zbot 
    11111089      !!---------------------------------------------------------------------- 
    11121090      ! 
     
    11191097      ENDIF 
    11201098 
    1121        IF( numbdy /= -1 ) THEN                  ! Adjust with bdy_msk if it exists     
    1122          CALL iom_get ( numbdy, jpdom_unknown, 'bdy_msk', zbdy, kstart = (/1,kjstr/), kcount = (/jpiglo, kjcnt/) ) 
    1123          zbot(:,:) = zbot(:,:) * zbdy(:,:) 
    1124       ENDIF 
    11251099      ! 
    11261100      ldoce(:,:) = zbot(:,:) > 0. 
     
    11281102      ! 
    11291103   END SUBROUTINE mpp_init_readbot_strip 
    1130  
    1131  
    1132    SUBROUTINE mpp_init_ioipsl 
    1133       !!---------------------------------------------------------------------- 
    1134       !!                  ***  ROUTINE mpp_init_ioipsl  *** 
    1135       !! 
    1136       !! ** Purpose :    
    1137       !! 
    1138       !! ** Method  :    
    1139       !! 
    1140       !! History : 
    1141       !!   9.0  !  04-03  (G. Madec )  MPP-IOIPSL  
    1142       !!   " "  !  08-12  (A. Coward)  addition in case of jpni*jpnj < jpnij 
    1143       !!---------------------------------------------------------------------- 
    1144       INTEGER, DIMENSION(2) ::   iglo, iloc, iabsf, iabsl, ihals, ihale, idid 
    1145       !!---------------------------------------------------------------------- 
    1146  
    1147       ! The domain is split only horizontally along i- or/and j- direction 
    1148       ! So we need at the most only 1D arrays with 2 elements. 
    1149       ! Set idompar values equivalent to the jpdom_local_noextra definition 
    1150       ! used in IOM. This works even if jpnij .ne. jpni*jpnj. 
    1151       iglo(1) = jpiglo 
    1152       iglo(2) = jpjglo 
    1153       iloc(1) = nlci 
    1154       iloc(2) = nlcj 
    1155       iabsf(1) = nimppt(narea) 
    1156       iabsf(2) = njmppt(narea) 
    1157       iabsl(:) = iabsf(:) + iloc(:) - 1 
    1158       ihals(1) = nldi - 1 
    1159       ihals(2) = nldj - 1 
    1160       ihale(1) = nlci - nlei 
    1161       ihale(2) = nlcj - nlej 
    1162       idid(1) = 1 
    1163       idid(2) = 2 
    1164  
    1165       IF(lwp) THEN 
    1166           WRITE(numout,*) 
    1167           WRITE(numout,*) 'mpp_init_ioipsl :   iloc  = ', iloc (1), iloc (2) 
    1168           WRITE(numout,*) '~~~~~~~~~~~~~~~     iabsf = ', iabsf(1), iabsf(2) 
    1169           WRITE(numout,*) '                    ihals = ', ihals(1), ihals(2) 
    1170           WRITE(numout,*) '                    ihale = ', ihale(1), ihale(2) 
    1171       ENDIF 
    1172       ! 
    1173       CALL flio_dom_set ( jpnij, nproc, idid, iglo, iloc, iabsf, iabsl, ihals, ihale, 'BOX', nidom) 
    1174       ! 
    1175    END SUBROUTINE mpp_init_ioipsl   
    1176  
    11771104 
    11781105   SUBROUTINE mpp_init_nfdcom 
Note: See TracChangeset for help on using the changeset viewer.