[commit: nofib] master: Fix bitrotted gc nofib code. (12b6903)
git at git.haskell.org
git at git.haskell.org
Wed Sep 10 02:38:11 UTC 2014
Repository : ssh://git@git.haskell.org/nofib
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/12b6903065ea7fedca06ff21e91272ad6fdd0192/nofib
>---------------------------------------------------------------
commit 12b6903065ea7fedca06ff21e91272ad6fdd0192
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date: Tue Sep 9 19:37:39 2014 -0700
Fix bitrotted gc nofib code.
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
>---------------------------------------------------------------
12b6903065ea7fedca06ff21e91272ad6fdd0192
gc/fibheaps/Main.lhs | 1 +
gc/happy/LALR.lhs | 1 +
gc/happy/ParseMonad.lhs | 12 ++++++++++++
gc/happy/ProduceCode.lhs | 1 +
gc/happy/happy.lhs | 2 +-
5 files changed, 16 insertions(+), 1 deletion(-)
diff --git a/gc/fibheaps/Main.lhs b/gc/fibheaps/Main.lhs
index 452ae6e..245335d 100644
--- a/gc/fibheaps/Main.lhs
+++ b/gc/fibheaps/Main.lhs
@@ -50,6 +50,7 @@ first understand binomial queues. See, for example, David King's
"Functional Binomial Queues" from the last Glasgow workshop.
> -- partain
+>{-# LANGUAGE FlexibleContexts #-}
>module Main (main) where
>import Data.Array
>import System.Environment
diff --git a/gc/happy/LALR.lhs b/gc/happy/LALR.lhs
index f8610fb..08a99b3 100644
--- a/gc/happy/LALR.lhs
+++ b/gc/happy/LALR.lhs
@@ -5,6 +5,7 @@ Generation of LALR parsing tables.
(c) 1997-2001 Simon Marlow
-----------------------------------------------------------------------------
+> {-# LANGUAGE FlexibleContexts #-}
> module LALR
> (genActionTable, genGotoTable, genLR0items, precalcClosure0,
> propLookaheads, calcLookaheads, mergeLookaheadInfo, countConflicts,
diff --git a/gc/happy/ParseMonad.lhs b/gc/happy/ParseMonad.lhs
index 9e576a5..4e29e9e 100644
--- a/gc/happy/ParseMonad.lhs
+++ b/gc/happy/ParseMonad.lhs
@@ -5,6 +5,7 @@ The parser monad.
-----------------------------------------------------------------------------
> module ParseMonad where
+> import Control.Monad(ap)
> data ParseResult a = OkP a | FailP String
> newtype P a = P (String -> Int -> ParseResult a)
@@ -13,6 +14,17 @@ The parser monad.
> lineP :: P Int
> lineP = P $ \_ l -> OkP l
+> instance Functor ParseResult where
+> fmap f (OkP a) = OkP (f a)
+> fmap f (FailP e) = FailP e
+
+> instance Functor P where
+> fmap f m = P $ \s l -> fmap f (runP m s l)
+
+> instance Applicative P where
+> pure = return
+> (<*>) = ap
+
> instance Monad P where
> return m = P $ \ _ _ -> OkP m
> m >>= k = P $ \s l -> case runP m s l of
diff --git a/gc/happy/ProduceCode.lhs b/gc/happy/ProduceCode.lhs
index cd1980d..0c0dcc5 100644
--- a/gc/happy/ProduceCode.lhs
+++ b/gc/happy/ProduceCode.lhs
@@ -4,6 +4,7 @@ The code generator.
(c) 1993-2001 Andy Gill, Simon Marlow
-----------------------------------------------------------------------------
+> {-# LANGUAGE FlexibleContexts #-}
> module ProduceCode (produceParser) where
> import Paths_happy ( version )
diff --git a/gc/happy/happy.lhs b/gc/happy/happy.lhs
index 149868d..2d8021d 100644
--- a/gc/happy/happy.lhs
+++ b/gc/happy/happy.lhs
@@ -25,7 +25,7 @@ Path settings auto-generated by Cabal:
> import System.Console.GetOpt
> import Control.Monad ( liftM )
> import System.Environment
-> import System.Exit
+> import System.Exit ( exitWith, ExitCode(ExitSuccess, ExitFailure) )
> import Data.Char
> import System.IO
> import Data.Array( assocs, elems, (!) )
More information about the ghc-commits
mailing list