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 11357 for NEMO/branches/2019 – NEMO

Changeset 11357 for NEMO/branches/2019


Ignore:
Timestamp:
2019-07-26T15:05:32+02:00 (5 years ago)
Author:
gsamson
Message:

dev_r11265_ABL : ABL compatibility with SAS (no diff with blk when using ABL src or not in ORCA2_SAS_ICE cfg), see #2131

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/SAS/diawri.F90

    r10425 r11357  
    2424   !!---------------------------------------------------------------------- 
    2525   USE oce             ! ocean dynamics and tracers  
     26   USE abl            ! abl variables in case ln_abl = .true. 
    2627   USE dom_oce         ! ocean space and time domain 
    2728   USE zdf_oce         ! ocean vertical physics 
     
    5152   PUBLIC   dia_wri_state 
    5253   PUBLIC   dia_wri_alloc           ! Called by nemogcm module 
    53  
     54#if ! defined key_iomput    
     55   PUBLIC   dia_wri_alloc_abl       ! Called by sbcabl  module (if ln_abl = .true.) 
     56#endif 
    5457   INTEGER ::   nid_T, nz_T, nh_T, ndim_T, ndim_hT   ! grid_T file 
    5558   INTEGER ::   nid_U, nz_U, nh_U, ndim_U, ndim_hU   ! grid_U file 
    5659   INTEGER ::   nid_V, nz_V, nh_V, ndim_V, ndim_hV   ! grid_V file 
     60   INTEGER ::   ndim_A, ndim_hA                      ! ABL file    
     61   INTEGER ::   nid_A, nz_A, nh_A                    ! grid_ABL file    
    5762   INTEGER ::   ndex(1)                              ! ??? 
    5863   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndex_hT, ndex_hU, ndex_hV 
     64   INTEGER, SAVE, ALLOCATABLE, DIMENSION(:) :: ndex_hA, ndex_A ! ABL 
    5965 
    6066   !! * Substitutions 
     
    114120   END FUNCTION dia_wri_alloc 
    115121    
     122   INTEGER FUNCTION dia_wri_alloc_abl() 
     123      !!---------------------------------------------------------------------- 
     124     ALLOCATE(   ndex_hA(jpi*jpj), ndex_A (jpi*jpj*jpkam1), STAT=dia_wri_alloc_abl) 
     125      CALL mpp_sum( 'diawri', dia_wri_alloc_abl ) 
     126      ! 
     127   END FUNCTION dia_wri_alloc_abl 
    116128   
    117129   SUBROUTINE dia_wri( kt ) 
     
    136148      INTEGER  ::   ierr                                     ! error code return from allocation 
    137149      INTEGER  ::   iimi, iima, ipk, it, itmod, ijmi, ijma   ! local integers 
     150      INTEGER  ::   ipka                                     ! ABL 
    138151      REAL(wp) ::   zsto, zout, zmax, zjulian                ! local scalars 
     152      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zw3d_abl   ! ABL 3D workspace 
    139153      !!---------------------------------------------------------------------- 
    140154      !  
     
    172186      ijmi = 1      ;      ijma = jpj 
    173187      ipk = jpk 
     188     IF(ln_abl) ipka = jpkam1 
    174189 
    175190      ! define time axis 
     
    239254 
    240255         ! No W grid FILE 
     256         IF( ln_abl ) THEN  
     257         ! Define the ABL grid FILE ( nid_A ) 
     258            CALL dia_nam( clhstnam, nwrite, 'grid_ABL' ) 
     259            IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam    ! filename 
     260            CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
     261               &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
     262               &          nit000-1, zjulian, rdt, nh_A, nid_A, domain_id=nidom, snc4chunks=snc4set ) 
     263            CALL histvert( nid_A, "ght_abl", "Vertical T levels",      &  ! Vertical grid: gdept 
     264               &           "m", ipka, ght_abl(2:jpka), nz_A, "up" ) 
     265            !                                                            ! Index of ocean points 
     266         ALLOCATE( zw3d_abl(jpi,jpj,ipka) )  
     267         zw3d_abl(:,:,:) = 1._wp  
     268         CALL wheneq( jpi*jpj*ipka, zw3d_abl, 1, 1., ndex_A , ndim_A  )      ! volume 
     269            CALL wheneq( jpi*jpj     , zw3d_abl, 1, 1., ndex_hA, ndim_hA )      ! surface 
     270         DEALLOCATE(zw3d_abl) 
     271         ENDIF 
    241272 
    242273         ! Declare all the output fields as NETCDF variables 
     
    259290         CALL histdef( nid_T, "sowindsp", "wind speed at 10m"                  , "m/s"    ,   &  ! wndm 
    260291            &          jpi, jpj, nh_T, 1  , 1, 1  , -99 , 32, clop, zsto, zout ) 
     292! 
     293         IF( ln_abl ) THEN 
     294         !                                                                                      !!! nid_A : 3D 
     295         CALL histdef( nid_A, "t_abl", "Potential Temperature"     , "K"        ,       &  ! t_abl 
     296               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout ) 
     297            CALL histdef( nid_A, "q_abl", "Humidity"                  , "kg/kg"    ,       &  ! q_abl 
     298               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout )  
     299            CALL histdef( nid_A, "u_abl", "Atmospheric U-wind   "     , "m/s"        ,     &  ! u_abl 
     300               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout ) 
     301            CALL histdef( nid_A, "v_abl", "Atmospheric V-wind   "     , "m/s"    ,         &  ! v_abl 
     302               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout )  
     303            CALL histdef( nid_A, "tke_abl", "Atmospheric TKE   "     , "m2/s2"    ,        &  ! tke_abl 
     304               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout )  
     305            CALL histdef( nid_A, "avm_abl", "Atmospheric turbulent viscosity", "m2/s"   ,  &  ! avm_abl 
     306               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout )  
     307            CALL histdef( nid_A, "avt_abl", "Atmospheric turbulent diffusivity", "m2/s2",  &  ! avt_abl 
     308               &          jpi, jpj, nh_A, ipka, 1, ipka, nz_A, 32, clop, zsto, zout )  
     309            CALL histdef( nid_A, "pblh", "Atmospheric boundary layer height "  , "m",      &  ! pblh 
     310               &          jpi, jpj, nh_A,  1  , 1, 1   , -99 , 32, clop, zsto, zout )                  
     311#if defined key_si3 
     312            CALL histdef( nid_A, "oce_frac", "Fraction of open ocean"  , " ",      &  ! ato_i 
     313               &          jpi, jpj, nh_A,  1  , 1, 1   , -99 , 32, clop, zsto, zout ) 
     314#endif 
     315          CALL histend( nid_A, snc4chunks=snc4set ) 
     316       ! 
     317       ENDIF 
     318! 
    261319 
    262320         CALL histend( nid_T, snc4chunks=snc4set ) 
     
    308366      CALL histwrite( nid_T, "soicecov", it, fr_i          , ndim_hT, ndex_hT )   ! ice fraction    
    309367      CALL histwrite( nid_T, "sowindsp", it, wndm          , ndim_hT, ndex_hT )   ! wind speed    
     368! 
     369      IF( ln_abl ) THEN  
     370        ALLOCATE( zw3d_abl(jpi,jpj,jpka) ) 
     371        IF( ln_mskland )   THEN  
     372          DO jk=1,jpka 
     373             zw3d_abl(:,:,jk) = tmask(:,:,1) 
     374            END DO 
     375       ELSE 
     376            zw3d_abl(:,:,:) = 1._wp      
     377         ENDIF        
     378       CALL histwrite( nid_A,  "pblh"   , it, pblh(:,:)                  *zw3d_abl(:,:,1     ), ndim_hA, ndex_hA )   ! pblh  
     379        CALL histwrite( nid_A,  "u_abl"  , it, u_abl   (:,:,2:jpka,nt_n  )*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! u_abl 
     380        CALL histwrite( nid_A,  "v_abl"  , it, v_abl   (:,:,2:jpka,nt_n  )*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! v_abl 
     381        CALL histwrite( nid_A,  "t_abl"  , it, tq_abl  (:,:,2:jpka,nt_n,1)*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! t_abl 
     382        CALL histwrite( nid_A,  "q_abl"  , it, tq_abl  (:,:,2:jpka,nt_n,2)*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! q_abl      
     383        CALL histwrite( nid_A,  "tke_abl", it, tke_abl (:,:,2:jpka,nt_n  )*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! tke_abl 
     384        CALL histwrite( nid_A,  "avm_abl", it, avm_abl (:,:,2:jpka       )*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! avm_abl 
     385        CALL histwrite( nid_A,  "avt_abl", it, avt_abl (:,:,2:jpka       )*zw3d_abl(:,:,2:jpka), ndim_A , ndex_A  )   ! avt_abl   
     386#if defined key_si3 
     387         CALL histwrite( nid_A,  "oce_frac"   , it, ato_i(:,:)                                  , ndim_hA, ndex_hA )   ! ato_i 
     388#endif 
     389       DEALLOCATE(zw3d_abl) 
     390     ENDIF 
     391! 
    310392 
    311393         ! Write fields on U grid 
     
    323405         CALL histclo( nid_U ) 
    324406         CALL histclo( nid_V ) 
     407         IF(ln_abl) CALL histclo( nid_A ) 
    325408      ENDIF 
    326409      ! 
Note: See TracChangeset for help on using the changeset viewer.