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 @ 15529

Last change on this file since 15529 was 15062, checked in by jchanut, 3 years ago

Suppress time varying scale factors and depths declarations with key_qco and key_linssh. Remove spaces that preclude from correct replacement of some scale factor arrays during preprocessing stage (at least with Apple clang version 11.0.3, this is problem).

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