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.
limdyn.F90 in branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/limdyn.F90 @ 6989

Last change on this file since 6989 was 6989, checked in by clem, 8 years ago

use a namelist parameter to choose between the different advection schemes

  • Property svn:keywords set to Id
File size: 10.1 KB
Line 
1MODULE limdyn
2   !!======================================================================
3   !!                     ***  MODULE  limdyn  ***
4   !!   Sea-Ice dynamics : 
5   !!======================================================================
6   !! history :  1.0  ! 2002-08  (C. Ethe, G. Madec)  original VP code
7   !!            3.0  ! 2007-03  (MA Morales Maqueda, S. Bouillon, M. Vancoppenolle)  LIM3: EVP-Cgrid
8   !!            3.5  ! 2011-02  (G. Madec) dynamical allocation
9   !!----------------------------------------------------------------------
10#if defined key_lim3
11   !!----------------------------------------------------------------------
12   !!   'key_lim3' :                                 LIM3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!    lim_dyn      : computes ice velocities
15   !!    lim_dyn_init : initialization and namelist read
16   !!----------------------------------------------------------------------
17   USE phycst           ! physical constants
18   USE dom_oce          ! ocean space and time domain
19   USE sbc_ice          ! Surface boundary condition: ice   fields
20   USE ice              ! LIM-3 variables
21   USE limrhg           ! LIM-3 rheology
22   USE lbclnk           ! lateral boundary conditions - MPP exchanges
23   USE lib_mpp          ! MPP library
24   USE wrk_nemo         ! work arrays
25   USE in_out_manager   ! I/O manager
26   USE prtctl           ! Print control
27   USE lib_fortran      ! glob_sum
28   USE timing           ! Timing
29   USE limcons          ! conservation tests
30   USE limvar
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   lim_dyn        ! routine called by sbcice_lim.F90
36   PUBLIC   lim_dyn_init   ! routine called by sbcice_lim.F90
37
38   !! * Substitutions
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2011)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE lim_dyn( kt )
48      !!-------------------------------------------------------------------
49      !!               ***  ROUTINE lim_dyn  ***
50      !!               
51      !! ** Purpose :   compute ice velocity
52      !!               
53      !! ** Method  :
54      !!
55      !! ** Action  : - Initialisation
56      !!              - Call of the dynamic routine for each hemisphere
57      !!------------------------------------------------------------------------------------
58      INTEGER, INTENT(in) ::   kt     ! number of iteration
59      !!
60      INTEGER  :: jl, jk ! dummy loop indices
61      REAL(wp) :: zvi_b, zsmv_b, zei_b, zfs_b, zfw_b, zft_b 
62     !!---------------------------------------------------------------------
63
64      IF( nn_timing == 1 )  CALL timing_start('limdyn')
65
66      CALL lim_var_agg(1)                      ! aggregate ice categories
67      !
68      ! conservation test
69      IF( ln_limdiahsb ) CALL lim_cons_hsm(0, 'limdyn', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
70     
71      ! ice velocities before rheology
72      u_ice_b(:,:) = u_ice(:,:) * umask(:,:,1)
73      v_ice_b(:,:) = v_ice(:,:) * vmask(:,:,1)
74     
75      ! Landfast ice parameterization: define max bottom friction
76      tau_icebfr(:,:) = 0._wp
77      IF( ln_landfast ) THEN
78         DO jl = 1, jpl
79            WHERE( ht_i(:,:,jl) > ht(:,:) * rn_gamma )  tau_icebfr(:,:) = tau_icebfr(:,:) + a_i(:,:,jl) * rn_icebfr
80         END DO
81      ENDIF
82     
83      ! Rheology (ice dynamics)
84      ! ========     
85      CALL lim_rhg
86      !
87      !
88      ! Control prints
89      IF(ln_ctl) THEN
90         CALL prt_ctl_info(' ')
91         CALL prt_ctl_info(' - Cell values : ')
92         CALL prt_ctl_info('   ~~~~~~~~~~~~~ ')
93         CALL prt_ctl(tab2d_1=divu_i    , clinfo1=' lim_dyn  : divu_i    :')
94         CALL prt_ctl(tab2d_1=delta_i   , clinfo1=' lim_dyn  : delta_i   :')
95         CALL prt_ctl(tab2d_1=strength  , clinfo1=' lim_dyn  : strength  :')
96         CALL prt_ctl(tab2d_1=e12t      , clinfo1=' lim_dyn  : cell area :')
97         CALL prt_ctl(tab2d_1=at_i      , clinfo1=' lim_dyn  : at_i      :')
98         CALL prt_ctl(tab2d_1=vt_i      , clinfo1=' lim_dyn  : vt_i      :')
99         CALL prt_ctl(tab2d_1=vt_s      , clinfo1=' lim_dyn  : vt_s      :')
100         CALL prt_ctl(tab2d_1=stress1_i , clinfo1=' lim_dyn  : stress1_i :')
101         CALL prt_ctl(tab2d_1=stress2_i , clinfo1=' lim_dyn  : stress2_i :')
102         CALL prt_ctl(tab2d_1=stress12_i, clinfo1=' lim_dyn  : stress12_i:')
103         DO jl = 1, jpl
104            CALL prt_ctl_info(' ')
105            CALL prt_ctl_info(' - Category : ', ivar1=jl)
106            CALL prt_ctl_info('   ~~~~~~~~~~')
107            CALL prt_ctl(tab2d_1=a_i   (:,:,jl)   , clinfo1= ' lim_dyn  : a_i      : ')
108            CALL prt_ctl(tab2d_1=ht_i  (:,:,jl)   , clinfo1= ' lim_dyn  : ht_i     : ')
109            CALL prt_ctl(tab2d_1=ht_s  (:,:,jl)   , clinfo1= ' lim_dyn  : ht_s     : ')
110            CALL prt_ctl(tab2d_1=v_i   (:,:,jl)   , clinfo1= ' lim_dyn  : v_i      : ')
111            CALL prt_ctl(tab2d_1=v_s   (:,:,jl)   , clinfo1= ' lim_dyn  : v_s      : ')
112            CALL prt_ctl(tab2d_1=e_s   (:,:,1,jl) , clinfo1= ' lim_dyn  : e_s      : ')
113            CALL prt_ctl(tab2d_1=t_su  (:,:,jl)   , clinfo1= ' lim_dyn  : t_su     : ')
114            CALL prt_ctl(tab2d_1=t_s   (:,:,1,jl) , clinfo1= ' lim_dyn  : t_snow   : ')
115            CALL prt_ctl(tab2d_1=sm_i  (:,:,jl)   , clinfo1= ' lim_dyn  : sm_i     : ')
116            CALL prt_ctl(tab2d_1=smv_i (:,:,jl)   , clinfo1= ' lim_dyn  : smv_i    : ')
117            DO jk = 1, nlay_i
118               CALL prt_ctl_info(' ')
119               CALL prt_ctl_info(' - Layer : ', ivar1=jk)
120               CALL prt_ctl_info('   ~~~~~~~')
121               CALL prt_ctl(tab2d_1=t_i(:,:,jk,jl) , clinfo1= ' lim_dyn  : t_i      : ')
122               CALL prt_ctl(tab2d_1=e_i(:,:,jk,jl) , clinfo1= ' lim_dyn  : e_i      : ')
123            END DO
124         END DO
125      ENDIF
126      !
127      ! conservation test
128      IF( ln_limdiahsb ) CALL lim_cons_hsm(1, 'limdyn', zvi_b, zsmv_b, zei_b, zfw_b, zfs_b, zft_b)
129      !
130      IF( nn_timing == 1 )  CALL timing_stop('limdyn')
131
132   END SUBROUTINE lim_dyn
133
134
135   SUBROUTINE lim_dyn_init
136      !!-------------------------------------------------------------------
137      !!                  ***  ROUTINE lim_dyn_init  ***
138      !!
139      !! ** Purpose : Physical constants and parameters linked to the ice
140      !!      dynamics
141      !!
142      !! ** Method  :  Read the namicedyn namelist and check the ice-dynamic
143      !!       parameter values called at the first timestep (nit000)
144      !!
145      !! ** input   :   Namelist namicedyn
146      !!-------------------------------------------------------------------
147      INTEGER  ::   ios                 ! Local integer output status for namelist read
148      NAMELIST/namicedyn/ nn_limadv, nn_limadv_ord,  &
149         &                nn_icestr, ln_icestr_bvf, rn_pe_rdg, rn_pstar, rn_crhg, rn_cio, rn_creepl, rn_ecc, &
150         &                nn_nevp, rn_relast, ln_landfast, rn_gamma, rn_icebfr, rn_lfrelax
151      !!-------------------------------------------------------------------
152
153      REWIND( numnam_ice_ref )              ! Namelist namicedyn in reference namelist : Ice dynamics
154      READ  ( numnam_ice_ref, namicedyn, IOSTAT = ios, ERR = 901)
155901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicedyn in reference namelist', lwp )
156
157      REWIND( numnam_ice_cfg )              ! Namelist namicedyn in configuration namelist : Ice dynamics
158      READ  ( numnam_ice_cfg, namicedyn, IOSTAT = ios, ERR = 902 )
159902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namicedyn in configuration namelist', lwp )
160      IF(lwm) WRITE ( numoni, namicedyn )
161     
162      IF(lwp) THEN                        ! control print
163         WRITE(numout,*)
164         WRITE(numout,*) 'lim_dyn_init : ice parameters for ice dynamics '
165         WRITE(numout,*) '~~~~~~~~~~~~'
166         ! limtrp
167         WRITE(numout,*)'    choose the advection scheme (-1=Prather, 0=Ulimate-Macho)   nn_limadv     = ', nn_limadv 
168         WRITE(numout,*)'    choose the order of the scheme (if ultimate)                nn_limadv_ord = ', nn_limadv_ord 
169         ! limrhg
170         WRITE(numout,*)'    ice strength parameterization (0=Hibler 1=Rothrock)         nn_icestr     = ', nn_icestr 
171         WRITE(numout,*)'    Including brine volume in ice strength comp.                ln_icestr_bvf = ', ln_icestr_bvf
172         WRITE(numout,*)'    Ratio of ridging work to PotEner change in ridging          rn_pe_rdg     = ', rn_pe_rdg 
173         WRITE(numout,*) '   drag coefficient for oceanic stress                         rn_cio        = ', rn_cio
174         WRITE(numout,*) '   first bulk-rheology parameter                               rn_pstar      = ', rn_pstar
175         WRITE(numout,*) '   second bulk-rhelogy parameter                               rn_crhg       = ', rn_crhg
176         WRITE(numout,*) '   creep limit                                                 rn_creepl     = ', rn_creepl
177         WRITE(numout,*) '   eccentricity of the elliptical yield curve                  rn_ecc        = ', rn_ecc
178         WRITE(numout,*) '   number of iterations for subcycling                         nn_nevp       = ', nn_nevp
179         WRITE(numout,*) '   ratio of elastic timescale over ice time step               rn_relast     = ', rn_relast
180         WRITE(numout,*) '   Landfast: param (T or F)                                    ln_landfast   = ', ln_landfast
181         WRITE(numout,*) '   Landfast: fraction of ocean depth that ice must reach       rn_gamma      = ', rn_gamma
182         WRITE(numout,*) '   Landfast: maximum bottom stress per unit area of contact    rn_icebfr     = ', rn_icebfr
183         WRITE(numout,*) '   Landfast: relax time scale (s-1) to reach static friction   rn_lfrelax    = ', rn_lfrelax
184      ENDIF
185      !
186   END SUBROUTINE lim_dyn_init
187
188#else
189   !!----------------------------------------------------------------------
190   !!   Default option          Empty module           NO LIM sea-ice model
191   !!----------------------------------------------------------------------
192CONTAINS
193   SUBROUTINE lim_dyn         ! Empty routine
194   END SUBROUTINE lim_dyn
195#endif 
196
197   !!======================================================================
198END MODULE limdyn
Note: See TracBrowser for help on using the repository browser.