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.
limcat_1D.F90 in branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_3/limcat_1D.F90 @ 5051

Last change on this file since 5051 was 5051, checked in by clem, 9 years ago

LIM3 initialization is now called at the same time as other sbc fields

File size: 8.1 KB
Line 
1MODULE limcat_1D
2   !!======================================================================
3   !!                     ***  MODULE  limcat_1D  ***
4   !!  Used for LIM3 to convert cell averages of ice thickness, snow thickness
5   !!  and ice cover into a prescribed distribution over the cell.
6   !!  (Example of application: BDY forcings when input are cell averaged) 
7   !!======================================================================
8   !! History :   -   ! Original code from M. Vancoppenolle (?)
9   !!                 ! 2011-12 (C. Rousset) rewritten for clarity
10   !!----------------------------------------------------------------------
11#if defined key_lim3
12   !!----------------------------------------------------------------------
13   !!   'key_lim3' :                                    LIM3 sea-ice model
14   !!----------------------------------------------------------------------
15   !!   lim_cat_1D      :  main subroutine
16   !!----------------------------------------------------------------------
17   !! Modules used
18   USE phycst
19   USE oce             ! dynamics and tracers variables
20   USE dom_oce
21   USE sbc_oce         ! Surface boundary condition: ocean fields
22   USE par_ice         ! ice parameters
23   USE ice             ! ice variables
24   USE eosbn2          ! equation of state
25   USE in_out_manager
26   USE dom_ice
27   USE ice
28   USE lbclnk
29   USE timing          ! Timing
30   USE wrk_nemo
31
32   IMPLICIT NONE
33   PRIVATE
34
35   !! Accessibility
36   PUBLIC lim_cat_1D     
37
38CONTAINS
39
40   SUBROUTINE lim_cat_1D( zhti, zhts, zai, zht_i, zht_s, za_i )
41      !! Local variables
42      INTEGER  :: ji, jk, jl             ! dummy loop indices
43      INTEGER  :: ijpij, i_fill, jl0 
44      REAL(wp) :: zarg, zV, zconv, zdh
45      REAL(wp), DIMENSION(:),   INTENT(in)    ::   zhti, zhts, zai    ! input ice/snow variables
46      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   zht_i, zht_s, za_i ! output ice/snow variables
47      INTEGER , POINTER, DIMENSION(:)         ::   itest
48 
49      IF( nn_timing == 1 )  CALL timing_start('limcat_1D')
50
51      CALL wrk_alloc( 4, itest )
52      !--------------------------------------------------------------------
53      ! initialisation of variables
54      !--------------------------------------------------------------------
55      ijpij = SIZE(zhti,1)
56      zht_i(1:ijpij,1:jpl) = 0._wp
57      zht_s(1:ijpij,1:jpl) = 0._wp
58      za_i (1:ijpij,1:jpl) = 0._wp
59
60      !------------------------------------------------------------------------------------
61      ! Distribute ice concentration and thickness into the categories
62      !------------------------------------------------------------------------------------
63      ! Method: we first try to fill the jpl ice categories bounded by thicknesses
64      !         hmax(0:jpl) with a gaussian distribution, and check whether the distribution
65      !         fulfills volume and area conservation, positivity and ice categories bounds.
66      !         In other words, if ice input is too thin, the last category (jpl)
67      !         cannot be filled, so we try to fill jpl-1 categories...
68      !         And so forth iteratively until the number of categories filled
69      !         fulfills ice volume concervation between input and output (itest=4)
70      !--------------------------------------------------------------------------------------
71
72      ! ----------------------------------------
73      ! distribution over the jpl ice categories
74      ! ----------------------------------------
75      DO ji = 1, ijpij
76         
77         IF( zhti(ji) > 0._wp ) THEN
78
79         ! initialisation of tests
80         itest(:)  = 0
81         
82         i_fill = jpl + 1                                             !====================================
83         DO WHILE ( ( SUM( itest(:) ) /= 4 ) .AND. ( i_fill >= 2 ) )  ! iterative loop on i_fill categories 
84            ! iteration                                               !====================================
85            i_fill = i_fill - 1
86           
87            ! initialisation of ice variables for each try
88            zht_i(ji,1:jpl) = 0._wp
89            za_i (ji,1:jpl) = 0._wp
90           
91            ! *** case very thin ice: fill only category 1
92            IF ( i_fill == 1 ) THEN
93               zht_i(ji,1) = zhti(ji)
94               za_i (ji,1) = zai (ji)
95
96            ! *** case ice is thicker: fill categories >1
97            ELSE
98
99               ! Fill ice thicknesses except the last one (i_fill) by hmean
100               DO jl = 1, i_fill - 1
101                  zht_i(ji,jl) = hi_mean(jl)
102               END DO
103               
104               ! find which category (jl0) the input ice thickness falls into
105               jl0 = i_fill
106               DO jl = 1, i_fill
107                  IF ( ( zhti(ji) >= hi_max(jl-1) ) .AND. ( zhti(ji) < hi_max(jl) ) ) THEN
108                     jl0 = jl
109           CYCLE
110                  ENDIF
111               END DO
112               
113               ! Concentrations in the (i_fill-1) categories
114               za_i(ji,jl0) = zai(ji) / SQRT(REAL(jpl))
115               DO jl = 1, i_fill - 1
116                  IF ( jl == jl0 ) CYCLE
117                  zarg        = ( zht_i(ji,jl) - zhti(ji) ) / ( zhti(ji) * 0.5_wp )
118                  za_i(ji,jl) =   za_i (ji,jl0) * EXP(-zarg**2)
119               END DO
120               
121               ! Concentration in the last (i_fill) category
122               za_i(ji,i_fill) = zai(ji) - SUM( za_i(ji,1:i_fill-1) )
123               
124               ! Ice thickness in the last (i_fill) category
125               zV = SUM( za_i(ji,1:i_fill-1) * zht_i(ji,1:i_fill-1) )
126               zht_i(ji,i_fill) = ( zhti(ji) * zai(ji) - zV ) / za_i(ji,i_fill) 
127               
128            ENDIF ! case ice is thick or thin
129           
130            !---------------------
131            ! Compatibility tests
132            !---------------------
133            ! Test 1: area conservation
134            zconv = ABS( zai(ji) - SUM( za_i(ji,1:jpl) ) )
135            IF ( zconv < epsi06 ) itest(1) = 1
136           
137            ! Test 2: volume conservation
138            zconv = ABS( zhti(ji)*zai(ji) - SUM( za_i(ji,1:jpl)*zht_i(ji,1:jpl) ) )
139            IF ( zconv < epsi06 ) itest(2) = 1
140           
141            ! Test 3: thickness of the last category is in-bounds ?
142            IF ( zht_i(ji,i_fill) >= hi_max(i_fill-1) ) itest(3) = 1
143           
144            ! Test 4: positivity of ice concentrations
145            itest(4) = 1
146            DO jl = 1, i_fill
147               IF ( za_i(ji,jl) < 0._wp ) itest(4) = 0
148            END DO           
149                                                           !============================
150         END DO                                            ! end iteration on categories
151                                                           !============================
152         ENDIF ! if zhti > 0
153      END DO ! i loop
154
155      ! ------------------------------------------------
156      ! Adding Snow in each category where za_i is not 0
157      ! ------------------------------------------------
158      DO jl = 1, jpl
159         DO ji = 1, ijpij
160            IF( za_i(ji,jl) > 0._wp ) THEN
161               zht_s(ji,jl) = zht_i(ji,jl) * ( zhts(ji) / zhti(ji) )
162               ! In case snow load is in excess that would lead to transformation from snow to ice
163               ! Then, transfer the snow excess into the ice (different from limthd_dh)
164               zdh = MAX( 0._wp, ( rhosn * zht_s(ji,jl) + ( rhoic - rau0 ) * zht_i(ji,jl) ) * r1_rau0 ) 
165               ! recompute ht_i, ht_s avoiding out of bounds values
166               zht_i(ji,jl) = MIN( hi_max(jl), zht_i(ji,jl) + zdh )
167               zht_s(ji,jl) = MAX( 0._wp, zht_s(ji,jl) - zdh * rhoic / rhosn )
168            ENDIF
169         ENDDO
170      ENDDO
171
172      CALL wrk_dealloc( 4, itest )
173      !
174      IF( nn_timing == 1 )  CALL timing_stop('limcat_1D')
175     
176    END SUBROUTINE lim_cat_1D
177   
178#else
179   !!----------------------------------------------------------------------
180   !!   Default option :         Empty module          NO LIM sea-ice model
181   !!----------------------------------------------------------------------
182CONTAINS
183   SUBROUTINE lim_cat_1D          ! Empty routine
184   END SUBROUTINE lim_cat_1D
185#endif
186
187   !!======================================================================
188END MODULE limcat_1D
Note: See TracBrowser for help on using the repository browser.