subroutine cartint use define implicit none ! Bi-linear interpolation of cylindrical grid to cartesian grid do j=1,gps do i=1,gps ifound = 0 reta = 2.*pi + atan2(yy(j),xx(i)) !radians if (reta .gt. 2*pi) then reta = reta - 2*pi endif radius = (xx(i)**2 + yy(j)**2)**0.5 !km ! Searching cylindrical grid for first cartesian point do ia=1,nl do ir=1,np rds1 = ir*res !km rds2 = (ir+1)*res !km ! Coordinate system defined so 0/360 is to the right...180---x---0 if (ia .lt. nl) then raz1 = ia*da*pi/180. !radians raz2 = (ia+1)*da*pi/180. !radians else if (ia .eq. nl) then raz1 = 0. !radians raz2 = da*pi/180. !radians endif ! Bracket point in x and y then do weighted bi-linear interpolation if (ia .eq. nl) then iaz = 1 else iaz = ia+1 endif if (rds1 .le. radius .and. rds2 .ge. radius .and. raz1 .le. reta .and. raz2 .ge. reta) then ! print*,rds1,radius,rds2 ! print*,raz1,reta,raz2 ! radial weights wght_lft = 1 - (abs(radius - rds1)/res) wght_rgt = 1 - (abs(radius - rds2)/res) bot(:) = wght_lft*field_polar(ir,ia,:) + wght_rgt*field_polar(ir+1,ia,:) top(:) = wght_lft*field_polar(ir,iaz,:) + wght_rgt*field_polar(ir+1,iaz,:) ! azimuthal weights wght_bot = 1 - (abs(raz1 - reta)/(da*pi/180.)) wght_top = 1 - (abs(raz2 - reta)/(da*pi/180.)) cart(i,j,:) = wght_bot*bot(:) + wght_top*top(:) ! print*,'wind' ! print*,wc(ir,ia,k),wc(ir+1,ia,k),wc(ir,iaz,k),wc(ir+1,iaz,k) ! print*,ci,cj,cart(ci,cj,k) ifound = 1 endif if (ifound .eq. 1) then goto 100 endif enddo enddo if (ifound .eq. 0) then cart(i,j,:) = 0. endif 100 continue enddo enddo return end