source: CONFIG/UNIFORM/v6/NEMO_v6.5/SOURCES/isfparmlt.F90 @ 6786

Last change on this file since 6786 was 6601, checked in by cetlod, 9 months ago

NEMOv6.5 : Update config to switch to NEMOv4.2.1 and PISCES gas

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