Skip to content

Commit 08b52fa

Browse files
jacobwilliamscertik
authored andcommitted
Initial fixed to free processing by SPAG
1 parent 1c23efa commit 08b52fa

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

99 files changed

+2547
-2177
lines changed

src/cfftb1.f

Lines changed: 0 additions & 63 deletions
This file was deleted.

src/cfftb1.f90

Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
!*==CFFTB1.spg processed by SPAG 6.72Dc at 19:17 on 14 Sep 2021
2+
SUBROUTINE CFFTB1(N,C,Ch,Wa,Ifac)
3+
USE FFTPACK_KIND
4+
IMPLICIT NONE
5+
!*--CFFTB15
6+
!*** Start of declarations inserted by SPAG
7+
REAL C , Ch , FFTPACK_KIND , rk , Wa
8+
INTEGER i , idl1 , ido , idot , Ifac , ip , iw , ix2 , ix3 , ix4 ,&
9+
& k1 , l1 , l2 , N , n2 , na , nac , nf
10+
!*** End of declarations inserted by SPAG
11+
DIMENSION Ch(*) , C(*) , Wa(*) , Ifac(*)
12+
nf = Ifac(2)
13+
na = 0
14+
l1 = 1
15+
iw = 1
16+
DO k1 = 1 , nf
17+
ip = Ifac(k1+2)
18+
l2 = ip*l1
19+
ido = N/l2
20+
idot = ido + ido
21+
idl1 = idot*l1
22+
IF ( ip==4 ) THEN
23+
ix2 = iw + idot
24+
ix3 = ix2 + idot
25+
IF ( na/=0 ) THEN
26+
CALL PASSB4(idot,l1,Ch,C,Wa(iw),Wa(ix2),Wa(ix3))
27+
ELSE
28+
CALL PASSB4(idot,l1,C,Ch,Wa(iw),Wa(ix2),Wa(ix3))
29+
ENDIF
30+
na = 1 - na
31+
ELSEIF ( ip==2 ) THEN
32+
IF ( na/=0 ) THEN
33+
CALL PASSB2(idot,l1,Ch,C,Wa(iw))
34+
ELSE
35+
CALL PASSB2(idot,l1,C,Ch,Wa(iw))
36+
ENDIF
37+
na = 1 - na
38+
ELSEIF ( ip==3 ) THEN
39+
ix2 = iw + idot
40+
IF ( na/=0 ) THEN
41+
CALL PASSB3(idot,l1,Ch,C,Wa(iw),Wa(ix2))
42+
ELSE
43+
CALL PASSB3(idot,l1,C,Ch,Wa(iw),Wa(ix2))
44+
ENDIF
45+
na = 1 - na
46+
ELSEIF ( ip/=5 ) THEN
47+
IF ( na/=0 ) THEN
48+
CALL PASSB(nac,idot,ip,l1,idl1,Ch,Ch,Ch,C,C,Wa(iw))
49+
ELSE
50+
CALL PASSB(nac,idot,ip,l1,idl1,C,C,C,Ch,Ch,Wa(iw))
51+
ENDIF
52+
IF ( nac/=0 ) na = 1 - na
53+
ELSE
54+
ix2 = iw + idot
55+
ix3 = ix2 + idot
56+
ix4 = ix3 + idot
57+
IF ( na/=0 ) THEN
58+
CALL PASSB5(idot,l1,Ch,C,Wa(iw),Wa(ix2),Wa(ix3),Wa(ix4))
59+
ELSE
60+
CALL PASSB5(idot,l1,C,Ch,Wa(iw),Wa(ix2),Wa(ix3),Wa(ix4))
61+
ENDIF
62+
na = 1 - na
63+
ENDIF
64+
l1 = l2
65+
iw = iw + (ip-1)*idot
66+
ENDDO
67+
IF ( na==0 ) RETURN
68+
n2 = N + N
69+
DO i = 1 , n2
70+
C(i) = Ch(i)
71+
ENDDO
72+
END subroutine cfftb1

src/cfftf1.f

Lines changed: 0 additions & 63 deletions
This file was deleted.

src/cfftf1.f90

Lines changed: 72 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,72 @@
1+
!*==CFFTF1.spg processed by SPAG 6.72Dc at 19:17 on 14 Sep 2021
2+
SUBROUTINE CFFTF1(N,C,Ch,Wa,Ifac)
3+
USE FFTPACK_KIND
4+
IMPLICIT NONE
5+
!*--CFFTF177
6+
!*** Start of declarations inserted by SPAG
7+
REAL C , Ch , FFTPACK_KIND , rk , Wa
8+
INTEGER i , idl1 , ido , idot , Ifac , ip , iw , ix2 , ix3 , ix4 ,&
9+
& k1 , l1 , l2 , N , n2 , na , nac , nf
10+
!*** End of declarations inserted by SPAG
11+
DIMENSION Ch(*) , C(*) , Wa(*) , Ifac(*)
12+
nf = Ifac(2)
13+
na = 0
14+
l1 = 1
15+
iw = 1
16+
DO k1 = 1 , nf
17+
ip = Ifac(k1+2)
18+
l2 = ip*l1
19+
ido = N/l2
20+
idot = ido + ido
21+
idl1 = idot*l1
22+
IF ( ip==4 ) THEN
23+
ix2 = iw + idot
24+
ix3 = ix2 + idot
25+
IF ( na/=0 ) THEN
26+
CALL PASSF4(idot,l1,Ch,C,Wa(iw),Wa(ix2),Wa(ix3))
27+
ELSE
28+
CALL PASSF4(idot,l1,C,Ch,Wa(iw),Wa(ix2),Wa(ix3))
29+
ENDIF
30+
na = 1 - na
31+
ELSEIF ( ip==2 ) THEN
32+
IF ( na/=0 ) THEN
33+
CALL PASSF2(idot,l1,Ch,C,Wa(iw))
34+
ELSE
35+
CALL PASSF2(idot,l1,C,Ch,Wa(iw))
36+
ENDIF
37+
na = 1 - na
38+
ELSEIF ( ip==3 ) THEN
39+
ix2 = iw + idot
40+
IF ( na/=0 ) THEN
41+
CALL PASSF3(idot,l1,Ch,C,Wa(iw),Wa(ix2))
42+
ELSE
43+
CALL PASSF3(idot,l1,C,Ch,Wa(iw),Wa(ix2))
44+
ENDIF
45+
na = 1 - na
46+
ELSEIF ( ip/=5 ) THEN
47+
IF ( na/=0 ) THEN
48+
CALL PASSF(nac,idot,ip,l1,idl1,Ch,Ch,Ch,C,C,Wa(iw))
49+
ELSE
50+
CALL PASSF(nac,idot,ip,l1,idl1,C,C,C,Ch,Ch,Wa(iw))
51+
ENDIF
52+
IF ( nac/=0 ) na = 1 - na
53+
ELSE
54+
ix2 = iw + idot
55+
ix3 = ix2 + idot
56+
ix4 = ix3 + idot
57+
IF ( na/=0 ) THEN
58+
CALL PASSF5(idot,l1,Ch,C,Wa(iw),Wa(ix2),Wa(ix3),Wa(ix4))
59+
ELSE
60+
CALL PASSF5(idot,l1,C,Ch,Wa(iw),Wa(ix2),Wa(ix3),Wa(ix4))
61+
ENDIF
62+
na = 1 - na
63+
ENDIF
64+
l1 = l2
65+
iw = iw + (ip-1)*idot
66+
ENDDO
67+
IF ( na==0 ) RETURN
68+
n2 = N + N
69+
DO i = 1 , n2
70+
C(i) = Ch(i)
71+
ENDDO
72+
END subroutine cfftf1

src/cffti1.f

Lines changed: 0 additions & 62 deletions
This file was deleted.

0 commit comments

Comments
 (0)