Skip to content
GitLab
Projects
Groups
Snippets
Help
Loading...
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
GHC
Project overview
Project overview
Details
Activity
Releases
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Locked Files
Issues
4,319
Issues
4,319
List
Boards
Labels
Service Desk
Milestones
Iterations
Merge Requests
368
Merge Requests
368
Requirements
Requirements
List
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Security & Compliance
Security & Compliance
Dependency List
License Compliance
Operations
Operations
Incidents
Environments
Analytics
Analytics
CI / CD
Code Review
Insights
Issue
Repository
Value Stream
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
c1e5ca56
Commit
c1e5ca56
authored
Apr 13, 2012
by
Simon Peyton Jones
Browse files
Options
Browse Files
Download
Plain Diff
Merge branch 'master' of
http://darcs.haskell.org//testsuite
Conflicts: tests/polykinds/all.T
parents
70665778
125a20ff
Changes
26
Show whitespace changes
Inline
Side-by-side
Showing
26 changed files
with
136 additions
and
19 deletions
+136
-19
testsuite/tests/concurrent/should_run/all.T
testsuite/tests/concurrent/should_run/all.T
+4
-9
testsuite/tests/ghci/scripts/T5975a.script
testsuite/tests/ghci/scripts/T5975a.script
+1
-0
testsuite/tests/ghci/scripts/T5975b.script
testsuite/tests/ghci/scripts/T5975b.script
+0
-0
testsuite/tests/ghci/scripts/all.T
testsuite/tests/ghci/scripts/all.T
+10
-1
testsuite/tests/indexed-types/should_fail/T5934.hs
testsuite/tests/indexed-types/should_fail/T5934.hs
+12
-0
testsuite/tests/indexed-types/should_fail/T5934.stderr
testsuite/tests/indexed-types/should_fail/T5934.stderr
+8
-0
testsuite/tests/indexed-types/should_fail/all.T
testsuite/tests/indexed-types/should_fail/all.T
+2
-0
testsuite/tests/polykinds/T5948.hs
testsuite/tests/polykinds/T5948.hs
+7
-0
testsuite/tests/polykinds/all.T
testsuite/tests/polykinds/all.T
+1
-0
testsuite/tests/rts/5993.hs
testsuite/tests/rts/5993.hs
+6
-0
testsuite/tests/rts/5993.stdout
testsuite/tests/rts/5993.stdout
+1
-0
testsuite/tests/rts/all.T
testsuite/tests/rts/all.T
+1
-0
testsuite/tests/safeHaskell/check/Check09.stderr
testsuite/tests/safeHaskell/check/Check09.stderr
+2
-1
testsuite/tests/safeHaskell/ghci/p11.stderr
testsuite/tests/safeHaskell/ghci/p11.stderr
+2
-1
testsuite/tests/safeHaskell/ghci/p12.stderr
testsuite/tests/safeHaskell/ghci/p12.stderr
+2
-1
testsuite/tests/safeHaskell/ghci/p17.stderr
testsuite/tests/safeHaskell/ghci/p17.stderr
+2
-1
testsuite/tests/safeHaskell/ghci/p3.stderr
testsuite/tests/safeHaskell/ghci/p3.stderr
+4
-2
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
...uite/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
+3
-3
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered12.hs
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered12.hs
+7
-0
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
...uite/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
+9
-0
testsuite/tests/safeHaskell/safeInfered/all.T
testsuite/tests/safeHaskell/safeInfered/all.T
+3
-0
testsuite/tests/typecheck/should_compile/PolytypeDecomp.hs
testsuite/tests/typecheck/should_compile/PolytypeDecomp.hs
+32
-0
testsuite/tests/typecheck/should_compile/all.T
testsuite/tests/typecheck/should_compile/all.T
+2
-0
testsuite/tests/typecheck/should_fail/T6001.hs
testsuite/tests/typecheck/should_fail/T6001.hs
+9
-0
testsuite/tests/typecheck/should_fail/T6001.stderr
testsuite/tests/typecheck/should_fail/T6001.stderr
+5
-0
testsuite/tests/typecheck/should_fail/all.T
testsuite/tests/typecheck/should_fail/all.T
+1
-0
No files found.
testsuite/tests/concurrent/should_run/all.T
View file @
c1e5ca56
...
...
@@ -30,8 +30,7 @@ test('3279', normal, compile_and_run, [''])
test
('
3429
',
extra_run_opts
('
+RTS -C0.001 -RTS
'),
compile_and_run
,
[''])
# without -O, goes into an infinite loop
# GHCi cannot deterct the infinite loop, because the thread is always reachable
# (see also conc033 and others). We should really fix this.
# GHCi does not detect the infinite loop. We should really fix this.
test
('
4030
',
omit_ways
('
ghci
'),
compile_and_run
,
['
-O
'])
# each of these runs for about a second
...
...
@@ -41,8 +40,7 @@ test('throwto002', [reqlib('random')], compile_and_run, [''])
test
('
throwto003
',
normal
,
compile_and_run
,
[''])
test
('
mask001
',
normal
,
compile_and_run
,
[''])
# ghci does not generate the BlockedIndefinitely exceptions, so omit:
test
('
mask002
',
omit_ways
(['
ghci
']),
compile_and_run
,
[''])
test
('
mask002
',
normal
,
compile_and_run
,
[''])
test
('
async001
',
normal
,
compile_and_run
,
[''])
...
...
@@ -110,8 +108,7 @@ test('conc019', compose(only_compiler_types(['ghc']),
extra_run_opts
('
+RTS -K16m -RTS
')),
compile_and_run
,
[''])
test
('
conc020
',
only_compiler_types
(['
ghc
']),
compile_and_run
,
[''])
test
('
conc021
',
compose
(
omit_ways
(['
ghci
']),
exit_code
(
1
)),
compile_and_run
,
[''])
test
('
conc021
',
[
omit_ways
(['
ghci
']),
exit_code
(
1
)
],
compile_and_run
,
[''])
test
('
conc022
',
only_compiler_types
(['
ghc
']),
compile_and_run
,
[''])
# On Windows, the non-threaded RTS creates a real OS thread for each
...
...
@@ -141,9 +138,7 @@ test('conc030', compose(only_compiler_types(['ghc']),
test
('
conc031
',
normal
,
compile_and_run
,
[''])
test
('
conc032
',
only_compiler_types
(['
ghc
']),
compile_and_run
,
[''])
# Omit for GHCi, because it just sits there waiting for you to press ^C
test
('
conc033
',
omit_ways
(['
ghci
']),
compile_and_run
,
[''])
test
('
conc033
',
normal
,
compile_and_run
,
[''])
# Omit for GHCi, because it just sits there waiting for you to press ^C
test
('
conc034
',
compose
(
only_compiler_types
(['
ghc
']),
...
...
testsuite/tests/ghci/scripts/T5975a.script
0 → 100644
View file @
c1e5ca56
:load föøbàr.hs
testsuite/tests/ghci/scripts/T5975b.script
0 → 100644
View file @
c1e5ca56
testsuite/tests/ghci/scripts/all.T
View file @
c1e5ca56
# coding=utf8
setTestOpts
(
if_compiler_profiled
(
skip
))
...
...
@@ -113,4 +114,12 @@ test('T5564', normal, ghci_script, ['T5564.script'])
test
('
Defer02
',
normal
,
ghci_script
,
['
Defer02.script
'])
test
('
T5820
',
normal
,
ghci_script
,
['
T5820.script
'])
test
('
T5836
',
normal
,
ghci_script
,
['
T5836.script
'])
test
('
T5979
',
normal
,
ghci_script
,
['
T5979.script
'])
test
('
T5979
',
normalise_slashes
,
ghci_script
,
['
T5979.script
'])
test
('
T5975a
',
[
pre_cmd
('
touch föøbàr.hs
'),
clean_cmd
('
rm föøbàr.hs
')],
ghci_script
,
['
T5975a.script
'])
test
('
T5975b
',
[
pre_cmd
('
touch föøbàr.hs
'),
clean_cmd
('
rm föøbàr.hs
')],
ghci_script
,
['
T5975b.script
'])
testsuite/tests/indexed-types/should_fail/T5934.hs
0 → 100644
View file @
c1e5ca56
{-# LANGUAGE RankNTypes, TypeFamilies, KindSignatures #-}
module
T5934
where
import
Control.Monad.ST
data
Gen
s
type
GenST
s
=
Gen
(
PrimState
(
ST
s
))
run
::
(
forall
s
.
GenST
s
)
->
Int
run
=
0
type
family
PrimState
(
m
::
*
->
*
)
testsuite/tests/indexed-types/should_fail/T5934.stderr
0 → 100644
View file @
c1e5ca56
T5934.hs:10:7:
No instance for (Num ((forall s. GenST s) -> Int))
arising from the literal `0'
Possible fix:
add an instance declaration for (Num ((forall s. GenST s) -> Int))
In the expression: 0
In an equation for `run': run = 0
testsuite/tests/indexed-types/should_fail/all.T
View file @
c1e5ca56
...
...
@@ -74,3 +74,5 @@ test('T5439', normal, compile_fail, [''])
test
('
T5515
',
normal
,
compile_fail
,
[''])
test
('
T5763
',
expect_broken
(
5673
),
compile_fail
,
[''])
test
('
T5934
',
normal
,
compile_fail
,
[''])
testsuite/tests/polykinds/T5948.hs
0 → 100644
View file @
c1e5ca56
{-# LANGUAGE DataKinds, TypeOperators #-}
module
T5948
where
type
Foo
=
(
Int
'
:
'
[]
)
type
Bar
=
Int
'
:
'
[]
testsuite/tests/polykinds/all.T
View file @
c1e5ca56
...
...
@@ -32,3 +32,4 @@ test('T5716', normal, compile_fail, [''])
test
('
T5937
',
normal
,
compile
,
[''])
test
('
T5935
',
normal
,
compile
,
[''])
test
('
T5938
',
normal
,
compile
,
[''])
test
('
T5948
',
normal
,
compile
,
[''])
testsuite/tests/rts/5993.hs
0 → 100644
View file @
c1e5ca56
import
Control.Concurrent
main
=
do
m
<-
newEmptyMVar
forkIO
$
putStrLn
"Hello World!"
>>
putMVar
m
()
takeMVar
m
testsuite/tests/rts/5993.stdout
0 → 100644
View file @
c1e5ca56
Hello World!
testsuite/tests/rts/all.T
View file @
c1e5ca56
...
...
@@ -129,3 +129,4 @@ test('T5423',
run_command
,
['
$MAKE -s --no-print-directory T5423
'])
test
('
5993
',
extra_run_opts
('
+RTS -k8 -RTS
'),
compile_and_run
,
[''])
testsuite/tests/safeHaskell/check/Check09.stderr
View file @
c1e5ca56
Check09.hs:4:1:
bytestring-0.10.0.0:Data.ByteString.Char8 can't be safely imported! The package (bytestring-0.10.0.0) the module resides in isn't trusted.
Data.ByteString.Char8: Can't be safely imported!
The package (bytestring-0.10.0.0) the module resides in isn't trusted.
testsuite/tests/safeHaskell/ghci/p11.stderr
View file @
c1e5ca56
E.hs:3:1:
base:System.IO.Unsafe can't be safely imported! The module itself isn't safe.
System.IO.Unsafe: Can't be safely imported!
The module itself isn't safe.
testsuite/tests/safeHaskell/ghci/p12.stderr
View file @
c1e5ca56
<no location info>:
bytestring-0.10.0.0:Data.ByteString can't be safely imported! The package (bytestring-0.10.0.0) the module resides in isn't trusted.
Data.ByteString: Can't be safely imported!
The package (bytestring-0.10.0.0) the module resides in isn't trusted.
testsuite/tests/safeHaskell/ghci/p17.stderr
View file @
c1e5ca56
<no location info>:
bytestring-0.10.0.0:Data.ByteString can't be safely imported! The package (bytestring-0.10.0.0) the module resides in isn't trusted.
Data.ByteString: Can't be safely imported!
The package (bytestring-0.10.0.0) the module resides in isn't trusted.
testsuite/tests/safeHaskell/ghci/p3.stderr
View file @
c1e5ca56
<no location info>:
base:System.IO.Unsafe can't be safely imported! The module itself isn't safe.
System.IO.Unsafe: Can't be safely imported!
The module itself isn't safe.
<no location info>:
bytestring-0.10.0.0:Data.ByteString can't be safely imported! The package (bytestring-0.10.0.0) the module resides in isn't trusted.
Data.ByteString: Can't be safely imported!
The package (bytestring-0.10.0.0) the module resides in isn't trusted.
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered11.stderr
View file @
c1e5ca56
[1 of 2] Compiling UnsafeInfered11_A ( UnsafeInfered11_A.hs, UnsafeInfered11_A.o )
UnsafeInfered11_A.hs:1:16:
Warning:
`UnsafeInfered11_A' has been infered as unsafe!
UnsafeInfered11_A.hs:1:16:
Warning:
`UnsafeInfered11_A' has been infered as unsafe!
Reason:
UnsafeInfered11_A.hs:17:11:
UnsafeInfered11_A.hs:17:11:
Warning:
Rule "lookupx/T" ignored
User defined rules are disabled under Safe Haskell
[2 of 2] Compiling UnsafeInfered11 ( UnsafeInfered11.hs, UnsafeInfered11.o )
...
...
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered12.hs
0 → 100644
View file @
c1e5ca56
{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -fwarn-unsafe -Werror #-}
module
UnsafeInfered12
where
a
::
Int
a
=
1
testsuite/tests/safeHaskell/safeInfered/UnsafeInfered12.stderr
0 → 100644
View file @
c1e5ca56
UnsafeInfered12.hs:2:16: Warning:
`UnsafeInfered12' has been infered as unsafe!
Reason:
UnsafeInfered12.hs:1:14:
-XTemplateHaskell is not allowed in Safe Haskell
<no location info>:
Failing due to -Werror.
testsuite/tests/safeHaskell/safeInfered/all.T
View file @
c1e5ca56
...
...
@@ -56,6 +56,9 @@ test('UnsafeInfered11',
[
extra_clean
(['
UnsafeInfered11_A.hi
',
'
UnsafeInfered11_A.o
'])
],
multimod_compile_fail
,
['
UnsafeInfered11
',
''])
# test should fail as unsafe and we made warn unsafe + -Werror
test
('
UnsafeInfered12
',
normal
,
compile_fail
,
[''])
# Mixed tests
test
('
Mixed01
',
normal
,
compile_fail
,
[''])
test
('
Mixed02
',
normal
,
compile_fail
,
[''])
...
...
testsuite/tests/typecheck/should_compile/PolytypeDecomp.hs
0 → 100644
View file @
c1e5ca56
{-# LANGUAGE TypeFamilies, LiberalTypeSynonyms, ImpredicativeTypes #-}
module
PolyTypeDecomp
where
{- The purpose of this test is to check if decomposition of wanted
equalities in the /constraint solver/ (vs. the unifier) works properly.
Unfortunately most equalities between polymorphic types are converted to
implication constraints early on in the unifier, so we have to make things
a bit more convoluted by introducing the myLength function. The wanted
constraints we get for this program are:
[forall a. Maybe a] ~ Id alpha
[forall a. F [a]] ~ Id alpha
Which, /after reactions/ should create a fresh implication:
forall a. Maybe a ~ F [a]
that is perfectly soluble.
-}
type
family
F
a
type
instance
F
[
a
]
=
Maybe
a
type
family
Id
a
type
instance
Id
a
=
a
f
::
[
forall
a
.
F
[
a
]]
f
=
undefined
g
::
[
forall
a
.
Maybe
a
]
->
Int
g
x
=
myLength
[
x
,
f
]
myLength
::
[
Id
a
]
->
Int
myLength
=
undefined
testsuite/tests/typecheck/should_compile/all.T
View file @
c1e5ca56
...
...
@@ -375,3 +375,5 @@ test('T3108', normal, compile, [''])
test
('
T5792
',
normal
,
run_command
,
['
$MAKE -s --no-print-directory T5792
'])
test
('
PolytypeDecomp
',
normal
,
compile
,
[''])
\ No newline at end of file
testsuite/tests/typecheck/should_fail/T6001.hs
0 → 100644
View file @
c1e5ca56
{-# LANGUAGE InstanceSigs #-}
module
T6001
where
data
DayKind
=
Work
|
Rest
instance
Num
DayKind
where
fromInteger
::
Int
->
DayKind
fromInteger
=
undefined
testsuite/tests/typecheck/should_fail/T6001.stderr
0 → 100644
View file @
c1e5ca56
T6001.hs:8:18:
Method signature does not match class; it should be
fromInteger :: Integer -> DayKind
In the instance declaration for `Num DayKind'
testsuite/tests/typecheck/should_fail/all.T
View file @
c1e5ca56
...
...
@@ -272,3 +272,4 @@ test('T5689', normal, compile_fail, [''])
test
('
T5684
',
normal
,
compile_fail
,
[''])
test
('
T5858
',
normal
,
compile_fail
,
[''])
test
('
T5957
',
normal
,
compile_fail
,
[''])
test
('
T6001
',
normal
,
compile_fail
,
[''])
Write
Preview
Markdown
is supported
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