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_oce.F90 in NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/ISF – NEMO

source: NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/ISF/isf_oce.F90 @ 13364

Last change on this file since 13364 was 13364, checked in by techene, 4 years ago

hydrostatic pressure gradient is computed with density anomaly when possible

File size: 12.9 KB
RevLine 
[11987]1MODULE isf_oce
[11395]2   !!======================================================================
[13364]3   !!                       ***  MODULE  isf_oce  ***
4   !! Ice shelves :  ice shelves variables defined in memory
[11395]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   !!----------------------------------------------------------------------
[11403]13   !!   isf          : define and allocate ice shelf variables
[11395]14   !!----------------------------------------------------------------------
15
[11931]16   USE par_oce       , ONLY: jpi, jpj, jpk
17   USE in_out_manager, ONLY: wp, jpts ! I/O manager
[11852]18   USE lib_mpp       , ONLY: ctl_stop, mpp_sum      ! MPP library
[11395]19   USE fldread        ! read input fields
20
21   IMPLICIT NONE
22
23   PRIVATE
24
[11987]25   PUBLIC   isf_alloc, isf_alloc_par, isf_alloc_cav, isf_alloc_cpl, isf_dealloc_cpl
[11395]26   !
[11423]27   !-------------------------------------------------------
28   ! 0 :              namelist parameter
29   !-------------------------------------------------------
[11395]30   !
[11423]31   ! 0.1 -------- ice shelf cavity parameter --------------
32   CHARACTER(LEN=256), PUBLIC :: cn_isfdir
[11521]33   LOGICAL           , PUBLIC :: ln_isf
[11876]34   LOGICAL           , PUBLIC :: ln_isfdebug
[11395]35   !
[11489]36   ! 0.2 -------- ice shelf cavity opened namelist parameter -------------
[11423]37   LOGICAL           , PUBLIC :: ln_isfcav_mlt   !: logical for the use of ice shelf parametrisation
38   REAL(wp)          , PUBLIC :: rn_gammat0      !: temperature exchange coeficient    []
39   REAL(wp)          , PUBLIC :: rn_gammas0      !: salinity    exchange coeficient    []
40   REAL(wp)          , PUBLIC :: rn_htbl         !: Losch top boundary layer thickness [m]
[12062]41   REAL(wp)          , PUBLIC :: rn_isfload_T    !:
42   REAL(wp)          , PUBLIC :: rn_isfload_S    !:
[11423]43   CHARACTER(LEN=256), PUBLIC :: cn_gammablk     !: gamma formulation
44   CHARACTER(LEN=256), PUBLIC :: cn_isfcav_mlt   !: melt formulation (cavity/param)
[11489]45   CHARACTER(LEN=256), PUBLIC :: cn_isfload      !: ice shelf load computation method
[11423]46   TYPE(FLD_N)       , PUBLIC :: sn_isfcav_fwf   !: information about the isf melting file to be read
[11403]47   !
[11489]48   ! 0.3 -------- ice shelf cavity parametrised namelist parameter -------------
[11423]49   LOGICAL           , PUBLIC :: ln_isfpar_mlt   !: logical for the computation of melt inside the cavity
50   CHARACTER(LEN=256), PUBLIC :: cn_isfpar_mlt   !: melt formulation (cavity/param)
51   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_fwf   !: information about the isf melting file to be read
52   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_zmax  !: information about the grounding line depth file to be read
53   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_zmin  !: information about the calving   line depth file to be read
54   TYPE(FLD_N)       , PUBLIC :: sn_isfpar_Leff  !: information about the effective length     file to be read
[11395]55   !
[11423]56   ! 0.4 -------- coupling namelist parameter -------------
57   LOGICAL, PUBLIC :: ln_isfcpl      !:
58   LOGICAL, PUBLIC :: ln_isfcpl_cons !:
59   INTEGER, PUBLIC :: nn_drown       !:
[11395]60   !
[11423]61   !-------------------------------------------------------
62   ! 1 :              ice shelf parameter
63   !-------------------------------------------------------
64   !
[11395]65   REAL(wp), PARAMETER, PUBLIC :: rLfusisf = 0.334e6_wp    !: latent heat of fusion of ice shelf     [J/kg]
66   REAL(wp), PARAMETER, PUBLIC :: rcpisf = 2000.0_wp       !: specific heat of ice shelf             [J/kg/K]
67   REAL(wp), PARAMETER, PUBLIC :: rkappa = 1.54e-6_wp      !: heat diffusivity through the ice-shelf [m2/s]
68   REAL(wp), PARAMETER, PUBLIC :: rhoisf = 920.0_wp        !: volumic mass of ice shelf              [kg/m3]
69   REAL(wp), PARAMETER, PUBLIC :: rtsurf = -20.0           !: surface temperature                    [C]
[11423]70   !
71   !-------------------------------------------------------
72   ! 2 :              ice shelf global variables
73   !-------------------------------------------------------
74   !
[11987]75   ! 2.1 -------- ice shelf cavity parameter --------------
[11423]76   LOGICAL , PUBLIC            :: l_isfoasis
77   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    ::   risfload                    !: ice shelf load
78   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)    ::   fwfisf_oasis
79   !
[11987]80   ! 2.2 -------- ice shelf cavity melt namelist parameter -------------
[11423]81   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mskisf_cav                    !:
82   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: misfkt_cav   , misfkb_cav     !:
83   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: rhisf_tbl_cav, rfrac_tbl_cav  !:
84   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fwfisf_cav   , fwfisf_cav_b   !: before and now net fwf from the ice shelf        [kg/m2/s]
85   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: risf_cav_tsc , risf_cav_tsc_b !: before and now T & S isf contents [K.m/s & PSU.m/s] 
86   TYPE(FLD), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     :: sf_isfcav_fwf                 !:
87   !
88   REAL(wp) , PUBLIC                                      :: risf_lamb1, risf_lamb2, risf_lamb3  ! freezing point linearization coeficient
89   !
[11987]90   ! 2.3 -------- ice shelf param. melt namelist parameter -------------
[11423]91   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: mskisf_par                    !:
92   INTEGER  , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: misfkt_par   , misfkb_par     !:
93   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: rhisf_tbl_par, rfrac_tbl_par  !:
94   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: fwfisf_par   , fwfisf_par_b   !: before and now net fwf from the ice shelf        [kg/m2/s]
95   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: risf_par_tsc , risf_par_tsc_b !: before and now T & S isf contents [K.m/s & PSU.m/s] 
96   TYPE(FLD), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     :: sf_isfpar_fwf                 !:
97   !
98   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: rhisf0_tbl_par                !: thickness of tbl (initial value)  [m]
99   REAL(wp) , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   :: risfLeff                      !:
100   !
[11987]101   ! 2.4 -------- coupling namelist parameter -------------
[11423]102   INTEGER , PUBLIC                                        ::   nstp_iscpl   !:
103   REAL(wp), PUBLIC                                        ::   rdt_iscpl    !:
[11529]104   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   risfcpl_ssh, risfcpl_cons_ssh, risfcpl_cons_ssh_b               !:
[11521]105   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   risfcpl_vol, risfcpl_cons_vol, risfcpl_cons_vol_b  !:
106   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   risfcpl_tsc, risfcpl_cons_tsc, risfcpl_cons_tsc_b  !:
[11423]107   !
[11395]108   !!----------------------------------------------------------------------
109   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
110   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
111   !! Software governed by the CeCILL license (see ./LICENSE)
112   !!----------------------------------------------------------------------
113CONTAINS
114
115   SUBROUTINE isf_alloc_par()
116      !!---------------------------------------------------------------------
[11403]117      !!                  ***  ROUTINE isf_alloc_par  ***
[11395]118      !!
119      !! ** Purpose :
120      !!
121      !! ** Method  :
122      !!
123      !!----------------------------------------------------------------------
124      INTEGER :: ierr, ialloc
125      !!----------------------------------------------------------------------
126      ierr = 0       ! set to zero if no array to be allocated
127      !
128      ALLOCATE(risfLeff(jpi,jpj), STAT=ialloc)
129      ierr = ierr + ialloc
130      !
[11403]131      ALLOCATE(misfkt_par(jpi,jpj), misfkb_par(jpi,jpj), STAT=ialloc )
132      ierr = ierr + ialloc
133      !
134      ALLOCATE( rfrac_tbl_par(jpi,jpj), STAT=ialloc)
135      ierr = ierr + ialloc
136      !
137      ALLOCATE( rhisf_tbl_par(jpi,jpj), rhisf0_tbl_par(jpi,jpj), STAT=ialloc)
138      ierr = ierr + ialloc
139      !
140      ALLOCATE( mskisf_par(jpi,jpj), STAT=ialloc)
141      ierr = ierr + ialloc
142      !
[11395]143      CALL mpp_sum ( 'isf', ierr )
144      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' )
[11423]145      !
[11395]146   END SUBROUTINE isf_alloc_par
147
[13364]148   
[11395]149   SUBROUTINE isf_alloc_cav()
150      !!---------------------------------------------------------------------
[11403]151      !!                  ***  ROUTINE isf_alloc_cav  ***
[11395]152      !!
153      !! ** Purpose :
154      !!
155      !! ** Method  :
156      !!
157      !!----------------------------------------------------------------------
158      INTEGER :: ierr, ialloc
159      !!----------------------------------------------------------------------
160      ierr = 0       ! set to zero if no array to be allocated
161      !
[11403]162      ALLOCATE(misfkt_cav(jpi,jpj), misfkb_cav(jpi,jpj), STAT=ialloc )
163      ierr = ierr + ialloc
164      !
165      ALLOCATE( rfrac_tbl_cav(jpi,jpj), STAT=ialloc)
166      ierr = ierr + ialloc
167      !
168      ALLOCATE( rhisf_tbl_cav(jpi,jpj), STAT=ialloc)
169      ierr = ierr + ialloc
170      !
[11395]171      CALL mpp_sum ( 'isf', ierr )
172      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' )
[11423]173      !
[11395]174   END SUBROUTINE isf_alloc_cav
175
[13364]176   
[11423]177   SUBROUTINE isf_alloc_cpl()
178      !!---------------------------------------------------------------------
179      !!                  ***  ROUTINE isf_alloc_cpl  ***
180      !!
[11987]181      !! ** Purpose : allocate array use for the ice sheet coupling
[11423]182      !!
183      !!----------------------------------------------------------------------
184      INTEGER :: ierr, ialloc
185      !!----------------------------------------------------------------------
186      ierr = 0
187      !
[13364]188      ALLOCATE( risfcpl_ssh(jpi,jpj) , risfcpl_tsc(jpi,jpj,jpk,jpts) , risfcpl_vol(jpi,jpj,jpk) , STAT=ialloc )
[11423]189      ierr = ierr + ialloc
190      !
[13364]191      risfcpl_tsc(:,:,:,:) = 0._wp ; risfcpl_vol(:,:,:) = 0._wp ; risfcpl_ssh(:,:) = 0._wp
[11553]192
[13364]193      IF ( ln_isfcpl_cons ) THEN
194         ALLOCATE( risfcpl_cons_tsc(jpi,jpj,jpk,jpts) , risfcpl_cons_vol(jpi,jpj,jpk) , risfcpl_cons_ssh(jpi,jpj) , STAT=ialloc )
[11553]195         ierr = ierr + ialloc
196         !
[13364]197         risfcpl_cons_tsc(:,:,:,:) = 0._wp ; risfcpl_cons_vol(:,:,:) = 0._wp ; risfcpl_cons_ssh(:,:) = 0._wp
[11553]198         !
199      END IF
200      !
[11423]201      CALL mpp_sum ( 'isf', ierr )
[11852]202      IF( ierr /= 0 )   CALL ctl_stop('STOP','isfcpl: failed to allocate arrays.')
[11423]203      !
204   END SUBROUTINE isf_alloc_cpl
205
[13364]206   
[11987]207   SUBROUTINE isf_dealloc_cpl()
208      !!---------------------------------------------------------------------
209      !!                  ***  ROUTINE isf_dealloc_cpl  ***
210      !!
211      !! ** Purpose : de-allocate useless public 3d array used for ice sheet coupling
212      !!
213      !!----------------------------------------------------------------------
214      INTEGER :: ierr, ialloc
215      !!----------------------------------------------------------------------
216      ierr = 0
217      !
[13364]218      DEALLOCATE( risfcpl_ssh , risfcpl_tsc , risfcpl_vol , STAT=ialloc )
[11987]219      ierr = ierr + ialloc
220      !
221      CALL mpp_sum ( 'isf', ierr )
222      IF( ierr /= 0 )   CALL ctl_stop('STOP','isfcpl: failed to deallocate arrays.')
223      !
224   END SUBROUTINE isf_dealloc_cpl
225
[13364]226   
[11395]227   SUBROUTINE isf_alloc()
228      !!---------------------------------------------------------------------
[11403]229      !!                  ***  ROUTINE isf_alloc  ***
[11395]230      !!
[11987]231      !! ** Purpose : allocate array used for the ice shelf cavity (cav and par)
[11395]232      !!
233      !!----------------------------------------------------------------------
234      INTEGER :: ierr, ialloc
235      !!----------------------------------------------------------------------
236      !
237      ierr = 0       ! set to zero if no array to be allocated
238      !
[13364]239      ALLOCATE( fwfisf_par  (jpi,jpj) , fwfisf_par_b(jpi,jpj) ,     &
240         &      fwfisf_cav  (jpi,jpj) , fwfisf_cav_b(jpi,jpj) ,     &
241         &      fwfisf_oasis(jpi,jpj)                         , STAT=ialloc )
[11395]242      ierr = ierr + ialloc
243      !
[13364]244      ALLOCATE( risf_par_tsc(jpi,jpj,jpts) , risf_par_tsc_b(jpi,jpj,jpts) , STAT=ialloc )
[11395]245      ierr = ierr + ialloc
246      !
[13364]247      ALLOCATE( risf_cav_tsc(jpi,jpj,jpts) , risf_cav_tsc_b(jpi,jpj,jpts) , STAT=ialloc )
[11395]248      ierr = ierr + ialloc
249      !
[13364]250      ALLOCATE( risfload(jpi,jpj) , STAT=ialloc )
[11395]251      ierr = ierr + ialloc
252      !
[13364]253      ALLOCATE( mskisf_cav(jpi,jpj) , STAT=ialloc )
[11423]254      ierr = ierr + ialloc
255      !
[11395]256      CALL mpp_sum ( 'isf', ierr )
257      IF( ierr /= 0 )   CALL ctl_stop( 'STOP', 'isf: failed to allocate arrays.' )
[11553]258      !
259      ! initalisation of fwf and tsc array to 0
[13364]260      risfload    (:,:)   = 0._wp
261      fwfisf_oasis(:,:)   = 0._wp
262      fwfisf_par  (:,:)   = 0._wp   ;   fwfisf_par_b  (:,:)   = 0._wp
263      fwfisf_cav  (:,:)   = 0._wp   ;   fwfisf_cav_b  (:,:)   = 0._wp
264      risf_cav_tsc(:,:,:) = 0._wp   ;   risf_cav_tsc_b(:,:,:) = 0._wp
265      risf_par_tsc(:,:,:) = 0._wp   ;   risf_par_tsc_b(:,:,:) = 0._wp
[11553]266      !
[11395]267   END SUBROUTINE isf_alloc
[13364]268   
269   !!======================================================================
[11987]270END MODULE isf_oce
Note: See TracBrowser for help on using the repository browser.