My Project
ice_init.f90
Go to the documentation of this file.
1 
2 
3 
4 
5 
6 
7 
8 
9 
10 
11 
12 !/===========================================================================/
13 ! CVS VERSION INFORMATION
14 ! $Id$
15 ! $Name$
16 ! $Revision$
17 !/===========================================================================/
18 
19 !=======================================================================
20 !BOP
21 !
22 ! !MODULE: ice_init - parameter and variable initializations
23 !
24 ! !DESCRIPTION:
25 !
26 ! parameter and variable initializations
27 !
28 ! !REVISION HISTORY:
29 !
30 ! authors Elizabeth C. Hunke, LANL
31 ! C. M. Bitz, UW
32 !
33 ! !INTERFACE:
34 !
35  module ice_init
36 !
37 ! !USES:
38 !
39  use ice_domain
40 !
41 !EOP
42 !
43  implicit none
44  save
45 
46  character (len=char_len) :: &
47  advection ! type of advection algorithm used
48  ! 'upwind' => 1st order mpdata scheme (donor cell)
49  ! 'mpdata' => 2nd order mpdata scheme
50  ! 'remap' (or anything else) => remapping scheme
51 
52  character(len=char_len) :: &
53  ice_ic ! method of ice cover initialization
54  ! 'default' => latitude and sst dependent
55  ! 'none' => no ice
56  ! note: restart = .true. overwrites
57 
58 !=======================================================================
59 
60  contains
61 
62 !=======================================================================
63 !BOP
64 !
65 ! !IROUTINE: input_data - namelist variables
66 !
67 ! !INTERFACE:
68 !
69  subroutine input_data
70 !
71 ! !DESCRIPTION:
72 !
73 ! Namelist variables, set to default values; may be altered
74 ! at run time
75 !
76 ! !REVISION HISTORY:
77 !
78 ! author Elizabeth C. Hunke, LANL
79 !
80 ! !USES:
81 !
82  use ice_albedo
84 ! use ice_diagnostics
85 ! use ice_history
86  use ice_calendar
87 ! use ice_dyn_evp
88  use ice_itd, only: kitd, kcatbound
89 ! use ice_ocean, only: oceanmixed_ice
90  use ice_flux_in, only: &
95 
96  use ice_grid
97 
98  use ice_fileunits
99 ! use ice_exit
100 !
101 ! !INPUT/OUTPUT PARAMETERS:
102 !
103 !EOP
104 !
105  integer (kind=int_kind) :: &
106  ni & ! index for processor count
107  , nml_error ! namelist i/o error flag
108 
109  character (len=6) :: chartmp
110 
111 !#ifdef CCSM
112  !-----------------------------------------------------------------
113  ! Declare namelist variables used for CCSM coupled runs and not
114  ! declared elsewhere in CICE
115  !-----------------------------------------------------------------
116 
117  integer (kind=int_kind) :: kcolumn ! 1 for column model
118 
119  character(len=char_len_long) :: &
120  runid ! identifier for coupled run
121 !#endif
122 
123  !-----------------------------------------------------------------
124  ! Namelist variables.
125  ! NOTE: Not all of these are used by both models.
126  !-----------------------------------------------------------------
127 
128  namelist /ice_nml/ &
129 ! & year_init, istep0, dt, npt
130  year_init, istep0, npt &
131 ! , diagfreq, print_points, print_global, diag_type &
132 ! , diag_file &
133 ! , histfreq, hist_avg, history_dir, history_file &
134 ! , dumpfreq, dumpfreq_n, dump_file &
135 ! , restart, restart_dir, pointer_file, ice_ic &
136 ! , grid_type, grid_file, kmt_file &
137  , grid_type &
138  , kitd, kcatbound &
139 ! , kdyn, ndyn_dt, ndte &
142  , fyear_init, ycycle &
143 ! , atm_data_type, atm_data_dir, precip_units &
144 ! , oceanmixed_ice, sss_data_type, sst_data_type &
145 ! , ocn_data_dir, oceanmixed_file, restore_sst, trestore &
146 ! , dbug
147 !#ifdef CCSM
148 ! These variables are used in CCSM, but not CICE
149 ! &, runid, runtype, kcolumn
150 ! , runid, runtype,
151  , kcolumn
152 !#endif
153 
154 
155 
156  !-----------------------------------------------------------------
157  ! default values
158  !-----------------------------------------------------------------
159 
160  year_init = 1 ! initial year
161  istep0 = 0 ! number of steps taken in previous integrations,
162  ! real (dumped) or imagined (use to set calendar)
163 ! dt = 3600.0_dbl_kind ! time step, s
164  dtice = 3600.0_dbl_kind ! time step, s
165  npt = 99999 ! total number of time steps (dt)
166 ! diagfreq = 24 ! how often diag output is written
167 ! print_points = .false. ! if true, print point data
168 ! print_global = .true. ! if true, print global diagnostic data
169 ! diag_type = 'stdout' ! 'file' writes to diag_file
170 ! diag_file = 'ice_diag.d' ! if diag_type /= 'file'
171 ! histfreq='m' ! output frequency
172 ! hist_avg = .true. ! if true, write time-averages rather than snapshots
173 ! history_dir = ' ' ! default = executable directory
174 ! history_file = 'iceh' ! history file name prefix
175 ! dumpfreq='y' ! restart frequency option
176 ! dumpfreq_n= 1 ! restart frequency
177 ! dump_file = 'iced' ! restart file name prefix
178 ! restart = .false. ! if true, read restart files for initialization
179 ! restart_dir = ' ' ! default = executable directory
180 ! pointer_file = 'ice.restart_file'
181 ! ice_ic = 'default' ! latitude and sst-dependent
182 ! grid_type = 'rectangular' ! define rectangular grid internally
183 ! grid_file = 'unknown_grid_file'
184 ! kmt_file = 'unknown_kmt_file'
185  kitd = 1 ! type of itd conversions (0 = delta, 1 = linear)
186  kcatbound = 1 ! category boundary formula (0 = old, 1 = new)
187 ! kdyn = 1 ! type of dynamics (1 = evp, 0 = off)
188  ndyn_dt = 2 ! dynamics subcycles per thermodynamics timestep
189 ! ndte = 120 ! subcycles per dynamics timestep: ndte=dyn_dt/dte
190 ! evp_damping = .false. ! if true, use damping procedure in evp dynamics
191  kstrength = 1 ! 1 = Rothrock 75 strength, 0 = Hibler 79 strength
192  krdg_partic = 1 ! 1 = LH06 participation, 0 = Thorndike et al 75
193  krdg_redist = 1 ! 1 = LH06 redistribution, 0 = Hibler 80
194 ! advection = 'remap' ! incremental remapping transport scheme
195  albicev = 0.78_dbl_kind ! visible ice albedo for h > ahmax
196  albicei = 0.36_dbl_kind ! near-ir ice albedo for h > ahmax
197  albsnowv = 0.98_dbl_kind ! cold snow albedo, visible
198  albsnowi = 0.70_dbl_kind ! cold snow albedo, near IR
199  fyear_init = 1900 ! first year of forcing cycle
200  ycycle = 1 ! number of years in forcing cycle
201 ! atm_data_type = 'default' ! see ice_flux_in.F for other options
202 ! atm_data_dir = ' '
203 ! precip_units = 'mks' ! 'mm_per_month' or
204  ! 'mm_per_sec' = 'mks' = kg/m^2 s
205 ! oceanmixed_ice = .false. ! if true, use internal ocean mixed layer
206 ! sss_data_type = 'default'
207 ! sst_data_type = 'default'
208 ! ocn_data_dir = ' '
209 ! oceanmixed_file = 'unknown_oceanmixed_file' ! ocean forcing data
210 ! restore_sst = .false. ! restore sst if true
211 ! trestore = 90 ! restoring timescale, days (0 instantaneous)
212 ! dbug = .false. ! true writes diagnostics for input forcing
213 
214 !#ifdef CCSM
215 ! ! The following are in CCSM but not CICE.
216 ! ! Note: CCSM acts as if print_global = .true., kcatbound = 0
217 ! runid = 'unknown' ! default run ID
218 ! runtype = 'unknown' ! default runtype
219  kcolumn = 1 ! 1 = column model
220 !#endif
221 
222  !-----------------------------------------------------------------
223  ! read from input file
224  !-----------------------------------------------------------------
225 ! if (my_task == master_task) then
226 ! open (nu_nml, file='ice_in', status='old')
227 ! 10 continue !*** keep reading until right namelist is found
228 ! read(nu_nml, nml=ice_nml, iostat=nml_error)
229 ! if (nml_error > 0) goto 10 ! An error occurred
230 ! if (nml_error < 0) goto 20 ! End of file condition
231 ! close(nu_nml)
232 ! 20 continue
233 ! endif
234 ! call ice_bcast_iscalar(nml_error)
235 
236 ! if (nml_error /= 0) then
237 ! call abort_ice ('ice: Namelist read error in ice_init.F')
238 ! endif
239 
240 ! if (trim(diag_type) == 'file') then
241 ! nu_diag = 48
242 ! else
243 ! nu_diag = 6
244 ! endif
245 
246 ! if (histfreq == '1') hist_avg = .false. ! potential conflict
247 ! chartmp = advection(1:6)
248 ! if (chartmp /= 'upwind' .and. chartmp /= 'mpdata')
249 ! & advection = 'remap'
250 
251 !#ifdef CCSM
252  if (kcolumn == 1) grid_type = 'column'
253 !#endif
254 
255  !-----------------------------------------------------------------
256  ! broadcast to all processors
257  !-----------------------------------------------------------------
258 
259 ! call ice_bcast_iscalar(year_init)
260 ! call ice_bcast_iscalar(istep0)
261 ! call ice_bcast_rscalar(dt)
262 ! call ice_bcast_iscalar(npt)
263 ! call ice_bcast_iscalar(diagfreq)
264 ! call ice_bcast_logical(print_points)
265 ! call ice_bcast_logical(print_global)
266 ! call ice_bcast_char (diag_type)
267 ! call ice_bcast_char (diag_file)
268 !! call ice_bcast_iscalar(nu_diag) ! only master_task writes to file
269 ! call ice_bcast_char (histfreq)
270 ! call ice_bcast_logical(hist_avg)
271 ! call ice_bcast_char (history_dir)
272 ! call ice_bcast_char (history_file)
273 ! call ice_bcast_char (dumpfreq)
274 ! call ice_bcast_iscalar(dumpfreq_n)
275 ! call ice_bcast_char (dump_file)
276 ! call ice_bcast_logical(restart)
277 ! call ice_bcast_char (restart_dir)
278 ! call ice_bcast_char (pointer_file)
279 ! call ice_bcast_char (ice_ic)
280 ! call ice_bcast_char (grid_type)
281 ! call ice_bcast_char (grid_file)
282 ! call ice_bcast_char (kmt_file)
283 ! call ice_bcast_iscalar(kitd)
284 ! call ice_bcast_iscalar(kcatbound)
285 ! call ice_bcast_iscalar(kdyn)
286 ! call ice_bcast_iscalar(ndyn_dt)
287 ! call ice_bcast_iscalar(ndte)
288 ! call ice_bcast_logical(evp_damping)
289 ! call ice_bcast_iscalar(kstrength)
290 ! call ice_bcast_iscalar(krdg_partic)
291 ! call ice_bcast_iscalar(krdg_redist)
292 ! call ice_bcast_char (advection)
293 ! call ice_bcast_rscalar(albicev)
294 ! call ice_bcast_rscalar(albicei)
295 ! call ice_bcast_rscalar(albsnowv)
296 ! call ice_bcast_rscalar(albsnowi)
297 ! call ice_bcast_iscalar(fyear_init)
298 ! call ice_bcast_iscalar(ycycle)
299 ! call ice_bcast_char (atm_data_type)
300 ! call ice_bcast_char (atm_data_dir)
301 ! call ice_bcast_char (precip_units)
302 ! call ice_bcast_logical(oceanmixed_ice)
303 ! call ice_bcast_char (sss_data_type)
304 ! call ice_bcast_char (sst_data_type)
305 ! call ice_bcast_char (ocn_data_dir)
306 ! call ice_bcast_char (oceanmixed_file)
307 ! call ice_bcast_logical(restore_sst)
308 ! call ice_bcast_iscalar(trestore)
309 ! call ice_bcast_logical(dbug)
310 
311 !#ifdef CCSM
312 ! ! The following are in CCSM but not CICE.
313 ! call ice_bcast_char (runid)
314 ! call ice_bcast_char (runtype)
315 ! call ice_bcast_iscalar(kcolumn)
316 !#endif
317  !-----------------------------------------------------------------
318  ! write namelist variables to diagnostic file
319  !-----------------------------------------------------------------
320 
321 ! if (my_task == master_task) then
322 ! if (trim(diag_type) == 'file') then
323 ! write(6,*) 'Diagnostic output will be in file ', diag_file
324 ! open (nu_diag, file=diag_file, status='unknown')
325 ! endif
326 
327 ! write(nu_diag,*) ' '
328 ! write(nu_diag,*) '--------------------------------'
329 ! write(nu_diag,*) ' CICE model diagnostic output '
330 ! write(nu_diag,*) '--------------------------------'
331 ! write(nu_diag,*) ' '
332 !#ifdef CCSM
333 ! if (trim(runid) /= 'unknown')
334 ! & write(nu_diag,*) ' runid = ',
335 ! & trim(runid)
336 ! if (trim(runtype) /= 'unknown')
337 ! & write(nu_diag,*) ' runtype = ',
338 ! & trim(runtype)
339 !#endif
340 ! write(nu_diag,*) ' year_init = ', year_init
341 ! write(nu_diag,*) ' istep0 = ', istep0
342 ! write(nu_diag,*) ' dt = ', dt
343 ! write(nu_diag,*) ' npt = ', npt
344 ! write(nu_diag,*) ' diagfreq = ', diagfreq
345 ! write(nu_diag,*) ' print_global = ', &
346 ! print_global
347 ! write(nu_diag,*) ' print_points = ', &
348 ! print_points
349 ! write(nu_diag,*) ' histfreq = ', &
350 ! trim(histfreq)
351 ! write(nu_diag,*) ' hist_avg = ', hist_avg
352 ! if (hist_avg) then
353 ! write (nu_diag,*) ' History data will be averaged over 1 ', &
354 ! histfreq
355 ! else
356 ! write (nu_diag,*) ' history data will be snapshots'
357 ! endif
358 ! write(nu_diag,*) ' history_dir = ', &
359 ! trim(history_dir)
360 ! write(nu_diag,*) ' history_file = ', &
361 ! trim(history_file)
362 ! write(nu_diag,*) ' dumpfreq = ', &
363 ! trim(dumpfreq)
364 ! write(nu_diag,*) ' dumpfreq_n = ', dumpfreq_n
365 ! write(nu_diag,*) ' dump_file = ', &
366 ! trim(dump_file)
367 ! write(nu_diag,*) ' restart = ', restart
368 ! write(nu_diag,*) ' restart_dir = ', &
369 ! trim(restart_dir)
370 ! write(nu_diag,*) ' pointer_file = ', &
371 ! trim(pointer_file)
372 ! write(nu_diag,*) ' ice_ic = ', ice_ic
373 ! write(nu_diag,*) ' grid_type = ', &
374 ! trim(grid_type)
375 ! if (trim(grid_type) /= 'rectangular' .or. &
376 ! trim(grid_type) /= 'column') then
377 ! write(nu_diag,*) ' grid_file = ', &
378 ! trim(grid_file)
379 ! write(nu_diag,*) ' kmt_file = ', &
380 ! trim(kmt_file)
381 ! endif
382 ! write(nu_diag,*) ' kitd = ', kitd
383 ! write(nu_diag,*) ' kcatbound = ', &
384 ! kcatbound
385 ! write(nu_diag,*) ' kdyn = ', kdyn
386 ! write(nu_diag,*) ' ndyn_dt = ', ndyn_dt
387 ! write(nu_diag,*) ' ndte = ', ndte
388 ! write(nu_diag,*) ' evp_damping = ', &
389 ! evp_damping
390 ! write(nu_diag,*) ' kstrength = ', kstrength
391 ! write(nu_diag,*) ' krdg_partic = ', &
392 ! krdg_partic
393 ! write(nu_diag,*) ' krdg_redist = ', &
394 ! krdg_redist
395 ! write(nu_diag,*) ' advection = ', &
396 ! trim(advection)
397 ! write(nu_diag,*) ' albicev = ', albicev
398 ! write(nu_diag,*) ' albicei = ', albicei
399 ! write(nu_diag,*) ' albsnowv = ', albsnowv
400 ! write(nu_diag,*) ' albsnowi = ', albsnowi
401 ! write(nu_diag,*) ' fyear_init = ', &
402 ! fyear_init
403 ! write(nu_diag,*) ' ycycle = ', ycycle
404 ! write(nu_diag,*) ' atm_data_type = ', &
405 ! trim(atm_data_type)
406 ! if (trim(atm_data_type) /= 'default') then
407 ! write(nu_diag,*) ' atm_data_dir = ', &
408 ! trim(atm_data_dir)
409 ! write(nu_diag,*) ' precip_units = ', &
410 ! trim(precip_units)
411 ! endif
412 ! write(nu_diag,*) ' oceanmixed_ice = ', &
413 ! oceanmixed_ice
414 ! write(nu_diag,*) ' sss_data_type = ', &
415 ! trim(sss_data_type)
416 ! write(nu_diag,*) ' sst_data_type = ', &
417 ! trim(sst_data_type)
418 ! if (trim(sss_data_type) /= 'default' .or. &
419 ! trim(sst_data_type) /= 'default') then
420 ! write(nu_diag,*) ' ocn_data_dir = ', &
421 ! trim(ocn_data_dir)
422 ! endif
423 ! if (trim(sss_data_type) == 'ncar' .or. &
424 ! trim(sst_data_type) == 'ncar') then
425 ! write(nu_diag,*) ' oceanmixed_file = ', &
426 ! trim(oceanmixed_file)
427 ! endif
428 
429 
430 ! if (grid_type /= 'displaced_pole' .and.
431 ! & grid_type /= 'column' .and.
432 ! & grid_type /= 'rectangular') then
433 ! call abort_ice('ice_init: unknown grid_type')
434 ! endif
435 
436  !-----------------------------------------------------------------
437  ! Document grid and subdomain sizes
438  !-----------------------------------------------------------------
439 
440 ! write(nu_diag,*) ' '
441 ! write(nu_diag,*) ' Grid and subdomain sizes:'
442 ! write(nu_diag,*) ' ------------------------ '
443 ! write(nu_diag,*) ' '
444 ! write(nu_diag,1050) imt_global, jmt_global
445 ! write(nu_diag,1060) nproc_s, nproc_x, nproc_y
446 ! write(nu_diag,1070) imt_local,jmt_local
447 ! write(nu_diag,1080) ihi-ilo+1,jhi-jlo+1
448 ! write(nu_diag,1090) ilo,jlo
449 ! write(nu_diag,1095) ihi,jhi
450 ! write(nu_diag,*) ' Global i start for each processor: ', &
451 ! (local_start(1,n),n=1,nproc_s)
452 ! write(nu_diag,*) ' Global j start for each processor: ', &
453 ! (local_start(2,n),n=1,nproc_s)
454 ! write(nu_diag,*) ' '
455 
456  1050 format(' Global problem size:',2x,i6,' x ',i6)
457  1060 format(' Using ',i6,' processors in a ',i6,' x ',i6, &
458  ' Cartesian decomposition')
459  1070 format(' Local array size is:',2x,i6,' x ',i6)
460  1080 format(' Physical domain is (approximately):',2x,i6,' x ',i6)
461  1090 format(' Local i,j start for each processor:',2x,i6,2x,i6)
462  1095 format(' Local i,j end for each processor:',2x,i6,2x,i6)
463 
464 ! endif ! my_task = master_task
465 
466  end subroutine input_data
467 
468 !=======================================================================
469 !BOP
470 !
471 ! !IROUTINE: init_state - initialize state for itd
472 !
473 ! !INTERFACE:
474 !
475  subroutine init_state
476 !
477 ! !DESCRIPTION:
478 !
479 ! Initialize state for the itd model
480 !
481 ! !REVISION HISTORY:
482 !
483 ! author C. M. Bitz
484 !
485 ! !USES:
486 !
487  use ice_model_size
488  use ice_constants
489  use ice_flux
491  use ice_grid
492  use ice_state
493  use ice_itd
494 !
495 ! !INPUT/OUTPUT PARAMETERS:
496 !
497 !EOP
498 !
499  integer (kind=int_kind) :: &
500  i, j & ! horizontal indices
501  , ij & ! horizontal index, combines i and j loops
502  , k & ! ice layer index
503  , ni & ! thickness category index
504  , icells ! number of cells initialized with ice
505 
506  integer (kind=int_kind), dimension(1:(ihi-ilo+1)*(jhi-jlo+1)) :: &
507  indxi, indxj ! compressed indices for cells with aicen > puny
508 
509  real (kind=dbl_kind) :: &
510  slope, ti, sum, hbar &
511  , ainit(ncat) &
512  , hinit(ncat)
513 
514  real (kind=dbl_kind), parameter :: &
515  hsno_init = 0.20_dbl_kind ! initial snow thickness (m)
516 
517  if (trim(ice_ic) == 'none') then
518  ! Initialize grid with no ice.
519  ! If restarting, these values are overwritten.
520 
521  do ni = 1,ncat
522  do j = 1,jmt_local
523  do i = 1,imt_local
524  aicen(i,j,ni) = c0i
525  vicen(i,j,ni) = c0i
526  vsnon(i,j,ni) = c0i
527  esnon(i,j,ni) = c0i
528  enddo
529  enddo
530  do j = jlo,jhi
531  do i = ilo,ihi
532  tsfcn(i,j,ni) = tf(i,j) ! Tf not defined for ghost cells
533  enddo
534  enddo
535 ! call bound(Tsfcn(:,:,n))
536  enddo
537 
538  do k = 1,ntilay
539  do j = 1,jmt_local
540  do i = 1,imt_local
541  eicen(i,j,k) = c0i
542  enddo
543  enddo
544  enddo
545 
546  else ! ice_ic = 'default'
547 
548  ! initial category areas in cells with ice
549  hbar = c3i ! initial ice thickness with greatest area
550  ! Note: the resulting average ice thickness
551  ! tends to be less than hbar due to the
552  ! nonlinear distribution of ice thicknesses
553  sum = c0i
554  do ni = 1, ncat
555  if (ni < ncat) then
556  hinit(ni) = p5*(hin_max(ni-1) + hin_max(ni)) ! m
557  else ! n=ncat
558  hinit(ni) = (hin_max(ni-1) + c1i) ! m
559  endif
560  ! parabola, max at h=hbar, zero at h=0, 2*hbar
561  ainit(ni) = max(c0i, (c2i*hbar*hinit(ni) - hinit(ni)**2))
562  sum = sum + ainit(ni)
563  enddo
564  do ni = 1, ncat
565  ainit(ni) = ainit(ni) / (sum + puny/ncat) ! normalize
566  enddo
567 
568  ! place ice at high latitudes where ocean sfc is cold
569  icells = 0
570  do j = jlo,jhi
571  do i = ilo,ihi
572  if (tmask(i,j)) then
573  if ((sst(i,j) <= tf(i,j)+p2) .and. &
574  (ulat(i,j) < -64.0_dbl_kind/rad_to_deg .or. &
575 ! ULAT(i,j) > 70.0_dbl_kind/rad_to_deg)) then
576  ulat(i,j) > 65.0_dbl_kind/rad_to_deg)) then
577  icells = icells + 1
578  indxi(icells) = i
579  indxj(icells) = j
580  endif ! cold surface
581  endif ! tmask
582  enddo ! i
583  enddo ! j
584  do ni = 1,ncat
585 !DIR$ CONCURRENT !Cray
586 !cdir nodep !NEC
587 !ocl novrec !Fujitsu
588  do ij = 1, icells
589  i = indxi(ij)
590  j = indxj(ij)
591 
592  aicen(i,j,ni) = ainit(ni)
593  vicen(i,j,ni) = hinit(ni) * ainit(ni) ! m
594  vsnon(i,j,ni) = min(aicen(i,j,ni)*hsno_init, p2*vicen(i,j,ni))
595  tsfcn(i,j,ni) = min(tsmelt, tair(i,j) - tffresh) ! deg C
596 
597  ! snow
598  ti = min(c0i, tsfcn(i,j,ni))
599  esnon(i,j,ni) = -rhos*(lfresh - cp_ice*ti)*vsnon(i,j,ni)
600  enddo ! ij
601 
602  do k = 1, nilyr
603  do ij = 1, icells
604  i = indxi(ij)
605  j = indxj(ij)
606 
607  ! assume linear temp profile and compute enthalpy
608  slope = tf(i,j) - tsfcn(i,j,ni)
609  ti = tsfcn(i,j,ni) &
610  + slope*(real(k,kind=dbl_kind)-p5) &
611  /real(nilyr,kind=dbl_kind)
612 
613  eicen(i,j,ilyr1(ni)+k-1) = &
614  -(rhoi * (cp_ice*(tmlt(k)-ti) &
615  + lfresh*(c1i-tmlt(k)/ti) - cp_ocn*tmlt(k))) &
616  * vicen(i,j,ni)/real(nilyr,kind=dbl_kind)
617 
618  enddo ! ij
619  enddo ! k
620  enddo ! n
621 
622  endif ! ice_ic
623 
624  ! compute aggregate ice state and open water area
625  call aggregate
626  call bound_aggregate
627 
628  do j = 1, jmt_local
629  do i = 1, imt_local
630  aice_init(i,j) = aice(i,j)
631  enddo
632  enddo
633 
634  end subroutine init_state
635 
636 !=======================================================================
637 !BOP
638 !
639 ! !IROUTINE: init_flux - initialize fluxes exchanged with coupler
640 !
641 ! !INTERFACE:
642 !
643  subroutine init_flux
644 !
645 ! !DESCRIPTION:
646 !
647 ! Initialize all fluxes exchanged with flux coupler
648 ! and some data derived fields
649 !
650 ! !REVISION HISTORY:
651 !
652 ! author Elizabeth C. Hunke, LANL
653 !
654 ! !USES:
655 !
656  use ice_constants
657  use ice_flux
658 !
659 ! !INPUT/OUTPUT PARAMETERS:
660 !
661 !EOP
662 !
663  integer i,j
664 
665  do j=jlo,jhi
666  do i=ilo,ihi
667  !-----------------------------------------------------------------
668  ! fluxes received
669  !-----------------------------------------------------------------
670  zlvl(i,j) = c10i ! atm level height (m)
671  uatm(i,j) = c0i ! wind velocity (m/s)
672  vatm(i,j) = c0i
673  pott(i,j) = 273._dbl_kind ! air potential temperature (K)
674  tair(i,j) = 273._dbl_kind ! air temperature (K)
675  qa(i,j) = 0.014_dbl_kind ! specific humidity (kg/kg)
676  rhoa(i,j) = 1.3_dbl_kind ! air density (kg/m^3)
677  fsnow(i,j) = 3.3e-6_dbl_kind ! snowfall rate (kg/m2/s)
678  frain(i,j) = c0i ! rainfall rate (kg/m2/s)
679  fsw(i,j) = c0i ! shortwave radiation (W/m^2)
680  swvdr(i,j) = c0i ! shortwave radiation (W/m^2)
681  swvdf(i,j) = c0i ! shortwave radiation (W/m^2)
682  swidr(i,j) = c0i ! shortwave radiation (W/m^2)
683  swidf(i,j) = c0i ! shortwave radiation (W/m^2)
684  flw(i,j) = 280.0_dbl_kind ! incoming longwave radiation (W/m^2)
685  sss(i,j) = 34.0_dbl_kind ! sea surface salinity (o/oo)
686 ! uocn (i,j) = c0i ! surface ocean currents (m/s)
687 ! vocn (i,j) = c0i
688  frzmlt(i,j) = c0i ! freezing/melting potential (W/m^2)
689 ! qdp (i,j) = c0i ! deep ocean heat flux
690 
691  !-----------------------------------------------------------------
692  ! derived or computed fields
693  !-----------------------------------------------------------------
694 
695  tf(i,j) = -depresst*sss(i,j) ! freezing temp (C)
696  sst(i,j) = tf(i,j) ! sea surface temp (C)
697 
698  wind(i,j) = sqrt(uatm(i,j)**2 + vatm(i,j)**2) ! wind speed, (m/s)
699 
700  strocnx(i,j) = c0i ! ice-ocean stress, x-direction (U-cell)
701  strocny(i,j) = c0i ! ice-ocean stress, y-direction (U-cell)
702  strocnxt(i,j) = c0i ! ice-ocean stress, x-direction (T-cell)
703  strocnyt(i,j) = c0i ! ice-ocean stress, y-direction (T-cell)
704 
705  enddo
706  enddo
707 
708  call init_flux_atm
709  call init_flux_ocn
710 
711  end subroutine init_flux
712 
713 !=======================================================================
714 !BOP
715 !
716 ! !IROUTINE: setup_mpi - initialize mpi
717 !
718 ! !INTERFACE:
719 !
720 ! subroutine setup_mpi
721 !
722 ! !DESCRIPTION:
723 !
724 ! This routine initializes mpi for either internal parallel
725 ! processing or for message passing with the coupler
726 !
727 ! !REVISION HISTORY:
728 !
729 ! author Elizabeth C. Hunke, LANL
730 ! code originally based on POP routine
731 !
732 ! !USES:
733 !
734 ! use ice_mpi_internal
735 ! use ice_coupling
736 ! use ice_exit
737 !
738 ! !INPUT/OUTPUT PARAMETERS:
739 !
740 !EOP
741 !
742 ! integer (kind=int_kind) :: &
743 ! coords1, coords2, n, ilen, jlen &
744 ! , interior_i, interior_j ! dummies for interior blocks
745 
746 ! master_task = 0
747 
748 !#ifdef coupled
749 ! ! if running in coupled mode
750 !#ifdef fcd_coupled
751 ! ! direct ice-ocean coupling
752 ! call MPI_COMM_DUP(MPI_COMM_WORLD, MPI_COMM_ICE, ierr)
753 !#else
754 ! ! CCSM coupling
755 ! call ice_coupling_setup('ice',MPI_COMM_ICE)
756 !#endif
757 !#else
758 ! ! if running in stand-alone MPI mode
759 !#ifdef _MPI
760 !#if fcd_coupled
761 !#else
762 ! call MPI_INIT(ierr)
763 !#endif
764 ! call MPI_COMM_DUP(MPI_COMM_WORLD, MPI_COMM_ICE, ierr)
765 !#endif
766 !#endif
767 !
768 !#ifdef _MPI
769 ! call MPI_COMM_SIZE (MPI_COMM_ICE, nb_tasks, ierr)
770 ! call MPI_COMM_RANK (MPI_COMM_ICE, my_task, ierr)
771 
772 ! if (nb_tasks /= nproc_s) then
773 ! write (6,*) 'nb_tasks, nproc_s =', nb_tasks, nproc_s
774 ! call abort_ice ('nb_tasks must equal nproc_s')
775 ! endif
776 
777 ! if (real(imt_global,kind=dbl_kind)/real(nproc_x,kind=dbl_kind)
778 ! & /= int(imt_global/nproc_x)) then
779 ! write (6,*) 'nproc_x, imt_global =', nproc_x, imt_global
780 ! call abort_ice
781 ! & ('number of pes in x must evenly divide imt_global')
782 ! endif
783 
784 ! if (real(jmt_global,kind=dbl_kind)/real(nproc_y,kind=dbl_kind)
785 ! & /= int(jmt_global/nproc_y)) then
786 ! write (6,*) 'nproc_y, jmt_global =', nproc_y, jmt_global
787 ! call abort_ice
788 ! & ('number of pes in y must evenly divide jmt_global')
789 ! endif
790 
791 ! if ( ierr /= MPI_SUCCESS ) then
792 ! call abort_ice('(setup_mpi) ERROR after MPI_COMM_xxx')
793 ! endif
794 
795 ! coords1 = mod(my_task,nproc_x)
796 ! coords2 = my_task/nproc_x
797 ! nbr_east = coords2*nproc_x+mod(my_task+1,nproc_x)
798 ! nbr_west = coords2*nproc_x+mod(my_task-1+nproc_x,nproc_x)
799 ! nbr_north = my_task+nproc_x
800 ! nbr_south = my_task-nproc_x
801 ! if (nbr_south < 0) nbr_south = -1
802 ! if (nbr_north > nproc_s-1) nbr_north=-1
803 !
804 ! ilen = ihi-ilo+1
805 ! jlen = jhi-jlo+1
806 !
807 ! do n=1,nproc_s
808 !
809 ! local_start(1,n)=((imt_global-1)/nproc_x+1)*mod((n-1),nproc_x)+1
810 ! local_start(2,n)=((jmt_global-1)/nproc_y+1)*((n-1)/nproc_x)+1
811 !
812 ! call MPI_TYPE_VECTOR(jlen, ilen, ilen,
813 ! & mpi_integer, mpi_interior_int(n), ierr)
814 ! call MPI_TYPE_COMMIT(mpi_interior_int(n), ierr)
815 !
816 ! call MPI_TYPE_VECTOR(jlen, ilen, ilen,
817 ! & mpi_real8, mpi_interior_real(n), ierr)
818 ! call MPI_TYPE_COMMIT(mpi_interior_real(n), ierr)
819 !
820 ! call MPI_TYPE_VECTOR(jlen, ilen, imt_global,
821 ! & mpi_integer, mpi_interior_int_global(n), ierr)
822 ! call MPI_TYPE_COMMIT(mpi_interior_int_global(n), ierr)
823 !
824 ! call MPI_TYPE_VECTOR(jlen, ilen, imt_global,
825 ! & mpi_real8, mpi_interior_real_global(n), ierr)
826 ! call MPI_TYPE_COMMIT(mpi_interior_real_global(n), ierr)
827 !
828 ! enddo
829 
830 ! do n=1,nproc_s
831 ! if (my_task == n-1) then
832 ! write (6,*) ' my_task,e,w,n,s ', my_task,
833 ! & nbr_east, nbr_west, nbr_north, nbr_south
834 ! endif
835 ! enddo
836 ! write (6,*) ' '
837 !
838 !#else
839 ! ! not MPI
840 ! local_start(1,1)= 1
841 ! local_start(2,1)= 1
842 ! my_task = master_task
843 ! nb_tasks = 1
844 !#endif
845 
846 ! end subroutine setup_mpi
847 
848 !=======================================================================
849 
850  end module ice_init
851 
852 !=======================================================================
real(kind=dbl_kind), dimension(:,:), allocatable, save tf
Definition: ice_flux.f90:91
character(char_len) sst_data_type
integer(kind=int_kind), parameter nilyr
real(kind=dbl_kind), parameter depresst
integer(kind=int_kind) kcatbound
Definition: ice_itd.f90:62
integer(kind=int_kind) ycycle
Definition: ice_flux_in.f90:54
character(char_len) sss_data_type
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save esnon
Definition: ice_state.f90:97
character(char_len_long) oceanmixed_file
real(kind=dbl_kind) rad_to_deg
logical(kind=log_kind) restore_sst
subroutine namelist
Definition: namelist.f90:41
real(kind=dbl_kind), dimension(:,:), allocatable, save strocnx
Definition: ice_flux.f90:55
real(kind=dbl_kind), dimension(:,:), allocatable, save strocnxt
Definition: ice_flux.f90:55
integer(kind=int_kind) ihi
Definition: ice_domain.f90:101
real(kind=dbl_kind), dimension(:,:), allocatable, save sss
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save fsw
Definition: ice_flux.f90:164
real(kind=dbl_kind), parameter c0i
character(char_len) precip_units
real(kind=dbl_kind), parameter c3i
real(kind=dbl_kind), parameter rhos
character(char_len_long) atm_data_dir
real(kind=dbl_kind), parameter c10i
real(kind=dbl_kind), dimension(:,:), allocatable, save swvdf
Definition: ice_flux.f90:91
real(kind=dbl_kind), parameter lfresh
integer(kind=int_kind) krdg_partic
Definition: ice_mechred.f90:81
real(kind=dbl_kind) albicei
Definition: ice_albedo.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save rhoa
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save pott
Definition: ice_flux.f90:91
integer(kind=int_kind) kitd
Definition: ice_itd.f90:62
character(len=char_len) advection
Definition: ice_init.f90:46
logical(kind=log_kind) dbug
real(kind=dbl_kind), dimension(:,:), allocatable ulat
Definition: ice_grid.f90:122
character(char_len) atm_data_type
integer(kind=int_kind) krdg_redist
Definition: ice_mechred.f90:81
real(kind=dbl_kind), dimension(:,:), allocatable, save flw
Definition: ice_flux.f90:91
character(char_len_long) ocn_data_dir
integer(kind=int_kind) trestore
integer(kind=int_kind) jlo
Definition: ice_domain.f90:101
real(kind=dbl_kind), dimension(:,:), allocatable, save sst
Definition: ice_flux.f90:91
subroutine init_flux_atm
Definition: ice_flux.f90:182
real(kind=dbl_kind), dimension(:,:), allocatable, save vatm
Definition: ice_flux.f90:91
character(len=char_len) ice_ic
Definition: ice_init.f90:52
integer(kind=int_kind) ndyn_dt
real(kind=dbl_kind), parameter cp_ice
real(kind=dbl_kind), dimension(nilyr+1) tmlt
integer(kind=int_kind) ilo
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter p5
real(kind=dbl_kind), parameter puny
real(kind=dbl_kind), parameter tffresh
real(kind=dbl_kind), parameter p2
real(kind=dbl_kind) dtice
integer(kind=int_kind) jhi
Definition: ice_domain.f90:101
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save tsfcn
Definition: ice_state.f90:97
real(kind=dbl_kind), parameter tsmelt
real(kind=dbl_kind), dimension(:,:), allocatable, save frain
Definition: ice_flux.f90:91
integer(kind=int_kind) fyear_init
Definition: ice_flux_in.f90:54
character(len=char_len) grid_type
Definition: ice_grid.f90:57
real(kind=dbl_kind) albsnowv
Definition: ice_albedo.f90:91
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save vicen
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, target, save aice
Definition: ice_state.f90:82
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save eicen
Definition: ice_state.f90:108
integer(kind=int_kind), parameter ncat
real(kind=dbl_kind), parameter c2i
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save aicen
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, save uatm
Definition: ice_flux.f90:91
integer(kind=int_kind) imt_local
Definition: ice_domain.f90:101
real(kind=dbl_kind), dimension(:,:), allocatable, save swvdr
Definition: ice_flux.f90:91
integer(kind=int_kind) year_init
real(kind=dbl_kind), dimension(:,:), allocatable, save frzmlt
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(0:ncat) hin_max
Definition: ice_itd.f90:74
real(kind=dbl_kind), dimension(:,:), allocatable, save zlvl
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save strocnyt
Definition: ice_flux.f90:55
real(kind=dbl_kind), dimension(:,:), allocatable, save fsnow
Definition: ice_flux.f90:91
real(kind=dbl_kind), parameter c1i
real(kind=dbl_kind), dimension(:,:), allocatable, save strocny
Definition: ice_flux.f90:55
real(kind=dbl_kind), dimension(:,:), allocatable, save qa
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save swidf
Definition: ice_flux.f90:91
subroutine init_flux
Definition: ice_init.f90:644
real(kind=dbl_kind) albsnowi
Definition: ice_albedo.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, target, save aice_init
Definition: ice_state.f90:82
subroutine init_flux_ocn
Definition: ice_flux.f90:239
subroutine bound_aggregate
Definition: ice_itd.f90:447
real(kind=dbl_kind) albicev
Definition: ice_albedo.f90:91
real(kind=dbl_kind), parameter rhoi
integer(kind=int_kind), parameter ntilay
subroutine init_state
Definition: ice_init.f90:476
real(kind=dbl_kind), dimension(:,:), allocatable, save wind
Definition: ice_flux.f90:164
real(kind=dbl_kind), dimension(:,:), allocatable, save tair
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save swidr
Definition: ice_flux.f90:91
integer(kind=int_kind), dimension(ncat) ilyr1
Definition: ice_itd.f90:62
integer(kind=int_kind) jmt_local
Definition: ice_domain.f90:101
subroutine aggregate
Definition: ice_itd.f90:234
logical(kind=log_kind), dimension(:,:), allocatable tmask
Definition: ice_grid.f90:164
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save vsnon
Definition: ice_state.f90:97
integer(kind=int_kind) kstrength
Definition: ice_mechred.f90:81
subroutine input_data
Definition: ice_init.f90:70
integer(kind=int_kind) istep0
real(kind=dbl_kind), parameter cp_ocn
integer(kind=int_kind) npt