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/ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfparmlt.F90 @ 11987

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

ENHANCE-02_ISF_nemo: changes needed after Dave's review

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