1 | MODULE limistate_2 |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE limistate_2 *** |
---|
4 | !! Initialisation of diagnostics ice variables |
---|
5 | !!====================================================================== |
---|
6 | !! History : 1.0 ! 01-04 (C. Ethe, G. Madec) Original code |
---|
7 | !! 2.0 ! 03-08 (G. Madec) add lim_istate_init |
---|
8 | !! ! 04-04 (S. Theetten) initialization from a file |
---|
9 | !! ! 06-07 (S. Masson) IOM to read the restart |
---|
10 | !! ! 07-10 (G. Madec) surface module |
---|
11 | !!-------------------------------------------------------------------- |
---|
12 | #if defined key_lim2 |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | !! 'key_lim2' : LIM 2.0 sea-ice model |
---|
15 | !!---------------------------------------------------------------------- |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | !! lim_istate_2 : Initialisation of diagnostics ice variables |
---|
18 | !! lim_istate_init_2 : initialization of ice state and namelist read |
---|
19 | !!---------------------------------------------------------------------- |
---|
20 | USE phycst |
---|
21 | USE par_ice_2 ! ice parameters |
---|
22 | USE dom_ice_2 |
---|
23 | USE eosbn2 ! equation of state |
---|
24 | USE lbclnk |
---|
25 | USE oce |
---|
26 | USE ice_2 |
---|
27 | USE iom |
---|
28 | USE in_out_manager |
---|
29 | |
---|
30 | IMPLICIT NONE |
---|
31 | PRIVATE |
---|
32 | |
---|
33 | PUBLIC lim_istate_2 ! routine called by lim_init_2.F90 |
---|
34 | |
---|
35 | !!! ** init namelist (namiceini) ** |
---|
36 | LOGICAL :: ln_limini = .FALSE. !: Ice initialization state |
---|
37 | REAL(wp) :: ttest = 2.0 ! threshold water temperature for initial sea ice |
---|
38 | REAL(wp) :: hninn = 0.5 ! initial snow thickness in the north |
---|
39 | REAL(wp) :: hginn = 3.0 ! initial ice thickness in the north |
---|
40 | REAL(wp) :: alinn = 0.05 ! initial leads area in the north |
---|
41 | REAL(wp) :: hnins = 0.1 ! initial snow thickness in the south |
---|
42 | REAL(wp) :: hgins = 1.0 ! initial ice thickness in the south |
---|
43 | REAL(wp) :: alins = 0.1 ! initial leads area in the south |
---|
44 | |
---|
45 | REAL(wp) :: zero = 0.e0 ! constant value = 0 |
---|
46 | REAL(wp) :: zone = 1.e0 ! constant value = 1 |
---|
47 | !!---------------------------------------------------------------------- |
---|
48 | !! LIM 2.0, UCL-LOCEAN-IPSL (2006) |
---|
49 | !! $Id$ |
---|
50 | !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) |
---|
51 | !!---------------------------------------------------------------------- |
---|
52 | |
---|
53 | CONTAINS |
---|
54 | |
---|
55 | SUBROUTINE lim_istate_2 |
---|
56 | !!------------------------------------------------------------------- |
---|
57 | !! *** ROUTINE lim_istate_2 *** |
---|
58 | !! |
---|
59 | !! ** Purpose : defined the sea-ice initial state |
---|
60 | !! |
---|
61 | !! ** Method : restart from a state defined in a binary file |
---|
62 | !! or from arbitrary sea-ice conditions |
---|
63 | !!-------------------------------------------------------------------- |
---|
64 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
65 | REAL(wp) :: zidto ! temporary scalar |
---|
66 | !-------------------------------------------------------------------- |
---|
67 | |
---|
68 | CALL lim_istate_init_2 ! reading the initials parameters of the ice |
---|
69 | |
---|
70 | IF( .NOT. ln_limini ) THEN |
---|
71 | |
---|
72 | tfu(:,:) = tfreez( sn(:,:,1) ) * tmask(:,:,1) ! freezing/melting point of sea water [Celcius] |
---|
73 | |
---|
74 | DO jj = 1, jpj |
---|
75 | DO ji = 1, jpi |
---|
76 | ! ! ice if sst <= t-freez + ttest |
---|
77 | IF( tn(ji,jj,1) - tfu(ji,jj) >= ttest ) THEN ; zidto = 0.e0 ! no ice |
---|
78 | ELSE ; zidto = 1.e0 ! ice |
---|
79 | ENDIF |
---|
80 | ! |
---|
81 | IF( fcor(ji,jj) >= 0.e0 ) THEN !-- Northern hemisphere. |
---|
82 | hicif(ji,jj) = zidto * hginn |
---|
83 | frld(ji,jj) = zidto * alinn + ( 1.0 - zidto ) * 1.0 |
---|
84 | hsnif(ji,jj) = zidto * hninn |
---|
85 | ELSE !--- Southern hemisphere. |
---|
86 | hicif(ji,jj) = zidto * hgins |
---|
87 | frld(ji,jj) = zidto * alins + ( 1.0 - zidto ) * 1.0 |
---|
88 | hsnif(ji,jj) = zidto * hnins |
---|
89 | ENDIF |
---|
90 | END DO |
---|
91 | END DO |
---|
92 | |
---|
93 | tfu(:,:) = tfu(:,:) + rt0 ! ftu converted from Celsius to Kelvin (rt0 over land) |
---|
94 | |
---|
95 | sist (:,:) = tfu(:,:) |
---|
96 | tbif (:,:,1) = tfu(:,:) |
---|
97 | tbif (:,:,2) = tfu(:,:) |
---|
98 | tbif (:,:,3) = tfu(:,:) |
---|
99 | |
---|
100 | ENDIF |
---|
101 | |
---|
102 | fsbbq (:,:) = 0.e0 |
---|
103 | qstoif(:,:) = 0.e0 |
---|
104 | u_ice (:,:) = 0.e0 |
---|
105 | v_ice (:,:) = 0.e0 |
---|
106 | |
---|
107 | !--- Moments for advection. |
---|
108 | |
---|
109 | sxice (:,:) = 0.e0 ; sxsn (:,:) = 0.e0 ; sxa (:,:) = 0.e0 |
---|
110 | syice (:,:) = 0.e0 ; sysn (:,:) = 0.e0 ; sya (:,:) = 0.e0 |
---|
111 | sxxice(:,:) = 0.e0 ; sxxsn(:,:) = 0.e0 ; sxxa (:,:) = 0.e0 |
---|
112 | syyice(:,:) = 0.e0 ; syysn(:,:) = 0.e0 ; syya (:,:) = 0.e0 |
---|
113 | sxyice(:,:) = 0.e0 ; sxysn(:,:) = 0.e0 ; sxya (:,:) = 0.e0 |
---|
114 | |
---|
115 | sxc0 (:,:) = 0.e0 ; sxc1 (:,:) = 0.e0 ; sxc2 (:,:) = 0.e0 |
---|
116 | syc0 (:,:) = 0.e0 ; syc1 (:,:) = 0.e0 ; syc2 (:,:) = 0.e0 |
---|
117 | sxxc0 (:,:) = 0.e0 ; sxxc1(:,:) = 0.e0 ; sxxc2(:,:) = 0.e0 |
---|
118 | syyc0 (:,:) = 0.e0 ; syyc1(:,:) = 0.e0 ; syyc2(:,:) = 0.e0 |
---|
119 | sxyc0 (:,:) = 0.e0 ; sxyc1(:,:) = 0.e0 ; sxyc2(:,:) = 0.e0 |
---|
120 | |
---|
121 | sxst (:,:) = 0.e0 |
---|
122 | syst (:,:) = 0.e0 |
---|
123 | sxxst (:,:) = 0.e0 |
---|
124 | syyst (:,:) = 0.e0 |
---|
125 | sxyst (:,:) = 0.e0 |
---|
126 | |
---|
127 | !-- lateral boundary conditions |
---|
128 | CALL lbc_lnk( hicif, 'T', 1. ) |
---|
129 | CALL lbc_lnk( frld , 'T', 1. ) |
---|
130 | |
---|
131 | ! C A U T I O N frld = 1 over land and lbc_lnk put zero along |
---|
132 | ! ************* closed boundaries herefore we force to one over land |
---|
133 | frld(:,:) = tms(:,:) * frld(:,:) + ( 1. - tms(:,:) ) |
---|
134 | |
---|
135 | CALL lbc_lnk( hsnif, 'T', 1. ) |
---|
136 | CALL lbc_lnk( sist , 'T', 1. , pval = rt0 ) ! set rt0 on closed boundary (required by bulk formulation) |
---|
137 | DO jk = 1, jplayersp1 |
---|
138 | CALL lbc_lnk(tbif(:,:,jk), 'T', 1. ) |
---|
139 | END DO |
---|
140 | CALL lbc_lnk( fsbbq , 'T', 1. ) |
---|
141 | CALL lbc_lnk( qstoif , 'T', 1. ) |
---|
142 | |
---|
143 | END SUBROUTINE lim_istate_2 |
---|
144 | |
---|
145 | |
---|
146 | SUBROUTINE lim_istate_init_2 |
---|
147 | !!------------------------------------------------------------------- |
---|
148 | !! *** ROUTINE lim_istate_init_2 *** |
---|
149 | !! |
---|
150 | !! ** Purpose : Definition of initial state of the ice |
---|
151 | !! |
---|
152 | !! ** Method : Read the namiceini namelist and check the parameter |
---|
153 | !! values called at the first timestep (nit000) |
---|
154 | !! |
---|
155 | !! ** input : Namelist namiceini |
---|
156 | !!------------------------------------------------------------------- |
---|
157 | INTEGER :: inum_ice |
---|
158 | INTEGER :: ji,jj |
---|
159 | |
---|
160 | NAMELIST/namiceini/ ln_limini, ttest, hninn, hginn, alinn, & |
---|
161 | & hnins, hgins, alins |
---|
162 | !!------------------------------------------------------------------- |
---|
163 | ! |
---|
164 | REWIND ( numnam_ice ) ! Read Namelist namiceini |
---|
165 | READ ( numnam_ice , namiceini ) |
---|
166 | ! |
---|
167 | IF(lwp) THEN |
---|
168 | WRITE(numout,*) |
---|
169 | WRITE(numout,*) 'lim_istate_init_2 : ice parameters inititialisation ' |
---|
170 | WRITE(numout,*) '~~~~~~~~~~~~~~~~~' |
---|
171 | WRITE(numout,*) ' threshold water temp. for initial sea-ice ttest = ', ttest |
---|
172 | WRITE(numout,*) ' initial snow thickness in the north hninn = ', hninn |
---|
173 | WRITE(numout,*) ' initial ice thickness in the north hginn = ', hginn |
---|
174 | WRITE(numout,*) ' initial leads area in the north alinn = ', alinn |
---|
175 | WRITE(numout,*) ' initial snow thickness in the south hnins = ', hnins |
---|
176 | WRITE(numout,*) ' initial ice thickness in the south hgins = ', hgins |
---|
177 | WRITE(numout,*) ' initial leads area in the south alins = ', alins |
---|
178 | WRITE(numout,*) ' Ice state initialization using input file ln_limini = ', ln_limini |
---|
179 | ENDIF |
---|
180 | |
---|
181 | IF( ln_limini ) THEN ! Ice initialization using input file |
---|
182 | ! |
---|
183 | CALL iom_open( 'Ice_initialization.nc', inum_ice ) |
---|
184 | ! |
---|
185 | IF( inum_ice > 0 ) THEN |
---|
186 | IF(lwp) WRITE(numout,*) |
---|
187 | IF(lwp) WRITE(numout,*) ' ice state initialization with : Ice_initialization.nc' |
---|
188 | |
---|
189 | CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif ) |
---|
190 | CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif ) |
---|
191 | CALL iom_get( inum_ice, jpdom_data, 'frld' , frld ) |
---|
192 | CALL iom_get( inum_ice, jpdom_data, 'ts' , sist ) |
---|
193 | CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(1:nlci,1:nlcj,:), & |
---|
194 | & kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) ) |
---|
195 | ! put some values in the extra-halo... |
---|
196 | DO jj = nlcj+1, jpj ; tbif(1:nlci,jj,:) = tbif(1:nlci,nlej,:) ; END DO |
---|
197 | DO ji = nlci+1, jpi ; tbif(ji ,: ,:) = tbif(nlei ,: ,:) ; END DO |
---|
198 | |
---|
199 | CALL iom_close( inum_ice) |
---|
200 | ! |
---|
201 | ENDIF |
---|
202 | ENDIF |
---|
203 | ! |
---|
204 | END SUBROUTINE lim_istate_init_2 |
---|
205 | |
---|
206 | #else |
---|
207 | !!---------------------------------------------------------------------- |
---|
208 | !! Default option : Empty module NO LIM 2.0 sea-ice model |
---|
209 | !!---------------------------------------------------------------------- |
---|
210 | CONTAINS |
---|
211 | SUBROUTINE lim_istate_2 ! Empty routine |
---|
212 | END SUBROUTINE lim_istate_2 |
---|
213 | #endif |
---|
214 | |
---|
215 | !!====================================================================== |
---|
216 | END MODULE limistate_2 |
---|