prismtrs_remap_conserv.F90

Go to the documentation of this file.
00001 !------------------------------------------------------------------------
00002 ! Copyright 2006-2010, CERFACS, Toulouse, France.
00003 ! All rights reserved. Use is subject to OASIS4 license terms.
00004 !-----------------------------------------------------------------------
00005 !BOP
00006 !
00007 ! !ROUTINE: PRISMTrs_remap_conserv
00008 !
00009 ! !INTERFACE
00010 subroutine prismtrs_remap_conserv (     &
00011    grid1_size, grid2_size,              &
00012    grid1_corners, grid2_corners,        &
00013    id_src_lonlatz_size,                 &
00014    id_index_size1,                      &
00015    grid1_corner_lat, grid1_corner_lon,  &
00016    grid2_corner_lat, grid2_corner_lon,  &
00017    ida_nbsrccells_pertgtpt,             &
00018    ida_index_array,                     &
00019    ida_srcepio_add,                     &
00020    id_epio_id,                          &
00021    id_interp_id,                        &
00022    id_idim,                             &
00023    num_wts,                             &
00024    id_err)
00025 
00026 !
00027 ! !USES:
00028   USE PRISMDrv, dummy_INTERFACE => PRISMTrs_remap_conserv
00029   IMPLICIT NONE
00030 !
00031 ! !PARAMETERS:
00032 !
00033   INTEGER :: grid1_size, grid2_size ! Source and target epio size
00034   !
00035   INTEGER :: grid1_corners, grid2_corners
00036   INTEGER :: id_src_lonlatz_size ! Size of array containing source corner info
00037   INTEGER :: id_index_size1 ! Size of array containing info of all source cells
00038   ! contributing to all epio target cells (sum of ida_nbsrccells_pertgtpt(:))
00039   DOUBLE PRECISION, DIMENSION (id_src_lonlatz_size)       :: grid1_corner_lat
00040   DOUBLE PRECISION, DIMENSION (id_src_lonlatz_size)       :: grid1_corner_lon
00041   DOUBLE PRECISION, DIMENSION (grid2_size, grid2_corners) :: grid2_corner_lat
00042   DOUBLE PRECISION, DIMENSION (grid2_size, grid2_corners) :: grid2_corner_lon
00043   ! Number of source cells contributing to the rremapping of each target cell
00044   INTEGER, DIMENSION(grid2_size)                          :: ida_nbsrccells_pertgtpt
00045   ! Index in id_src_lonlatz_size of each contributing source cell corner
00046   INTEGER, DIMENSION(id_index_size1,grid1_corners)        :: ida_index_array
00047   ! Index in grid1_size of each contributing source cell
00048   INTEGER, DIMENSION(id_index_size1)                      :: ida_srcepio_add
00049   INTEGER :: id_epio_id   ! EPIO Id
00050   INTEGER :: id_interp_id ! Interpolation Id
00051   INTEGER :: id_idim      ! Dimension concerned with the current interpolation
00052   INTEGER :: num_wts      ! Number of weights for 2D conservative remapping
00053   INTEGER :: id_err, il_add
00054 !
00055 ! !RETURN VALUE
00056 !
00057 ! !DESCRIPTION
00058 !
00059 ! SUBROUTINE "PRISMTrs_remap_conserv" computes for weights with a
00060 ! 2d conservative remapping method, derived from the SCRIP 1.4
00061 ! library available from Los Alamos National Laboratory.
00062 !
00063 ! !REVISED HISTORY
00064 !   Date      Programmer   Description
00065 ! ----------  ----------   -----------
00066 ! 14/12/2006  S. Valcke    Created (based on SCRIP library)
00067 !
00068 ! EOP
00069 !----------------------------------------------------------------------
00070 ! $Id: prismtrs_remap_conserv.F90 2082 2009-10-21 13:31:19Z hanke $
00071 ! $Author: hanke $
00072 !----------------------------------------------------------------------
00073 !
00074 ! Local declarations
00075 ! 
00076   CHARACTER(LEN=len_cvs_string), SAVE  :: mycvs = 
00077      '$Id: prismtrs_remap_conserv.F90 2082 2009-10-21 13:31:19Z hanke $'
00078 ! ---------------------------------------------------------------------
00079 !
00080 ! max number of subsegments per segment to prevent infinite loop
00081   INTEGER, PARAMETER ::  max_subseg = 10000
00082 !
00083   INTEGER  ::   
00084      grid2_add,  ! current linear address for grid2 cell in tgt epio
00085      grid1_add,  ! current linear address for grid1 cell in src epio
00086      n, nwgt,    ! generic counters
00087      npart,      ! generic counters
00088      corner,     ! corner of cell that segment starts from
00089      next_corn,  ! corner of cell that segment ends on
00090      num_subseg, ! number of subsegments
00091      il_loop, il_count, il_bou, i, il_grid1,  ! loop counter
00092      num_srch_cells,  ! Number of search cell for each source and target cell
00093      il_nbrsrc_cells, ! Number of source cells treated in grid1 sweep
00094      il_cumul,   ! index in ida_index_array 
00095      il_action,  ! defines action in prismtrs_store_link_cnsrv: 
00096                   ! 0 if first call, 2 if last call, 1 otherwise
00097      il_stride, & ! stride in lat/lon corner array for Gaussian Red src grid
00098      nb_corner_grid1cell  ! real number of corners for source grid 
00099 
00100 #ifdef DEBUGX
00101   INTEGER, PARAMETER :: nbr_src_cells = 4
00102   INTEGER, DIMENSION(nbr_src_cells) :: grid_src ! number of source cells linked to grid_tgt
00103   INTEGER  :: grid_tgt  ! EPIO target number of the target cell under investigation
00104   INTEGER :: ii
00105   DOUBLE PRECISION, PARAMETER :: dbl_rad2deg = 360.0/6.2831853
00106 #endif
00107 
00108   LOGICAL  :: 
00109      lcoinc,     ! flag for coincident segments
00110      lrevers,    ! flag for reversing direction of segment
00111      lbegin       ! flag for first integration of a segment
00112 
00113   LOGICAL ::  ll_gaussred ! flag true if source grid is Gaussian Reduced
00114   LOGICAL ::  ll_debug    ! for debug outputs
00115 
00116   LOGICAL, DIMENSION(:), ALLOCATABLE :: 
00117      srch_mask   ! mask for restricting searches
00118 
00119   DOUBLE PRECISION ::                     
00120      intrsct_lat, intrsct_lon,        ! lat/lon of next intersect
00121      beglat, endlat, beglon, endlon,  ! endpoints of current seg.
00122      norm_factor                       ! factor for normalizing wts
00123 
00124   DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE :: 
00125      grid1cell_corner_lat, grid1cell_corner_lon ! corner of a given source cell
00126  
00127   DOUBLE PRECISION, DIMENSION(:), ALLOCATABLE ::    
00128      grid2_centroid_lat, grid2_centroid_lon ,      ! centroid coords on each grid
00129      grid1_centroid_lat, grid1_centroid_lon
00130 
00131   DOUBLE PRECISION, DIMENSION(grid1_size) ::   
00132      grid1_center_lat, grid1_center_lon,       ! center coords on each grid
00133      grid1_frac,                               ! intersected part of the cell
00134      grid1_larea                                ! cell area as estimated here
00135 
00136   DOUBLE PRECISION, DIMENSION(grid2_size) ::   
00137      grid2_center_lat, grid2_center_lon,       ! center coords on each grid
00138      grid2_frac,                               ! intersected part of the cell
00139      grid2_larea                                ! cell area as estimated here
00140 
00141   DOUBLE PRECISION, DIMENSION(:,:), ALLOCATABLE ::    
00142      srch_corner_lat,   ! lat of each corner of srch cells
00143      srch_corner_lon     ! lon of each corner of srch cells
00144 
00145   DOUBLE PRECISION, DIMENSION(2) :: begseg ! begin lat/lon for full segment
00146 
00147   DOUBLE PRECISION, DIMENSION(6) :: lcl_weights ! local wgt array
00148 
00149   INTEGER, DIMENSION(id_index_size1) :: ila_grid2_assoc
00150   LOGICAL, DIMENSION(grid1_size)     :: ll_grid1done ! .true. if associated source grid has been treated
00151   INTEGER, DIMENSION(:), allocatable :: srch_add
00152 
00153   !
00154   ! ---------------------------------------------------------------------
00155   !
00156 #ifdef VERBOSE
00157   PRINT *, '| | | | | | | Enter PRISMTrs_remap_conserv'
00158   call psmile_flushstd
00159 #endif
00160   !
00161   nb_corner_grid1cell = grid1_corners
00162   !
00163 #ifdef DEBUGX
00164 !  grid_tgt = 7282
00165   grid_tgt = 7290
00166   grid_src(1) = 2202
00167   grid_src(2) = 2195
00168   grid_src(3) = 2200
00169   grid_src(4) = 2201
00170 #endif
00171   !
00172   ! Check if the source grid is Gaussian Reduced
00173   !
00174   ll_gaussred = .false.
00175   il_stride = 0
00176 
00177   IF (Drv_Epios(id_epio_id)%src_grid_type == PRISM_Gaussreduced_regvrt .OR. &
00178      Drv_Epios(id_epio_id)%src_grid_type == PRISM_Gaussreduced_sigmavrt) THEN
00179       ll_gaussred = .TRUE.
00180       il_stride = Drv_Epios(id_epio_id)%gaussred_stride
00181       nb_corner_grid1cell = 4
00182 
00183 #ifdef DEBUG
00184       IF (il_stride == 0) THEN
00185           PRINT *, '| | | | | | Pb in prismtrs_remap_conserv: Stride in '
00186           PRINT *, '| | | | | | lat/lon corner array for Gaussian Red = 0'
00187           call psmile_abort
00188       ENDIF
00189 #endif
00190   ENDIF
00191   !
00192   ! Allocate array that will contain the corner of a given source cell
00193   !
00194   ALLOCATE (grid1cell_corner_lat(nb_corner_grid1cell))
00195   ALLOCATE (grid1cell_corner_lon(nb_corner_grid1cell))
00196   !
00197   !  initialize centroid arrays
00198   !
00199       allocate( grid1_centroid_lat(grid1_size), &
00200                 grid1_centroid_lon(grid1_size), &
00201                 grid2_centroid_lat(grid2_size), &
00202                 grid2_centroid_lon(grid2_size))
00203 
00204       grid1_centroid_lat = zero
00205       grid1_centroid_lon = zero
00206       grid2_centroid_lat = zero
00207       grid2_centroid_lon = zero
00208   !
00209       ! Initialize cell areas and fraction for local calculation
00210       grid1_larea = zero
00211       grid2_larea = zero
00212       grid1_frac  = zero
00213       grid2_frac  = zero
00214       !
00215       ! For now the center of the grid cells will be calculated
00216       grid1_center_lat = zero
00217       grid1_center_lon = zero
00218       grid2_center_lat = zero
00219       grid2_center_lon = zero
00220       !
00221       lcl_weights = zero
00222   ! integrate around each cell on grid1
00223   !
00224 #ifdef VERBOSE
00225   PRINT *,'grid1 sweep '
00226   call psmile_flushstd
00227 #endif
00228 
00229 !  DO grid1_add = 1,grid1_size
00230         !***
00231         !*** create search arrays for each source mesh
00232         !***
00233 !
00234       allocate(srch_mask(grid2_size))
00235 !
00236   srch_mask (:) = .FALSE.
00237   ila_grid2_assoc(:) = 0
00238   il_count = 1
00239   !
00240   ! Define grid2_add associated to each source cell of ida_index_array
00241   ! and calculate center lat and lon
00242   !
00243   DO grid2_add = 1,grid2_size
00244     ila_grid2_assoc(il_count : il_count+ida_nbsrccells_pertgtpt(grid2_add)-1) = grid2_add
00245     il_count = il_count + ida_nbsrccells_pertgtpt(grid2_add)
00246     grid2_center_lat(grid2_add) = SUM(grid2_corner_lat(grid2_add,:))/grid2_corners
00247     grid2_center_lon(grid2_add) = SUM(grid2_corner_lon(grid2_add,:))/grid2_corners
00248   ENDDO
00249   !
00250   ll_grid1done(:) = .FALSE.
00251   il_nbrsrc_cells = 0
00252   il_action = 0
00253 
00254   PRINT *,'grid1 sweep '
00255 
00256   DO il_loop = 1, id_index_size1
00257     grid1_add = ida_srcepio_add(il_loop)
00258     !
00259     ! Define all target cells associated to each source cell of ida_index_array
00260     ! Each source cell may appear more than once in ida_index_array
00261     ! ll_grid1done indicates if this source cell was already treated or not
00262     !
00263     IF (.NOT. ll_grid1done(grid1_add)) THEN
00264         ll_grid1done(grid1_add) = .TRUE.
00265         ! Number of source cells treated
00266         il_nbrsrc_cells = il_nbrsrc_cells + 1
00267         !
00268 #ifdef DEBUGX
00269         DO ii=1,nbr_src_cells
00270           IF (grid1_add == grid_src(ii)) THEN
00271               WRITE(88,*) 'grid1_add=', grid1_add
00272           ENDIF
00273         ENDDO
00274 #endif
00275 
00276         ! Define the corners of the source cell
00277         !
00278         IF (ll_gaussred) THEN 
00279             grid1cell_corner_lon(1) = &
00280                grid1_corner_lon(ida_index_array(il_loop,1))
00281             grid1cell_corner_lon(2) = &
00282                grid1_corner_lon(ida_index_array(il_loop,1)+il_stride)
00283             grid1cell_corner_lon(3) = &
00284                grid1_corner_lon(ida_index_array(il_loop,1)+il_stride)
00285             grid1cell_corner_lon(4) = &
00286                grid1_corner_lon(ida_index_array(il_loop,1))
00287             grid1cell_corner_lat(1) = &
00288                grid1_corner_lat(ida_index_array(il_loop,1))
00289             grid1cell_corner_lat(2) = &
00290                grid1_corner_lat(ida_index_array(il_loop,1))
00291             grid1cell_corner_lat(3) = &
00292                grid1_corner_lat(ida_index_array(il_loop,1)+il_stride)
00293             grid1cell_corner_lat(4) = &
00294                grid1_corner_lat(ida_index_array(il_loop,1)+il_stride)
00295         ELSE
00296             grid1cell_corner_lat(:) = grid1_corner_lat(ida_index_array(il_loop,:))
00297             grid1cell_corner_lon(:) = grid1_corner_lon(ida_index_array(il_loop,:))
00298         ENDIF
00299         !
00300         ! Calculate lat and lon for centers of source grid cells 
00301         ! Hypothesis: it is an average of the corner lats and lons
00302         !
00303         DO il_bou = 1, nb_corner_grid1cell
00304           grid1_center_lat(grid1_add) = grid1_center_lat(grid1_add) + &
00305              grid1cell_corner_lat(il_bou)
00306           grid1_center_lon(grid1_add) = grid1_center_lon(grid1_add) + &
00307              grid1cell_corner_lon(il_bou)
00308         ENDDO
00309         grid1_center_lat(grid1_add) = grid1_center_lat(grid1_add)/nb_corner_grid1cell
00310         grid1_center_lon(grid1_add) = grid1_center_lon(grid1_add)/nb_corner_grid1cell
00311         !
00312         num_srch_cells = 0
00313         srch_mask(:) = .FALSE.
00314         DO il_bou = 1, id_index_size1
00315           !
00316           ! Identify all target cells for grid1_add source cell 
00317           IF (ida_srcepio_add(il_bou) == grid1_add) THEN
00318               num_srch_cells = num_srch_cells + 1
00319               srch_mask(ila_grid2_assoc(il_bou)) = .TRUE.
00320           ENDIF
00321         ENDDO
00322         !
00323         IF (num_srch_cells .GT. grid2_size) THEN
00324             PRINT *, '| | | | | | Number of search cell on target grid'
00325             PRINT *, '| | | | | | greater than epio target size ' 
00326             PRINT *, '| | | | | | Calling psmile_abort in prismtrs_remap_conserv'
00327             call psmile_abort 
00328         ENDIF
00329         !
00330         ALLOCATE(srch_add(num_srch_cells), &
00331            srch_corner_lat(grid2_corners,num_srch_cells), &
00332            srch_corner_lon(grid2_corners,num_srch_cells))
00333         srch_add(:) = 0
00334         srch_corner_lat(:,:) = zero
00335         srch_corner_lon(:,:) = zero
00336         !
00337         n = 0
00338         !
00339         ! Store lon and lat of target cells associated to grid1_add source cell
00340         !
00341         gather1: DO grid2_add = 1, grid2_size 
00342           if (srch_mask(grid2_add)) then
00343             n = n+1
00344             srch_add(n) = grid2_add
00345             srch_corner_lat(:,n) = grid2_corner_lat(grid2_add,:)
00346             srch_corner_lon(:,n) = grid2_corner_lon(grid2_add,:)
00347           endif
00348         end do gather1
00349         !
00350 #ifdef DEBUGX
00351         DO ii=1,nbr_src_cells
00352           IF (grid1_add == grid_src(ii)) THEN
00353               WRITE(88,*)'    '
00354               WRITE(88,*)'  ** Grid1 cell and associated search cells **'
00355               WRITE(88,*) 'grid1_add=', grid1_add
00356               DO corner = 1, nb_corner_grid1cell
00357                 WRITE(88,1111) corner, &
00358                    dbl_rad2deg*grid1cell_corner_lon(corner), &
00359                    dbl_rad2deg*grid1cell_corner_lat(corner)
00360               ENDDO
00361               WRITE(88,*) '  num_srch_cells=', num_srch_cells
00362               WRITE(88,*) '    '
00363               IF (num_srch_cells .NE. 0) & 
00364                  WRITE(88,*) '  srch_add(:)=', srch_add(:)
00365               DO n=1, num_srch_cells
00366                 DO corner = 1,grid2_corners
00367                   WRITE(88,1112) n, dbl_rad2deg*srch_corner_lon(corner,n), &
00368                                dbl_rad2deg*srch_corner_lat(corner,n)
00369                 END DO
00370               END DO
00371               WRITE(88,*)'    ***************************************'
00372               WRITE(88,*)'    '
00373           ENDIF
00374         ENDDO
00375 
00376  1111 format ('   grid1 corner, lon, lat = ', I2, 2X, F12.4, 2X, F12.4)
00377  1112 format ('     srch cell, lon, lat = ', I2, 2X, F12.4, 2X, F12.4) 
00378 #endif
00379         !
00380         DO corner = 1,nb_corner_grid1cell
00381           next_corn = mod(corner,nb_corner_grid1cell) + 1
00382 
00383           !***
00384           !*** define endpoints of the current segment
00385           !***
00386           beglat = grid1cell_corner_lat(corner)
00387           beglon = grid1cell_corner_lon(corner)
00388           endlat = grid1cell_corner_lat(next_corn)
00389           endlon = grid1cell_corner_lon(next_corn)
00390 
00391           lrevers = .false.
00392 
00393           !***
00394           !*** to ensure exact path taken during both
00395           !*** sweeps, always integrate segments in the same 
00396           !*** direction (SW to NE).
00397           !***
00398 
00399           if ((endlat < beglat) .or.  &
00400             (endlat == beglat .and. endlon < beglon)) then 
00401               beglat = grid1cell_corner_lat(next_corn)
00402               beglon = grid1cell_corner_lon(next_corn)
00403               endlat = grid1cell_corner_lat(corner)
00404               endlon = grid1cell_corner_lon(corner)
00405               lrevers = .true.
00406 #ifdef DEBUGX
00407         DO ii=1,nbr_src_cells
00408           IF (grid1_add == grid_src(ii)) THEN
00409               WRITE(88, *) ' sweep1 LREVERS TRUE'
00410               WRITE(88,*) 'grid1_add=', grid1_add
00411           ENDIF
00412         ENDDO
00413 #endif
00414           endif
00415           begseg(1) = beglat
00416           begseg(2) = beglon
00417           lbegin = .true.
00418           num_subseg = 0
00419 
00420           !***
00421           !*** if this is a constant-longitude segment, skip the rest 
00422           !*** since the line integral contribution will be zero.
00423           !***
00424 #ifdef DEBUGX
00425         DO ii=1,nbr_src_cells
00426           IF (grid1_add == grid_src(ii)) THEN
00427               IF (endlon .EQ. beglon) THEN
00428                   WRITE(88,1110) grid1_add,corner,next_corn
00429                   WRITE(88,1113) dbl_rad2deg*beglon, dbl_rad2deg*beglat 
00430                   WRITE(88,1114) dbl_rad2deg*endlon, dbl_rad2deg*endlat
00431                   WRITE(88, *)'  sweep1 endlon == beglon; skip segment'
00432                   WRITE(88,*) '             '
00433               ENDIF
00434           ENDIF
00435         ENDDO
00436  1110 FORMAT ('    grid1_add, corners = ', 2X, I6, 2X, I2, 2X, I2)
00437  1113 format ('   endlon == beglon;  beglon, beglat = ', &
00438               2X, F12.4, 2X, F12.4)
00439  1114 format ('   endlon == beglon;  endlon, endlat = ', &
00440               2X, F12.4, 2X, F12.4)
00441 #endif
00442 
00443           if (endlon /= beglon) then
00444           !***
00445           !*** integrate along this segment, detecting intersections 
00446           !*** and computing the line integral for each sub-segment
00447           !***
00448 
00449               DO WHILE (beglat /= endlat .OR. beglon /= endlon)
00450               !***
00451               !*** prevent infinite loops if integration gets stuck
00452               !*** near cell or threshold boundary
00453               !***
00454                 num_subseg = num_subseg + 1
00455                 if (num_subseg > max_subseg) THEN
00456                     print*, 'ERROR=>integration stalled:' 
00457                     print*, 'num_subseg exceeded limit'
00458                     print*, '=>Verify corners in grids.nc, especially'
00459                     print*, 'if calculated by OASIS routine corners'           
00460                     PRINT *, 'integration stalled: num_subseg exceeded limit'
00461                     call psmile_abort
00462                 endif
00463 
00464                 !***
00465                 !*** find next intersection of this segment with a grid
00466                 !*** line on grid 2.
00467                 !***
00468 
00469 !                call timer_start(2)
00470 
00471 #ifdef DEBUGX
00472         DO ii=1,nbr_src_cells
00473           IF (grid1_add == grid_src(ii)) THEN
00474               WRITE(88,1110) grid1_add,corner,next_corn
00475               WRITE(88,*) '             '
00476               WRITE(88,1115) dbl_rad2deg*beglon, dbl_rad2deg*beglat 
00477               WRITE(88,1116) dbl_rad2deg*endlon, dbl_rad2deg*endlat
00478               WRITE(88,*) '             '
00479           ENDIF
00480         ENDDO
00481 
00482  1115 format ('   avant intersection;  beglon, beglat = ', &
00483               2X, F12.4, 2X, F12.4)
00484  1116 format ('   avant intersection;  endlon, endlat = ', &
00485               2X, F12.4, 2X, F12.4)
00486 #endif
00487 
00488                 call prismtrs_intersection(grid2_add,intrsct_lat,intrsct_lon, &
00489                     lcoinc, beglat, beglon, endlat, endlon, begseg, &
00490                     lbegin, lrevers, &
00491                     num_srch_cells, grid2_corners, &
00492                     srch_corner_lat, srch_corner_lon, srch_add)
00493 
00494 #ifdef DEBUGX
00495         DO ii=1,nbr_src_cells
00496 !          IF (grid1_add == grid_src(ii) .AND. grid2_add==grid_tgt) THEN
00497           IF (grid1_add == grid_src(ii) ) THEN
00498               WRITE(88,*) 'grid1_add=', grid1_add
00499               WRITE(88,*) ' After call intersection, grid2_add', &
00500                                 grid2_add
00501               WRITE(88,1117) dbl_rad2deg*beglon, dbl_rad2deg*beglat 
00502               WRITE(88,1118) dbl_rad2deg*endlon, dbl_rad2deg*endlat
00503               WRITE(88,1119) dbl_rad2deg*intrsct_lon, dbl_rad2deg*intrsct_lat
00504               WRITE(88,*) '   '
00505           ENDIF
00506         ENDDO
00507 
00508  1117 format('   après intersection;  beglon, beglat =           ', &
00509               2X, F12.4, 2X, F12.4)
00510  1118 format ('   après intersection;  endlon, endlat =          ', &
00511               2X, F12.4, 2X, F12.4)
00512  1119 format ('   après intersection; intrsct_lon, intrsct_lat = ', &
00513                     2X, F12.4, 2X, F12.4)
00514 #endif
00515 
00516 !                call timer_stop(2)
00517                 lbegin = .false.
00518 
00519                 !***
00520                 !*** compute line integral for this subsegment.
00521                 !***
00522 
00523                 ! call timer_start(3)
00524                 if (grid2_add /= 0) THEN
00525                     !
00526                     call prismtrs_line_integral(lcl_weights, &
00527                                beglon, intrsct_lon, beglat, intrsct_lat, &
00528                                grid1_center_lon(grid1_add), &
00529                                grid2_center_lon(grid2_add), &
00530                                num_wts)
00531 
00532 #ifdef DEBUGX
00533         DO ii=1,nbr_src_cells
00534 !          IF (grid1_add == grid_src(ii) .AND. grid2_add==grid_tgt) THEN
00535           IF (grid1_add == grid_src(ii)) THEN
00536               WRITE(88,*) 'grid1_add=', grid1_add
00537               WRITE(88,*) '  A1) WEIGHTS for this subsegment =', &
00538                                    lcl_weights(1)
00539               WRITE(88,*) '     '
00540           ENDIF
00541         ENDDO
00542 #endif
00543 
00544                 else
00545                     call prismtrs_line_integral(lcl_weights, &
00546                                beglon, intrsct_lon, beglat, intrsct_lat, &
00547                                grid1_center_lon(grid1_add), &
00548                                grid1_center_lon(grid1_add), &
00549                                num_wts)
00550 
00551 #ifdef DEBUGX
00552         DO ii=1,nbr_src_cells
00553           IF (grid1_add == grid_src(ii)) THEN
00554               WRITE(88,*) 'grid1_add=', grid1_add
00555               WRITE(88,*) '  B1) WEIGHTS for this subsegment =', &
00556                                    lcl_weights(1)
00557               WRITE(88,*) '     ' 
00558           ENDIF
00559         ENDDO
00560 #endif
00561 
00562                 endif
00563                 ! call timer_stop(3)
00564                 !***
00565                 !*** if integrating in reverse order, change
00566                 !*** sign of lcl_weights
00567                 !***
00568 
00569                 if (lrevers) then
00570                     lcl_weights = -lcl_weights
00571 #ifdef DEBUGX
00572         DO ii=1,nbr_src_cells
00573 !          IF (grid1_add == grid_src(ii) .AND. grid2_add==grid_tgt) THEN
00574           IF (grid1_add == grid_src(ii)) THEN
00575               WRITE(88,*) 'grid1_add=', grid1_add
00576               WRITE(88,*) '  LREVERS; WEIGHTS for this subsegment =', &
00577                               lcl_weights(1)
00578               WRITE(88,*) '     '
00579           ENDIF
00580         ENDDO
00581 #endif
00582                 endif
00583                 !***
00584                 !*** store the appropriate addresses and lcl_weights. 
00585                 !*** also add contributions to cell areas and centroids.
00586                 !***
00587 
00588 
00589                 if (grid2_add /= 0) then
00590                     if (Drv_Epios(id_epio_id)%src_mask_pointer(grid1_add) == 1) then
00591                         ! call timer_start(4)
00592                         call prismtrs_store_link_cnsrv(grid1_add, grid2_add, & 
00593                             lcl_weights, il_action, id_epio_id, num_wts)
00594 
00595 #ifdef DEBUGX
00596         DO ii=1,nbr_src_cells
00597 !          IF (grid1_add == grid_src(ii) .AND. grid2_add==grid_tgt) THEN
00598           IF (grid1_add == grid_src(ii)) THEN
00599               WRITE(88,*) '      after store_link_cnsrv'
00600               WRITE(88,1120) grid1_add, grid2_add,dbl_rad2deg*beglon, dbl_rad2deg*beglat, &
00601                              dbl_rad2deg*intrsct_lon,dbl_rad2deg*intrsct_lat,lcl_weights(1)
00602           ENDIF
00603         ENDDO
00604 
00605  1120 format ('      STORE add1,add2,blon,blat,ilon,ilat,WEIGHTS=', &
00606                1X,I6,1X,I6,1X,F12.8,1X,F12.8,1X,F12.8,1X,F12.8,1X,E15.8)
00607 #endif
00608 
00609                         il_action = 1
00610                         ! call timer_stop(4)
00611                         grid1_frac(grid1_add) = &
00612                            grid1_frac(grid1_add)+lcl_weights(1)
00613                         grid2_frac(grid2_add) = &
00614                            grid2_frac(grid2_add)+lcl_weights(num_wts+1)
00615                     endif
00616                 endif
00617 
00618                 grid1_larea(grid1_add) = &
00619                    grid1_larea(grid1_add) + lcl_weights(1)
00620                  
00621                 grid1_centroid_lat(grid1_add) = &
00622                    grid1_centroid_lat(grid1_add) + lcl_weights(2)
00623                 grid1_centroid_lon(grid1_add) = &
00624                    grid1_centroid_lon(grid1_add) + lcl_weights(3)
00625 
00626                 !***
00627                 !*** reset beglat and beglon for next subsegment.
00628                 !***
00629 
00630                 beglat = intrsct_lat
00631                 beglon = intrsct_lon
00632 
00633               END DO
00634 
00635           endif
00636 
00637           !***
00638           !*** end of segment
00639           !***
00640 
00641         END DO
00642 
00643         !***
00644         !*** finished with this cell: deallocate search array and
00645         !*** start on next cell
00646         deallocate(srch_add, srch_corner_lat, srch_corner_lon)
00647     ENDIF                        
00648   END DO
00649 #ifdef VERBOSE
00650   PRINT *, 'Number of source cells in epio = ', grid1_size
00651   PRINT *, 'Number of source cells in grid1 sweep = ', il_nbrsrc_cells
00652 #endif
00653   IF (il_nbrsrc_cells /= grid1_size) THEN 
00654       PRINT *, '| | |WARNING: Number of source cells in grid1 sweep '
00655       PRINT *, '| | |not equal to number of source cells in epio '
00656   ENDIF
00657 
00658       deallocate(srch_mask)
00659  
00660       print *,'grid1 end sweep '
00661 !-----------------------------------------------------------------------
00662 !
00663 !     integrate around each cell on grid2
00664 !
00665 !-----------------------------------------------------------------------
00666 
00667       print *,'grid2 sweep '
00668       il_cumul = 0
00669       do grid2_add = 1,grid2_size
00670 
00671 #ifdef DEBUGX
00672         IF (grid2_add == grid_tgt) THEN 
00673             WRITE(88,*) 'grid2_add=', grid2_add
00674         ENDIF
00675 #endif
00676 
00677         num_srch_cells = ida_nbsrccells_pertgtpt (grid2_add)
00678 
00679         allocate(srch_add(num_srch_cells), &
00680                  srch_corner_lat(nb_corner_grid1cell,num_srch_cells), &
00681                  srch_corner_lon(nb_corner_grid1cell,num_srch_cells))
00682 
00683         gather2: DO il_grid1 = 1, num_srch_cells
00684             il_cumul = il_cumul + 1
00685             srch_add(il_grid1) = ida_srcepio_add (il_cumul)
00686             IF (ll_gaussred) THEN
00687                 srch_corner_lon(1,il_grid1) = &
00688                    grid1_corner_lon(ida_index_array(il_cumul,1))
00689                 srch_corner_lon(2,il_grid1) = &
00690                    grid1_corner_lon(ida_index_array(il_cumul,1)+il_stride)
00691                 srch_corner_lon(3,il_grid1) = &
00692                    grid1_corner_lon(ida_index_array(il_cumul,1)+il_stride)
00693                 srch_corner_lon(4,il_grid1) = &
00694                    grid1_corner_lon(ida_index_array(il_cumul,1))
00695                 srch_corner_lat(1,il_grid1) = &
00696                    grid1_corner_lat(ida_index_array(il_cumul,1))
00697                 srch_corner_lat(2,il_grid1) = &
00698                    grid1_corner_lat(ida_index_array(il_cumul,1))
00699                 srch_corner_lat(3,il_grid1) = &
00700                    grid1_corner_lat(ida_index_array(il_cumul,1)+il_stride)
00701                 srch_corner_lat(4,il_grid1) = &
00702                    grid1_corner_lat(ida_index_array(il_cumul,1)+il_stride)  
00703             ELSE
00704                 srch_corner_lat(:,il_grid1) = grid1_corner_lat(ida_index_array(il_cumul,:))
00705                 srch_corner_lon(:,il_grid1) = grid1_corner_lon(ida_index_array(il_cumul,:))
00706             ENDIF
00707         end do gather2
00708 
00709 #ifdef DEBUGX
00710         IF (grid2_add == grid_tgt) THEN 
00711             WRITE(88,*)'    '
00712             WRITE(88,*)'  ** Grid2 cell and associated search cells **'
00713             DO corner = 1,grid2_corners 
00714               WRITE(88,1131) corner, &
00715                  dbl_rad2deg*grid2_corner_lon(grid2_add,corner), &
00716                  dbl_rad2deg*grid2_corner_lat(grid2_add,corner)
00717             ENDDO
00718             WRITE(88,*) '  num_srch_cells=', num_srch_cells
00719             WRITE(88,*) '    '
00720             WRITE(88,*) '  srch_add(:)=', srch_add(:)
00721             DO n=1, num_srch_cells
00722               DO corner = 1,nb_corner_grid1cell
00723                 WRITE(88,1132) n, dbl_rad2deg*srch_corner_lon(corner,n), &
00724                               dbl_rad2deg*srch_corner_lat(corner,n)
00725               END DO
00726             END DO
00727             WRITE(88,*)'    ***************************************'
00728             WRITE(88,*)'    '
00729         ENDIF
00730  1131 format ('   grid2 corner, lon, lat = ', I2, 2X, F12.4, 2X, F12.4)
00731  1132 format ('     srch cell, lon, lat = ', I2, 2X, F12.4, 2X, F12.4) 
00732 #endif
00733 
00734         do corner = 1,grid2_corners
00735           next_corn = mod(corner,grid2_corners) + 1
00736 
00737           beglat = grid2_corner_lat(grid2_add,corner)
00738           beglon = grid2_corner_lon(grid2_add,corner)
00739           endlat = grid2_corner_lat(grid2_add,next_corn)
00740           endlon = grid2_corner_lon(grid2_add,next_corn)
00741           lrevers = .false.
00742 
00743           !***
00744           !*** to ensure exact path taken during both
00745           !*** sweeps, always integrate in the same direction
00746           !***
00747 
00748           if ((endlat < beglat) .or. &
00749               (endlat == beglat .and. endlon < beglon)) then 
00750             beglat = grid2_corner_lat(grid2_add,next_corn)
00751             beglon = grid2_corner_lon(grid2_add,next_corn)
00752             endlat = grid2_corner_lat(grid2_add,corner)
00753             endlon = grid2_corner_lon(grid2_add,corner)
00754             lrevers = .true.
00755 #ifdef DEBUGX
00756             IF (grid2_add == grid_tgt) WRITE(88, *) ' sweep2 LREVERS TRUE'
00757 #endif
00758           endif
00759           begseg(1) = beglat
00760           begseg(2) = beglon
00761           lbegin = .true.
00762 
00763           !***
00764           !*** if this is a constant-longitude segment, skip the rest 
00765           !*** since the line integral contribution will be zero.
00766           !***
00767 
00768 #ifdef DEBUGX
00769           IF (grid2_add == grid_tgt) THEN
00770               IF (endlon .EQ. beglon) THEN
00771                   WRITE(88,1113) dbl_rad2deg*beglon, dbl_rad2deg*beglat 
00772                   WRITE(88,1114) dbl_rad2deg*endlon, dbl_rad2deg*endlat
00773                   WRITE(88, *)'  sweep2 endlon == beglon; skip segment'
00774                   WRITE(88,*) '             '
00775               ENDIF
00776           ENDIF
00777 #endif
00778 
00779           if (endlon /= beglon) then
00780           num_subseg = 0
00781 
00782           !***
00783           !*** integrate along this segment, detecting intersections 
00784           !*** and computing the line integral for each sub-segment
00785           !***
00786 
00787           do while (beglat /= endlat .or. beglon /= endlon)
00788 
00789             !***
00790             !*** prevent infinite loops if integration gets stuck
00791             !*** near cell or threshold boundary
00792             !***
00793 
00794             num_subseg = num_subseg + 1
00795             if (num_subseg > max_subseg) THEN
00796                 print*, 'ERROR=>integration stalled:' 
00797                 print*, 'num_subseg exceeded limit'
00798                 print*, '=>Verify corners in grids.nc, especially'
00799                 print*, 'if calculated by OASIS routine corners' 
00800                 PRINT *, 'integration stalled: num_subseg exceeded limit'
00801                 call psmile_abort
00802             endif
00803 
00804             !***
00805             !*** find next intersection of this segment with a line 
00806             !*** on grid 2.
00807             !***
00808 
00809             !call timer_start(6)
00810 
00811 #ifdef DEBUGX
00812             IF (grid2_add == grid_tgt) THEN
00813                 WRITE(88,*) '             '
00814                 WRITE(88,1115) dbl_rad2deg*beglon, dbl_rad2deg*beglat 
00815                 WRITE(88,1116) dbl_rad2deg*endlon, dbl_rad2deg*endlat
00816                 WRITE(88,*) '             '
00817             ENDIF
00818 #endif
00819             call prismtrs_intersection(grid1_add,intrsct_lat,intrsct_lon,lcoinc, &
00820                               beglat, beglon, endlat, endlon, begseg, &
00821                               lbegin, lrevers, &
00822                               num_srch_cells, nb_corner_grid1cell, &
00823                               srch_corner_lat, srch_corner_lon, srch_add)
00824 
00825 #ifdef DEBUGX
00826             IF (grid2_add == grid_tgt) THEN
00827                 WRITE(88,*) ' After call intersection, grid1_add', &
00828                    grid1_add
00829                 WRITE(88,1117) dbl_rad2deg*beglon, dbl_rad2deg*beglat 
00830                 WRITE(88,1118) dbl_rad2deg*endlon, dbl_rad2deg*endlat
00831                 WRITE(88,1119) dbl_rad2deg*intrsct_lon, dbl_rad2deg*intrsct_lat
00832                 WRITE(88,*) '   '
00833             ENDIF
00834 #endif
00835 
00836             !call timer_stop(6)
00837             lbegin = .false.
00838 
00839             !***
00840             !*** compute line integral for this subsegment.
00841             !***
00842 
00843             ! call timer_start(7)
00844             if (grid1_add /= 0) then
00845 
00846                 ! Check if grid1 center was calculated 
00847                 IF (.NOT. ll_grid1done(grid1_add)) THEN
00848                     PRINT *, &
00849                        '| | | | Center of grid1 mesh not known - cannot call prismtrs_line_integral'
00850                     call psmile_abort
00851                 ENDIF
00852 
00853               call prismtrs_line_integral(lcl_weights, &
00854                               beglon, intrsct_lon, beglat, intrsct_lat, &
00855                               grid1_center_lon(grid1_add), &
00856                               grid2_center_lon(grid2_add), &
00857                               num_wts)
00858 
00859 #ifdef DEBUGX
00860               IF (grid2_add == grid_tgt) THEN
00861                   WRITE(88,*) '  A2) WEIGHTS for this subsegment =', &
00862                                   lcl_weights(1)
00863                   WRITE(88,*) '     ' 
00864               ENDIF
00865 #endif
00866 
00867             else
00868               call prismtrs_line_integral(lcl_weights, &
00869                              beglon, intrsct_lon, beglat, intrsct_lat, &
00870                              grid2_center_lon(grid2_add), &
00871                              grid2_center_lon(grid2_add), &
00872                              num_wts)
00873 
00874 #ifdef DEBUGX
00875              IF (grid2_add == grid_tgt) THEN
00876                  WRITE(88,*) '  B2) WEIGHTS for this subsegment =', &
00877                      lcl_weights(1)
00878                   WRITE(88,*) '     ' 
00879               ENDIF
00880 #endif
00881 
00882             endif
00883             ! call timer_stop(7)
00884 
00885             if (lrevers) then
00886               lcl_weights = -lcl_weights
00887 #ifdef DEBUGX
00888               IF (grid2_add == grid_tgt) THEN
00889                 WRITE(88,*) '  LREVERS; WEIGHTS for this subsegment =', &
00890                    lcl_weights(1)
00891                 WRITE(88,*) '     '
00892               ENDIF
00893 #endif
00894             endif
00895             !***
00896             !*** store the appropriate addresses and weights. 
00897             !*** also add contributions to cell areas and centroids.
00898             !*** if there is a coincidence, do not store weights
00899             !*** because they have been captured in the previous loop.
00900             !*** the grid1 mask is the master mask
00901             !***
00902 
00903 #ifdef DEBUGX
00904             IF (lcoinc .AND. grid2_add == grid_tgt) &
00905                WRITE(88,*) '  LCOINC is TRUE; weight not stored'
00906 #endif
00907 
00908             if (.not. lcoinc .and. grid1_add /= 0) then
00909               if (Drv_Epios(id_epio_id)%src_mask_pointer(grid1_add) == 1) then
00910                   ! call timer_start(8)
00911                   call prismtrs_store_link_cnsrv(grid1_add, grid2_add, & 
00912                      lcl_weights, il_action, id_epio_id, num_wts)
00913 
00914 #ifdef DEBUGX
00915                   IF (grid2_add == grid_tgt) THEN
00916                       WRITE(88,*) '      after store_link_cnsrv'
00917                       WRITE(88,1120) grid1_add, grid2_add,dbl_rad2deg*beglon, dbl_rad2deg*beglat, &
00918                                      dbl_rad2deg*intrsct_lon,dbl_rad2deg*intrsct_lat,lcl_weights(1)
00919                   ENDIF
00920 #endif
00921 
00922                   il_action = 1
00923                   ! call timer_stop(8)
00924                   grid1_frac(grid1_add) = &
00925                      grid1_frac(grid1_add) + lcl_weights(1)
00926                   grid2_frac(grid2_add) = &
00927                      grid2_frac(grid2_add) + lcl_weights(num_wts+1)
00928               endif
00929 
00930             endif
00931 
00932             grid2_larea(grid2_add) = &
00933                grid2_larea(grid2_add) + lcl_weights(num_wts+1)
00934             grid2_centroid_lat(grid2_add) = &
00935                grid2_centroid_lat(grid2_add) + lcl_weights(num_wts+2)
00936             grid2_centroid_lon(grid2_add) = &
00937                grid2_centroid_lon(grid2_add) + lcl_weights(num_wts+3)
00938 
00939             !***
00940             !*** reset beglat and beglon for next subsegment.
00941             !***
00942 
00943             beglat = intrsct_lat
00944             beglon = intrsct_lon
00945 
00946           end DO
00947 
00948           END if
00949 
00950           !***
00951           !*** end of segment
00952           !***
00953 
00954         end do
00955 
00956         !***
00957         !*** finished with this cell: deallocate search array and
00958         !*** start on next cell
00959 
00960         deallocate(srch_add, srch_corner_lat, srch_corner_lon)
00961 
00962       end do
00963 
00964       print *,'grid2 end sweep '
00965 
00966 #ifdef DEBUGX
00967       IF (grid2_add == grid_tgt) THEN
00968           do n=1,Drv_Epios(id_epio_id)%num_links_map1
00969             WRITE(88,*) 'grid1, grid2, weight= ', &
00970            Drv_Epios(id_epio_id)%grid1_add_map1(n), Drv_Epios(id_epio_id)%grid2_add_map1(n), &
00971            Drv_Epios(id_epio_id)%wts_map1(1,n)
00972           END DO
00973       ENDIF
00974 #endif
00975 !-----------------------------------------------------------------------
00976 !
00977 !     correct for situations where N/S pole not explicitly included in
00978 !     grid (i.e. as a grid corner point). if pole is missing from only
00979 !     one grid, need to correct only the area and centroid of that 
00980 !     grid.  if missing from both, do complete weight calculation.
00981 !
00982 !-----------------------------------------------------------------------
00983       !*** North Pole
00984       lcl_weights(1) =  dble_pi2
00985       lcl_weights(2) =  dble_pi*dble_pi
00986       lcl_weights(3) =  zero
00987       lcl_weights(4) =  dble_pi2
00988       lcl_weights(5) =  dble_pi*dble_pi
00989       lcl_weights(6) =  zero
00990 
00991       grid1_add = 0
00992       pole_loop1: do n=1,grid1_size
00993         if (grid1_larea(n) < -three*dble_pih .and. &
00994             grid1_center_lat(n) > zero) then
00995           grid1_add = n
00996           exit pole_loop1
00997         endif
00998       end do pole_loop1
00999 
01000       grid2_add = 0
01001       pole_loop2: do n=1,grid2_size
01002         if (grid2_larea(n) < -three*dble_pih .and. &
01003             grid2_center_lat(n) > zero) then
01004           grid2_add = n
01005           exit pole_loop2
01006         endif
01007       end do pole_loop2
01008 
01009       if (grid1_add /=0) then
01010         grid1_larea(grid1_add) = grid1_larea(grid1_add) + lcl_weights(1)
01011         grid1_centroid_lat(grid1_add) = &
01012         grid1_centroid_lat(grid1_add) + lcl_weights(2)
01013         grid1_centroid_lon(grid1_add) = &
01014         grid1_centroid_lon(grid1_add) + lcl_weights(3)
01015       endif
01016 
01017       if (grid2_add /=0) then
01018         grid2_larea(grid2_add) = grid2_larea(grid2_add) + &
01019                                         lcl_weights(num_wts+1)
01020         grid2_centroid_lat(grid2_add) = &
01021         grid2_centroid_lat(grid2_add) + lcl_weights(num_wts+2)
01022         grid2_centroid_lon(grid2_add) = &
01023         grid2_centroid_lon(grid2_add) + lcl_weights(num_wts+3)
01024       endif
01025 
01026       if (grid1_add /= 0 .and. grid2_add /=0) then
01027           call prismtrs_store_link_cnsrv(grid1_add, grid2_add, & 
01028              lcl_weights, il_action, id_epio_id, num_wts)
01029           il_action = 1
01030         grid1_frac(grid1_add) = &
01031            grid1_frac(grid1_add) + lcl_weights(1)
01032         grid2_frac(grid2_add) = &
01033            grid2_frac(grid2_add) + lcl_weights(num_wts+1)
01034       endif
01035 
01036       !*** South Pole
01037       lcl_weights(1) =  dble_pi2
01038       lcl_weights(2) = -dble_pi*dble_pi
01039       lcl_weights(3) =  zero
01040       lcl_weights(4) =  dble_pi2
01041       lcl_weights(5) = -dble_pi*dble_pi
01042       lcl_weights(6) =  zero
01043 
01044       grid1_add = 0
01045       pole_loop3: do n=1,grid1_size
01046         if (grid1_larea(n) < -three*dble_pih .and. &
01047             grid1_center_lat(n) < zero) then
01048           grid1_add = n
01049           exit pole_loop3
01050         endif
01051       end do pole_loop3
01052 
01053       grid2_add = 0
01054       pole_loop4: do n=1,grid2_size
01055         if (grid2_larea(n) < -three*dble_pih .and. &
01056             grid2_center_lat(n) < zero) then
01057           grid2_add = n
01058           exit pole_loop4
01059         endif
01060       end do pole_loop4
01061 
01062       if (grid1_add /=0) then
01063         grid1_larea(grid1_add) = grid1_larea(grid1_add) + lcl_weights(1)
01064         grid1_centroid_lat(grid1_add) = &
01065         grid1_centroid_lat(grid1_add) + lcl_weights(2)
01066         grid1_centroid_lon(grid1_add) = &
01067         grid1_centroid_lon(grid1_add) + lcl_weights(3)
01068       endif
01069 
01070       if (grid2_add /=0) then
01071         grid2_larea(grid2_add) = grid2_larea(grid2_add) + &
01072                                         lcl_weights(num_wts+1)
01073         grid2_centroid_lat(grid2_add) = &
01074         grid2_centroid_lat(grid2_add) + lcl_weights(num_wts+2)
01075         grid2_centroid_lon(grid2_add) = &
01076         grid2_centroid_lon(grid2_add) + lcl_weights(num_wts+3)
01077       endif
01078 
01079       if (grid1_add /= 0 .and. grid2_add /=0) then
01080         call prismtrs_store_link_cnsrv(grid1_add, grid2_add, lcl_weights, 1, &
01081            id_epio_id, num_wts)
01082         grid1_frac(grid1_add) = grid1_frac(grid1_add) + & 
01083                                 lcl_weights(1)
01084         grid2_frac(grid2_add) = grid2_frac(grid2_add) + &
01085                                 lcl_weights(num_wts+1)
01086       endif
01087 
01088 !-----------------------------------------------------------------------
01089 !
01090 !     finish centroid computation
01091 !
01092 !-----------------------------------------------------------------------
01093 
01094       where (grid1_larea /= zero)
01095         grid1_centroid_lat = grid1_centroid_lat/grid1_larea
01096         grid1_centroid_lon = grid1_centroid_lon/grid1_larea
01097       end where
01098 
01099       where (grid2_larea /= zero)
01100         grid2_centroid_lat = grid2_centroid_lat/grid2_larea
01101         grid2_centroid_lon = grid2_centroid_lon/grid2_larea
01102       end where
01103 !
01104 !-----------------------------------------------------------------------
01105 !
01106 !     include centroids in weights and normalize using destination
01107 !     area if requested
01108 !
01109 !-----------------------------------------------------------------------
01110 
01111       do n=1,Drv_Epios(id_epio_id)%num_links_map1
01112 
01113         grid1_add = Drv_Epios(id_epio_id)%grid1_add_map1(n)
01114         grid2_add = Drv_Epios(id_epio_id)%grid2_add_map1(n)
01115         do nwgt=1,num_wts
01116           lcl_weights(nwgt) = Drv_Epios(id_epio_id)%wts_map1(nwgt,n)
01117         end do
01118 #ifdef DEBUGX
01119         il_add = 7202
01120         IF (grid2_add == il_add) THEN
01121             PRINT *, 'Source and weight before normalisation for target point ', il_add
01122             PRINT *, grid1_add, lcl_weights(1)
01123         ENDIF
01124 #endif
01125 
01126         select case(Drv_Interps(id_interp_id)%arg4(id_idim))
01127         case (PSMILe_destarea)
01128           if (grid2_larea(grid2_add) /= zero) then
01129             !if (luse_grid2_area) then
01130             !  norm_factor = one/grid2_area_in(grid2_add)
01131             !else
01132               norm_factor = one/grid2_larea(grid2_add)
01133             !endif
01134           else
01135             norm_factor = zero
01136           endif
01137         case (PSMILe_fracarea)
01138           if (grid2_frac(grid2_add) /= zero) then
01139             !if (luse_grid2_area) then
01140             !  norm_factor = grid2_larea(grid2_add)/
01141      !&                     (grid2_frac(grid2_add)*
01142      !&                      grid2_larea_in(grid2_add))
01143             !else
01144               norm_factor = one/grid2_frac(grid2_add)
01145             !endif
01146           else
01147             norm_factor = zero
01148           endif
01149         case (PSMILe_none)
01150           norm_factor = one
01151         end select
01152 
01153         Drv_Epios(id_epio_id)%wts_map1(1,n)= lcl_weights(1)*norm_factor
01154         Drv_Epios(id_epio_id)%wts_map1(2,n)=(lcl_weights(2) - lcl_weights(1)* &
01155            grid1_centroid_lat(grid1_add))* norm_factor
01156         Drv_Epios(id_epio_id)%wts_map1(3,n)=(lcl_weights(3) - lcl_weights(1)* &
01157            grid1_centroid_lon(grid1_add))* norm_factor
01158 
01159 #ifdef DEBUGX
01160         il_add = 7202
01161         IF (grid2_add == il_add) THEN
01162             PRINT *, 'Source and weight after normalisation for target point ', il_add
01163             PRINT *, grid1_add, Drv_Epios(id_epio_id)%wts_map1(1,n)
01164         ENDIF
01165 #endif
01166       end do
01167       print *, 'Total number of links = ',Drv_Epios(id_epio_id)%num_links_map1
01168 
01169       where (grid1_larea /= zero) &
01170          grid1_frac = &
01171          grid1_frac/grid1_larea
01172       where (grid2_larea /= zero) &
01173          grid2_frac = &
01174          grid2_frac/grid2_larea
01175 
01176 !
01177 !-----------------------------------------------------------------------
01178 !
01179 !     perform some error checking on final weights
01180 !
01181 !-----------------------------------------------------------------------
01182 
01183       !grid2_centroid_lat = zero
01184       !grid2_centroid_lon = zero
01185 #ifdef DEBUG
01186       do n=1,grid1_size
01187         if (grid1_larea(n) < -.01) then
01188           print *,'Grid 1 area error: n, area, mask =' &
01189                 ,n,grid1_larea(n), &
01190                 Drv_Epios(id_epio_id)%src_mask_pointer(n)
01191         endif
01192         if (grid1_centroid_lat(n) < -dble_pih-.01 .or. &
01193             grid1_centroid_lat(n) >  dble_pih+.01) then
01194             print *,'Grid 1 centroid lat error: n, centroid_lat, mask=' &
01195                 ,n,grid1_centroid_lat(n), &
01196                 Drv_Epios(id_epio_id)%src_mask_pointer(n)
01197         endif
01198         grid1_centroid_lat(n) = zero
01199         grid1_centroid_lon(n) = zero
01200       end do
01201 
01202       do n=1,grid2_size
01203         if (grid2_larea(n) < -.01) then
01204             PRINT *,'Grid 2 area error:  n, area, mask =' &
01205             ,n,grid2_larea(n), &
01206             Drv_Epios(id_epio_id)%tgt_mask_pointer(n)
01207         endif
01208         if (grid2_centroid_lat(n) < -dble_pih-.01 .or. &
01209             grid2_centroid_lat(n) >  dble_pih+.01) then
01210           PRINT *,'Grid 2 centroid lat error: n, centroid_lat, mask =' &
01211                 ,n,grid2_centroid_lat(n), &
01212                 Drv_Epios(id_epio_id)%tgt_mask_pointer(n)
01213         endif
01214         grid2_centroid_lat(n) = zero
01215         grid2_centroid_lon(n) = zero
01216       end do
01217 
01218 ! Rene: print statements prohibit vectorisation, better put this in a VERBOSE statement
01219 !   to spped up producton runs. Stripmining of loop to avoid problems on the SX.
01220 
01221       do npart = 1, Drv_Epios(id_epio_id)%num_links_map1, 5000
01222       do n = npart, min(Drv_Epios(id_epio_id)%num_links_map1,npart+5000-1)
01223 
01224         grid1_add = Drv_Epios(id_epio_id)%grid1_add_map1(n)
01225         grid2_add = Drv_Epios(id_epio_id)%grid2_add_map1(n)
01226         
01227         if (Drv_Epios(id_epio_id)%wts_map1(1,n) < -.01) then
01228           print *,'Map 1 weight < 0 '
01229           PRINT *, &
01230               'grid1_add, grid2_add, wts_map1, grid1_mask, grid2_mask', &
01231               grid1_add, grid2_add, Drv_Epios(id_epio_id)%wts_map1(1,n), & 
01232               Drv_Epios(id_epio_id)%src_mask_pointer(grid1_add), &
01233               Drv_Epios(id_epio_id)%tgt_mask_pointer(grid2_add) 
01234         endif
01235         if (Drv_Interps(id_interp_id)%arg4(id_idim) /= PSMILe_none .and. Drv_Epios(id_epio_id)%wts_map1(1,n) > 1.01) then
01236           print *,'Map 1 weight > 1 '
01237           PRINT *, &
01238               'grid1_add, grid2_add, wts_map1, grid1_mask, grid2_mask', &
01239               grid1_add, grid2_add, Drv_Epios(id_epio_id)%wts_map1(1,n), & 
01240               Drv_Epios(id_epio_id)%src_mask_pointer(grid1_add), &
01241               Drv_Epios(id_epio_id)%tgt_mask_pointer(grid2_add) 
01242         endif
01243         grid2_centroid_lat(grid2_add) = &
01244         grid2_centroid_lat(grid2_add) + Drv_Epios(id_epio_id)%wts_map1(1,n)
01245 
01246       end do
01247       end do
01248 
01249       do n=1,grid2_size
01250         select case(Drv_Interps(id_interp_id)%arg4(id_idim))
01251         case (PSMILe_destarea)
01252           norm_factor = grid2_frac(n)
01253         case (PSMILe_fracarea)
01254           norm_factor = one
01255         case (PSMILe_none)
01256           ! if (luse_grid2_area) then
01257           !  norm_factor = grid2_area_in(grid2_add)
01258           ! else
01259             norm_factor = grid2_larea(n)
01260           ! endif
01261         end select
01262         if (abs(grid2_centroid_lat(n)-norm_factor) > .01) then
01263           print *, &
01264       'Error sum wts map1:grid2_add,grid2_centroid_lat,norm_factor, mask=' &
01265       ,n,grid2_centroid_lat(n), &
01266       norm_factor,Drv_Epios(id_epio_id)%tgt_mask_pointer(n)  
01267         endif
01268       end do
01269 #endif
01270       ! Call prismtrs_store_link_cnsrv juste to deallocate local save arrays
01271       !
01272       il_action = il_action + 1
01273       IF (il_action == 2) THEN
01274           call prismtrs_store_link_cnsrv(grid1_add, grid2_add, lcl_weights, &
01275              il_action, id_epio_id, num_wts)
01276       ENDIF
01277       !
01278 !-----------------------------------------------------------------------
01279 !
01280 !     deallocate allocated arrays
01281 !
01282 !----------------------------------------------------------------------- 
01283 
01284       deallocate (grid1_centroid_lat, grid1_centroid_lon, &
01285                   grid2_centroid_lat, grid2_centroid_lon)
01286       DEALLOCATE (grid1cell_corner_lat, grid1cell_corner_lon)
01287 
01288 !-----------------------------------------------------------------------
01289 !
01290 #ifdef VERBOSE
01291   PRINT *, '| | | | | | | Quit PRISMTrs_remap_conserv'
01292   call psmile_flushstd
01293 #endif
01294 END SUBROUTINE PRISMTrs_remap_conserv
01295 

Generated on 18 Mar 2011 for Oasis4 by  doxygen 1.6.1