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/trunk/src/OCE/ISF – NEMO

source: NEMO/trunk/src/OCE/ISF/isfparmlt.F90 @ 15004

Last change on this file since 15004 was 15004, checked in by mathiot, 3 years ago

ticket #2960: commit fix to the trunk (WARNING: output convention of isf fluxes changed from oce->isf to isf->oce), no impact on the input file needed for some options

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