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.
limthd_ent.F90 in branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/limthd_ent.F90 @ 8326

Last change on this file since 8326 was 8325, checked in by clem, 7 years ago

STEP4 (1): put all thermodynamics in 1D

  • Property svn:keywords set to Id
File size: 7.3 KB
Line 
1MODULE limthd_ent
2   !!======================================================================
3   !!                       ***  MODULE limthd_ent   ***
4   !!                  Redistribution of Enthalpy in the ice
5   !!                        on the new vertical grid
6   !!                       after vertical growth/decay
7   !!======================================================================
8   !! History :  LIM  ! 2003-05 (M. Vancoppenolle) Original code in 1D
9   !!                 ! 2005-07 (M. Vancoppenolle) 3D version
10   !!                 ! 2006-11 (X. Fettweis) Vectorized
11   !!            3.0  ! 2008-03 (M. Vancoppenolle) Energy conservation and clean code
12   !!            3.4  ! 2011-02 (G. Madec) dynamical allocation
13   !!             -   ! 2014-05 (C. Rousset) complete rewriting
14   !!----------------------------------------------------------------------
15#if defined key_lim3
16   !!----------------------------------------------------------------------
17   !!   'key_lim3'                                      LIM3 sea-ice model
18   !!----------------------------------------------------------------------
19   !!   lim_thd_ent   : ice redistribution of enthalpy
20   !!----------------------------------------------------------------------
21   USE par_oce        ! ocean parameters
22   USE dom_oce        ! domain variables
23   USE domain         !
24   USE phycst         ! physical constants
25   USE ice            ! LIM variables
26   USE thd_ice        ! LIM thermodynamics
27   USE limvar         ! LIM variables
28   USE in_out_manager ! I/O manager
29   USE lib_mpp        ! MPP library
30   USE wrk_nemo       ! work arrays
31   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   lim_thd_ent         ! called by limthd and limthd_lac
37
38   !!----------------------------------------------------------------------
39   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
40   !! $Id$
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44 
45   SUBROUTINE lim_thd_ent( kideb, kiut, qnew )
46      !!-------------------------------------------------------------------
47      !!               ***   ROUTINE lim_thd_ent  ***
48      !!
49      !! ** Purpose :
50      !!           This routine computes new vertical grids in the ice,
51      !!           and consistently redistributes temperatures.
52      !!           Redistribution is made so as to ensure to energy conservation
53      !!
54      !!
55      !! ** Method  : linear conservative remapping
56      !!           
57      !! ** Steps : 1) cumulative integrals of old enthalpies/thicknesses
58      !!            2) linear remapping on the new layers
59      !!
60      !! ------------ cum0(0)                        ------------- cum1(0)
61      !!                                    NEW      -------------
62      !! ------------ cum0(1)               ==>      -------------
63      !!     ...                                     -------------
64      !! ------------                                -------------
65      !! ------------ cum0(nlay_i+2)                 ------------- cum1(nlay_i)
66      !!
67      !!
68      !! References : Bitz & Lipscomb, JGR 99; Vancoppenolle et al., GRL, 2005
69      !!-------------------------------------------------------------------
70      INTEGER , INTENT(in) ::   kideb, kiut   ! Start/End point on which the  the computation is applied
71
72      REAL(wp), INTENT(inout), DIMENSION(:,:) :: qnew          ! new enthlapies (J.m-3, remapped)
73
74      INTEGER  :: ji         !  dummy loop indices
75      INTEGER  :: jk0, jk1   !  old/new layer indices
76      !
77      REAL(wp), POINTER, DIMENSION(:,:) :: zeh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces
78      REAL(wp), POINTER, DIMENSION(:,:) :: zeh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces
79      REAL(wp), POINTER, DIMENSION(:)   :: zhnew               ! new layers thicknesses
80      !!-------------------------------------------------------------------
81
82      CALL wrk_alloc( jpij, nlay_i+3, zeh_cum0, zh_cum0, kjstart = 0 )
83      CALL wrk_alloc( jpij, nlay_i+1, zeh_cum1, zh_cum1, kjstart = 0 )
84      CALL wrk_alloc( jpij, zhnew )
85
86      !--------------------------------------------------------------------------
87      !  1) Cumulative integral of old enthalpy * thickness and layers interfaces
88      !--------------------------------------------------------------------------
89      zeh_cum0(:,0:nlay_i+2) = 0._wp 
90      zh_cum0 (:,0:nlay_i+2) = 0._wp
91      DO jk0 = 1, nlay_i+2
92         DO ji = kideb, kiut
93            zeh_cum0(ji,jk0) = zeh_cum0(ji,jk0-1) + eh_i_old(ji,jk0-1)
94            zh_cum0 (ji,jk0) = zh_cum0 (ji,jk0-1) + h_i_old (ji,jk0-1)
95         ENDDO
96      ENDDO
97
98      !------------------------------------
99      !  2) Interpolation on the new layers
100      !------------------------------------
101      ! new layer thickesses
102      DO ji = kideb, kiut
103         zhnew(ji) = SUM( h_i_old(ji,0:nlay_i+1) ) * r1_nlay_i 
104      ENDDO
105
106      ! new layers interfaces
107      zh_cum1(:,0:nlay_i) = 0._wp
108      DO jk1 = 1, nlay_i
109         DO ji = kideb, kiut
110            zh_cum1(ji,jk1) = zh_cum1(ji,jk1-1) + zhnew(ji)
111         ENDDO
112      ENDDO
113
114      zeh_cum1(:,0:nlay_i) = 0._wp 
115      ! new cumulative q*h => linear interpolation
116      DO jk0 = 1, nlay_i+1
117         DO jk1 = 1, nlay_i-1
118            DO ji = kideb, kiut
119               IF( zh_cum1(ji,jk1) <= zh_cum0(ji,jk0) .AND. zh_cum1(ji,jk1) > zh_cum0(ji,jk0-1) ) THEN
120                  zeh_cum1(ji,jk1) = ( zeh_cum0(ji,jk0-1) * ( zh_cum0(ji,jk0) - zh_cum1(ji,jk1  ) ) +  &
121                     &                 zeh_cum0(ji,jk0  ) * ( zh_cum1(ji,jk1) - zh_cum0(ji,jk0-1) ) )  &
122                     &             / ( zh_cum0(ji,jk0) - zh_cum0(ji,jk0-1) )
123               ENDIF
124            ENDDO
125         ENDDO
126      ENDDO
127      ! to ensure that total heat content is strictly conserved, set:
128      zeh_cum1(:,nlay_i) = zeh_cum0(:,nlay_i+2) 
129
130      ! new enthalpies
131      DO jk1 = 1, nlay_i
132         DO ji = kideb, kiut
133            rswitch      = MAX( 0._wp , SIGN( 1._wp , zhnew(ji) - epsi20 ) ) 
134            qnew(ji,jk1) = rswitch * ( zeh_cum1(ji,jk1) - zeh_cum1(ji,jk1-1) ) / MAX( zhnew(ji), epsi20 )
135         ENDDO
136      ENDDO
137
138      ! --- diag error on heat remapping --- !
139      ! comment: if input h_i_old and eh_i_old are already multiplied by a_i (as in limthd_lac),
140      ! then we should not (* a_i) again but not important since this is just to check that remap error is ~0
141      DO ji = kideb, kiut
142         hfx_err_rem_1d(ji) = hfx_err_rem_1d(ji) + a_i_1d(ji) * r1_rdtice *  &
143            &               ( SUM( qnew(ji,1:nlay_i) ) * zhnew(ji) - SUM( eh_i_old(ji,0:nlay_i+1) ) ) 
144      END DO
145     
146      !
147      CALL wrk_dealloc( jpij, nlay_i+3, zeh_cum0, zh_cum0, kjstart = 0 )
148      CALL wrk_dealloc( jpij, nlay_i+1, zeh_cum1, zh_cum1, kjstart = 0 )
149      CALL wrk_dealloc( jpij, zhnew )
150      !
151   END SUBROUTINE lim_thd_ent
152
153#else
154   !!----------------------------------------------------------------------
155   !!   Default option                               NO  LIM3 sea-ice model
156   !!----------------------------------------------------------------------
157CONTAINS
158   SUBROUTINE lim_thd_ent          ! Empty routine
159   END SUBROUTINE lim_thd_ent
160#endif
161
162   !!======================================================================
163END MODULE limthd_ent
Note: See TracBrowser for help on using the repository browser.