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 NEMO/branches/UKMO/NEMO_4.0.3_icb_speed_limit/src/OCE/ICB – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.3_icb_speed_limit/src/OCE/ICB/icbutl.F90 @ 14259

Last change on this file since 14259 was 14259, checked in by davestorkey, 3 years ago

UKMO/NEMO_4.0.3_icb_speed_limit : Bug fix and extra write-outs for error trap in icbutl_bilin_e.

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