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 10384 – NEMO

Changeset 10384


Ignore:
Timestamp:
2018-12-12T20:06:29+01:00 (5 years ago)
Author:
clem
Message:

first step toward a working ocean restart in the nesting tools

File:
1 edited

Legend:

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

    r10381 r10384  
    1717  USE agrif_interpolation 
    1818  USE agrif_partial_steps         
     19  USE agrif_connect_topo 
    1920  ! 
    2021  IMPLICIT NONE 
     
    3839  CHARACTER*20 :: vert_coord_name 
    3940  CHARACTER*1 :: posvar 
    40   CHARACTER*100 :: Child_file,Childcoordinates,varname,Childbathy,Childbathymeter    
     41  CHARACTER*100 :: Child_file,Childcoordinates,varname,Child_Bathy_Level,Child_Bathy_Meter    
    4142  REAL*8, POINTER, DIMENSION(:,:) :: lonChild,latChild => NULL() 
    4243  REAL*8, POINTER, DIMENSION(:,:) :: lonParent,latParent => NULL() 
     
    7273  CHARACTER(len=20) :: timedimname 
    7374 
     75  LOGICAL, PARAMETER :: conservation = .FALSE. 
    7476  !       
    7577  ! Variables for dimg 
     
    100102 
    101103  IF (iom_activated) THEN 
    102      timedimname = 't' 
     104     timedimname = 'time_counter' 
    103105  ELSE 
    104106     timedimname='time' 
     
    113115  !        
    114116  CALL set_child_name(parent_coordinate_file,Childcoordinates)    
    115   CALL set_child_name(parent_bathy_level,Childbathy)  
    116   CALL set_child_name(parent_bathy_meter,Childbathymeter)    
     117  IF( TRIM(parent_bathy_level) /= '' )   CALL set_child_name(parent_bathy_level,Child_Bathy_Level)  
     118  IF( TRIM(parent_bathy_meter) /= '' )   CALL set_child_name(parent_bathy_meter,Child_Bathy_Meter)    
    117119  ! 
    118120  ! create this file 
     
    131133  CALL Read_Ncdf_dim('x',restart_file,x) 
    132134  CALL Read_Ncdf_dim('y',restart_file,y)  
    133   CALL Read_Ncdf_dim('z',restart_file,z) 
     135  CALL Read_Ncdf_dim('nav_lev',restart_file,z) 
    134136  CALL Read_Ncdf_dim('x_a',restart_file,x_a) 
    135137  CALL Read_Ncdf_dim('y_a',restart_file,y_a) 
     
    165167  ENDIF 
    166168  ! 
     169  ! one needs bathy_level 
     170  IF( TRIM(parent_bathy_level) /= '' ) THEN 
     171     status = Read_bathy_level(TRIM(parent_bathy_level),G0) 
     172     status = Read_bathy_level(TRIM(child_bathy_level),G1) 
     173  ELSE 
     174     status = read_bathy_meter(TRIM(parent_bathy_meter),G0) 
     175     status = read_bathy_meter(TRIM(child_bathy_meter),G1) 
     176     CALL meter_to_levels(G0) 
     177     CALL meter_to_levels(G1) 
     178  ENDIF 
     179  ! get masks 
    167180  CALL Init_mask(parent_bathy_level,G0,x,y) 
    168   CALL Init_mask(childbathy,G1,1,1) 
     181  CALL Init_mask(child_bathy_level,G1,1,1) 
    169182 
    170183  G0%tmask = 1.     
     
    295308     CALL Write_Ncdf_dim('x',Child_file,nxfin) 
    296309     CALL Write_Ncdf_dim('y',Child_file,nyfin) 
    297      CALL Write_Ncdf_dim('z',Child_file,z) 
     310     CALL Write_Ncdf_dim('nav_lev',Child_file,z) 
    298311     CALL Write_Ncdf_dim(TRIM(timedimname),Child_file,0)  
    299312     IF (.NOT.iom_activated) THEN 
     
    354367        CALL Read_Ncdf_var('nav_lev',TRIM(restart_file),nav_lev)  
    355368        IF(.NOT. dimg ) THEN 
    356            CALL Write_Ncdf_var('nav_lev','z',Child_file,nav_lev,'float') 
     369           CALL Write_Ncdf_var('nav_lev','nav_lev',Child_file,nav_lev,'float') 
    357370           CALL Copy_Ncdf_att('nav_lev',TRIM(restart_file),Child_file)       
    358371        ENDIF 
     
    445458 
    446459        WRITE(*,*) TRIM(varname),'interpolation ...'     
    447         vert_coord_name = 'z'              
     460        vert_coord_name = 'nav_lev'              
    448461        posvar='U' 
    449462        Interpolation = .TRUE.   
     
    463476 
    464477        WRITE(*,*) TRIM(varname),'interpolation ...'       
    465         vert_coord_name = 'z' 
     478        vert_coord_name = 'nav_lev' 
    466479        posvar='V' 
    467480        Interpolation = .TRUE.      
     
    497510 
    498511        WRITE(*,*) TRIM(varname),'interpolation ...'      
    499         vert_coord_name = 'z' 
     512        vert_coord_name = 'nav_lev' 
    500513        posvar='T' 
    501514        Interpolation = .TRUE.             
     
    505518        irec = 12 * z + 6 
    506519        WRITE(*,*) TRIM(varname),'interpolation ...'      
    507         vert_coord_name = 'z' 
     520        vert_coord_name = 'nav_lev' 
    508521        posvar='T' 
    509522        Interpolation = .TRUE.              
     
    516529     IF( Interpolation ) THEN 
    517530        !         
    518         IF( vert_coord_name == 'z') THEN 
     531        IF( vert_coord_name == 'nav_lev') THEN 
    519532           nbvert_lev = z  
    520533        ELSE IF( vert_coord_name == 'z_b') THEN 
     
    592605                         nxfin,nyfin,matrix,src_add,dst_add)  
    593606                 END SELECT 
    594                  !                       
    595                  CALL Correctforconservation(tabvar1(:,:,1,1),tabinterp4d(:,:,1,1), & 
    596                       G0%e1t,G0%e2t,G1%e1t,G1%e2t,nxfin,nyfin,posvar,imin-jpizoom+1,jmin-jpjzoom+1) 
    597  
     607                 ! 
     608                 IF( conservation ) THEN ! clem: it currently does not work 
     609                    CALL Correctforconservation(tabvar1(:,:,1,1),tabinterp4d(:,:,1,1), & 
     610                       G0%e1t,G0%e2t,G1%e1t,G1%e2t,nxfin,nyfin,posvar,imin-jpizoom+1,jmin-jpjzoom+1) 
     611                 ENDIF 
    598612 
    599613              ENDIF 
     
    625639                 END SELECT 
    626640                 !                       
    627                  CALL Correctforconservation(tabvar1(:,:,1,1),tabinterp4d(:,:,1,1), & 
    628                       G0%e1u,G0%e2u,G1%e1u,G1%e2u,nxfin,nyfin,posvar,imin-jpizoom+1,jmin-jpjzoom+1) 
    629  
     641                 IF( conservation ) THEN ! clem: not coded for U 
     642                    CALL Correctforconservation(tabvar1(:,:,1,1),tabinterp4d(:,:,1,1), & 
     643                       G0%e1u,G0%e2u,G1%e1u,G1%e2u,nxfin,nyfin,posvar,imin-jpizoom+1,jmin-jpjzoom+1) 
     644                 ENDIF 
    630645              ENDIF 
    631646 
     
    658673                 END SELECT 
    659674                 !                       
    660                  CALL Correctforconservation(tabvar1(:,:,1,1),tabinterp4d(:,:,1,1), & 
    661                       G0%e1v,G0%e2v,G1%e1v,G1%e2v,nxfin,nyfin,posvar,imin-jpizoom+1,jmin-jpjzoom+1) 
    662  
     675                 IF( conservation ) THEN ! clem: not coded for V 
     676                    CALL Correctforconservation(tabvar1(:,:,1,1),tabinterp4d(:,:,1,1), & 
     677                       G0%e1v,G0%e2v,G1%e1v,G1%e2v,nxfin,nyfin,posvar,imin-jpizoom+1,jmin-jpjzoom+1) 
     678                 ENDIF 
    663679              ENDIF 
    664680 
     
    777793        dimnames(1)='x' 
    778794        dimnames(2)='y' 
    779         dimnames(3)='z' 
     795        dimnames(3)='nav_lev' 
    780796        dimnames(4)=TRIM(timedimname) 
    781797        CALL Write_Ncdf_var('tb',dimnames,Child_file,tb,'double') 
     
    803819        dimnames(1)='x' 
    804820        dimnames(2)='y' 
    805         dimnames(3)='z' 
     821        dimnames(3)='nav_lev' 
    806822        dimnames(4)=TRIM(timedimname) 
    807823        CALL Write_Ncdf_var('sb',dimnames,Child_file,sb,'double') 
     
    875891  !       
    876892  IF(partial_steps) THEN 
    877      status = Read_Bathy_Meter(TRIM(Childbathymeter),G1) 
     893     status = Read_Bathy_Meter(TRIM(Child_Bathy_Meter),G1) 
    878894     CALL get_scale_factors( G1,fse3t,fse3u,fse3v ) 
    879895  ELSE        
     
    961977     dimnames(1)='x' 
    962978     dimnames(2)='y' 
    963      dimnames(3)='z' 
     979     dimnames(3)='nav_lev' 
    964980     dimnames(4)=TRIM(timedimname) 
    965981     CALL Write_Ncdf_var('rotn',dimnames,Child_file,rotn,'double') 
Note: See TracChangeset for help on using the changeset viewer.