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

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

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

ENHANCE-02_ISF: simplify use of ln_isf, add extra comments + minor changes (ticket #2142)

File size: 5.0 KB
Line 
1MODULE isfhdiv
2
3   USE dom_oce
4   USE iom
5   USE isf
6   USE isfutils
7   USE phycst
8   USE in_out_manager
9
10   IMPLICIT NONE
11
12   PRIVATE
13
14   PUBLIC isf_hdiv
15
16CONTAINS
17
18   SUBROUTINE isf_hdiv( kt, phdiv )
19      !!----------------------------------------------------------------------
20      !!                  ***  SUBROUTINE isf_hdiv  ***
21      !!       
22      !! ** Purpose :   update the horizontal divergence with the ice shelf contribution
23      !!                (parametrisation, explicit, ice sheet coupling conservation
24      !!                 increment)
25      !!
26      !!----------------------------------------------------------------------
27      REAL(wp), DIMENSION(:,:,:), INTENT( inout ) ::   phdiv   ! horizontal divergence
28      !!----------------------------------------------------------------------
29      INTEGER, INTENT(in) :: kt
30      !
31      IF ( ln_isf ) THEN
32         !
33         ! ice shelf cavity contribution
34         IF ( ln_isfcav_mlt ) CALL isf_hdiv_mlt(misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, fwfisf_cav, fwfisf_cav_b, phdiv)
35         !
36         ! ice shelf parametrisation contribution
37         IF ( ln_isfpar_mlt ) CALL isf_hdiv_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, fwfisf_par, fwfisf_par_b, phdiv)
38         !
39         !
40         ! ice sheet coupling contribution
41         IF ( ln_isfcpl ) THEN
42            !
43            ! correct divergence only for the first time step
44            IF ( kt == nit000   ) CALL isf_hdiv_cpl(risfcpl_vol       , phdiv)
45            IF ( kt == nit000+1 ) CALL isf_hdiv_cpl(risfcpl_vol*0.5_wp, phdiv)
46            !
47            ! correct divergence every time step to remove any trend due to coupling
48            ! conservation option
49            IF ( ln_isfcpl_cons ) CALL isf_hdiv_cpl(risfcpl_cons_vol, phdiv)
50            !
51         END IF
52         !
53      END IF
54      !
55   END SUBROUTINE isf_hdiv
56
57   SUBROUTINE isf_hdiv_mlt(ktop, kbot, phtbl, pfrac, pfwf, pfwf_b, phdiv)
58      !!----------------------------------------------------------------------
59      !!                  ***  SUBROUTINE sbc_isf_div  ***
60      !!       
61      !! ** Purpose :   update the horizontal divergence with the ice shelf inflow
62      !!
63      !! ** Method  :   pfwf is positive (outflow) and expressed as kg/m2/s
64      !!                increase the divergence
65      !!
66      !! ** Action  :   phdivn   increased by the ice shelf outflow
67      !!----------------------------------------------------------------------
68      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: phdiv
69      !!----------------------------------------------------------------------
70      INTEGER , DIMENSION(jpi,jpj), INTENT(in   ) :: ktop , kbot
71      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pfrac, phtbl
72      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) :: pfwf , pfwf_b
73      !!----------------------------------------------------------------------
74      INTEGER  ::   ji, jj, jk   ! dummy loop indices
75      INTEGER  ::   ikt, ikb 
76      REAL(wp), DIMENSION(jpi,jpj) :: zhdiv
77      !!----------------------------------------------------------------------
78      !
79      !==   fwf distributed over several levels   ==!
80      !
81      ! compute integrated divergence correction
82      zhdiv(:,:) = 0.5_wp * ( pfwf(:,:) + pfwf_b(:,:) ) * r1_rau0 / phtbl(:,:)
83      !
84      ! update divergence at each level affected by ice shelf top boundary layer
85      DO jj = 1,jpj
86         DO ji = 1,jpi
87            ikt = ktop(ji,jj)
88            ikb = kbot(ji,jj)
89            ! level fully include in the ice shelf boundary layer
90            DO jk = ikt, ikb - 1
91               phdiv(ji,jj,jk) = phdiv(ji,jj,jk) + zhdiv(ji,jj)
92            END DO
93            ! level partially include in ice shelf boundary layer
94            phdiv(ji,jj,ikb) = phdiv(ji,jj,ikb) + zhdiv(ji,jj) * pfrac(ji,jj)
95         END DO
96      END DO
97      !
98   END SUBROUTINE isf_hdiv_mlt
99
100   SUBROUTINE isf_hdiv_cpl(pqvol, phdiv)
101      !!----------------------------------------------------------------------
102      !!                  ***  SUBROUTINE isf_hdiv_cpl  ***
103      !!       
104      !! ** Purpose :   update the horizontal divergence with the ice shelf
105      !!                coupling conservation increment
106      !!
107      !! ** Method  :   pqvol is positive (outflow) and expressed as m3/s
108      !!                increase the divergence
109      !!
110      !! ** Action  :   phdivn   increased by the ice shelf outflow
111      !!
112      !!----------------------------------------------------------------------
113      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: phdiv
114      !!----------------------------------------------------------------------
115      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in   ) :: pqvol
116      !!----------------------------------------------------------------------
117      INTEGER :: jk
118      !!----------------------------------------------------------------------
119      !
120      DO jk=1,jpk 
121         phdiv(:,:,jk) =  phdiv(:,:,jk) + pqvol(:,:,jk) * r1_e1e2t(:,:) / e3t_n(:,:,jk)
122      END DO
123      !
124   END SUBROUTINE isf_hdiv_cpl
125
126END MODULE isfhdiv
Note: See TracBrowser for help on using the repository browser.