psmile_tricu_gauss2_extra.F90

Go to the documentation of this file.
00001 !-----------------------------------------------------------------------
00002 ! Copyright 2006-2010, NEC Europe Ltd., London, UK.
00003 ! Copyright 2011, DKRZ, Hamburg, Germany.
00004 ! All rights reserved. Use is subject to OASIS4 license terms.
00005 !-----------------------------------------------------------------------
00006 !BOP
00007 !
00008 ! !ROUTINE: psmile_tricu_gauss2_extra
00009 !
00010 ! !INTERFACE:
00011 
00012       subroutine psmile_tricu_gauss2_extra (search, grid_id, mask_array, &
00013                         mask_shape, mask_available, ibuf, len_item,      &
00014                         n_send, num_neigh, ierror)
00015 !
00016 ! !USES:
00017 !
00018       use PRISM
00019       use PSMILe, dummy_interface => psmile_tricu_gauss2_extra
00020       use psmile_grid_reduced_gauss
00021 
00022       Implicit none
00023 !
00024 ! !INPUT PARAMETERS:
00025 !
00026 
00027       Integer,                      Intent (In)    :: grid_id
00028 
00029 
00030       Integer,                      Intent (In)    :: mask_shape (2, ndim_3d)
00031 
00032 !     Dimension of (method) mask array
00033 
00034       Logical,                      Intent (In)    ::     
00035           mask_array ( mask_shape (1,1):mask_shape (2,1), 
00036                        mask_shape (1,2):mask_shape (2,2), 
00037                        mask_shape (1,3):mask_shape (2,3) )
00038 !     Mask of the method
00039 
00040       Logical,                     Intent (In)     :: mask_available
00041 
00042 !     Is mask specified in array "mask_array" ?
00043 !     mask_available = .false. : Mask is not available
00044 !                      .true.  : Mask is     available
00045 !
00046 
00047       Integer,                     Intent (In)     :: len_item
00048 !
00049 !     Number of pieces of information in integer buffer "ibuf".
00050 !        1:3: (i,j,k) index of lower left corner
00051 !        4  : Index in
00052 !        5  : Code for points required
00053 !
00054       Integer,                     Intent (In)    :: n_send
00055 !
00056 !     Number of extra points sent
00057 
00058       Integer,                     Intent (In)    :: num_neigh
00059 !
00060 !     (Maximal) Number of interpolations bases required..
00061 !
00062 !
00063 ! !INPUT/OUTPUT PARAMETERS:
00064 !
00065       Type (Enddef_global_search), Intent (InOut) :: search
00066 
00067 !     Data on the points to be searched
00068 
00069       Integer,                     Intent (InOut) :: ibuf (len_item, n_send)
00070 !
00071 !     Integer buffer containing the packed integer data.
00072 !     On return, ibuf (5, *) contains the code of the points found.
00073 !
00074 ! !OUTPUT PARAMETERS:
00075 !
00076       Integer,                     Intent (Out)   :: ierror
00077 
00078 !     Returns the error code of PSMILe_Search_donor_extra;
00079 !             ierror = 0 : No error
00080 !             ierror > 0 : Severe error
00081 !
00082 ! !LOCAL PARAMETERS:
00083 !
00084 ! n_corners_3d = Number of interpolation bases in 3d case
00085 !
00086 ! masked_out   = Hash value for a point which is masked out
00087 !
00088       Integer, Parameter           :: n_corners_3d = 4 * 4 * 4
00089 !
00090       Integer, Parameter           :: masked_out = 0
00091 !
00092 ! !LOCAL VARIABLES
00093 !
00094 !     ... loop variables
00095 !
00096       Integer                      :: j, n, i, k
00097 !
00098 !     ... For Grids
00099 !
00100       Type (Grid), Pointer         :: grid_info
00101       Integer,     Pointer         :: grid_valid_shape (:, :)
00102 !
00103 !     ... For Gaussreduced Grids
00104 !
00105       Logical                      :: virtual_cell_available
00106 !
00107 !     ... For searched points of control volume
00108 !
00109       Integer                      :: code, n_corners, outside
00110 !
00111       Integer, Allocatable         :: locs (:, :)
00112       Integer, Allocatable         :: neighbours_3d_extra (:, :, :)
00113       Integer, Allocatable         :: hash (:)
00114 !
00115 !
00116 !
00117       Logical                      :: missing_points(num_neigh, n_send)
00118       Integer                      :: decode_mask(num_neigh)
00119       Integer                      :: num_missing_points
00120 
00121       integer, parameter           :: shift_3d(ndim_3d, 9) = 
00122                                           reshape ((/-1,-1,0, 0,-1,0, +1,-1,0,
00123                                                      -1, 0,0, 0, 0,0, +1, 0,0,
00124                                                      -1,+1,0, 0,+1,0, +1,+1,0/), 
00125                                                    (/ndim_3d,9/))
00126 !
00127 !     ... for error parameters
00128 !
00129       Integer, parameter           :: nerrp = 1
00130       Integer                      :: ierrp (nerrp)
00131 !
00132 #ifdef DEBUG_TRACE
00133       Integer                      :: ictl_req, ind_loc (n_corners_3d)
00134 #endif
00135 !
00136 ! !DESCRIPTION:
00137 !
00138 ! Subroutine "psmile_tricu_gauss2_extra" performs the
00139 ! additional (global) search for grids of type "PRISM_Gaussreduced_regvrt".
00140 !
00141 ! !REVISION HISTORY:
00142 !
00143 !   Date      Programmer   Description
00144 ! ----------  ----------   -----------
00145 ! 03.07.05    H. Ritzdorf  created as psmile_tricu_gauss2_extra_dble.F90
00146 ! 27.01.11    M. Hanke     simplified code and corrected shifting, removed difference
00147 !                          between dble and real implementation
00148 !
00149 !EOP
00150 !----------------------------------------------------------------------
00151 !
00152 ! $Id: psmile_tricu_gauss2_extra.F90 3032 2011-03-18 17:29:36Z hanke $
00153 ! $Author: hanke $
00154 !
00155    Character(len=len_cvs_string), save :: mycvs = 
00156        '$Id: psmile_tricu_gauss2_extra.F90 3032 2011-03-18 17:29:36Z hanke $'
00157 !
00158 !----------------------------------------------------------------------
00159 !
00160 !  Initialization
00161 !
00162 #ifdef VERBOSE
00163       print 9990, trim(ch_id), grids(grid_id)%comp_id
00164 
00165       call psmile_flushstd
00166 #endif /* VERBOSE */
00167 !
00168       ierror = 0
00169       n_corners = num_neigh
00170 
00171 !
00172 !===> Get grid info
00173 !
00174 !  grid_valid_shape (2, ndim_3d) : Specifies the valid block shape
00175 !                                  for the "ndim_3d"-dimensional block
00176 !                                  (without halo/overlap regions)
00177 !
00178       grid_info => Grids(grid_id)
00179 !
00180       grid_valid_shape => grid_info%grid_shape
00181 !
00182       virtual_cell_available = len_item > ndim_3d + 2 ! unschoen
00183 !
00184       if (grid_info%grid_type /= PRISM_Gaussreduced_Regvrt) then
00185          print *, "grid_type", grid_info%grid_type
00186          call psmile_assert (__FILE__, __LINE__, &
00187                    "This routine is not designed for this grid type")
00188       endif
00189 !
00190       outside = grid_valid_shape (1, 1) - 11
00191 !
00192 #ifdef PRISM_ASSERTION
00193 
00194       if (num_neigh < 1 .or. num_neigh > n_corners_3d) then
00195          print *, 'num_neigh', num_neigh, n_corners_3d
00196          call psmile_assert ( __FILE__, __LINE__, &
00197                 'Invalid value for num_neigh (number of interpolation bases')
00198       endif
00199 !
00200 !===> Control input values contained in "ibuf"
00201 !
00202 !cdir vector
00203       do n = 1, n_send
00204          if (ibuf (2, n) < 1 .or. &
00205              ibuf (2, n) > size(grid_info%reduced_gauss_data%nbr_points_per_lat)) exit
00206       end do
00207 !
00208       if (n <= n_send) then
00209          print *, "i,j,k, gnbr_lats", ibuf(1:3,n), &
00210                   size(grid_info%reduced_gauss_data%nbr_points_per_lat)
00211          call psmile_assert (__FILE__, __LINE__, &
00212                    "second (virtual) index out of range")
00213       endif
00214 !
00215 !cdir vector
00216       do n = 1, n_send
00217          if (ibuf (1, n) < 1 .or. &
00218              ibuf (1, n) > grid_info%reduced_gauss_data%nbr_points_per_lat(ibuf(2,n))) exit
00219       end do
00220 !
00221       if (n <= n_send) then
00222          print *, "i,j,k, gpoints_per_lat", &
00223                   ibuf(1:3,n), grid_info%reduced_gauss_data%nbr_points_per_lat(ibuf(2,n))
00224          call psmile_assert (__FILE__, __LINE__, &
00225                    "first (virtual) index out of range")
00226       endif
00227 #endif
00228 
00229 #ifdef DEBUG_TRACE
00230 !cdir vector
00231       do ictl_req = 1, n_send
00232          if (ibuf (4, ictl_req) == 1) exit
00233       end do
00234 #endif
00235 
00236       ! 1st we rebuilt the neighbours_3d (global 3d representation) array
00237       ! for the source locations received
00238 
00239       allocate (neighbours_3d_extra (ndim_3d, n_send, 16), stat=ierror)
00240       if (ierror /= 0) then
00241          call psmile_error ( PRISM_Error_Alloc, 'locs', (/ndim_3d * n_send * 16/), 1, &
00242                  __FILE__, __LINE__ )
00243          return
00244       endif
00245 
00246       if (virtual_cell_available) then
00247          ! for all locations
00248          do n = 1, n_send
00249 
00250             if (ibuf(6, n) == 0) then
00251 
00252                neighbours_3d_extra(:,n,1:16) = &
00253                   psmile_gauss_get_bicu_stencil (grid_id, ibuf(1:3,n))
00254 
00255             else
00256 
00257                neighbours_3d_extra(:,n,1:16) = &
00258                   psmile_gauss_shift_bicu_stencil (grid_id, ibuf(1:3,n), &
00259                                                                                 shift_3d(:,ibuf(6, n)))
00260 
00261             endif
00262          enddo ! n
00263       else
00264          neighbours_3d_extra(:,n,1:16) = psmile_gauss_get_bicu_stencil (grid_id, ibuf(1:3,n))
00265       endif
00266 !
00267 !  decode which points are missing
00268 !
00269       do i = 1, num_neigh
00270          decode_mask(i) = ishft (1, i - 1)
00271       enddo
00272 
00273       do n = 1, n_send
00274          missing_points(:, n) = iand (decode_mask(:), ibuf(5, n)) /= 0
00275       enddo
00276 !
00277 !  how many points are missing?
00278 !
00279       num_missing_points = count (missing_points)
00280 #ifdef PRISM_ASSERTION
00281       if (num_missing_points <= 0) then
00282          call psmile_assert ( __FILE__, __LINE__, &
00283                              'Number of points to be searched == 0 ?!?')
00284       endif
00285 #endif
00286 
00287 #ifdef DEBUGX
00288       print *, 'code for locations to be searched (n_send =', num_missing_points, ')'
00289       do n = 1, n_send
00290          print *, n, 'srcloc =', ibuf(1:3,n), 'code =', ibuf (5, n)
00291          print *, '   decoded     =', missing_points(:,n)
00292       end do
00293 #endif
00294 !
00295 #ifdef DEBUG_TRACE
00296       if (ictl_req <= n_send) then
00297          print *, 'code for indices_req', ibuf (4, ictl_req)
00298          print *, 'ictl_req', ictl_req, 'srcloc', ibuf(1:3,ictl_req), &
00299                   'code', ibuf (5, ictl_req), missing_points(:, ictl_req)
00300       endif
00301 #endif
00302 !
00303 !  Allocate memory for the indices of the missing points
00304 !
00305       Allocate (locs (ndim_3d, num_missing_points), stat = ierror)
00306       if (ierror /= 0) then
00307          call psmile_error ( PRISM_Error_Alloc, 'locs', (/ndim_3d * num_missing_points/), 1, &
00308                  __FILE__, __LINE__ )
00309          return
00310       endif
00311 
00312       k = 0
00313 
00314       do i = 1, n_corners
00315 !cdir vector
00316          do n = 1, n_send
00317             if (missing_points (i,n)) then
00318 
00319                k = k + 1
00320 
00321                locs (:, k) = neighbours_3d_extra(:, n, iand (i-1, 15)+1)
00322 
00323                if (grid_valid_shape(2,3) - grid_valid_shape(1,3) >= ishft(n_corners, -4) - 1 .and. &
00324                    n_corners > 16) then
00325                   locs (3, k) = locs (3, k) + ishft (i-1, -4)
00326                endif
00327             end if
00328          end do ! n
00329       end do ! i
00330 !
00331 #ifdef PRISM_ASSERTION
00332       if (k /= num_missing_points) then
00333          print *, 'k, num_missing_points', k, num_missing_points
00334          call psmile_assert ( __FILE__, __LINE__, &
00335                 'Inconsistent values of k and num_missing_points; must be same value')
00336       endif
00337 #endif
00338 
00339 #ifdef DEBUG_TRACE
00340       if (ictl_req <= n_send) then
00341          ind_loc (:) = 0
00342          n = 0
00343          do j = 1, n_corners
00344 !cdir vector
00345             do i = 1, n_send
00346                if (missing_points (j,i)) then
00347                   n = n + 1
00348                   if (i == ictl_req) ind_loc (j) = n
00349                end if
00350             end do ! i
00351          end do ! j
00352 !
00353          print *, 'locs searched for indices_req', ibuf (4, ictl_req)
00354          do j = 1, n_corners
00355             n = ind_loc (j)
00356             if (n > 0) &
00357             print *, 'ictl_req', ictl_req, ', n ', n, &
00358                            ': locs', locs (1:ndim_3d, n)
00359          end do
00360       endif
00361 #endif
00362 
00363 !
00364 !===> Transform indices from global (virtual) 3d indices
00365 !                       into local  (virtual) 3d indices
00366 !
00367       locs(1,:) = psmile_gauss_3d_to_local_1d (grid_id, locs(:,:), &
00368                                                num_missing_points, outside)
00369       locs(2,:) = 1
00370       !locs(3,:) = locs(3,:)
00371 !
00372 !===> Create compact list of points to be sent and
00373 !     return hash value "hash" (index in fortran order) for each location
00374 !
00375       Allocate (hash (num_missing_points), stat = ierror)
00376       if (ierror /= 0) then
00377          ierrp (1) = num_missing_points
00378 
00379          ierror = PRISM_Error_Alloc
00380 
00381          call psmile_error ( ierror, 'hash', ierrp, 1, &
00382                  __FILE__, __LINE__ )
00383          return
00384       endif
00385 !
00386       call psmile_hash_extra (search, locs, hash, num_missing_points,                &
00387               mask_array, mask_shape, mask_available, grid_valid_shape, &
00388               ierror)
00389       if (ierror > 0) return
00390 !
00391 #ifdef DEBUGX
00392       print *, 'hash values and locs ', grid_valid_shape
00393       n = 0
00394       do j = 1, n_corners
00395 !cdir vector
00396          do i = 1, n_send
00397             if (missing_points (j,i)) then
00398                n = n + 1
00399                print *, 'i, j, n, hash(n), locs(:,n) ', &
00400                          i, j, n, hash(n), locs(:,n)
00401             end if
00402          end do ! i
00403       end do ! j
00404 #endif
00405 !
00406 !===> Save coded mask of points found in "ibuf"
00407 !     ??? Ob das so clever ist ?
00408 !
00409       if (search%n_liste > 0) then
00410          ibuf (5, 1:n_send) = 0
00411 !
00412          n = 0
00413          code = 1
00414          do j = 1, n_corners
00415 !cdir vector
00416             do i = 1, n_send
00417                if (missing_points (j,i)) then
00418 
00419                   n = n + 1
00420 !
00421                   if (hash (n) >= 0) then
00422 !
00423 !===> ...... Required "j-th" interpolation base was found
00424 !            (may be masked out (hash(n) == masked_out).
00425 !            Corresponding value is stored in position "index_found(n)".
00426 !
00427                      ibuf (5, i) = ibuf (5, i) + code
00428                   endif
00429 !
00430                endif
00431             end do ! i
00432 
00433             code = code * 2
00434          end do ! j
00435 
00436 #ifdef PRISM_ASSERTION
00437          if (n /= num_missing_points) then
00438             print *, 'num_missing_points, n', num_missing_points, n
00439             call psmile_assert ( __FILE__, __LINE__, &
00440                                 'n /= num_missing_points')
00441          endif
00442 #endif
00443 !
00444 #ifdef DEBUGX
00445          print *, 'code for locations found', n_send
00446          do i = 1, n_send
00447             print *, 'code', i, ibuf (5, i), missing_points(:, i)
00448          end do
00449 #endif
00450 !
00451 #ifdef DEBUG_TRACE
00452          if (ictl_req <= n_send) then
00453             print *, 'code for locations found for indices_req', ibuf (4, ictl_req)
00454             print *, 'ictl_req', ictl_req, ': code', ibuf (5, ictl_req), missing_points(:, ictl_req)
00455          endif
00456 #endif
00457 
00458       endif
00459 !
00460 !===> Deallocate memory allocated
00461 !
00462       Deallocate (locs, hash, neighbours_3d_extra)
00463 !
00464 !===> All done
00465 !
00466 #ifdef VERBOSE
00467       print 9980, trim(ch_id), ierror, search%n_found, n_send
00468 
00469       call psmile_flushstd
00470 #endif /* VERBOSE */
00471 !
00472       return
00473 !
00474 !  Formats:
00475 !
00476 #ifdef VERBOSE
00477 9990 format (1x, a, ': psmile_tricu_gauss2_extra: comp_id =', i3)
00478 9980 format (1x, a, ': psmile_tricu_gauss2_extra: eof', &
00479                     ', ierror =', i4, ', n_found =', i8, i8)
00480 #endif /* VERBOSE */
00481 
00482       end subroutine psmile_tricu_gauss2_extra

Generated on 1 Dec 2011 for Oasis4 by  doxygen 1.6.1