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

source: NEMO/branches/UKMO/NEMO_4.0.2_GO8_package_ENHANCE-02_ISF_nemo/src/ISF/isftbl.F90 @ 12721

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

NEMO_4.0.2_GO8_package_ENHANCE-02_ISF_nemo: add last year isf dev

File size: 12.5 KB
Line 
1MODULE isftbl
2   !!======================================================================
3   !!                       ***  MODULE  isftbl  ***
4   !! isftbl module :  compute properties of top boundary layer
5   !!======================================================================
6   !! History :  4.1  !  2019-09  (P. Mathiot) original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   isftbl       : routine to compute :
11   !!                  - geometry of the ice shelf tbl (isf_tbl_lvl, isftbl_ktop, isftbl_kbot)
12   !!                    (top and bottom level, thickness and fraction of deepest level affected)
13   !!                  - tbl averaged properties (isf_tbl, isf_tbl_avg)
14   !!----------------------------------------------------------------------
15
16   USE isf_oce ! ice shelf variables
17
18   USE dom_oce ! vertical scale factor and depth
19
20   IMPLICIT NONE
21
22   PRIVATE
23
24   PUBLIC isf_tbl, isf_tbl_avg, isf_tbl_lvl, isf_tbl_ktop, isf_tbl_kbot
25
26CONTAINS
27
28   SUBROUTINE isf_tbl( pvarin, pvarout, cd_ptin, ktop, phtbl, kbot, pfrac )
29      !!--------------------------------------------------------------------
30      !!                  ***  SUBROUTINE isf_tbl  ***
31      !!
32      !! ** Purpose : compute mean T/S/U/V in the boundary layer at T- point
33      !!
34      !! ** Method : Average properties over a specific thickness
35      !!
36      !! ** Reference : inspired from : Losch, Modeling ice shelf cavities in a z coordinate ocean general circulation model
37      !!                https://doi.org/10.1029/2007JC004368 , 2008
38      !!
39      !!-------------------------- OUT -------------------------------------
40      REAL(wp), DIMENSION(jpi,jpj)          , INTENT(  out) :: pvarout ! 2d average of pvarin
41      !!-------------------------- IN  -------------------------------------
42      CHARACTER(len=1)                      , INTENT(in   ) :: cd_ptin       ! point of variable in/out
43      REAL(wp), DIMENSION(jpi,jpj,jpk)      , INTENT(in   ) :: pvarin        ! 3d variable to average over the tbl
44      INTEGER,  DIMENSION(jpi,jpj)          , INTENT(in   ) :: ktop          ! top level
45      REAL(wp), DIMENSION(jpi,jpj)          , INTENT(in   ) :: phtbl         ! tbl thickness
46      !!-------------------------- IN OPTIONAL -----------------------------
47      INTEGER,  DIMENSION(jpi,jpj), OPTIONAL, INTENT(in   ) :: kbot          ! bottom level
48      REAL(wp), DIMENSION(jpi,jpj), OPTIONAL, INTENT(in   ) :: pfrac         ! fraction of bottom cell affected by tbl
49      !!--------------------------------------------------------------------
50      INTEGER ::   ji, jj                     ! loop index
51      INTEGER , DIMENSION(jpi,jpj) :: ikbot   ! bottom level of the tbl
52      REAL(wp), DIMENSION(jpi,jpj) :: zvarout ! 2d average of pvarin
53      REAL(wp), DIMENSION(jpi,jpj) :: zhtbl   ! thickness of the tbl
54      REAL(wp), DIMENSION(jpi,jpj) :: zfrac   ! thickness of the tbl
55      !!--------------------------------------------------------------------
56      !
57      SELECT CASE ( cd_ptin )
58      CASE ( 'U' )
59         !
60         ! copy phtbl (phtbl is INTENT in as we don't want to change it)
61         zhtbl = phtbl
62         !
63         ! compute tbl lvl and thickness
64         CALL isf_tbl_lvl( hu_n, e3u_n, ktop, ikbot, zhtbl, zfrac )
65         !
66         ! compute tbl property at U point
67         CALL isf_tbl_avg( miku, ikbot, zhtbl, zfrac, e3u_n, pvarin, zvarout )
68         !
69         ! compute tbl property at T point
70         pvarout(1,:) = 0._wp
71         DO jj = 1, jpj
72            DO ji = 2, jpi
73               pvarout(ji,jj) = 0.5_wp * (zvarout(ji,jj) + zvarout(ji-1,jj))
74            END DO
75         END DO
76         ! lbclnk not needed as a final communication is done after the computation of fwf
77         !
78      CASE ( 'V' )
79         !
80         ! copy phtbl (phtbl is INTENT in as we don't want to change it)
81         zhtbl = phtbl
82         !
83         ! compute tbl lvl and thickness
84         CALL isf_tbl_lvl( hv_n, e3v_n, ktop, ikbot, zhtbl, zfrac )
85         !
86         ! compute tbl property at V point
87         CALL isf_tbl_avg( mikv, ikbot, zhtbl, zfrac, e3v_n, pvarin, zvarout )
88         !
89         ! pvarout is an averaging of wet point
90         pvarout(:,1) = 0._wp
91         DO jj = 2, jpj
92            DO ji = 1, jpi
93               pvarout(ji,jj) = 0.5_wp * (zvarout(ji,jj) + zvarout(ji,jj-1))
94            END DO
95         END DO
96         ! lbclnk not needed as a final communication is done after the computation of fwf
97         !
98      CASE ( 'T' )
99         !
100         ! compute tbl property at T point
101         CALL isf_tbl_avg( ktop, kbot, phtbl, pfrac, e3t_n, pvarin, pvarout )
102         !
103      END SELECT
104      !
105   END SUBROUTINE isf_tbl
106
107   SUBROUTINE isf_tbl_avg( ktop, kbot, phtbl, pfrac, pe3, pvarin, pvarout )
108      !!--------------------------------------------------------------------
109      !!                  ***  ROUTINE isf_tbl_avg  ***
110      !!
111      !! ** Purpose : compute mean property in the boundary layer
112      !!
113      !! ** Method  : Depth average is made between the top level ktop and the bottom level kbot
114      !!              over a thickness phtbl. The bottom level is partially counted (pfrac).
115      !!
116      !!-------------------------- OUT -------------------------------------
117      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(  out) :: pvarout      ! tbl property averaged over phtbl between level ktop and kbot
118      !!-------------------------- IN  -------------------------------------
119      INTEGER,  DIMENSION(jpi,jpj)    , INTENT(in   ) :: ktop, kbot   ! top and bottom level of the top boundary layer
120      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   ) :: phtbl, pfrac ! fraction of bottom level to be affected by the tbl
121      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) :: pe3          ! vertical scale factor
122      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) :: pvarin       ! tbl property to average between ktop, kbot over phtbl
123      !!--------------------------------------------------------------------
124      INTEGER  :: ji,jj,jk                    ! loop indices
125      INTEGER  :: ikt, ikb                    ! top and bottom levels
126      !!--------------------------------------------------------------------
127      !
128      ! compute tbl top.bottom level and thickness
129      DO jj = 1,jpj
130         DO ji = 1,jpi
131            !
132            ! tbl top/bottom indices initialisation
133            ikt = ktop(ji,jj) ; ikb = kbot(ji,jj)
134            !
135            ! level fully include in the ice shelf boundary layer
136            pvarout(ji,jj) = SUM( pvarin(ji,jj,ikt:ikb-1) * pe3(ji,jj,ikt:ikb-1) ) / phtbl(ji,jj)
137            !
138            ! level partially include in ice shelf boundary layer
139            pvarout(ji,jj) = pvarout(ji,jj) + pvarin(ji,jj,ikb) * pe3(ji,jj,ikb) / phtbl(ji,jj) * pfrac(ji,jj)
140            !
141         END DO
142      END DO
143
144   END SUBROUTINE isf_tbl_avg
145
146   SUBROUTINE isf_tbl_lvl( phw, pe3, ktop, kbot, phtbl, pfrac )
147      !!--------------------------------------------------------------------
148      !!                  ***  ROUTINE isf_tbl_lvl  ***
149      !!
150      !! ** Purpose : - compute bottom level off the top boundary layer
151      !!              - thickness of the top boundary layer
152      !!              - fraction of the bottom level affected by the tbl
153      !!
154      !!-------------------------- OUT --------------------------------------
155      INTEGER,  DIMENSION(jpi,jpj)    , INTENT(  out) :: kbot   ! bottom level of the top boundary layer
156      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(  out) :: pfrac  ! fraction of bottom level in the tbl
157      !!-------------------------- IN  --------------------------------------
158      INTEGER,  DIMENSION(jpi,jpj)    , INTENT(in   ) :: ktop   ! top level of the top boundary layer
159      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   ) :: phw    ! water column thickness
160      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) :: pe3    ! vertical scale factor
161      !!-------------------------- INOUT ------------------------------------
162      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(inout) :: phtbl  ! top boundary layer thickness
163      !!---------------------------------------------------------------------
164      INTEGER :: ji,jj,jk
165      INTEGER :: ikt, ikb
166      !!---------------------------------------------------------------------
167      !
168      ! get htbl
169      DO jj = 1,jpj
170         DO ji = 1,jpi
171            !
172            ! tbl top/bottom indices initialisation
173            ikt = ktop(ji,jj)
174            !
175            ! limit the tbl to water thickness.
176            phtbl(ji,jj) = MIN( phtbl(ji,jj), phw(ji,jj) )
177            !
178            ! thickness of boundary layer must be at least the top level thickness
179            phtbl(ji,jj) = MAX( phtbl(ji,jj), pe3(ji,jj,ikt) )
180            !
181         END DO
182      END DO
183      !
184      ! get ktbl
185      CALL isf_tbl_kbot(ktop, phtbl, pe3, kbot)
186      !
187      ! get pfrac
188      DO jj = 1,jpj
189         DO ji = 1,jpi
190            !
191            ! tbl top/bottom indices initialisation
192            ikt = ktop(ji,jj) ; ikb = kbot(ji,jj)
193            !
194            ! proportion of the bottom cell included in ice shelf boundary layer
195            pfrac(ji,jj) = ( phtbl(ji,jj) - SUM( pe3(ji,jj,ikt:ikb-1) ) ) / pe3(ji,jj,ikb)
196            !
197         END DO
198      END DO
199      !
200   END SUBROUTINE isf_tbl_lvl
201   !
202   SUBROUTINE isf_tbl_kbot(ktop, phtbl, pe3, kbot)
203      !!--------------------------------------------------------------------
204      !!                  ***  ROUTINE isf_tbl_bot  ***
205      !!
206      !! ** Purpose : compute bottom level of the isf top boundary layer
207      !!
208      !!-------------------------- OUT -------------------------------------
209      INTEGER,  DIMENSION(jpi,jpj)    , INTENT(  out) :: kbot   ! bottom level of the top boundary layer
210      !!-------------------------- IN  -------------------------------------
211      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   ) :: phtbl  ! top boundary layer thickness
212      INTEGER,  DIMENSION(jpi,jpj)    , INTENT(in   ) :: ktop   ! top level of the top boundary layer
213      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) :: pe3    ! vertical scale factor
214      !!--------------------------------------------------------------------
215      INTEGER :: ji, jj
216      INTEGER :: ikt, ikb
217      !!--------------------------------------------------------------------
218      !
219      ! phtbl need to be bounded by water column thickness before
220      ! test: if htbl = water column thickness, should return mbathy
221      ! test: if htbl = 0 should return ktop (phtbl cap to e3t(ji,jj,1))
222      !
223      ! get ktbl
224      DO jj = 1,jpj
225         DO ji = 1,jpi
226            !
227            ! determine the deepest level influenced by the boundary layer
228            ikt = ktop(ji,jj)
229            ikb = ikt
230            DO WHILE ( SUM(pe3(ji,jj,ikt:ikb-1)) < phtbl(ji,jj ) ) ;  ikb = ikb + 1 ;  END DO
231            kbot(ji,jj) = ikb - 1
232            !
233         END DO
234      END DO
235      !
236   END SUBROUTINE isf_tbl_kbot
237      !
238   SUBROUTINE isf_tbl_ktop(pdep, ktop)
239      !!--------------------------------------------------------------------
240      !!                  ***  ROUTINE isf_tbl_top  ***
241      !!
242      !! ** Purpose : compute top level of the isf top boundary layer in case of an ice shelf parametrisation
243      !!
244      !!-------------------------- OUT -------------------------------------
245      INTEGER,  DIMENSION(jpi,jpj), INTENT(  out) :: ktop        ! top level affected by the ice shelf parametrisation
246      !!-------------------------- IN  -------------------------------------
247      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pdep        ! top depth of the parametrisation influence
248      !!--------------------------------------------------------------------
249      INTEGER :: ji,jj
250      INTEGER :: ikt
251      !!--------------------------------------------------------------------
252      !
253      ! if we need to recompute the top level at every time stepcompute top level (z*, z~)
254      ! in case of weak ht_n variation we can assume the top level of htbl to be constant
255      ! => only done using gdepw_0
256      ! be sure pdep is already correctly bounded
257      ! test: this routine run on isfdraft should return mikt
258      ! test: this routine run with pdep = 0 should return 1
259      !
260      DO ji = 1, jpi
261         DO jj = 1, jpj
262            ! comput ktop
263            ikt = 2
264            DO WHILE ( gdepw_0(ji,jj,ikt) <= pdep(ji,jj ) ) ;  ikt = ikt + 1 ;  END DO
265            ktop(ji,jj) = ikt - 1
266            !
267            ! update pdep
268            pdep(ji,jj) = gdepw_0(ji,jj,ktop(ji,jj))
269         END DO
270      END DO
271      !
272   END SUBROUTINE isf_tbl_ktop
273
274END MODULE isftbl
Note: See TracBrowser for help on using the repository browser.