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 @ 11987

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

ENHANCE-02_ISF_nemo: changes needed after Dave's review

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