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

Ignore:
Timestamp:
2018-05-30T17:44:50+02:00 (6 years ago)
Author:
clem
Message:

change the nesting tools to choose the number of points copied from mother to child grids in the namelist (npt_copy) and change the name of nb_connection_pts to npt_connect

File:
1 edited

Legend:

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

    r9628 r9694  
    172172     CALL init_constant_bathy(G0%bathy_meter,bathy_fin_constant) 
    173173     ! 
    174      boundary = connectionsize*irafx + nbghostcellsfine + 1  
     174     boundary = npt_copy*irafx + nbghostcellsfine + 1  
    175175     ! 
    176176     ! connection carried out by copying parent grid values for the fine points 
     
    285285              Cell_lonmax = MAX(G1%glamf(ji-1,jj-1),G1%glamf(ji,jj-1),G1%glamf(ji,jj),G1%glamf(ji-1,jj)) 
    286286              Cell_latmin = MIN(G1%gphif(ji-1,jj-1),G1%gphif(ji,jj-1),G1%gphif(ji,jj),G1%gphif(ji-1,jj)) 
    287               Cell_latmax = MAX(G1%gphif(ji-1,jj-1),G1%gphif(ji,jj-1),G1%gphif(ji,jj),G1%gphif(ji-1,jj))                     
     287              Cell_latmax = MAX(G1%gphif(ji-1,jj-1),G1%gphif(ji,jj-1),G1%gphif(ji,jj),G1%gphif(ji-1,jj))  
    288288              !                
    289289              ! SEARCH FOR ALL POINTS CONTAINED IN THIS CELL 
     
    329329                 ALLOCATE( vardep(nxhr,nyhr) ) 
    330330                 ALLOCATE( mask_oce(nxhr,nyhr) ) 
    331                  mask_oce = 0         
     331                 mask_oce = 0        
    332332 
    333333                 vardep(:,:) = G0%bathy_meter(iimin:iimax,jjmin:jjmax) 
     
    356356                          G1%bathy_meter(ji,jj) = ( vardep1d(SUM(mask_oce)/2) + vardep1d(SUM(mask_oce)/2+1) )/2.0 
    357357                       END IF 
    358                        DEALLOCATE(vardep1d)         
     358                       DEALLOCATE(vardep1d)    
    359359                    ENDIF 
    360360                 ENDIF 
     
    458458        CALL Check_interp(G0,gdepw_ps_interp)      ! interpolation in connection zone (3 coarse grid cells) 
    459459        ! 
    460         boundary = connectionsize*irafx + nbghostcellsfine + 1                      
     460        boundary = npt_copy*irafx + nbghostcellsfine + 1                      
    461461! J chanut: exclude matching if no open boundaries 
    462462        IF (.NOT.ASSOCIATED(G1%wgt)) & 
     
    504504 
    505505        IF(.NOT. smoothing) WRITE(*,*) 'No smoothing process only connection is carried out' 
    506         WRITE(*,*) ' linear connection on ',nb_connection_pts,'coarse grid points' 
    507  
    508         connectionsize = 2 + nb_connection_pts  
     506        WRITE(*,*) ' linear connection on ',npt_connect,'coarse grid points' 
     507 
    509508        !             
    510509        gdepw_ps_interp = 0. 
     
    521520        ! 
    522521        wghts = 1. 
    523         DO ji = boundary + 1 , boundary + nb_connection_pts * irafx 
    524             wghts = wghts - (1. / (nb_connection_pts*irafx - 1. ) ) 
     522        DO ji = boundary + 1 , boundary + npt_connect * irafx 
     523            wghts = wghts - (1. / (npt_connect*irafx - 1. ) ) 
    525524            DO jj=1,nyfin 
    526525               IF (G1%gdepw_ps(nbghostcellsfine+1,jj) > 0.) THEN 
     
    531530       
    532531        wghts = 1. 
    533         DO ji = nxfin - boundary , nxfin - boundary - nb_connection_pts * irafx +1 , -1 
    534             wghts = wghts - (1. / (nb_connection_pts*irafx - 1. ) ) 
     532        DO ji = nxfin - boundary , nxfin - boundary - npt_connect * irafx +1 , -1 
     533            wghts = wghts - (1. / (npt_connect*irafx - 1. ) ) 
    535534            DO jj=1,nyfin 
    536535               IF (G1%gdepw_ps(nxfin-nbghostcellsfine,jj) > 0.) THEN 
     
    541540 
    542541        wghts = 1. 
    543         DO jj = boundary + 1 , boundary + nb_connection_pts * irafy 
    544             wghts = wghts - (1. / (nb_connection_pts*irafy - 1. ) ) 
     542        DO jj = boundary + 1 , boundary + npt_connect * irafy 
     543            wghts = wghts - (1. / (npt_connect*irafy - 1. ) ) 
    545544            DO ji=1,nxfin 
    546545               IF (G1%gdepw_ps(ji,nbghostcellsfine+1) > 0.) THEN 
     
    551550 
    552551        wghts = 1. 
    553         DO jj = nyfin - boundary , nyfin - boundary - nb_connection_pts * irafy +1, -1 
    554             wghts = wghts - (1. / (nb_connection_pts*irafy - 1. ) ) 
     552        DO jj = nyfin - boundary , nyfin - boundary - npt_connect * irafy +1, -1 
     553            wghts = wghts - (1. / (npt_connect*irafy - 1. ) ) 
    555554            DO ji=1,nxfin 
    556555               IF (G1%gdepw_ps(ji,nyfin-nbghostcellsfine) > 0.) THEN 
     
    564563        G1%bathy_meter = G1%gdepw_ps 
    565564        !                      
    566         connectionsize = 2  
    567565        !  
    568566! Chanut: remove smoothing if child grid bathymetry is found to already exist 
     
    570568 
    571569           ! 
    572            ! Smoothing to connect the connection zone (3 + nb_connection_pts coarse grid cells) and the interior domain 
     570           ! Smoothing to connect the connection zone (3 + npt_connect coarse grid cells) and the interior domain 
    573571           ! 
    574572! Chanut: smoothing everywhere then discard result in connection zone 
    575573           CALL smooth_topo(G1%gdepw_ps(1:nxfin,1:nyfin),nbiter) 
    576574           WHERE (G1%wgt(:,:)==0.) G1%bathy_meter(:,:) = G1%gdepw_ps(:,:) 
    577 !           boundary = (connectionsize+nb_connection_pts)*irafx + nbghostcellsfine + 1  
     575!           boundary = (npt_copy+npt_connect)*irafx + nbghostcellsfine + 1  
    578576!           CALL smooth_topo(G1%gdepw_ps(boundary:nxfin-boundary+1,boundary:nyfin-boundary+1),nbiter) 
    579577!           G1%bathy_meter = G1%gdepw_ps                          
     
    658656     CALL init_constant_bathy(G0%bathy_meter,bathy_fin_constant) 
    659657     ! 
    660      boundary = connectionsize*irafx + nbghostcellsfine + 1    
     658     boundary = npt_copy*irafx + nbghostcellsfine + 1    
    661659     !              
    662660     G1%bathy_meter(1:boundary,:) = bathy_fin_constant(1:boundary,:) 
Note: See TracChangeset for help on using the changeset viewer.