1 |
! |
2 |
! translated to f95 Nov. 2009 |
3 |
!=============================================================== |
4 |
! NOTE THE INTERPOLATION ROUTINE STARTS AT BIN 0 NOT 1 |
5 |
! |
6 |
! Cart_to_Polar |
7 |
! |
8 |
! Bradley W. Hindman |
9 |
! version 2: June 19, 1998 |
10 |
! rewritten as subroutine |
11 |
! Deborah Haber (DH) Oct 22, 2007 |
12 |
! added azimuthal average Jan. 2009 - DH |
13 |
! works now with ringanalysis_sngl.f |
14 |
! 16 Sept 2009 - DH |
15 |
! passes arrays to be written to files |
16 |
! back to ringanalysis_sngl.f to be |
17 |
! passed to c wrapper for actual output |
18 |
! |
19 |
! This routine converts the power spectra contained in |
20 |
! powxy from Cartesian (kx,ky,nu) coordinates to polar |
21 |
! (theta,k,nu) coordinates. The resulting power spectra has |
22 |
! pixels evenly spaced in k and in theta. Cubic convolution |
23 |
! interpolation is used to convert from the initially evenly |
24 |
! spaced rectangular data. |
25 |
! This routine outputs the data in array "powthtk", |
26 |
! which holds the data in polar format, |
27 |
! |
28 |
! (azimuth, wavenumber, frequency). |
29 |
! |
30 |
! Inputs_____________________________________________________ |
31 |
! |
32 |
! powxy Input array = the (nkx,nky,nnu) original spectrum. Real*4 |
33 |
! powthtk Output array = the unwrapped (ntht,nk,nnu) spectrum. Real*4 |
34 |
! x0 Center of powxy in x direction in pixels. Real*4 = crpix1. |
35 |
! y0 Center of powxy in y direction in pixels. Real*4 = crpix2. |
36 |
! |
37 |
! Data Array_________________________________________________ |
38 |
! |
39 |
! powbuf(nkx,nky) Cartesian frequency slice |
40 |
! |
41 |
! Book Keeping Variables_____________________________________ |
42 |
! |
43 |
! nkx,nky The number of data elements in the |
44 |
! ntht,nk appropriate dimension of the Carte- |
45 |
! sian or polar coordinate systems. |
46 |
! nnu Number of data elements in the frequen- |
47 |
! cy dimension in both Cartesian and |
48 |
! polar coordinates. |
49 |
! ikx,iky,inu Index variables for the appropriate |
50 |
! itht,ik data dimensions. |
51 |
! kx,ky Location polar grid points in Cartesian |
52 |
! coordinates. |
53 |
! |
54 |
! lnbase Keyword specifying whether powxy is the |
55 |
! power or log(power), passed from main routine |
56 |
! = 0.0 data is in units of power |
57 |
! = 2.718 data is in units of log(power) |
58 |
! |
59 |
! ROUTINES___________________________________________________ |
60 |
! |
61 |
! CCINT2(powbuf,nkx,nky,kx,ky) Function |
62 |
! |
63 |
!=============================================================== |
64 |
module cart |
65 |
contains |
66 |
SUBROUTINE cart_to_polar(powxy,powthtk,nkx,nky,nnu,ntht,nk, & |
67 |
& x0,y0,lnbase,verbose,ierr) |
68 |
implicit none |
69 |
integer, parameter :: single = 4 |
70 |
integer :: nk,nkx,nky,nnu,ntht,ier,ierr |
71 |
integer :: ik,inu,itht,ikx,iky,ik3,inu3 |
72 |
integer :: verbose |
73 |
real(kind=single) :: kx,ky,x0,y0,dtht,theta,lnbase,pi |
74 |
real(kind=single), dimension(nkx,nky) :: powbuf |
75 |
real(kind=single), dimension(nkx,nky,nnu) :: powxy |
76 |
real(kind=single), dimension(ntht,nk,nnu) :: powthtk |
77 |
real(kind=single), dimension(ntht) :: cosine, sine |
78 |
real(kind=single) :: CCINT2 |
79 |
|
80 |
!--------------------------------------------------------------- |
81 |
! Initialize cosine and sine arrays for later use. |
82 |
!--------------------------------------------------------------- |
83 |
pi=ACOS(-1.0) |
84 |
dtht=2.0*pi/real(ntht) |
85 |
DO itht=1,ntht |
86 |
theta=(itht-1)*dtht |
87 |
cosine(itht)=COS(theta) |
88 |
sine(itht)=SIN(theta) |
89 |
END DO |
90 |
! if (verbose == 1) then |
91 |
! write(*,'("cosine")') |
92 |
! write(*,'(8(f8.4,2x))')(cosine(itht),itht=1,ntht) |
93 |
! write(*,'("sine")') |
94 |
! write(*,'(8(f8.4,2x))')(cosine(itht),itht=1,ntht) |
95 |
! endif |
96 |
|
97 |
|
98 |
!---------------------------------------------------------- |
99 |
! Initialize error catching variable |
100 |
!---------------------------------------------------------- |
101 |
|
102 |
ierr=0 |
103 |
|
104 |
!--------------------------------------------------------- |
105 |
! If debugging write out some intermediary variables |
106 |
!--------------------------------------------------------- |
107 |
|
108 |
IF (verbose == 1) THEN |
109 |
WRITE(*,'(" nkx, nky, nnu")') |
110 |
WRITE(*,*) nkx, nky, nnu |
111 |
WRITE(*,'(" ntht, dtht, x0, y0")') |
112 |
WRITE(*,*) ntht, dtht, x0, y0 |
113 |
WRITE(*,'(" lnbase = ",f8.4)') lnbase |
114 |
ENDIF |
115 |
|
116 |
!--------------------------------------------------------------- |
117 |
! Step through each azimuth and wave number and interpolate |
118 |
! for each frequency value inu out of total nnu values |
119 |
! If lnbase is not 0.0 THEN the power is already in log space |
120 |
! else take log of power before proceeding |
121 |
!--------------------------------------------------------------- |
122 |
|
123 |
IF (lnbase /= 0.0) THEN |
124 |
DO inu=1,nnu |
125 |
DO iky = 1,nky |
126 |
DO ikx = 1,nkx |
127 |
powbuf(ikx,iky)=powxy(ikx,iky,inu) |
128 |
! write(*,'("ikx,iky,inu",3i8)')ikx,iky,inu |
129 |
! write(*,'("powbuf, powxy ",2(1pe14.4,2x))')powbuf(ikx,iky), & |
130 |
! & powxy(ikx,iky,inu) |
131 |
END DO |
132 |
END DO |
133 |
DO ik = 1,nk |
134 |
DO itht = 1,ntht |
135 |
kx=real(ik)*cosine(itht)+x0 |
136 |
ky=real(ik)*sine(itht)+y0 |
137 |
powthtk(itht,ik,inu)=EXP(ccint2(powbuf,nkx,nky,kx,ky)) |
138 |
END DO |
139 |
END DO |
140 |
! write(*,'("powthtk = ",4pe13.4)') ((powthtk(itht,ik,inu),itht=1,2),ik=10,11) |
141 |
END DO |
142 |
ELSE |
143 |
DO inu=1,nnu |
144 |
DO iky = 1,nky |
145 |
DO ikx = 1,nkx |
146 |
if (powxy(ikx,iky,inu) > 0.0) then |
147 |
powbuf(ikx,iky)=alog(powxy(ikx,iky,inu)) |
148 |
else |
149 |
write(*,*)" Negative power in Cart_to_Polar" |
150 |
ierr=11 |
151 |
goto 9999 |
152 |
endif |
153 |
END DO |
154 |
END DO |
155 |
DO ik = 1,nk |
156 |
DO itht = 1,ntht |
157 |
kx=real(ik)*cosine(itht)+x0 |
158 |
ky=real(ik)*sine(itht)+y0 |
159 |
powthtk(itht,ik,inu)=EXP(ccint2(powbuf,nkx,nky,kx,ky)) |
160 |
END DO |
161 |
END DO |
162 |
END DO |
163 |
END IF |
164 |
IF (verbose == 1)THEN |
165 |
WRITE(*,*)" cart powthtk " |
166 |
ik3=nk/3 |
167 |
inu3=nnu/3 |
168 |
WRITE(*,20)((powthtk(1,ik,inu),ik=ik3,ik3+2),inu=inu3,inu3+1) |
169 |
20 format(3(2(1pe13.5,2x))) |
170 |
WRITE(*,*)" Finishing Cart_to_Polar" |
171 |
ENDIF |
172 |
9999 IF (ierr .NE. 0) THEN |
173 |
WRITE(*,'(" Problem in cart_to_polar subroutine ")') |
174 |
WRITE(*,'(" ierr = ",i4)') ierr |
175 |
ENDIF |
176 |
RETURN |
177 |
END subroutine cart_to_polar |
178 |
end module cart |