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.
isfdiags.F90 in NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ISF – NEMO

source: NEMO/branches/2020/dev_r12558_HPC-08_epico_Extra_Halo/src/OCE/ISF/isfdiags.F90 @ 12939

Last change on this file since 12939 was 12939, checked in by smasson, 4 years ago

Extra_Halo: update with trunk@12933, see #2366

File size: 6.1 KB
Line 
1MODULE isfdiags
2   !!======================================================================
3   !!                       ***  MODULE  isfdiags  ***
4   !! ice shelf diagnostics module :  manage the 2d and 3d flux outputs from the ice shelf module
5   !!======================================================================
6   !! History :  3.2  !  2011-02  (C.Harris  ) Original code isf cav
7   !!            X.X  !  2006-02  (C. Wang   ) Original code bg03
8   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   sbc_isf       : update sbc under ice shelf
13   !!----------------------------------------------------------------------
14
15   USE in_out_manager ! I/O manager
16   USE dom_oce
17   USE isf_oce        ! ice shelf variable
18   USE iom            !
19
20   IMPLICIT NONE
21
22   PRIVATE
23
24   PUBLIC   isf_diags_flx
25
26   !! * Substitutions
27#  include "do_loop_substitute.h90"
28   !!----------------------------------------------------------------------
29   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
30   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
31   !! Software governed by the CeCILL license (see ./LICENSE)
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE isf_diags_flx(Kmm, ktop, kbot, phtbl, pfrac, cdisf, pqfwf, pqoce, pqlat, pqhc)
37      !!---------------------------------------------------------------------
38      !!                  ***  ROUTINE isf_diags_flx ***
39      !!
40      !! ** Purpose : manage the 2d and 3d flux outputs of the ice shelf module
41      !!              fwf, latent heat flux, heat content flux, oce->ice heat flux
42      !!
43      !!----------------------------------------------------------------------
44      !!-------------------------- OUT -------------------------------------
45      !!-------------------------- IN  -------------------------------------
46      INTEGER,                      INTENT(in) :: Kmm                       ! ocean time level index
47      INTEGER , DIMENSION(jpi,jpj), INTENT(in) :: ktop , kbot               ! top and bottom level of the tbl
48      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: phtbl, pfrac              ! thickness of the tbl and fraction of last cell affected by the tbl
49      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pqfwf, pqoce, pqlat, pqhc ! 2d var to map in 3d
50      CHARACTER(LEN=3), INTENT(in) :: cdisf                                 ! parametrisation or interactive melt
51      !!---------------------------------------------------------------------
52      CHARACTER(LEN=256) :: cvarqfwf  , cvarqoce  , cvarqlat  , cvarqhc
53      CHARACTER(LEN=256) :: cvarqfwf3d, cvarqoce3d, cvarqlat3d, cvarqhc3d
54      !!---------------------------------------------------------------------
55      !
56      ! output melt
57      cvarqfwf = 'fwfisf_'//cdisf  ; cvarqfwf3d = 'fwfisf3d_'//cdisf
58      cvarqoce = 'qoceisf_'//cdisf ; cvarqoce3d = 'qoceisf3d_'//cdisf
59      cvarqlat = 'qlatisf_'//cdisf ; cvarqlat3d = 'qlatisf3d_'//cdisf 
60      cvarqhc  = 'qhcisf_'//cdisf  ; cvarqhc3d  = 'qhcisf3d_'//cdisf
61      !
62      ! output 2d melt rate, latent heat and heat content flux from the injected water
63      CALL iom_put( TRIM(cvarqfwf), pqfwf(:,:) )   ! mass         flux ( >0 out )
64      CALL iom_put( TRIM(cvarqoce), pqoce(:,:) )   ! oce to ice   flux ( >0 out )
65      CALL iom_put( TRIM(cvarqlat), pqlat(:,:) )   ! latent heat  flux ( >0 out )
66      CALL iom_put( TRIM(cvarqhc) , pqhc (:,:) )   ! heat content flux ( >0 out )
67      !
68      ! output 3d Diagnostics
69      IF ( iom_use( TRIM(cvarqfwf3d) ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqfwf3d) , pqfwf(:,:))
70      IF ( iom_use( TRIM(cvarqoce3d) ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqoce3d) , pqoce(:,:))
71      IF ( iom_use( TRIM(cvarqlat3d) ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqlat3d) , pqoce(:,:))
72      IF ( iom_use( TRIM(cvarqhc3d)  ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqhc3d)  , pqhc (:,:))
73      !
74   END SUBROUTINE
75
76   SUBROUTINE isf_diags_2dto3d(Kmm, ktop, kbot, phtbl, pfrac, cdvar, pvar2d)
77      !!---------------------------------------------------------------------
78      !!                  ***  ROUTINE isf_diags_2dto3d ***
79      !!
80      !! ** Purpose : compute the 3d flux outputs as they are injected into NEMO
81      !!              (ie uniformaly spread into the top boundary layer or parametrisation layer)
82      !!
83      !!----------------------------------------------------------------------
84      !!-------------------------- OUT -------------------------------------
85      !!-------------------------- IN  -------------------------------------
86      INTEGER,                      INTENT(in) :: Kmm           ! ocean time level index
87      INTEGER , DIMENSION(jpi,jpj), INTENT(in) :: ktop , kbot   ! top and bottom level of the tbl
88      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: phtbl, pfrac  ! thickness of the tbl and fraction of last cell affected by the tbl
89      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pvar2d        ! 2d var to map in 3d
90      CHARACTER(LEN=*), INTENT(in) :: cdvar
91      !!---------------------------------------------------------------------
92      INTEGER  :: ji, jj, jk                       ! loop indices
93      INTEGER  :: ikt, ikb                         ! top and bottom level of the tbl
94      REAL(wp), DIMENSION(jpi,jpj)     :: zvar2d   !
95      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvar3d   ! 3d var to output
96      !!---------------------------------------------------------------------
97      !
98      ! compute 3d output
99      zvar2d(:,:) = pvar2d(:,:) / phtbl(:,:)
100      zvar3d(:,:,:) = 0._wp
101      !
102      DO_2D_11_11
103         ikt = ktop(ji,jj)
104         ikb = kbot(ji,jj)
105         DO jk = ikt, ikb - 1
106            zvar3d(ji,jj,jk) = zvar2d(ji,jj) * e3t(ji,jj,jk,Kmm)
107         END DO
108         zvar3d(ji,jj,ikb) = zvar2d(ji,jj) * e3t(ji,jj,ikb,Kmm) * pfrac(ji,jj)
109      END_2D
110      !
111      CALL iom_put( TRIM(cdvar) , zvar3d(:,:,:))
112      !
113   END SUBROUTINE isf_diags_2dto3d
114
115END MODULE isfdiags
Note: See TracBrowser for help on using the repository browser.