Skip to content

Commit 4cd8fe7

Browse files
committed
lowercase
1 parent 08b52fa commit 4cd8fe7

Some content is hidden

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

49 files changed

+1444
-1444
lines changed

src/cfftb1.f90

Lines changed: 48 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -1,72 +1,72 @@
11
!*==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
2+
subroutine cfftb1(n,c,Ch,Wa,Ifac)
3+
use fftpack_kind
4+
implicit none
55
!*--CFFTB15
66
!*** 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
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
1010
!*** End of declarations inserted by SPAG
11-
DIMENSION Ch(*) , C(*) , Wa(*) , Ifac(*)
11+
dimension Ch(*) , c(*) , Wa(*) , Ifac(*)
1212
nf = Ifac(2)
1313
na = 0
1414
l1 = 1
1515
iw = 1
16-
DO k1 = 1 , nf
16+
do k1 = 1 , nf
1717
ip = Ifac(k1+2)
1818
l2 = ip*l1
19-
ido = N/l2
19+
ido = n/l2
2020
idot = ido + ido
2121
idl1 = idot*l1
22-
IF ( ip==4 ) THEN
22+
if ( ip==4 ) then
2323
ix2 = iw + idot
2424
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
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
3030
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
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
3737
na = 1 - na
38-
ELSEIF ( ip==3 ) THEN
38+
elseif ( ip==3 ) then
3939
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
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
4545
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
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
5454
ix2 = iw + idot
5555
ix3 = ix2 + idot
5656
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
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
6262
na = 1 - na
63-
ENDIF
63+
endif
6464
l1 = l2
6565
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
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.f90

Lines changed: 48 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -1,72 +1,72 @@
11
!*==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
2+
subroutine cfftf1(n,c,Ch,Wa,Ifac)
3+
use fftpack_kind
4+
implicit none
55
!*--CFFTF177
66
!*** 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
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
1010
!*** End of declarations inserted by SPAG
11-
DIMENSION Ch(*) , C(*) , Wa(*) , Ifac(*)
11+
dimension Ch(*) , c(*) , Wa(*) , Ifac(*)
1212
nf = Ifac(2)
1313
na = 0
1414
l1 = 1
1515
iw = 1
16-
DO k1 = 1 , nf
16+
do k1 = 1 , nf
1717
ip = Ifac(k1+2)
1818
l2 = ip*l1
19-
ido = N/l2
19+
ido = n/l2
2020
idot = ido + ido
2121
idl1 = idot*l1
22-
IF ( ip==4 ) THEN
22+
if ( ip==4 ) then
2323
ix2 = iw + idot
2424
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
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
3030
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
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
3737
na = 1 - na
38-
ELSEIF ( ip==3 ) THEN
38+
elseif ( ip==3 ) then
3939
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
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
4545
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
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
5454
ix2 = iw + idot
5555
ix3 = ix2 + idot
5656
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
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
6262
na = 1 - na
63-
ENDIF
63+
endif
6464
l1 = l2
6565
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
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.f90

Lines changed: 41 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -1,73 +1,73 @@
11
!*==CFFTI1.spg processed by SPAG 6.72Dc at 19:17 on 14 Sep 2021
2-
SUBROUTINE CFFTI1(N,Wa,Ifac)
3-
USE FFTPACK_KIND
4-
IMPLICIT NONE
2+
subroutine cffti1(n,Wa,Ifac)
3+
use fftpack_kind
4+
implicit none
55
!*--CFFTI1149
66
!*** Start of declarations inserted by SPAG
7-
REAL arg , argh , argld , FFTPACK_KIND , fi , rk , tpi , Wa
8-
INTEGER i , i1 , ib , ido , idot , Ifac , ii , ip , ipm , j , k1 ,&
9-
& l1 , l2 , ld , N , nf , nl , nq , nr , ntry
10-
INTEGER ntryh
7+
real arg , argh , argld , fftpack_kind , fi , rk , tpi , Wa
8+
integer i , i1 , ib , ido , idot , Ifac , ii , ip , ipm , j , k1 ,&
9+
& l1 , l2 , ld , n , nf , nl , nq , nr , ntry
10+
integer ntryh
1111
!*** End of declarations inserted by SPAG
12-
DIMENSION Wa(*) , Ifac(*) , ntryh(4)
13-
DATA ntryh(1) , ntryh(2) , ntryh(3) , ntryh(4)/3 , 4 , 2 , 5/
14-
nl = N
12+
dimension Wa(*) , Ifac(*) , ntryh(4)
13+
data ntryh(1) , ntryh(2) , ntryh(3) , ntryh(4)/3 , 4 , 2 , 5/
14+
nl = n
1515
nf = 0
1616
j = 0
1717
100 j = j + 1
18-
IF ( j<=4 ) THEN
18+
if ( j<=4 ) then
1919
ntry = ntryh(j)
20-
ELSE
20+
else
2121
ntry = ntry + 2
22-
ENDIF
22+
endif
2323
200 nq = nl/ntry
2424
nr = nl - ntry*nq
25-
IF ( nr/=0 ) GOTO 100
25+
if ( nr/=0 ) goto 100
2626
nf = nf + 1
2727
Ifac(nf+2) = ntry
2828
nl = nq
29-
IF ( ntry==2 ) THEN
30-
IF ( nf/=1 ) THEN
31-
DO i = 2 , nf
29+
if ( ntry==2 ) then
30+
if ( nf/=1 ) then
31+
do i = 2 , nf
3232
ib = nf - i + 2
3333
Ifac(ib+2) = Ifac(ib+1)
34-
ENDDO
34+
enddo
3535
Ifac(3) = 2
36-
ENDIF
37-
ENDIF
38-
IF ( nl/=1 ) GOTO 200
39-
Ifac(1) = N
36+
endif
37+
endif
38+
if ( nl/=1 ) goto 200
39+
Ifac(1) = n
4040
Ifac(2) = nf
41-
tpi = 6.28318530717958647692D0
42-
argh = tpi/REAL(N,rk)
41+
tpi = 6.28318530717958647692d0
42+
argh = tpi/real(n,rk)
4343
i = 2
4444
l1 = 1
45-
DO k1 = 1 , nf
45+
do k1 = 1 , nf
4646
ip = Ifac(k1+2)
4747
ld = 0
4848
l2 = l1*ip
49-
ido = N/l2
49+
ido = n/l2
5050
idot = ido + ido + 2
5151
ipm = ip - 1
52-
DO j = 1 , ipm
52+
do j = 1 , ipm
5353
i1 = i
54-
Wa(i-1) = 1.0D0
55-
Wa(i) = 0.0D0
54+
Wa(i-1) = 1.0d0
55+
Wa(i) = 0.0d0
5656
ld = ld + l1
57-
fi = 0.0D0
58-
argld = REAL(ld,rk)*argh
59-
DO ii = 4 , idot , 2
57+
fi = 0.0d0
58+
argld = real(ld,rk)*argh
59+
do ii = 4 , idot , 2
6060
i = i + 2
61-
fi = fi + 1.D0
61+
fi = fi + 1.d0
6262
arg = fi*argld
63-
Wa(i-1) = COS(arg)
64-
Wa(i) = SIN(arg)
65-
ENDDO
66-
IF ( ip>5 ) THEN
63+
Wa(i-1) = cos(arg)
64+
Wa(i) = sin(arg)
65+
enddo
66+
if ( ip>5 ) then
6767
Wa(i1-1) = Wa(i-1)
6868
Wa(i1) = Wa(i)
69-
ENDIF
70-
ENDDO
69+
endif
70+
enddo
7171
l1 = l2
72-
ENDDO
73-
END subroutine cffti1
72+
enddo
73+
end subroutine cffti1

0 commit comments

Comments
 (0)