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.
isfload.F90 in NEMO/branches/2019/UKMO_MERGE_2019/src/OCE/ISF – NEMO

source: NEMO/branches/2019/UKMO_MERGE_2019/src/OCE/ISF/isfload.F90 @ 12068

Last change on this file since 12068 was 12068, checked in by davestorkey, 4 years ago

2019/UKMO_MERGE_2019 : Merging in changes from ENHANCE-02_ISF_nemo.

File size: 5.4 KB
Line 
1MODULE isfload
2   !!======================================================================
3   !!                       ***  MODULE  isfload  ***
4   !! isfload module :  compute ice shelf load (needed for the hpg)
5   !!======================================================================
6   !! History :  4.1  !  2019-09  (P. Mathiot) original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   isfload      : compute ice shelf load
11   !!----------------------------------------------------------------------
12
13   USE isf, ONLY: cn_isfload   ! ice shelf variables
14
15   USE dom_oce, ONLY: e3w, gdept, risfdep, mikt     ! vertical scale factor
16   USE eosbn2 , ONLY: eos                           ! eos routine
17
18   USE lib_mpp, ONLY: ctl_stop ! ctl_stop routine
19   USE in_out_manager  !
20
21   IMPLICIT NONE
22
23   PRIVATE
24
25   PUBLIC isf_load
26
27CONTAINS
28
29   SUBROUTINE isf_load ( Kmm, pisfload )
30      !!--------------------------------------------------------------------
31      !!                  ***  SUBROUTINE isf_load  ***
32      !!
33      !! ** Purpose : compute the ice shelf load
34      !!
35      !!--------------------------------------------------------------------
36      !!-------------------------- OUT -------------------------------------
37      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pisfload
38      !!-------------------------- IN  -------------------------------------
39      INTEGER,                      INTENT(in)    :: Kmm           ! ocean time level index
40      !!----------------------------------------------------------------------
41      !
42      ! quality test: ice shelf in a stratify/uniform ocean should not drive any flow.
43      !               the smaller the residual flow is, the better it is.
44      !
45      ! ice shelf cavity
46      SELECT CASE ( cn_isfload )
47      CASE ( 'isomip' )
48         CALL isf_load_isomip ( Kmm, pisfload )
49      CASE DEFAULT
50         CALL ctl_stop('STOP','method cn_isfload to compute ice shelf load does not exist (isomip), check your namelist')
51      END SELECT
52      !
53   END SUBROUTINE isf_load
54
55   SUBROUTINE isf_load_isomip( Kmm, pisfload )
56      !!--------------------------------------------------------------------
57      !!                  ***  SUBROUTINE isf_load  ***
58      !!
59      !! ** Purpose : compute the ice shelf load
60      !!
61      !! ** Method  : The ice shelf is assumed to be in hydro static equilibrium
62      !!              in water at -1.9 C and 34.4 PSU. Weight of the ice shelf is
63      !!              integrated from top to bottom.
64      !!
65      !!--------------------------------------------------------------------
66      !!-------------------------- OUT -------------------------------------
67      REAL(wp), DIMENSION(jpi,jpj), INTENT(  out) :: pisfload
68      !!-------------------------- IN  -------------------------------------
69      INTEGER,                      INTENT(in)    :: Kmm           ! ocean time level index
70      !!--------------------------------------------------------------------
71      INTEGER  :: ji, jj, jk
72      INTEGER  :: ikt
73      REAL(wp)                          :: znad        !
74      REAL(wp), DIMENSION(jpi,jpj)      :: zrhdtop_isf ! water density    displaced by the ice shelf (at the interface)
75      REAL(wp), DIMENSION(jpi,jpj,jpts) :: zts_top     ! water properties displaced by the ice shelf   
76      REAL(wp), DIMENSION(jpi,jpj,jpk)  :: zrhd        ! water density    displaced by the ice shelf
77      !!----------------------------------------------------------------------
78      !
79      znad = 1._wp                     !- To use density and not density anomaly
80      !
81      !                                !- assume water displaced by the ice shelf is at T=-1.9 and S=34.4 (rude)
82      zts_top(:,:,jp_tem) = -1.9_wp   ;   zts_top(:,:,jp_sal) = 34.4_wp
83      !
84      DO jk = 1, jpk                   !- compute density of the water displaced by the ice shelf
85         CALL eos( zts_top(:,:,:), gdept(:,:,jk,Kmm), zrhd(:,:,jk) )
86      END DO
87      !
88      !                                !- compute rhd at the ice/oce interface (ice shelf side)
89      CALL eos( zts_top , risfdep, zrhdtop_isf )
90      !
91      !                                !- Surface value + ice shelf gradient
92      pisfload(:,:) = 0._wp                       ! compute pressure due to ice shelf load
93      DO jj = 1, jpj                         ! (used to compute hpgi/j for all the level from 1 to miku/v)
94         DO ji = 1, jpi                      ! divided by 2 later
95            ikt = mikt(ji,jj)
96            !
97            IF ( ikt > 1 ) THEN
98               !
99               ! top layer of the ice shelf
100               pisfload(ji,jj) = pisfload(ji,jj) + (znad + zrhd(ji,jj,1) ) * e3w(ji,jj,1,Kmm)
101               !
102               ! core layers of the ice shelf
103               DO jk = 2, ikt-1
104                  pisfload(ji,jj) = pisfload(ji,jj) + (2._wp * znad + zrhd(ji,jj,jk-1) + zrhd(ji,jj,jk)) * e3w(ji,jj,jk,Kmm)
105               END DO
106               !
107               ! deepest part of the ice shelf (between deepest T point and ice/ocean interface
108               pisfload(ji,jj) = pisfload(ji,jj) + (2._wp * znad + zrhdtop_isf(ji,jj) + zrhd(ji,jj,ikt-1)) &
109                  &                                              * ( risfdep(ji,jj) - gdept(ji,jj,ikt-1,Kmm) )
110               !
111            END IF
112         END DO
113      END DO
114      !
115   END SUBROUTINE isf_load_isomip
116
117END MODULE isfload
Note: See TracBrowser for help on using the repository browser.