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

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

ENHANCE-02_ISF_nemo: add check on presence of restart variables

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