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.
icbutl.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/icbutl.F90 @ 3381

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

NEMO branch dev_r3337_NOCS10_ICB: Changes to allow branch to compile with key_agrif. Not yet complete.

Along the way replace unnecessary POINTER declarations

File size: 32.7 KB
Line 
1MODULE icbutl
2
3   !!======================================================================
4   !!                       ***  MODULE  icbutl  ***
5   !! Icebergs:  various iceberg utility routines
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   !!----------------------------------------------------------------------
12   !!----------------------------------------------------------------------
13   !!   icb_utl_interp   :
14   !!   icb_utl_bilin    :
15   !!   icb_utl_bilin_e  :
16   !!----------------------------------------------------------------------
17   USE par_oce                             ! ocean parameters
18   USE dom_oce                             ! ocean domain
19   USE in_out_manager                      ! IO parameters
20   USE lbclnk                              ! lateral boundary condition
21   USE lib_mpp                             ! MPI code and lk_mpp in particular
22   USE icb_oce                             ! define iceberg arrays
23   USE sbc_oce                             ! ocean surface boundary conditions
24#if defined key_lim2
25   USE ice_2,         ONLY: u_ice, v_ice   ! LIM-2 ice velocities  (CAUTION in C-grid do not use key_vp option)
26   USE ice_2,         ONLY: hicif          ! LIM-2 ice thickness
27#elif defined key_lim3
28   USE ice,           ONLY: u_ice, v_ice   ! LIM-3 variables  (always in C-grid)
29                                           ! gm  LIM3 case the mean ice thickness (i.e. averaged over categories)
30                                           ! gm            has to be computed somewhere in the ice and accessed here
31#endif
32
33   IMPLICIT NONE
34   PRIVATE
35
36   PUBLIC   icb_utl_copy          ! routine called in icbstp module
37   PUBLIC   icb_utl_interp        ! routine called in icbdyn, icbthm modules
38   PUBLIC   icb_utl_bilin         ! routine called in icbini, icbdyn modules
39   PUBLIC   icb_utl_bilin_x       ! routine called in icbdyn module
40   PUBLIC   icb_utl_add           ! routine called in icbini.F90, icbclv, icblbc and icbrst modules
41   PUBLIC   icb_utl_delete        ! routine called in icblbc, icbthm modules
42   PUBLIC   icb_utl_destroy       ! routine called in icbstp module
43   PUBLIC   icb_utl_track         ! routine not currently used, retain just in case
44   PUBLIC   icb_utl_print_berg    ! routine called in icbthm module
45   PUBLIC   icb_utl_print         ! routine called in icbini, icbstp module
46   PUBLIC   icb_utl_count         ! routine called in icbdia, icbini, icblbc, icbrst modules
47   PUBLIC   icb_utl_incr          ! routine called in icbini, icbclv modules
48   PUBLIC   icb_utl_yearday       ! routine called in icbclv, icbstp module
49   PUBLIC   icb_utl_mass          ! routine called in icbdia module
50   PUBLIC   icb_utl_heat          ! routine called in icbdia module
51
52   !!----------------------------------------------------------------------
53   !! NEMO/OPA 3.3 , NEMO Consortium (2011)
54   !! $Id:$
55   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
56   !!-------------------------------------------------------------------------
57
58CONTAINS
59
60   SUBROUTINE icb_utl_copy()
61      !!----------------------------------------------------------------------
62      !!                  ***  ROUTINE icb_utl_copy  ***
63      !!
64      !! ** Purpose :   iceberg initialization.
65      !!
66      !! ** Method  : - blah blah
67      !!----------------------------------------------------------------------
68
69      ! copy nemo forcing arrays into iceberg versions with extra halo
70      ! only necessary for variables not on T points
71      ! and ssh which is used to calculate gradients
72
73      uo_e(:,:) = 0._wp ;   uo_e(1:jpi, 1:jpj) = ssu_m(:,:)
74      vo_e(:,:) = 0._wp ;   vo_e(1:jpi, 1:jpj) = ssv_m(:,:)
75      ff_e(:,:) = 0._wp ;   ff_e(1:jpi, 1:jpj) = ff   (:,:)
76      ua_e(:,:) = 0._wp ;   ua_e(1:jpi, 1:jpj) = utau (:,:)
77      va_e(:,:) = 0._wp ;   va_e(1:jpi, 1:jpj) = vtau (:,:)
78
79      CALL lbc_lnk_e( uo_e, 'U', -1._wp, 1, 1 )
80      CALL lbc_lnk_e( vo_e, 'V', -1._wp, 1, 1 )
81      CALL lbc_lnk_e( ff_e, 'F', +1._wp, 1, 1 )
82      CALL lbc_lnk_e( ua_e, 'U', -1._wp, 1, 1 )
83      CALL lbc_lnk_e( va_e, 'V', -1._wp, 1, 1 )
84
85#if defined key_lim2 || defined key_lim3
86      ui_e(:,:) = 0._wp ;   ui_e(1:jpi, 1:jpj) = u_ice(:,:)
87      vi_e(:,:) = 0._wp ;   vi_e(1:jpi, 1:jpj) = v_ice(:,:)
88
89      CALL lbc_lnk_e( ui_e, 'U', -1._wp, 1, 1 )
90      CALL lbc_lnk_e( vi_e, 'V', -1._wp, 1, 1 )
91#endif
92
93      !! special for ssh which is used to calculate slope
94      !! so fudge some numbers all the way around the boundary
95
96      ssh_e(:,:) = 0._wp ;   ssh_e(1:jpi, 1:jpj) = ssh_m(:,:)
97      ssh_e(0    ,    :) = ssh_e(1  ,  :)
98      ssh_e(jpi+1,    :) = ssh_e(jpi,  :)
99      ssh_e(:    ,    0) = ssh_e(:  ,  1)
100      ssh_e(:    ,jpj+1) = ssh_e(:  ,jpj)
101      ssh_e(0,0)         = ssh_e(1,1)
102      ssh_e(jpi+1,0)     = ssh_e(jpi,1)
103      ssh_e(0,jpj+1)     = ssh_e(1,jpj)
104      ssh_e(jpi+1,jpj+1) = ssh_e(jpi,jpj)
105      CALL lbc_lnk_e( ssh_e, 'T', +1._wp, 1, 1 )
106      !
107   END SUBROUTINE icb_utl_copy
108
109
110   SUBROUTINE icb_utl_interp( pi, pe1, puo, pui, pua, pssh_i,   &
111      &                       pj, pe2, pvo, pvi, pva, pssh_j,   &
112      &                       psst, pcn, phi, pff            )
113      !!----------------------------------------------------------------------
114      !!                  ***  ROUTINE icb_utl_interp  ***
115      !!
116      !! ** Purpose :   interpolation
117      !!
118      !! ** Method  : - interpolate from various ocean arrays onto iceberg position
119      !!
120      !!       !!gm  CAUTION here I do not care of the slip/no-slip conditions
121      !!             this can be done later (not that easy to do...)
122      !!             right now, U is 0 in land so that the coastal value of velocity parallel to the coast
123      !!             is half the off shore value, wile the normal-to-the-coast value is zero.
124      !!             This is OK as a starting point.
125      !!
126      !!----------------------------------------------------------------------
127      REAL(wp), INTENT(in   ) ::   pi , pj                        ! position in (i,j) referential
128      REAL(wp), INTENT(  out) ::   pe1, pe2                       ! i- and j scale factors
129      REAL(wp), INTENT(  out) ::   puo, pvo, pui, pvi, pua, pva   ! ocean, ice and wind speeds
130      REAL(wp), INTENT(  out) ::   pssh_i, pssh_j                 ! ssh i- & j-gradients
131      REAL(wp), INTENT(  out) ::   psst, pcn, phi, pff            ! SST, ice concentration, ice thickness, Coriolis
132      !
133      REAL(wp) ::   zcd, zmod       ! local scalars
134      !!----------------------------------------------------------------------
135
136      pe1 = icb_utl_bilin_e( e1t, e1u, e1v, e1f, pi, pj )         ! scale factors
137      pe2 = icb_utl_bilin_e( e2t, e2u, e2v, e2f, pi, pj )
138      !
139      puo  = icb_utl_bilin_h( uo_e, pi, pj, 'U' )             ! ocean velocities
140      pvo  = icb_utl_bilin_h( vo_e, pi, pj, 'V' )
141      psst = icb_utl_bilin( sst_m, pi, pj, 'T' )            ! SST
142      pcn  = icb_utl_bilin( fr_i , pi, pj, 'T' )            ! ice concentration
143      pff  = icb_utl_bilin_h( ff_e , pi, pj, 'F' )            ! Coriolis parameter
144      !
145      pua  = icb_utl_bilin_h( ua_e , pi, pj, 'U' )            ! 10m wind
146      pva  = icb_utl_bilin_h( va_e , pi, pj, 'V' )            ! here (ua,va) are stress => rough conversion from stress to speed
147      zcd  = 1.22_wp * 1.5e-3_wp                                  ! air density * drag coefficient
148      zmod = 1._wp / MAX(  1.e-20, SQRT(  zcd * SQRT( pua*pua + pva*pva)  )  )
149      pua  = pua * zmod                                           ! note: stress module=0 necessarly implies ua=va=0
150      pva  = pva * zmod
151
152#if defined key_lim2 || defined key_lim3
153      pui = icb_utl_bilin_h( ui_e, pi, pj, 'U' )              ! sea-ice velocities
154      pvi = icb_utl_bilin_h( vi_e, pi, pj, 'V' )
155      phi = icb_utl_bilin(hicif, pi, pj, 'T' )              ! ice thickness
156#else
157      pui = 0._wp
158      pvi = 0._wp
159      phi = 0._wp
160#endif
161
162      ! Estimate SSH gradient in i- and j-direction (centred evaluation)
163      pssh_i = ( icb_utl_bilin_h( ssh_e, pi+0.1_wp, pj, 'T' ) -   &
164          &      icb_utl_bilin_h( ssh_e, pi-0.1_wp, pj, 'T' )  ) / ( 0.2_wp * pe1 )
165      pssh_j = ( icb_utl_bilin_h( ssh_e, pi, pj+0.1_wp, 'T' ) -   &
166          &      icb_utl_bilin_h( ssh_e, pi, pj-0.1_wp, 'T' )  ) / ( 0.2_wp * pe2 )
167      !
168   END SUBROUTINE icb_utl_interp
169
170
171   REAL(wp) FUNCTION icb_utl_bilin_h( pfld, pi, pj, cd_type )
172      !!----------------------------------------------------------------------
173      !!                  ***  FUNCTION icb_utl_bilin  ***
174      !!
175      !! ** Purpose :   bilinear interpolation at berg location depending on the grid-point type
176      !!                this version deals with extra halo points
177      !!
178      !!       !!gm  CAUTION an optional argument should be added to handle
179      !!             the slip/no-slip conditions  ==>>> to be done later
180      !!
181      !!----------------------------------------------------------------------
182      REAL(wp), DIMENSION(0:jpi+1,0:jpj+1), INTENT(in) ::   pfld      ! field to be interpolated
183      REAL(wp)                            , INTENT(in) ::   pi, pj    ! targeted coordinates in (i,j) referential
184      CHARACTER(len=1)                    , INTENT(in) ::   cd_type   ! type of pfld array grid-points: = T , U , V or F points
185      !
186      INTEGER  ::   ii, ij   ! local integer
187      REAL(wp) ::   zi, zj   ! local real
188      !!----------------------------------------------------------------------
189      !
190      SELECT CASE ( cd_type )
191         CASE ( 'T' )
192            ! note that here there is no +0.5 added
193            ! since we're looking for four T points containing quadrant we're in of
194            ! current T cell
195            ii = INT( pi     )
196            ij = INT( pj      )    ! T-point
197            zi = pi - REAL(ii,wp)
198            zj = pj - REAL(ij,wp)
199         CASE ( 'U' )
200            ii = INT( pi-0.5 )
201            ij = INT( pj      )    ! U-point
202            zi = pi - 0.5 - REAL(ii,wp)
203            zj = pj - REAL(ij,wp)
204         CASE ( 'V' )
205            ii = INT( pi     )
206            ij = INT( pj -0.5 )    ! V-point
207            zi = pi - REAL(ii,wp)
208            zj = pj - 0.5 - REAL(ij,wp)
209         CASE ( 'F' )
210            ii = INT( pi-0.5 )
211            ij = INT( pj -0.5 )    ! F-point
212            zi = pi - 0.5 - REAL(ii,wp)
213            zj = pj - 0.5 - REAL(ij,wp)
214      END SELECT
215      !
216      ! find position in this processor
217      ii = mi1( ii )
218      ij = mj1( ij )
219      !
220      icb_utl_bilin_h = ( pfld(ii,ij  ) * (1.-zi) + pfld(ii+1,ij  ) * zi ) * (1.-zj)   &
221         &            + ( pfld(ii,ij+1) * (1.-zi) + pfld(ii+1,ij+1) * zi ) *     zj
222      !
223   END FUNCTION icb_utl_bilin_h
224
225
226   REAL(wp) FUNCTION icb_utl_bilin( pfld, pi, pj, cd_type )
227      !!----------------------------------------------------------------------
228      !!                  ***  FUNCTION icb_utl_bilin  ***
229      !!
230      !! ** Purpose :   bilinear interpolation at berg location depending on the grid-point type
231      !!
232      !!       !!gm  CAUTION an optional argument should be added to handle
233      !!             the slip/no-slip conditions  ==>>> to be done later
234      !!
235      !!----------------------------------------------------------------------
236      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pfld      ! field to be interpolated
237      REAL(wp)                    , INTENT(in) ::   pi, pj    ! targeted coordinates in (i,j) referential
238      CHARACTER(len=1)            , INTENT(in) ::   cd_type   ! type of pfld array grid-points: = T , U , V or F points
239      !
240      INTEGER  ::   ii, ij   ! local integer
241      REAL(wp) ::   zi, zj   ! local real
242      !!----------------------------------------------------------------------
243      !
244      SELECT CASE ( cd_type )
245         CASE ( 'T' )
246            ! note that here there is no +0.5 added
247            ! since we're looking for four T points containing quadrant we're in of
248            ! current T cell
249            ii = INT( pi     )
250            ij = INT( pj      )    ! T-point
251            zi = pi - REAL(ii,wp)
252            zj = pj - REAL(ij,wp)
253         CASE ( 'U' )
254            ii = INT( pi-0.5 )
255            ij = INT( pj      )    ! U-point
256            zi = pi - 0.5 - REAL(ii,wp)
257            zj = pj - REAL(ij,wp)
258         CASE ( 'V' )
259            ii = INT( pi     )
260            ij = INT( pj -0.5 )    ! V-point
261            zi = pi - REAL(ii,wp)
262            zj = pj - 0.5 - REAL(ij,wp)
263         CASE ( 'F' )
264            ii = INT( pi-0.5 )
265            ij = INT( pj -0.5 )    ! F-point
266            zi = pi - 0.5 - REAL(ii,wp)
267            zj = pj - 0.5 - REAL(ij,wp)
268      END SELECT
269      !
270      ! find position in this processor
271      ii = mi1( ii )
272      ij = mj1( ij )
273      !
274      icb_utl_bilin = ( pfld(ii,ij  ) * (1.-zi) + pfld(ii+1,ij  ) * zi ) * (1.-zj)   &
275         &          + ( pfld(ii,ij+1) * (1.-zi) + pfld(ii+1,ij+1) * zi ) *     zj
276      !
277   END FUNCTION icb_utl_bilin
278
279
280   REAL(wp) FUNCTION icb_utl_bilin_x( pfld, pi, pj )
281      !!----------------------------------------------------------------------
282      !!                  ***  FUNCTION icb_utl_bilin_x  ***
283      !!
284      !! ** Purpose :   bilinear interpolation at berg location depending on the grid-point type
285      !!                Special case for interpolating longitude
286      !!
287      !!       !!gm  CAUTION an optional argument should be added to handle
288      !!             the slip/no-slip conditions  ==>>> to be done later
289      !!
290      !!----------------------------------------------------------------------
291      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pfld      ! field to be interpolated
292      REAL(wp)                    , INTENT(in) ::   pi, pj    ! targeted coordinates in (i,j) referential
293      !
294      INTEGER                                  ::   ii, ij   ! local integer
295      REAL(wp)                                 ::   zi, zj   ! local real
296      REAL(wp)                                 ::   zret     ! local real
297      REAL(wp), DIMENSION(4)                   ::   z4
298      !!----------------------------------------------------------------------
299      !
300      ! note that here there is no +0.5 added
301      ! since we're looking for four T points containing quadrant we're in of
302      ! current T cell
303      ii = INT( pi     )
304      ij = INT( pj      )    ! T-point
305      zi = pi - REAL(ii,wp)
306      zj = pj - REAL(ij,wp)
307      !
308      ! find position in this processor          !!gm use here mig, mjg arrays
309      ii = mi1( ii )
310      ij = mj1( ij )
311      z4(1) = pfld(ii  ,ij  )
312      z4(2) = pfld(ii+1,ij  )
313      z4(3) = pfld(ii  ,ij+1)
314      z4(4) = pfld(ii+1,ij+1)
315      IF( MAXVAL(z4) - MINVAL(z4) > 90._wp ) THEN
316         WHERE( z4 < 0._wp ) z4 = z4 + 360._wp
317      ENDIF
318      !
319      zret = (z4(1) * (1.-zi) + z4(2) * zi) * (1.-zj) + (z4(3) * (1.-zi) + z4(4) * zi) * zj
320      IF( zret > 180._wp ) zret = zret - 360._wp
321      icb_utl_bilin_x = zret
322      !
323   END FUNCTION icb_utl_bilin_x
324
325
326   REAL(wp) FUNCTION icb_utl_bilin_e( pet, peu, pev, pef, pi, pj )
327      !!----------------------------------------------------------------------
328      !!                  ***  FUNCTION dom_init  ***
329      !!
330      !! ** Purpose :   bilinear interpolation at berg location of horizontal scale factor
331      !! ** Method  :   interpolation done using the 4 nearest grid points among
332      !!                t-, u-, v-, and f-points.
333      !!----------------------------------------------------------------------
334      REAL(wp), DIMENSION(:,:), INTENT(in) ::   pet, peu, pev, pef   ! horizontal scale factor to be interpolated at t-,u-,v- & f-pts
335      REAL(wp)                , INTENT(in) ::   pi, pj               ! targeted coordinates in (i,j) referential
336      !
337      INTEGER  ::   ii, ij, icase   ! local integer
338      !
339      ! weights corresponding to corner points of a T cell quadrant
340      REAL(wp) ::   zi, zj          ! local real
341      !
342      ! values at corner points of a T cell quadrant
343      ! 00 = bottom left, 10 = bottom right, 01 = top left, 11 = top right
344      REAL(wp) ::   ze00, ze10, ze01, ze11
345      !!----------------------------------------------------------------------
346      !
347      ii = INT( pi )   ;   ij = INT( pj )    ! left bottom T-point (i,j) indices
348
349      ! fractional box spacing
350      ! 0   <= zi < 0.5, 0   <= zj < 0.5   -->  NW quadrant of current T cell
351      ! 0.5 <= zi < 1  , 0   <= zj < 0.5   -->  NE quadrant
352      ! 0   <= zi < 0.5, 0.5 <= zj < 1     -->  SE quadrant
353      ! 0.5 <= zi < 1  , 0.5 <= zj < 1     -->  SW quadrant
354
355      zi = pi - REAL(ii,wp)          !!gm use here mig, mjg arrays
356      zj = pj - REAL(ij,wp)
357
358      ! find position in this processor
359      ii = mi1( ii )
360      ij = mj1( ij )
361
362      IF(    0.0_wp <= zi .AND. zi < 0.5_wp   ) THEN
363         IF( 0.0_wp <= zj .AND. zj < 0.5_wp        )   THEN        !  NE quadrant
364            !                                                      !             i=I       i=I+1/2
365            ze01 = pev(ii  ,ij  )   ;   ze11 = pef(ii  ,ij  )      !   j=J+1/2    V ------- F
366            ze00 = pet(ii  ,ij  )   ;   ze10 = peu(ii  ,ij  )      !   j=J        T ------- U
367            zi = 2._wp * zi
368            zj = 2._wp * zj
369         ELSE                                                      !  SE quadrant
370            !                                                                    !             i=I       i=I+1/2
371            ze01 = pet(ii  ,ij+1)   ;   ze11 = peu(ii  ,ij+1)      !   j=J+1      T ------- U
372            ze00 = pev(ii  ,ij  )   ;   ze10 = pef(ii  ,ij  )      !   j=J+1/2    V ------- F
373            zi = 2._wp *  zi
374            zj = 2._wp * (zj-0.5_wp)
375         ENDIF
376      ELSE
377         IF( 0.0_wp <= zj .AND. zj < 0.5_wp        )   THEN        !  NW quadrant
378            !                                                                    !             i=I       i=I+1/2
379            ze01 = pef(ii  ,ij  )   ;   ze11 = pev(ii+1,ij)        !   j=J+1/2    F ------- V
380            ze00 = peu(ii  ,ij  )   ;   ze10 = pet(ii+1,ij)        !   j=J        U ------- T
381            zi = 2._wp * (zi-0.5_wp)
382            zj = 2._wp *  zj
383         ELSE                                                      !  SW quadrant
384            !                                                                    !             i=I+1/2   i=I+1
385            ze01 = peu(ii  ,ij+1)   ;   ze11 = pet(ii+1,ij+1)      !   j=J+1      U ------- T
386            ze00 = pef(ii  ,ij  )   ;   ze10 = pev(ii+1,ij  )      !   j=J+1/2    F ------- V
387            zi = 2._wp * (zi-0.5_wp)
388            zj = 2._wp * (zj-0.5_wp)
389         ENDIF
390      ENDIF
391      !
392      icb_utl_bilin_e = ( ze01 * (1.-zi) + ze11 * zi ) *     zj    &
393         &            + ( ze00 * (1.-zi) + ze10 * zi ) * (1.-zj)
394      !
395   END FUNCTION icb_utl_bilin_e
396
397
398   SUBROUTINE icb_utl_add( bergvals, ptvals )
399      !!----------------------------------------------------------------------
400      !!                ***  ROUTINE icb_utl_add           ***
401      !!
402      !! ** Purpose :   add a new berg to the iceberg list
403      !!
404      !!----------------------------------------------------------------------
405      TYPE(iceberg), INTENT(in)           ::   bergvals
406      TYPE(point)  , INTENT(in)           ::   ptvals
407      !
408      TYPE(iceberg), POINTER ::   new => NULL()
409      !!----------------------------------------------------------------------
410      !
411      new => NULL()
412      CALL icb_utl_create( new, bergvals, ptvals )
413      CALL icb_utl_insert( new )
414      new => NULL()     ! Clear new
415      !
416   END SUBROUTINE icb_utl_add         
417
418
419   SUBROUTINE icb_utl_create( berg, bergvals, ptvals )
420      !!----------------------------------------------------------------------
421      !!                ***  ROUTINE icb_utl_create  ***
422      !!
423      !! ** Purpose :   add a new berg to the iceberg list
424      !!
425      !!----------------------------------------------------------------------
426      TYPE(iceberg), INTENT(in) ::   bergvals
427      TYPE(point)  , INTENT(in) ::   ptvals
428      TYPE(iceberg), POINTER    ::   berg
429      !
430      TYPE(point)  , POINTER    ::   pt
431      INTEGER                   ::   istat
432      !!----------------------------------------------------------------------
433      !
434      IF( ASSOCIATED(berg) )   CALL ctl_stop( 'icebergs, icb_utl_create: berg already associated' )
435      ALLOCATE(berg, STAT=istat)
436      IF( istat /= 0 ) CALL ctl_stop( 'failed to allocate iceberg' )
437      berg%number(:) = bergvals%number(:)
438      berg%mass_scaling = bergvals%mass_scaling
439      berg%prev => NULL()
440      berg%next => NULL()
441      !
442      ALLOCATE(pt, STAT=istat)
443      IF( istat /= 0 ) CALL ctl_stop( 'failed to allocate first iceberg point' )
444      pt = ptvals
445      berg%current_point => pt
446      !
447   END SUBROUTINE icb_utl_create
448
449
450   SUBROUTINE icb_utl_insert( newberg )
451      !!----------------------------------------------------------------------
452      !!                 ***  ROUTINE icb_utl_insert  ***
453      !!
454      !! ** Purpose :   add a new berg to the iceberg list
455      !!
456      !!----------------------------------------------------------------------
457      TYPE(iceberg), POINTER  ::   newberg
458      !
459      TYPE(iceberg), POINTER  ::   this, prev, last
460      !!----------------------------------------------------------------------
461      !
462      IF( ASSOCIATED( first_berg ) ) THEN
463         last => first_berg
464         DO WHILE (ASSOCIATED(last%next))
465            last => last%next
466         ENDDO
467         newberg%prev => last
468         last%next    => newberg
469         last         => newberg
470      ELSE                       ! list is empty so create it
471         first_berg => newberg
472      ENDIF
473      !
474   END SUBROUTINE icb_utl_insert
475
476
477   REAL(wp) FUNCTION icb_utl_yearday(kmon, kday, khr, kmin, ksec)
478      !!----------------------------------------------------------------------
479      !!                 ***  FUNCTION icb_utl_yearday  ***
480      !!
481      !! ** Purpose :   
482      !!
483      ! sga - improved but still only applies to 365 day year, need to do this properly
484      !
485      !!gm  all these info are already known in daymod, no???
486      !!
487      !!----------------------------------------------------------------------
488      INTEGER, INTENT(in)     :: kmon, kday, khr, kmin, ksec
489      !
490      INTEGER, DIMENSION(12)  :: imonths = (/ 0,31,28,31,30,31,30,31,31,30,31,30 /)
491      !!----------------------------------------------------------------------
492      !
493      icb_utl_yearday = REAL( SUM( imonths(1:kmon) ), wp )
494      icb_utl_yearday = icb_utl_yearday + REAL(kday-1,wp) + (REAL(khr,wp) + (REAL(kmin,wp) + REAL(ksec,wp)/60.)/60.)/24.
495      !
496   END FUNCTION icb_utl_yearday
497
498   !!-------------------------------------------------------------------------
499
500   SUBROUTINE icb_utl_delete( first, berg )
501      !!----------------------------------------------------------------------
502      !!                 ***  ROUTINE icb_utl_delete  ***
503      !!
504      !! ** Purpose :   
505      !!
506      !!----------------------------------------------------------------------
507      TYPE(iceberg), POINTER :: first, berg
508      !!----------------------------------------------------------------------
509      ! Connect neighbors to each other
510      IF ( ASSOCIATED(berg%prev) ) THEN
511        berg%prev%next => berg%next
512      ELSE
513        first => berg%next
514      ENDIF
515      IF (ASSOCIATED(berg%next)) berg%next%prev => berg%prev
516      !
517      CALL icb_utl_destroy(berg)
518      !
519   END SUBROUTINE icb_utl_delete
520
521
522   SUBROUTINE icb_utl_destroy( berg )
523      !!----------------------------------------------------------------------
524      !!                 ***  ROUTINE icb_utl_destroy  ***
525      !!
526      !! ** Purpose :   remove a single iceberg instance
527      !!
528      !!----------------------------------------------------------------------
529      TYPE(iceberg), POINTER :: berg
530      !!----------------------------------------------------------------------
531      !
532      ! Remove any points
533      IF( ASSOCIATED( berg%current_point ) )   DEALLOCATE( berg%current_point )
534      !
535      DEALLOCATE(berg)
536      !
537   END SUBROUTINE icb_utl_destroy
538
539
540   SUBROUTINE icb_utl_track( knum, cd_label, kt )
541      !!----------------------------------------------------------------------
542      !!                 ***  ROUTINE icb_utl_track  ***
543      !!
544      !! ** Purpose :   
545      !!
546      !!----------------------------------------------------------------------
547      INTEGER, DIMENSION(nkounts)    :: knum       ! iceberg number
548      CHARACTER(len=*)               :: cd_label   !
549      INTEGER                        :: kt         ! timestep number
550      !
551      TYPE(iceberg), POINTER         :: this
552      LOGICAL                        :: match
553      INTEGER                        :: k
554      !!----------------------------------------------------------------------
555      !
556      this => first_berg
557      DO WHILE( ASSOCIATED(this) )
558         match = .TRUE.
559         DO k = 1, nkounts
560            IF( this%number(k) /= knum(k) ) match = .FALSE.
561         END DO
562         IF( match )   CALL icb_utl_print_berg(this, kt)
563         this => this%next
564      END DO
565      !
566   END SUBROUTINE icb_utl_track
567
568
569   SUBROUTINE icb_utl_print_berg( berg, kt )
570      !!----------------------------------------------------------------------
571      !!                 ***  ROUTINE icb_utl_print_berg  ***
572      !!
573      !! ** Purpose :   print one
574      !!
575      !!----------------------------------------------------------------------
576      TYPE(iceberg), POINTER :: berg
577      TYPE(point)  , POINTER :: pt
578      INTEGER                :: kt      ! timestep number
579      !!----------------------------------------------------------------------
580      !
581      pt => berg%current_point
582      WRITE(numicb, 9200) kt, berg%number(1), &
583                   pt%xi, pt%yj, pt%lon, pt%lat, pt%uvel, pt%vvel,  &
584                   pt%uo, pt%vo, pt%ua, pt%va, pt%ui, pt%vi
585      CALL flush( numicb )
586 9200 FORMAT(5x,i5,2x,i10,6(2x,2f10.4))
587      !
588   END SUBROUTINE icb_utl_print_berg
589
590
591   SUBROUTINE icb_utl_print( cd_label, kt )
592      !!----------------------------------------------------------------------
593      !!                 ***  ROUTINE icb_utl_print  ***
594      !!
595      !! ** Purpose :   print many
596      !!
597      !!----------------------------------------------------------------------
598      CHARACTER(len=*)       :: cd_label
599      INTEGER                :: kt             ! timestep number
600      !
601      INTEGER                :: ibergs, inbergs
602      TYPE(iceberg), POINTER :: this
603      !!----------------------------------------------------------------------
604      !
605      this => first_berg
606      IF( ASSOCIATED(this) ) THEN
607         WRITE(numicb,'(a," pe=(",i3,")")' ) cd_label, narea
608         WRITE(numicb,'(a8,4x,a6,12x,a5,15x,a7,19x,a3,17x,a5,17x,a5,17x,a5)' )   &
609            &         'timestep', 'number', 'xi,yj','lon,lat','u,v','uo,vo','ua,va','ui,vi'
610      ENDIF
611      DO WHILE( ASSOCIATED(this) )
612        CALL icb_utl_print_berg(this, kt)
613        this => this%next
614      END DO
615      ibergs = icb_utl_count()
616      inbergs = ibergs
617      IF( lk_mpp )   CALL mpp_sum(inbergs)
618      IF( ibergs > 0 )   WRITE(numicb,'(a," there are",i5," bergs out of",i6," on PE ",i4)')   &
619         &                                  cd_label, ibergs, inbergs, narea
620      !
621   END SUBROUTINE icb_utl_print
622
623
624   SUBROUTINE icb_utl_incr()
625      !!----------------------------------------------------------------------
626      !!                 ***  ROUTINE icb_utl_incr  ***
627      !!
628      !! ** Purpose :   
629      !!
630      ! Small routine for coping with very large integer values labelling icebergs
631      ! num_bergs is a array of integers
632      ! the first member is incremented in steps of jpnij starting from narea
633      ! this means each iceberg is labelled with a unique number
634      ! when this gets to the maximum allowed integer the second and subsequent members are
635      ! used to count how many times the member before cycles
636      !!----------------------------------------------------------------------
637      INTEGER ::   ii, ibig
638      !!----------------------------------------------------------------------
639
640      ibig = HUGE(num_bergs(1))
641      IF( ibig-jpnij < num_bergs(1) ) THEN
642         num_bergs(1) = narea
643         DO ii = 2,nkounts
644            IF( num_bergs(ii) == ibig ) THEN
645               num_bergs(ii) = 0
646               IF( ii == nkounts ) CALL ctl_stop('Sorry, run out of iceberg number space')
647            ELSE
648               num_bergs(ii) = num_bergs(ii) + 1
649               EXIT
650            ENDIF
651         END DO
652      ELSE
653         num_bergs(1) = num_bergs(1) + jpnij
654      ENDIF
655      !
656   END SUBROUTINE icb_utl_incr
657
658
659   INTEGER FUNCTION icb_utl_count()
660      !!----------------------------------------------------------------------
661      !!                 ***  FUNCTION icb_utl_count  ***
662      !!
663      !! ** Purpose :   
664      !!----------------------------------------------------------------------
665      TYPE(iceberg), POINTER :: this
666      !!----------------------------------------------------------------------
667      !
668      icb_utl_count = 0
669      this => first_berg
670      DO WHILE( ASSOCIATED(this) )
671         icb_utl_count = icb_utl_count+1
672         this => this%next
673      END DO
674      !
675   END FUNCTION icb_utl_count
676
677
678   REAL(wp) FUNCTION icb_utl_mass( first, justbits, justbergs )
679      !!----------------------------------------------------------------------
680      !!                 ***  FUNCTION icb_utl_mass  ***
681      !!
682      !! ** Purpose :   compute the mass all iceberg, all berg bits or all bergs.
683      !!----------------------------------------------------------------------
684      TYPE(iceberg)      , POINTER  ::   first
685      TYPE(point)        , POINTER  ::   pt
686      LOGICAL, INTENT(in), OPTIONAL ::   justbits, justbergs
687      !
688      TYPE(iceberg), POINTER ::   this
689      !!----------------------------------------------------------------------
690      icb_utl_mass = 0._wp
691      this => first
692      !
693      IF( PRESENT( justbergs  ) ) THEN
694         DO WHILE( ASSOCIATED( this ) )
695            pt => this%current_point
696            icb_utl_mass = icb_utl_mass + pt%mass         * this%mass_scaling
697            this => this%next
698         END DO
699      ELSEIF( PRESENT(justbits) ) THEN
700         DO WHILE( ASSOCIATED( this ) )
701            pt => this%current_point
702            icb_utl_mass = icb_utl_mass + pt%mass_of_bits * this%mass_scaling
703            this => this%next
704         END DO
705      ELSE
706         DO WHILE( ASSOCIATED( this ) )
707            pt => this%current_point
708            icb_utl_mass = icb_utl_mass + ( pt%mass + pt%mass_of_bits ) * this%mass_scaling
709            this => this%next
710         END DO
711      ENDIF
712      !
713   END FUNCTION icb_utl_mass
714
715
716   REAL(wp) FUNCTION icb_utl_heat( first, justbits, justbergs )
717      !!----------------------------------------------------------------------
718      !!                 ***  FUNCTION icb_utl_heat  ***
719      !!
720      !! ** Purpose :   compute the heat in all iceberg, all bergies or all bergs.
721      !!----------------------------------------------------------------------
722      TYPE(iceberg)      , POINTER  ::   first
723      LOGICAL, INTENT(in), OPTIONAL ::   justbits, justbergs
724      !
725      TYPE(iceberg)      , POINTER  ::   this
726      TYPE(point)        , POINTER  ::   pt
727      !!----------------------------------------------------------------------
728      icb_utl_heat = 0._wp
729      this => first
730      !
731      IF( PRESENT( justbergs  ) ) THEN
732         DO WHILE( ASSOCIATED( this ) )
733            pt => this%current_point
734            icb_utl_heat = icb_utl_heat + pt%mass         * this%mass_scaling * pt%heat_density
735            this => this%next
736         END DO
737      ELSEIF( PRESENT(justbits) ) THEN
738         DO WHILE( ASSOCIATED( this ) )
739            pt => this%current_point
740            icb_utl_heat = icb_utl_heat + pt%mass_of_bits * this%mass_scaling * pt%heat_density
741            this => this%next
742         END DO
743      ELSE
744         DO WHILE( ASSOCIATED( this ) )
745            pt => this%current_point
746            icb_utl_heat = icb_utl_heat + ( pt%mass + pt%mass_of_bits ) * this%mass_scaling * pt%heat_density
747            this => this%next
748         END DO
749      ENDIF
750      !
751   END FUNCTION icb_utl_heat
752
753   !!======================================================================
754END MODULE icbutl
Note: See TracBrowser for help on using the repository browser.