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.
isfpar_mlt.F90 in NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

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

Last change on this file since 11395 was 11395, checked in by mathiot, 5 years ago

ENHANCE-02_ISF_nemo : Initial commit isf simplification (add ISF directory, moved isf routine in and split isf cavity and isf parametrisation, ...) (ticket #2142)

File size: 7.5 KB
Line 
1MODULE isfparmlt
2   !!======================================================================
3   !!                       ***  MODULE  sbcisf  ***
4   !! Surface module :  update surface ocean boundary condition under ice
5   !!                   shelf
6   !!======================================================================
7   !! History :  4.0  ! original code
8   !!----------------------------------------------------------------------
9
10   USE oce            ! ocean dynamics and tracers
11   USE isf
12   USE isftbl
13   USE dom_oce        ! ocean space and time domain
14   USE phycst         ! physical constants
15   USE eosbn2         ! equation of state
16
17   USE in_out_manager ! I/O manager
18   USE iom            ! I/O library
19   USE fldread
20
21   IMPLICIT NONE
22
23   PRIVATE
24
25   PUBLIC  isfpar_mlt 
26   
27   !!----------------------------------------------------------------------
28   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
29   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
30   !! Software governed by the CeCILL license (see ./LICENSE)
31   !!----------------------------------------------------------------------
32CONTAINS
33
34! -------------------------------------------------------------------------------------------------------
35! -------------------------------- PUBLIC SUBROUTINE ----------------------------------------------------
36! -------------------------------------------------------------------------------------------------------
37
38  SUBROUTINE isfpar_mlt( kt, pqfwf, pqoce, pqhc )
39      !!---------------------------------------------------------------------
40      !!                  ***  ROUTINE sbc_isf  ***
41      !!
42      !! ** Purpose : Compute Salt and Heat fluxes related to ice_shelf
43      !!              melting and freezing
44      !!
45      !! ** Method  :  2 parameterizations are available according to XXXXX
46      !!                        2 : Beckmann & Goose parameterization
47      !!                        3 : Specified runoff in deptht (Mathiot & al. 2017)
48      !!----------------------------------------------------------------------
49      !!-------------------------- OUT -------------------------------------
50      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqfwf,pqoce, pqhc  ! fresh water, ice-ocean heat and heat content fluxes
51      !!-------------------------- IN  -------------------------------------
52      INTEGER, INTENT(in) ::   kt   ! ocean time step
53      !!---------------------------------------------------------------------
54      !
55      ! Choose among the available ice shelf parametrisation
56      SELECT CASE ( cn_isfpar_mlt )
57      CASE ( 'spe' )    ! specified runoff in depth (Mathiot et al., 2017 in preparation)
58         CALL isfpar_mlt_spe(kt, pqhc, pqoce, pqfwf)
59      CASE ( 'bg03' )    ! Beckmann and Goosse parametrisation
60         CALL isfpar_mlt_bg03(kt, pqhc, pqoce, pqfwf)
61      CASE ( 'oasis' )
62         !CALL isfpar_mlt_oasis
63      CASE DEFAULT
64         CALL ctl_stop('STOP', 'unknown isf melt formulation : cn_isfpar (should not see this)')
65      END SELECT
66      !
67   END SUBROUTINE isfpar_mlt
68
69! -------------------------------------------------------------------------------------------------------
70! -------------------------------- PRIVATE SUBROUTINE ---------------------------------------------------
71! -------------------------------------------------------------------------------------------------------
72
73   SUBROUTINE isfpar_mlt_spe(kt, pqhc, pqfwf, pqoce)
74      !!---------------------------------------------------------------------
75      !!                  ***  ROUTINE sbc_isf_bg03  ***
76      !!
77      !! ** Purpose : prescribed ice shelf melting in case ice shelf cavities are closed.
78      !!              data read into a forcing files.
79      !!
80      !! ** Reference : Mathiot et al. (2017)
81      !!----------------------------------------------------------------------
82      !!-------------------------- OUT -------------------------------------
83      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqfwf,pqoce  ! fresh water and ice-ocean heat fluxes
84      !!-------------------------- IN  -------------------------------------
85      INTEGER,  INTENT(in) :: kt
86      !!--------------------------------------------------------------------
87      INTEGER :: jk
88      REAL(wp), DIMENSION(jpi,jpj,jpk)  :: ztfrz3d
89      REAL(wp), DIMENSION(jpi,jpj)      :: ztfrz
90      !!--------------------------------------------------------------------
91      !
92      ! specified runoff in depth (Mathiot et al., 2017)
93      CALL fld_read ( kt, nn_fsbc, sf_isfpar_fwf   )
94      !
95      ! compute ptfrz
96      ! 0. ------------Mean freezing point
97      DO jk = 1,jpk
98         CALL eos_fzp(tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk))
99      END DO
100      CALL isf_tbl(ztfrz3d, ztfrz, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par )
101      !
102      pqfwf(:,:) = - sf_isfpar_fwf(1)%fnow(:,:,1)      ! fresh water flux from the isf (fwfisf <0 mean melting)
103      pqoce(:,:) =   pqfwf(:,:) * rLfusisf             ! ocean/ice shelf flux assume to be equal to latent heat flux
104      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux
105      !
106   END SUBROUTINE isfpar_mlt_spe
107
108   SUBROUTINE isfpar_mlt_bg03(kt, pqhc, pqoce, pqfwf)
109      !!---------------------------------------------------------------------
110      !!                  ***  ROUTINE sbc_isf_bg03  ***
111      !!
112      !! ** Purpose : compute an estimate of ice shelf melting in case cavities are closed
113      !!              based on the far fields T and S properties.
114      !!
115      !! ** Method  :   See reference
116      !!
117      !! ** Reference : Beckmann and Goosse (2003), "A parameterization of ice shelf-ocean
118      !!         interaction for climate models", Ocean Modelling 5(2003) 157-170.
119      !!         (hereafter BG)
120      !!----------------------------------------------------------------------
121      !!-------------------------- OUT -------------------------------------
122      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqfwf,pqoce  ! fresh water and ice-ocean heat fluxes
123      !!-------------------------- IN  -------------------------------------
124      INTEGER,  INTENT(in) :: kt
125      !!--------------------------------------------------------------------
126      INTEGER :: jk
127      REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztfrz3d        ! freezing point
128      REAL(wp), DIMENSION(jpi,jpj)     :: ztfrz          ! freezing point
129      REAL(wp), DIMENSION(jpi,jpj)     :: ztavg          ! temperature avg
130      !!----------------------------------------------------------------------
131      !
132      ! 0. ------------Mean freezing point
133      DO jk = 1,jpk
134         CALL eos_fzp(tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk))
135      END DO
136      CALL isf_tbl(ztfrz3d, ztfrz, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par )
137      !
138      ! 1. ------------Mean temperature
139      CALL isf_tbl(tsn(:,:,jk,jp_tem), ztavg, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par )
140      !
141      ! 2. ------------Net heat flux and fresh water flux due to the ice shelf
142      pqoce(:,:) = - rau0 * rcp * rn_gammat0 * risfLeff(:,:) * e1t(:,:) * ( ztfrz(:,:) - ztavg(:,:) ) * r1_e1e2t(:,:)
143      pqfwf(:,:) =   pqoce(:,:) / rLfusisf
144      pqhc (:,:) =   pqfwf(:,:) * ztfrz(:,:) * rcp     ! heat content flux
145      !
146      ! output ttbl
147      CALL iom_put('ttbl_par', ztavg(:,:) )
148      !
149      ! output thermal driving
150      CALL iom_put('isfthermald_par',( ztfrz(:,:) - ztavg(:,:) ))
151      !
152      !
153   END SUBROUTINE isfpar_mlt_bg03
154
155   SUBROUTINE isfpar_mlt_oasis
156   !TODO
157   END SUBROUTINE isfpar_mlt_oasis
158
159END MODULE isfparmlt
Note: See TracBrowser for help on using the repository browser.