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

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

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

ENHANCE-02_ISF_nemo : add comments, renaming file (AGRIF), add isfload module (ticket #2142)

  • Property svn:keywords set to Id
File size: 10.6 KB
RevLine 
[11403]1MODULE isfstp
[4666]2   !!======================================================================
[11403]3   !!                       ***  MODULE  isfstp  ***
4   !! Surface module :  compute iceshelf load, melt and heat flux
[4666]5   !!======================================================================
[9019]6   !! History :  3.2  !  2011-02  (C.Harris  ) Original code isf cav
7   !!            X.X  !  2006-02  (C. Wang   ) Original code bg03
8   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization
[11395]9   !!            4.1  !  2019-09  (P. Mathiot) Split param/explicit ice shelf and re-organisation
[4666]10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
[11403]13   !!   isfstp       : compute iceshelf melt and heat flux
[4666]14   !!----------------------------------------------------------------------
[9019]15   USE oce            ! ocean dynamics and tracers
16   USE dom_oce        ! ocean space and time domain
17   USE phycst         ! physical constants
18   USE eosbn2         ! equation of state
19   USE sbc_oce        ! surface boundary condition: ocean fields
20   USE zdfdrg         ! vertical physics: top/bottom drag coef.
[5836]21   !
[9019]22   USE in_out_manager ! I/O manager
23   USE iom            ! I/O library
24   USE fldread        ! read input field at current time step
25   USE lbclnk         !
26   USE lib_fortran    ! glob_sum
[11395]27   !
28   USE isfrst         ! iceshelf restart
29   USE isftbl         ! ice shelf boundary layer
30   USE isfpar         ! ice shelf parametrisation
31   USE isfcav         ! ice shelf cavity
[11403]32   USE isfload        ! ice shelf load
[11395]33   USE isf            ! isf variables
[4666]34
35   IMPLICIT NONE
[11395]36
[4666]37   PRIVATE
38
[11403]39   PUBLIC   isf_stp, isf_stp_init  ! routine called in sbcmod and divhor
[4666]40
41   !!----------------------------------------------------------------------
[9598]42   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[5215]43   !! $Id$
[10068]44   !! Software governed by the CeCILL license (see ./LICENSE)
[4666]45   !!----------------------------------------------------------------------
46CONTAINS
47 
[11403]48  SUBROUTINE isf_stp( kt )
[5836]49      !!---------------------------------------------------------------------
[11403]50      !!                  ***  ROUTINE isf_stp  ***
[6140]51      !!
[11403]52      !! ** Purpose : compute total heat flux and total fwf due to ice shelf melt
[6140]53      !!
[11403]54      !! ** Method  : For each case (parametrisation or explicity cavity) :
55      !!              - define the before fields
56      !!              - compute top boundary layer properties
57      !!                (in case of parametrisation, this is the
58      !!                 depth range model array used to compute mean far fields properties)
59      !!              - compute fluxes
60      !!              - write restart variables
[11395]61      !!
[6140]62      !!----------------------------------------------------------------------
[9019]63      INTEGER, INTENT(in) ::   kt   ! ocean time step
[4666]64      !!---------------------------------------------------------------------
65      !
[11395]66      IF ( ln_isfcav_mlt ) THEN
[9019]67         !
[11395]68         ! before time step
69         IF ( kt /= nit000 ) THEN
70            risf_cav_tsc_b (:,:,:) = risf_cav_tsc (:,:,:)
71            fwfisf_cav_b(:,:)      = fwfisf_cav(:,:)
72         END IF
[7788]73         !
[11395]74         ! compute tbl lvl/h
75         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav)
76         !
77         ! compute ice shelf melt
78         CALL isf_cav( kt, risf_cav_tsc, fwfisf_cav)
79         !
80         ! write restart variables (qoceisf, qhcisf, fwfisf for now and before)
81         IF (lrst_oce) CALL isfrst_write(kt, 'cav', risf_cav_tsc, fwfisf_cav)
82         !
83      END IF
[9019]84      !
[11395]85      IF ( ln_isfpar_mlt ) THEN
[4666]86         !
[11395]87         ! before time step
88         IF ( kt /= nit000 ) THEN
89            risf_par_tsc_b (:,:) = risf_par_tsc (:,:)
90            fwfisf_par_b(:,:)    = fwfisf_par(:,:)
91         END IF
[4666]92         !
[11395]93         ! compute misfkb, rhisf_tbl, rfrac (deepest level, thickness, fraction of deepest cell affected by tbl)
94         CALL isf_tbl_lvl(ht_n, e3t_n, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par)
95         !
96         ! compute ice shelf melt
97         CALL isf_par( kt, risf_par_tsc, fwfisf_par)
98         !
99         ! write restart variables (qoceisf, qhcisf, fwfisf for now and before)
100         IF (lrst_oce) CALL isfrst_write(kt, 'par', risf_par_tsc, fwfisf_par)
101         !
102      END IF
103      !
[11403]104   END SUBROUTINE isf_stp
[4666]105
[11403]106   SUBROUTINE isf_stp_init
[6140]107      !!---------------------------------------------------------------------
[11403]108      !!                  ***  ROUTINE isfstp_init  ***
[6140]109      !!
[11403]110      !! ** Purpose :   Initialisation of the ice shelf public variables
[6140]111      !!
[11403]112      !! ** Method  :   Read the namsbc namelist and set derived parameters
113      !!                Call init routines for all other SBC modules that have one
[11395]114      !!
[11403]115      !! ** Action  : - read namsbc parameters
116      !!              - allocate memory
117      !!              - call cav/param init routine
[5836]118      !!----------------------------------------------------------------------
[6140]119      INTEGER               :: inum, ierror
120      INTEGER               :: ios                  ! Local integer output status for namelist read
[11395]121      INTEGER               :: ikt, ikb
122      INTEGER               :: ji, jj
[5836]123      !!----------------------------------------------------------------------
[11395]124      NAMELIST/namisf/ ln_isfcav_mlt, cn_isfcav_mlt, cn_gammablk, rn_gammat0, rn_gammas0, rn_htbl, sn_isfcav_fwf,  &
125         &             ln_isfpar_mlt, cn_isfpar_mlt, sn_isfpar_fwf, sn_isfpar_zmin, sn_isfpar_zmax, sn_isfpar_Leff
[6140]126      !!----------------------------------------------------------------------
[11403]127      !
128      ! Allocate public array
129      CALL isf_alloc()
130      !
131      riceload(:,:)       = 0.0_wp
132      fwfisf_cpl(:,:)     = 0.0_wp
133      fwfisf_par(:,:)     = 0.0_wp    ; fwfisf_par_b(:,:)     = 0.0_wp
134      fwfisf_cav(:,:)     = 0.0_wp    ; fwfisf_cav_b(:,:)     = 0.0_wp
135      risf_cav_tsc(:,:,:) = 0.0_wp    ; risf_cav_tsc_b(:,:,:) = 0.0_wp
136      risf_par_tsc(:,:,:) = 0.0_wp    ; risf_par_tsc_b(:,:,:) = 0.0_wp
137      !
138      ! terminate routine now if no ice shelf melt formulation specify
139      IF ( .NOT. ln_isf ) RETURN
140      !
[6140]141      REWIND( numnam_ref )              ! Namelist namsbc_rnf in reference namelist : Runoffs
[11395]142      READ  ( numnam_ref, namisf, IOSTAT = ios, ERR = 901)
143901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namisf in reference namelist', lwp )
[11403]144      !
[6140]145      REWIND( numnam_cfg )              ! Namelist namsbc_rnf in configuration namelist : Runoffs
[11395]146      READ  ( numnam_cfg, namisf, IOSTAT = ios, ERR = 902 )
147902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namisf in configuration namelist', lwp )
148      IF(lwm) WRITE ( numond, namisf )
149      !
[9168]150      IF(lwp) WRITE(numout,*)
[11395]151      IF(lwp) WRITE(numout,*) 'isf_init : ice shelf initialisation'
[9168]152      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
[11395]153      IF(lwp) WRITE(numout,*) '   Namelist namisf :'
[11403]154      !
[11395]155      IF(lwp) WRITE(numout,*) '      melt inside the cavity                  ln_isfcav_mlt   = ', ln_isfcav_mlt
156      IF ( ln_isfcav ) THEN
157         IF(lwp) WRITE(numout,*) '         melt formulation                        cn_isfcav_mlt   = ', cn_isfcav_mlt
158         IF(lwp) WRITE(numout,*) '         thickness of the top boundary layer     rn_htbl     = ', rn_htbl
159         IF(lwp) WRITE(numout,*) '         gamma formulation                       cn_gammablk = ', cn_gammablk 
160         IF ( TRIM(cn_gammablk) .NE. 'spe' ) THEN
161            IF(lwp) WRITE(numout,*) '            gammat coefficient                      rn_gammat0  = ', rn_gammat0 
162            IF(lwp) WRITE(numout,*) '            gammas coefficient                      rn_gammas0  = ', rn_gammas0 
163            IF(lwp) WRITE(numout,*) '            top drag coef. used (from namdrg_top)   rn_Cd0      = ', r_Cdmin_top 
[6140]164         END IF
[11395]165      END IF
[11403]166      !
[11395]167      IF(lwp) WRITE(numout,*) ''
[11403]168      !
[11395]169      IF(lwp) WRITE(numout,*) '      ice shelf melt parametrisation          ln_isfpar_mlt    = ', ln_isfpar_mlt
170      IF ( ln_isfpar_mlt ) THEN
171         IF(lwp) WRITE(numout,*) '         isf parametrisation formulation         cn_isfpar_mlt   = ', cn_isfpar_mlt
172      END IF
173      IF(lwp) WRITE(numout,*) ''
[5302]174      !
[11403]175      ! sanity check
176      ! melt in the cavity without cavity
177      IF ( ln_isfcav_mlt .AND. (.NOT. ln_isfcav) ) &
178         &   CALL ctl_stop('ice shelf melt in the cavity activated (ln_isfcav_mlt) but no cavity detected in domcfg (ln_isfcav), STOP' )
[6140]179      !
[11403]180      IF ( ln_cpl ) THEN
181         !
182         CALL ctl_stop( ' ln_ctl and ice shelf not tested' )
183         !
184         ! NEMO coupled to ATMO model with isf cavity need oasis method for melt computation
185         IF ( ln_isfcav_mlt .AND. TRIM(cn_isfcav_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis is the only option availble with ln_cpl' )
186         IF ( ln_isfpar_mlt .AND. TRIM(cn_isfpar_mlt) /= 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis is the only option availble with ln_cpl' )
187         !
188         ! oasis melt computation not tested (coded but not tested)
189         IF ( ln_isfcav_mlt .OR. ln_isfpar_mlt ) THEN
190            IF ( TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfcav_mlt = oasis not tested' )
191            IF ( TRIM(cn_isfpar_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis not tested' )
192         END IF
193         !
194         ! oasis melt computation with cavity open and cavity parametrised (not coded)
195         IF ( ln_isfcav_mlt .AND. ln_isfpar_mlt ) THEN
196            IF ( TRIM(cn_isfpar_mlt) == 'oasis' .AND. TRIM(cn_isfcav_mlt) == 'oasis' ) CALL ctl_stop( 'cn_isfpar_mlt = oasis and cn_isfcav_mlt = oasis not coded' )
197         END IF
198      END IF
[9019]199      !
[11403]200      ! initialisation ice shelf load
201      IF ( ln_isfcav ) THEN
202         !
203         ! compute ice shelf mask
204         mskisf_cav(:,:) = (1._wp - tmask(:,:,1)) * ssmask(:,:)
205         !
206         ! compute ice shelf load
207         CALL isf_load( risfload )
208         !
209      END IF
[5836]210      !
[11395]211      ! initialisation useful variable
212      r1_Lfusisf =  1._wp / rLfusisf
[4666]213      !
[11403]214      ! initialisation melt in the cavity
[11395]215      IF ( ln_isfcav_mlt ) THEN
216         !
217         ! initialisation  of cav variable
218         CALL isf_cav_init()
219         !
220         ! read cav variable from restart
221         IF ( ln_rstart ) CALL isfrst_read('cav', risf_cav_tsc, fwfisf_cav, risf_cav_tsc_b, fwfisf_cav_b)
222         !
223      END IF
224      !
[11403]225      ! initialisation parametrised melt
[11395]226      IF ( ln_isfpar_mlt ) THEN
227         !
228         ! initialisation  of par variable
229         CALL isf_par_init()
230         !
231         ! read par variable from restart
232         IF ( ln_rstart ) CALL isfrst_read('par', risf_par_tsc, fwfisf_par, risf_par_tsc_b, fwfisf_par_b)
233         !
234      END IF
235      !
[11403]236  END SUBROUTINE isf_stp_init
[6140]237   !!======================================================================
[11403]238END MODULE isfstp
Note: See TracBrowser for help on using the repository browser.