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

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isf.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: 9.0 KB
Line 
1MODULE isf
2   !!======================================================================
3   !!                       ***  MODULE  sbcisf  ***
4   !! Surface module :  compute iceshelf melt and heat flux
5   !!======================================================================
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
9   !!            4.1  !  2019-09  (P. Mathiot) Split param/explicit ice shelf and re-organisation
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   isfmlt       : compute iceshelf melt and heat flux
14   !!----------------------------------------------------------------------
15
16   USE in_out_manager ! I/O manager
17   USE lib_mpp        ! MPP library
18   USE fldread        ! read input fields
19
20   IMPLICIT NONE
21
22   PRIVATE
23
24   PUBLIC   isf_alloc, isf_alloc_par, isf_alloc_cav
25
26   ! public in order to be able to output then
27
28   LOGICAL, PUBLIC :: ln_isfpar_mlt                  !: logical for the computation of melt inside the cavity
29   LOGICAL, PUBLIC :: ln_isfcav_mlt                  !: logical for the use of ice shelf parametrisation
30   REAL(wp), PUBLIC ::   rn_hisf_tbl                 !: thickness of top boundary layer [m]
31   REAL(wp), PUBLIC ::   rn_gammat0                  !: temperature exchange coeficient    []
32   REAL(wp), PUBLIC ::   rn_gammas0                  !: salinity    exchange coeficient    []
33   REAL(wp), PUBLIC ::   rn_htbl                     !: Losch top boundary layer thickness [m]
34   CHARACTER(LEN=256), PUBLIC :: cn_gammablk         !: gamma formulation
35   CHARACTER(LEN=256), PUBLIC :: cn_isfcav_mlt, cn_isfpar_mlt !: melt formulation (cavity/param)
36   TYPE(FLD_N), PUBLIC                                  :: sn_isfcav_fwf   !: information about the isf melting file to be read
37   TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_fwf   !: information about the isf melting file to be read
38   TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_zmax  !: information about the grounding line depth file to be read
39   TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_zmin  !: information about the calving   line depth file to be read
40   TYPE(FLD_N), PUBLIC                                  :: sn_isfpar_Leff  !: information about the effective length     file to be read
41
42   LOGICAL, PUBLIC :: l_isfcpl
43   !
44   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   misfkt_par, misfkt_cav   !: Level of ice shelf base
45   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   misfkb_par, misfkb_cav   !: Level of ice shelf base
46   !
47   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   mskisf_par, mskisf_cav   !: Level of ice shelf base
48   !
49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf_tbl, rhisf_tbl_0   !: thickness of tbl  [m]
50   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf_tbl_cav, rhisf_tbl_par !: thickness of tbl  [m]
51   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rfrac_tbl_cav, rfrac_tbl_par !: fraction of the deepest cell affect by isf tbl  []
52   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rhisf0_tbl_par
53   !
54   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fwfisf_par, fwfisf_par_b !: net fwf from the ice shelf        [kg/m2/s]
55   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fwfisf_cav, fwfisf_cav_b !: net fwf from the ice shelf        [kg/m2/s]
56   !
57   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   risfdep                  !: Iceshelf draft                              (ISF)
58   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   bathy                    !: Bathymetry (needed for isf tbl definition)  (ISF)
59   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   risfLeff
60   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   risf_cav_tsc_b, risf_cav_tsc     !: before and now T & S isf contents [K.m/s & PSU.m/s] 
61   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   risf_par_tsc_b, risf_par_tsc     !: before and now T & S isf contents [K.m/s & PSU.m/s] 
62
63   REAL(wp), PARAMETER, PUBLIC :: rLfusisf = 0.334e6_wp    !: latent heat of fusion of ice shelf     [J/kg]
64   REAL(wp), PARAMETER, PUBLIC :: rcpisf = 2000.0_wp       !: specific heat of ice shelf             [J/kg/K]
65   REAL(wp), PARAMETER, PUBLIC :: rkappa = 1.54e-6_wp      !: heat diffusivity through the ice-shelf [m2/s]
66   REAL(wp), PARAMETER, PUBLIC :: rhoisf = 920.0_wp        !: volumic mass of ice shelf              [kg/m3]
67   REAL(wp), PARAMETER, PUBLIC :: rtsurf = -20.0           !: surface temperature                    [C]
68   REAL(wp), PARAMETER, PUBLIC :: risf_eps = 1.e-20_wp       
69
70   REAL(wp), PUBLIC            :: risf_lamb1, risf_lamb2, risf_lamb3  ! freezing point linearization coeficient
71
72   REAL(wp), PUBLIC            :: r1_Lfusisf               !: 1/rLfusisf
73
74   TYPE(FLD)  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: sf_isfcav_fwf
75   TYPE(FLD)  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) :: sf_isfpar_fwf
76
77!: Variable used in fldread to read the forcing file (nn_isf == 4 .OR. nn_isf == 3)
78   CHARACTER(len=100), PUBLIC           :: cn_dirisf  = './' !: Root directory for location of ssr files
79   TYPE(FLD_N)       , PUBLIC           :: sn_fwfisf         !: information about the isf melting file to be read
80   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_fwfisf
81   TYPE(FLD_N)       , PUBLIC           :: sn_rnfisf         !: information about the isf melting param.   file to be read
82   TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_rnfisf           
83   
84   !!----------------------------------------------------------------------
85   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
86   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
87   !! Software governed by the CeCILL license (see ./LICENSE)
88   !!----------------------------------------------------------------------
89CONTAINS
90
91   SUBROUTINE isf_alloc_par()
92      !!---------------------------------------------------------------------
93      !!                  ***  ROUTINE isfmlt_alloc  ***
94      !!
95      !! ** Purpose :
96      !!
97      !! ** Method  :
98      !!
99      !!----------------------------------------------------------------------
100      INTEGER :: ierr, ialloc
101      !!----------------------------------------------------------------------
102      ierr = 0       ! set to zero if no array to be allocated
103      !
104      ALLOCATE(risfLeff(jpi,jpj), STAT=ialloc)
105      ierr = ierr + ialloc
106      !
107      CALL mpp_sum ( 'isf', ierr )
108      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' )
109   END SUBROUTINE isf_alloc_par
110
111   SUBROUTINE isf_alloc_cav()
112      !!---------------------------------------------------------------------
113      !!                  ***  ROUTINE isfmlt_alloc  ***
114      !!
115      !! ** Purpose :
116      !!
117      !! ** Method  :
118      !!
119      !!----------------------------------------------------------------------
120      INTEGER :: ierr, ialloc
121      !!----------------------------------------------------------------------
122      ierr = 0       ! set to zero if no array to be allocated
123      !
124      CALL mpp_sum ( 'isf', ierr )
125      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' )
126   END SUBROUTINE isf_alloc_cav
127
128   SUBROUTINE isf_alloc()
129      !!---------------------------------------------------------------------
130      !!                  ***  ROUTINE isfmlt_alloc  ***
131      !!
132      !! ** Purpose :
133      !!
134      !! ** Method  :
135      !!
136      !!----------------------------------------------------------------------
137      INTEGER :: ierr, ialloc
138      !!----------------------------------------------------------------------
139      !
140      ierr = 0       ! set to zero if no array to be allocated
141      !
142      ALLOCATE(misfkt_par(jpi,jpj), misfkb_par(jpi,jpj),             &
143         &     misfkt_cav(jpi,jpj), misfkb_cav(jpi,jpj), STAT=ialloc )
144      ierr = ierr + ialloc
145      !
146      ALLOCATE(fwfisf_par(jpi,jpj), fwfisf_par_b(jpi,jpj),             &
147         &     fwfisf_cav(jpi,jpj), fwfisf_cav_b(jpi,jpj), STAT=ialloc )
148      ierr = ierr + ialloc
149      !
150      ALLOCATE(risf_cav_tsc(jpi,jpj,jpts), risf_cav_tsc_b(jpi,jpj,jpts),             &
151         &     risf_par_tsc(jpi,jpj,jpts), risf_par_tsc_b(jpi,jpj,jpts), STAT=ialloc )
152      ierr = ierr + ialloc
153      !
154      ALLOCATE( rfrac_tbl_cav(jpi,jpj), rfrac_tbl_par(jpi,jpj), STAT=ialloc)
155      ierr = ierr + ialloc
156      !
157      ALLOCATE( rhisf_tbl_par(jpi,jpj), rhisf_tbl_cav(jpi,jpj), STAT=ialloc)
158      ierr = ierr + ialloc
159      !
160      ALLOCATE( mskisf_cav(jpi,jpj), mskisf_par(jpi,jpj), STAT=ialloc)
161      ierr = ierr + ialloc
162      !
163      ALLOCATE(risfdep(jpi,jpj), bathy(jpi,jpj), STAT=ialloc)
164      ierr = ierr + ialloc
165      !
166      CALL mpp_sum ( 'isf', ierr )
167      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' )
168
169   END SUBROUTINE isf_alloc
170   !
171END MODULE isf
Note: See TracBrowser for help on using the repository browser.