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.
isfparmlt.F90 in NEMO/branches/2019/UKMO_MERGE_2019/src/OCE/ISF – NEMO

source: NEMO/branches/2019/UKMO_MERGE_2019/src/OCE/ISF/isfparmlt.F90 @ 12377

Last change on this file since 12377 was 12077, checked in by mathiot, 4 years ago

include ENHANCE-02_ISF_nemo in UKMO merge branch

File size: 11.6 KB
RevLine 
[11395]1MODULE isfparmlt
2   !!======================================================================
[11403]3   !!                       ***  MODULE  isfparmlt  ***
[11541]4   !! Ice shelf parametrisation module :  update surface ocean boundary condition under ice
5   !!                   shelf using an ice shelf melt parametrisation
[11395]6   !!======================================================================
7   !! History :  4.0  ! original code
8   !!----------------------------------------------------------------------
9
[12077]10   USE isf_oce                  ! ice shelf
[11852]11   USE isftbl , ONLY: isf_tbl   ! ice shelf depth average
[11395]12
[11852]13   USE dom_oce                  ! ocean space and time domain
[12068]14   USE oce    , ONLY: ts        ! ocean dynamics and tracers
[11852]15   USE phycst , ONLY: rcp, rau0 ! physical constants
16   USE eosbn2 , ONLY: eos_fzp   ! equation of state
[11395]17
[11852]18   USE in_out_manager              ! I/O manager
19   USE iom        , ONLY: iom_put  ! I/O library
[11931]20   USE fldread    , ONLY: fld_read, FLD, FLD_N !
[11852]21   USE lib_fortran, ONLY: glob_sum !
22   USE lib_mpp    , ONLY: ctl_stop !
23
[11395]24   IMPLICIT NONE
25
26   PRIVATE
27
28   PUBLIC  isfpar_mlt 
29   
30   !!----------------------------------------------------------------------
31   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
32   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
33   !! Software governed by the CeCILL license (see ./LICENSE)
34   !!----------------------------------------------------------------------
35CONTAINS
36
37! -------------------------------------------------------------------------------------------------------
38! -------------------------------- PUBLIC SUBROUTINE ----------------------------------------------------
39! -------------------------------------------------------------------------------------------------------
40
[12068]41  SUBROUTINE isfpar_mlt( kt, Kmm, pqhc, pqoce, pqfwf )
[11395]42      !!---------------------------------------------------------------------
[11494]43      !!                  ***  ROUTINE isfpar_mlt  ***
[11395]44      !!
45      !! ** Purpose : Compute Salt and Heat fluxes related to ice_shelf
46      !!              melting and freezing
47      !!
[11403]48      !! ** Method  :  2 parameterizations are available according
49      !!                        1 : Specified melt flux
[11395]50      !!                        2 : Beckmann & Goose parameterization
[11931]51      !!
[11395]52      !!-------------------------- OUT -------------------------------------
[11494]53      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqfwf, pqoce, pqhc  ! fresh water, ice-ocean heat and heat content fluxes
[11395]54      !!-------------------------- IN  -------------------------------------
55      INTEGER, INTENT(in) ::   kt   ! ocean time step
[12068]56      INTEGER, INTENT(in) ::   Kmm  ! ocean time level index
[11395]57      !!---------------------------------------------------------------------
58      !
59      ! Choose among the available ice shelf parametrisation
60      SELECT CASE ( cn_isfpar_mlt )
61      CASE ( 'spe' )    ! specified runoff in depth (Mathiot et al., 2017 in preparation)
[12068]62         CALL isfpar_mlt_spe(kt, Kmm, pqhc, pqoce, pqfwf)
[11395]63      CASE ( 'bg03' )    ! Beckmann and Goosse parametrisation
[12068]64         CALL isfpar_mlt_bg03(kt, Kmm, pqhc, pqoce, pqfwf)
[11395]65      CASE ( 'oasis' )
[12068]66         CALL isfpar_mlt_oasis( kt, Kmm, pqhc, pqoce, pqfwf)
[11395]67      CASE DEFAULT
68         CALL ctl_stop('STOP', 'unknown isf melt formulation : cn_isfpar (should not see this)')
69      END SELECT
70      !
71   END SUBROUTINE isfpar_mlt
72
73! -------------------------------------------------------------------------------------------------------
74! -------------------------------- PRIVATE SUBROUTINE ---------------------------------------------------
75! -------------------------------------------------------------------------------------------------------
76
[12068]77   SUBROUTINE isfpar_mlt_spe(kt, Kmm, pqhc, pqoce, pqfwf)
[11395]78      !!---------------------------------------------------------------------
[11403]79      !!                  ***  ROUTINE isfpar_mlt_spe  ***
[11395]80      !!
81      !! ** Purpose : prescribed ice shelf melting in case ice shelf cavities are closed.
82      !!              data read into a forcing files.
83      !!
84      !!-------------------------- OUT -------------------------------------
[11494]85      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqfwf, pqoce  ! fresh water and ice-ocean heat fluxes
[11395]86      !!-------------------------- IN  -------------------------------------
87      INTEGER,  INTENT(in) :: kt
[12068]88      INTEGER,  INTENT(in) :: Kmm    !  ocean time level index
[11395]89      !!--------------------------------------------------------------------
90      INTEGER :: jk
91      REAL(wp), DIMENSION(jpi,jpj,jpk)  :: ztfrz3d
92      REAL(wp), DIMENSION(jpi,jpj)      :: ztfrz
93      !!--------------------------------------------------------------------
94      !
[11403]95      ! 0. ------------Read specified runoff
[11852]96      CALL fld_read ( kt, 1, sf_isfpar_fwf   )
[11395]97      !
98      ! compute ptfrz
[11403]99      ! 1. ------------Mean freezing point
[11395]100      DO jk = 1,jpk
[12068]101         CALL eos_fzp(ts(:,:,jk,jp_sal,Kmm), ztfrz3d(:,:,jk), gdept(:,:,jk,Kmm))
[11395]102      END DO
[12068]103      CALL isf_tbl(Kmm, ztfrz3d, ztfrz, 'T', misfkt_par, rhisf_tbl_par, misfkb_par, rfrac_tbl_par )
[11395]104      !
105      pqfwf(:,:) = - sf_isfpar_fwf(1)%fnow(:,:,1)      ! fresh water flux from the isf (fwfisf <0 mean melting)
106      pqoce(:,:) =   pqfwf(:,:) * rLfusisf             ! ocean/ice shelf flux assume to be equal to latent heat flux
107      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux
[11931]108      !
[11876]109      CALL iom_put('isftfrz_par', ztfrz )
[11395]110      !
111   END SUBROUTINE isfpar_mlt_spe
112
[12068]113   SUBROUTINE isfpar_mlt_bg03(kt, Kmm, pqhc, pqoce, pqfwf)
[11395]114      !!---------------------------------------------------------------------
[11403]115      !!                  ***  ROUTINE isfpar_mlt_bg03  ***
[11395]116      !!
[11403]117      !! ** Purpose : compute an estimate of ice shelf melting and
118      !!              latent, ocean-ice and heat content heat fluxes
119      !!              in case cavities are closed based on the far fields T and S properties.
[11395]120      !!
[11403]121      !! ** Method  : The ice shelf melt is computed as proportional to the differences between the
122      !!              mean temperature and mean freezing point in front of the ice shelf averaged
123      !!              over the ice shelf min ice shelf draft and max ice shelf draft and the freezing point
[11395]124      !!
125      !! ** Reference : Beckmann and Goosse (2003), "A parameterization of ice shelf-ocean
[11403]126      !!                interaction for climate models", Ocean Modelling 5(2003) 157-170.
[11395]127      !!----------------------------------------------------------------------
128      !!-------------------------- OUT -------------------------------------
[11494]129      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqfwf, pqoce  ! fresh water and ice-ocean heat fluxes
[11395]130      !!-------------------------- IN  -------------------------------------
131      INTEGER,  INTENT(in) :: kt
[12068]132      INTEGER,  INTENT(in) :: Kmm    !  ocean time level index
[11395]133      !!--------------------------------------------------------------------
134      INTEGER :: jk
135      REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztfrz3d        ! freezing point
136      REAL(wp), DIMENSION(jpi,jpj)     :: ztfrz          ! freezing point
137      REAL(wp), DIMENSION(jpi,jpj)     :: ztavg          ! temperature avg
138      !!----------------------------------------------------------------------
139      !
140      ! 0. ------------Mean freezing point
141      DO jk = 1,jpk
[12068]142         CALL eos_fzp(ts(:,:,jk,jp_sal,Kmm), ztfrz3d(:,:,jk), gdept(:,:,jk,Kmm))
[11395]143      END DO
[12068]144      CALL isf_tbl(Kmm, ztfrz3d, ztfrz, 'T', misfkt_par, rhisf_tbl_par, misfkb_par, rfrac_tbl_par )
[11395]145      !
146      ! 1. ------------Mean temperature
[12068]147      CALL isf_tbl(Kmm, ts(:,:,jk,jp_tem,Kmm), ztavg, 'T', misfkt_par, rhisf_tbl_par, misfkb_par, rfrac_tbl_par )
[11395]148      !
149      ! 2. ------------Net heat flux and fresh water flux due to the ice shelf
[11403]150      pqoce(:,:) =   rau0 * rcp * rn_gammat0 * risfLeff(:,:) * e1t(:,:) * ( ztavg(:,:) - ztfrz(:,:) ) * r1_e1e2t(:,:)
[11541]151      pqfwf(:,:) = - pqoce(:,:) / rLfusisf             ! derived from the latent heat flux
[11395]152      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux
153      !
[11403]154      ! 3. ------------BG03 output
[11395]155      ! output ttbl
[11521]156      CALL iom_put('ttbl_par', ztavg(:,:) * mskisf_par(:,:) )
[11395]157      !
158      ! output thermal driving
[11521]159      CALL iom_put('isfthermald_par',( ztfrz(:,:) - ztavg(:,:) ) * mskisf_par(:,:))
[11931]160      !
161      ! output freezing point used to define the thermal driving and heat content fluxes
[11876]162      CALL iom_put('isftfrz_par', ztfrz )
[11395]163      !
164   END SUBROUTINE isfpar_mlt_bg03
165
[12068]166   SUBROUTINE isfpar_mlt_oasis(kt, Kmm, pqhc , pqoce, pqfwf )
[11403]167      !!----------------------------------------------------------------------
[11541]168      !!                  ***  ROUTINE isfpar_mlt_oasis  ***
[11403]169      !!
170      !! ** Purpose    : scale the fwf read from input file by the total amount received by the sbccpl interface
171      !!
[11494]172      !! ** Purpose    : - read ice shelf melt from forcing file and scale it by the input file total amount => pattern
173      !!                 - compute total amount of fwf given by sbccpl (fwfisf_oasis)
[11403]174      !!                 - scale fwf and compute heat fluxes
175      !!
176      !!---------------------------------------------------------------------
177      !!-------------------------- OUT -------------------------------------
178      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pqhc, pqoce, pqfwf  ! heat content, latent heat and fwf fluxes
179      !!-------------------------- IN  -------------------------------------
180      INTEGER                     , INTENT(in   ) :: kt                  ! current time step
[12068]181      INTEGER                     , INTENT(in   ) :: Kmm                 !  ocean time level index
[11403]182      !!--------------------------------------------------------------------
183      INTEGER                           :: jk                            ! loop index
[11541]184      REAL(wp)                          :: zfwf_fld, zfwf_oasis          ! total fwf in the forcing fields (pattern) and from the cpl interface (amount)
[11403]185      REAL(wp), DIMENSION(jpi,jpj)      :: ztfrz                         ! tbl freezing temperature
186      REAL(wp), DIMENSION(jpi,jpj)      :: zfwf                          ! 2d fwf map after scaling
187      REAL(wp), DIMENSION(jpi,jpj,jpk)  :: ztfrz3d
188      !!--------------------------------------------------------------------
189      !
190      ! 0. ------------Read specified runoff
[11852]191      CALL fld_read ( kt, 1, sf_isfpar_fwf   )
[11403]192      !
[11541]193      ! 1. ------------Mean freezing point (needed for heat content flux)
[11403]194      DO jk = 1,jpk
[12068]195         CALL eos_fzp(ts(:,:,jk,jp_sal,Kmm), ztfrz3d(:,:,jk), gdept(:,:,jk,Kmm))
[11403]196      END DO
[12068]197      CALL isf_tbl(Kmm, ztfrz3d, ztfrz, 'T', misfkt_par, rhisf_tbl_par, misfkb_par, rfrac_tbl_par )
[11403]198      !
[11541]199      ! 2. ------------Scale isf melt pattern with total amount from oasis
[11403]200      ! ice shelf 2d map
201      zfwf(:,:) = - sf_isfpar_fwf(1)%fnow(:,:,1)
202      !
203      ! compute glob sum from input file
[11425]204      ! (PM) should we consider delay sum as in fwb ? (it will offset by 1 time step if I understood well)
205      zfwf_fld = glob_sum('isfcav_mlt', e1e2t(:,:) * zfwf(:,:))
[11403]206      !
207      ! compute glob sum from atm->oce ice shelf fwf
[11425]208      ! (PM) should we consider delay sum as in fwb ?
209      zfwf_oasis = glob_sum('isfcav_mlt', e1e2t(:,:) * fwfisf_oasis(:,:))
[11403]210      !
211      ! scale fwf
[11423]212      zfwf(:,:) = zfwf(:,:) * zfwf_oasis / zfwf_fld
[11403]213      !
[11931]214      ! 3. -----------Define fwf and qoce
[11403]215      ! ocean heat flux is assume to be equal to the latent heat
216      pqfwf(:,:) =   zfwf(:,:)                         ! fwf                ( >0 out )
217      pqoce(:,:) = - pqfwf(:,:) * rLfusisf             ! ocean heat flux    ( >0 out ) (assumed to be the latent heat flux)
218      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux  ( >0 out )
219      !
[11876]220      CALL iom_put('isftfrz_par', ztfrz )
221      !
[11395]222   END SUBROUTINE isfpar_mlt_oasis
223
224END MODULE isfparmlt
Note: See TracBrowser for help on using the repository browser.