Skip to content

Commit 575cccd

Browse files
committed
change name of local fypp macro real kinds list
1 parent 61ca3ef commit 575cccd

File tree

2 files changed

+38
-38
lines changed

2 files changed

+38
-38
lines changed

src/stdlib_specialfunctions_gamma.fypp

Lines changed: 32 additions & 32 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
#:include "common.fypp"
2-
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES[0:2]
2+
#:set R_KINDS_TYPES = REAL_KINDS_TYPES[0:2]
33
#:set CI_KINDS_TYPES = INT_KINDS_TYPES + CMPLX_KINDS_TYPES[0:2]
44
module stdlib_specialfunctions_gamma
55
use iso_fortran_env, only : qp => real128
@@ -14,7 +14,7 @@ module stdlib_specialfunctions_gamma
1414
integer(int32), parameter :: max_fact_int32 = 13_int32
1515
integer(int64), parameter :: max_fact_int64 = 21_int64
1616

17-
#:for k1, t1 in RC_KINDS_TYPES
17+
#:for k1, t1 in R_KINDS_TYPES
1818
${t1}$, parameter :: tol_${k1}$ = epsilon(1.0_${k1}$)
1919
#:endfor
2020
real(qp), parameter :: tol_qp = epsilon(1.0_qp)
@@ -62,12 +62,12 @@ module stdlib_specialfunctions_gamma
6262
!! Lower incomplete gamma function
6363
!!
6464
#:for k1, t1 in INT_KINDS_TYPES
65-
#:for k2, t2 in RC_KINDS_TYPES
65+
#:for k2, t2 in R_KINDS_TYPES
6666
module procedure ingamma_low_${t1[0]}$${k1}$${k2}$
6767
#:endfor
6868
#:endfor
6969

70-
#:for k1, t1 in RC_KINDS_TYPES
70+
#:for k1, t1 in R_KINDS_TYPES
7171
module procedure ingamma_low_${t1[0]}$${k1}$
7272
#:endfor
7373
end interface lower_incomplete_gamma
@@ -78,12 +78,12 @@ module stdlib_specialfunctions_gamma
7878
!! Logarithm of lower incomplete gamma function
7979
!!
8080
#:for k1, t1 in INT_KINDS_TYPES
81-
#:for k2, t2 in RC_KINDS_TYPES
81+
#:for k2, t2 in R_KINDS_TYPES
8282
module procedure l_ingamma_low_${t1[0]}$${k1}$${k2}$
8383
#:endfor
8484
#:endfor
8585

86-
#:for k1, t1 in RC_KINDS_TYPES
86+
#:for k1, t1 in R_KINDS_TYPES
8787
module procedure l_ingamma_low_${t1[0]}$${k1}$
8888
#:endfor
8989
end interface log_lower_incomplete_gamma
@@ -94,12 +94,12 @@ module stdlib_specialfunctions_gamma
9494
!! Upper incomplete gamma function
9595
!!
9696
#:for k1, t1 in INT_KINDS_TYPES
97-
#:for k2, t2 in RC_KINDS_TYPES
97+
#:for k2, t2 in R_KINDS_TYPES
9898
module procedure ingamma_up_${t1[0]}$${k1}$${k2}$
9999
#:endfor
100100
#:endfor
101101

102-
#:for k1, t1 in RC_KINDS_TYPES
102+
#:for k1, t1 in R_KINDS_TYPES
103103
module procedure ingamma_up_${t1[0]}$${k1}$
104104
#:endfor
105105
end interface upper_incomplete_gamma
@@ -110,12 +110,12 @@ module stdlib_specialfunctions_gamma
110110
!! Logarithm of upper incomplete gamma function
111111
!!
112112
#:for k1, t1 in INT_KINDS_TYPES
113-
#:for k2, t2 in RC_KINDS_TYPES
113+
#:for k2, t2 in R_KINDS_TYPES
114114
module procedure l_ingamma_up_${t1[0]}$${k1}$${k2}$
115115
#:endfor
116116
#:endfor
117117

118-
#:for k1, t1 in RC_KINDS_TYPES
118+
#:for k1, t1 in R_KINDS_TYPES
119119
module procedure l_ingamma_up_${t1[0]}$${k1}$
120120
#:endfor
121121
end interface log_upper_incomplete_gamma
@@ -126,12 +126,12 @@ module stdlib_specialfunctions_gamma
126126
!! Regularized (normalized) lower incomplete gamma function, P
127127
!!
128128
#:for k1, t1 in INT_KINDS_TYPES
129-
#:for k2, t2 in RC_KINDS_TYPES
129+
#:for k2, t2 in R_KINDS_TYPES
130130
module procedure regamma_p_${t1[0]}$${k1}$${k2}$
131131
#:endfor
132132
#:endfor
133133

134-
#:for k1, t1 in RC_KINDS_TYPES
134+
#:for k1, t1 in R_KINDS_TYPES
135135
module procedure regamma_p_${t1[0]}$${k1}$
136136
#:endfor
137137
end interface regularized_gamma_p
@@ -142,12 +142,12 @@ module stdlib_specialfunctions_gamma
142142
!! Regularized (normalized) upper incomplete gamma function, Q
143143
!!
144144
#:for k1, t1 in INT_KINDS_TYPES
145-
#:for k2, t2 in RC_KINDS_TYPES
145+
#:for k2, t2 in R_KINDS_TYPES
146146
module procedure regamma_q_${t1[0]}$${k1}$${k2}$
147147
#:endfor
148148
#:endfor
149149

150-
#:for k1, t1 in RC_KINDS_TYPES
150+
#:for k1, t1 in R_KINDS_TYPES
151151
module procedure regamma_q_${t1[0]}$${k1}$
152152
#:endfor
153153
end interface regularized_gamma_q
@@ -158,12 +158,12 @@ module stdlib_specialfunctions_gamma
158158
! Incomplete gamma G function.
159159
! Internal use only
160160
!
161-
#:for k1, t1 in RC_KINDS_TYPES
161+
#:for k1, t1 in R_KINDS_TYPES
162162
module procedure gpx_${t1[0]}$${k1}$ !for real p and x
163163
#:endfor
164164

165165
#:for k1, t1 in INT_KINDS_TYPES
166-
#:for k2, t2 in RC_KINDS_TYPES
166+
#:for k2, t2 in R_KINDS_TYPES
167167
module procedure gpx_${t1[0]}$${k1}$${k2}$ !for integer p and real x
168168
#:endfor
169169
#:endfor
@@ -176,7 +176,7 @@ module stdlib_specialfunctions_gamma
176176
! Internal use only
177177
!
178178
#:for k1, t1 in INT_KINDS_TYPES
179-
#:for k2, t2 in RC_KINDS_TYPES
179+
#:for k2, t2 in R_KINDS_TYPES
180180
module procedure l_gamma_${t1[0]}$${k1}$${k2}$
181181
#:endfor
182182
#:endfor
@@ -372,7 +372,7 @@ contains
372372

373373

374374
#:for k1, t1 in INT_KINDS_TYPES
375-
#:for k2, t2 in RC_KINDS_TYPES
375+
#:for k2, t2 in R_KINDS_TYPES
376376

377377
impure elemental function l_gamma_${t1[0]}$${k1}$${k2}$(z, x) result(res)
378378
!
@@ -555,7 +555,7 @@ contains
555555

556556

557557

558-
#:for k1, t1 in RC_KINDS_TYPES
558+
#:for k1, t1 in R_KINDS_TYPES
559559
#:if k1 == "sp"
560560
#:set k2 = "dp"
561561
#:elif k1 == "dp"
@@ -701,7 +701,7 @@ contains
701701

702702

703703
#:for k1, t1 in INT_KINDS_TYPES
704-
#:for k2, t2 in RC_KINDS_TYPES
704+
#:for k2, t2 in R_KINDS_TYPES
705705
impure elemental function gpx_${t1[0]}$${k1}$${k2}$(p, x) result(res)
706706
!
707707
! Approximation of incomplete gamma G function with integer argument p.
@@ -840,7 +840,7 @@ contains
840840

841841

842842

843-
#:for k1, t1 in RC_KINDS_TYPES
843+
#:for k1, t1 in R_KINDS_TYPES
844844
impure elemental function ingamma_low_${t1[0]}$${k1}$(p, x) result(res)
845845
!
846846
! Approximation of lower incomplete gamma function with real p.
@@ -877,7 +877,7 @@ contains
877877

878878

879879
#:for k1, t1 in INT_KINDS_TYPES
880-
#:for k2, t2 in RC_KINDS_TYPES
880+
#:for k2, t2 in R_KINDS_TYPES
881881
impure elemental function ingamma_low_${t1[0]}$${k1}$${k2}$(p, x) &
882882
result(res)
883883
!
@@ -917,7 +917,7 @@ contains
917917

918918

919919

920-
#:for k1, t1 in RC_KINDS_TYPES
920+
#:for k1, t1 in R_KINDS_TYPES
921921
impure elemental function l_ingamma_low_${t1[0]}$${k1}$(p, x) result(res)
922922

923923
${t1}$, intent(in) :: p, x
@@ -954,7 +954,7 @@ contains
954954

955955

956956
#:for k1, t1 in INT_KINDS_TYPES
957-
#:for k2, t2 in RC_KINDS_TYPES
957+
#:for k2, t2 in R_KINDS_TYPES
958958
impure elemental function l_ingamma_low_${t1[0]}$${k1}$${k2}$(p, x) &
959959
result(res)
960960

@@ -986,7 +986,7 @@ contains
986986

987987

988988

989-
#:for k1, t1 in RC_KINDS_TYPES
989+
#:for k1, t1 in R_KINDS_TYPES
990990
impure elemental function ingamma_up_${t1[0]}$${k1}$(p, x) result(res)
991991
!
992992
! Approximation of upper incomplete gamma function with real p.
@@ -1024,7 +1024,7 @@ contains
10241024

10251025

10261026
#:for k1, t1 in INT_KINDS_TYPES
1027-
#:for k2, t2 in RC_KINDS_TYPES
1027+
#:for k2, t2 in R_KINDS_TYPES
10281028
impure elemental function ingamma_up_${t1[0]}$${k1}$${k2}$(p, x) &
10291029
result(res)
10301030
!
@@ -1066,7 +1066,7 @@ contains
10661066

10671067

10681068

1069-
#:for k1, t1 in RC_KINDS_TYPES
1069+
#:for k1, t1 in R_KINDS_TYPES
10701070
impure elemental function l_ingamma_up_${t1[0]}$${k1}$(p, x) result(res)
10711071

10721072
${t1}$, intent(in) :: p, x
@@ -1104,7 +1104,7 @@ contains
11041104

11051105

11061106
#:for k1, t1 in INT_KINDS_TYPES
1107-
#:for k2, t2 in RC_KINDS_TYPES
1107+
#:for k2, t2 in R_KINDS_TYPES
11081108
impure elemental function l_ingamma_up_${t1[0]}$${k1}$${k2}$(p, x) &
11091109
result(res)
11101110

@@ -1145,7 +1145,7 @@ contains
11451145

11461146

11471147

1148-
#:for k1, t1 in RC_KINDS_TYPES
1148+
#:for k1, t1 in R_KINDS_TYPES
11491149
impure elemental function regamma_p_${t1[0]}$${k1}$(p, x) result(res)
11501150
!
11511151
! Approximation of regularized incomplete gamma function P(p,x) for real p
@@ -1180,7 +1180,7 @@ contains
11801180

11811181

11821182
#:for k1, t1 in INT_KINDS_TYPES
1183-
#:for k2, t2 in RC_KINDS_TYPES
1183+
#:for k2, t2 in R_KINDS_TYPES
11841184
impure elemental function regamma_p_${t1[0]}$${k1}$${k2}$(p, x) result(res)
11851185
!
11861186
! Approximation of regularized incomplete gamma function P(p,x) for integer p
@@ -1216,7 +1216,7 @@ contains
12161216

12171217

12181218

1219-
#:for k1, t1 in RC_KINDS_TYPES
1219+
#:for k1, t1 in R_KINDS_TYPES
12201220
impure elemental function regamma_q_${t1[0]}$${k1}$(p, x) result(res)
12211221
!
12221222
! Approximation of regularized incomplete gamma function Q(p,x) for real p
@@ -1251,7 +1251,7 @@ contains
12511251

12521252

12531253
#:for k1, t1 in INT_KINDS_TYPES
1254-
#:for k2, t2 in RC_KINDS_TYPES
1254+
#:for k2, t2 in R_KINDS_TYPES
12551255
impure elemental function regamma_q_${t1[0]}$${k1}$${k2}$(p, x) result(res)
12561256
!
12571257
! Approximation of regularized incomplet gamma function Q(p,x) for integer p

test/specialfunctions/test_specialfunctions_gamma.fypp

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
#:include "common.fypp"
2-
#:set RC_KINDS_TYPES = REAL_KINDS_TYPES[0:2]
2+
#:set R_KINDS_TYPES = REAL_KINDS_TYPES[0:2]
33
#:set CI_KINDS_TYPES = INT_KINDS_TYPES + CMPLX_KINDS_TYPES[0:2]
44
module test_specialfunctions_gamma
55
use testdrive, only : new_unittest, unittest_type, error_type, check
@@ -17,7 +17,7 @@ module test_specialfunctions_gamma
1717

1818
public :: collect_specialfunctions_gamma
1919

20-
#:for k1, t1 in RC_KINDS_TYPES
20+
#:for k1, t1 in R_KINDS_TYPES
2121
${t1}$, parameter :: tol_${k1}$ = 1000 * epsilon(1.0_${k1}$)
2222
#:endfor
2323

@@ -45,7 +45,7 @@ contains
4545
#:endfor
4646

4747
#:for k1, t1 in INT_KINDS_TYPES
48-
#:for k2, t2 in RC_KINDS_TYPES
48+
#:for k2, t2 in R_KINDS_TYPES
4949
, new_unittest("lower_incomplete_gamma_${t1[0]}$${k1}$${k2}$", &
5050
test_lincgamma_${t1[0]}$${k1}$${k2}$) &
5151
, new_unittest("log_lower_incomplete_gamma_${t1[0]}$${k1}$${k2}$", &
@@ -61,7 +61,7 @@ contains
6161
#:endfor
6262
#:endfor
6363

64-
#:for k1, t1 in RC_KINDS_TYPES
64+
#:for k1, t1 in R_KINDS_TYPES
6565
, new_unittest("lower_incomplete_gamma_${t1[0]}$${k1}$", &
6666
test_lincgamma_${t1[0]}$${k1}$) &
6767
, new_unittest("log_lower_incomplete_gamma_${t1[0]}$${k1}$", &
@@ -267,7 +267,7 @@ contains
267267

268268

269269
#:for k1, t1 in INT_KINDS_TYPES
270-
#:for k2, t2 in RC_KINDS_TYPES
270+
#:for k2, t2 in R_KINDS_TYPES
271271

272272
subroutine test_lincgamma_${t1[0]}$${k1}$${k2}$(error)
273273
type(error_type), allocatable, intent(out) :: error
@@ -416,7 +416,7 @@ contains
416416

417417

418418

419-
#:for k1, t1 in RC_KINDS_TYPES
419+
#:for k1, t1 in R_KINDS_TYPES
420420

421421
subroutine test_lincgamma_${t1[0]}$${k1}$(error)
422422
type(error_type), allocatable, intent(out) :: error

0 commit comments

Comments
 (0)