Changes between Version 3 and Version 4 of CameraObjects


Ignore:
Timestamp:
04/24/12 12:32:34 (13 years ago)
Author:
Jonathan
Comment:

Legend:

Unmodified
Added
Removed
Modified
  • CameraObjects

    v3 v4  
    4848
    4949[[Image(rotating.gif, width=500)]]
     50
     51
     52Clearly there are still some aliasing effects.  The routine that bins a cell into an image pixel is given below:
     53{{{
     54
     55   SUBROUTINE BinCell(Camera, pos, dx, data, rho)
     56      TYPE(CameraDef), POINTER :: Camera
     57      REAL(KIND=qPREC) :: pos(3),xpos(3)
     58      REAL(KIND=qPREC) :: dx, ddx, xlower(3)
     59      REAL(KIND=qPREC), DIMENSION(:,:) :: data
     60      REAL(KIND=qPREC) :: rho
     61      INTEGER :: ipos(2), sample_res, i, j, k
     62      xlower=pos-half*dx
     63      sample_res=2d0*ceiling(camera%FOV(1)/camera%res / (dx/sqrt(sum(pos-Camera%pos)**2)))
     64      ddx=dx/REAL(sample_res)
     65      xlower=xlower-half*ddx
     66      DO i=1,sample_res
     67         xpos(1)=xlower(1)+ddx*i
     68         DO j=1,sample_res
     69            xpos(2)=xlower(2)+ddx*j
     70            DO k=1,sample_res
     71               xpos(3)=xlower(3)+ddx*k
     72               ipos(1:2)=nint(GetPos(Camera, xpos)*shape(data))
     73               IF (ALL(ipos(1:2) >= 1) .AND. ALL(ipos(1:2) <= shape(data))) THEN
     74                  data(ipos(1),ipos(2))=data(ipos(1),ipos(2))+ rho*ddx**3
     75               END IF
     76            END DO
     77         END DO
     78      END DO
     79   END SUBROUTINE BinCell
     80}}}
     81 We could in principal continue to raise the sample_res but it gets computationally expensive... A better approach would be to sample along each ray at some interval...  Then the sampling is pixel based instead of volume based - and should reduce the aliasing...