For GrADS developers
Ren Diandong
dd_ren at ROSSBY.METR.OU.EDU
Mon Nov 13 18:59:43 EST 2006
Dear Sir/Madam,
I had sent over (three hours ago) the attached figure and the same two
subroutines as I sent previously to Nina and Javier for check.
If that is what is needed, would you please implement the attached *.f90
routine into GrADS as another option of the pdef so persons interested
in those kind of data can easily use grids to display and pinpoint the
data they need.
Suggestion for the options name as ROT.
Thanks,
Diandong Ren
OU/SoM
subroutine RotFindIjForLatlon
(Nx,Ny,sgn,polelat,polelon,x1,y1,dx,dy, &
LOCATION,LOCATIONij)
IMPLICIT NONE
INTEGER :: Nx,Ny,i,j,sgn
real, dimension (1:nx,1:ny,1:2) :: LOCATION
integer, dimension (1:nx,1:ny,1:2) :: LOCATIONij
REAL :: polelat, polelon, x1, y1,dx,dy
real, parameter :: pi=3.14159265,DR=pi/180.0,badvalue=-999.9
REAL :: sin_phi_pole, cos_phi_pole
REAL :: E_x,E_y
REAL :: arg,arg2,a_phi,term1,term2,a_lambda
REAL, dimension (1:Nx,1:Ny) :: wrot
IF (polelat.ge.0) THEN
sin_phi_pole = sin(DR*polelat)
cos_phi_pole = cos(DR*polelat)
ELSE
sin_phi_pole = -sin(DR*polelat)
cos_phi_pole = cos(DR*polelat)
ENDIF
DO j=1,Ny
DO i=1,Nx
a_lambda=180.0+LOCATION(i,j,1)-polelon
a_phi=LOCATION(i,j,2)*DR
arg=sin(a_phi)
term2=COS(a_phi)
IF (ABS(term2).lt.1e-5) THEN
a_lambda=0.0
ELSE
a_lambda=a_lambda*sgn
arg=cos(DR*a_lambda)
term1 =term2*arg
ENDIF
E_y=asin(sin_phi_pole*arg-cos_phi_pole*term1)
E_x=acos((arg*cos_phi_pole+term1*sin_phi_pole)/cos(E_y))
if(sgn>0.0)then
E_x=E_x-2.0*pi
E_y=pi-E_y
endif
LOCATIONij (i,j,1)=(1+int((E_x/DR-x1)/dx))
LOCATIONij (i,j,2)=(1+int((E_y/DR-y1)/dy))
ENDDO
ENDDO
end subroutine RotFindIjForLatlon
-------------- next part --------------
A non-text attachment was scrubbed...
Name: gridMess.eps
Type: application/postscript
Size: 32290 bytes
Desc: not available
Url : http://gradsusr.org/pipermail/gradsusr/attachments/20061113/374d1bad/attachment.eps
-------------- next part --------------
A non-text attachment was scrubbed...
Name: gridMess2.eps
Type: application/postscript
Size: 33408 bytes
Desc: not available
Url : http://gradsusr.org/pipermail/gradsusr/attachments/20061113/374d1bad/attachment-0001.eps
-------------- next part --------------
A non-text attachment was scrubbed...
Name: gridMess3.eps
Type: application/postscript
Size: 27954 bytes
Desc: not available
Url : http://gradsusr.org/pipermail/gradsusr/attachments/20061113/374d1bad/attachment-0002.eps
-------------- next part --------------
A non-text attachment was scrubbed...
Name: gridMess4.eps
Type: application/postscript
Size: 26317 bytes
Desc: not available
Url : http://gradsusr.org/pipermail/gradsusr/attachments/20061113/374d1bad/attachment-0003.eps
More information about the gradsusr
mailing list