Skip to content

Commit

Permalink
Tidy parser
Browse files Browse the repository at this point in the history
Ignore-this: c4abd311a54eb26267a9096db0be68b8

darcs-hash:20111020101838-e29d1-604b7a6d8741562d03f0152c9bc199eb9ca6221d.gz
  • Loading branch information
adamgundry committed Oct 20, 2011
1 parent ea02b74 commit b63780a
Show file tree
Hide file tree
Showing 2 changed files with 7 additions and 8 deletions.
2 changes: 1 addition & 1 deletion Main.lhs
Expand Up @@ -27,7 +27,7 @@
> modHeader (Just m) = "module " ++ m ++ " where\n"

> preprocess :: String -> String -> Either String String
> preprocess fn s = case parse program fn s of
> preprocess fn s = case parseProgram fn s of
> Right (p, mn) -> case runCheckProg p of
> Right (p', st) -> case runStateT (eraseProg p') st of
> Right (p'', st) -> Right $ modHeader mn ++ show (prettyProgram p'')
Expand Down
13 changes: 6 additions & 7 deletions Parser.lhs
@@ -1,10 +1,10 @@
> module Parser where
> module Parser (parseProgram) where

> import Control.Applicative
> import Control.Monad
> import Data.Char

> import Text.ParserCombinators.Parsec hiding (optional, many, (<|>))
> import Text.ParserCombinators.Parsec hiding (parse, optional, many, (<|>))
> import Text.ParserCombinators.Parsec.Expr
> import Text.ParserCombinators.Parsec.Language
> import qualified Text.ParserCombinators.Parsec.Token as T
Expand All @@ -17,12 +17,11 @@
> import Kit
> import Kind hiding (kind)

> parseProgram = I.parse program

> parse = I.parse
> def = haskellDef

> toyDef = haskellDef

> lexer = T.makeTokenParser toyDef
> lexer = T.makeTokenParser def

> identifier = IT.identifier lexer
> reserved = IT.reserved lexer
Expand Down Expand Up @@ -50,7 +49,7 @@


> specialOp s = try $
> string s >> notFollowedBy (opLetter toyDef) >> whiteSpace
> string s >> notFollowedBy (opLetter def) >> whiteSpace


> doubleColon = reservedOp "::"
Expand Down

0 comments on commit b63780a

Please sign in to comment.