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

source: NEMO/trunk/src/OCE/ISF/isfdiags.F90 @ 13286

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

trunk: Mid-year merge, merge back KERNEL-06_techene_e3

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#  include "domzgr_substitute.h90"
29   !!----------------------------------------------------------------------
30   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
31   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
32   !! Software governed by the CeCILL license (see ./LICENSE)
33   !!----------------------------------------------------------------------
34
35CONTAINS
36
37   SUBROUTINE isf_diags_flx(Kmm, ktop, kbot, phtbl, pfrac, cdisf, pqfwf, pqoce, pqlat, pqhc)
38      !!---------------------------------------------------------------------
39      !!                  ***  ROUTINE isf_diags_flx ***
40      !!
41      !! ** Purpose : manage the 2d and 3d flux outputs of the ice shelf module
42      !!              fwf, latent heat flux, heat content flux, oce->ice heat flux
43      !!
44      !!----------------------------------------------------------------------
45      !!-------------------------- OUT -------------------------------------
46      !!-------------------------- IN  -------------------------------------
47      INTEGER,                      INTENT(in) :: Kmm                       ! ocean time level index
48      INTEGER , DIMENSION(jpi,jpj), INTENT(in) :: ktop , kbot               ! top and bottom level of the tbl
49      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: phtbl, pfrac              ! thickness of the tbl and fraction of last cell affected by the tbl
50      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pqfwf, pqoce, pqlat, pqhc ! 2d var to map in 3d
51      CHARACTER(LEN=3), INTENT(in) :: cdisf                                 ! parametrisation or interactive melt
52      !!---------------------------------------------------------------------
53      CHARACTER(LEN=256) :: cvarqfwf  , cvarqoce  , cvarqlat  , cvarqhc
54      CHARACTER(LEN=256) :: cvarqfwf3d, cvarqoce3d, cvarqlat3d, cvarqhc3d
55      !!---------------------------------------------------------------------
56      !
57      ! output melt
58      cvarqfwf = 'fwfisf_'//cdisf  ; cvarqfwf3d = 'fwfisf3d_'//cdisf
59      cvarqoce = 'qoceisf_'//cdisf ; cvarqoce3d = 'qoceisf3d_'//cdisf
60      cvarqlat = 'qlatisf_'//cdisf ; cvarqlat3d = 'qlatisf3d_'//cdisf 
61      cvarqhc  = 'qhcisf_'//cdisf  ; cvarqhc3d  = 'qhcisf3d_'//cdisf
62      !
63      ! output 2d melt rate, latent heat and heat content flux from the injected water
64      CALL iom_put( TRIM(cvarqfwf), pqfwf(:,:) )   ! mass         flux ( >0 out )
65      CALL iom_put( TRIM(cvarqoce), pqoce(:,:) )   ! oce to ice   flux ( >0 out )
66      CALL iom_put( TRIM(cvarqlat), pqlat(:,:) )   ! latent heat  flux ( >0 out )
67      CALL iom_put( TRIM(cvarqhc) , pqhc (:,:) )   ! heat content flux ( >0 out )
68      !
69      ! output 3d Diagnostics
70      IF ( iom_use( TRIM(cvarqfwf3d) ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqfwf3d) , pqfwf(:,:))
71      IF ( iom_use( TRIM(cvarqoce3d) ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqoce3d) , pqoce(:,:))
72      IF ( iom_use( TRIM(cvarqlat3d) ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqlat3d) , pqoce(:,:))
73      IF ( iom_use( TRIM(cvarqhc3d)  ) ) CALL isf_diags_2dto3d( Kmm, ktop, kbot, phtbl, pfrac, TRIM(cvarqhc3d)  , pqhc (:,:))
74      !
75   END SUBROUTINE
76
77   SUBROUTINE isf_diags_2dto3d(Kmm, ktop, kbot, phtbl, pfrac, cdvar, pvar2d)
78      !!---------------------------------------------------------------------
79      !!                  ***  ROUTINE isf_diags_2dto3d ***
80      !!
81      !! ** Purpose : compute the 3d flux outputs as they are injected into NEMO
82      !!              (ie uniformaly spread into the top boundary layer or parametrisation layer)
83      !!
84      !!----------------------------------------------------------------------
85      !!-------------------------- OUT -------------------------------------
86      !!-------------------------- IN  -------------------------------------
87      INTEGER,                      INTENT(in) :: Kmm           ! ocean time level index
88      INTEGER , DIMENSION(jpi,jpj), INTENT(in) :: ktop , kbot   ! top and bottom level of the tbl
89      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: phtbl, pfrac  ! thickness of the tbl and fraction of last cell affected by the tbl
90      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: pvar2d        ! 2d var to map in 3d
91      CHARACTER(LEN=*), INTENT(in) :: cdvar
92      !!---------------------------------------------------------------------
93      INTEGER  :: ji, jj, jk                       ! loop indices
94      INTEGER  :: ikt, ikb                         ! top and bottom level of the tbl
95      REAL(wp), DIMENSION(jpi,jpj)     :: zvar2d   !
96      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zvar3d   ! 3d var to output
97      !!---------------------------------------------------------------------
98      !
99      ! compute 3d output
100      zvar2d(:,:) = pvar2d(:,:) / phtbl(:,:)
101      zvar3d(:,:,:) = 0._wp
102      !
103      DO_2D_11_11
104         ikt = ktop(ji,jj)
105         ikb = kbot(ji,jj)
106         DO jk = ikt, ikb - 1
107            zvar3d(ji,jj,jk) = zvar2d(ji,jj) * e3t(ji,jj,jk,Kmm)
108         END DO
109         zvar3d(ji,jj,ikb) = zvar2d(ji,jj) * e3t(ji,jj,ikb,Kmm) * pfrac(ji,jj)
110      END_2D
111      !
112      CALL iom_put( TRIM(cdvar) , zvar3d(:,:,:))
113      !
114   END SUBROUTINE isf_diags_2dto3d
115
116END MODULE isfdiags
Note: See TracBrowser for help on using the repository browser.