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

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icedyn.F90 @ 8516

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

changes in style - part5 - I think I can see the end of the tunnel

File size: 9.8 KB
RevLine 
[8516]1MODULE icedyn
2   !!======================================================================
3   !!                     ***  MODULE  icedyn  ***
4   !!   Sea-Ice dynamics : 
5   !!======================================================================
6   !! history :  4.0  ! 2017-09  (C. Rousset)  original code
7   !!----------------------------------------------------------------------
8#if defined key_lim3
9   !!----------------------------------------------------------------------
10   !!   'key_lim3'                                       LIM3 sea-ice model
11   !!----------------------------------------------------------------------
12   !!   ice_dyn       : dynamics of sea ice
13   !!   ice_dyn_init  : initialisation of sea-ice dynamics
14   !!----------------------------------------------------------------------
15   USE phycst         ! physical constants
16   USE dom_oce        ! ocean space and time domain
17   USE ice            ! sea-ice: variables
18   USE icerhg         ! sea-ice: rheology
19   USE iceadv         ! sea-ice: advection
20   USE icerdgrft      ! sea-ice: ridging/rafting
21   USE icecor         ! sea-ice: corrections
22   USE icevar         ! sea-ice: operations
23   !
24   USE lbclnk         ! lateral boundary conditions - MPP exchanges
25   USE lib_mpp        ! MPP library
26   USE in_out_manager ! I/O manager
27   USE lib_fortran    ! glob_sum
28   USE timing         ! Timing
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   ice_dyn        ! called by icestp.F90
34   PUBLIC   ice_dyn_init   ! called by icestp.F90
35   
36   INTEGER ::              nice_dyn   ! choice of the type of advection scheme
37   !                                        ! associated indices:
38   INTEGER, PARAMETER ::   np_dynNO   = 0   ! no ice dynamics and ice advection
39   INTEGER, PARAMETER ::   np_dynFULL = 1   ! full ice dynamics  (rheology + advection + ridging/rafting + correction)
40   INTEGER, PARAMETER ::   np_dyn     = 2   ! no ridging/rafting (rheology + advection                   + correction)
41   INTEGER, PARAMETER ::   np_dynPURE = 3   ! pure dynamics      (rheology + advection)
42
43   !! * Substitutions
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
47   !! $Id: icedyn.F90 8378 2017-07-26 13:55:59Z clem $
48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE ice_dyn( kt )
53      !!-------------------------------------------------------------------
54      !!               ***  ROUTINE ice_dyn  ***
55      !!               
56      !! ** Purpose :   this routine manages sea ice dynamics
57      !!
58      !! ** Action : - Initialisation of some variables
59      !!             - call ice_rhg
60      !!--------------------------------------------------------------------
61      INTEGER, INTENT(in) ::   kt     ! ice time step
62      !!
63      INTEGER  ::   jl   ! dummy loop indices
64      !!--------------------------------------------------------------------
65      !
66      IF( nn_timing == 1 )  CALL timing_start('icedyn')
67      !
68      IF( kt == nit000 .AND. lwp ) THEN
69         WRITE(numout,*)
70         WRITE(numout,*)'ice_dyn: sea-ice dynamics'
71         WRITE(numout,*)'~~~~~~~'
72      ENDIF
73
74      CALL ice_var_agg(1)           ! -- aggregate ice categories
75      !                     
76      IF( ln_landfast ) THEN        ! -- Landfast ice parameterization: define max bottom friction
77         tau_icebfr(:,:) = 0._wp
78         DO jl = 1, jpl
79            WHERE( ht_i(:,:,jl) > ht_n(:,:) * rn_gamma )   tau_icebfr(:,:) = tau_icebfr(:,:) + a_i(:,:,jl) * rn_icebfr
80         END DO
81      ENDIF
82
83      SELECT CASE( nice_dyn )       ! -- Set which dynamics is running
84
85      CASE ( np_dynFULL )          !==  all dynamical processes  ==!
86         CALL ice_rhg   ( kt )          ! -- rheology 
87         CALL ice_adv   ( kt )          ! -- advection of ice
88         CALL ice_rdgrft( kt )          ! -- ridging/rafting
89         CALL ice_cor   ( kt , 1 )      ! -- Corrections
90
91      CASE ( np_dyn )              !==  pure dynamics only ==!   (no ridging/rafting)   (nono cat. case 2)
92         CALL ice_rhg   ( kt )          ! -- rheology 
93         CALL ice_adv   ( kt )          ! -- advection of ice
94         CALL ice_cor   ( kt , 1 )      ! -- Corrections
95
96      CASE ( np_dynPURE )          !==  pure dynamics only ==!   (nn_icedyn= 1 )
97         CALL ice_rhg   ( kt )          ! -- rheology 
98         CALL ice_adv   ( kt )          ! -- advection of ice
99
100      CASE ( np_dynNO )            !==  prescribed ice velocities ==!   (nn_icedyn= 0 )
101         u_ice(:,:) = rn_uice * umask(:,:,1)
102         v_ice(:,:) = rn_vice * vmask(:,:,1)
103         !!CALL RANDOM_NUMBER(u_ice(:,:))
104         !!CALL RANDOM_NUMBER(v_ice(:,:))
105
106      END SELECT
107      !
108      IF( nn_timing == 1 )   CALL timing_stop('icedyn')
109      !
110   END SUBROUTINE ice_dyn
111
112
113   SUBROUTINE ice_dyn_init
114      !!-------------------------------------------------------------------
115      !!                  ***  ROUTINE ice_dyn_init  ***
116      !!
117      !! ** Purpose : Physical constants and parameters linked to the ice
118      !!      dynamics
119      !!
120      !! ** Method  :  Read the namice_dyn namelist and check the ice-dynamic
121      !!       parameter values called at the first timestep (nit000)
122      !!
123      !! ** input   :   Namelist namice_dyn
124      !!-------------------------------------------------------------------
125      INTEGER ::   ios   ! Local integer output status for namelist read
126      !!
127      NAMELIST/namice_dyn/ ln_icedyn  , nn_icedyn, rn_uice  , rn_vice ,    &
128         &                 rn_ishlat  , rn_cio   ,                         &
129         &                 ln_landfast, rn_gamma , rn_icebfr, rn_lfrelax
130      !!-------------------------------------------------------------------
131      !
132      REWIND( numnam_ice_ref )         ! Namelist namice_dyn in reference namelist : Ice dynamics
133      READ  ( numnam_ice_ref, namice_dyn, IOSTAT = ios, ERR = 901)
134901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dyn in reference namelist', lwp )
135      !
136      REWIND( numnam_ice_cfg )         ! Namelist namice_dyn in configuration namelist : Ice dynamics
137      READ  ( numnam_ice_cfg, namice_dyn, IOSTAT = ios, ERR = 902 )
138902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dyn in configuration namelist', lwp )
139      IF(lwm) WRITE ( numoni, namice_dyn )
140      !
141      IF(lwp) THEN                     ! control print
142         WRITE(numout,*)
143         WRITE(numout,*) 'ice_dyn_init: ice parameters for ice dynamics '
144         WRITE(numout,*) '~~~~~~~~~~~~'
145         WRITE(numout,*) '   Namelist namice_dyn'
146         WRITE(numout,*) '      Ice dynamics       (T) or not (F)                         ln_icedyn  = ', ln_icedyn
147         WRITE(numout,*) '         associated switch                                      nn_icedyn  = ', nn_icedyn
148         WRITE(numout,*) '            =2 all processes (default option)'
149         WRITE(numout,*) '            =1 advection only (no ridging/rafting)'
150         WRITE(numout,*) '            =0 advection only with prescribed velocity given by '
151         WRITE(numout,*) '               a uniform field               (u,v)_ice = (rn_uice,rn_vice) = (', rn_uice,',', rn_vice,')'
152         WRITE(numout,*) '      lateral boundary condition for sea ice dynamics        rn_ishlat     = ', rn_ishlat
153         WRITE(numout,*) '      drag coefficient for oceanic stress                    rn_cio        = ', rn_cio
154         WRITE(numout,*) '      Landfast: param (T or F)                               ln_landfast   = ', ln_landfast
155         WRITE(numout,*) '         fraction of ocean depth that ice must reach         rn_gamma      = ', rn_gamma
156         WRITE(numout,*) '         maximum bottom stress per unit area of contact      rn_icebfr     = ', rn_icebfr
157         WRITE(numout,*) '         relax time scale (s-1) to reach static friction     rn_lfrelax    = ', rn_lfrelax
158      ENDIF
159      !                             !== set the choice of ice dynamics ==!
160      SELECT CASE( nn_icedyn )
161      CASE( 2 )                   
162         IF( nn_monocat /= 2 ) THEN          !--- full dynamics (rheology + advection + ridging/rafting + correction)
163            nice_dyn = np_dynFULL
164         ELSE
165            nice_dyn = np_dyn                !--- dynamics without ridging/rafting
166         ENDIF
167      CASE( 1 )                              !--- dynamics without ridging/rafting and correction
168         nice_dyn = np_dynPURE
169      CASE( 0 )                              !--- prescribed ice velocities (from namelist)
170         nice_dyn = np_dynNO
171      END SELECT
172      !
173      !                                      !--- Lateral boundary conditions
174      IF     (      rn_ishlat == 0.                ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  free-slip'
175      ELSEIF (      rn_ishlat == 2.                ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  no-slip'
176      ELSEIF ( 0. < rn_ishlat .AND. rn_ishlat < 2. ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  partial-slip'
177      ELSEIF ( 2. < rn_ishlat                      ) THEN   ;   IF(lwp) WRITE(numout,*) '   ===>>>   ice lateral  strong-slip'
178      ENDIF
179      !
180      !                                      !--- NO Landfast ice : set to zero once for all
181      IF( .NOT. ln_landfast )   tau_icebfr(:,:) = 0._wp 
182      !
183      !                                      !--- simple conservative piling, comparable with LIM2
184      l_piling = nn_icedyn == 1 .OR. ( nn_monocat == 2  .AND.  jpl == 1 )
185      !
186   END SUBROUTINE ice_dyn_init
187
188#else
189   !!----------------------------------------------------------------------
190   !!   Default option         Empty module          NO LIM-3 sea-ice model
191   !!----------------------------------------------------------------------
192#endif 
193
194   !!======================================================================
195END MODULE icedyn
Note: See TracBrowser for help on using the repository browser.