New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
icbclv.F90 in NEMO/trunk/src/OCE/ICB – NEMO

source: NEMO/trunk/src/OCE/ICB/icbclv.F90 @ 9932

Last change on this file since 9932 was 9932, checked in by acc, 6 years ago

Some necessary (but not yet sufficient) changes to iceberg code to reinstate restartability. Details on ticket #2113

  • Property svn:keywords set to Id
File size: 9.0 KB
Line 
1MODULE icbclv
2   !!======================================================================
3   !!                       ***  MODULE  icbclv  ***
4   !! Icebergs:  calving routines for iceberg calving
5   !!======================================================================
6   !! History : 3.3.1 !  2010-01  (Martin&Adcroft) Original code
7   !!            -    !  2011-03  (Madec)          Part conversion to NEMO form
8   !!            -    !                            Removal of mapping from another grid
9   !!            -    !  2011-04  (Alderson)       Split into separate modules
10   !!            -    !  2011-05  (Alderson)       budgets into separate module
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   icb_clv_flx   : transfer input flux of ice into iceberg classes
15   !!   icb_clv       : calve icebergs from stored ice
16   !!----------------------------------------------------------------------
17   USE par_oce        ! NEMO parameters
18   USE dom_oce        ! NEMO ocean domain
19   USE phycst         ! NEMO physical constants
20   USE lib_mpp        ! NEMO MPI library, lk_mpp in particular
21   USE lbclnk         ! NEMO boundary exchanges for gridded data
22
23   USE icb_oce        ! iceberg variables
24   USE icbdia         ! iceberg diagnostics
25   USE icbutl         ! iceberg utility routines
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   icb_clv_flx  ! routine called in icbstp.F90 module
31   PUBLIC   icb_clv      ! routine called in icbstp.F90 module
32
33   !!----------------------------------------------------------------------
34   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
35   !! $Id$
36   !! Software governed by the CeCILL licence     (./LICENSE)
37   !!----------------------------------------------------------------------
38CONTAINS
39
40   SUBROUTINE icb_clv_flx( kt )
41      !!----------------------------------------------------------------------
42      !!                 ***  ROUTINE icb_clv_flx  ***
43      !!
44      !! ** Purpose :   accumulate ice available for calving into class arrays
45      !!
46      !!----------------------------------------------------------------------
47      INTEGER, INTENT(in) ::   kt
48      !
49      REAL(wp)      ::   zcalving_used, zdist, zfact
50      INTEGER       ::   jn, ji, jj                    ! loop counters
51      INTEGER       ::   imx                           ! temporary integer for max berg class
52      LOGICAL, SAVE ::   ll_first_call = .TRUE.
53      !!----------------------------------------------------------------------
54      !
55      ! Adapt calving flux and calving heat flux from coupler for use here
56      ! Use interior mask: so no bergs in overlap areas and convert from km^3/year to kg/s
57      ! this assumes that input is given as equivalent water flux so that pure water density is appropriate
58
59      zfact = ( (1000._wp)**3 / ( NINT(rday) * nyear_len(1) ) ) * 850._wp
60      berg_grid%calving(:,:) = src_calving(:,:) * tmask_i(:,:) * zfact
61
62      ! Heat in units of W/m2, and mask (just in case)
63      berg_grid%calving_hflx(:,:) = src_calving_hflx(:,:) * tmask_i(:,:)
64
65      IF( ll_first_call .AND. .NOT. l_restarted_bergs ) THEN      ! This is a hack to simplify initialization
66         ll_first_call = .FALSE.
67         !do jn=1, nclasses
68         !  where (berg_grid%calving==0.) berg_grid%stored_ice(:,:,jn)=0.
69         !end do
70         DO jj = 2, jpjm1
71            DO ji = 2, jpim1
72               IF( berg_grid%calving(ji,jj) /= 0._wp )                                          &    ! Need units of J
73                  berg_grid%stored_heat(ji,jj) = SUM( berg_grid%stored_ice(ji,jj,:) ) *         &    ! initial stored ice in kg
74                     &                   berg_grid%calving_hflx(ji,jj) * e1e2t(ji,jj) / berg_grid%calving(ji,jj)   ! J/s/m2 x m^2
75                     !                                                                                             ! = J/s/calving in kg/s
76            END DO
77         END DO
78      ENDIF
79
80      ! assume that all calving flux must be distributed even if distribution array does not sum
81      ! to one - this may not be what is intended, but it's what you've got
82      DO jj = 1, jpj
83         DO ji = 1, jpi
84            imx = berg_grid%maxclass(ji,jj)
85            zdist = SUM( rn_distribution(1:nclasses) ) / SUM( rn_distribution(1:imx) )
86            DO jn = 1, imx
87               berg_grid%stored_ice(ji,jj,jn) = berg_grid%stored_ice(ji,jj,jn)     &
88                  &                           + berg_dt * berg_grid%calving(ji,jj) * rn_distribution(jn) * zdist
89            END DO
90         END DO
91      END DO
92
93      ! before changing the calving, save the amount we're about to use and do budget
94      zcalving_used = SUM( berg_grid%calving(:,:) )
95      berg_grid%tmp(:,:) = berg_dt * berg_grid%calving_hflx(:,:) * e1e2t(:,:) * tmask_i(:,:)
96      berg_grid%stored_heat (:,:) = berg_grid%stored_heat (:,:) + berg_grid%tmp(:,:)
97      CALL icb_dia_income( kt,  zcalving_used, berg_grid%tmp )
98      !
99   END SUBROUTINE icb_clv_flx
100
101
102   SUBROUTINE icb_clv( kt )
103      !!----------------------------------------------------------------------
104      !!                 ***  ROUTINE icb_clv  ***
105      !!
106      !! ** Purpose :   This routine takes a stored ice field and calves to the ocean,
107      !!                so the gridded array stored_ice has only non-zero entries at selected
108      !!                wet points adjacent to known land based calving points
109      !!
110      !! ** method  : - Look at each grid point and see if there's enough for each size class to calve
111      !!                If there is, a new iceberg is calved.  This happens in the order determined by
112      !!                the class definition arrays (which in the default case is smallest first)
113      !!                Note that only the non-overlapping part of the processor where icebergs are allowed
114      !!                is considered
115      !!----------------------------------------------------------------------
116      INTEGER, INTENT(in) ::   kt
117      INTEGER       ::   ji, jj, jn   ! dummy loop indices
118      INTEGER       ::   icnt, icntmax
119      TYPE(iceberg) ::   newberg
120      TYPE(point)   ::   newpt
121      REAL(wp)      ::   zday, zcalved_to_berg, zheat_to_berg
122      !!----------------------------------------------------------------------
123      !
124      icntmax = 0
125      zday    = REAL(nday_year,wp) + REAL(nsec_day,wp)/86400.0_wp
126      !
127      DO jn = 1, nclasses
128         DO jj = nicbdj, nicbej
129            DO ji = nicbdi, nicbei
130               !
131               icnt = 0
132               !
133               DO WHILE (berg_grid%stored_ice(ji,jj,jn) >= rn_initial_mass(jn) * rn_mass_scaling(jn) )
134                  !
135                  newpt%lon = glamt(ji,jj)         ! at t-point (centre of the cell)
136                  newpt%lat = gphit(ji,jj)
137                  newpt%xi  = REAL( mig(ji), wp )
138                  newpt%yj  = REAL( mjg(jj), wp )
139                  !
140                  newpt%uvel = 0._wp               ! initially at rest
141                  newpt%vvel = 0._wp
142                  !                                ! set berg characteristics
143                  newpt%mass           = rn_initial_mass     (jn)
144                  newpt%thickness      = rn_initial_thickness(jn)
145                  newpt%width          = first_width         (jn)
146                  newpt%length         = first_length        (jn)
147                  newberg%mass_scaling = rn_mass_scaling     (jn)
148                  newpt%mass_of_bits   = 0._wp                          ! no bergy
149                  !
150                  newpt%year   = nyear
151                  newpt%day    = zday
152                  newpt%heat_density = berg_grid%stored_heat(ji,jj) / berg_grid%stored_ice(ji,jj,jn)   ! This is in J/kg
153                  !
154                  CALL icb_utl_incr()
155                  newberg%number(:) = num_bergs(:)
156                  !
157                  CALL icb_utl_add( newberg, newpt )
158                  !
159                  zcalved_to_berg = rn_initial_mass(jn) * rn_mass_scaling(jn)           ! Units of kg
160                  !                                ! Heat content
161                  zheat_to_berg           = zcalved_to_berg * newpt%heat_density             ! Units of J
162                  berg_grid%stored_heat(ji,jj) = berg_grid%stored_heat(ji,jj) - zheat_to_berg
163                  !                                ! Stored mass
164                  berg_grid%stored_ice(ji,jj,jn) = berg_grid%stored_ice(ji,jj,jn) - zcalved_to_berg
165                  !
166                  icnt = icnt + 1
167                  !
168                  CALL icb_dia_calve(ji, jj, jn,  zcalved_to_berg, zheat_to_berg )
169               END DO
170               icntmax = MAX( icntmax, icnt )
171            END DO
172         END DO
173      END DO
174      !
175      DO jn = 1, nclasses
176         CALL lbc_lnk( berg_grid%stored_ice(:,:,jn), 'T', 1._wp )
177      END DO
178      CALL lbc_lnk( berg_grid%stored_heat, 'T', 1._wp )
179      !
180      IF( nn_verbose_level > 0 .AND. icntmax > 1 )   WRITE(numicb,*) 'icb_clv: icnt=', icnt,' on', narea
181      !
182   END SUBROUTINE  icb_clv
183
184   !!======================================================================
185END MODULE icbclv
Note: See TracBrowser for help on using the repository browser.