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

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/iceadv.F90 @ 8506

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

changes in style - part5 - start changing init routines

File size: 10.1 KB
Line 
1MODULE iceadv
2   !!======================================================================
3   !!                       ***  MODULE iceadv   ***
4   !! LIM transport ice model : sea-ice advection/diffusion
5   !!======================================================================
6   !! History : LIM-2 ! 2000-01 (M.A. Morales Maqueda, H. Goosse, and T. Fichefet)  Original code
7   !!            3.0  ! 2005-11 (M. Vancoppenolle)   Multi-layer sea ice, salinity variations
8   !!            4.0  ! 2011-02 (G. Madec) dynamical allocation
9   !!----------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3'                                       LIM3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   ice_adv       : advection/diffusion process of sea ice
15   !!----------------------------------------------------------------------
16   USE phycst         ! physical constant
17   USE dom_oce        ! ocean domain
18   USE sbc_oce , ONLY : nn_fsbc   ! frequency of sea-ice call
19   USE ice            ! sea-ice: variables
20   USE icevar         ! sea-ice: operations
21   USE iceadv_prather ! sea-ice: advection scheme (Prather)
22   USE iceadv_umx     ! sea-ice: advection scheme (ultimate-macho)
23   USE icectl         ! sea-ice: control prints
24   !
25   USE in_out_manager ! I/O manager
26   USE lbclnk         ! lateral boundary conditions -- MPP exchanges
27   USE lib_mpp        ! MPP library
28   USE prtctl         ! Print control
29   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
30   USE timing         ! Timing
31   USE iom            !
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   ice_adv    ! called by icestp
37
38   !! * Substitution
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
42   !! $Id: iceadv.F90 8373 2017-07-25 17:44:54Z clem $
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE ice_adv( kt ) 
48      !!----------------------------------------------------------------------
49      !!                   ***  ROUTINE ice_adv ***
50      !!                   
51      !! ** purpose : advection of sea ice
52      !!
53      !! ** method  : variables included in the process are scalar,   
54      !!     other values are considered as second order.
55      !!     For advection, one can choose between
56      !!     a) an Ultimate-Macho scheme (whose order is defined by nn_limadv_ord) => nn_limadv=0
57      !!     b) and a second order Prather scheme => nn_limadv=-1
58      !!
59      !! ** action :
60      !!----------------------------------------------------------------------
61      INTEGER, INTENT(in) ::   kt   ! number of iteration
62      !
63      INTEGER  ::   ji, jj, jk, jl, jt      ! dummy loop indices
64      INTEGER  ::   initad                  ! number of sub-timestep for the advection
65      REAL(wp) ::   zcfl , zusnit           !   -      -
66      CHARACTER(len=80) :: cltmp
67      !
68      REAL(wp) ::    zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b
69      REAL(wp) ::    zdv
70      REAL(wp), DIMENSION(jpi,jpj)           ::   zatold, zeiold, zesold, zsmvold 
71      REAL(wp), DIMENSION(jpi,jpj,jpl)       ::   zhimax, zviold, zvsold
72      !!---------------------------------------------------------------------
73      IF( nn_timing == 1 )  CALL timing_start('iceadv')
74 
75      IF( kt == nit000 .AND. lwp ) THEN
76         WRITE(numout,*)
77         WRITE(numout,*) 'iceadv: sea-ice advection'
78         WRITE(numout,*) '~~~~~~'
79      ENDIF
80     
81      CALL ice_var_agg( 1 ) ! integrated values + ato_i
82
83      ! conservation test
84      IF( ln_limdiachk )   CALL ice_cons_hsm(0, 'iceadv', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
85     
86      ! store old values for diag
87      zviold (:,:,:) = v_i(:,:,:)
88      zvsold (:,:,:) = v_s(:,:,:)
89      zsmvold(:,:)   = SUM( smv_i(:,:,:), dim=3 )
90      zeiold (:,:)   = et_i(:,:)
91      zesold (:,:)   = et_s(:,:)
92
93      ! Thickness correction init.
94      zatold(:,:) = at_i
95      WHERE( a_i(:,:,:) >= epsi20 )
96         ht_i(:,:,:) = v_i(:,:,:) / a_i(:,:,:)
97         ht_s(:,:,:) = v_s(:,:,:) / a_i(:,:,:)
98      ELSEWHERE
99         ht_i(:,:,:) = 0._wp
100         ht_s(:,:,:) = 0._wp         
101      END WHERE
102         
103      ! Record max of the surrounding ice thicknesses for correction in case advection creates ice too thick
104      zhimax(:,:,:) = ht_i(:,:,:) + ht_s(:,:,:)
105      DO jl = 1, jpl
106         DO jj = 2, jpjm1
107            DO ji = 2, jpim1
108!!gm use of MAXVAL here is very probably less efficient than expending the 9 values
109               zhimax(ji,jj,jl) = MAX( epsi20, MAXVAL( ht_i(ji-1:ji+1,jj-1:jj+1,jl) + ht_s(ji-1:ji+1,jj-1:jj+1,jl) ) )
110            END DO
111         END DO
112      END DO
113      CALL lbc_lnk( zhimax(:,:,:), 'T', 1. )
114     
115      !----------
116      ! Advection
117      !----------
118      SELECT CASE ( nn_limadv )
119      CASE ( 0 )                    !-- ULTIMATE-MACHO scheme
120         CALL ice_adv_umx( kt, u_ice, v_ice,  &
121            &              ato_i, v_i, v_s, smv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i )
122         
123      CASE ( -1 )                   !-- PRATHER scheme
124         CALL ice_adv_prather( kt, u_ice, v_ice,  &
125            &                  ato_i, v_i, v_s, smv_i, oa_i, a_i, a_ip, v_ip, e_s, e_i )
126         
127      END SELECT
128
129      ! total ice fraction
130      at_i(:,:) = a_i(:,:,1)
131      DO jl = 2, jpl
132         at_i(:,:) = at_i(:,:) + a_i(:,:,jl)
133      END DO
134     
135      !------------
136      ! diagnostics
137      !------------
138      DO jj = 1, jpj
139         DO ji = 1, jpi
140            diag_trp_ei (ji,jj) = ( SUM( e_i  (ji,jj,1:nlay_i,:) ) -  zeiold(ji,jj) ) * r1_rdtice
141            diag_trp_es (ji,jj) = ( SUM( e_s  (ji,jj,1:nlay_s,:) ) -  zesold(ji,jj) ) * r1_rdtice
142            diag_trp_smv(ji,jj) = ( SUM( smv_i(ji,jj,:)          ) - zsmvold(ji,jj) ) * r1_rdtice
143            diag_trp_vi (ji,jj) =   SUM(   v_i(ji,jj,:)            -  zviold(ji,jj,:) ) * r1_rdtice
144            diag_trp_vs (ji,jj) =   SUM(   v_s(ji,jj,:)            -  zvsold(ji,jj,:) ) * r1_rdtice
145         END DO
146      END DO
147      IF( iom_use('icetrp') )   CALL iom_put( "icetrp" , diag_trp_vi * rday  )         ! ice volume transport
148      IF( iom_use('snwtrp') )   CALL iom_put( "snwtrp" , diag_trp_vs * rday  )         ! snw volume transport
149      IF( iom_use('saltrp') )   CALL iom_put( "saltrp" , diag_trp_smv * rday * rhoic ) ! salt content transport
150      IF( iom_use('deitrp') )   CALL iom_put( "deitrp" , diag_trp_ei         )         ! advected ice enthalpy (W/m2)
151      IF( iom_use('destrp') )   CALL iom_put( "destrp" , diag_trp_es         )         ! advected snw enthalpy (W/m2)
152     
153      !--------------------------------------
154      ! Thickness correction in case too high
155      !--------------------------------------
156      IF( nn_limdyn == 2 ) THEN
157         !
158         CALL ice_var_zapsmall                       !-- zap small areas
159         !
160         DO jl = 1, jpl
161            DO jj = 1, jpj
162               DO ji = 1, jpi
163                  IF ( v_i(ji,jj,jl) > 0._wp ) THEN  !-- bound to zhimax
164                     !
165                     ht_i  (ji,jj,jl) = v_i (ji,jj,jl) / a_i(ji,jj,jl)
166                     ht_s  (ji,jj,jl) = v_s (ji,jj,jl) / a_i(ji,jj,jl)
167                     zdv = v_i(ji,jj,jl) + v_s(ji,jj,jl) - zviold(ji,jj,jl) - zvsold(ji,jj,jl) 
168                     !
169                     IF ( ( zdv >  0.0 .AND. (ht_i(ji,jj,jl)+ht_s(ji,jj,jl)) > zhimax(ji,jj,jl) .AND. zatold(ji,jj) < 0.80 ) .OR. &
170                        & ( zdv <= 0.0 .AND. (ht_i(ji,jj,jl)+ht_s(ji,jj,jl)) > zhimax(ji,jj,jl) ) ) THEN
171                        a_i (ji,jj,jl) = ( v_i(ji,jj,jl) + v_s(ji,jj,jl) ) / zhimax(ji,jj,jl)
172                        ht_i(ji,jj,jl) =   v_i(ji,jj,jl) / a_i(ji,jj,jl)
173                     ENDIF
174                     !
175                  ENDIF
176               END DO
177            END DO
178         END DO
179                 
180         WHERE( ht_i(:,:,jpl) > hi_max(jpl) )        !-- bound ht_i to hi_max (99 m)
181            ht_i(:,:,jpl) = hi_max(jpl)
182            a_i (:,:,jpl) = v_i(:,:,jpl) / hi_max(jpl)
183         END WHERE
184
185         IF ( nn_pnd_scheme > 0 ) THEN               !-- correct pond fraction to avoid a_ip > a_i
186            WHERE( a_ip(:,:,:) > a_i(:,:,:) )   a_ip(:,:,:) = a_i(:,:,:)
187         ENDIF
188         !
189      ENDIF
190         
191      !------------------------------------------------------------
192      ! Impose a_i < amax if no ridging/rafting or in mono-category
193      !------------------------------------------------------------
194      IF( l_piling ) THEN                            !-- simple conservative piling, comparable with 1-cat models
195         at_i(:,:) = SUM( a_i(:,:,:), dim=3 )
196         DO jl = 1, jpl
197            WHERE( at_i(:,:) > epsi20 )
198               a_i(:,:,jl) = a_i(:,:,jl) * (  1._wp + MIN( rn_amax_2d(:,:) - at_i(:,:) , 0._wp ) / at_i(:,:)  )
199            END WHERE
200         END DO
201      ENDIF
202     
203      ! agglomerate variables
204      vt_i(:,:) = SUM( v_i(:,:,:), dim=3 )
205      vt_s(:,:) = SUM( v_s(:,:,:), dim=3 )
206      at_i(:,:) = SUM( a_i(:,:,:), dim=3 )
207
208      ! MV MP 2016 (remove once we get rid of a_i_frac and ht_i)
209      IF ( nn_pnd_scheme > 0 ) THEN
210          at_ip(:,:) = SUM( a_ip(:,:,:), dim = 3 )
211          vt_ip(:,:) = SUM( v_ip(:,:,:), dim = 3 )
212      ENDIF
213      ! END MP 2016
214     
215      ! open water = 1 if at_i=0
216      WHERE( at_i == 0._wp ) ato_i = 1._wp 
217     
218      ! conservation test
219      IF( ln_limdiachk )   CALL ice_cons_hsm(1, 'iceadv', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
220       
221      ! --------------
222      ! control prints
223      ! --------------
224      IF( ln_limctl )   CALL ice_prt( kt, iiceprt, jiceprt,-1, ' - ice dyn & trp - ' )
225      !
226      IF( nn_timing == 1 )  CALL timing_stop('iceadv')
227      !
228   END SUBROUTINE ice_adv
229
230#else
231   !!----------------------------------------------------------------------
232   !!   Default option         Empty Module                No sea-ice model
233   !!----------------------------------------------------------------------
234#endif
235
236   !!======================================================================
237END MODULE iceadv
238
Note: See TracBrowser for help on using the repository browser.