Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
fc898b0c
Commit
fc898b0c
authored
Oct 29, 2010
by
Ian Lynagh
Browse files
Add a test for trac #4444
parent
e53cf244
Changes
2
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/typecheck/should_compile/T4444.hs
0 → 100644
View file @
fc898b0c
-- #4444: We shouldn't warn about SPECIALISE INLINE pragmas on
-- non-overloaded functions
{-# LANGUAGE GADTs, MagicHash #-}
module
Q
where
import
GHC.Exts
data
Arr
e
where
ArrInt
::
!
Int
->
ByteArray
#
->
Arr
Int
ArrPair
::
!
Int
->
Arr
e1
->
Arr
e2
->
Arr
(
e1
,
e2
)
(
!:
)
::
Arr
e
->
Int
->
e
{-# SPECIALISE INLINE (!:) :: Arr Int -> Int -> Int #-}
{-# SPECIALISE INLINE (!:) :: Arr (a, b) -> Int -> (a, b) #-}
(
ArrInt
_
ba
)
!:
(
I
#
i
)
=
I
#
(
indexIntArray
#
ba
i
)
(
ArrPair
_
a1
a2
)
!:
i
=
(
a1
!:
i
,
a2
!:
i
)
testsuite/tests/ghc-regress/typecheck/should_compile/all.T
View file @
fc898b0c
...
...
@@ -330,4 +330,5 @@ test('T4401', normal, compile, [''])
test
('
T4404
',
expect_broken
(
4404
),
compile
,
['
-Wall
'])
test
('
HasKey
',
normal
,
compile
,
[''])
test
('
T4418
',
normal
,
compile
,
[''])
test
('
T4444
',
normal
,
compile
,
[''])
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment