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/2019/fix_ticket2229/src/OCE/ICB – NEMO

source: NEMO/branches/2019/fix_ticket2229/src/OCE/ICB/icbutl.F90 @ 10678

Last change on this file since 10678 was 10678, checked in by mathiot, 5 years ago

mask used in icb_bilin_h should have extra haloe (ticket #2229)

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