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

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/traisf.F90 @ 11395

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

ENHANCE-02_ISF_nemo : Initial commit isf simplification (add ISF directory, moved isf routine in and split isf cavity and isf parametrisation, ...) (ticket #2142)

File size: 6.3 KB
Line 
1MODULE traisf
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
6   !! History :    4.0  !  2019-09  (P. Mathiot) original file
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   tra_isf       : update the tracer trend at ocean surface
11   !!----------------------------------------------------------------------
12   USE oce            ! ocean dynamics and active tracers
13   USE dom_oce        ! ocean space domain variables
14   USE phycst         ! physical constant
15   USE eosbn2         ! Equation Of State
16   USE isf            ! Ice shelf variable
17   USE isfutils       !
18   USE iscplini       ! Ice sheet coupling
19   !
20   USE in_out_manager ! I/O manager
21   USE iom            ! xIOS server
22   USE timing         ! Timing
23
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   tra_isf   ! routine called by step.F90
28
29   !! * Substitutions
30#  include "vectopt_loop_substitute.h90"
31   !!----------------------------------------------------------------------
32   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
33   !! $Id: trasbc.F90 10499 2019-01-10 15:12:24Z deazer $
34   !! Software governed by the CeCILL license (see ./LICENSE)
35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE tra_isf ( kt )
39      !!----------------------------------------------------------------------
40      !!                  ***  ROUTINE tra_sbc  ***
41      !!                   
42      !! ** Purpose :   Compute the tracer surface boundary condition trend of
43      !!      (flux through the interface, concentration/dilution effect)
44      !!      and add it to the general trend of tracer equations.
45      !!
46      !! ** Method :   The (air+ice)-sea flux has two components:
47      !!      (1) Fext, external forcing (i.e. flux through the (air+ice)-sea interface);
48      !!      (2) Fwe , tracer carried with the water that is exchanged with air+ice.
49      !!               The input forcing fields (emp, rnf, sfx, isf) contain Fext+Fwe,
50      !!             they are simply added to the tracer trend (tsa).
51      !!               In linear free surface case (ln_linssh=T), the volume of the
52      !!             ocean does not change with the water exchanges at the (air+ice)-sea
53      !!             interface. Therefore another term has to be added, to mimic the
54      !!             concentration/dilution effect associated with water exchanges.
55      !!
56      !! ** Action  : - Update tsa with the surface boundary condition trend
57      !!              - send trends to trdtra module for further diagnostics(l_trdtra=T)
58      !!----------------------------------------------------------------------
59      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
60      !!----------------------------------------------------------------------
61      !
62      IF( ln_timing )   CALL timing_start('tra_sbc')
63      !
64      !----------------------------------------
65      !       Ice Shelf effects (ISF)
66      !     tbl treated as in Losh (2008) JGR
67      !----------------------------------------
68      IF ( ln_isfcav_mlt ) CALL tra_isf_mlt(misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, risf_cav_tsc, risf_cav_tsc_b, tsa)
69      IF ( ln_isfpar_mlt ) CALL tra_isf_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, risf_par_tsc, risf_par_tsc_b, tsa)
70      !
71      !CALL tra_isf_cpl()
72      !
73      IF( ln_timing )   CALL timing_stop('tra_isf')
74      !
75   END SUBROUTINE tra_isf
76   !
77   SUBROUTINE tra_isf_mlt(ktop, kbot, phtbl, pfrac, ptsc, ptsc_b, pts)
78      !!----------------------------------------------------------------------
79      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: pts
80      !!----------------------------------------------------------------------
81      INTEGER , DIMENSION(jpi,jpj)     , INTENT(in   ) :: ktop , kbot
82      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: phtbl, pfrac
83      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc , ptsc_b
84      !!----------------------------------------------------------------------
85      !
86      INTEGER  ::   ji, jj, jk, jn              ! dummy loop indices 
87      INTEGER  ::   ikt, ikb                    ! local integers
88      REAL(wp) :: zeps = 1.e-20
89      REAL(wp), DIMENSION(jpi,jpj) :: ztc
90      !!----------------------------------------------------------------------
91      !
92      !----------------------------------------
93      !       Ice Shelf effects (ISF)
94      !     tbl treated as in Losh (2008) JGR
95      !----------------------------------------
96      !
97      ! compute 2d total trend due to isf
98      ztc(:,:) = 0.5_wp * ( ptsc(:,:,jp_tem) + ptsc_b(:,:,jp_tem) ) / phtbl(:,:)
99      !
100      ! update tsa
101      DO jj = 1,jpj
102         DO ji = 1,jpi
103            !
104            ikt = ktop(ji,jj)
105            ikb = kbot(ji,jj)
106            !
107            ! level fully include in the ice shelf boundary layer
108            ! sign - because fwf sign of evapo (rnf sign of precip)
109            DO jk = ikt, ikb - 1
110               pts(ji,jj,jk,jp_tem) = pts(ji,jj,jk,jp_tem) + ztc(ji,jj)
111            END DO
112            !
113            ! level partially include in ice shelf boundary layer
114            pts(ji,jj,ikb,jp_tem) = pts(ji,jj,ikb,jp_tem) + ztc(ji,jj) * pfrac(ji,jj)
115            !
116         END DO
117      END DO
118      !
119   END SUBROUTINE tra_isf_mlt
120   !
121   !SUBROUTINE tra_isf_cpl
122       !
123!      !----------------------------------------
124!      !        Ice Sheet coupling imbalance correction to have conservation
125!      !----------------------------------------
126!      !
127!      IF( ln_iscpl .AND. ln_iscpl_hsb) THEN         ! input of heat and salt due to river runoff
128!         DO jk = 1,jpk
129!            DO jj = 2, jpj
130!               DO ji = fs_2, fs_jpim1
131!                  zdep = 1._wp / e3t_n(ji,jj,jk)
132!                  tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) - htsc_iscpl(ji,jj,jk,jp_tem) * zdep
133!                  tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) - htsc_iscpl(ji,jj,jk,jp_sal) * zdep 
134!               END DO 
135!            END DO 
136!         END DO
137!      ENDIF
138!      !
139!   END SUBROUTINE tra_isf_cpl
140   !
141END MODULE traisf
Note: See TracBrowser for help on using the repository browser.