1 | MODULE icbini |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE icbini *** |
---|
4 | !! Icebergs: initialise variables for iceberg tracking |
---|
5 | !!====================================================================== |
---|
6 | !! History : - ! 2010-01 (T. Martin & A. Adcroft) Original code |
---|
7 | !! 3.3 ! 2011-03 (G. Madec) Part conversion to NEMO form ; Removal of mapping from another grid |
---|
8 | !! - ! 2011-04 (S. Alderson) Split into separate modules ; Restore restart routines |
---|
9 | !! - ! 2011-05 (S. Alderson) generate_test_icebergs restored ; new forcing arrays with extra halo ; |
---|
10 | !! - ! north fold exchange arrays added |
---|
11 | !!---------------------------------------------------------------------- |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! icb_init : initialise icebergs |
---|
14 | !! icb_ini_gen : generate test icebergs |
---|
15 | !! icb_nam : read iceberg namelist |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | USE dom_oce ! ocean domain |
---|
18 | USE in_out_manager ! IO routines and numout in particular |
---|
19 | USE lib_mpp ! mpi library and lk_mpp in particular |
---|
20 | USE sbc_oce ! ocean : surface boundary condition |
---|
21 | USE sbc_ice ! sea-ice: surface boundary condition |
---|
22 | USE iom ! IOM library |
---|
23 | USE fldread ! field read |
---|
24 | USE lbclnk ! lateral boundary condition - MPP link |
---|
25 | ! |
---|
26 | USE icb_oce ! define iceberg arrays |
---|
27 | USE icbutl ! iceberg utility routines |
---|
28 | USE icbrst ! iceberg restart routines |
---|
29 | USE icbtrj ! iceberg trajectory I/O routines |
---|
30 | USE icbdia ! iceberg budget routines |
---|
31 | |
---|
32 | IMPLICIT NONE |
---|
33 | PRIVATE |
---|
34 | |
---|
35 | PUBLIC icb_init ! routine called in nemogcm.F90 module |
---|
36 | |
---|
37 | CHARACTER(len=100) :: cn_dir = './' !: Root directory for location of icb files |
---|
38 | TYPE(FLD_N) :: sn_icb !: information about the calving file to be read |
---|
39 | TYPE(FLD), PUBLIC, ALLOCATABLE , DIMENSION(:) :: sf_icb !: structure: file information, fields read |
---|
40 | !: used in icbini and icbstp |
---|
41 | !!---------------------------------------------------------------------- |
---|
42 | !! NEMO/OPA 3.3 , NEMO Consortium (2011) |
---|
43 | !! $Id$ |
---|
44 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
45 | !!---------------------------------------------------------------------- |
---|
46 | CONTAINS |
---|
47 | |
---|
48 | SUBROUTINE icb_init( pdt, kt ) |
---|
49 | !!---------------------------------------------------------------------- |
---|
50 | !! *** ROUTINE dom_init *** |
---|
51 | !! |
---|
52 | !! ** Purpose : iceberg initialization. |
---|
53 | !! |
---|
54 | !! ** Method : - read the iceberg namelist |
---|
55 | !! - find non-overlapping processor interior since we can only |
---|
56 | !! have one instance of a particular iceberg |
---|
57 | !! - calculate the destinations for north fold exchanges |
---|
58 | !! - setup either test icebergs or calving file |
---|
59 | !!---------------------------------------------------------------------- |
---|
60 | REAL(wp), INTENT(in) :: pdt ! iceberg time-step (rdt*nn_fsbc) |
---|
61 | INTEGER , INTENT(in) :: kt ! time step number |
---|
62 | ! |
---|
63 | INTEGER :: ji, jj, jn ! dummy loop indices |
---|
64 | INTEGER :: i1, i2, i3 ! local integers |
---|
65 | INTEGER :: ii, inum, ivar ! - - |
---|
66 | INTEGER :: istat1, istat2, istat3 ! - - |
---|
67 | CHARACTER(len=300) :: cl_sdist ! local character |
---|
68 | !!---------------------------------------------------------------------- |
---|
69 | ! |
---|
70 | CALL icb_nam ! Read and print namelist parameters |
---|
71 | ! |
---|
72 | IF( .NOT. ln_icebergs ) RETURN |
---|
73 | |
---|
74 | ! ! allocate gridded fields |
---|
75 | IF( icb_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'icb_alloc : unable to allocate arrays' ) |
---|
76 | |
---|
77 | ! ! open ascii output file or files for iceberg status information |
---|
78 | ! ! note that we choose to do this on all processors since we cannot |
---|
79 | ! ! predict where icebergs will be ahead of time |
---|
80 | CALL ctl_opn( numicb, 'icebergs.stat', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) |
---|
81 | |
---|
82 | ! set parameters (mostly from namelist) |
---|
83 | ! |
---|
84 | berg_dt = pdt |
---|
85 | first_width (:) = SQRT( rn_initial_mass(:) / ( rn_LoW_ratio * rn_rho_bergs * rn_initial_thickness(:) ) ) |
---|
86 | first_length(:) = rn_LoW_ratio * first_width(:) |
---|
87 | |
---|
88 | berg_grid%calving (:,:) = 0._wp |
---|
89 | berg_grid%calving_hflx (:,:) = 0._wp |
---|
90 | berg_grid%stored_heat (:,:) = 0._wp |
---|
91 | berg_grid%floating_melt(:,:) = 0._wp |
---|
92 | berg_grid%maxclass (:,:) = nclasses |
---|
93 | berg_grid%stored_ice (:,:,:) = 0._wp |
---|
94 | berg_grid%tmp (:,:) = 0._wp |
---|
95 | src_calving (:,:) = 0._wp |
---|
96 | src_calving_hflx (:,:) = 0._wp |
---|
97 | |
---|
98 | ! ! domain for icebergs |
---|
99 | IF( lk_mpp .AND. jpni == 1 ) CALL ctl_stop( 'icbinit: having ONE processor in x currently does not work' ) |
---|
100 | ! NB: the issue here is simply that cyclic east-west boundary condition have not been coded in mpp case |
---|
101 | ! for the north fold we work out which points communicate by asking |
---|
102 | ! lbc_lnk to pass processor number (valid even in single processor case) |
---|
103 | ! borrow src_calving arrays for this |
---|
104 | ! |
---|
105 | ! pack i and j together using a scaling of a power of 10 |
---|
106 | nicbpack = 10000 |
---|
107 | IF( jpiglo >= nicbpack ) CALL ctl_stop( 'icbini: processor index packing failure' ) |
---|
108 | nicbfldproc(:) = -1 |
---|
109 | |
---|
110 | DO jj = 1, jpj |
---|
111 | DO ji = 1, jpi |
---|
112 | src_calving_hflx(ji,jj) = narea |
---|
113 | src_calving (ji,jj) = nicbpack * mjg(jj) + mig(ji) |
---|
114 | END DO |
---|
115 | END DO |
---|
116 | CALL lbc_lnk( src_calving_hflx, 'T', 1._wp ) |
---|
117 | CALL lbc_lnk( src_calving , 'T', 1._wp ) |
---|
118 | |
---|
119 | ! work out interior of processor from exchange array |
---|
120 | ! first entry with narea for this processor is left hand interior index |
---|
121 | ! last entry is right hand interior index |
---|
122 | jj = nlcj/2 |
---|
123 | nicbdi = -1 |
---|
124 | nicbei = -1 |
---|
125 | DO ji = 1, jpi |
---|
126 | i3 = INT( src_calving(ji,jj) ) |
---|
127 | i2 = INT( i3/nicbpack ) |
---|
128 | i1 = i3 - i2*nicbpack |
---|
129 | i3 = INT( src_calving_hflx(ji,jj) ) |
---|
130 | IF( i1 == mig(ji) .AND. i3 == narea ) THEN |
---|
131 | IF( nicbdi < 0 ) THEN ; nicbdi = ji |
---|
132 | ELSE ; nicbei = ji |
---|
133 | ENDIF |
---|
134 | ENDIF |
---|
135 | END DO |
---|
136 | ! |
---|
137 | ! repeat for j direction |
---|
138 | ji = nlci/2 |
---|
139 | nicbdj = -1 |
---|
140 | nicbej = -1 |
---|
141 | DO jj = 1, jpj |
---|
142 | i3 = INT( src_calving(ji,jj) ) |
---|
143 | i2 = INT( i3/nicbpack ) |
---|
144 | i1 = i3 - i2*nicbpack |
---|
145 | i3 = INT( src_calving_hflx(ji,jj) ) |
---|
146 | IF( i2 == mjg(jj) .AND. i3 == narea ) THEN |
---|
147 | IF( nicbdj < 0 ) THEN ; nicbdj = jj |
---|
148 | ELSE ; nicbej = jj |
---|
149 | ENDIF |
---|
150 | ENDIF |
---|
151 | END DO |
---|
152 | ! |
---|
153 | ! special for east-west boundary exchange we save the destination index |
---|
154 | i1 = MAX( nicbdi-1, 1) |
---|
155 | i3 = INT( src_calving(i1,nlcj/2) ) |
---|
156 | jj = INT( i3/nicbpack ) |
---|
157 | ricb_left = REAL( i3 - nicbpack*jj, wp ) |
---|
158 | i1 = MIN( nicbei+1, jpi ) |
---|
159 | i3 = INT( src_calving(i1,nlcj/2) ) |
---|
160 | jj = INT( i3/nicbpack ) |
---|
161 | ricb_right = REAL( i3 - nicbpack*jj, wp ) |
---|
162 | |
---|
163 | ! north fold |
---|
164 | IF( npolj > 0 ) THEN |
---|
165 | ! |
---|
166 | ! icebergs in row nicbej+1 get passed across fold |
---|
167 | nicbfldpts(:) = INT( src_calving(:,nicbej+1) ) |
---|
168 | nicbflddest(:) = INT( src_calving_hflx(:,nicbej+1) ) |
---|
169 | ! |
---|
170 | ! work out list of unique processors to talk to |
---|
171 | ! pack them into a fixed size array where empty slots are marked by a -1 |
---|
172 | DO ji = nicbdi, nicbei |
---|
173 | ii = nicbflddest(ji) |
---|
174 | IF( ii .GT. 0 ) THEN ! Needed because land suppression can mean |
---|
175 | ! that unused points are not set in edge haloes |
---|
176 | DO jn = 1, jpni |
---|
177 | ! work along array until we find an empty slot |
---|
178 | IF( nicbfldproc(jn) == -1 ) THEN |
---|
179 | nicbfldproc(jn) = ii |
---|
180 | EXIT !!gm EXIT should be avoided: use DO WHILE expression instead |
---|
181 | ENDIF |
---|
182 | ! before we find an empty slot, we may find processor number is already here so we exit |
---|
183 | IF( nicbfldproc(jn) == ii ) EXIT |
---|
184 | END DO |
---|
185 | ENDIF |
---|
186 | END DO |
---|
187 | ENDIF |
---|
188 | ! |
---|
189 | IF( nn_verbose_level > 0) THEN |
---|
190 | WRITE(numicb,*) 'processor ', narea |
---|
191 | WRITE(numicb,*) 'jpi, jpj ', jpi, jpj |
---|
192 | WRITE(numicb,*) 'nldi, nlei ', nldi, nlei |
---|
193 | WRITE(numicb,*) 'nldj, nlej ', nldj, nlej |
---|
194 | WRITE(numicb,*) 'berg i interior ', nicbdi, nicbei |
---|
195 | WRITE(numicb,*) 'berg j interior ', nicbdj, nicbej |
---|
196 | WRITE(numicb,*) 'berg left ', ricb_left |
---|
197 | WRITE(numicb,*) 'berg right ', ricb_right |
---|
198 | jj = nlcj/2 |
---|
199 | WRITE(numicb,*) "central j line:" |
---|
200 | WRITE(numicb,*) "i processor" |
---|
201 | WRITE(numicb,*) (INT(src_calving_hflx(ji,jj)), ji=1,jpi) |
---|
202 | WRITE(numicb,*) "i point" |
---|
203 | WRITE(numicb,*) (INT(src_calving(ji,jj)), ji=1,jpi) |
---|
204 | ji = nlci/2 |
---|
205 | WRITE(numicb,*) "central i line:" |
---|
206 | WRITE(numicb,*) "j processor" |
---|
207 | WRITE(numicb,*) (INT(src_calving_hflx(ji,jj)), jj=1,jpj) |
---|
208 | WRITE(numicb,*) "j point" |
---|
209 | WRITE(numicb,*) (INT(src_calving(ji,jj)), jj=1,jpj) |
---|
210 | IF( npolj > 0 ) THEN |
---|
211 | WRITE(numicb,*) 'north fold destination points ' |
---|
212 | WRITE(numicb,*) nicbfldpts |
---|
213 | WRITE(numicb,*) 'north fold destination procs ' |
---|
214 | WRITE(numicb,*) nicbflddest |
---|
215 | WRITE(numicb,*) 'north fold destination proclist ' |
---|
216 | WRITE(numicb,*) nicbfldproc |
---|
217 | ENDIF |
---|
218 | CALL flush(numicb) |
---|
219 | ENDIF |
---|
220 | |
---|
221 | src_calving (:,:) = 0._wp |
---|
222 | src_calving_hflx(:,:) = 0._wp |
---|
223 | |
---|
224 | ! assign each new iceberg with a unique number constructed from the processor number |
---|
225 | ! and incremented by the total number of processors |
---|
226 | num_bergs(:) = 0 |
---|
227 | num_bergs(1) = narea - jpnij |
---|
228 | |
---|
229 | ! when not generating test icebergs we need to setup calving file |
---|
230 | IF( nn_test_icebergs < 0 ) THEN |
---|
231 | ! |
---|
232 | ! maximum distribution class array does not change in time so read it once |
---|
233 | cl_sdist = TRIM( cn_dir )//TRIM( sn_icb%clname ) |
---|
234 | CALL iom_open ( cl_sdist, inum ) ! open file |
---|
235 | ivar = iom_varid( inum, 'maxclass', ldstop=.FALSE. ) |
---|
236 | IF( ivar > 0 ) THEN |
---|
237 | CALL iom_get ( inum, jpdom_data, 'maxclass', src_calving ) ! read the max distribution array |
---|
238 | berg_grid%maxclass(:,:) = INT( src_calving ) |
---|
239 | src_calving(:,:) = 0._wp |
---|
240 | ENDIF |
---|
241 | CALL iom_close( inum ) ! close file |
---|
242 | ! |
---|
243 | WRITE(numicb,*) |
---|
244 | WRITE(numicb,*) ' calving read in a file' |
---|
245 | ALLOCATE( sf_icb(1), STAT=istat1 ) ! Create sf_icb structure (calving) |
---|
246 | ALLOCATE( sf_icb(1)%fnow(jpi,jpj,1), STAT=istat2 ) |
---|
247 | ALLOCATE( sf_icb(1)%fdta(jpi,jpj,1,2), STAT=istat3 ) |
---|
248 | IF( istat1+istat2+istat3 > 0 ) THEN |
---|
249 | CALL ctl_stop( 'sbc_icb: unable to allocate sf_icb structure' ) ; RETURN |
---|
250 | ENDIF |
---|
251 | ! ! fill sf_icb with the namelist (sn_icb) and control print |
---|
252 | CALL fld_fill( sf_icb, (/ sn_icb /), cn_dir, 'icb_init', 'read calving data', 'namicb' ) |
---|
253 | ! |
---|
254 | ENDIF |
---|
255 | |
---|
256 | IF( .NOT.ln_rstart ) THEN |
---|
257 | IF( nn_test_icebergs > 0 ) CALL icb_ini_gen() |
---|
258 | ELSE |
---|
259 | IF( nn_test_icebergs > 0 ) THEN |
---|
260 | CALL icb_ini_gen() |
---|
261 | ELSE |
---|
262 | CALL icb_rst_read() |
---|
263 | l_restarted_bergs = .TRUE. |
---|
264 | ENDIF |
---|
265 | ENDIF |
---|
266 | ! |
---|
267 | IF( nn_sample_rate .GT. 0 ) CALL icb_trj_init( nitend ) |
---|
268 | ! |
---|
269 | CALL icb_dia_init() |
---|
270 | ! |
---|
271 | IF( nn_verbose_level >= 2 ) CALL icb_utl_print('icb_init, initial status', nit000-1) |
---|
272 | ! |
---|
273 | END SUBROUTINE icb_init |
---|
274 | |
---|
275 | |
---|
276 | SUBROUTINE icb_ini_gen() |
---|
277 | !!---------------------------------------------------------------------- |
---|
278 | !! *** ROUTINE icb_ini_gen *** |
---|
279 | !! |
---|
280 | !! ** Purpose : iceberg generation |
---|
281 | !! |
---|
282 | !! ** Method : - at each grid point of the test box supplied in the namelist |
---|
283 | !! generate an iceberg in one class determined by the value of |
---|
284 | !! parameter nn_test_icebergs |
---|
285 | !!---------------------------------------------------------------------- |
---|
286 | INTEGER :: ji, jj, ibergs |
---|
287 | TYPE(iceberg) :: localberg ! NOT a pointer but an actual local variable |
---|
288 | TYPE(point) :: localpt |
---|
289 | INTEGER :: iyr, imon, iday, ihr, imin, isec |
---|
290 | INTEGER :: iberg |
---|
291 | !!---------------------------------------------------------------------- |
---|
292 | |
---|
293 | ! For convenience |
---|
294 | iberg = nn_test_icebergs |
---|
295 | |
---|
296 | ! call get_date(Time, iyr, imon, iday, ihr, imin, isec) |
---|
297 | ! Convert nemo time variables from dom_oce into local versions |
---|
298 | iyr = nyear |
---|
299 | imon = nmonth |
---|
300 | iday = nday |
---|
301 | ihr = INT(nsec_day/3600) |
---|
302 | imin = INT((nsec_day-ihr*3600)/60) |
---|
303 | isec = nsec_day - ihr*3600 - imin*60 |
---|
304 | |
---|
305 | ! no overlap for icebergs since we want only one instance of each across the whole domain |
---|
306 | ! so restrict area of interest |
---|
307 | ! use tmask here because tmask_i has been doctored on one side of the north fold line |
---|
308 | |
---|
309 | DO jj = nicbdj, nicbej |
---|
310 | DO ji = nicbdi, nicbei |
---|
311 | IF( tmask(ji,jj,1) > 0._wp .AND. & |
---|
312 | rn_test_box(1) < glamt(ji,jj) .AND. glamt(ji,jj) < rn_test_box(2) .AND. & |
---|
313 | rn_test_box(3) < gphit(ji,jj) .AND. gphit(ji,jj) < rn_test_box(4) ) THEN |
---|
314 | localberg%mass_scaling = rn_mass_scaling(iberg) |
---|
315 | localpt%xi = REAL( mig(ji), wp ) |
---|
316 | localpt%yj = REAL( mjg(jj), wp ) |
---|
317 | localpt%lon = icb_utl_bilin(glamt, localpt%xi, localpt%yj, 'T' ) |
---|
318 | localpt%lat = icb_utl_bilin(gphit, localpt%xi, localpt%yj, 'T' ) |
---|
319 | localpt%mass = rn_initial_mass (iberg) |
---|
320 | localpt%thickness = rn_initial_thickness(iberg) |
---|
321 | localpt%width = first_width (iberg) |
---|
322 | localpt%length = first_length(iberg) |
---|
323 | localpt%year = iyr |
---|
324 | localpt%day = REAL(iday,wp)+(REAL(ihr,wp)+REAL(imin,wp)/60._wp)/24._wp |
---|
325 | localpt%mass_of_bits = 0._wp |
---|
326 | localpt%heat_density = 0._wp |
---|
327 | localpt%uvel = 0._wp |
---|
328 | localpt%vvel = 0._wp |
---|
329 | CALL icb_utl_incr() |
---|
330 | localberg%number(:) = num_bergs(:) |
---|
331 | call icb_utl_add(localberg, localpt) |
---|
332 | ENDIF |
---|
333 | END DO |
---|
334 | END DO |
---|
335 | ! |
---|
336 | ibergs = icb_utl_count() |
---|
337 | IF( lk_mpp ) CALL mpp_sum(ibergs) |
---|
338 | WRITE(numicb,'(a,i6,a)') 'diamonds, icb_ini_gen: ',ibergs,' were generated' |
---|
339 | ! |
---|
340 | END SUBROUTINE icb_ini_gen |
---|
341 | |
---|
342 | |
---|
343 | SUBROUTINE icb_nam |
---|
344 | !!---------------------------------------------------------------------- |
---|
345 | !! *** ROUTINE icb_nam *** |
---|
346 | !! |
---|
347 | !! ** Purpose : read iceberg namelist and print the variables. |
---|
348 | !! |
---|
349 | !! ** input : - namberg namelist |
---|
350 | !!---------------------------------------------------------------------- |
---|
351 | INTEGER :: jn ! dummy loop indices |
---|
352 | INTEGER :: ios ! Local integer output status for namelist read |
---|
353 | REAL(wp) :: zfact ! local scalar |
---|
354 | ! |
---|
355 | NAMELIST/namberg/ ln_icebergs , ln_bergdia , nn_sample_rate , rn_initial_mass , & |
---|
356 | & rn_distribution, rn_mass_scaling, rn_initial_thickness, nn_verbose_write , & |
---|
357 | & rn_rho_bergs , rn_LoW_ratio , nn_verbose_level , ln_operator_splitting, & |
---|
358 | & rn_bits_erosion_fraction , rn_sicn_shift , ln_passive_mode , & |
---|
359 | & ln_time_average_weight , nn_test_icebergs , rn_test_box , & |
---|
360 | & rn_speed_limit , cn_dir, sn_icb |
---|
361 | !!---------------------------------------------------------------------- |
---|
362 | |
---|
363 | #if !defined key_agrif |
---|
364 | REWIND( numnam_ref ) ! Namelist namberg in reference namelist : Iceberg parameters |
---|
365 | READ ( numnam_ref, namberg, IOSTAT = ios, ERR = 901) |
---|
366 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in reference namelist', lwp ) |
---|
367 | REWIND( numnam_cfg ) ! Namelist namberg in configuration namelist : Iceberg parameters |
---|
368 | READ ( numnam_cfg, namberg, IOSTAT = ios, ERR = 902 ) |
---|
369 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namberg in configuration namelist', lwp ) |
---|
370 | IF(lwm) WRITE ( numond, namberg ) |
---|
371 | #else |
---|
372 | IF(lwp) THEN |
---|
373 | WRITE(numout,*) |
---|
374 | WRITE(numout,*) 'icbini : AGRIF is not compatible with namelist namberg : ' |
---|
375 | WRITE(numout,*) ' definition of rn_initial_mass(nclasses) with nclasses as PARAMETER ' |
---|
376 | WRITE(numout,*) ' namelist namberg not read' |
---|
377 | ENDIF |
---|
378 | ln_icebergs = .false. |
---|
379 | #endif |
---|
380 | IF( .NOT. ln_icebergs ) THEN ! no icebergs |
---|
381 | IF(lwp) THEN |
---|
382 | WRITE(numout,*) |
---|
383 | WRITE(numout,*) 'icbini : Namelist namberg ln_icebergs = F , NO icebergs used' |
---|
384 | WRITE(numout,*) '~~~~~~~~ ' |
---|
385 | ENDIF |
---|
386 | RETURN |
---|
387 | ENDIF |
---|
388 | |
---|
389 | IF( nn_test_icebergs > nclasses ) THEN |
---|
390 | IF(lwp) WRITE(numout,*) 'Resetting nn_test_icebergs to ', nclasses |
---|
391 | nn_test_icebergs = nclasses |
---|
392 | ENDIF |
---|
393 | |
---|
394 | zfact = SUM( rn_distribution ) |
---|
395 | IF( zfact < 1._wp ) THEN |
---|
396 | IF( zfact <= 0._wp ) THEN |
---|
397 | |
---|
398 | ELSE |
---|
399 | rn_distribution(:) = rn_distribution(:) / zfact |
---|
400 | CALL ctl_warn( 'icb_nam: sum of berg input distribution not equal to one and so RESCALED' ) |
---|
401 | ENDIF |
---|
402 | ENDIF |
---|
403 | |
---|
404 | ! IF( lk_lim3 .AND. ln_icebergs ) THEN |
---|
405 | ! CALL ctl_stop( 'icb_nam: the use of ICB with LIM3 not allowed. ice thickness missing in ICB' ) |
---|
406 | ! ENDIF |
---|
407 | |
---|
408 | IF(lwp) THEN ! control print |
---|
409 | WRITE(numout,*) |
---|
410 | WRITE(numout,*) 'icb_nam : iceberg initialization through namberg namelist read' |
---|
411 | WRITE(numout,*) '~~~~~~~~ ' |
---|
412 | WRITE(numout,*) ' Calculate budgets ln_bergdia = ', ln_bergdia |
---|
413 | WRITE(numout,*) ' Period between sampling of position for trajectory storage nn_sample_rate = ', nn_sample_rate |
---|
414 | WRITE(numout,*) ' Mass thresholds between iceberg classes (kg) rn_initial_mass =' |
---|
415 | DO jn=1,nclasses |
---|
416 | WRITE(numout,'(a,f15.2)') ' ',rn_initial_mass(jn) |
---|
417 | ENDDO |
---|
418 | WRITE(numout,*) ' Fraction of calving to apply to this class (non-dim) rn_distribution =' |
---|
419 | DO jn = 1, nclasses |
---|
420 | WRITE(numout,'(a,f10.2)') ' ',rn_distribution(jn) |
---|
421 | END DO |
---|
422 | WRITE(numout,*) ' Ratio between effective and real iceberg mass (non-dim) rn_mass_scaling = ' |
---|
423 | DO jn = 1, nclasses |
---|
424 | WRITE(numout,'(a,f10.2)') ' ',rn_mass_scaling(jn) |
---|
425 | END DO |
---|
426 | WRITE(numout,*) ' Total thickness of newly calved bergs (m) rn_initial_thickness = ' |
---|
427 | DO jn = 1, nclasses |
---|
428 | WRITE(numout,'(a,f10.2)') ' ',rn_initial_thickness(jn) |
---|
429 | END DO |
---|
430 | WRITE(numout,*) ' Timesteps between verbose messages nn_verbose_write = ', nn_verbose_write |
---|
431 | |
---|
432 | WRITE(numout,*) ' Density of icebergs rn_rho_bergs = ', rn_rho_bergs |
---|
433 | WRITE(numout,*) ' Initial ratio L/W for newly calved icebergs rn_LoW_ratio = ', rn_LoW_ratio |
---|
434 | WRITE(numout,*) ' Turn on more verbose output level = ', nn_verbose_level |
---|
435 | WRITE(numout,*) ' Use first order operator splitting for thermodynamics ', & |
---|
436 | & 'use_operator_splitting = ', ln_operator_splitting |
---|
437 | WRITE(numout,*) ' Fraction of erosion melt flux to divert to bergy bits ', & |
---|
438 | & 'bits_erosion_fraction = ', rn_bits_erosion_fraction |
---|
439 | |
---|
440 | WRITE(numout,*) ' Shift of sea-ice concentration in erosion flux modulation ', & |
---|
441 | & '(0<sicn_shift<1) rn_sicn_shift = ', rn_sicn_shift |
---|
442 | WRITE(numout,*) ' Do not add freshwater flux from icebergs to ocean ', & |
---|
443 | & ' passive_mode = ', ln_passive_mode |
---|
444 | WRITE(numout,*) ' Time average the weight on the ocean time_average_weight = ', ln_time_average_weight |
---|
445 | WRITE(numout,*) ' Create icebergs in absence of a restart file nn_test_icebergs = ', nn_test_icebergs |
---|
446 | WRITE(numout,*) ' in lon/lat box = ', rn_test_box |
---|
447 | WRITE(numout,*) ' CFL speed limit for a berg speed_limit = ', rn_speed_limit |
---|
448 | WRITE(numout,*) ' Writing Iceberg status information to icebergs.stat file ' |
---|
449 | ENDIF |
---|
450 | ! |
---|
451 | END SUBROUTINE icb_nam |
---|
452 | |
---|
453 | !!====================================================================== |
---|
454 | END MODULE icbini |
---|