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.
icbthm.F90 in branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB – NEMO

source: branches/2012/dev_r3337_NOCS10_ICB/NEMOGCM/NEMO/OPA_SRC/ICB/icbthm.F90 @ 3370

Last change on this file since 3370 was 3370, checked in by sga, 12 years ago

NEMO branch dev_r3337_NOCS10_ICB: lots of cosmetic Gurvanistic changes (the odd space or exclamation mark!)

File size: 11.4 KB
Line 
1MODULE icbthm
2
3   !!======================================================================
4   !!                       ***  MODULE  icbthm  ***
5   !! Icebergs:  thermodynamics routines for icebergs
6   !!======================================================================
7   !! History : 3.3.1 !  2010-01  (Martin&Adcroft) Original code
8   !!            -    !  2011-03  (Madec)          Part conversion to NEMO form
9   !!            -    !                            Removal of mapping from another grid
10   !!            -    !  2011-04  (Alderson)       Split into separate modules
11   !!            -    !  2011-05  (Alderson)       Use tmask instead of tmask_i
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   thermodynamics : initialise
15   !!                    reference for equations - M = Martin + Adcroft, OM 34, 2010
16   !!----------------------------------------------------------------------
17   USE par_oce        ! NEMO parameters
18   USE dom_oce        ! NEMO domain
19   USE in_out_manager ! NEMO IO routines, numout in particular
20   USE lib_mpp        ! NEMO MPI routines, ctl_stop in particular
21   USE phycst         ! NEMO physical constants
22   USE sbc_oce
23
24   USE icb_oce        ! define iceberg arrays
25   USE icbutl         ! iceberg utility routines
26   USE icbdia         ! iceberg budget routines
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   thermodynamics ! routine called in icbrun.F90 module
32
33CONTAINS
34
35   SUBROUTINE thermodynamics( kt )
36      !!----------------------------------------------------------------------
37      !!                  ***  ROUTINE thermodynamics  ***
38      !!
39      !! ** Purpose :   compute the iceberg thermodynamics.
40      !!
41      !! ** Method  : - blah blah
42      !!----------------------------------------------------------------------
43      INTEGER, INTENT(in) ::   kt   ! timestep number, just passed to print_berg
44      !
45      INTEGER  ::   ii, ij
46      REAL(wp) ::   zM, zT, zW, zL, zSST, zVol, zLn, zWn, zTn, znVol, zIC, zDn
47      REAL(wp) ::   zMv, zMe, zMb, zmelt, zdvo, zdva, zdM, zSs, zdMe, zdMb, zdMv
48      REAL(wp) ::   zMnew, zMnew1, zMnew2, zheat
49      REAL(wp) ::   zMbits, znMbits, zdMbitsE, zdMbitsM, zLbits, zAbits, zMbb
50      REAL(wp) ::   zxi, zyj, zff, z1_rday, z1_e1e2, zdt, z1_dt, z1_dt_e1e2
51      TYPE(iceberg), POINTER ::   this, next
52      TYPE(point)  , POINTER ::   pt
53      !!----------------------------------------------------------------------
54      !
55      z1_rday = 1._wp / rday
56     
57      ! we're either going to ignore berg fresh water melt flux and associated heat
58      ! or we pass it into the ocean, so at this point we set them both to zero,
59      ! accumulate the contributions to them from each iceberg in the while loop following
60      ! and then pass them (or not) to the ocean
61      !
62      berg_grid%floating_melt(:,:) = 0._wp
63      berg_grid%calving_hflx(:,:)  = 0._wp
64   
65      this => first_berg
66      DO WHILE( associated(this) )
67         !
68         pt => this%current_point
69         nknberg = this%number(1)
70         CALL interp_flds( pt%xi, pt%e1, pt%uo, pt%ui, pt%ua, pt%ssh_x, &
71         &                 pt%yj, pt%e2, pt%vo, pt%vi, pt%va, pt%ssh_y, &
72         &                 pt%sst, pt%cn, pt%hi, zff )
73         !
74         zSST = pt%sst
75         zIC  = MIN( 1._wp, pt%cn + rn_sicn_shift )     ! Shift sea-ice concentration       !!gm ???
76         zM   = pt%mass
77         zT   = pt%thickness                               ! total thickness
78       ! D   = (rn_rho_bergs/pp_rho_seawater)*zT ! draught (keel depth)
79       ! F   = zT - D ! freeboard
80         zW   = pt%width
81         zL   = pt%length
82         zxi  = pt%xi                                      ! position in (i,j) referential
83         zyj  = pt%yj
84         ii  = INT( zxi + 0.5 ) - nimpp + 1                    ! t-cell of the berg
85         ij  = INT( zyj + 0.5 ) - njmpp + 1
86         zVol = zT * zW * zL
87         zdt = berg_dt   ;   z1_dt = 1._wp / zdt
88
89         ! Environment
90         zdvo = SQRT( (pt%uvel-pt%uo)**2 + (pt%vvel-pt%vo)**2 )
91         zdva = SQRT( (pt%ua  -pt%uo)**2 + (pt%va  -pt%vo)**2 )
92         zSs  = 1.5 * SQRT( zdva ) + 0.1 * zdva                ! Sea state      (eqn M.A9)
93
94         ! Melt rates in m/s (i.e. division by rday)
95         zMv = MAX( 7.62e-3*zSST+1.29e-3*(zSST**2)            , 0._wp ) * z1_rday   ! Buoyant convection at sides (eqn M.A10)
96         zMb = MAX( 0.58*(zdvo**0.8)*(zSST+4.0)/(zL**0.2)      , 0._wp ) * z1_rday   ! Basal turbulent melting     (eqn M.A7 )
97         zMe = MAX( 1./12.*(zSST+2.)*zSs*(1+cos(rpi*(zIC**3))) , 0._wp ) * z1_rday   ! Wave erosion                (eqn M.A8 )
98
99         IF( ln_operator_splitting ) THEN      ! Operator split update of volume/mass
100            zTn    = MAX( zT - zMb*zdt , 0._wp )         ! new total thickness (m)
101            znVol  = zTn * zW * zL                        ! new volume (m^3)
102            zMnew1 = (znVol/zVol) * zM                    ! new mass (kg)
103            zdMb   = zM - zMnew1                         ! mass lost to basal melting (>0) (kg)
104            !
105            zLn    = MAX( zL - zMv*zdt , 0._wp )         ! new length (m)
106            zWn    = MAX( zW - zMv*zdt , 0._wp )         ! new width (m)
107            znVol  = zTn * zWn * zLn                      ! new volume (m^3)
108            zMnew2 = (znVol/zVol) * zM                    ! new mass (kg)
109            zdMv   = zMnew1 - zMnew2                     ! mass lost to buoyant convection (>0) (kg)
110            !
111            zLn    = MAX( zLn - zMe*zdt , 0._wp )        ! new length (m)
112            zWn    = MAX( zWn - zMe*zdt , 0._wp )        ! new width (m)
113            znVol  = zTn * zWn * zLn                      ! new volume (m^3)
114            zMnew  = ( znVol / zVol ) * zM                ! new mass (kg)
115            zdMe   = zMnew2 - zMnew                      ! mass lost to erosion (>0) (kg)
116            zdM    = zM - zMnew                          ! mass lost to all erosion and melting (>0) (kg)
117            !
118         ELSE                                         ! Update dimensions of berg
119            zLn = MAX( zL -(zMv+zMe)*zdt ,0._wp )         ! (m)
120            zWn = MAX( zW -(zMv+zMe)*zdt ,0._wp )         ! (m)
121            zTn = MAX( zT - zMb    *zdt ,0._wp )         ! (m)
122            ! Update volume and mass of berg
123            znVol = zTn*zWn*zLn                           ! (m^3)
124            zMnew = (znVol/zVol)*zM                       ! (kg)
125            zdM   = zM - zMnew                           ! (kg)
126            zdMb = (zM/zVol) * (zW*   zL ) *zMb*zdt         ! approx. mass loss to basal melting (kg)
127            zdMe = (zM/zVol) * (zT*(zW+zL)) *zMe*zdt         ! approx. mass lost to erosion (kg)
128            zdMv = (zM/zVol) * (zT*(zW+zL)) *zMv*zdt         ! approx. mass loss to buoyant convection (kg)
129         ENDIF
130
131         IF( rn_bits_erosion_fraction > 0._wp ) THEN      ! Bergy bits
132            !
133            zMbits   = pt%mass_of_bits                                               ! mass of bergy bits (kg)
134            zdMbitsE = rn_bits_erosion_fraction * zdMe                        ! change in mass of bits (kg)
135            znMbits  = zMbits + zdMbitsE                                               ! add new bergy bits to mass (kg)
136            zLbits   = MIN( zL, zW, zT, 40._wp )                                        ! assume bergy bits are smallest dimension or 40 meters
137            zAbits   = ( zMbits / rn_rho_bergs ) / zLbits                           ! Effective bottom area (assuming T=Lbits)
138            zMbb     = MAX( 0.58*(zdvo**0.8)*(zSST+2.0)/(zLbits**0.2), 0.) * z1_rday    ! Basal turbulent melting (for bits)
139            zMbb     = rn_rho_bergs * zAbits * zMbb                                 ! in kg/s
140            zdMbitsM = MIN( zMbb*zdt , znMbits )                                       ! bergy bits mass lost to melting (kg)
141            znMbits  = znMbits-zdMbitsM                                                ! remove mass lost to bergy bits melt
142            IF( zMnew == 0._wp ) THEN                                                ! if parent berg has completely melted then
143               zdMbitsM = zdMbitsM + znMbits                                           ! instantly melt all the bergy bits
144               znMbits  = 0._wp
145            ENDIF
146         ELSE                                                     ! No bergy bits
147            zAbits   = 0._wp
148            zdMbitsE = 0._wp
149            zdMbitsM = 0._wp
150            znMbits  = pt%mass_of_bits                             ! retain previous value incase non-zero
151         ENDIF
152
153         ! use tmask rather than tmask_i when dealing with icebergs
154         IF( tmask(ii,ij,1) /= 0._wp ) THEN    ! Add melting to the grid and field diagnostics
155            z1_e1e2    = 1._wp / e1e2t(ii,ij) * this%mass_scaling
156            z1_dt_e1e2 = z1_dt * z1_e1e2
157            zmelt    = ( zdM - ( zdMbitsE - zdMbitsM ) ) * z1_dt   ! kg/s
158            berg_grid%floating_melt(ii,ij) = berg_grid%floating_melt(ii,ij) + zmelt    * z1_e1e2    ! kg/m2/s
159            zheat = zmelt * pt%heat_density              ! kg/s x J/kg = J/s
160            berg_grid%calving_hflx (ii,ij) = berg_grid%calving_hflx (ii,ij) + zheat    * z1_e1e2    ! W/m2
161            CALL melt_budget( ii, ij, zMnew, zheat, this%mass_scaling,       &
162            &                         zdM, zdMbitsE, zdMbitsM, zdMb, zdMe,   &
163            &                         zdMv, z1_dt_e1e2 )
164         ELSE
165            WRITE(numout,*) 'thermodynamics: berg ',this%number(:),' appears to have grounded  at ',narea,ii,ij
166            CALL print_berg( this, kt )
167            WRITE(numout,*) 'msk=',tmask(ii,ij,1), e1e2t(ii,ij)
168            CALL ctl_stop('thermodynamics', 'berg appears to have grounded!')
169         ENDIF
170
171         ! Rolling
172         zDn = ( rn_rho_bergs / pp_rho_seawater ) * zTn       ! draught (keel depth)
173         IF( zDn > 0._wp .AND. MAX(zWn,zLn) < SQRT( 0.92*(zDn**2) + 58.32*zDn ) ) THEN
174            zT  = zTn
175            zTn = zWn
176            zWn = zT
177         endif
178
179         ! Store the new state of iceberg (with L>W)
180         pt%mass         = zMnew
181         pt%mass_of_bits = znMbits
182         pt%thickness    = zTn
183         pt%width        = min(zWn,zLn)
184         pt%length       = max(zWn,zLn)
185
186         next=>this%next
187
188!!gm  add a test to avoid over melting ?
189
190         IF( zMnew <= 0._wp ) THEN       ! Delete the berg if completely melted
191            CALL delete_iceberg_from_list( first_berg, this )
192            !
193         ELSE                            ! Diagnose mass distribution on grid
194            z1_e1e2 = 1._wp / e1e2t(ii,ij) * this%mass_scaling
195            CALL size_budget( ii, ij, zWn, zLn, zAbits,   &
196            &                 this%mass_scaling, zMnew, znMbits, z1_e1e2)
197         ENDIF
198         !
199         this=>next
200         !
201      END DO
202     
203      ! now use melt and associated heat flux in ocean (or not)
204      !
205      IF(.NOT. ln_passive_mode ) THEN
206         emp (:,:) = emp (:,:) - berg_grid%floating_melt(:,:)
207         emps(:,:) = emps(:,:) - berg_grid%floating_melt(:,:)
208!!       qns (:,:) = qns (:,:) + berg_grid%calving_hflx (:,:)  !!gm heat flux not yet properly coded ==>> need it, SOLVE that!
209      ENDIF
210      !
211   END SUBROUTINE thermodynamics
212
213   !!======================================================================
214END MODULE icbthm
Note: See TracBrowser for help on using the repository browser.