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
22535fa3
Commit
22535fa3
authored
Oct 06, 2010
by
Ian Lynagh
Browse files
Update tests now -fglasgow-exts is deprecated
parent
811690f9
Changes
255
Hide whitespace changes
Inline
Side-by-side
testsuite/tests/ghc-regress/codeGen/should_compile/1916.hs
View file @
22535fa3
{-# OPTIONS -fglasgow-exts #-}
module
Bug
(
tst
)
where
tst
::
Float
->
Bool
tst
x
=
truncate
x
>
(
0
::
Int
)
testsuite/tests/ghc-regress/codeGen/should_compile/cg001.hs
View file @
22535fa3
{-#
OPTIONS -fglasgow-exts
#-}
{-#
LANGUAGE MagicHash
#-}
module
ShouldCompile
where
...
...
testsuite/tests/ghc-regress/codeGen/should_compile/cg006.hs
View file @
22535fa3
{-#
OPTIONS_GHC -cpp -fglasgow-exts
#-}
{-#
LANGUAGE MagicHash
#-}
module
ShouldCompile
where
-- exposed a bug in the NCG in 6.4.2
...
...
testsuite/tests/ghc-regress/deSugar/should_compile/all.T
View file @
22535fa3
...
...
@@ -53,7 +53,7 @@ test('ds045', normal, compile, [''])
test
('
ds046
',
normal
,
compile
,
['
-funbox-strict-fields
'])
test
('
ds047
',
normal
,
compile
,
[''])
test
('
ds048
',
normal
,
compile
,
[''])
test
('
ds050
',
normal
,
compile
,
['
-fglasgow-exts
'])
test
('
ds050
',
normal
,
compile
,
[''])
test
('
ds051
',
normal
,
compile
,
[''])
test
('
ds052
',
normal
,
compile
,
[''])
test
('
ds053
',
normal
,
compile
,
[''])
...
...
testsuite/tests/ghc-regress/deSugar/should_compile/ds035.hs
View file @
22535fa3
{-#
OPTIONS -fglasgow-exts
#-}
{-#
LANGUAGE MagicHash
#-}
module
ShouldCompile
where
import
GHC.Exts
...
...
testsuite/tests/ghc-regress/deSugar/should_compile/ds050.hs
View file @
22535fa3
{-# LANGUAGE Rank2Types #-}
module
ShouldCompile
where
data
Q
=
Q
{
f
::
forall
a
.
a
->
a
}
...
...
testsuite/tests/ghc-regress/deSugar/should_compile/ds055.hs
View file @
22535fa3
{-#
OPTIONS -fglasgow-exts
#-}
{-#
LANGUAGE ExistentialQuantification, DeriveDataTypeable
#-}
-- This module requires quite trick desugaring,
-- because of the context in the existentials
...
...
testsuite/tests/ghc-regress/deSugar/should_compile/ds057.hs
View file @
22535fa3
{-#
OPTIONS_GHC -fglasgow-ext
s #-}
{-#
LANGUAGE MagicHash, UnboxedTuple
s #-}
module
ShouldCompile
where
import
Data.Word
...
...
testsuite/tests/ghc-regress/deriving/should_compile/drv012.hs
View file @
22535fa3
{-#
OPTIONS_GHC -fglasgow-ext
s #-}
{-#
LANGUAGE GADT
s #-}
-- !!! deriving for GADTs which declare Haskell98 data types.
-- bug reported as http://hackage.haskell.org/trac/ghc/ticket/902
...
...
testsuite/tests/ghc-regress/deriving/should_compile/drv013.hs
View file @
22535fa3
{-#
OPTIONS_GHC -fglasgow-exts
#-}
{-#
LANGUAGE DeriveDataTypeable
#-}
-- Deriving Typeable has various special cases
module
Foo
where
...
...
testsuite/tests/ghc-regress/deriving/should_compile/drv015.hs
View file @
22535fa3
{-# OPTIONS -fglasgow-exts #-}
-- July 07: I'm changing this from "should_compile" to "should_fail".
-- It would generate an instance decl like
...
...
testsuite/tests/ghc-regress/deriving/should_compile/drv020.hs
View file @
22535fa3
{-# OPTIONS_GHC -fglasgow-exts #-}
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
FlexibleInstances, GeneralizedNewtypeDeriving #-}
-- Test deriving of a multi-parameter class for
-- one-argument newtype defined in the same module
...
...
testsuite/tests/ghc-regress/ffi/should_compile/ffi-deriv1.hs
View file @
22535fa3
{-#
OPTIONS -fglasgow-exts
#-}
{-#
LANGUAGE GeneralizedNewtypeDeriving
#-}
-- Tests newtype unwrapping for the IO monad itself
-- Notice the RenderM monad, which is used in the
...
...
testsuite/tests/ghc-regress/gadt/Arith.hs
View file @
22535fa3
{-#
OPTIONS_GHC -fglasgow-ext
s #-}
{-#
LANGUAGE GADT
s #-}
module
Arith
where
...
...
testsuite/tests/ghc-regress/gadt/CasePrune.hs
View file @
22535fa3
{-#
OPTIONS_GHC -fglasgow-exts
#-}
{-#
LANGUAGE GADTs, GeneralizedNewtypeDeriving
#-}
-- See Trac #1251 and the comments
-- Note [Pruning dead case alternatives] in types/Unify.lhs
...
...
testsuite/tests/ghc-regress/gadt/Gadt17_help.hs
View file @
22535fa3
{-# OPTIONS -fglasgow-exts -O #-}
{-# LANGUAGE GADTs #-}
{-# OPTIONS_GHC -O #-}
module
Gadt17_help
(
TernOp
(
..
),
applyTernOp
...
...
testsuite/tests/ghc-regress/gadt/Gadt23_AST.hs
View file @
22535fa3
{-#
OPTIONS_GHC -XGADTs -fglasgow-ext
s #-}
{-#
LANGUAGE GADTs, KindSignature
s #-}
module
Gadt23_AST
where
...
...
testsuite/tests/ghc-regress/gadt/Nilsson.hs
View file @
22535fa3
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE GADT
s #-}
-- Supplied by Henrik Nilsson, showed up a bug in GADTs
...
...
testsuite/tests/ghc-regress/gadt/Session.hs
View file @
22535fa3
{-#
OPTIONS -fglasgow-ext
s #-}
{-#
LANGUAGE GADTs, KindSignature
s #-}
-- See Trac #1323; crashed GHC 6.6
...
...
testsuite/tests/ghc-regress/gadt/T2040.hs
View file @
22535fa3
{-# OPTIONS_GHC -Wall -fglasgow-exts #-}
{-# LANGUAGE GADTs, ScopedTypeVariables, FlexibleContexts,
MultiParamTypeClasses #-}
{-# OPTIONS_GHC -Wall #-}
module
T2040
where
...
...
Prev
1
2
3
4
5
…
13
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