Skip to content
Snippets Groups Projects
Commit 188b280d authored by Arnaud Spiwack's avatar Arnaud Spiwack
Browse files

LinearTypes => MonoLocalBinds

parent 522c12a4
No related branches found
No related tags found
No related merge requests found
......@@ -2861,6 +2861,9 @@ impliedXFlags
-- The extensions needed to declare an H98 unlifted data type
, (LangExt.UnliftedDatatypes, turnOn, LangExt.DataKinds)
, (LangExt.UnliftedDatatypes, turnOn, LangExt.StandaloneKindSignatures)
-- See Note [Destructuring AbsBinds aren't linear] in GHC.Tc.Gen.Bind
, (LangExt.LinearTypes, turnOn, LangExt.MonoLocalBinds)
]
-- | Things you get with `-dlint`.
......
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE LinearTypes, NoMonoLocalBinds #-}
{-# LANGUAGE UndecidableInstances, Rank2Types,
KindSignatures, EmptyDataDecls, MultiParamTypeClasses, CPP #-}
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment