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 @ 8342

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

simplify the code

  • Property svn:keywords set to Id
File size: 7.2 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( 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      REAL(wp), INTENT(inout), DIMENSION(:,:) :: qnew          ! new enthlapies (J.m-3, remapped)
71
72      INTEGER  :: ji         !  dummy loop indices
73      INTEGER  :: jk0, jk1   !  old/new layer indices
74      !
75      REAL(wp), POINTER, DIMENSION(:,:) :: zeh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces
76      REAL(wp), POINTER, DIMENSION(:,:) :: zeh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces
77      REAL(wp), POINTER, DIMENSION(:)   :: zhnew               ! new layers thicknesses
78      !!-------------------------------------------------------------------
79
80      CALL wrk_alloc( jpij, nlay_i+3, zeh_cum0, zh_cum0, kjstart = 0 )
81      CALL wrk_alloc( jpij, nlay_i+1, zeh_cum1, zh_cum1, kjstart = 0 )
82      CALL wrk_alloc( jpij, zhnew )
83
84      !--------------------------------------------------------------------------
85      !  1) Cumulative integral of old enthalpy * thickness and layers interfaces
86      !--------------------------------------------------------------------------
87      zeh_cum0(:,0:nlay_i+2) = 0._wp 
88      zh_cum0 (:,0:nlay_i+2) = 0._wp
89      DO jk0 = 1, nlay_i+2
90         DO ji = 1, nidx
91            zeh_cum0(ji,jk0) = zeh_cum0(ji,jk0-1) + eh_i_old(ji,jk0-1)
92            zh_cum0 (ji,jk0) = zh_cum0 (ji,jk0-1) + h_i_old (ji,jk0-1)
93         ENDDO
94      ENDDO
95
96      !------------------------------------
97      !  2) Interpolation on the new layers
98      !------------------------------------
99      ! new layer thickesses
100      DO ji = 1, nidx
101         zhnew(ji) = SUM( h_i_old(ji,0:nlay_i+1) ) * r1_nlay_i 
102      ENDDO
103
104      ! new layers interfaces
105      zh_cum1(:,0:nlay_i) = 0._wp
106      DO jk1 = 1, nlay_i
107         DO ji = 1, nidx
108            zh_cum1(ji,jk1) = zh_cum1(ji,jk1-1) + zhnew(ji)
109         ENDDO
110      ENDDO
111
112      zeh_cum1(:,0:nlay_i) = 0._wp 
113      ! new cumulative q*h => linear interpolation
114      DO jk0 = 1, nlay_i+1
115         DO jk1 = 1, nlay_i-1
116            DO ji = 1, nidx
117               IF( zh_cum1(ji,jk1) <= zh_cum0(ji,jk0) .AND. zh_cum1(ji,jk1) > zh_cum0(ji,jk0-1) ) THEN
118                  zeh_cum1(ji,jk1) = ( zeh_cum0(ji,jk0-1) * ( zh_cum0(ji,jk0) - zh_cum1(ji,jk1  ) ) +  &
119                     &                 zeh_cum0(ji,jk0  ) * ( zh_cum1(ji,jk1) - zh_cum0(ji,jk0-1) ) )  &
120                     &             / ( zh_cum0(ji,jk0) - zh_cum0(ji,jk0-1) )
121               ENDIF
122            ENDDO
123         ENDDO
124      ENDDO
125      ! to ensure that total heat content is strictly conserved, set:
126      zeh_cum1(:,nlay_i) = zeh_cum0(:,nlay_i+2) 
127
128      ! new enthalpies
129      DO jk1 = 1, nlay_i
130         DO ji = 1, nidx
131            rswitch      = MAX( 0._wp , SIGN( 1._wp , zhnew(ji) - epsi20 ) ) 
132            qnew(ji,jk1) = rswitch * ( zeh_cum1(ji,jk1) - zeh_cum1(ji,jk1-1) ) / MAX( zhnew(ji), epsi20 )
133         ENDDO
134      ENDDO
135
136      ! --- diag error on heat remapping --- !
137      ! comment: if input h_i_old and eh_i_old are already multiplied by a_i (as in limthd_lac),
138      ! then we should not (* a_i) again but not important since this is just to check that remap error is ~0
139      DO ji = 1, nidx
140         hfx_err_rem_1d(ji) = hfx_err_rem_1d(ji) + a_i_1d(ji) * r1_rdtice *  &
141            &               ( SUM( qnew(ji,1:nlay_i) ) * zhnew(ji) - SUM( eh_i_old(ji,0:nlay_i+1) ) ) 
142      END DO
143     
144      !
145      CALL wrk_dealloc( jpij, nlay_i+3, zeh_cum0, zh_cum0, kjstart = 0 )
146      CALL wrk_dealloc( jpij, nlay_i+1, zeh_cum1, zh_cum1, kjstart = 0 )
147      CALL wrk_dealloc( jpij, zhnew )
148      !
149   END SUBROUTINE lim_thd_ent
150
151#else
152   !!----------------------------------------------------------------------
153   !!   Default option                               NO  LIM3 sea-ice model
154   !!----------------------------------------------------------------------
155CONTAINS
156   SUBROUTINE lim_thd_ent          ! Empty routine
157   END SUBROUTINE lim_thd_ent
158#endif
159
160   !!======================================================================
161END MODULE limthd_ent
Note: See TracBrowser for help on using the repository browser.