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 11403 for NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavmlt.F90 – NEMO

Ignore:
Timestamp:
2019-08-05T19:14:52+02:00 (5 years ago)
Author:
mathiot
Message:

ENHANCE-02_ISF_nemo : add comments, renaming file (AGRIF), add isfload module (ticket #2142)

File:
1 moved

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcavmlt.F90

    r11395 r11403  
    1212   !!---------------------------------------------------------------------- 
    1313   USE oce            ! ocean dynamics and tracers 
    14    USE isf 
    15    USE isfdiags 
     14   USE isf            ! ice shelf public variables 
    1615   USE dom_oce        ! ocean space and time domain 
    1716   USE phycst         ! physical constants 
    1817   USE eosbn2         ! equation of state 
    19    USE zdfdrg         ! vertical physics: top/bottom drag coef. 
    2018   ! 
    2119   USE in_out_manager ! I/O manager 
    2220   USE iom            ! I/O library 
    2321   USE fldread        ! read input field at current time step 
    24    USE lbclnk         ! 
     22   USE lib_fortran 
    2523 
    2624   IMPLICIT NONE 
     
    4038! ------------------------------------------------------------------------------------------------------- 
    4139 
    42    SUBROUTINE isfcav_mlt(kt, pgt, pgs , pttbl, pstbl,   & 
    43       &                           pqhc, pqoce, pqfwf    ) 
    44       !!---------------------------------------------------------------------- 
    45       !! ** Purpose    :  
    46       !! 
    47       !! ** Method     :  
    48       !!--------------------------------------------------------------------- 
    49       !!-------------------------- OUT ------------------------------------- 
    50       REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqoce, pqfwf  ! heat and fwf fluxes 
     40   SUBROUTINE isfcav_mlt(kt, pgt, pgs , pttbl, pstbl, & 
     41      &                           pqhc, pqoce, pqfwf  ) 
     42      !!---------------------------------------------------------------------- 
     43      !! 
     44      !! ** Purpose    : compute ice shelf fwf/heqt fluxes  
     45      !! 
     46      !!--------------------------------------------------------------------- 
     47      !!-------------------------- OUT ------------------------------------- 
     48      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pqhc, pqoce, pqfwf  ! heat and fwf fluxes 
    5149      !!-------------------------- IN  ------------------------------------- 
    5250      INTEGER, INTENT(in) :: kt 
     
    5957      SELECT CASE ( cn_isfcav_mlt ) 
    6058      CASE ( 'spe' )   ! ice shelf melt specified (read input file, and heat fluxes derived from 
    61          CALL isfmlt_spe( kt, pstbl,                  & 
    62             &                  pqhc, pqoce, pqfwf    ) 
     59         CALL isfmlt_spe( kt, pstbl,               & 
     60            &                  pqhc, pqoce, pqfwf  ) 
    6361      CASE ( '2eq' )   !  ISOMIP  formulation (2 equations) for volume flux (Hunter et al., 2006) 
    64          CALL isfmlt_2eq( pgt, pttbl, pstbl,          & 
    65             &                  pqhc , pqoce, pqfwf    ) 
     62         CALL isfmlt_2eq( pgt, pttbl, pstbl,       & 
     63            &                  pqhc , pqoce, pqfwf ) 
    6664      CASE ( '3eq' )   ! ISOMIP+ formulation (3 equations) for volume flux (Asay-Davis et al., 2015) 
    67          CALL isfmlt_3eq( pgt, pgs , pttbl, pstbl,   & 
    68             &                  pqhc, pqoce, pqfwf    ) 
     65         CALL isfmlt_3eq( pgt, pgs , pttbl, pstbl, & 
     66            &                  pqhc, pqoce, pqfwf  ) 
    6967      CASE ( 'oasis' ) ! fwf pass trough oasis 
    70          !CALL isfmlt_oasis( kt, pstbl,               & 
    71          !   &                    zqhc, zqoce, pqfwf  ) 
     68         CALL isfmlt_oasis( kt, pstbl,              & 
     69            &                   pqhc, pqoce, pqfwf  ) 
    7270      CASE DEFAULT 
    7371         CALL ctl_stop('STOP', 'unknown isf melt formulation : cn_isfcav (should not see this)') 
     
    8078! ------------------------------------------------------------------------------------------------------- 
    8179 
    82    SUBROUTINE isfmlt_spe(kt, pstbl,                  &  ! <<== in 
    83       &                       pqhc, pqoce, pqfwf    )  ! ==>> out 
    84       !!---------------------------------------------------------------------- 
    85       !! ** Purpose    :  
    86       !! 
    87       !! ** Method     :  
    88       !!--------------------------------------------------------------------- 
    89       !!-------------------------- OUT ------------------------------------- 
    90       REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqoce, pqfwf  ! heat content, latent heat and fwf fluxes 
    91       !!-------------------------- IN  ------------------------------------- 
    92       INTEGER                     , INTENT(in   ) :: kt 
    93       REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pstbl         ! salinity in top boundary layer 
    94       !!-------------------------------------------------------------------- 
    95       REAL(wp), DIMENSION(jpi,jpj) :: ztfrz         ! freezing temperature 
     80   SUBROUTINE isfmlt_spe(kt, pstbl,              &  ! <<== in 
     81      &                      pqhc , pqoce, pqfwf )  ! ==>> out 
     82      !!---------------------------------------------------------------------- 
     83      !! ** Purpose    : - read ice shelf melt from forcing file 
     84      !!                 - compute ocea-ice heat flux (assuming it is equal to latent heat) 
     85      !!                 - compute heat content flux 
     86      !!--------------------------------------------------------------------- 
     87      !!-------------------------- OUT ------------------------------------- 
     88      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pqhc, pqoce, pqfwf  ! heat content, latent heat and fwf fluxes 
     89      !!-------------------------- IN  ------------------------------------- 
     90      INTEGER                     , INTENT(in   ) :: kt                  ! current time step 
     91      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pstbl               ! salinity in tbl 
     92      !!-------------------------------------------------------------------- 
     93      REAL(wp), DIMENSION(jpi,jpj) :: ztfrz                              ! tbl freezing temperature 
    9694      !!-------------------------------------------------------------------- 
    9795      ! 
     
    103101      ! 
    104102      ! define fwf and qoce 
    105       pqfwf(:,:) = -sf_isfcav_fwf(1)%fnow(:,:,1)            ! fwf 
    106103      ! ocean heat flux is assume to be equal to the latent heat 
    107       pqoce(:,:) =  pqfwf(:,:) * rLfusisf             ! ocean heat flux 
    108       pqhc (:,:) =  pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux 
     104      pqfwf(:,:) = - sf_isfcav_fwf(1)%fnow(:,:,1)      ! fwf                ( >0 out) 
     105      pqoce(:,:) = - pqfwf(:,:) * rLfusisf             ! ocean heat flux    ( >0 out) 
     106      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux  ( >0 out) 
    109107      ! 
    110108   END SUBROUTINE isfmlt_spe 
    111109 
    112    SUBROUTINE isfmlt_2eq(pgt, pttbl, pstbl,          &  ! <<== in 
    113       &                       pqhc , pqoce, pqfwf    )  ! ==>> out 
    114       !!---------------------------------------------------------------------- 
    115       !! ** Purpose    :  
    116       !! 
    117       !! ** Method     :  
    118       !!--------------------------------------------------------------------- 
    119       !!-------------------------- OUT ------------------------------------- 
    120       REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqoce, pqfwf  ! hean content, ocean-ice heat and fwf fluxes 
     110   SUBROUTINE isfmlt_2eq(pgt, pttbl, pstbl,       &  ! <<== in 
     111      &                       pqhc , pqoce, pqfwf )  ! ==>> out 
     112      !!---------------------------------------------------------------------- 
     113      !! ** Purpose    : Compute ice shelf fwf/heqt fluxes using ISOMIP formulation (Hunter et al., 2006) 
     114      !! 
     115      !! ** Method     : The ice shelf melt latent heat is defined as being equal to the ocean/ice heat flux. 
     116      !!                 From this we can derived the fwf, ocean/ice heat flux and the heat content flux as being : 
     117      !!                   qfwf  = Gammat * Rau0 * Cp * ( Tw - Tfrz ) / Lf  
     118      !!                   qhoce = qlat 
     119      !!                   qhc   = qfwf * Cp * Tfrz 
     120      !! 
     121      !! ** Reference  : Hunter,  J.  R.:  Specification  for  test  models  of  ice  shelf  cavities,   
     122      !!                 Tech.  Rep.  June,  Antarctic  Climate  &  Ecosystems  Cooperative  Research  Centre,  available  at:   
     123      !!                 http://staff.acecrc.org.au/~bkgalton/ISOMIP/test_cavities.pdf (last access: 21 July 2016), 2006. 
     124      !!--------------------------------------------------------------------- 
     125      !!-------------------------- OUT ------------------------------------- 
     126      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pqhc, pqoce, pqfwf  ! hean content, ocean-ice heat and fwf fluxes 
    121127      !!-------------------------- IN  ------------------------------------- 
    122128      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pgt           ! temperature exchange coeficient 
     
    124130      !!-------------------------------------------------------------------- 
    125131      REAL(wp), DIMENSION(jpi,jpj) :: ztfrz         ! freezing temperature 
     132      REAL(wp), DIMENSION(jpi,jpj) :: zthd          ! thermal driving 
    126133      !!-------------------------------------------------------------------- 
    127134      ! 
     
    129136      CALL eos_fzp( pstbl(:,:), ztfrz(:,:), risfdep(:,:) ) 
    130137      ! 
     138      ! thermal driving 
     139      zthd (:,:) = pttbl(:,:) - ztfrz(:,:) 
     140      ! 
    131141      ! compute ocean-ice heat flux and then derive fwf assuming that ocean heat flux equal latent heat 
    132       pqfwf(:,:) = - pgt(:,:) * rau0_rcp * ( pttbl(:,:)-ztfrz(:,:) ) * r1_Lfusisf  ! fresh water flux ( > 0 out ) 
    133       pqoce(:,:) = - pqfwf(:,:) * rLfusisf                                         ! ocea-ice flux (assume to be equal to latent heat flux) ( > 0 out ) 
    134       pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp                                 ! heat content flux ( > 0 out ) 
     142      pqfwf(:,:) = - pgt(:,:) * rau0_rcp * zthd(:,:) * r1_Lfusisf  ! fresh water flux ( > 0 out ) 
     143      pqoce(:,:) = - pqfwf(:,:) * rLfusisf                         ! ocea-ice flux    ( > 0 out ) 
     144      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp                 ! heat content flux ( > 0 out ) 
    135145      ! 
    136146      ! output thermal driving 
    137       CALL iom_put('isfthermald_cav',( pttbl(:,:)-ztfrz(:,:) )) 
     147      CALL iom_put('isfthermald_cav', zthd ) 
    138148      ! 
    139149   END SUBROUTINE isfmlt_2eq 
    140150 
    141    SUBROUTINE isfmlt_3eq(pgt, pgs , pttbl, pstbl,   & 
    142       &                       pqhc, pqoce, pqfwf    ) 
    143       !!---------------------------------------------------------------------- 
    144       !! ** Purpose    :  
    145       !! 
    146       !! ** Method     :  
    147       !!--------------------------------------------------------------------- 
    148       !!-------------------------- OUT ------------------------------------- 
    149       REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqoce, pqfwf  ! latent heat and fwf fluxes 
    150       !!-------------------------- IN  ------------------------------------- 
    151       REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pgt  , pgs    ! temperature exchange coeficient 
    152       REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pttbl, pstbl  ! temperature and salinity in top boundary layer 
    153       !!-------------------------------------------------------------------- 
    154       REAL(wp) :: zeps1,zeps2,zeps3,zeps4,zeps6,zeps7 
    155       REAL(wp) :: zaqe,zbqe,zcqe,zaqer,zdis,zsfrz,zcfac 
     151   SUBROUTINE isfmlt_3eq(pgt, pgs , pttbl, pstbl, & 
     152      &                       pqhc, pqoce, pqfwf  ) 
     153      !!---------------------------------------------------------------------- 
     154      !! ** Purpose    : Compute ice shelf fwf/heqt fluxes using the 3 equation formulation  
     155      !! 
     156      !! ** Method     : The melt rate is determined considering the heat balance, the salt balance 
     157      !!                 at the phase change interface and a linearisation of the equation of state. 
     158      !! 
     159      !! ** Reference  : - Holland, D. M. and Jenkins, A., 
     160      !!                   Modeling Thermodynamic Ice-Ocean Interactions at the Base of an Ice Shelf, 
     161      !!                   J. Phys. Oceanogr., 29, 1999. 
     162      !!                 - Asay-Davis, X. S., Cornford, S. L., Durand, G., Galton-Fenzi, B. K., Gladstone,  
     163      !!                   R. M., Gudmundsson, G. H., Hattermann, T., Holland, D. M., Holland, D., Holland,  
     164      !!                   P. R., Martin, D. F., Mathiot, P., Pattyn, F., and Seroussi, H.: 
     165      !!                   Experimental design for three interrelated marine ice sheet and ocean model intercomparison projects:  
     166      !!                   MISMIP v. 3 (MISMIP +), ISOMIP v. 2 (ISOMIP +) and MISOMIP v. 1 (MISOMIP1),  
     167      !!                   Geosci. Model Dev., 9, 2471-2497, https://doi.org/10.5194/gmd-9-2471-2016, 2016.  
     168      !!--------------------------------------------------------------------- 
     169      !!-------------------------- OUT ------------------------------------- 
     170      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pqhc, pqoce, pqfwf  ! latent heat and fwf fluxes 
     171      !!-------------------------- IN  ------------------------------------- 
     172      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pgt  , pgs          ! heat/salt exchange coeficient 
     173      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pttbl, pstbl        ! mean temperature and salinity in top boundary layer 
     174      !!-------------------------------------------------------------------- 
     175      REAL(wp) :: zeps1,zeps2,zeps3,zeps4,zeps6,zeps7       ! dummy local scalar for quadratic equation resolution 
     176      REAL(wp) :: zaqe,zbqe,zcqe,zaqer,zdis,zsfrz,zcfac     ! dummy local scalar for quadratic equation resolution 
    156177      REAL(wp) :: zeps = 1.e-20 
    157       REAL(wp), DIMENSION(jpi,jpj) :: ztfrz             ! freezing point 
    158       REAL(wp), DIMENSION(jpi,jpj) :: zqcon             ! conductive flux through the ice shelf 
     178      REAL(wp), DIMENSION(jpi,jpj) :: ztfrz         ! freezing point 
     179      REAL(wp), DIMENSION(jpi,jpj) :: zqcon         ! conductive flux through the ice shelf 
     180      REAL(wp), DIMENSION(jpi,jpj) :: zthd          ! thermal driving 
    159181      ! 
    160182      INTEGER  ::   ji, jj     ! dummy loop indices 
     
    162184      ! 
    163185      ! compute upward heat flux zhtflx and upward water flux zwflx 
    164       ! Resolution of a 2d equation from equation 24, 25 and 26 
     186      ! Resolution of a 3d equation from equation 24, 25 and 26 (note conduction through the ice has been added to Eq 24) 
    165187      DO jj = 1, jpj 
    166188         DO ji = 1, jpi 
     
    188210            ztfrz(ji,jj) = zeps4 + risf_lamb1 * zsfrz 
    189211            ! 
     212            ! thermal driving 
     213            zthd(ji,jj) = pttbl(ji,jj) - ztfrz(ji,jj) 
     214            ! 
    190215            ! compute the upward water and heat flux (eq. 24 and eq. 26) 
    191             ! ocean heat content flux added later on. 
    192             pqfwf(ji,jj) = rau0 * pgs(ji,jj) * ( zsfrz - pstbl(ji,jj) ) / MAX(zsfrz,zeps) ! fresh water flux (> 0 out) 
    193             pqoce(ji,jj) = pgt(ji,jj) * rau0_rcp * ( pttbl(ji,jj) - ztfrz(ji,jj) )        ! ocean-ice heat flux (> 0 out) 
    194             pqhc (ji,jj) = pqfwf(ji,jj) * ztfrz(ji,jj) * rcp                              ! heat content   flux (> 0 out) 
    195             zqcon(ji,jj) = zeps3 * ( ztfrz(ji,jj) - rtsurf ) ! to be check 
     216            pqfwf(ji,jj) = rau0     * pgs(ji,jj) * ( zsfrz - pstbl(ji,jj) ) / MAX(zsfrz,zeps) ! fresh water flux    (> 0 out) 
     217            pqoce(ji,jj) = rau0_rcp * pgt(ji,jj) * zthd (ji,jj)                               ! ocean-ice heat flux (> 0 out) 
     218            pqhc (ji,jj) = rcp      * pqfwf(ji,jj) * ztfrz(ji,jj)                             ! heat content  flux (> 0 out) 
     219            ! 
     220            zqcon(ji,jj) = zeps3 * ( ztfrz(ji,jj) - rtsurf )                                  ! conductive flux through the ice (> 0 out) 
    196221            ! 
    197222         END DO 
     
    202227      ! 
    203228      ! output thermal driving 
    204       CALL iom_put('isfthermald_cav',( pttbl(:,:) - ztfrz(:,:) )) 
     229      CALL iom_put('isfthermald_cav', zthd) 
    205230      ! 
    206231   END SUBROUTINE isfmlt_3eq 
     232 
     233   SUBROUTINE isfmlt_oasis(kt, pstbl,              &  ! <<== in 
     234      &                        pqhc , pqoce, pqfwf )  ! ==>> out 
     235      !!---------------------------------------------------------------------- 
     236      !! 
     237      !! ** Purpose    : scale the fwf read from input file by the total amount received by the sbccpl interface 
     238      !! 
     239      !! ** Purpose    : - read ice shelf melt from forcing file => pattern 
     240      !!                 - total amount of fwf is given by sbccpl (fwfisf_cpl) 
     241      !!                 - scale fwf and compute heat fluxes 
     242      !! 
     243      !!--------------------------------------------------------------------- 
     244      !!-------------------------- OUT ------------------------------------- 
     245      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pqhc, pqoce, pqfwf  ! heat content, latent heat and fwf fluxes 
     246      !!-------------------------- IN  ------------------------------------- 
     247      INTEGER                     , INTENT(in   ) :: kt                  ! current time step 
     248      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pstbl               ! salinity in tbl 
     249      !!-------------------------------------------------------------------- 
     250      REAL(wp)                     :: zfwf_fld, zfwf_cpl                 ! total fwf in the forcing fields (pattern) and from the cpl interface (amount) 
     251      REAL(wp), DIMENSION(jpi,jpj) :: ztfrz                              ! tbl freezing temperature 
     252      REAL(wp), DIMENSION(jpi,jpj) :: zfwf                               ! 2d fwf map after scaling 
     253      !!-------------------------------------------------------------------- 
     254      ! 
     255      ! Calculate freezing temperature 
     256      CALL eos_fzp( pstbl(:,:), ztfrz(:,:), risfdep(:,:) ) 
     257      ! 
     258      ! read input file 
     259      CALL fld_read ( kt, nn_fsbc, sf_isfcav_fwf ) 
     260      ! 
     261      ! ice shelf 2d map 
     262      zfwf(:,:) = - sf_isfcav_fwf(1)%fnow(:,:,1) 
     263      ! 
     264      ! compute glob sum from input file 
     265      zfwf_fld = glob_sum('isfcav_mlt', zfwf(:,:)) 
     266      ! 
     267      ! compute glob sum from atm->oce ice shelf fwf 
     268      zfwf_cpl = glob_sum('isfcav_mlt', fwfisf_cpl(:,:)) 
     269      ! 
     270      ! scale fwf 
     271      zfwf(:,:) = zfwf(:,:) * zfwf_cpl / zfwf_fld 
     272      !  
     273      ! define fwf and qoce 
     274      ! ocean heat flux is assume to be equal to the latent heat 
     275      pqfwf(:,:) =   zfwf(:,:)                         ! fwf                ( >0 out) 
     276      pqoce(:,:) = - pqfwf(:,:) * rLfusisf             ! ocean heat flux    ( >0 out) 
     277      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux  ( >0 out) 
     278      ! 
     279   END SUBROUTINE isfmlt_oasis 
    207280 
    208281   !SUBROUTINE isfmlt_3eq_frz_ktm1 
Note: See TracChangeset for help on using the changeset viewer.