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/UKMO/NEMO_4.0.2_GO8_package_ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.2_GO8_package_ENHANCE-02_ISF_nemo/src/OCE/ISF/isfdiags.F90 @ 12767

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

NEMO_4.0.2_GO8_package_ENHANCE-02_ISF_nemo: change to be able to run WED025

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