[commit: ghc] master: mkGadtDecl no longer in P monad (afbd30b)

git at git.haskell.org git at git.haskell.org
Wed Nov 11 13:27:23 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/afbd30b6cc486378dd556f738a5337e126bf65a7/ghc

>---------------------------------------------------------------

commit afbd30b6cc486378dd556f738a5337e126bf65a7
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Wed Nov 11 13:28:01 2015 +0100

    mkGadtDecl no longer in P monad
    
    Since `mkGadtDecl` does not use any of the functions specific to the `P`
    monad we can extract it from that monad and reuse in other parts of the
    compiler.
    
    Test Plan: ./validate
    
    Reviewers: austin, bgamari
    
    Reviewed By: bgamari
    
    Subscribers: thomie, mpickering
    
    Differential Revision: https://phabricator.haskell.org/D1461


>---------------------------------------------------------------

afbd30b6cc486378dd556f738a5337e126bf65a7
 compiler/parser/Parser.y    |  2 +-
 compiler/parser/RdrHsSyn.hs | 20 +++++++++-----------
 2 files changed, 10 insertions(+), 12 deletions(-)

diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 479fc28..40481e5 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -1874,7 +1874,7 @@ gadt_constr :: { LConDecl RdrName }
     -- see Note [Difference in parsing GADT and data constructors]
     -- Returns a list because of:   C,D :: ty
         : con_list '::' sigtype
-                {% do { (anns,gadtDecl) <- mkGadtDecl (unLoc $1) $3
+                {% do { let { (anns, gadtDecl) = mkGadtDecl (unLoc $1) $3 }
                       ; ams (sLL $1 $> gadtDecl)
                             (mj AnnDcolon $2:anns) } }
 
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index 2a5faff..f804e44 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -498,29 +498,27 @@ mkSimpleConDecl name qvars cxt details
 
 mkGadtDecl :: [Located RdrName]
            -> LHsType RdrName     -- Always a HsForAllTy
-           -> P ([AddAnn], ConDecl RdrName)
-mkGadtDecl names (L l ty) = do
-  let
-    (anns,ty') = flattenHsForAllTyKeepAnns ty
-  gadt <- mkGadtDecl' names (L l ty')
-  return (anns,gadt)
+           -> ([AddAnn], ConDecl RdrName)
+mkGadtDecl names (L l ty) =
+  let (anns, ty') = flattenHsForAllTyKeepAnns ty
+      gadt        = mkGadtDecl' names (L l ty')
+  in (anns, gadt)
 
 mkGadtDecl' :: [Located RdrName]
-           -> LHsType RdrName     -- Always a HsForAllTy
-           -> P (ConDecl RdrName)
-
+            ->  LHsType RdrName     -- Always a HsForAllTy
+            -> (ConDecl RdrName)
 -- We allow C,D :: ty
 -- and expand it as if it had been
 --    C :: ty; D :: ty
 -- (Just like type signatures in general.)
 mkGadtDecl' names (L ls (HsForAllTy imp _ qvars cxt tau))
-  = return $ mk_gadt_con names
+  = mk_gadt_con names
   where
     (details, res_ty)           -- See Note [Sorting out the result type]
       = case tau of
           L _ (HsFunTy (L l (HsRecTy flds)) res_ty)
                                             -> (RecCon (L l flds), res_ty)
-          _other                                    -> (PrefixCon [], tau)
+          _other                            -> (PrefixCon [], tau)
 
     mk_gadt_con names
        = ConDecl { con_names    = names



More information about the ghc-commits mailing list