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

Changeset 12811


Ignore:
Timestamp:
2020-04-24T17:20:27+02:00 (4 years ago)
Author:
clem
Message:

debug a restartability issue. All sette tests passed now

Location:
NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/ICE/icethd_pnd.F90

    r12726 r12811  
    184184            h_ip_1d(ji)      = 0._wp 
    185185            h_il_1d(ji)      = 0._wp 
    186             ! 
    187             ! clem: problem with conservation or not ? 
    188186            !                                                         !--------------------------------! 
    189187         ELSE                                                         ! Case ice thickness >= rn_himin ! 
     
    267265               zhp = ( h_i_1d(ji) * ( rau0 - rhoi ) + h_ip_1d(ji) * ( rau0 - rhow * a_ip_1d(ji) / a_i_1d(ji) ) ) * r1_rau0 
    268266 
    269                ! Calculate the permeability of the ice (Assur 1958) 
     267               ! Calculate the permeability of the ice (Assur 1958, see Flocco 2010) 
    270268               DO jk = 1, nlay_i 
    271269                  zsbr = - 1.2_wp                                  & 
    272270                     &   - 21.8_wp    * ( t_i_1d(ji,jk) - rt0 )    & 
    273271                     &   - 0.919_wp   * ( t_i_1d(ji,jk) - rt0 )**2 & 
    274                      &   - 0.0178_wp  * ( t_i_1d(ji,jk) - rt0 )**3 ! clem: error here the factor was 0.01878 instead of 0.0178 (cf Flocco 2010) 
     272                     &   - 0.0178_wp  * ( t_i_1d(ji,jk) - rt0 )**3 
    275273                  ztmp(jk) = sz_i_1d(ji,jk) / zsbr 
    276274               END DO 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbc_ice.F90

    r12785 r12811  
    7070   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wndm_ice       !: wind speed module at T-point                 [m/s] 
    7171   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sstfrz         !: sea surface freezing temperature            [degC] 
    72    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   cloud_fra      !: cloud cover                                    [-] 
    7372#endif 
    7473 
     
    10099#endif 
    101100 
    102    REAL(wp), PUBLIC, SAVE ::   cldf_ice = 0.81    !: cloud fraction over sea ice, summer CLIO value   [-] 
     101   REAL(wp), PUBLIC, SAVE ::   pp_cldf = 0.81    !: cloud fraction over sea ice, summer CLIO value   [-] 
    103102 
    104103   !! arrays relating to embedding ice in the ocean 
     
    133132         &      qemp_ice(jpi,jpj)     , qevap_ice(jpi,jpj,jpl) , qemp_oce   (jpi,jpj)     ,   & 
    134133         &      qns_oce (jpi,jpj)     , qsr_oce  (jpi,jpj)     , emp_oce    (jpi,jpj)     ,   & 
    135          &      emp_ice (jpi,jpj)     , sstfrz   (jpi,jpj)     , cloud_fra  (jpi,jpj)     , STAT= ierr(2) ) 
     134         &      emp_ice (jpi,jpj)     , sstfrz   (jpi,jpj)     , STAT= ierr(2) ) 
    136135#endif 
    137136 
     
    169168   LOGICAL         , PUBLIC, PARAMETER ::   lk_si3     = .FALSE.  !: no SI3 ice model 
    170169   LOGICAL         , PUBLIC, PARAMETER ::   lk_cice    = .FALSE.  !: no CICE ice model 
    171    REAL(wp)        , PUBLIC, PARAMETER ::   cldf_ice = 0.81       !: cloud fraction over sea ice, summer CLIO value   [-] 
     170   REAL(wp)        , PUBLIC, PARAMETER ::   pp_cldf    = 0.81     !: cloud fraction over sea ice, summer CLIO value   [-] 
    172171   INTEGER         , PUBLIC, PARAMETER ::   jpl = 1  
    173172   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_ice, v_ice                        ! jpi, jpj 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbc_oce.F90

    r12132 r12811  
    136136   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   atm_co2           !: atmospheric pCO2                             [ppm] 
    137137   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: xcplmask          !: coupling mask for ln_mixcpl (warning: allocated in sbccpl) 
     138   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   cloud_fra         !: cloud cover (fraction of cloud in a gridcell) [-] 
    138139 
    139140   !!---------------------------------------------------------------------- 
     
    178179         &      fwficb  (jpi,jpj), fwficb_b(jpi,jpj), STAT=ierr(3) ) 
    179180         ! 
    180       ALLOCATE( tprecip(jpi,jpj) , sprecip(jpi,jpj) , fr_i(jpi,jpj) ,     & 
    181          &      atm_co2(jpi,jpj) ,                                        & 
    182          &      ssu_m  (jpi,jpj) , sst_m(jpi,jpj) , frq_m(jpi,jpj) ,      & 
    183          &      ssv_m  (jpi,jpj) , sss_m(jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) ) 
     181      ALLOCATE( tprecip(jpi,jpj) , sprecip  (jpi,jpj) , fr_i(jpi,jpj) ,   & 
     182         &      atm_co2(jpi,jpj) , cloud_fra(jpi,jpj) ,                   & 
     183         &      ssu_m  (jpi,jpj) , sst_m    (jpi,jpj) , frq_m(jpi,jpj) ,  & 
     184         &      ssv_m  (jpi,jpj) , sss_m    (jpi,jpj) , ssh_m(jpi,jpj) , STAT=ierr(4) ) 
    184185         ! 
    185186      ALLOCATE( e3t_m(jpi,jpj) , STAT=ierr(5) ) 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbcblk.F90

    r12785 r12811  
    242242      ENDDO 
    243243      ! fill cloud cover array with constant value if "not used" 
    244       IF( TRIM(sf(jp_cc)%clrootname) == 'NOT USED' )   sf(jp_cc)%fnow(:,:,1) = cldf_ice 
     244      IF( TRIM(sf(jp_cc)%clrootname) == 'NOT USED' )   sf(jp_cc)%fnow(:,:,1) = pp_cldf 
    245245          
    246246      IF ( ln_wave ) THEN 
     
    395395      zst(:,:) = pst(:,:) + rt0      ! convert SST from Celcius to Kelvin (and set minimum value far above 0 K) 
    396396 
     397      ! --- cloud cover --- ! 
     398      cloud_fra(:,:) = sf(jp_cc)%fnow(:,:,1) 
     399 
    397400      ! ----------------------------------------------------------------------------- ! 
    398401      !      0   Wind components and module at T-point relative to the moving ocean   ! 
     
    914917      END DO 
    915918 
    916       ! --- cloud cover --- ! 
    917       cloud_fra(:,:) = sf(jp_cc)%fnow(:,:,1) 
    918        
    919919      ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 
    920920      ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/src/OCE/SBC/sbccpl.F90

    r12785 r12811  
    21002100!!$         cloud_fra(:,:) = frcv(jpr_clfra)*z3(:,:,1) 
    21012101!!$      END SELECT 
    2102       zcloud_fra(:,:) = cldf_ice   ! should be real cloud fraction instead (as in the bulk) but needs to be read from atm. 
     2102      zcloud_fra(:,:) = pp_cldf   ! should be real cloud fraction instead (as in the bulk) but needs to be read from atm. 
    21032103      IF( ln_mixcpl ) THEN 
    21042104         cloud_fra(:,:) = cloud_fra(:,:) * xcplmask(:,:,0) + zcloud_fra(:,:)* zmsk(:,:) 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/ICE_ADV1D/MY_SRC/usrdef_sbc.F90

    r10513 r12811  
    108108      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness 
    109109      !! 
     110      INTEGER  ::   jl 
    110111      REAL(wp) ::   zfr1, zfr2                 ! local variables 
    111112      REAL(wp), DIMENSION(jpi,jpj) ::   zsnw   ! snw distribution after wind blowing 
     113      REAL(wp), DIMENSION(jpi,jpj) ::   ztri 
    112114      !!--------------------------------------------------------------------- 
    113115      ! 
     
    142144 
    143145      ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 
    144       zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice )            ! transmission when hi>10cm 
    145       zfr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice )            ! zfr2 such that zfr1 + zfr2 to equal 1 
     146      cloud_fra(:,:) = pp_cldf 
     147      ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm 
    146148      ! 
    147       WHERE    ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) <  0.1_wp )       ! linear decrease from hi=0 to 10cm   
    148          qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) ) 
    149       ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp )       ! constant (zfr1) when hi>10cm 
    150          qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1 
    151       ELSEWHERE                                                         ! zero when hs>0 
    152          qtr_ice_top(:,:,:) = 0._wp  
    153       END WHERE 
    154            
     149      DO jl = 1, jpl 
     150         WHERE    ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) <  0.1_wp )     ! linear decrease from hi=0 to 10cm   
     151            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) ) 
     152         ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp )     ! constant (ztri) when hi>10cm 
     153            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:) 
     154         ELSEWHERE                                                         ! zero when hs>0 
     155            qtr_ice_top(:,:,jl) = 0._wp 
     156         END WHERE 
     157      ENDDO 
     158          
     159  
    155160   END SUBROUTINE usrdef_sbc_ice_flx 
    156161 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/ICE_ADV2D/MY_SRC/usrdef_sbc.F90

    r10515 r12811  
    108108      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   phi    ! ice thickness 
    109109      !! 
     110      INTEGER  ::   jl 
    110111      REAL(wp) ::   zfr1, zfr2                 ! local variables 
    111112      REAL(wp), DIMENSION(jpi,jpj) ::   zsnw   ! snw distribution after wind blowing 
     113      REAL(wp), DIMENSION(jpi,jpj) ::   ztri 
    112114      !!--------------------------------------------------------------------- 
    113115      ! 
     
    142144 
    143145      ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 
    144       zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice )            ! transmission when hi>10cm 
    145       zfr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice )            ! zfr2 such that zfr1 + zfr2 to equal 1 
     146      cloud_fra(:,:) = pp_cldf 
     147      ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm 
    146148      ! 
    147       WHERE    ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) <  0.1_wp )       ! linear decrease from hi=0 to 10cm   
    148          qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) ) 
    149       ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp )       ! constant (zfr1) when hi>10cm 
    150          qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1 
    151       ELSEWHERE                                                         ! zero when hs>0 
    152          qtr_ice_top(:,:,:) = 0._wp  
    153       END WHERE 
    154            
     149      DO jl = 1, jpl 
     150         WHERE    ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) <  0.1_wp )     ! linear decrease from hi=0 to 10cm   
     151            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) ) 
     152         ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp )     ! constant (ztri) when hi>10cm 
     153            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:) 
     154         ELSEWHERE                                                         ! zero when hs>0 
     155            qtr_ice_top(:,:,jl) = 0._wp 
     156         END WHERE 
     157      ENDDO 
     158          
     159  
    155160   END SUBROUTINE usrdef_sbc_ice_flx 
    156161 
  • NEMO/branches/2020/r4.0-HEAD_r12713_clem_dan_fixcpl/tests/ICE_AGRIF/MY_SRC/usrdef_sbc.F90

    r10516 r12811  
    108108      REAL(wp), DIMENSION(:,:,:), INTENT(in)  ::   phi    ! ice thickness 
    109109      !! 
     110      INTEGER  ::   jl 
    110111      REAL(wp) ::   zfr1, zfr2                 ! local variables 
    111112      REAL(wp), DIMENSION(jpi,jpj) ::   zsnw   ! snw distribution after wind blowing 
     113      REAL(wp), DIMENSION(jpi,jpj) ::   ztri 
    112114      !!--------------------------------------------------------------------- 
    113115      ! 
     
    142144 
    143145      ! --- shortwave radiation transmitted below the surface (W/m2, see Grenfell Maykut 77) --- ! 
    144       zfr1 = ( 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice )            ! transmission when hi>10cm 
    145       zfr2 = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice )            ! zfr2 such that zfr1 + zfr2 to equal 1 
     146      cloud_fra(:,:) = pp_cldf 
     147      ztri(:,:) = 0.18 * ( 1.0 - cloud_fra(:,:) ) + 0.35 * cloud_fra(:,:)  ! surface transmission when hi>10cm 
    146148      ! 
    147       WHERE    ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) <  0.1_wp )       ! linear decrease from hi=0 to 10cm   
    148          qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( zfr1 + zfr2 * ( 1._wp - phi(:,:,:) * 10._wp ) ) 
    149       ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp )       ! constant (zfr1) when hi>10cm 
    150          qtr_ice_top(:,:,:) = qsr_ice(:,:,:) * zfr1 
    151       ELSEWHERE                                                         ! zero when hs>0 
    152          qtr_ice_top(:,:,:) = 0._wp  
    153       END WHERE 
     149      DO jl = 1, jpl 
     150         WHERE    ( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) <  0.1_wp )     ! linear decrease from hi=0 to 10cm   
     151            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ( ztri(:,:) + ( 1._wp - ztri(:,:) ) * ( 1._wp - phi(:,:,jl) * 10._wp ) ) 
     152         ELSEWHERE( phs(:,:,jl) <= 0._wp .AND. phi(:,:,jl) >= 0.1_wp )     ! constant (ztri) when hi>10cm 
     153            qtr_ice_top(:,:,jl) = qsr_ice(:,:,jl) * ztri(:,:) 
     154         ELSEWHERE                                                         ! zero when hs>0 
     155            qtr_ice_top(:,:,jl) = 0._wp 
     156         END WHERE 
     157      ENDDO 
    154158           
    155159   END SUBROUTINE usrdef_sbc_ice_flx 
Note: See TracChangeset for help on using the changeset viewer.