Skip to content

Instantly share code, notes, and snippets.

@sw17ch
Created March 16, 2012 04:31
Show Gist options
  • Star 8 You must be signed in to star a gist
  • Fork 2 You must be signed in to fork a gist
  • Save sw17ch/2048516 to your computer and use it in GitHub Desktop.
Save sw17ch/2048516 to your computer and use it in GitHub Desktop.
A full example demonstrating the use of the indentation parser provided by the 'indents' package: http://hackage.haskell.org/package/indents
> module Main where
First, import all the needed modules.
> import Text.Parsec hiding (State)
> import Text.Parsec.Indent
> import Control.Monad.State
Next, define our new Parser type. This replaces the Identity monad
with the (State SourcePos) monad.
> type IParser a = ParsecT String () (State SourcePos) a
Now we define our new parse function. This one accepts an IParser
(which we've just defined) instead of a Parser.
> iParse :: IParser a -> SourceName -> String -> Either ParseError a
> iParse aParser source_name input =
> runIndent source_name $ runParserT aParser () source_name input
Define our sample input string. Note: the unlines function joins
strings together with newline characters.
> input_text :: String
> input_text = unlines [
> "listName:",
> " item1",
> " item2",
> " item3"
> ]
Define main. It parses the input text and prints the parsed value. If
there was an error, it prints the error.
> main :: IO ()
> main = do
> case iParse aNamedList "indented_example" input_text of
> Left err -> print err
> Right result -> putStrLn $ "I parsed: " ++ show result
Define a datatype to hold our parsed value.
> data NamedList = NamedList Name [Item]
> deriving (Show)
Define what we mean by 'Name' and 'Item'. In this case, they are both
strings.
> type Name = String
> type Item = String
Define how we parse a NamedList. A Named list is a Name and a list of
Items contained in the NamedList data structure. Read more about the
withBlock function here:
http://hackage.haskell.org/packages/archive/indents/0.3.2/doc/html/Text-Parsec-Indent.html#v:withBlock
> aNamedList :: IParser NamedList
> aNamedList = do
> b <- withBlock NamedList aName anItem
> spaces
> return b
A name is an alpha-numeric string followed by a ':' and some
whitespace.
> aName :: IParser Name
> aName = do
> s <- many1 alphaNum
> _ <- char ':'
> spaces
> return s
An item is an alpha-numeric string followed by some whitespace.
> anItem :: IParser Item
> anItem = do
> i <- many1 alphaNum
> spaces
> return i
Output:
> runhaskell -Wall indented_parsec_example.hs
I parsed: NamedList "listName" ["item1","item2","item3"]
@bergerab
Copy link

Hey sw17ch!

Thanks for this example. It has helped to point me in the right direction for this.

It seems as though the "indent" module has been updated or something and I couldn't get this code to work with the most recent version of Text.Parsec.Indent (0.4.0.0).

I got it to work by changing the type of the IParser to use IndentParser, and use runIndentParser in your iParse function.

type IParser a = IndentParser String () a

iParse :: IParser a -> SourceName -> String -> Either ParseError a
iParse aParser source_name input =
runIndentParser aParser () source_name input

Just leaving this comment for helping my future self/other people.

Thanks for this again.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment