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 15540 for NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/SBC/sbcblk_skin_coare.F90 – NEMO

Ignore:
Timestamp:
2021-11-26T12:27:56+01:00 (3 years ago)
Author:
sparonuz
Message:

Mixed precision version, tested up to 30 years on ORCA2.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14116_HPC-10_mcastril_Mixed_Precision_implementation/src/OCE/SBC/sbcblk_skin_coare.F90

    r14072 r15540  
    3636 
    3737   !! Cool-skin related parameters: 
    38    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: dT_cs !: dT due to cool-skin effect 
     38   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: dT_cs !: dT due to cool-skin effect 
    3939   !                                                      ! => temperature difference between air-sea interface (z=0) 
    4040   !                                                      !    and right below viscous layer (z=delta) 
    4141 
    4242   !! Warm-layer related parameters: 
    43    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: dT_wl !: dT due to warm-layer effect 
     43   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: dT_wl !: dT due to warm-layer effect 
    4444   !                                                      ! => difference between "almost surface (right below 
    4545   !                                                      !    viscous layer, z=delta) and depth of bulk SST (z=gdept_1d(1)) 
    46    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: Hz_wl !: depth (aka thickness) of warm-layer [m] 
    47    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: Qnt_ac !: time integral / accumulated heat stored by the warm layer 
     46   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: Hz_wl !: depth (aka thickness) of warm-layer [m] 
     47   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: Qnt_ac !: time integral / accumulated heat stored by the warm layer 
    4848   !                                                      !         Qxdt => [J/m^2] (reset to zero every midnight) 
    49    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: Tau_ac !: time integral / accumulated momentum 
     49   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:), PUBLIC :: Tau_ac !: time integral / accumulated momentum 
    5050   !                                                      !         Tauxdt => [N.s/m^2] (reset to zero every midnight) 
    5151 
    52    REAL(wp), PARAMETER, PUBLIC :: Hwl_max = 20._wp    !: maximum depth of warm layer (adjustable) 
     52   REAL(dp), PARAMETER, PUBLIC :: Hwl_max = 20._wp    !: maximum depth of warm layer (adjustable) 
    5353   ! 
    54    REAL(wp), PARAMETER :: rich   = 0.65_wp   !: critical Richardson number 
     54   REAL(dp), PARAMETER :: rich   = 0.65_wp   !: critical Richardson number 
    5555   ! 
    56    REAL(wp), PARAMETER :: zfr0   = 0.5_wp    !: initial value of solar flux absorption 
     56   REAL(dp), PARAMETER :: zfr0   = 0.5_wp    !: initial value of solar flux absorption 
    5757   ! 
    5858   !!---------------------------------------------------------------------- 
     
    8181      !!------------------------------------------------------------------ 
    8282      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pQsw   ! net solar a.k.a shortwave radiation into the ocean (after albedo) [W/m^2] 
    83       REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pQnsol ! non-solar heat flux to the ocean [W/m^2] 
    84       REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pustar  ! friction velocity, temperature and humidity (u*,t*,q*) 
    85       REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pSST ! bulk SST [K] 
    86       REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pQlat  ! latent heat flux [W/m^2] 
     83      REAL(dp), DIMENSION(jpi,jpj), INTENT(in) :: pQnsol ! non-solar heat flux to the ocean [W/m^2] 
     84      REAL(dp), DIMENSION(jpi,jpj), INTENT(in) :: pustar  ! friction velocity, temperature and humidity (u*,t*,q*) 
     85      REAL(dp), DIMENSION(jpi,jpj), INTENT(in) :: pSST ! bulk SST [K] 
     86      REAL(dp), DIMENSION(jpi,jpj), INTENT(in) :: pQlat  ! latent heat flux [W/m^2] 
    8787      !!--------------------------------------------------------------------- 
    8888      INTEGER  :: ji, jj, jc 
    89       REAL(wp) :: zQabs, zdlt, zfr, zalfa, zqlat, zus 
     89      REAL(dp) :: zQabs, zdlt, zfr, zalfa, zqlat, zus 
    9090      !!--------------------------------------------------------------------- 
    9191      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
     
    131131      !!--------------------------------------------------------------------- 
    132132      REAL(wp), DIMENSION(jpi,jpj), INTENT(in)  :: pQsw     ! surface net solar radiation into the ocean [W/m^2]     => >= 0 ! 
    133       REAL(wp), DIMENSION(jpi,jpj), INTENT(in)  :: pQnsol   ! surface net non-solar heat flux into the ocean [W/m^2] => normally < 0 ! 
    134       REAL(wp), DIMENSION(jpi,jpj), INTENT(in)  :: pTau     ! wind stress [N/m^2] 
    135       REAL(wp), DIMENSION(jpi,jpj), INTENT(in)  :: pSST     ! bulk SST at depth gdept_1d(1) [K] 
     133      REAL(dp), DIMENSION(jpi,jpj), INTENT(in)  :: pQnsol   ! surface net non-solar heat flux into the ocean [W/m^2] => normally < 0 ! 
     134      REAL(dp), DIMENSION(jpi,jpj), INTENT(in)  :: pTau     ! wind stress [N/m^2] 
     135      REAL(dp), DIMENSION(jpi,jpj), INTENT(in)  :: pSST     ! bulk SST at depth gdept_1d(1) [K] 
    136136      INTEGER ,                     INTENT(in)  :: iwait    ! if /= 0 then wait before updating accumulated fluxes 
    137137      !! 
    138138      INTEGER :: ji,jj 
    139139      ! 
    140       REAL(wp) :: zdTwl, zHwl, zQabs, zfr 
    141       REAL(wp) :: zqac, ztac 
    142       REAL(wp) :: zalfa, zcd1, zcd2, flg 
    143       !!--------------------------------------------------------------------- 
    144  
    145       REAL(wp) :: ztime, znoon, zmidn 
     140      REAL(dp) :: zdTwl, zHwl, zQabs, zfr 
     141      REAL(dp) :: zqac, ztac 
     142      REAL(dp) :: zalfa, zcd1, zcd2, flg 
     143      !!--------------------------------------------------------------------- 
     144 
     145      REAL(dp) :: ztime, znoon, zmidn 
    146146      INTEGER  :: jl 
    147147 
     
    271271      !! L. Brodeau, october 2019 
    272272      !!--------------------------------------------------------------------- 
    273       REAL(wp)                :: delta_skin_layer 
    274       REAL(wp), INTENT(in)    :: palpha   ! thermal expansion coefficient of sea-water (SST accurate enough!) 
    275       REAL(wp), INTENT(in)    :: pQd ! < 0 !!! part of the net heat flux actually absorbed in the WL [W/m^2] 
     273      REAL(dp)                :: delta_skin_layer 
     274      REAL(dp), INTENT(in)    :: palpha   ! thermal expansion coefficient of sea-water (SST accurate enough!) 
     275      REAL(dp), INTENT(in)    :: pQd ! < 0 !!! part of the net heat flux actually absorbed in the WL [W/m^2] 
    276276      !                              !  => term "Q + Rs*fs" in eq.6 of Fairall et al. 1996 
    277       REAL(wp), INTENT(in)    :: pQlat    ! latent heat flux [W/m^2] 
    278       REAL(wp), INTENT(in)    :: pustar_a ! friction velocity in the air (u*) [m/s] 
    279       !!--------------------------------------------------------------------- 
    280       REAL(wp) :: zusw, zusw2, zlamb, zQd, ztf, ztmp 
     277      REAL(dp), INTENT(in)    :: pQlat    ! latent heat flux [W/m^2] 
     278      REAL(dp), INTENT(in)    :: pustar_a ! friction velocity in the air (u*) [m/s] 
     279      !!--------------------------------------------------------------------- 
     280      REAL(dp) :: zusw, zusw2, zlamb, zQd, ztf, ztmp 
    281281      !!--------------------------------------------------------------------- 
    282282 
     
    302302      !! Fraction of solar heat flux absorbed inside warm layer 
    303303      !!--------------------------------------------------------------------- 
    304       REAL(wp)             :: frac_solar_abs 
    305       REAL(wp), INTENT(in) :: pHwl   ! thickness of warm-layer [m] 
     304      REAL(dp)             :: frac_solar_abs 
     305      REAL(dp), INTENT(in) :: pHwl   ! thickness of warm-layer [m] 
    306306      !!--------------------------------------------------------------------- 
    307307      frac_solar_abs = 1._wp - ( 0.28*0.014  *(1._wp - EXP(-pHwl/0.014)) & 
Note: See TracChangeset for help on using the changeset viewer.