:def and ghci command output

Claus Reinke claus.reinke at talk21.com
Fri Aug 31 07:57:58 EDT 2007


>> i'd like to run a ghci command, and capture its ouput as a haskell 
>> String, eg, to pass it on to another ghci command, or to a haskell 
>> function.
> 
> It would be possible, but needs a bit of refactoring because all the output 
> is currently just sent to stdout.  I'd go with something like your second 
> option, but perhaps add some new syntax:

i think i've found a less disruptive approach. replace

  io (putStrLn output)

with 

  enqueueCommands ["let output = "++show output,"putStrLn output"]

there's not always such a nice output/io separation for many commands,
but we could introduce this a few commands at a time, following demand.

    :b Data.List
    ..
    putStrLn $ unlines $ filter (\l->"Bool" `elem` words l) $ lines output

    all :: (a -> Bool) -> [a] -> Bool
    and :: [Bool] -> Bool
    any :: (a -> Bool) -> [a] -> Bool
    elem :: (Eq a) => a -> [a] -> Bool
    notElem :: (Eq a) => a -> [a] -> Bool
    null :: [a] -> Bool
    or :: [Bool] -> Bool
    isPrefixOf :: (Eq a) => [a] -> [a] -> Bool
    isSuffixOf :: (Eq a) => [a] -> [a] -> Bool
    isInfixOf :: (Eq a) => [a] -> [a] -> Bool

what worries me is that ghci's standard "it" bindings do not seem to be
done this way at all, but are burried somewhere in the type-checking?

also, it might be nice to introduce a GHCi qualifier, so that we could
refer to GHCi.ouput and GHCi.it, in case of ambiguities?

claus

oh, and while i'm at it, the pretty-printing is rather less than optimal:-)

    zip7 ::
      [a]
      -> [b]
      -> [c]
      -> [d]
      -> [e]
      -> [f]
      -> [g]
      -> [(a, b, c, d, e, f, g)]



More information about the Glasgow-haskell-users mailing list