File: power-operator.f90

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (141 lines) | stat: -rw-r--r-- 3,413 bytes parent folder | download | duplicates (12)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
! RUN: bbc -emit-fir %s -o - | FileCheck %s --check-prefixes="CHECK,PRECISE"
! RUN: bbc --math-runtime=precise -emit-fir %s -o - | FileCheck %s --check-prefixes="PRECISE"
! RUN: bbc --force-mlir-complex -emit-fir %s -o - | FileCheck %s --check-prefixes="FAST"
! RUN: %flang_fc1 -emit-fir %s -o - | FileCheck %s --check-prefixes="CHECK,PRECISE"
! RUN: %flang_fc1 -fapprox-func -emit-fir %s -o - | FileCheck %s --check-prefixes="CHECK,FAST"
! RUN: %flang_fc1 -emit-fir -mllvm --math-runtime=precise %s -o - | FileCheck %s --check-prefixes="PRECISE"
! RUN: %flang_fc1 -emit-fir -mllvm --force-mlir-complex %s -o - | FileCheck %s --check-prefixes="FAST"

! Test power operation lowering

! CHECK-LABEL: pow_r4_i4
subroutine pow_r4_i4(x, y, z)
  real :: x, z
  integer :: y
  z = x ** y
  ! CHECK: math.fpowi {{.*}} : f32, i32
end subroutine

! CHECK-LABEL: pow_r4_r4
subroutine pow_r4_r4(x, y, z)
  real :: x, z, y
  z = x ** y
  ! CHECK: math.powf %{{.*}}, %{{.*}} : f32
end subroutine

! CHECK-LABEL: pow_r4_i8
subroutine pow_r4_i8(x, y, z)
  real :: x, z
  integer(8) :: y
  z = x ** y
  ! CHECK: math.fpowi {{.*}} : f32, i64
end subroutine

! CHECK-LABEL: pow_r8_i4
subroutine pow_r8_i4(x, y, z)
  real(8) :: x, z
  integer :: y
  z = x ** y
  ! CHECK: math.fpowi {{.*}} : f64, i32
end subroutine

! CHECK-LABEL: pow_r8_i8
subroutine pow_r8_i8(x, y, z)
  real(8) :: x, z
  integer(8) :: y
  z = x ** y
  ! CHECK: math.fpowi {{.*}} : f64, i64
end subroutine

! CHECK-LABEL: pow_r8_r8
subroutine pow_r8_r8(x, y, z)
  real(8) :: x, z, y
  z = x ** y
  ! CHECK: math.powf %{{.*}}, %{{.*}} : f64
end subroutine

! CHECK-LABEL: pow_r4_r8
subroutine pow_r4_r8(x, y, z)
  real(4) :: x
  real(8) :: z, y
  z = x ** y
  ! CHECK: %{{.*}} = fir.convert %{{.*}} : (f32) -> f64
  ! CHECK: math.powf %{{.*}}, %{{.*}} : f64
end subroutine

! CHECK-LABEL: pow_i1_i1
subroutine pow_i1_i1(x, y, z)
  integer(1) :: x, y, z
  z = x ** y
  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i8
end subroutine

! CHECK-LABEL: pow_i2_i2
subroutine pow_i2_i2(x, y, z)
  integer(2) :: x, y, z
  z = x ** y
  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i16
end subroutine

! CHECK-LABEL: pow_i4_i4
subroutine pow_i4_i4(x, y, z)
  integer(4) :: x, y, z
  z = x ** y
  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i32
end subroutine

! CHECK-LABEL: pow_i8_i8
subroutine pow_i8_i8(x, y, z)
  integer(8) :: x, y, z
  z = x ** y
  ! CHECK: math.ipowi %{{.*}}, %{{.*}} : i64
end subroutine

! CHECK-LABEL: pow_c4_i4
subroutine pow_c4_i4(x, y, z)
  complex :: x, z
  integer :: y
  z = x ** y
  ! CHECK: call @_FortranAcpowi
end subroutine

! CHECK-LABEL: pow_c4_i8
subroutine pow_c4_i8(x, y, z)
  complex :: x, z
  integer(8) :: y
  z = x ** y
  ! CHECK: call @_FortranAcpowk
end subroutine

! CHECK-LABEL: pow_c8_i4
subroutine pow_c8_i4(x, y, z)
  complex(8) :: x, z
  integer :: y
  z = x ** y
  ! CHECK: call @_FortranAzpowi
end subroutine

! CHECK-LABEL: pow_c8_i8
subroutine pow_c8_i8(x, y, z)
  complex(8) :: x, z
  integer(8) :: y
  z = x ** y
  ! CHECK: call @_FortranAzpowk
end subroutine

! CHECK-LABEL: pow_c4_c4
subroutine pow_c4_c4(x, y, z)
  complex :: x, y, z
  z = x ** y
  ! FAST: complex.pow %{{.*}}, %{{.*}} : complex<f32>
  ! PRECISE: call @cpowf
end subroutine

! CHECK-LABEL: pow_c8_c8
subroutine pow_c8_c8(x, y, z)
  complex(8) :: x, y, z
  z = x ** y
  ! FAST: complex.pow %{{.*}}, %{{.*}} : complex<f64>
  ! PRECISE: call @cpow
end subroutine