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
8415c28b
Commit
8415c28b
authored
Dec 18, 2010
by
Ian Lynagh
Browse files
Implement GADTSyntax extension
parent
dea74f19
Changes
2
Hide whitespace changes
Inline
Side-by-side
compiler/main/DynFlags.hs
View file @
8415c28b
...
...
@@ -321,6 +321,7 @@ data ExtensionFlag
|
Opt_RecordPuns
|
Opt_ViewPatterns
|
Opt_GADTs
|
Opt_GADTSyntax
|
Opt_NPlusKPatterns
|
Opt_DoAndIfThenElse
|
Opt_RebindableSyntax
...
...
@@ -1585,6 +1586,7 @@ xFlags = [
(
"DisambiguateRecordFields"
,
Opt_DisambiguateRecordFields
,
nop
),
(
"OverloadedStrings"
,
Opt_OverloadedStrings
,
nop
),
(
"GADTs"
,
Opt_GADTs
,
nop
),
(
"GADTSyntax"
,
Opt_GADTSyntax
,
nop
),
(
"ViewPatterns"
,
Opt_ViewPatterns
,
nop
),
(
"TypeFamilies"
,
Opt_TypeFamilies
,
nop
),
(
"BangPatterns"
,
Opt_BangPatterns
,
nop
),
...
...
@@ -1662,6 +1664,7 @@ impliedFlags
,
(
Opt_RebindableSyntax
,
turnOff
,
Opt_ImplicitPrelude
)
-- NB: turn off!
,
(
Opt_GADTs
,
turnOn
,
Opt_GADTSyntax
)
,
(
Opt_GADTs
,
turnOn
,
Opt_MonoLocalBinds
)
,
(
Opt_TypeFamilies
,
turnOn
,
Opt_MonoLocalBinds
)
...
...
compiler/typecheck/TcTyClsDecls.lhs
View file @
8415c28b
...
...
@@ -753,11 +753,12 @@ tcTyClDecl1 parent calc_isrec
; kind_signatures <- xoptM Opt_KindSignatures
; existential_ok <- xoptM Opt_ExistentialQuantification
; gadt_ok <- xoptM Opt_GADTs
; gadtSyntax_ok <- xoptM Opt_GADTSyntax
; is_boot <- tcIsHsBoot -- Are we compiling an hs-boot file?
; let ex_ok = existential_ok || gadt_ok -- Data cons can have existential context
-- Check that we don't use GADT syntax in H98 world
; checkTc (gadt_ok || h98_syntax) (badGadtDecl tc_name)
; checkTc (gadt
Syntax
_ok || h98_syntax) (badGadtDecl tc_name)
-- Check that we don't use kind signatures without Glasgow extensions
; checkTc (kind_signatures || isNothing mb_ksig) (badSigTyDecl tc_name)
...
...
@@ -846,12 +847,12 @@ tcConDecl :: Bool -- True <=> -funbox-strict_fields
-> TcM DataCon
tcConDecl unbox_strict existential_ok rep_tycon res_tmpl -- Data types
(ConDecl {con_name =name, con_qvars = tvs, con_cxt = ctxt
con@
(ConDecl {con_name =
name, con_qvars = tvs, con_cxt = ctxt
, con_details = details, con_res = res_ty })
= addErrCtxt (dataConCtxt name) $
tcTyVarBndrs tvs $ \ tvs' -> do
{ ctxt' <- tcHsKindedContext ctxt
; checkTc (existential_ok ||
(null tvs && null (unLoc ctxt))
)
; checkTc (existential_ok ||
conRepresentibleWithH98Syntax con
)
(badExistential name)
; (univ_tvs, ex_tvs, eq_preds, res_ty') <- tcResultType res_tmpl tvs' res_ty
; let
...
...
@@ -946,6 +947,21 @@ consUseH98Syntax (L _ (ConDecl { con_res = ResTyGADT _ }) : _) = False
consUseH98Syntax _ = True
-- All constructors have same shape
conRepresentibleWithH98Syntax :: ConDecl Name -> Bool
conRepresentibleWithH98Syntax
(ConDecl {con_qvars = tvs, con_cxt = ctxt, con_res = ResTyH98 })
= null tvs && null (unLoc ctxt)
conRepresentibleWithH98Syntax
(ConDecl {con_qvars = tvs, con_cxt = ctxt, con_res = ResTyGADT (L _ t) })
= null (unLoc ctxt) && f t (map (hsTyVarName . unLoc) tvs)
where -- Each type variable should be used exactly once in the
-- result type, and the result type must just be the type
-- constructor applied to type variables
f (HsAppTy (L _ t1) (L _ (HsTyVar v2))) vs
= (v2 `elem` vs) && f t1 (delete v2 vs)
f (HsTyVar _) [] = True
f _ _ = False
-------------------
tcConArg :: Bool -- True <=> -funbox-strict_fields
-> LHsType Name
...
...
@@ -1536,7 +1552,7 @@ badGadtDecl tc_name
badExistential :: Located Name -> SDoc
badExistential con_name
= hang (ptext (sLit "Data constructor") <+> quotes (ppr con_name) <+>
ptext (sLit "has existential type variables,
or
a context"))
ptext (sLit "has existential type variables, a context
, or a specialised result type
"))
2 (parens $ ptext (sLit "Use -XExistentialQuantification or -XGADTs to allow this"))
badStupidTheta :: Name -> SDoc
...
...
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