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

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/LIM_SRC_3/icedyn.F90 @ 9076

Last change on this file since 9076 was 9076, checked in by vancop, 6 years ago

monocat to virtual_itd

File size: 13.7 KB
Line 
1MODULE icedyn
2   !!======================================================================
3   !!                     ***  MODULE  icedyn  ***
4   !!   Sea-Ice dynamics : master routine for sea ice dynamics
5   !!======================================================================
6   !! history :  4.0  ! 2017-09  (C. Rousset)  original code
7   !!----------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3'                                       ESIM sea-ice model
11   !!----------------------------------------------------------------------
12   !!   ice_dyn       : dynamics of sea ice
13   !!   ice_dyn_init  : initialization and namelist read
14   !!----------------------------------------------------------------------
15   USE phycst         ! physical constants
16   USE dom_oce        ! ocean space and time domain
17   USE ice            ! sea-ice: variables
18   USE icedyn_rhg     ! sea-ice: rheology
19   USE icedyn_adv     ! sea-ice: advection
20   USE icedyn_rdgrft  ! sea-ice: ridging/rafting
21   USE icecor         ! sea-ice: corrections
22   USE icevar         ! sea-ice: operations
23   !
24   USE in_out_manager ! I/O manager
25   USE iom            ! I/O manager library
26   USE lib_mpp        ! MPP library
27   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
28   USE lbclnk         ! lateral boundary conditions (or mpp links)
29   USE timing         ! Timing
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   ice_dyn        ! called by icestp.F90
35   PUBLIC   ice_dyn_init   ! called by icestp.F90
36   
37   INTEGER ::              nice_dyn   ! choice of the type of dynamics
38   !                                        ! associated indices:
39   INTEGER, PARAMETER ::   np_dynFULL    = 1   ! full ice dynamics               (rheology + advection + ridging/rafting + correction)
40   INTEGER, PARAMETER ::   np_dynRHGADV  = 2   ! pure dynamics                   (rheology + advection)
41   INTEGER, PARAMETER ::   np_dynADV     = 3   ! only advection w prescribed vel.(rn_uvice + advection)
42   !
43   ! ** namelist (namdyn) **
44   LOGICAL  ::   ln_dynFULL       ! full ice dynamics               (rheology + advection + ridging/rafting + correction)
45   LOGICAL  ::   ln_dynRHGADV     ! no ridge/raft & no corrections  (rheology + advection)
46   LOGICAL  ::   ln_dynADV        ! only advection w prescribed vel.(rn_uvice + advection)
47   REAL(wp) ::   rn_uice          !    prescribed u-vel (case np_dynADV)
48   REAL(wp) ::   rn_vice          !    prescribed v-vel (case np_dynADV)
49   
50   !! * Substitutions
51#  include "vectopt_loop_substitute.h90"
52   !!----------------------------------------------------------------------
53   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
54   !! $Id: icedyn.F90 8378 2017-07-26 13:55:59Z clem $
55   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
56   !!----------------------------------------------------------------------
57CONTAINS
58
59   SUBROUTINE ice_dyn( kt )
60      !!-------------------------------------------------------------------
61      !!               ***  ROUTINE ice_dyn  ***
62      !!               
63      !! ** Purpose :   this routine manages sea ice dynamics
64      !!
65      !! ** Action : - Initialisation of some variables
66      !!             - call ice_rhg
67      !!--------------------------------------------------------------------
68      INTEGER, INTENT(in) ::   kt     ! ice time step
69      !!
70      INTEGER ::   ji, jj, jl         ! dummy loop indices
71      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zhmax
72      !!--------------------------------------------------------------------
73      !
74      IF( nn_timing == 1 )   CALL timing_start('icedyn')
75      !
76      IF( kt == nit000 .AND. lwp ) THEN
77         WRITE(numout,*)
78         WRITE(numout,*)'ice_dyn: sea-ice dynamics'
79         WRITE(numout,*)'~~~~~~~'
80      ENDIF
81
82      !                     
83      IF( ln_landfast ) THEN            !-- Landfast ice parameterization: define max bottom friction
84         tau_icebfr(:,:) = 0._wp
85         DO jl = 1, jpl
86            WHERE( h_i(:,:,jl) > ht_n(:,:) * rn_gamma )   tau_icebfr(:,:) = tau_icebfr(:,:) + a_i(:,:,jl) * rn_icebfr
87         END DO
88         IF( iom_use('tau_icebfr') )   CALL iom_put( 'tau_icebfr', tau_icebfr ) 
89      ENDIF
90
91      zhmax(:,:,:) = h_i_b(:,:,:)      !-- Record max of the surrounding 9-pts ice thick. (for CALL Hbig)
92      DO jl = 1, jpl
93         DO jj = 2, jpjm1
94            DO ji = 2, jpim1
95!!gm use of MAXVAL here is very probably less efficient than expending the 9 values
96               zhmax(ji,jj,jl) = MAX( epsi20, MAXVAL( h_i_b(ji-1:ji+1,jj-1:jj+1,jl) ) )
97            END DO
98         END DO
99      END DO
100      CALL lbc_lnk( zhmax(:,:,:), 'T', 1. )
101      !
102      !
103      SELECT CASE( nice_dyn )           !-- Set which dynamics is running
104
105      CASE ( np_dynFULL )          !==  all dynamical processes  ==!
106         CALL ice_dyn_rhg   ( kt )                            ! -- rheology 
107         CALL ice_dyn_adv   ( kt )   ;   CALL Hbig( zhmax )   ! -- advection of ice + correction on ice thickness
108         CALL ice_dyn_rdgrft( kt )                            ! -- ridging/rafting
109         CALL ice_cor       ( kt , 1 )                        ! -- Corrections
110
111      CASE ( np_dynRHGADV  )       !==  no ridge/raft & no corrections ==!
112         CALL ice_dyn_rhg   ( kt )                            ! -- rheology 
113         CALL ice_dyn_adv   ( kt )                            ! -- advection of ice
114         CALL Hpiling                                         ! -- simple pile-up (replaces ridging/rafting)
115
116      CASE ( np_dynADV )           !==  pure advection ==!   (prescribed velocities)
117         u_ice(:,:) = rn_uice * umask(:,:,1)
118         v_ice(:,:) = rn_vice * vmask(:,:,1)
119         !!CALL RANDOM_NUMBER(u_ice(:,:))
120         !!CALL RANDOM_NUMBER(v_ice(:,:))
121         CALL ice_dyn_adv   ( kt )                            ! -- advection of ice
122
123      END SELECT
124      !
125      IF( nn_timing == 1 )   CALL timing_stop('icedyn')
126      !
127   END SUBROUTINE ice_dyn
128
129   SUBROUTINE Hbig( phmax )
130      !!-------------------------------------------------------------------
131      !!                  ***  ROUTINE Hbig  ***
132      !!
133      !! ** Purpose : Thickness correction in case advection scheme creates
134      !!              abnormally tick ice
135      !!
136      !! ** Method  : 1- check whether ice thickness resulting from advection is
137      !!                 larger than the surrounding 9-points before advection
138      !!                 and reduce it if a) divergence or b) convergence & at_i>0.8
139      !!              2- bound ice thickness with hi_max (99m)
140      !!
141      !! ** input   : Max thickness of the surrounding 9-points
142      !!-------------------------------------------------------------------
143      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   phmax   ! max ice thick from surrounding 9-pts
144      !
145      INTEGER  ::   ji, jj, jl         ! dummy loop indices
146      REAL(wp) ::   zh, zdv
147      !!-------------------------------------------------------------------
148      !
149      CALL ice_var_zapsmall                       !-- zap small areas
150      !
151      DO jl = 1, jpl
152         DO jj = 1, jpj
153            DO ji = 1, jpi
154               IF ( v_i(ji,jj,jl) > 0._wp ) THEN  !-- bound to hmax
155                  !
156                  zh  = v_i (ji,jj,jl) / a_i(ji,jj,jl)
157                  zdv = v_i(ji,jj,jl) - v_i_b(ji,jj,jl) 
158                  !
159                  IF ( ( zdv >  0.0 .AND. zh > phmax(ji,jj,jl) .AND. at_i_b(ji,jj) < 0.80 ) .OR. &
160                     & ( zdv <= 0.0 .AND. zh > phmax(ji,jj,jl) ) ) THEN
161                     a_i (ji,jj,jl) = v_i(ji,jj,jl) / MIN( phmax(ji,jj,jl), hi_max(jpl) )   !-- bound h_i to hi_max (99 m)
162                  ENDIF
163                  !
164               ENDIF
165            END DO
166         END DO
167      END DO 
168      !                                           !-- correct pond fraction to avoid a_ip > a_i
169      WHERE( a_ip(:,:,:) > a_i(:,:,:) )   a_ip(:,:,:) = a_i(:,:,:)
170      !
171   END SUBROUTINE Hbig
172
173   SUBROUTINE Hpiling
174      !!-------------------------------------------------------------------
175      !!                  ***  ROUTINE Hpiling  ***
176      !!
177      !! ** Purpose : Simple conservative piling comparable with 1-cat models
178      !!
179      !! ** Method  : pile-up ice when no ridging/rafting
180      !!
181      !! ** input   : a_i
182      !!-------------------------------------------------------------------
183      INTEGER ::   jl         ! dummy loop indices
184      !!-------------------------------------------------------------------
185      !
186      CALL ice_var_zapsmall                       !-- zap small areas
187      !
188      at_i(:,:) = SUM( a_i(:,:,:), dim=3 )
189      DO jl = 1, jpl
190         WHERE( at_i(:,:) > epsi20 )
191            a_i(:,:,jl) = a_i(:,:,jl) * (  1._wp + MIN( rn_amax_2d(:,:) - at_i(:,:) , 0._wp ) / at_i(:,:)  )
192         END WHERE
193      END DO
194      !
195   END SUBROUTINE Hpiling
196
197
198   SUBROUTINE ice_dyn_init
199      !!-------------------------------------------------------------------
200      !!                  ***  ROUTINE ice_dyn_init  ***
201      !!
202      !! ** Purpose : Physical constants and parameters linked to the ice
203      !!      dynamics
204      !!
205      !! ** Method  :  Read the namdyn namelist and check the ice-dynamic
206      !!       parameter values called at the first timestep (nit000)
207      !!
208      !! ** input   :   Namelist namdyn
209      !!-------------------------------------------------------------------
210      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read
211      !!
212      NAMELIST/namdyn/ ln_dynFULL, ln_dynRHGADV, ln_dynADV, rn_uice, rn_vice,  &
213         &             rn_ishlat  ,                                            &
214         &             ln_landfast, rn_gamma , rn_icebfr, rn_lfrelax
215      !!-------------------------------------------------------------------
216      !
217      REWIND( numnam_ice_ref )         ! Namelist namdyn in reference namelist : Ice dynamics
218      READ  ( numnam_ice_ref, namdyn, IOSTAT = ios, ERR = 901)
219901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn in reference namelist', lwp )
220      !
221      REWIND( numnam_ice_cfg )         ! Namelist namdyn in configuration namelist : Ice dynamics
222      READ  ( numnam_ice_cfg, namdyn, IOSTAT = ios, ERR = 902 )
223902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namdyn in configuration namelist', lwp )
224      IF(lwm) WRITE ( numoni, namdyn )
225      !
226      IF(lwp) THEN                     ! control print
227         WRITE(numout,*)
228         WRITE(numout,*) 'ice_dyn_init: ice parameters for ice dynamics '
229         WRITE(numout,*) '~~~~~~~~~~~~'
230         WRITE(numout,*) '   Namelist namdyn:'
231         WRITE(numout,*) '      Full ice dynamics      (rhg + adv + ridge/raft + corr)  ln_dynFULL   = ', ln_dynFULL
232         WRITE(numout,*) '      No ridge/raft & No cor (rhg + adv)                      ln_dynRHGADV = ', ln_dynRHGADV
233         WRITE(numout,*) '      Advection only         (rn_uvice + adv)                 ln_dynADV    = ', ln_dynADV
234         WRITE(numout,*) '           with prescribed velocity given by '
235         WRITE(numout,*) '               a uniform field               (u,v)_ice = (rn_uice,rn_vice) = (', rn_uice,',', rn_vice,')'
236         WRITE(numout,*) '      lateral boundary condition for sea ice dynamics         rn_ishlat    = ', rn_ishlat
237         WRITE(numout,*) '      Landfast: param (T or F)                                ln_landfast  = ', ln_landfast
238         WRITE(numout,*) '         fraction of ocean depth that ice must reach          rn_gamma     = ', rn_gamma
239         WRITE(numout,*) '         maximum bottom stress per unit area of contact       rn_icebfr    = ', rn_icebfr
240         WRITE(numout,*) '         relax time scale (s-1) to reach static friction      rn_lfrelax   = ', rn_lfrelax
241      ENDIF
242      !                             !== set the choice of ice dynamics ==!
243      ioptio = 0 
244      !      !--- full dynamics                               (rheology + advection + ridging/rafting + correction)
245      IF( ln_dynFULL   ) THEN   ;   ioptio = ioptio + 1   ;   nice_dyn = np_dynFULL      ;   ENDIF
246      !      !--- dynamics without ridging/rafting and corr   (rheology + advection)
247      IF( ln_dynRHGADV ) THEN   ;   ioptio = ioptio + 1   ;   nice_dyn = np_dynRHGADV    ;   ENDIF
248      !      !--- advection only with prescribed ice velocities (from namelist)
249      IF( ln_dynADV    ) THEN   ;   ioptio = ioptio + 1   ;   nice_dyn = np_dynADV       ;   ENDIF
250      !
251      IF( ioptio /= 1 )    CALL ctl_stop( 'ice_dyn_init: one and only one ice dynamics option has to be defined ' )
252      !
253      !                                      !--- Lateral boundary conditions
254      IF     (      rn_ishlat == 0.                ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  free-slip'
255      ELSEIF (      rn_ishlat == 2.                ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  no-slip'
256      ELSEIF ( 0. < rn_ishlat .AND. rn_ishlat < 2. ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  partial-slip'
257      ELSEIF ( 2. < rn_ishlat                      ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  strong-slip'
258      ENDIF
259      !                                      !--- NO Landfast ice : set to zero once for all
260      IF( .NOT. ln_landfast )   tau_icebfr(:,:) = 0._wp
261      !
262      CALL ice_dyn_rdgrft_init          ! set ice ridging/rafting parameters
263      CALL ice_dyn_rhg_init             ! set ice rheology parameters
264      CALL ice_dyn_adv_init             ! set ice advection parameters
265      !
266   END SUBROUTINE ice_dyn_init
267
268#else
269   !!----------------------------------------------------------------------
270   !!   Default option         Empty module           NO ESIM sea-ice model
271   !!----------------------------------------------------------------------
272#endif 
273
274   !!======================================================================
275END MODULE icedyn
Note: See TracBrowser for help on using the repository browser.