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
7e19c456
Commit
7e19c456
authored
Oct 08, 2010
by
Ian Lynagh
Browse files
Remove more -fglasgow-exts uses from tests
parent
27dc4363
Changes
107
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/ghci/scripts/Makefile
View file @
7e19c456
...
...
@@ -11,8 +11,8 @@ ghci024:
printf
":show languages
\n
"
\
|
'
$(TEST_HC)
'
--interactive
-v0
-ignore-dot-ghci
\
|
grep
-E
"^([^ ]| -XImplicitPrelude| -XMagicHash)"
@
echo
"~~~~~~~~~~ Testing :show languages, with -
fglasgow-exts
"
printf
":set -
fglasgow-exts
\n
:show languages
\n
"
\
@
echo
"~~~~~~~~~~ Testing :show languages, with -
XMagicHash
"
printf
":set -
XMagicHash
\n
:show languages
\n
"
\
|
'
$(TEST_HC)
'
--interactive
-v0
-ignore-dot-ghci
\
|
grep
-E
"^([^ ]| -XImplicitPrelude| -XMagicHash)"
@
echo
"~~~~~~~~~~ Testing :show packages"
...
...
testsuite/tests/ghc-regress/ghci/scripts/ghci024.script
View file @
7e19c456
putStrLn "-- ghci024.stdout is a generated file! please edit ghci024.py instead."
:set
:show languages
putStrLn "-- :set -
fglasgow-exts
"
:set -
fglasgow-exts
putStrLn "-- :set -
XMagicHash
"
:set -
XMagicHash
:show languages
:show packages
putStrLn "-- :set -package ghc"
...
...
testsuite/tests/ghc-regress/ghci/scripts/ghci024.stdout
View file @
7e19c456
...
...
@@ -7,7 +7,7 @@ other dynamic, non-language, flag settings:
~~~~~~~~~~ Testing :show languages
active language flags:
-XImplicitPrelude
~~~~~~~~~~ Testing :show languages, with -
fglasgow-exts
~~~~~~~~~~ Testing :show languages, with -
XMagicHash
active language flags:
-XMagicHash
-XImplicitPrelude
...
...
testsuite/tests/ghc-regress/indexed-types/should_compile/Gentle.hs
View file @
7e19c456
{-# OPTIONS -fglasgow-exts #-}
{-# LANGUAGE OverlappingInstances, UndecidableInstances #-}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances,
OverlappingInstances, UndecidableInstances #-}
-- Rather exotic example posted to Haskell mailing list 17 Oct 07
-- It concerns context reduction and functional dependencies
...
...
testsuite/tests/ghc-regress/indexed-types/should_fail/SimpleFail12.hs
View file @
7e19c456
{-# LANGUAGE TypeFamilies #-}
{-# OPTIONS_GHC -fglasgow-exts #-}
{-# LANGUAGE TypeFamilies
, Rank2Types
#-}
module
ShouldFail
where
...
...
testsuite/tests/ghc-regress/indexed-types/should_run/T2985.hs
View file @
7e19c456
{-# LANGUAGE TypeFamilies, UndecidableInstances #-}
{-# OPTIONS
-fglasgow-exts
-Wnot #-}
{-# OPTIONS
_GHC
-Wnot #-}
module
Main
where
...
...
testsuite/tests/ghc-regress/rename/should_fail/rn_dup.hs
View file @
7e19c456
{-# OPTIONS -fglasgow-exts #-}
-- Test for top-level duplicates
...
...
testsuite/tests/ghc-regress/rename/should_fail/rnfail018.hs
View file @
7e19c456
{-#
OPTIONS -fglasgow-exts
#-}
{-#
LANGUAGE MultiParamTypeClasses, ExplicitForAll
#-}
module
ShouldFail
where
...
...
testsuite/tests/ghc-regress/rename/should_fail/rnfail026.hs
View file @
7e19c456
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE Rank2Types, FlexibleInstance
s #-}
-- This one made ghc-4.08 crash
-- rename/RnEnv.lhs:239: Non-exhaustive patterns in function get_tycon_key
...
...
testsuite/tests/ghc-regress/typecheck/prog001/A.hs
View file @
7e19c456
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
module
A
where
class
Matrix
a
fa
|
a
->
fa
where
...
...
testsuite/tests/ghc-regress/typecheck/prog001/B.hs
View file @
7e19c456
{-# LANGUAGE MultiParamTypeClasses #-}
module
B
where
import
A
newtype
Val
=
Val
[
Int
]
...
...
testsuite/tests/ghc-regress/typecheck/prog001/test.T
View file @
7e19c456
...
...
@@ -3,4 +3,4 @@ test('typecheck.prog001',
[
skip_if_fast
,
extra_clean
(['
A.hi
',
'
A.o
',
'
B.hi
',
'
B.o
',
'
C.hi
',
'
C.o
'])],
multimod_compile
,
['
C
',
'
-v0
-fglasgow-exts
'])
['
C
',
'
-v0
'])
testsuite/tests/ghc-regress/typecheck/prog002/A.hs
View file @
7e19c456
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE TypeOperator
s #-}
module
A
where
...
...
testsuite/tests/ghc-regress/typecheck/prog002/B.hs
View file @
7e19c456
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE TypeOperator
s #-}
module
B
where
import
A
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc134.hs
View file @
7e19c456
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE ScopedTypeVariable
s #-}
-- !!! Scoped type variables: result sig
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc141.hs
View file @
7e19c456
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE ScopedTypeVariable
s #-}
-- Scoped type variables on pattern bindings
-- This should *fail* on GHC 5.02 and lower,
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc153.hs
View file @
7e19c456
-- No
-fglasgow-ext
s, so (v::a) means (v:: forall a.a)
-- No
ScopedTypeVariable
s, so (v::a) means (v:: forall a.a)
module
ShouldCompile
where
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc155.hs
View file @
7e19c456
...
...
@@ -2,7 +2,7 @@
-- The type sig for 'test' is illegal in H98 because of the
-- partial application of the type sig.
-- But with
-fglasgow-ext
s it should be OK because when
-- But with
LiberalTypeSynonym
s it should be OK because when
-- you expand the type synonyms it's just Int->Int
-- c.f should_fail/tcfail107.hs
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc191.hs
View file @
7e19c456
{-# OPTIONS -fglasgow-exts #-}
-- This only typechecks if forall-hoisting works ok when
-- importing from an interface file. The type of Twins.gzipWithQ
...
...
testsuite/tests/ghc-regress/typecheck/should_compile/tc200.hs
View file @
7e19c456
{-# OPTIONS
-w -fglasgow-exts
#-}
{-# OPTIONS
_GHC -w
#-}
-- A nasty case that crashed GHC 6.4 with a Lint error;
-- see Note [Multiple instantiation] in TcExpr
...
...
Prev
1
2
3
4
5
6
Next
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