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 10025 for utils/tools/NESTING/src/agrif_partial_steps.f90 – NEMO

Ignore:
Timestamp:
2018-08-02T15:25:27+02:00 (6 years ago)
Author:
clem
Message:

nesting tools are partly rewritten (mostly for create_coordinates and bathy) to get better functionality. Now you can use the nesting to either define an agrif zoom or a regional domain (for bdy purposes). Also, the nesting tools output a domain_cfg.nc that can be directly used in NEMO4 without the need of DOMAINcfg tool. The option of median average for bathymetry interpolation still does not work properly but it's not new

File:
1 edited

Legend:

Unmodified
Added
Removed
  • utils/tools/NESTING/src/agrif_partial_steps.f90

    r9694 r10025  
    276276    REAL,DIMENSION(N) :: gdepw,e3t 
    277277    REAL :: za0,za1,za2,zsur,zacr,zacr2,zkth,zkth2,zmin,zmax,zdepth 
    278     INTEGER :: kbathy,jk,diff 
    279     INTEGER :: bornex,borney,bornex2,borney2 
     278    INTEGER :: kbathy,jk 
    280279    ! 
    281280    IF ( ( pa0 == 0 .OR. pa1 == 0 .OR. psur == 0 ) & 
     
    348347       e3t(N) = e3t(N-1) 
    349348    END IF 
    350     ! 
    351     diff = 0       
    352     IF ( MOD(irafx,2) .EQ. 0 ) diff = 1 
    353     !        
    354     bornex = nbghostcellsfine + 1 + CEILING(irafx/2.0) + diff - irafx 
    355     borney = nbghostcellsfine + 1 + CEILING(irafy/2.0) + diff - irafy 
    356     bornex2 = nxfin - nbghostcellsfine - irafx - CEILING(irafx/2.0)  
    357     borney2 = nyfin - nbghostcellsfine - irafy - CEILING(irafy/2.0)                       
    358     ! 
     349    !               
    359350    ! 
    360351    ! west boundary 
    361     ! 
    362  
    363     CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,2+nbghostcellsfine+(npt_copy+npt_connect)*irafx-1, & 
    364          1,nyfin) 
    365  
     352    IF( ln_agrif_domain ) THEN 
     353       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,2+nbghostcellsfine+(npt_copy+npt_connect)*irafx-1,1,nyfin) 
     354    ELSE 
     355       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,(npt_copy+npt_connect)*irafx,1,nyfin) 
     356    ENDIF 
    366357    ! 
    367358    ! east boundary 
    368     ! 
    369  
    370     CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,nxfin-1-nbghostcellsfine-((npt_copy+npt_connect)*irafx-1),nxfin, & 
    371          1,nyfin) 
    372  
     359    IF( ln_agrif_domain ) THEN 
     360       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,nxfin-1-nbghostcellsfine-((npt_copy+npt_connect)*irafx-1),nxfin,1,nyfin) 
     361    ELSE 
     362       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,nxfin-((npt_copy+npt_connect)*irafx+1),nxfin,1,nyfin) 
     363    ENDIF 
    373364    ! 
    374365    ! north boundary 
    375     ! 
    376  
    377     CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,nxfin, & 
    378          nyfin-1 - nbghostcellsfine -((npt_copy+npt_connect)*irafy-1),nyfin ) 
    379  
     366    IF( ln_agrif_domain ) THEN 
     367       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,nxfin,nyfin-1-nbghostcellsfine-((npt_copy+npt_connect)*irafy-1),nyfin) 
     368    ELSE 
     369       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,nxfin,nyfin-((npt_copy+npt_connect)*irafy+1),nyfin) 
     370    ENDIF 
    380371    ! 
    381372    ! south boundary 
    382     ! 
    383     CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,nxfin, & 
    384          1,2+nbghostcellsfine+(npt_copy+npt_connect)*irafy-1 ) 
    385  
     373    IF( ln_agrif_domain ) THEN 
     374       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,nxfin,1,2+nbghostcellsfine+(npt_copy+npt_connect)*irafy-1) 
     375    ELSE 
     376       CALL correct_level( gdepwchild,ParentGrid,gdepw,e3t,1,nxfin,1,(npt_copy+npt_connect)*irafy) 
     377    ENDIF 
    386378    !        
    387379    ! 
     
    398390    INTEGER :: kbathy,jk,indx,indy,diff 
    399391    REAL :: xdiff 
    400     INTEGER :: i,j,ji,ij,ii,jj,jpt,ipt 
     392    INTEGER :: i,j,ji,ij,ii,jj,jpt,ipt,i1,i2,j1,j2,ii1,ii2,jj1,jj2 
    401393    REAL*8 :: slopex, slopey,val,tmp1,tmp2,tmp3,tmp4 
    402394    INTEGER :: parentbathy 
     
    471463    jend = pty + agrif_int((y-ymin-dyfin/2.)/dyfin)                
    472464 
    473  
    474     ALLOCATE(gdepwtemp(ibegin-irafx:iend+irafx,jbegin-irafy:jend+irafy)) 
    475     ALLOCATE(parentbathytab(ibegin-irafx:iend+irafx,jbegin-irafy:jend+irafy)) 
    476  
     465    IF( ln_agrif_domain ) THEN 
     466       ALLOCATE(gdepwtemp(ibegin-irafx:iend+irafx,jbegin-irafy:jend+irafy)) 
     467       ALLOCATE(parentbathytab(ibegin-irafx:iend+irafx,jbegin-irafy:jend+irafy)) 
     468 
     469       i1 = ibegin 
     470       i2 = iend 
     471       j1 = jbegin 
     472       j2 = jend 
     473        
     474       ii1 = -FLOOR(irafx/2.0)+diff 
     475       ii2 =  FLOOR(irafx/2.0) 
     476       jj1 = -FLOOR(irafy/2.0)+diff 
     477       jj2 =  FLOOR(irafy/2.0) 
     478    ELSE 
     479       ibegin = minboundx 
     480       jbegin = minboundy 
     481       iend   = maxboundx ! (npt_copy+npt_connect)*irafx 
     482       jend   = maxboundy ! (npt_copy+npt_connect)*irafy 
     483       ! 
     484       ipbegin = imin + (ibegin-1)/irafx 
     485       jpbegin = jmin + (jbegin-1)/irafy 
     486       ipend   = ipbegin + (npt_copy+npt_connect) - 1 
     487       jpend   = jpbegin + (npt_copy+npt_connect) - 1 
     488       ! 
     489       i1 = ibegin 
     490       i2 = iend 
     491       j1 = jbegin 
     492       j2 = jend 
     493        
     494       ii1 = 0 
     495       ii2 = irafx - 1 
     496       jj1 = 0 
     497       jj2 = irafy - 1 
     498       ! 
     499       ALLOCATE(gdepwtemp(ibegin:iend,jbegin:jend)) 
     500       ALLOCATE(parentbathytab(ibegin:iend,jbegin:jend)) 
     501 
     502    ENDIF 
     503     
    477504 
    478505    jpt=jpbegin 
     
    482509 
    483510 
    484        DO i=ibegin,iend,irafx 
     511       DO i=i1,i2,irafx 
    485512 
    486513 
     
    524551          ! interpolation on fine grid points (connection zone) 
    525552          ! 
    526           DO ii = i-FLOOR(irafx/2.0)+diff,i+FLOOR(irafx/2.0) 
    527              x = ii-i - xdiff/2. 
     553          DO ii = i+ii1,i+ii2 
     554!!             x = ii-i - xdiff/2. 
    528555!!             val = parentgrid%gdepw_ps(ipt,jpt)+slopex * x 
    529556!! chanut: uncomment this to get nearest neighbor interpolation 
     
    563590 
    564591          slopey = vanleer(gdepwtemp(i,j-irafy:j+irafy:irafy))/REAL(irafy) 
    565  
     592           
    566593          tmp1 = (maxdepth - gdepwtemp(i,j)) / REAL(irafy) 
    567594          tmp2 = (gdepwtemp(i,j) - mindepth) / REAL(irafy) 
     
    583610 
    584611 
    585           DO jj = j-FLOOR(irafy/2.0)+diff,j+FLOOR(irafy/2.0) 
    586              y = jj-j - xdiff/2. 
     612          DO jj = j+jj1,j+jj2 
     613!!             y = jj-j - xdiff/2. 
    587614!!             val = gdepwtemp(i,j) + slopey*y 
    588615!! chanut: uncomment this to get nearest neighbor interpolation 
Note: See TracChangeset for help on using the changeset viewer.