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/UKMO_MERGE_2019/src/OCE/ISF – NEMO

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