1 | MODULE limdmp_2 |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE limdmp_2 *** |
---|
4 | !! LIM-2 ice model : restoring Ice thickness and Fraction leads |
---|
5 | !!====================================================================== |
---|
6 | !! History : 2.0 ! 2004-04 (S. Theetten) Original code |
---|
7 | !! 3.3 ! 2010-06 (J.-M. Molines) use of fldread |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | #if defined key_lim2 |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! 'key_lim2' LIM 2.0 sea-ice model |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! lim_dmp_2 : ice model damping |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE ice_2 ! ice variables |
---|
16 | USE sbc_oce, ONLY : nn_fsbc ! for fldread |
---|
17 | USE dom_oce ! for mi0; mi1 etc ... |
---|
18 | USE fldread ! read input fields |
---|
19 | USE in_out_manager ! I/O manager |
---|
20 | USE lib_mpp ! MPP library |
---|
21 | USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) |
---|
22 | |
---|
23 | IMPLICIT NONE |
---|
24 | PRIVATE |
---|
25 | |
---|
26 | PUBLIC lim_dmp_2 ! called by sbc_ice_lim2 |
---|
27 | |
---|
28 | REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: resto_ice ! restoring coeff. on ICE [s-1] |
---|
29 | |
---|
30 | INTEGER, PARAMETER :: jp_hicif = 1 , jp_frld = 2 |
---|
31 | TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_icedmp ! structure of ice damping input |
---|
32 | |
---|
33 | !! * Substitution |
---|
34 | # include "vectopt_loop_substitute.h90" |
---|
35 | !!---------------------------------------------------------------------- |
---|
36 | !! NEMO/LIM 3.3 , UCL-NEMO-consortium (2010) |
---|
37 | !! $Id$ |
---|
38 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
39 | !!---------------------------------------------------------------------- |
---|
40 | CONTAINS |
---|
41 | |
---|
42 | SUBROUTINE lim_dmp_2( kt ) |
---|
43 | !!------------------------------------------------------------------- |
---|
44 | !! *** ROUTINE lim_dmp_2 *** |
---|
45 | !! |
---|
46 | !! ** purpose : ice model damping : restoring ice thickness and fraction leads |
---|
47 | !! |
---|
48 | !! ** method : the key_tradmp must be used to compute resto(:,:,1) coef. |
---|
49 | !!--------------------------------------------------------------------- |
---|
50 | INTEGER, INTENT(in) :: kt ! ocean time-step |
---|
51 | ! |
---|
52 | INTEGER :: ji, jj ! dummy loop indices |
---|
53 | REAL(wp) :: zfrld, zhice ! local scalars |
---|
54 | !!--------------------------------------------------------------------- |
---|
55 | ! |
---|
56 | IF (kt == nit000) THEN |
---|
57 | IF(lwp) WRITE(numout,*) |
---|
58 | IF(lwp) WRITE(numout,*) 'lim_dmp_2 : Ice thickness and ice concentration restoring' |
---|
59 | IF(lwp) WRITE(numout,*) '~~~~~~~~~~' |
---|
60 | ! |
---|
61 | ! ice_resto_init create resto_ice (in 1/s) for restoring ice parameters near open boundaries. |
---|
62 | ! Double check this routine to verify if it corresponds to your config |
---|
63 | CALL lim_dmp_init |
---|
64 | ENDIF |
---|
65 | ! |
---|
66 | IF( ln_limdmp ) THEN ! ice restoring in this case |
---|
67 | ! |
---|
68 | CALL fld_read( kt, nn_fsbc, sf_icedmp ) |
---|
69 | ! |
---|
70 | !CDIR COLLAPSE |
---|
71 | hicif(:,:) = MAX( 0._wp, & ! h >= 0 avoid spurious out of physical range |
---|
72 | & hicif(:,:) - rdt_ice * resto_ice(:,:,1) * ( hicif(:,:) - sf_icedmp(jp_hicif)%fnow(:,:,1) ) ) |
---|
73 | !CDIR COLLAPSE |
---|
74 | hicif(:,:) = MAX( 0._wp, MIN( 1._wp, & ! 0<= frld<=1 values which blow the run up |
---|
75 | & frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) ) ) ) |
---|
76 | ! |
---|
77 | ENDIF |
---|
78 | ! |
---|
79 | END SUBROUTINE lim_dmp_2 |
---|
80 | |
---|
81 | |
---|
82 | SUBROUTINE lim_dmp_init |
---|
83 | !!---------------------------------------------------------------------- |
---|
84 | !! *** ROUTINE lim_dmp_init *** |
---|
85 | !! |
---|
86 | !! ** Purpose : Initialization for the ice thickness and concentration |
---|
87 | !! restoring |
---|
88 | !! restoring will be used. It is used to mimic ice open |
---|
89 | !! boundaries. |
---|
90 | !! |
---|
91 | !! ** Method : ????? |
---|
92 | !! |
---|
93 | !! ** Action : define resto_ice(:,:,1) |
---|
94 | !!---------------------------------------------------------------------- |
---|
95 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
96 | INTEGER :: irelax, ierror ! error flag for allocation |
---|
97 | ! |
---|
98 | REAL(wp) :: zdmpmax, zdmpmin, zfactor, zreltim ! temporary scalar |
---|
99 | ! |
---|
100 | CHARACTER(len=100) :: cn_dir ! Root directory for location of ssr files |
---|
101 | TYPE(FLD_N), DIMENSION (2) :: sl_icedmp ! informations about the icedmp field to be read |
---|
102 | TYPE(FLD_N) :: sn_hicif ! |
---|
103 | TYPE(FLD_N) :: sn_frld ! |
---|
104 | NAMELIST/namice_dmp/ cn_dir, ln_limdmp, sn_hicif, sn_frld |
---|
105 | !!---------------------------------------------------------------------- |
---|
106 | ! |
---|
107 | ! 1) initialize fld read structure for input data |
---|
108 | ! -------------------------------------------- |
---|
109 | ln_limdmp = .false. !* set file information (default values) |
---|
110 | cn_dir = './' |
---|
111 | ! (NB: frequency positive => hours, negative => months) |
---|
112 | ! ! file ! frequency ! variable ! time intep ! clim ! 'yearly' or ! weights ! rotation ! |
---|
113 | ! ! name ! (hours) ! name ! (T/F) ! (T/F) ! 'monthly' ! filename ! pairs ! |
---|
114 | sn_hicif = FLD_N( 'ice_damping ', -1 , 'hicif' , .true. , .true. , 'yearly' , '' , '' ) |
---|
115 | sn_frld = FLD_N( 'ice_damping ', -1 , 'frld' , .true. , .true. , 'yearly' , '' , '' ) |
---|
116 | |
---|
117 | REWIND( numnam_ice ) !* read in namelist_ice namicedmp |
---|
118 | READ ( numnam_ice, namice_dmp ) |
---|
119 | ! |
---|
120 | IF ( lwp ) THEN !* control print |
---|
121 | WRITE (numout,*)' lim_dmp_init : lim_dmp initialization ' |
---|
122 | WRITE (numout,*)' Namelist namicedmp read ' |
---|
123 | WRITE (numout,*)' Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp |
---|
124 | WRITE (numout,*) |
---|
125 | WRITE (numout,*)' CAUTION : here hard coded ice restoring along northern and southern boundaries' |
---|
126 | WRITE (numout,*)' adapt the lim_dmp_init routine to your needs' |
---|
127 | ENDIF |
---|
128 | |
---|
129 | ! 2) initialise resto_ice ==> config dependant ! |
---|
130 | ! -------------------- ++++++++++++++++ |
---|
131 | ! |
---|
132 | IF( ln_limdmp ) THEN !* ice restoring is used, follow initialization |
---|
133 | ! |
---|
134 | sl_icedmp ( jp_hicif ) = sn_hicif |
---|
135 | sl_icedmp ( jp_frld ) = sn_frld |
---|
136 | ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror ) |
---|
137 | IF( ierror > 0 ) THEN |
---|
138 | CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' ) ; RETURN |
---|
139 | ENDIF |
---|
140 | ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) ) |
---|
141 | ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) ) |
---|
142 | ! ! fill sf_icedmp with sn_icedmp and control print |
---|
143 | CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice restoring input data', 'namicedmp' ) |
---|
144 | |
---|
145 | resto_ice(:,:,:) = 0._wp |
---|
146 | ! Re-calculate the North and South boundary restoring term |
---|
147 | ! because those boundaries may change with the prescribed zoom area. |
---|
148 | ! |
---|
149 | irelax = 16 ! width of buffer zone with respect to close boundary |
---|
150 | zdmpmax = 10._wp ! max restoring time scale (days) (low restoring) |
---|
151 | zdmpmin = rdt_ice / 86400._wp ! min restoring time scale (days) (high restoring) |
---|
152 | ! ! days / grid-point |
---|
153 | zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp ) |
---|
154 | |
---|
155 | ! South boundary restoring term |
---|
156 | ! REM: if there is no ice in the model and in the data, |
---|
157 | ! no restoring even with non zero resto_ice |
---|
158 | DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax) |
---|
159 | zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 ) |
---|
160 | resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp ) |
---|
161 | END DO |
---|
162 | |
---|
163 | ! North boundary restoring term |
---|
164 | DO jj = mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo) |
---|
165 | zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 )) |
---|
166 | resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 ) |
---|
167 | END DO |
---|
168 | ENDIF |
---|
169 | ! |
---|
170 | END SUBROUTINE lim_dmp_init |
---|
171 | |
---|
172 | #else |
---|
173 | !!---------------------------------------------------------------------- |
---|
174 | !! Default option Empty Module No ice damping |
---|
175 | !!---------------------------------------------------------------------- |
---|
176 | CONTAINS |
---|
177 | SUBROUTINE lim_dmp_2( kt ) ! Dummy routine |
---|
178 | WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt |
---|
179 | END SUBROUTINE lim_dmp_2 |
---|
180 | #endif |
---|
181 | |
---|
182 | !!====================================================================== |
---|
183 | END MODULE limdmp_2 |
---|