My Project
Functions/Subroutines | Variables
ice_therm_itd Module Reference

Functions/Subroutines

subroutine thermo_itd
 
subroutine add_new_ice
 
subroutine lateral_melt (rside)
 
subroutine freeboard
 

Variables

real(kind=dbl_kind), dimension(:,:,:), allocatable, save hicen
 

Function/Subroutine Documentation

◆ add_new_ice()

subroutine ice_therm_itd::add_new_ice ( )

Definition at line 250 of file ice_therm_itd.f90.

250 !
251 ! !USES:
252 !
253 ! !INPUT/OUTPUT PARAMETERS:
254 !
255 !EOP
256 !
257  integer (kind=int_kind) :: &
258  & i, j & ! horizontal indices
259  &, ni & ! ice category index
260  &, k ! ice layer index
261 
262  real (kind=dbl_kind), dimension(ilo:ihi,jlo:jhi) :: &
263  & ai0new & ! area of new ice added to cat 1
264  &, vi0new & ! volume of new ice added to cat 1
265  &, hsurp & ! thickness of new ice added to each cat
266  &, vlyr ! ice layer volume
267 
268  real (kind=dbl_kind), dimension (imt_local,jmt_local) :: &
269  & vice_init, vice_final ! ice volume summed over categories
270 
271  real (kind=dbl_kind) :: &
272  & fnew & ! heat flx to open water for new ice (W/m^2)
273  &, hi0new & ! thickness of new ice
274  &, hi0max & ! max allowed thickness of new ice
275  &, qi0(nilyr) & ! frazil ice enthalpy
276  &, qi0av & ! mean value of qi0 for new ice (J kg-1)
277  &, vsurp & ! volume of new ice added to each cat
278  &, area1 & ! starting fractional area of existing ice
279  &, rnilyr & ! real(nilyr)
280  &, dfresh & ! change in fresh
281  &, dfsalt & ! change in fsalt
282  &, vi_frzmlt & ! ice vol formed by frzmlt acting alone
283  &, vi_diff ! vi0new - vi_frzmlt
284 
285  real (kind=dbl_kind), parameter :: &
286  & hfrazilmin = 0.05_dbl_kind ! min thickness of new frazil ice (m)
287 
288  integer (kind=int_kind) :: &
289  & icells, jcells, kcells &! grid cell counters
290  &, ij ! combined i/j horizontal index
291 
292  integer (kind=int_kind), &
293  & dimension (1:(ihi-ilo+1)*(jhi-jlo+1)) :: &
294  & indxi, indxj & ! compressed i/j indices
295  &, indxi2, indxj2 &
296  &, indxi3, indxj3
297 
298  character (len=char_len) :: &
299  & fieldid ! field identifier
300 
301  if (ncat > 1) then
302  hi0max = hin_max(1)*0.9_dbl_kind ! not too close to boundary
303  else
304  hi0max = 1.e8_dbl_kind ! big number
305  endif
306 
307  ! initial ice volume in each grid cell
308  call column_sum (ncat, vicen, vice_init)
309 
310  !-----------------------------------------------------------------
311  ! Compute average enthalpy of new ice.
312  !
313  ! POP assumes new ice is fresh. Otherwise, it would be better
314  ! to do something like this:
315  ! qi0(i,j,k) = -rhoi * (cp_ice*(Tmlt(k)-Tf(i,j))
316  ! + Lfresh*(1.-Tmlt(k)/Tf(i,j)) - cp_ocn*Tmlt(k))
317  !-----------------------------------------------------------------
318 
319  rnilyr = real(nilyr,kind=dbl_kind)
320  qi0av = c0i
321  do k = 1, nilyr
322  qi0(k) = -rhoi*lfresh ! note sign convention, qi < 0
323  qi0av = qi0av + qi0(k)
324  enddo
325  qi0av = qi0av/rnilyr
326 
327  !-----------------------------------------------------------------
328  ! Identify ice/ocean grid points.
329  !-----------------------------------------------------------------
330  icells = 0
331  do j = jlo, jhi
332  do i = ilo, ihi
333  if (tmask(i,j)) then
334  icells = icells + 1
335  indxi(icells) = i
336  indxj(icells) = j
337  endif
338  enddo ! i
339  enddo ! j
340 
341  !-----------------------------------------------------------------
342  ! Compute the volume, area, and thickness of new ice.
343  !-----------------------------------------------------------------
344 
345 !DIR$ CONCURRENT !Cray
346 !cdir nodep !NEC
347 !ocl novrec !Fujitsu
348  do ij = 1, icells
349  i = indxi(ij)
350  j = indxj(ij)
351 
352  fnew = max(frzmlt(i,j), c0i) ! fnew > 0 iff frzmlt > 0
353  vi0new(i,j) = -fnew*dtice / qi0av ! note sign convention, qi < 0
354 ! vi0new(i,j) = -fnew*dt / qi0av ! note sign convention, qi < 0
355 
356  ! increment ice volume
357  vice_init(i,j) = vice_init(i,j) + vi0new(i,j)
358 
359  ! history diagnostics
360  frazil(i,j) = vi0new(i,j)
361  if (frazil(i,j) > puny .and. frz_onset(i,j) < puny) &
362  & frz_onset(i,j) = yday
363 
364  !-----------------------------------------------------------------
365  ! Update fresh water and salt fluxes.
366  !
367  ! NOTE: POP assumes fresh water and salt flux due to frzmlt > 0
368  ! is NOT included in fluxes fresh and fsalt.
369  !-----------------------------------------------------------------
370 
371 !!! dfresh = -rhoi*vi0new(i,j)/dt ! if POP had not already adjusted
372  ! itself based on frzmlt
373 !!! dfsalt = ice_ref_salinity*p001*dfresh
374 
375 !!! fresh(i,j) = fresh(i,j) + dfresh
376 !!! fresh_hist(i,j) = fresh_hist(i,j) + dfresh
377 !!! fsalt(i,j) = fsalt(i,j) + dfsalt
378 !!! fsalt_hist(i,j) = fsalt_hist(i,j) + dfsalt
379 
380 !! There is no adjust in FVCOM when it is coupled with CICE model
381 !! be careful to adjust the fresh water balance
382  !dfresh = -rhoi*vi0new(i,j)/dt ! if POP had not already adjusted
383  dfresh = -rhoi*vi0new(i,j)/dtice ! if POP had not already adjusted
384  ! itself based on frzmlt
385  dfsalt = ice_ref_salinity*p001*dfresh
386 
387  fresh(i,j) = fresh(i,j) + dfresh
388  fresh_hist(i,j) = fresh_hist(i,j) + dfresh
389  fsalt(i,j) = fsalt(i,j) + dfsalt
390  fsalt_hist(i,j) = fsalt_hist(i,j) + dfsalt
391 
392 
393 
394 
395 
396  !-----------------------------------------------------------------
397  ! Decide how to distribute the new ice.
398  !-----------------------------------------------------------------
399 
400  hsurp(i,j) = c0i
401  ai0new(i,j) = c0i
402 
403  if (vi0new(i,j) > c0i) then
404 
405  ! new ice area and thickness
406  ! hin_max(0) < new ice thickness < hin_max(1)
407  if (aice0(i,j) > puny) then
408  hi0new = max(vi0new(i,j)/aice0(i,j), hfrazilmin)
409  if (hi0new > hi0max .and. aice0(i,j)+puny < c1i) then
410  ! distribute excess volume over all categories (below)
411  hi0new = hi0max
412  ai0new(i,j) = aice0(i,j)
413  vsurp = vi0new(i,j) - ai0new(i,j)*hi0new
414  hsurp(i,j) = vsurp / aice(i,j)
415  vi0new(i,j) = ai0new(i,j)*hi0new
416  else
417  ! put ice in a single category, with hsurp = 0
418  ai0new(i,j) = vi0new(i,j)/hi0new
419  endif
420  else ! aice0 < puny
421  hsurp(i,j) = vi0new(i,j)/aice(i,j) ! new thickness in each cat
422  vi0new(i,j) = c0i
423  endif ! aice0 > puny
424  endif ! vi0new > puny
425 
426  enddo ! ij
427 
428  !-----------------------------------------------------------------
429  ! Identify grid cells receiving new ice.
430  !-----------------------------------------------------------------
431  jcells = 0
432  kcells = 0
433 
434  do ij = 1, icells
435  i = indxi(ij)
436  j = indxj(ij)
437 
438  if (vi0new(i,j) > c0i) then ! add ice to category 1
439  jcells = jcells + 1
440  indxi2(jcells) = i
441  indxj2(jcells) = j
442  endif
443 
444  if (hsurp(i,j) > c0i) then ! add ice to all categories
445  kcells = kcells + 1
446  indxi3(kcells) = i
447  indxj3(kcells) = j
448  endif
449 
450  enddo
451 
452  !-----------------------------------------------------------------
453  ! Distribute excess ice volume among ice categories by increasing
454  ! ice thickness, leaving ice area unchanged.
455  !-----------------------------------------------------------------
456 
457  do ni = 1, ncat
458 
459 !DIR$ CONCURRENT !Cray
460 !cdir nodep !NEC
461 !ocl novrec !Fujitsu
462  do ij = 1, kcells
463  i = indxi3(ij)
464  j = indxj3(ij)
465 
466  vicen(i,j,ni) = vicen(i,j,ni) + aicen(i,j,ni)*hsurp(i,j)
467  vlyr(i,j) = hsurp(i,j)/rnilyr * aicen(i,j,ni)
468  enddo ! ij
469 
470  do k=1,nilyr
471 !DIR$ CONCURRENT !Cray
472 !cdir nodep !NEC
473 !ocl novrec !Fujitsu
474  do ij = 1, kcells
475  i = indxi3(ij)
476  j = indxj3(ij)
477 
478  eicen(i,j,ilyr1(ni)+k-1) = &
479  & eicen(i,j,ilyr1(ni)+k-1) + qi0(k)*vlyr(i,j)
480  enddo ! ij
481  enddo ! k
482 
483  enddo ! n
484 
485  !-----------------------------------------------------------------
486  ! Combine new ice grown in open water with category 1 ice.
487  ! NOTE: vsnon and esnon are unchanged.
488  !-----------------------------------------------------------------
489 !DIR$ CONCURRENT !Cray
490 !cdir nodep !NEC
491 !ocl novrec !Fujitsu
492  do ij = 1, jcells
493  i = indxi2(ij)
494  j = indxj2(ij)
495 
496  area1 = aicen(i,j,1) ! save
497  aicen(i,j,1) = aicen(i,j,1) + ai0new(i,j)
498  aice0(i,j) = aice0(i,j) - ai0new(i,j)
499  vicen(i,j,1) = vicen(i,j,1) + vi0new(i,j)
500  tsfcn(i,j,1) = (tf(i,j)*ai0new(i,j) + tsfcn(i,j,1)*area1) &
501  & / aicen(i,j,1)
502  tsfcn(i,j,1) = min(tsfcn(i,j,1), c0i)
503  vlyr(i,j) = vi0new(i,j)/rnilyr
504  enddo ! ij
505 
506  do k = 1, nilyr
507 !DIR$ CONCURRENT !Cray
508 !cdir nodep !NEC
509 !ocl novrec !Fujitsu
510  do ij = 1, jcells
511  i = indxi2(ij)
512  j = indxj2(ij)
513  eicen(i,j,k) = eicen(i,j,k) + qi0(k)*vlyr(i,j)
514  enddo
515  enddo
516 
517  call column_sum (ncat, vicen, vice_final)
518  fieldid = 'vice, add_new_ice'
519  call column_conservation_check(vice_init, vice_final, &
520  & puny, fieldid)
521 
real(kind=dbl_kind), dimension(:,:), allocatable, save tf
Definition: ice_flux.f90:91
real(kind=dbl_kind), dimension(:,:), allocatable, save fsalt_hist
Definition: ice_flux.f90:140
integer(kind=int_kind), parameter nilyr
integer(kind=int_kind) ihi
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter c0i
real(kind=dbl_kind), parameter lfresh
real(kind=dbl_kind), parameter ice_ref_salinity
real(kind=dbl_kind), dimension(:,:), allocatable, save fresh
Definition: ice_flux.f90:120
integer(kind=int_kind) jlo
Definition: ice_domain.f90:101
integer(kind=int_kind) ilo
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter puny
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 p001
real(kind=dbl_kind), dimension(:,:), allocatable, save frazil
Definition: ice_flux.f90:140
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, save fresh_hist
Definition: ice_flux.f90:140
real(kind=dbl_kind), dimension(:,:), allocatable, save fsalt
Definition: ice_flux.f90:120
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save eicen
Definition: ice_state.f90:108
real(kind=dbl_kind), dimension(:,:), allocatable, target, save aice0
Definition: ice_state.f90:105
integer(kind=int_kind), parameter ncat
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save aicen
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, save frzmlt
Definition: ice_flux.f90:91
real(kind=dbl_kind), parameter c1i
real(kind=dbl_kind), dimension(:,:), allocatable, save frz_onset
Definition: ice_flux.f90:140
real(kind=dbl_kind), parameter rhoi
logical(kind=log_kind), dimension(:,:), allocatable tmask
Definition: ice_grid.f90:164
Here is the call graph for this function:
Here is the caller graph for this function:

◆ freeboard()

subroutine ice_therm_itd::freeboard ( )

Definition at line 675 of file ice_therm_itd.f90.

675 !
676 ! !USES:
677 !
678 ! !INPUT/OUTPUT PARAMETERS:
679 !
680 !EOP
681 !
682  integer (kind=int_kind) :: i, j, ni, k
683 
684  real (kind=dbl_kind) :: &
685  & hi & ! ice thickness (m)
686  &, hs & ! snow thickness (m)
687  &, dhi & ! change in ice thickness (m)
688  &, dhs & ! change in snow thickness (m)
689  &, dz & ! distance freeboard below SL (m)
690  &, fs ! salt flux due to snow-ice conversion
691 
692  real (kind=dbl_kind), dimension(ilo:ihi,jlo:jhi) :: &
693  & de ! energy transferred to each ice layer(J/m^2)
694 
695  integer (kind=int_kind) :: &
696  & icells & ! number of cells with ice
697  &, jcells & ! number of cells with freeboard adjustment
698  &, ij ! combined i/j horizontal index
699 
700  integer (kind=int_kind), &
701  & dimension (1:(ihi-ilo+1)*(jhi-jlo+1)) :: &
702  & indxi & ! compressed i/j indices
703  &, indxj &
704  &, indxi2 &
705  &, indxj2
706 
707  do ni = 1, ncat
708 
709  !-----------------------------------------------------------------
710  ! Identify grid cells with ice.
711  !-----------------------------------------------------------------
712  icells = 0
713  do j = jlo, jhi
714  do i = ilo, ihi
715  if (aicen(i,j,ni) > puny) then
716  icells = icells + 1
717  indxi(icells) = i
718  indxj(icells) = j
719  endif
720  enddo ! i
721  enddo ! j
722 
723  jcells = 0 ! freeboard adjustment counter
724 
725 !DIR$ CONCURRENT !Cray
726 !cdir nodep !NEC
727 !ocl novrec !Fujitsu
728  do ij = 1, icells ! aicen > puny
729  i = indxi(ij)
730  j = indxj(ij)
731 
732  !-----------------------------------------------------------------
733  ! Determine whether snow lies below freeboard.
734  !-----------------------------------------------------------------
735 
736  hi = vicen(i,j,ni) / aicen(i,j,ni)
737  hs = vsnon(i,j,ni) / aicen(i,j,ni)
738 
739  dz = hs - hi*(rhow-rhoi)/rhos
740 
741  if (dz > puny .and. hs > puny) then ! snow below freeboard
742  jcells = jcells + 1
743  indxi2(jcells) = i
744  indxj2(jcells) = j
745 
746  dhs = min(dz*rhoi/rhow, hs) ! snow to remove
747  dhi = dhs*rhos/rhoi ! ice to add
748 
749  !-----------------------------------------------------------------
750  ! Compute energy transferred from snow to ice.
751  ! NOTE: It would be more realistic to transfer energy only to
752  ! the top ice layer, but it is simpler to transfer equal
753  ! energy to all layers.)
754  !-----------------------------------------------------------------
755 
756  de(i,j) = esnon(i,j,ni)*dhs/hs
757  esnon(i,j,ni) = esnon(i,j,ni) - de(i,j)
758  de(i,j) = de(i,j)/real(nilyr,kind=dbl_kind) ! energy to each ice layer
759 
760  !-----------------------------------------------------------------
761  ! Adjust snow and ice volume.
762  !-----------------------------------------------------------------
763 
764  hi = hi + dhi
765  hs = hs - dhs
766  vicen(i,j,ni) = hi * aicen(i,j,ni)
767  vsnon(i,j,ni) = hs * aicen(i,j,ni)
768 
769  !-----------------------------------------------------------------
770  ! Update history and coupler variables.
771  !-----------------------------------------------------------------
772 
773  ! history diagnostic
774  snoice(i,j) = snoice(i,j) + dhi*aicen(i,j,ni)
775 
776  ! Remove salt from the ocean.
777  ! This is not physically realistic but is needed to
778  ! conserve salt, because salt will be returned to the ocean
779  ! when the ice melts.
780 
781 ! fs = -ice_ref_salinity*p001*aicen(i,j,n)*dhi*rhoi/dt
782  fs = -ice_ref_salinity*p001*aicen(i,j,ni)*dhi*rhoi/dtice
783  fsalt(i,j) = fsalt(i,j) + fs
784  fsalt_hist(i,j) = fsalt_hist(i,j) + fs
785 
786  endif ! dz > puny and hs > puny
787  enddo ! ij
788 
789  !-----------------------------------------------------------------
790  ! Adjust ice energy.
791  !-----------------------------------------------------------------
792  do k = 1, nilyr
793 !DIR$ CONCURRENT !Cray
794 !cdir nodep !NEC
795 !ocl novrec !Fujitsu
796  do ij = 1, jcells ! just cells with freeboard adjustment
797  i = indxi2(ij)
798  j = indxj2(ij)
799  eicen(i,j,ilyr1(ni)+k-1) = &
800  & eicen(i,j,ilyr1(ni)+k-1) + de(i,j)
801  enddo ! ij
802  enddo ! k
803 
804  enddo ! n
805 
real(kind=dbl_kind), dimension(:,:), allocatable, save fsalt_hist
Definition: ice_flux.f90:140
integer(kind=int_kind), parameter nilyr
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save esnon
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, save snoice
Definition: ice_flux.f90:140
integer(kind=int_kind) ihi
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter rhos
real(kind=dbl_kind), parameter ice_ref_salinity
integer(kind=int_kind) jlo
Definition: ice_domain.f90:101
integer(kind=int_kind) ilo
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter puny
real(kind=dbl_kind) dtice
integer(kind=int_kind) jhi
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter p001
real(kind=dbl_kind), parameter rhow
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save vicen
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, save fsalt
Definition: ice_flux.f90:120
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save eicen
Definition: ice_state.f90:108
integer(kind=int_kind), parameter ncat
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save aicen
Definition: ice_state.f90:97
real(sp), dimension(:,:), allocatable, target dz
Definition: mod_main.f90:1092
real(kind=dbl_kind), parameter rhoi
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save vsnon
Definition: ice_state.f90:97
Here is the caller graph for this function:

◆ lateral_melt()

subroutine ice_therm_itd::lateral_melt ( real (kind=dbl_kind), dimension(ilo:ihi,jlo:jhi), intent(in)  rside)

Definition at line 543 of file ice_therm_itd.f90.

543 !
544 ! !USES:
545 !
546 ! !INPUT/OUTPUT PARAMETERS:
547 !
548  real (kind=dbl_kind), dimension(ilo:ihi,jlo:jhi), &
549  & intent(in) :: &
550  & rside ! fraction of ice that melts laterally
551 !
552 !EOP
553 !
554  integer (kind=int_kind) :: &
555  & i, j & ! horizontal indices
556  &, ni & ! thickness category index
557  &, k &! layer index
558  &, ij &! horizontal index, combines i and j loops
559  &, icells ! number of cells with aice > puny
560 
561  integer (kind=int_kind), dimension(1:(ihi-ilo+1)*(jhi-jlo+1)) :: &
562  & indxi, indxj ! compressed indices for cells with aice > puny
563 
564  real (kind=dbl_kind) :: &
565  & dfhnet & ! change in fhnet
566  &, dfresh & ! change in fresh
567  &, dfsalt ! change in fsalt
568 
569  do ni = 1, ncat
570 
571  !-----------------------------------------------------------------
572  ! Identify grid cells with lateral melting.
573  !-----------------------------------------------------------------
574 
575  icells = 0
576  do j = jlo, jhi
577  do i = ilo, ihi
578  if (rside(i,j) > c0i) then
579  icells = icells + 1
580  indxi(icells) = i
581  indxj(icells) = j
582  endif
583  enddo ! i
584  enddo ! j
585 
586  !-----------------------------------------------------------------
587  ! Melt the ice and increment fluxes.
588  !-----------------------------------------------------------------
589 
590 !DIR$ CONCURRENT !Cray
591 !cdir nodep !NEC
592 !ocl novrec !Fujitsu
593  do ij = 1, icells
594  i = indxi(ij)
595  j = indxj(ij)
596 
597  ! fluxes to coupler (except heat flux for ice melt)
598  ! dfhnet < 0, dfresh > 0, dfsalt > 0
599 
600  dfhnet = esnon(i,j,ni)*rside(i,j) / dtice
601 ! dfhnet = esnon(i,j,n)*rside(i,j) / dt
602  dfresh = (rhos*vsnon(i,j,ni) + rhoi*vicen(i,j,ni)) &
603 ! & * rside(i,j) / dt
604  & * rside(i,j) / dtice
605  dfsalt = rhoi*vicen(i,j,ni)*ice_ref_salinity*p001 &
606  & * rside(i,j) / dtice
607 ! & * rside(i,j) / dt
608 
609  fhnet(i,j) = fhnet(i,j) + dfhnet
610  fhnet_hist(i,j) = fhnet_hist(i,j) + dfhnet
611 
612  fresh(i,j) = fresh(i,j) + dfresh
613  fresh_hist(i,j) = fresh_hist(i,j) + dfresh
614 
615  fsalt(i,j) = fsalt(i,j) + dfsalt
616  fsalt_hist(i,j) = fsalt_hist(i,j) + dfsalt
617 
618  ! history diagnostics
619  meltl(i,j) = meltl(i,j) + vicen(i,j,ni)*rside(i,j)
620 
621  ! state variables (except ice energy)
622  aicen(i,j,ni) = aicen(i,j,ni) * (c1i - rside(i,j))
623  vicen(i,j,ni) = vicen(i,j,ni) * (c1i - rside(i,j))
624  vsnon(i,j,ni) = vsnon(i,j,ni) * (c1i - rside(i,j))
625  esnon(i,j,ni) = esnon(i,j,ni) * (c1i - rside(i,j))
626 
627  enddo ! ij
628 
629  do k = 1, nilyr
630 !DIR$ CONCURRENT !Cray
631 !cdir nodep !NEC
632 !ocl novrec !Fujitsu
633  do ij = 1, icells
634  i = indxi(ij)
635  j = indxj(ij)
636 
637  ! heat flux to coupler for ice melt (dfhnet < 0)
638 
639 ! dfhnet = eicen(i,j,ilyr1(ni)+k-1)*rside(i,j) / dt
640  dfhnet = eicen(i,j,ilyr1(ni)+k-1)*rside(i,j) / dtice
641  fhnet(i,j) = fhnet(i,j) + dfhnet
642  fhnet_hist(i,j) = fhnet_hist(i,j) + dfhnet
643 
644  ! ice energy
645  eicen(i,j,ilyr1(ni)+k-1) = eicen(i,j,ilyr1(ni)+k-1) &
646  & * (c1i - rside(i,j))
647  enddo ! ij
648  enddo ! k
649 
650  enddo ! n
651 
real(kind=dbl_kind), dimension(:,:), allocatable, save fsalt_hist
Definition: ice_flux.f90:140
integer(kind=int_kind), parameter nilyr
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save esnon
Definition: ice_state.f90:97
integer(kind=int_kind) ihi
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter c0i
real(kind=dbl_kind), parameter rhos
real(kind=dbl_kind), dimension(:,:), allocatable, save meltl
Definition: ice_flux.f90:140
real(kind=dbl_kind), parameter ice_ref_salinity
real(kind=dbl_kind), dimension(:,:), allocatable, save fhnet_hist
Definition: ice_flux.f90:140
real(kind=dbl_kind), dimension(:,:), allocatable, save fresh
Definition: ice_flux.f90:120
integer(kind=int_kind) jlo
Definition: ice_domain.f90:101
integer(kind=int_kind) ilo
Definition: ice_domain.f90:101
real(kind=dbl_kind) dtice
integer(kind=int_kind) jhi
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter p001
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save vicen
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, save fresh_hist
Definition: ice_flux.f90:140
real(kind=dbl_kind), dimension(:,:), allocatable, save fsalt
Definition: ice_flux.f90:120
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save eicen
Definition: ice_state.f90:108
integer(kind=int_kind), parameter ncat
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save aicen
Definition: ice_state.f90:97
real(kind=dbl_kind), parameter c1i
real(kind=dbl_kind), dimension(:,:), allocatable, save rside
real(kind=dbl_kind), parameter rhoi
real(kind=dbl_kind), dimension(:,:), allocatable, save fhnet
Definition: ice_flux.f90:120
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save vsnon
Definition: ice_state.f90:97
Here is the caller graph for this function:

◆ thermo_itd()

subroutine ice_therm_itd::thermo_itd ( )

Definition at line 96 of file ice_therm_itd.f90.

96 !
97 ! !USES:
98 !
99 ! use ice_timers
100  use ice_itd_linear
102 !
103 !EOP
104 !
105  integer (kind=int_kind) :: &
106  & i, j & ! horizontal indices
107  &, ni & ! thickness category index
108  &, k ! ice layer index
109 
110 ! call ice_timer_start(4) ! column model
111 
112  !-----------------------------------------------------------------
113  ! Save the ice area passed to the coupler.
114  ! This is needed to make the history fields consistent with
115  ! the coupler fields.
116  !-----------------------------------------------------------------
117  aice_init = aice
118 
119  !-----------------------------------------------------------------
120  ! Initialize ocean fluxes sent to the coupler.
121  !-----------------------------------------------------------------
122  call init_flux_ocn
123 
124  !-----------------------------------------------------------------
125  ! Let rain drain through to the ocean.
126  !-----------------------------------------------------------------
127 
128  do j=jlo,jhi
129  do i=ilo,ihi
130  fresh(i,j) = fresh(i,j) + frain(i,j)*aice(i,j)
131  fresh_hist(i,j) = fresh_hist(i,j) + frain(i,j)*aice(i,j)
132  enddo
133  enddo
134 
135  !-----------------------------------------------------------------
136  ! Update ice thickness.
137  !-----------------------------------------------------------------
138 
139 ! call ice_timer_start(5) ! thermodynamics
140  do ni = 1, ncat
141  do j=jlo,jhi
142  do i=ilo,ihi
143  if (aicen(i,j,ni) > puny) then
144  hicen(i,j,ni) = vicen(i,j,ni) / aicen(i,j,ni)
145  else
146  hicen(i,j,ni) = c0i
147  hicen_old(i,j,ni) = c0i
148  endif
149  enddo ! i
150  enddo ! j
151  enddo ! n
152 ! call ice_timer_stop(5) ! thermodynamics
153 
154  !-----------------------------------------------------------------
155  ! Given thermodynamic growth rates, transport ice between
156  ! thickness categories.
157  !-----------------------------------------------------------------
158 
159 ! call ice_timer_start(7) ! category conversions (transport in h)
160  if (kitd == 1) call linear_itd (hicen_old, hicen)
161 ! call ice_timer_stop(7) ! category conversions
162 
163  !-----------------------------------------------------------------
164  ! Add frazil ice growing in leads.
165  !-----------------------------------------------------------------
166 
167 ! call ice_timer_start(5) ! thermodynamics
168  call add_new_ice
169 
170  !-----------------------------------------------------------------
171  ! Melt ice laterally.
172  !-----------------------------------------------------------------
173  call lateral_melt (rside)
174 
175  !-----------------------------------------------------------------
176  ! Convert snow below freeboard to ice.
177  !-----------------------------------------------------------------
178  call freeboard
179 ! call ice_timer_stop(5) ! thermodynamics
180 
181  !-----------------------------------------------------------------
182  ! Make sure ice in each category is within its thickness bounds.
183  ! NOTE: The rebin subroutine is needed only in the rare cases
184  ! when the linear_itd subroutine cannot transfer ice
185  ! correctly (e.g., very fast ice growth).
186  !-----------------------------------------------------------------
187 
188 ! call ice_timer_start(7) ! category conversions
189  if (ncat==1) then
190  call reduce_area (hicen_old(:,:,1), hicen(:,:,1))
191  else
192  call rebin
193  endif ! ncat = 1
194 ! call ice_timer_stop(7) ! category conversions
195 
196  !-----------------------------------------------------------------
197  ! Zero out ice categories with very small areas.
198  !-----------------------------------------------------------------
199  call zap_small_areas
200 
201  !-----------------------------------------------------------------
202  ! Aggregate cell values over thickness categories.
203  !-----------------------------------------------------------------
204  call aggregate
205 
206  !-----------------------------------------------------------------
207  ! Compute thermodynamic area and volume tendencies.
208  !-----------------------------------------------------------------
209 
210  do j=jlo,jhi
211  do i=ilo,ihi
212 ! daidtt(i,j) = (aice(i,j) - daidtt(i,j)) / dt
213 ! dvidtt(i,j) = (vice(i,j) - dvidtt(i,j)) / dt
214  daidtt(i,j) = (aice(i,j) - daidtt(i,j)) / dtice
215  dvidtt(i,j) = (vice(i,j) - dvidtt(i,j)) / dtice
216 
217  daidtd(i,j) = aice(i,j) ! temporarily used for initial area
218  dvidtd(i,j) = vice(i,j) ! temporarily used for initial volume
219  enddo ! i
220  enddo ! j
221 
222 ! call ice_timer_stop(4) ! column model
223 
real(kind=dbl_kind), dimension(:,:,:), allocatable, save hicen_old
integer(kind=int_kind) ihi
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter c0i
subroutine linear_itd(hicen_old, hicen)
integer(kind=int_kind) kitd
Definition: ice_itd.f90:62
real(kind=dbl_kind), dimension(:,:), allocatable, save fresh
Definition: ice_flux.f90:120
integer(kind=int_kind) jlo
Definition: ice_domain.f90:101
real(kind=dbl_kind), dimension(:,:), allocatable, save daidtd
Definition: ice_flux.f90:55
integer(kind=int_kind) ilo
Definition: ice_domain.f90:101
real(kind=dbl_kind), parameter puny
real(kind=dbl_kind) dtice
integer(kind=int_kind) jhi
Definition: ice_domain.f90:101
real(kind=dbl_kind), dimension(:,:), allocatable, save frain
Definition: ice_flux.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, save fresh_hist
Definition: ice_flux.f90:140
integer(kind=int_kind), parameter ncat
real(kind=dbl_kind), dimension(:,:,:), allocatable, target, save aicen
Definition: ice_state.f90:97
real(kind=dbl_kind), dimension(:,:), allocatable, save dvidtt
Definition: ice_flux.f90:140
real(kind=dbl_kind), dimension(:,:), allocatable, save daidtt
Definition: ice_flux.f90:140
real(kind=dbl_kind), dimension(:,:), allocatable, target, save vice
Definition: ice_state.f90:82
real(kind=dbl_kind), dimension(:,:), allocatable, target, save aice_init
Definition: ice_state.f90:82
subroutine init_flux_ocn
Definition: ice_flux.f90:239
real(kind=dbl_kind), dimension(:,:), allocatable, save rside
real(kind=dbl_kind), dimension(:,:), allocatable, save dvidtd
Definition: ice_flux.f90:55
Here is the call graph for this function:

Variable Documentation

◆ hicen

real (kind=dbl_kind), dimension (:,:,:), allocatable, save ice_therm_itd::hicen

Definition at line 66 of file ice_therm_itd.f90.

66  real (kind=dbl_kind), dimension (:,:,:),allocatable,save :: &
67  & hicen ! ice thickness (m)