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 11858 for NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src – NEMO

Ignore:
Timestamp:
2019-11-05T15:32:44+01:00 (4 years ago)
Author:
gsamson
Message:

dev_r11265_ABL: add write/read restart options for abl (#2131)

Location:
NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src
Files:
1 added
4 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/ABL/par_abl.F90

    r11363 r11858  
    2828   LOGICAL , PUBLIC            ::   ln_hpgls_frc   !: forcing of ABL winds by large-scale pressure gradient  
    2929   LOGICAL , PUBLIC            ::   ln_smth_pblh   !: smoothing of atmospheric PBL height  
     30 
     31   CHARACTER(len=256), PUBLIC ::   cn_ablrst_in     !: suffix of abl restart name (input) 
     32   CHARACTER(len=256), PUBLIC ::   cn_ablrst_out    !: suffix of abl restart name (output) 
     33   CHARACTER(len=256), PUBLIC ::   cn_ablrst_indir  !: abl restart input directory 
     34   CHARACTER(len=256), PUBLIC ::   cn_ablrst_outdir !: abl restart output directory 
    3035 
    3136   !!--------------------------------------------------------------------- 
  • NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/ABL/sbcabl.F90

    r11586 r11858  
    1616   USE par_abl        ! abl parameters 
    1717   USE ablmod 
     18   USE ablrst 
    1819 
    1920   USE phycst         ! physical constants 
     
    6768      REAL(wp)           ::   zcff,zcff1 
    6869      LOGICAL            ::   lluldl 
    69       NAMELIST/namsbc_abl/ cn_dir , cn_dom, ln_hpgls_frc, ln_geos_winds,          & 
    70          &                 nn_dyn_restore,                                        & 
     70      NAMELIST/namsbc_abl/ cn_dir, cn_dom, cn_ablrst_in, cn_ablrst_out,           & 
     71         &                 cn_ablrst_indir, cn_ablrst_outdir,                     & 
     72         &                 ln_hpgls_frc, ln_geos_winds, nn_dyn_restore,           & 
    7173         &                 rn_ldyn_min , rn_ldyn_max, rn_ltra_min, rn_ltra_max,   & 
    7274         &                 nn_amxl, rn_cm, rn_ct, rn_ce, rn_ceps, rn_Rod, rn_Ric, & 
     
    267269      CALL sbc_blk_init 
    268270 
    269       ! initialize ABL from data or restart 
    270       !!GS  disabled for now 
    271       !IF( ln_rstart ) THEN 
    272       !  CALL ctl_stop( 'STOP', 'sbc_abl_init: restart mode not supported yet' ) 
    273       !ELSE 
    274  
    275       CALL fld_read( nit000, nn_fsbc, sf ) ! input fields provided at the first time-step 
    276  
    277271      ! Initialize the time index for now time (nt_n) and after time (nt_a) 
    278272      nt_n = 1 + MOD( nit000  , 2) 
    279273      nt_a = 1 + MOD( nit000+1, 2) 
    280274 
    281        u_abl(:,:,:,nt_n      ) = sf(jp_wndi)%fnow(:,:,:) 
    282        v_abl(:,:,:,nt_n      ) = sf(jp_wndj)%fnow(:,:,:) 
    283       tq_abl(:,:,:,nt_n,jp_ta) = sf(jp_tair)%fnow(:,:,:) 
    284       tq_abl(:,:,:,nt_n,jp_qa) = sf(jp_humi)%fnow(:,:,:) 
    285  
    286       tke_abl(:,:,:,nt_n     ) = tke_min 
    287       avm_abl(:,:,:          ) = avm_bak 
    288       avt_abl(:,:,:          ) = avt_bak 
    289       mxl_abl(:,:,:          ) = mxl_min  
    290       pblh   (:,:            ) = ghw_abl( 3 )  !<-- assume that the pbl contains 3 grid points  
    291       u_abl  (:,:,:,nt_a     ) = 0._wp 
    292       v_abl  (:,:,:,nt_a     ) = 0._wp 
    293       tq_abl (:,:,:,nt_a,:   ) = 0._wp 
    294       tke_abl(:,:,:,nt_a     ) = 0._wp 
    295       !ENDIF 
    296       !!GS restart case not supported 
     275      ! initialize ABL from data or restart 
     276      IF( ln_rstart ) THEN 
     277         CALL abl_rst_read 
     278      ELSE 
     279         CALL fld_read( nit000, nn_fsbc, sf ) ! input fields provided at the first time-step 
     280 
     281          u_abl(:,:,:,nt_n      ) = sf(jp_wndi)%fnow(:,:,:) 
     282          v_abl(:,:,:,nt_n      ) = sf(jp_wndj)%fnow(:,:,:) 
     283         tq_abl(:,:,:,nt_n,jp_ta) = sf(jp_tair)%fnow(:,:,:) 
     284         tq_abl(:,:,:,nt_n,jp_qa) = sf(jp_humi)%fnow(:,:,:) 
     285    
     286         tke_abl(:,:,:,nt_n     ) = tke_min 
     287         avm_abl(:,:,:          ) = avm_bak 
     288         avt_abl(:,:,:          ) = avt_bak 
     289         mxl_abl(:,:,:          ) = mxl_min  
     290         pblh   (:,:            ) = ghw_abl( 3 )  !<-- assume that the pbl contains 3 grid points  
     291         u_abl  (:,:,:,nt_a     ) = 0._wp 
     292         v_abl  (:,:,:,nt_a     ) = 0._wp 
     293         tq_abl (:,:,:,nt_a,:   ) = 0._wp 
     294         tke_abl(:,:,:,nt_a     ) = 0._wp 
     295      ENDIF 
    297296      
    298297   END SUBROUTINE sbc_abl_init 
    299298 
    300    
    301299 
    302300   SUBROUTINE sbc_abl( kt ) 
     
    379377         &            sst_m, zsen, zevp                                ) 
    380378 
     379      CALL abl_rst_opn( kt )                       ! Open abl restart file (if necessary)  
     380      IF( lrst_abl ) CALL abl_rst_write( kt )      ! -- abl restart file  
     381 
    381382#if defined key_si3 
    382383      ! Avoid a USE abl in icesbc module 
  • NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/OCE/IOM/in_out_manager.F90

    r11413 r11858  
    8787   LOGICAL ::   lrst_oce              !: logical to control the oce restart write  
    8888   LOGICAL ::   lrst_ice              !: logical to control the ice restart write  
     89   LOGICAL ::   lrst_abl              !: logical to control the abl restart write  
    8990   INTEGER ::   numror = 0            !: logical unit for ocean restart (read). Init to 0 is needed for SAS (in daymod.F90) 
    9091   INTEGER ::   numrir                !: logical unit for ice   restart (read) 
     92   INTEGER ::   numrar                !: logical unit for abl   restart (read) 
    9193   INTEGER ::   numrow                !: logical unit for ocean restart (write) 
    9294   INTEGER ::   numriw                !: logical unit for ice   restart (write) 
     95   INTEGER ::   numraw                !: logical unit for abl   restart (write) 
    9396   INTEGER ::   nrst_lst              !: number of restart to output next 
    9497 
  • NEMO/branches/2019/dev_r11265_ASINTER-01_Guillaume_ABL1D/src/OCE/IOM/iom_nf90.F90

    r11586 r11858  
    1919   !!---------------------------------------------------------------------- 
    2020   USE dom_oce         ! ocean space and time domain 
     21   USE sbc_oce, ONLY: jpka, ght_abl ! abl vertical level number and height 
    2122   USE lbclnk          ! lateal boundary condition / mpp exchanges 
    2223   USE iom_def         ! iom variables definitions 
     
    5657      LOGICAL                , INTENT(in   )           ::   ldok        ! check the existence  
    5758      INTEGER, DIMENSION(2,5), INTENT(in   ), OPTIONAL ::   kdompar     ! domain parameters:  
    58       INTEGER                , INTENT(in   ), OPTIONAL ::   kdlev       ! size of the third dimension 
     59      INTEGER                , INTENT(in   ), OPTIONAL ::   kdlev       ! size of the ice/abl third dimension 
    5960 
    6061      CHARACTER(LEN=256) ::   clinfo           ! info character 
     
    6970      INTEGER            ::   ihdf5            ! local variable for retrieval of value for NF90_HDF5 
    7071      LOGICAL            ::   llclobber        ! local definition of ln_clobber 
    71       INTEGER            ::   ilevels           ! vertical levels 
     72      INTEGER            ::   ilevels          ! vertical levels 
    7273      !--------------------------------------------------------------------- 
    7374      ! 
     
    7677      ! 
    7778      !                 !number of vertical levels 
    78       IF( PRESENT(kdlev) ) THEN   ;   ilevels = kdlev    ! use input value (useful for sea-ice) 
    79       ELSE                        ;   ilevels = jpk      ! by default jpk 
     79      IF( PRESENT(kdlev) )   THEN   ;   ilevels = kdlev    ! use input value (useful for sea-ice and abl) 
     80      ELSE                          ;   ilevels = jpk      ! by default jpk 
    8081      ENDIF 
    8182      ! 
     
    126127            CALL iom_nf90_check(NF90_DEF_DIM( if90id,            'x',   kdompar(1,1), idmy ), clinfo) 
    127128            CALL iom_nf90_check(NF90_DEF_DIM( if90id,            'y',   kdompar(2,1), idmy ), clinfo) 
    128             CALL iom_nf90_check(NF90_DEF_DIM( if90id,      'nav_lev',            jpk, idmy ), clinfo) 
    129             CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'time_counter', NF90_UNLIMITED, idmy ), clinfo) 
    130             IF( PRESENT(kdlev) )   & 
    131                CALL iom_nf90_check(NF90_DEF_DIM( if90id,    'numcat',          kdlev, idmy ), clinfo) 
     129            IF( PRESENT(kdlev) ) THEN 
     130              IF( kdlev == jpka ) THEN 
     131                 CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'nav_lev',          kdlev, idmy ), clinfo) 
     132                 CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'time_counter', NF90_UNLIMITED, idmy ), clinfo) 
     133              ELSE 
     134                 CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'nav_lev',            jpk, idmy ), clinfo) 
     135                 CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'time_counter', NF90_UNLIMITED, idmy ), clinfo) 
     136                 CALL iom_nf90_check(NF90_DEF_DIM( if90id,  'numcat',          kdlev, idmy ), clinfo) 
     137              ENDIF 
     138            ELSE 
     139               CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'nav_lev',            jpk, idmy ), clinfo) 
     140               CALL iom_nf90_check(NF90_DEF_DIM( if90id, 'time_counter', NF90_UNLIMITED, idmy ), clinfo) 
     141            ENDIF 
    132142            ! global attributes 
    133143            CALL iom_nf90_check(NF90_PUT_ATT( if90id, NF90_GLOBAL, 'DOMAIN_number_total'   , jpnij              ), clinfo) 
     
    584594         IF(     PRESENT(pv_r0d) ) THEN   ;   idims = 0 
    585595         ELSEIF( PRESENT(pv_r1d) ) THEN 
    586             IF( SIZE(pv_r1d,1) == jpk ) THEN   ;   idim3 = 3 
    587             ELSE                               ;   idim3 = 5 
     596            IF(( SIZE(pv_r1d,1) == jpk ).OR.( SIZE(pv_r1d,1) == jpka )) THEN   ;   idim3 = 3 
     597            ELSE                                                               ;   idim3 = 5 
    588598            ENDIF 
    589599                                              idims = 2   ;   idimid(1:idims) = (/idim3,4/) 
    590600         ELSEIF( PRESENT(pv_r2d) ) THEN   ;   idims = 3   ;   idimid(1:idims) = (/1,2  ,4/) 
    591601         ELSEIF( PRESENT(pv_r3d) ) THEN 
    592             IF( SIZE(pv_r3d,3) == jpk ) THEN   ;   idim3 = 3 
    593             ELSE                               ;   idim3 = 5 
     602            IF(( SIZE(pv_r3d,3) == jpk ).OR.( SIZE(pv_r3d,3) == jpka )) THEN   ;   idim3 = 3 
     603            ELSE                                                               ;   idim3 = 5 
    594604            ENDIF 
    595605                                              idims = 4   ;   idimid(1:idims) = (/1,2,idim3,4/) 
     
    674684               CALL iom_nf90_check( NF90_PUT_VAR  ( if90id, idmy, gphit(ix1:ix2, iy1:iy2) ), clinfo ) 
    675685               CALL iom_nf90_check( NF90_INQ_VARID( if90id, 'nav_lev'     , idmy ), clinfo ) 
    676                CALL iom_nf90_check( NF90_PUT_VAR  ( if90id, idmy, gdept_1d       ), clinfo ) 
     686               IF (iom_file(kiomid)%nlev == jpka) THEN   ;   CALL iom_nf90_check( NF90_PUT_VAR  ( if90id, idmy,  ght_abl), clinfo ) 
     687               ELSE                                      ;   CALL iom_nf90_check( NF90_PUT_VAR  ( if90id, idmy, gdept_1d), clinfo ) 
     688               ENDIF 
    677689               IF( NF90_INQ_VARID( if90id, 'numcat', idmy ) == nf90_noerr ) THEN 
    678690                  CALL iom_nf90_check( NF90_PUT_VAR  ( if90id, idmy, (/ (idlv, idlv = 1,iom_file(kiomid)%nlev) /)), clinfo ) 
Note: See TracChangeset for help on using the changeset viewer.