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/ICE_SRC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/ICE_SRC/icedyn.F90 @ 9570

Last change on this file since 9570 was 9570, checked in by nicolasmartin, 6 years ago

Global renaming for core routines (./NEMO)

  • Folders
    • LIM_SRC_3 -> ICE_SRC
    • OPA_SRC -> OCE_SRC
  • CPP key: key_lim3 -> key_si3
  • Modules, (sub)routines and variables names
    • MPI: mpi_comm_opa -> mpi_comm_oce, MPI_COMM_OPA -> MPI_COMM_OCE, mpi_init_opa -> mpi_init_oce
    • AGRIF: agrif_opa_* -> agrif_oce_*, agrif_lim3_* -> agrif_si3_* and few more
    • TOP-PISCES: p.zlim -> p.zice, namp.zlim -> namp.zice
  • Comments
    • NEMO/OPA -> NEMO/OCE
    • ESIM|LIM3 -> SI3
File size: 13.6 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_si3
9   !!----------------------------------------------------------------------
10   !!   'key_si3'                                       SI3 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( ln_timing )   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( ln_timing )   CALL timing_stop('icedyn')
126      !
127   END SUBROUTINE ice_dyn
128
129
130   SUBROUTINE Hbig( phmax )
131      !!-------------------------------------------------------------------
132      !!                  ***  ROUTINE Hbig  ***
133      !!
134      !! ** Purpose : Thickness correction in case advection scheme creates
135      !!              abnormally tick ice
136      !!
137      !! ** Method  : 1- check whether ice thickness resulting from advection is
138      !!                 larger than the surrounding 9-points before advection
139      !!                 and reduce it if a) divergence or b) convergence & at_i>0.8
140      !!              2- bound ice thickness with hi_max (99m)
141      !!
142      !! ** input   : Max thickness of the surrounding 9-points
143      !!-------------------------------------------------------------------
144      REAL(wp), DIMENSION(:,:,:), INTENT(in) ::   phmax   ! max ice thick from surrounding 9-pts
145      !
146      INTEGER  ::   ji, jj, jl         ! dummy loop indices
147      REAL(wp) ::   zh, zdv
148      !!-------------------------------------------------------------------
149      !
150      CALL ice_var_zapsmall                       !-- zap small areas
151      !
152      DO jl = 1, jpl
153         DO jj = 1, jpj
154            DO ji = 1, jpi
155               IF ( v_i(ji,jj,jl) > 0._wp ) THEN  !-- bound to hmax
156                  !
157                  zh  = v_i (ji,jj,jl) / a_i(ji,jj,jl)
158                  zdv = v_i(ji,jj,jl) - v_i_b(ji,jj,jl) 
159                  !
160                  IF ( ( zdv >  0.0 .AND. zh > phmax(ji,jj,jl) .AND. at_i_b(ji,jj) < 0.80 ) .OR. &
161                     & ( zdv <= 0.0 .AND. zh > phmax(ji,jj,jl) ) ) THEN
162                     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)
163                  ENDIF
164                  !
165               ENDIF
166            END DO
167         END DO
168      END DO 
169      !                                           !-- correct pond fraction to avoid a_ip > a_i
170      WHERE( a_ip(:,:,:) > a_i(:,:,:) )   a_ip(:,:,:) = a_i(:,:,:)
171      !
172   END SUBROUTINE Hbig
173
174
175   SUBROUTINE Hpiling
176      !!-------------------------------------------------------------------
177      !!                  ***  ROUTINE Hpiling  ***
178      !!
179      !! ** Purpose : Simple conservative piling comparable with 1-cat models
180      !!
181      !! ** Method  : pile-up ice when no ridging/rafting
182      !!
183      !! ** input   : a_i
184      !!-------------------------------------------------------------------
185      INTEGER ::   jl         ! dummy loop indices
186      !!-------------------------------------------------------------------
187      !
188      CALL ice_var_zapsmall                       !-- zap small areas
189      !
190      at_i(:,:) = SUM( a_i(:,:,:), dim=3 )
191      DO jl = 1, jpl
192         WHERE( at_i(:,:) > epsi20 )
193            a_i(:,:,jl) = a_i(:,:,jl) * (  1._wp + MIN( rn_amax_2d(:,:) - at_i(:,:) , 0._wp ) / at_i(:,:)  )
194         END WHERE
195      END DO
196      !
197   END SUBROUTINE Hpiling
198
199
200   SUBROUTINE ice_dyn_init
201      !!-------------------------------------------------------------------
202      !!                  ***  ROUTINE ice_dyn_init  ***
203      !!
204      !! ** Purpose : Physical constants and parameters linked to the ice
205      !!      dynamics
206      !!
207      !! ** Method  :  Read the namdyn namelist and check the ice-dynamic
208      !!       parameter values called at the first timestep (nit000)
209      !!
210      !! ** input   :   Namelist namdyn
211      !!-------------------------------------------------------------------
212      INTEGER ::   ios, ioptio   ! Local integer output status for namelist read
213      !!
214      NAMELIST/namdyn/ ln_dynFULL, ln_dynRHGADV, ln_dynADV, rn_uice, rn_vice,  &
215         &             rn_ishlat  ,                                            &
216         &             ln_landfast, rn_gamma , rn_icebfr, rn_lfrelax
217      !!-------------------------------------------------------------------
218      !
219      REWIND( numnam_ice_ref )         ! Namelist namdyn in reference namelist : Ice dynamics
220      READ  ( numnam_ice_ref, namdyn, IOSTAT = ios, ERR = 901)
221901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdyn in reference namelist', lwp )
222      REWIND( numnam_ice_cfg )         ! Namelist namdyn in configuration namelist : Ice dynamics
223      READ  ( numnam_ice_cfg, namdyn, IOSTAT = ios, ERR = 902 )
224902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namdyn in configuration namelist', lwp )
225      IF(lwm) WRITE( numoni, namdyn )
226      !
227      IF(lwp) THEN                     ! control print
228         WRITE(numout,*)
229         WRITE(numout,*) 'ice_dyn_init: ice parameters for ice dynamics '
230         WRITE(numout,*) '~~~~~~~~~~~~'
231         WRITE(numout,*) '   Namelist namdyn:'
232         WRITE(numout,*) '      Full ice dynamics      (rhg + adv + ridge/raft + corr)  ln_dynFULL   = ', ln_dynFULL
233         WRITE(numout,*) '      No ridge/raft & No cor (rhg + adv)                      ln_dynRHGADV = ', ln_dynRHGADV
234         WRITE(numout,*) '      Advection only         (rn_uvice + adv)                 ln_dynADV    = ', ln_dynADV
235         WRITE(numout,*) '         with prescribed velocity given by   (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         WRITE(numout,*)
242      ENDIF
243      !                             !== set the choice of ice dynamics ==!
244      ioptio = 0 
245      !      !--- full dynamics                               (rheology + advection + ridging/rafting + correction)
246      IF( ln_dynFULL   ) THEN   ;   ioptio = ioptio + 1   ;   nice_dyn = np_dynFULL      ;   ENDIF
247      !      !--- dynamics without ridging/rafting and corr   (rheology + advection)
248      IF( ln_dynRHGADV ) THEN   ;   ioptio = ioptio + 1   ;   nice_dyn = np_dynRHGADV    ;   ENDIF
249      !      !--- advection only with prescribed ice velocities (from namelist)
250      IF( ln_dynADV    ) THEN   ;   ioptio = ioptio + 1   ;   nice_dyn = np_dynADV       ;   ENDIF
251      !
252      IF( ioptio /= 1 )    CALL ctl_stop( 'ice_dyn_init: one and only one ice dynamics option has to be defined ' )
253      !
254      !                                      !--- Lateral boundary conditions
255      IF     (      rn_ishlat == 0.                ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  free-slip'
256      ELSEIF (      rn_ishlat == 2.                ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  no-slip'
257      ELSEIF ( 0. < rn_ishlat .AND. rn_ishlat < 2. ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  partial-slip'
258      ELSEIF ( 2. < rn_ishlat                      ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  strong-slip'
259      ENDIF
260      !                                      !--- NO Landfast ice : set to zero once for all
261      IF( .NOT.ln_landfast )   tau_icebfr(:,:) = 0._wp
262      !
263      CALL ice_dyn_rdgrft_init          ! set ice ridging/rafting parameters
264      CALL ice_dyn_rhg_init             ! set ice rheology parameters
265      CALL ice_dyn_adv_init             ! set ice advection parameters
266      !
267   END SUBROUTINE ice_dyn_init
268
269#else
270   !!----------------------------------------------------------------------
271   !!   Default option         Empty module           NO SI3 sea-ice model
272   !!----------------------------------------------------------------------
273#endif 
274
275   !!======================================================================
276END MODULE icedyn
Note: See TracBrowser for help on using the repository browser.