diff options
author | Zubin Duggal <zubin@cmi.ac.in> | 2020-01-08 16:28:28 +0100 |
---|---|---|
committer | Marge Bot <ben+marge-bot@smart-cactus.org> | 2020-07-25 00:44:30 -0400 |
commit | 02133353e712e98bfbbc6ed32305b137bb3654eb (patch) | |
tree | 12909a607dd2910501813fc4d0550913ade367be /ghc/GHCi/UI.hs | |
parent | ba205046e4f2ea94b1c978c050b917de4daaf092 (diff) | |
download | haskell-02133353e712e98bfbbc6ed32305b137bb3654eb.tar.gz |
Simplify XRec definition
Change `Located X` usage to `XRec pass X`
This increases the scope of the LPat experiment to almost all of GHC.
Introduce UnXRec and MapXRec classes
Fixes #17587 and #18408
Updates haddock submodule
Co-authored-by: Philipp Krüger <philipp.krueger1@gmail.com>
Diffstat (limited to 'ghc/GHCi/UI.hs')
-rw-r--r-- | ghc/GHCi/UI.hs | 6 |
1 files changed, 5 insertions, 1 deletions
diff --git a/ghc/GHCi/UI.hs b/ghc/GHCi/UI.hs index 8e7a7485a2..7180bc71ac 100644 --- a/ghc/GHCi/UI.hs +++ b/ghc/GHCi/UI.hs @@ -9,6 +9,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE ViewPatterns #-} +{-# LANGUAGE TypeFamilies #-} ----------------------------------------------------------------------------- -- @@ -1255,7 +1256,9 @@ runStmt input step = do mk_stmt :: SrcSpan -> HsBind GhcPs -> GhciLStmt GhcPs mk_stmt loc bind = - let l = L loc + let + l :: a -> Located a + l = L loc in l (LetStmt noExtField (l (HsValBinds noExtField (ValBinds noExtField (unitBag (l bind)) [])))) -- | Clean up the GHCi environment after a statement has run @@ -2797,6 +2800,7 @@ showDynFlags show_all dflags = do text "warning settings:" $$ nest 2 (vcat (map (setting "-W" "-Wno-" wopt) DynFlags.wWarningFlags)) where + setting :: String -> String -> (flag -> DynFlags -> Bool) -> FlagSpec flag -> SDoc setting prefix noPrefix test flag | quiet = empty | is_on = text prefix <> text name |