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 14952 for utils/tools/DOMAINcfg – NEMO

Ignore:
Timestamp:
2021-06-04T17:42:50+02:00 (3 years ago)
Author:
jchanut
Message:

#2638, closed domains AGRIF new convention + various add ons

Location:
utils/tools/DOMAINcfg
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/DOMAINcfg/make_namelist.py

    r14690 r14952  
    4343print("Found", len(grid), "grids", ":") 
    4444 
    45 f1="namelist_ref" 
     45f1="namelist_cfg" 
    4646 
    4747 
     
    6565    f2.close() 
    6666 
    67     if int(grid[cnt-1][2]) == 1: 
    68         nbghostcells_y_s = 0 
    69     if int(grid[cnt-1][3]) == int(Nj0glo_parent) + 1: 
    70         nbghostcells_y_n = 0 
    71     if int(grid[cnt-1][1]) + int(grid[cnt-1][0]) == int(Ni0glo_parent) + 2 : 
     67    print(int(Ni0glo_parent), int(Nj0glo_parent)) 
     68 
     69    if (int(grid[cnt-1][2]) == 2 ): 
     70        nbghostcells_y_s = 1  
     71    if int(grid[cnt-1][3]) == int(Nj0glo_parent) : 
     72        nbghostcells_y_n = 1  
     73    if int(grid[cnt-1][1]) - int(grid[cnt-1][0]) == int(Ni0glo_parent) : 
    7274        nbghostcells_x = 0 
     75 
    7376    Ni0glo = (int(grid[cnt-1][1])-int(grid[cnt-1][0]))*int(grid[cnt-1][4]) + 2*nbghostcells_x 
    7477    Nj0glo = (int(grid[cnt-1][3])-int(grid[cnt-1][2]))*int(grid[cnt-1][5]) + nbghostcells_y_n  + nbghostcells_y_s 
    7578    #print( "Grid "+str(cnt)+" : jpiglo = "+cnt(jpiglo)+ "  jpjglo = "+str(jpjglo) )  
     79    print(int(grid[cnt-1][0]), int(grid[cnt-1][1]), int(grid[cnt-1][2]),int(grid[cnt-1][3])) 
     80    print(nbghostcells_x, nbghostcells_y_s, nbghostcells_y_n) 
    7681    print('Grid {:1d} : Ni0glo = {:3d} , Nj0glo = {:3d}'.format(cnt, Ni0glo, Nj0glo)) 
    7782 
     
    8388           line = fp.readline() 
    8489           if line.strip().startswith('jperio'): 
    85                if int(grid[cnt-1][1]) + int(grid[cnt-1][0]) == int(Ni0glo_parent) + 2: 
     90               if int(grid[cnt-1][1]) - int(grid[cnt-1][0]) == int(Ni0glo_parent): 
    8691                   line = "   jperio = 1\n" 
    8792               else: 
  • utils/tools/DOMAINcfg/src/agrif_connect.F90

    r14721 r14952  
    2323      CALL agrif_connection() 
    2424      ! 
    25       CALL Agrif_Bc_variable(bottom_level_id, procname = connect_bottom_level) 
     25!      CALL Agrif_Bc_variable(bottom_level_id, procname = connect_bottom_level) 
    2626      !  
    27       CALL Agrif_Bc_variable(e3t_copy_id, procname = connect_e3t_copy) 
     27!      CALL Agrif_Bc_variable(e3t_copy_id, procname = connect_e3t_copy) 
    2828 
    2929      ALLOCATE(e3t_interp(jpi,jpj,jpk)) 
     
    174174 
    175175      ALLOCATE(ztabramp(jpi,jpj)) 
    176       ispongearea = 1 + npt_connect * Agrif_irhox() 
    177       istart = npt_copy * Agrif_irhox() 
     176      ispongearea = 1 + npt_connect * Agrif_iRhox() 
     177      istart = npt_copy * Agrif_iRhox() 
    178178      z1_spongearea = 1._wp / REAL( ispongearea, wp ) 
    179179       
     
    218218      ENDIF 
    219219 
     220      ispongearea = 1 + npt_connect * Agrif_iRhoy() 
     221      istart = npt_copy * Agrif_iRhoy() 
     222      z1_spongearea = 1._wp / REAL( ispongearea, wp ) 
     223 
    220224      ! --- South --- ! 
    221225      IF(( (nbondj == -1) .OR. (nbondj == 2) ).AND.(lk_south)) THEN 
  • utils/tools/DOMAINcfg/src/agrif_recompute_scales.F90

    r13204 r14952  
    3939         END DO 
    4040      END DO 
    41       IF ( ln_isfcav ) THEN 
    42       ! (ISF) define e3uw (adapted for 2 cells in the water column) 
    43       print *,'NOT READY SINCE:' 
    44       print *,'MBATHY HAS NOT BEEN CORRECTED / UPDATED' 
    45       print *,'EVEN NOT COMPUTED IN THE CASE ln_read_cfg = .TRUE.' 
    46       STOP 
    47          DO jj = 2, jpjm1  
    48             DO ji = 2, jpim1   ! vector opt.  
    49                ikb = MAX(mbathy (ji,jj),mbathy (ji+1,jj)) 
    50                ikt = MAX(misfdep(ji,jj),misfdep(ji+1,jj)) 
    51                IF (ikb == ikt+1) e3uw_0(ji,jj,ikb) =  MIN( gdept_0(ji,jj,ikb  ), gdept_0(ji+1,jj  ,ikb  ) ) & 
    52                                        &            - MAX( gdept_0(ji,jj,ikb-1), gdept_0(ji+1,jj  ,ikb-1) ) 
    53                ikb = MAX(mbathy (ji,jj),mbathy (ji,jj+1)) 
    54                ikt = MAX(misfdep(ji,jj),misfdep(ji,jj+1)) 
    55                IF (ikb == ikt+1) e3vw_0(ji,jj,ikb) =  MIN( gdept_0(ji,jj,ikb  ), gdept_0(ji  ,jj+1,ikb  ) ) & 
    56                                        &            - MAX( gdept_0(ji,jj,ikb-1), gdept_0(ji  ,jj+1,ikb-1) ) 
    57             END DO 
    58          END DO 
    59       END IF 
     41!      IF ( ln_isfcav ) THEN 
     42!      ! (ISF) define e3uw (adapted for 2 cells in the water column) 
     43!      print *,'NOT READY SINCE:' 
     44!      print *,'MBATHY HAS NOT BEEN CORRECTED / UPDATED' 
     45!      print *,'EVEN NOT COMPUTED IN THE CASE ln_read_cfg = .TRUE.' 
     46!      STOP 
     47!         DO jj = 2, jpjm1  
     48!            DO ji = 2, jpim1   ! vector opt.  
     49!               ikb = MAX(mbathy (ji,jj),mbathy (ji+1,jj)) 
     50!               ikt = MAX(misfdep(ji,jj),misfdep(ji+1,jj)) 
     51!               IF (ikb == ikt+1) e3uw_0(ji,jj,ikb) =  MIN( gdept_0(ji,jj,ikb  ), gdept_0(ji+1,jj  ,ikb  ) ) & 
     52!                                       &            - MAX( gdept_0(ji,jj,ikb-1), gdept_0(ji+1,jj  ,ikb-1) ) 
     53!               ikb = MAX(mbathy (ji,jj),mbathy (ji,jj+1)) 
     54!               ikt = MAX(misfdep(ji,jj),misfdep(ji,jj+1)) 
     55!               IF (ikb == ikt+1) e3vw_0(ji,jj,ikb) =  MIN( gdept_0(ji,jj,ikb  ), gdept_0(ji  ,jj+1,ikb  ) ) & 
     56!                                       &            - MAX( gdept_0(ji,jj,ikb-1), gdept_0(ji  ,jj+1,ikb-1) ) 
     57!            END DO 
     58!         END DO 
     59!      END IF 
    6060 
    6161      CALL lbc_lnk('toto', e3u_0 , 'U', 1._wp )   ;   CALL lbc_lnk('toto', e3uw_0, 'U', 1._wp )   ! lateral boundary conditions 
  • utils/tools/DOMAINcfg/src/agrif_user.F90

    r14720 r14952  
    105105 
    106106      ! Correct South and North 
     107      IF ((.not.lk_south).AND.((nbondj == -1).OR.(nbondj == 2))) THEN 
     108         glamt(:,1+nn_hls) = glamt(:,2+nn_hls) 
     109         gphit(:,1+nn_hls) = gphit(:,2+nn_hls) 
     110         glamu(:,1+nn_hls) = glamu(:,2+nn_hls) 
     111         gphiu(:,1+nn_hls) = gphiu(:,2+nn_hls) 
     112      ENDIF 
     113      !South: 
    107114      IF ((nbondj == -1).OR.(nbondj == 2)) THEN 
    108          glamt(:,1) = glamt(:,2) 
    109          gphit(:,1) = gphit(:,2) 
    110          glamu(:,1) = glamu(:,2) 
    111          gphiu(:,1) = gphiu(:,2) 
    112          glamv(:,1) = glamv(:,2) 
    113          gphiv(:,1) = gphiv(:,2) 
    114       ENDIF 
     115         glamf(:,nn_hls) = glamf(:,1+nn_hls) 
     116         gphif(:,nn_hls) = gphif(:,1+nn_hls) 
     117      ENDIF 
     118 
    115119      IF ((nbondj == 1).OR.(nbondj == 2)) THEN 
    116120         glamt(:,jpj) = glamt(:,jpj-1) 
     
    133137            glamv(1,:) = glamv(2,:) 
    134138            gphiv(1,:) = gphiv(2,:) 
     139            glamf(1,:) = glamf(2,:) 
     140            gphif(1,:) = gphif(2,:) 
    135141         ENDIF 
    136142         IF( (nbondi == 1) .OR. (nbondi == 2) ) THEN 
     
    145151         ENDIF 
    146152      ENDIF 
    147  
     153      !South: 
     154      IF ((nbondj == -1).OR.(nbondj == 2)) THEN 
     155         glamf(:,1) = glamf(:,2)  
     156      ENDIF  
    148157      CALL agrif_init_scales() 
    149158 
    150159      ! Correct South and North 
    151       IF( (nbondj == -1) .OR. (nbondj == 2) ) THEN 
    152          e1t(:,1) = e1t(:,2) 
    153          e2t(:,1) = e2t(:,2) 
    154          e1u(:,1) = e1u(:,2) 
    155          e2u(:,1) = e2u(:,2) 
    156          e1v(:,1) = e1v(:,2) 
    157          e2v(:,1) = e2v(:,2) 
     160      IF ((.not.lk_south).AND.((nbondj == -1).OR.(nbondj == 2))) THEN 
     161         e1t(:,1+nn_hls) = e1t(:,2+nn_hls) 
     162         e2t(:,1+nn_hls) = e2t(:,2+nn_hls) 
     163         e1u(:,1+nn_hls) = e1u(:,2+nn_hls) 
     164         e2u(:,1+nn_hls) = e2u(:,2+nn_hls) 
    158165      ENDIF 
    159166      IF( (nbondj == 1) .OR. (nbondj == 2) ) THEN 
     
    208215      INTEGER :: ind1, ind2, ind3 
    209216      INTEGER ::nbghostcellsfine_tot_x, nbghostcellsfine_tot_y 
    210       INTEGER :: irafx 
     217      INTEGER :: iraf 
    211218 
    212219      EXTERNAL :: nemo_mapping 
     
    221228      nbghostcellsfine_tot_y=max(nbghostcells_y_s,nbghostcells_y_n)+1 
    222229 
    223       irafx = Agrif_irhox() 
     230      iraf = MAX(Agrif_irhox(), Agrif_irhoy())  
    224231 
    225232      ! In case of East-West periodicity, prevent AGRIF interpolation at east and west boundaries 
     
    352359      CALL Agrif_Set_bcinterp(e3t_copy_id,interp=AGRIF_constant) 
    353360      CALL Agrif_Set_interp(e3t_copy_id,interp=AGRIF_constant) 
    354       CALL Agrif_Set_bc( e3t_copy_id, (/-npt_copy*irafx-1,max(nbghostcellsfine_tot_x,nbghostcellsfine_tot_y)-1/)) 
     361      CALL Agrif_Set_bc( e3t_copy_id, (/-npt_copy*iraf-1,max(nbghostcellsfine_tot_x,nbghostcellsfine_tot_y)-1/)) 
    355362 
    356363!      CALL Agrif_Set_bcinterp(e3t_connect_id,interp=AGRIF_linear) 
     
    358365      CALL Agrif_Set_bcinterp(e3t_connect_id,interp=AGRIF_constant) 
    359366      CALL Agrif_Set_interp(e3t_connect_id,interp=AGRIF_constant) 
    360       CALL Agrif_Set_bc( e3t_connect_id, (/-(npt_copy+npt_connect)*irafx-1,-npt_copy*irafx-1/)) 
     367!      CALL Agrif_Set_bc( e3t_connect_id, (/-(npt_copy+npt_connect)*iraf-1,-npt_copy*iraf-1/)) 
     368      CALL Agrif_Set_bc( e3t_connect_id, & 
     369      & (/-(npt_copy+npt_connect)*iraf-1,max(nbghostcellsfine_tot_x,nbghostcellsfine_tot_y)-1/)) 
    361370 
    362371      CALL Agrif_Set_bcinterp(e3u_id, interp1=Agrif_linear, interp2=AGRIF_ppm) 
     
    373382      CALL Agrif_Set_bcinterp(bottom_level_id,interp=AGRIF_constant) 
    374383      CALL Agrif_Set_interp(bottom_level_id,interp=AGRIF_constant) 
    375       CALL Agrif_Set_bc( bottom_level_id, (/-npt_copy*irafx-1,max(nbghostcellsfine_tot_x,nbghostcellsfine_tot_y)-1/)) 
     384      CALL Agrif_Set_bc( bottom_level_id, (/-npt_copy*iraf-1,max(nbghostcellsfine_tot_x,nbghostcellsfine_tot_y)-1/)) 
    376385      CALL Agrif_Set_Updatetype( bottom_level_id, update = AGRIF_Update_Max) 
    377386 
     
    11051114   ! Set the number of ghost cells according to periodicity 
    11061115 
    1107       nbghostcells_x = nbghostcells 
    1108       nbghostcells_y_s = nbghostcells 
    1109       nbghostcells_y_n = nbghostcells 
    1110  
    1111       IF ((jperio == 1).OR.(jperio == 4)) THEN 
    1112         nbghostcells_x = 0 
    1113       ENDIF 
    1114       IF (jperio == 4) THEN 
    1115         nbghostcells_y_s = 0 
    1116       ENDIF 
    1117  
    11181116      IF (.not.agrif_root()) THEN 
    11191117         lk_west  = .NOT. ( Agrif_Ix() == 1 ) 
    11201118         lk_east  = .NOT. ( Agrif_Ix() + nbcellsx/AGRIF_Irhox() == Agrif_Parent(Ni0glo) + 1 ) 
    11211119         lk_south = .NOT. ( Agrif_Iy() == 1 ) 
    1122          lk_north = .NOT. ( Agrif_Iy() + nbcellsy/AGRIF_Irhoy() == Agrif_Parent(Nj0glo) + 1) 
     1120         lk_north = .NOT. ( Agrif_Iy() + nbcellsy/AGRIF_Irhoy() == Agrif_Parent(Nj0glo) - 1 ) 
     1121 
     1122         nbghostcells_x   = nbghostcells 
     1123         nbghostcells_y_s = nbghostcells 
     1124         nbghostcells_y_n = nbghostcells 
     1125 
    11231126         IF (.NOT.lk_south) THEN 
    1124             nbghostcells_y_s = 0 
     1127            nbghostcells_y_s = 1  
    11251128         ENDIF 
    11261129         IF (.NOT.lk_north) THEN 
    1127             nbghostcells_y_n = 0 
     1130            nbghostcells_y_n = 1  
     1131         ENDIF 
     1132 
     1133         IF ((jperio == 1).OR.(jperio == 4)) THEN 
     1134            nbghostcells_x = 0 
    11281135         ENDIF 
    11291136         IF(lwp) THEN                     ! Control print 
     
    11381145         ENDIF 
    11391146      ELSE ! root grid 
    1140          nbghostcells_x   = 0  
    1141          nbghostcells_y_s = 0  
    1142          nbghostcells_y_n = 0  
     1147         nbghostcells_x   = 1  
     1148         nbghostcells_y_s = 1  
     1149         nbghostcells_y_n = 1  
     1150 
     1151         IF ((jperio == 1).OR.(jperio == 4)) THEN 
     1152           nbghostcells_x = 0 
     1153         ENDIF 
     1154         IF (jperio == 4) THEN 
     1155           nbghostcells_y_n = 0 ! for completeness 
     1156         ENDIF 
    11431157      ENDIF 
    11441158 
  • utils/tools/DOMAINcfg/src/domhgr.F90

    r14630 r14952  
    188188         ! Position coordinates (in kilometers) 
    189189         !                          ========== 
    190          glam0 = 0._wp 
    191          gphi0 = - ppe2_m * 1.e-3 
     190         glam0 = - 0.5*ppe1_m * 1.e-3  
     191         gphi0 = - 0.5*ppe2_m * 1.e-3 
     192         ! 
     193         IF ( cp_cfg=='DOME' ) THEN 
     194            glam0 = glam0 - 1700._wp 
     195            gphi0 = gphi0 -  800._wp  
     196         ENDIF 
    192197         ! 
    193198         DO jj = 1, jpj 
    194199            DO ji = 1, jpi 
    195                glamt(ji,jj) = glam0 + ppe1_m * 1.e-3 * ( REAL( ji - 1 + nimpp - 1 )       ) 
    196                glamu(ji,jj) = glam0 + ppe1_m * 1.e-3 * ( REAL( ji - 1 + nimpp - 1 ) + 0.5 ) 
     200               glamt(ji,jj) = glam0 + ppe1_m * 1.e-3 *  REAL( mig0(ji)-1   )  
     201               glamu(ji,jj) = glam0 + ppe1_m * 1.e-3 *  REAL( mig0(ji)-0.5 )  
    197202               glamv(ji,jj) = glamt(ji,jj) 
    198203               glamf(ji,jj) = glamu(ji,jj) 
    199204               ! 
    200                gphit(ji,jj) = gphi0 + ppe2_m * 1.e-3 * ( REAL( jj - 1 + njmpp - 1 )       ) 
     205               gphit(ji,jj) = gphi0 + ppe2_m * 1.e-3 *  REAL( mjg0(jj) -1   ) 
    201206               gphiu(ji,jj) = gphit(ji,jj) 
    202                gphiv(ji,jj) = gphi0 + ppe2_m * 1.e-3 * ( REAL( jj - 1 + njmpp - 1 ) + 0.5 ) 
     207               gphiv(ji,jj) = gphi0 + ppe2_m * 1.e-3 *  REAL( mjg0(jj) -0.5 )   
    203208               gphif(ji,jj) = gphiv(ji,jj) 
    204209            END DO 
  • utils/tools/DOMAINcfg/src/domzgr.F90

    r14630 r14952  
    560560      REAL(wp) ::   r_bump , h_bump , h_oce   ! bump characteristics  
    561561      REAL(wp) ::   zi, zj, zh, zhmin         ! local scalars 
    562       INTEGER , ALLOCATABLE, DIMENSION(:,:) ::   idta   ! global domain integer data 
    563       REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zdta   ! global domain scalar data 
    564562      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zrand  
    565563      !!---------------------------------------------------------------------- 
     
    571569      IF( ntopo == 0 .OR. ntopo == -1 ) THEN          !   defined by hand  ! 
    572570         !                                            ! ================== ! 
    573          !                                            ! global domain level and meter bathymetry (idta,zdta) 
    574571         ! 
    575          ALLOCATE( idta(jpiglo,jpjglo), STAT=ierror ) 
    576          IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'zgr_bat: unable to allocate idta array' ) 
    577          ALLOCATE( zdta(jpiglo,jpjglo), zrand(jpiglo,jpjglo), STAT=ierror ) 
    578          IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'zgr_bat: unable to allocate zdta array' ) 
    579572         ! 
    580573         IF( ntopo == 0 ) THEN                        ! flat basin 
     
    583576            IF( rn_bathy > 0.01 ) THEN  
    584577               IF(lwp) WRITE(numout,*) '         Depth = rn_bathy read in namelist' 
    585                zdta(:,:) = rn_bathy 
    586                IF( ln_sco ) THEN                                   ! s-coordinate (zsc       ): idta()=jpk 
    587                   idta(:,:) = jpkm1 
     578               bathy(:,:) = rn_bathy 
     579               IF( ln_sco ) THEN                                   ! s-coordinate (zsc       ):  
     580                  mbathy(:,:) = jpkm1 
    588581               ELSE                                                ! z-coordinate (zco or zps): step-like topography 
    589                   idta(:,:) = jpkm1 
     582                  mbathy(:,:) = jpkm1 
    590583                  DO jk = 1, jpkm1 
    591                      WHERE( gdept_1d(jk) < zdta(:,:) .AND. zdta(:,:) <= gdept_1d(jk+1) )   idta(:,:) = jk 
     584                     WHERE( gdept_1d(jk) < bathy(:,:) .AND. bathy(:,:) <= gdept_1d(jk+1) )   mbathy(:,:) = jk 
    592585                  END DO 
    593586               ENDIF 
    594587            ELSE 
    595588               IF(lwp) WRITE(numout,*) '         Depth = depthw(jpkm1)' 
    596                idta(:,:) = jpkm1                            ! before last level 
    597                zdta(:,:) = gdepw_1d(jpk)                     ! last w-point depth 
    598                h_oce     = gdepw_1d(jpk) 
     589               mbathy(:,:) = jpkm1                            ! before last level 
     590               bathy(:,:) = gdepw_1d(jpk)                     ! last w-point depth 
     591               h_oce       = gdepw_1d(jpk) 
    599592            ENDIF 
    600          ELSE                                         ! bump centered in the basin 
     593         ELSE                                 ! flat basin with random noise 
    601594            IF(lwp) WRITE(numout,*) 
    602 !            IF(lwp) WRITE(numout,*) '         bathymetry field: flat basin with a bump' 
    603595            IF(lwp) WRITE(numout,*) '         bathymetry field: flat basin with random noise' 
    604             ii_bump = jpiglo / 2                           ! i-index of the bump center 
    605             ij_bump = jpjglo / 2                           ! j-index of the bump center 
    606             r_bump  = 50000._wp                            ! bump radius (meters)        
    607             h_bump  =  2700._wp                            ! bump height (meters) 
     596            ALLOCATE( zrand(jpiglo,jpjglo), STAT=ierror ) 
     597            IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'zgr_bat: unable to allocate zrand array' ) 
    608598            h_oce   = gdepw_1d(jpk)                        ! background ocean depth (meters) 
    609 !            IF(lwp) WRITE(numout,*) '            bump characteristics: ' 
    610 !            IF(lwp) WRITE(numout,*) '               bump center (i,j)   = ', ii_bump, ii_bump 
    611 !            IF(lwp) WRITE(numout,*) '               bump height         = ', h_bump , ' meters' 
    612 !            IF(lwp) WRITE(numout,*) '               bump radius         = ', r_bump , ' index' 
    613 !            IF(lwp) WRITE(numout,*) '            background ocean depth = ', h_oce  , ' meters' 
    614599            !                                         
    615600            CALL RANDOM_SEED() 
    616601            CALL RANDOM_NUMBER(zrand) 
    617             DO jj = 1, jpjglo                              ! zdta : 
    618                DO ji = 1, jpiglo 
    619 !                  zi = FLOAT( ji - ii_bump ) * ppe1_m / r_bump 
    620 !                  zj = FLOAT( jj - ij_bump ) * ppe2_m / r_bump 
    621 !                  zdta(ji,jj) = h_oce - h_bump * EXP( -( zi*zi + zj*zj ) ) 
    622                   zdta(ji,jj) = h_oce + 0.1_wp *h_oce * (zrand(ji,jj)-1._wp)  
     602            DO_2D( 0, 0, 0, 0 ) 
     603               bathy(ji,jj) = h_oce + 0.1_wp *h_oce * (zrand(mig(ji),mjg(jj))-1._wp)  
     604            END_2D 
     605            IF ( cp_cfg=='OVERFLOW' ) THEN 
     606               DO jj=1,jpj 
     607                  bathy(:,jj) = +(  500. + 0.5 * 1500. * ( 1.0 + tanh( (glamt(:,3) - 40.) / 7. ) )) 
    623608               END DO 
    624             END DO 
    625             !                                              ! idta : 
     609            ENDIF 
     610            IF ( cp_cfg=='DOME' ) THEN 
     611               bathy(:,:) = MIN(3600._wp, MAX( 600._wp,  600._wp -gphit(:,:)*1.e3*0.01 )) 
     612               WHERE (gphit(:,:) >0._wp) bathy(:,:) = 0._wp 
     613               ! Dig inlet: 
     614               WHERE ((gphit(:,:)>0._wp).AND.(glamt(:,:)>-50._wp).AND.(glamt(:,:)<50._wp)) bathy(:,:) = 600._wp 
     615            ENDIF 
     616!            CALL lbc_lnk( 'zgr_bat', bathy, 'T', 1._wp ) 
     617            ! 
     618            DEALLOCATE(zrand) 
     619            !                                               
    626620            IF( ln_sco ) THEN                                   ! s-coordinate (zsc       ): idta()=jpk 
    627                idta(:,:) = jpkm1 
     621               mbathy(:,:) = jpkm1 
    628622            ELSE                                                ! z-coordinate (zco or zps): step-like topography 
    629                idta(:,:) = jpkm1 
     623               mbathy(:,:) = jpkm1 
    630624               DO jk = 1, jpkm1 
    631                   WHERE( gdept_1d(jk) < zdta(:,:) .AND. zdta(:,:) <= gdept_1d(jk+1) )   idta(:,:) = jk 
     625                  WHERE( gdept_1d(jk) < bathy(:,:) .AND. bathy(:,:) <= gdept_1d(jk+1) )   mbathy(:,:) = jk 
    632626               END DO 
    633627            ENDIF 
    634628         ENDIF 
    635629         ! 
    636          !                                            ! set GLOBAL boundary conditions  
    637          IF( jperio == 1 .OR. jperio == 4 .OR. jperio == 6 ) THEN 
    638             idta( :    , 1    ) = -1                ;      zdta( :    , 1    ) = -1._wp 
    639             idta( :    ,jpjglo) =  0                ;      zdta( :    ,jpjglo) =  0._wp 
    640          ELSEIF( jperio == 2 ) THEN 
    641             idta( :    , 1    ) = idta( : ,  3  )   ;      zdta( :    , 1    ) = zdta( : ,  3  ) 
    642             idta( :    ,jpjglo) = 0                 ;      zdta( :    ,jpjglo) =  0._wp 
    643             idta( 1    , :    ) = 0                 ;      zdta( 1    , :    ) =  0._wp 
    644             idta(jpiglo, :    ) = 0                 ;      zdta(jpiglo, :    ) =  0._wp 
    645          ELSE 
    646             ih = 0                                  ;      zh = 0._wp 
    647             IF( ln_sco )   ih = jpkm1               ;      IF( ln_sco )   zh = h_oce 
    648             idta( :    , 1    ) = ih                ;      zdta( :    , 1    ) =  zh 
    649             idta( :    ,jpjglo) = ih                ;      zdta( :    ,jpjglo) =  zh 
    650             idta( 1    , :    ) = ih                ;      zdta( 1    , :    ) =  zh 
    651             idta(jpiglo, :    ) = ih                ;      zdta(jpiglo, :    ) =  zh 
    652          ENDIF 
    653  
    654          !                                            ! local domain level and meter bathymetries (mbathy,bathy) 
    655          mbathy(:,:) = 0                                   ! set to zero extra halo points 
    656          bathy (:,:) = 0._wp                               ! (require for mpp case) 
    657          DO_2D( 0, 0, 0, 0 ) 
    658                mbathy(ji,jj) = idta( mig(ji), mjg(jj) ) 
    659                bathy (ji,jj) = zdta( mig(ji), mjg(jj) ) 
    660          END_2D 
    661630         risfdep(:,:)=0.e0 
    662631         misfdep(:,:)=1 
    663          ! 
    664          DEALLOCATE( idta, zdta , zrand) 
    665632         ! 
    666633         !                                            ! ================ ! 
Note: See TracChangeset for help on using the changeset viewer.