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/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2014/dev_r4650_UKMO2_ice_shelves/NEMOGCM/NEMO/LIM_SRC_3/limthd_ent.F90 @ 4924

Last change on this file since 4924 was 4924, checked in by mathiot, 9 years ago

UKM02_ice_shelves merged and SETTE tested with revision 4879 of trunk

  • Property svn:keywords set to Id
File size: 7.5 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 sbc_oce        ! Surface boundary condition: ocean fields
26   USE ice            ! LIM variables
27   USE par_ice        ! LIM parameters
28   USE thd_ice        ! LIM thermodynamics
29   USE limvar         ! LIM variables
30   USE in_out_manager ! I/O manager
31   USE lib_mpp        ! MPP library
32   USE wrk_nemo       ! work arrays
33   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
34
35   IMPLICIT NONE
36   PRIVATE
37
38   PUBLIC   lim_thd_ent         ! called by limthd and limthd_lac
39
40   REAL(wp) :: epsi20 = 1.e-20   ! constant values
41   REAL(wp) :: epsi10 = 1.e-10   ! constant values
42
43   !!----------------------------------------------------------------------
44   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
45   !! $Id$
46   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48CONTAINS
49 
50   SUBROUTINE lim_thd_ent( kideb, kiut, qnew )
51      !!-------------------------------------------------------------------
52      !!               ***   ROUTINE lim_thd_ent  ***
53      !!
54      !! ** Purpose :
55      !!           This routine computes new vertical grids in the ice,
56      !!           and consistently redistributes temperatures.
57      !!           Redistribution is made so as to ensure to energy conservation
58      !!
59      !!
60      !! ** Method  : linear conservative remapping
61      !!           
62      !! ** Steps : 1) cumulative integrals of old enthalpies/thicknesses
63      !!            2) linear remapping on the new layers
64      !!
65      !! ------------ cum0(0)                        ------------- cum1(0)
66      !!                                    NEW      -------------
67      !! ------------ cum0(1)               ==>      -------------
68      !!     ...                                     -------------
69      !! ------------                                -------------
70      !! ------------ cum0(nlay_i+2)                 ------------- cum1(nlay_i)
71      !!
72      !!
73      !! References : Bitz & Lipscomb, JGR 99; Vancoppenolle et al., GRL, 2005
74      !!-------------------------------------------------------------------
75      INTEGER , INTENT(in) ::   kideb, kiut   ! Start/End point on which the  the computation is applied
76
77      REAL(wp), INTENT(inout), DIMENSION(:,:) :: qnew          ! new enthlapies (J.m-3, remapped)
78
79      INTEGER  :: ji         !  dummy loop indices
80      INTEGER  :: jk0, jk1   !  old/new layer indices
81      REAL(wp) :: zswitch
82      !
83      REAL(wp), POINTER, DIMENSION(:,:) :: zqh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces
84      REAL(wp), POINTER, DIMENSION(:,:) :: zqh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces
85      REAL(wp), POINTER, DIMENSION(:)   :: zhnew               ! new layers thicknesses
86      !!-------------------------------------------------------------------
87
88      CALL wrk_alloc( jpij, nlay_i+3, zqh_cum0, zh_cum0, kjstart = 0 )
89      CALL wrk_alloc( jpij, nlay_i+1, zqh_cum1, zh_cum1, kjstart = 0 )
90      CALL wrk_alloc( jpij, zhnew )
91
92      !--------------------------------------------------------------------------
93      !  1) Cumulative integral of old enthalpy * thicnkess and layers interfaces
94      !--------------------------------------------------------------------------
95      zqh_cum0(:,0:nlay_i+2) = 0._wp 
96      zh_cum0 (:,0:nlay_i+2) = 0._wp
97      DO jk0 = 1, nlay_i+2
98         DO ji = kideb, kiut
99            zqh_cum0(ji,jk0) = zqh_cum0(ji,jk0-1) + qh_i_old(ji,jk0-1)
100            zh_cum0 (ji,jk0) = zh_cum0 (ji,jk0-1) + h_i_old (ji,jk0-1)
101         ENDDO
102      ENDDO
103
104      !------------------------------------
105      !  2) Interpolation on the new layers
106      !------------------------------------
107      ! new layer thickesses
108      DO ji = kideb, kiut
109         zhnew(ji) = SUM( h_i_old(ji,0:nlay_i+1) ) / REAL( nlay_i ) 
110      ENDDO
111
112      ! new layers interfaces
113      zh_cum1(:,0:nlay_i) = 0._wp
114      DO jk1 = 1, nlay_i
115         DO ji = kideb, kiut
116            zh_cum1(ji,jk1) = zh_cum1(ji,jk1-1) + zhnew(ji)
117         ENDDO
118      ENDDO
119
120      zqh_cum1(:,0:nlay_i) = 0._wp 
121      ! new cumulative q*h => linear interpolation
122      DO jk0 = 1, nlay_i+1
123         DO jk1 = 1, nlay_i-1
124            DO ji = kideb, kiut
125               IF( zh_cum1(ji,jk1) <= zh_cum0(ji,jk0) .AND. zh_cum1(ji,jk1) > zh_cum0(ji,jk0-1) ) THEN
126                  zqh_cum1(ji,jk1) = ( zqh_cum0(ji,jk0-1) * ( zh_cum0(ji,jk0) - zh_cum1(ji,jk1  ) ) +  &
127                     &                 zqh_cum0(ji,jk0  ) * ( zh_cum1(ji,jk1) - zh_cum0(ji,jk0-1) ) )  &
128                     &             / ( zh_cum0(ji,jk0) - zh_cum0(ji,jk0-1) )
129               ENDIF
130            ENDDO
131         ENDDO
132      ENDDO
133      ! to ensure that total heat content is strictly conserved, set:
134      zqh_cum1(:,nlay_i) = zqh_cum0(:,nlay_i+2) 
135
136      ! new enthalpies
137      DO jk1 = 1, nlay_i
138         DO ji = kideb, kiut
139            zswitch      = 1._wp - MAX( 0._wp , SIGN( 1._wp , - zhnew(ji) + epsi10 ) ) 
140            qnew(ji,jk1) = zswitch * ( zqh_cum1(ji,jk1) - zqh_cum1(ji,jk1-1) ) / MAX( zhnew(ji), epsi10 )
141         ENDDO
142      ENDDO
143
144      ! --- diag error on heat remapping --- !
145      ! comment: if input h_i_old and qh_i_old are already multiplied by a_i (as in limthd_lac),
146      ! then we should not (* a_i) again but not important since this is just to check that remap error is ~0
147      DO ji = kideb, kiut
148         hfx_err_rem_1d(ji) = hfx_err_rem_1d(ji) + a_i_1d(ji) * r1_rdtice *  &
149            &               ( SUM( qnew(ji,1:nlay_i) ) * zhnew(ji) - SUM( qh_i_old(ji,0:nlay_i+1) ) ) 
150      END DO
151     
152      !
153      CALL wrk_dealloc( jpij, nlay_i+3, zqh_cum0, zh_cum0, kjstart = 0 )
154      CALL wrk_dealloc( jpij, nlay_i+1, zqh_cum1, zh_cum1, kjstart = 0 )
155      CALL wrk_dealloc( jpij, zhnew )
156      !
157   END SUBROUTINE lim_thd_ent
158
159#else
160   !!----------------------------------------------------------------------
161   !!   Default option                               NO  LIM3 sea-ice model
162   !!----------------------------------------------------------------------
163CONTAINS
164   SUBROUTINE lim_thd_ent          ! Empty routine
165   END SUBROUTINE lim_thd_ent
166#endif
167
168   !!======================================================================
169END MODULE limthd_ent
Note: See TracBrowser for help on using the repository browser.