[Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Stefan Klinger
Hello!

Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could
use IO as inner monad, and perform IO operations during parsing.

But I failed. Monad transformers still bend my mind. My problem: I
don't see a function to actually lift the IO operation into the
ParsecT. It should be something like

  lift :: IO a - ParsecT s u IO a

The following is a toy example, I just could not make something
smaller: Let's parse command line arguments (tokens are Strings), and
execute them while parsing.

 import Text.Parsec.Prim
 import Text.Parsec.Pos
 import Text.Parsec
 import System.Environment ( getArgs )


Command line interface parser (Clip) type: Inner monad IO, user state
u, tokens are Strings, returns something typed a.

 type Clip u a = ParsecT [String] u IO a


Source code position for command line arguments: The line is always 1,
column n represents the n-th command line argument.

 nextPos p _ _ = incSourceColumn p 1


Two primitive parsers, one for flags (with a dash) and one for other
arguments:

clipFlag x accepts the command line flag -x, and returns x.

 clipFlag :: String - Clip u String
 clipFlag x
 = tokenPrim
   id
   nextPos
   (\y - if '-':x == y then Just x else Nothing)


clipValue accepts any command line argument that does not tart with a
dash '-'.

 clipValue :: Clip u String
 clipValue
 = tokenPrim id nextPos test
 where
 test ('-':_) = Nothing
 test other = Just other



Now the test program:

Load files given on the command line, and sum up their word count,
until -p is given. -p prints the current word count and sets the
counter to zero. Further files may be processed then. At the end, show
the sum of all word counts.

Example: foo has 12 words, bar has 34 words:

  main foo -p bar -p foo bar -p
  Counted 12 words, reset counter.
  Counted 34 words, reset counter.
  Counted 46 words, reset counter.
  Grand total: 92


 type CurrentCount = Int -- the user state used with Clip/ParsecT.


root implements the command line grammar (filename+ -p)* and
returns the sum of all word counts.

 root :: Clip CurrentCount Int
 root
 = do ns - many (many1 loadFile  printSize)
  eof
  return $ sum ns


Interprets each non-flag on the command line as filename, loads it,
counts its words, and adds the count to the state.

 loadFile :: Clip CurrentCount ()
 loadFile
 = do -- expect a filename
  filename - clipValue

  -- load the file: IO
  content - lift $ readFile filename

  -- add wordcount to state
  modifyState ((+) (length $ words content))


If -p shows up on the command line, print accumulated count, reset
counter to cero and return count for grand-total calculation.

 printSize :: Clip CurrentCount Int
 printSize
 = do -- expect flag -p
  clipFlag p

  -- print current word count: IO
  n - getState
  lift . putStrLn $ Counted ++show n++ words, reset counter.

  -- reset user state to zero, return word count for grand total
  putState 0
  return n


main just runs the root parser on the command line arguments and
checks the result.

 main
 = do result - getArgs = runParserT root 0 command line
  case result of
Left err - error $ show err
Right n - putStrLn $ Grand total: ++show n


So where is the lift function? Does it exist? Here, I need your help.

 lift :: IO a - ParsecT s u IO a
 lift = undefined


Any comments are appreciated.

Thank you!
Stefan


[1] 
http://hackage.haskell.org/packages/archive/parsec/3.0.0/doc/html/Text-Parsec-Prim.html#t:ParsecT


-- 
Stefan Klinger  o/klettern
/\/  bis zum
send plaintext only - max size 32kB - no spam \   Abfallen
http://stefan-klinger.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Gregory Collins
Stefan Klinger all-li...@stefan-klinger.de writes:

 Hello!

 Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could
 use IO as inner monad, and perform IO operations during parsing.

 But I failed. Monad transformers still bend my mind. My problem: I
 don't see a function to actually lift the IO operation into the
 ParsecT. It should be something like

   lift :: IO a - ParsecT s u IO a

ParsecT has a MonadIO instance:

class Monad m = MonadIO m where
liftIO :: IO a - m a

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 10:37 AM, Stefan Klinger
all-li...@stefan-klinger.de wrote:
 Hello!

 Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could
 use IO as inner monad, and perform IO operations during parsing.

 But I failed. Monad transformers still bend my mind. My problem: I
 don't see a function to actually lift the IO operation into the
 ParsecT. It should be something like

  lift :: IO a - ParsecT s u IO a

That operation, with that name, and (a generalization of) that type,
is *the* method of the MonadTrans class.  Essentially the presence of
that operation is the definition of what it means to be a monad
transformer.

 The following is a toy example, I just could not make something
 smaller: Let's parse command line arguments (tokens are Strings), and
 execute them while parsing.

 import Text.Parsec.Prim
 import Text.Parsec.Pos
 import Text.Parsec
 import System.Environment ( getArgs )


 Command line interface parser (Clip) type: Inner monad IO, user state
 u, tokens are Strings, returns something typed a.

 type Clip u a = ParsecT [String] u IO a


 Source code position for command line arguments: The line is always 1,
 column n represents the n-th command line argument.

 nextPos p _ _ = incSourceColumn p 1


 Two primitive parsers, one for flags (with a dash) and one for other
 arguments:

 clipFlag x accepts the command line flag -x, and returns x.

 clipFlag :: String - Clip u String
 clipFlag x
     = tokenPrim
       id
       nextPos
       (\y - if '-':x == y then Just x else Nothing)


 clipValue accepts any command line argument that does not tart with a
 dash '-'.

 clipValue :: Clip u String
 clipValue
     = tokenPrim id nextPos test
     where
     test ('-':_) = Nothing
     test other = Just other



 Now the test program:

 Load files given on the command line, and sum up their word count,
 until -p is given. -p prints the current word count and sets the
 counter to zero. Further files may be processed then. At the end, show
 the sum of all word counts.

 Example: foo has 12 words, bar has 34 words:

  main foo -p bar -p foo bar -p
  Counted 12 words, reset counter.
  Counted 34 words, reset counter.
  Counted 46 words, reset counter.
  Grand total: 92


 type CurrentCount = Int -- the user state used with Clip/ParsecT.


 root implements the command line grammar (filename+ -p)* and
 returns the sum of all word counts.

 root :: Clip CurrentCount Int
 root
     = do ns - many (many1 loadFile  printSize)
          eof
          return $ sum ns


 Interprets each non-flag on the command line as filename, loads it,
 counts its words, and adds the count to the state.

 loadFile :: Clip CurrentCount ()
 loadFile
     = do -- expect a filename
          filename - clipValue

          -- load the file: IO
          content - lift $ readFile filename

          -- add wordcount to state
          modifyState ((+) (length $ words content))


 If -p shows up on the command line, print accumulated count, reset
 counter to cero and return count for grand-total calculation.

 printSize :: Clip CurrentCount Int
 printSize
     = do -- expect flag -p
          clipFlag p

          -- print current word count: IO
          n - getState
          lift . putStrLn $ Counted ++show n++ words, reset counter.

          -- reset user state to zero, return word count for grand total
          putState 0
          return n


 main just runs the root parser on the command line arguments and
 checks the result.

 main
     = do result - getArgs = runParserT root 0 command line
          case result of
            Left err - error $ show err
            Right n - putStrLn $ Grand total: ++show n


 So where is the lift function? Does it exist? Here, I need your help.

 lift :: IO a - ParsecT s u IO a
 lift = undefined


 Any comments are appreciated.

 Thank you!
 Stefan

 
 [1] 
 http://hackage.haskell.org/packages/archive/parsec/3.0.0/doc/html/Text-Parsec-Prim.html#t:ParsecT


 --
 Stefan Klinger                                      o/klettern
                                                    /\/  bis zum
 send plaintext only - max size 32kB - no spam         \   Abfallen
 http://stefan-klinger.de
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Stefan Klinger
On 18 March 2010, Gregory Collins wrote with possible deletions:
 ParsecT has a MonadIO instance:
 
 class Monad m = MonadIO m where
 liftIO :: IO a - m a

Thank you! I didn't see this. Great!

Kind regards,
Stefan


-- 
Stefan Klinger  o/klettern
/\/  bis zum
send plaintext only - max size 32kB - no spam \   Abfallen
http://stefan-klinger.de
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Job Vranish
Hoogle is a great tool for finding haskell functions:

http://www.haskell.org/hoogle/

You can punch in the type of a function you want and it will give you a list
of functions that might do what you need.
Generalizing the types a bit usually helps. Searching for either  m a - n m
a   or   IO a - m a   would give you 'lift' and 'liftIO' as one of the top
results.

- Job

On Thu, Mar 18, 2010 at 1:58 PM, Stefan Klinger all-li...@stefan-klinger.de
 wrote:

 On 18 March 2010, Gregory Collins wrote with possible deletions:
  ParsecT has a MonadIO instance:
 
  class Monad m = MonadIO m where
  liftIO :: IO a - m a

 Thank you! I didn't see this. Great!

 Kind regards,
 Stefan


 --
 Stefan Klinger  o/klettern
/\/  bis zum
 send plaintext only - max size 32kB - no spam \   Abfallen
 http://stefan-klinger.de
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Andrew Coppin

Job Vranish wrote:

Hoogle is a great tool for finding haskell functions:

http://www.haskell.org/hoogle/

You can punch in the type of a function you want and it will give you 
a list of functions that might do what you need.
Generalizing the types a bit usually helps. Searching for either  m a 
- n m a   or   IO a - m a   would give you 'lift' and 'liftIO' as 
one of the top results.


Is there a tool anywhere which can figure out how to construct a 
function with a specific type signature? Hoogle works if the thing you 
seek is a single function, but not so much if you need to throw several 
functions together.


(For example, the signature x - [x - y] - [y] can be implemented by 
\ x - map ($ x), but this is initially non-obvious.)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Stephen Tetley
On 18 March 2010 21:34, Andrew Coppin andrewcop...@btinternet.com wrote:

 Is there a tool anywhere which can figure out how to construct a function
 with a specific type signature? Hoogle works if the thing you seek is a
 single function, but not so much if you need to throw several functions
 together.



Hi Andrew

There is Lennart Augustsson's Djinn  Oleg Kiselyov's 'de-typechecker'


http://hackage.haskell.org/package/djinn

Reversing Haskell typechecker: converting from undefined to defined
http://okmij.org/ftp/Haskell/types.html

Clean has something similar to generate test functions for GAST -
Clean's equivalent to QuickCheck.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe