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.F90 in NEMO/branches/UKMO/NEMO_4.0.2_ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.2_ENHANCE-02_ISF_nemo/src/OCE/ISF/isfpar.F90 @ 12709

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

NEMO_4.0.2_ENHANCE-02_ISF_nemo: remove svn keywords

File size: 8.0 KB
Line 
1MODULE isfpar
2   !!======================================================================
3   !!                       ***  MODULE  isfpar  ***
4   !! ice shelf module :  update ocean boundary condition under ice
5   !!                   shelf
6   !!======================================================================
7   !! History :  3.2  !  2011-02  (C.Harris  ) Original code isf cav
8   !!            X.X  !  2006-02  (C. Wang   ) Original code bg03
9   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization
10   !!            4.1  !  2019-09  (P. Mathiot) Restructuration
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   isfpar       : compute ice shelf melt using a prametrisation of ice shelf cavities
15   !!----------------------------------------------------------------------
16   USE isf_oce        ! ice shelf
17   !
18   USE isfrst   , ONLY: isfrst_write, isfrst_read ! ice shelf restart read/write subroutine
19   USE isftbl   , ONLY: isf_tbl_ktop, isf_tbl_lvl ! ice shelf top boundary layer properties subroutine
20   USE isfparmlt, ONLY: isfpar_mlt                ! ice shelf melt formulation subroutine
21   USE isfdiags , ONLY: isf_diags_flx             ! ice shelf diags subroutine
22   USE isfutils , ONLY: debug, read_2dcstdta      ! ice shelf debug subroutine
23   !
24   USE dom_oce  , ONLY: bathy          ! ocean space and time domain
25   USE par_oce  , ONLY: jpi,jpj        ! ocean space and time domain
26   USE phycst   , ONLY: r1_rau0_rcp    ! physical constants
27   !
28   USE in_out_manager ! I/O manager
29   USE iom            ! I/O library
30   USE fldread        ! read input field at current time step
31   USE lbclnk         ! lbc_lnk
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   isf_par, isf_par_init
37
38   !!----------------------------------------------------------------------
39   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
40   !! $Id$
41   !! Software governed by the CeCILL license (see ./LICENSE)
42   !!----------------------------------------------------------------------
43CONTAINS
44 
45   SUBROUTINE isf_par( kt, ptsc, pqfwf )
46      !!---------------------------------------------------------------------
47      !!                     ***  ROUTINE isf_par ***     
48      !!
49      !! ** Purpose : compute the heat and fresh water due to ice shelf melting/freezing using a parametrisation
50      !!
51      !! ** Comment : in isf_par and all its call tree,
52      !!              'tbl' means parametrisation layer (ie how the far field temperature/salinity is computed)
53      !!              instead of in a proper top boundary layer as at the ice shelf ocean interface
54      !!              as the action to compute the properties of the tbl or the parametrisation layer are the same,
55      !!              (ie average T/S over a specific depth (can be across multiple levels))
56      !!              the name tbl was kept.
57      !!
58      !!---------------------------------------------------------------------
59      !!-------------------------- OUT --------------------------------------
60      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(inout) :: pqfwf
61      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(inout) :: ptsc
62      !!-------------------------- IN  --------------------------------------
63      INTEGER, INTENT(in) ::   kt                                           ! ocean time step
64      !!---------------------------------------------------------------------
65      REAL(wp), DIMENSION(jpi,jpj) :: zqoce, zqhc, zqlat, zqh
66      !!---------------------------------------------------------------------
67      !
68      ! compute heat content, latent heat and melt fluxes (2d)
69      CALL isfpar_mlt( kt, zqhc, zqoce, pqfwf  )
70      !
71      ! compute heat and water flux ( > 0 out )
72      pqfwf(:,:) = pqfwf(:,:) * mskisf_par(:,:)
73      zqoce(:,:) = zqoce(:,:) * mskisf_par(:,:)
74      zqhc (:,:) = zqhc(:,:)  * mskisf_par(:,:)
75      !
76      ! compute heat content flux ( > 0 out )
77      zqlat(:,:) = pqfwf(:,:) * rLfusisf    ! 2d latent heat flux (W/m2)
78      !
79      ! total heat flux ( > 0 out )
80      zqh(:,:) = ( zqhc (:,:) + zqoce(:,:) )
81      !
82      ! lbclnk on melt and heat fluxes
83      CALL lbc_lnk_multi( 'isfmlt', zqh, 'T', 1., pqfwf, 'T', 1.)
84      !
85      ! output fluxes
86      CALL isf_diags_flx( misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, 'par', pqfwf, zqoce, zqlat, zqhc)
87      !
88      ! set temperature content
89      ptsc(:,:,jp_tem) = zqh(:,:) * r1_rau0_rcp
90      !
91      ! write restart variables (qoceisf, qhcisf, fwfisf for now and before)
92      IF (lrst_oce) CALL isfrst_write(kt, 'par', ptsc, pqfwf)
93      !
94      IF ( ln_isfdebug ) THEN
95         CALL debug('isf_par: ptsc T',ptsc(:,:,1))
96         CALL debug('isf_par: ptsc S',ptsc(:,:,2))
97         CALL debug('isf_par: pqfwf fwf',pqfwf(:,:))
98      END IF
99      !
100   END SUBROUTINE isf_par
101
102   SUBROUTINE isf_par_init
103      !!---------------------------------------------------------------------
104      !!                  ***  ROUTINE isf_par_init  ***
105      !!
106      !! ** Purpose : initialisation of the variable needed for the parametrisation of ice shelf melt
107      !!
108      !!----------------------------------------------------------------------
109      INTEGER               :: ierr
110      REAL(wp), DIMENSION(jpi,jpj) :: ztblmax, ztblmin
111      !!----------------------------------------------------------------------
112      !
113      ! allocation
114      CALL isf_alloc_par()
115      !
116      ! initialisation
117      misfkt_par(:,:)     = 1         ; misfkb_par(:,:)       = 1         
118      rhisf_tbl_par(:,:)  = 1e-20     ; rfrac_tbl_par(:,:)    = 0.0_wp
119      !
120      ! define isf tbl tickness, top and bottom indice
121      CALL read_2dcstdta(TRIM(sn_isfpar_zmax%clname), TRIM(sn_isfpar_zmax%clvar), ztblmax)
122      CALL read_2dcstdta(TRIM(sn_isfpar_zmin%clname), TRIM(sn_isfpar_zmin%clvar), ztblmin)
123      !
124      ! mask ice shelf parametrisation location
125      ztblmax(:,:) = ztblmax(:,:) * ssmask(:,:)
126      ztblmin(:,:) = ztblmin(:,:) * ssmask(:,:)
127      !
128      ! if param used under an ice shelf overwrite ztblmin by the ice shelf draft
129      WHERE ( risfdep > 0._wp .AND. ztblmin > 0._wp )
130         ztblmin(:,:) = risfdep(:,:)
131      END WHERE
132      !
133      ! ensure ztblmax <= bathy
134      WHERE ( ztblmax(:,:) > bathy(:,:) )
135         ztblmax(:,:) = bathy(:,:)
136      END WHERE
137      !
138      ! compute ktop and update ztblmin to gdepw_0(misfkt_par)
139      CALL isf_tbl_ktop(ztblmin, misfkt_par) !   out: misfkt_par
140      !                                      ! inout: ztblmin
141      !
142      ! initial tbl thickness
143      rhisf0_tbl_par(:,:) = ztblmax(:,:) - ztblmin(:,:)
144      !
145      ! define iceshelf parametrisation mask
146      mskisf_par = 0
147      WHERE ( rhisf0_tbl_par(:,:) > 0._wp )
148         mskisf_par(:,:) = 1._wp
149      END WHERE
150      !
151      ! read par variable from restart
152      IF ( ln_rstart ) CALL isfrst_read('par', risf_par_tsc, fwfisf_par, risf_par_tsc_b, fwfisf_par_b)
153      !
154      SELECT CASE ( TRIM(cn_isfpar_mlt) )
155         !
156      CASE ( 'spe' )
157         !
158         ALLOCATE( sf_isfpar_fwf(1), STAT=ierr )
159         ALLOCATE( sf_isfpar_fwf(1)%fnow(jpi,jpj,1), sf_isfpar_fwf(1)%fdta(jpi,jpj,1,2) )
160         CALL fld_fill( sf_isfpar_fwf, (/ sn_isfpar_fwf /), cn_isfdir, 'isf_par_init', 'read fresh water flux isf data', 'namisf' )
161         !
162         IF(lwp) WRITE(numout,*)
163         IF(lwp) WRITE(numout,*) '      ==>>>   ice melt read from forcing field (cn_isfmlt_par = spe)'
164         !
165      CASE ( 'bg03' )
166         !
167         IF(lwp) WRITE(numout,*)
168         IF(lwp) WRITE(numout,*) '      ==>>>   bg03 parametrisation (cn_isfmlt_par = bg03)'
169         !
170         ! read effective length
171         CALL read_2dcstdta(TRIM(sn_isfpar_Leff%clname), TRIM(sn_isfpar_Leff%clvar), risfLeff)
172         risfLeff = risfLeff*1000.0_wp           !: convertion in m
173         !
174      CASE ( 'oasis' )
175         !
176         IF(lwp) WRITE(numout,*)
177         IF(lwp) WRITE(numout,*) '      ==>>>    isf melt provided by OASIS (cn_isfmlt_par = oasis)'
178         !
179      CASE DEFAULT
180         CALL ctl_stop( 'sbc_isf_init: wrong value of nn_isf' )
181      END SELECT
182      !
183   END SUBROUTINE isf_par_init
184
185END MODULE isfpar
Note: See TracBrowser for help on using the repository browser.