Treating a String as a Haskell Program - haskell

As a small part of a larger University project, I need to write what is essentially an extremely crude IDE. The idea is to to take input from a gtk text box, treat that string as if it is in a .hs file, and evaluate a function within it.
My main approach has been to use the GHC API to compile and evaluate a test function. I had already managed to get a toy example working for compiling from a .hs file. GHC's Target data type had an optional constructor for getting a target from a StringBuffer, so I decided to try and alter my code to get it to work from a String Buffer:
compileText :: SourceView -> IO ()
compileText tview = do
txtBuff <- textViewGetBuffer tview
startIt <- textBufferGetStartIter txtBuff
endIt <- textBufferGetEndIter txtBuff
compTime <- getClockTime
srcString <- textBufferGetText txtBuff startIt endIt False
defaultErrorHandler defaultLogAction $ do
func <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
addTarget $ haskellFileFromText srcString compTime
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
m <- findModule (mkModuleName "Test") Nothing
setContext [IIModule m]
value <- compileExpr ("Test.print")
do let value' = (unsafeCoerce value) :: String -> IO ()
return value'
func "Hello"
return ()
haskellFileFromText :: String -> ClockTime -> GHC.Target
haskellFileFromText codeStr cTime = GHC.Target (TargetModule (mkModuleName "Test")) False (Just ((stringToStringBuffer codeStr), cTime))
The following code being in the text box at the time:
module Test (Test.print) where
print :: String -> IO ()
print x = putStrLn x
However, this does not seem to work. I get the error:
textEdit: panic! (the 'impossible' happened)
(GHC version 7.4.1 for x86_64-unknown-linux):
Could not find module `Test'
Use -v to see a list of the files searched for.
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
What am I doing wrong? I feel I am crucially misunderstanding something about the way this code works.
An alternative to this method which has been suggested to me is to use something like hint or mueval to evaluate the text in the textbox. This would appear to work fine if i simply want to evaluate a single function in isolation, but would this scale if I wanted to evaluate a function which depended on the context of running 4 other functions defined within the same source file?

As C.A. McCann notes, hint does lots of this work for you. It's a wrapper around the GHC api, not just a standalone evaluator like mueval.
Even if it is missing something you need, it will be far easier to learn from it and extend it than start from scratch.

Related

Haskell: Can a function be compiled?

Consider a simple Haskell Brainf*ck interpreter. Just look at the interpret function.
import Prelude hiding (Either(..))
import Control.Monad
import Data.Char (ord, chr)
-- function in question
interpret :: String -> IO ()
interpret strprog = let (prog, []) = parse strprog
in execBF prog
interpretFile :: FilePath -> IO ()
interpretFile fp = readFile fp >>= interpret
type BF = [BFInstr]
data BFInstr = Left | Right | Inc | Dec | Input | Output | Loop BF
type Tape = ([Integer], [Integer])
emptyTape = (repeat 0, repeat 0)
execBFTape :: Tape -> BF -> IO Tape
execBFTape = foldM doBF
execBF :: BF -> IO ()
execBF prog = do
execBFTape emptyTape prog
return ()
doBF :: Tape -> BFInstr -> IO Tape
doBF ((x:lefts), rights) Left = return (lefts, x:rights)
doBF (lefts, (x:rights)) Right = return (x:lefts, rights)
doBF (left, (x:rights)) Inc = return (left, (x+1):rights)
doBF (left, (x:rights)) Dec = return (left, (x-1):rights)
doBF (left, (_:rights)) Input = getChar >>= \c -> return (left, fromIntegral (ord c):rights)
doBF t#(_, (x: _)) Output = putChar (chr (fromIntegral x)) >> return t
doBF t#(left, (x: _)) (Loop bf) = if x == 0
then return t
else do t' <- execBFTape t bf
doBF t' (Loop bf)
simpleCommands = [('<', Left),
('>', Right),
(',', Input),
('.', Output),
('+', Inc),
('-', Dec)]
parse :: String -> (BF, String)
parse [] = ([], [])
parse (char:prog) = case lookup char simpleCommands of
Just command -> let (rest, prog') = parse prog
in (command : rest, prog')
Nothing ->
case char of
']' -> ([], prog)
'[' -> let (loop, prog') = parse prog
(rest, prog'') = parse prog'
in (Loop loop:rest, prog'')
_ -> parse prog
So I have a function applied like interpret "[->+<]". This gives me an IO () monadic action which executes the given program. It has the right type to be a main of some program.
Let's say I would like to have this action compiled to an executable, that is, I would like to generate an executable file with the result of interpret ... to be the main function. Of course, this executable would have to contain the GHC runtime system (for infinite lists, integer arithmetic etc.).
Questions:
It is my opinion that it is not possible at all to just take the monadic action and save it to be a new file. Is this true?
How could one go about reaching a comparable solution? Do the GHC Api and hint help?
EDIT
Sorry, I oversimplified in the original question. Of course, I can just write a file like this:
main = interpret "..."
But this is not what we usually do when we try to compile something, so consider interpretFile :: FilePath -> IO () instead. Let the BF program be saved in a file (helloworld.bf).
How would I go about creating an executable which executes the contents of helloworld.bf without actually needing the file?
$ ./MyBfCompiler helloworld.bf -o helloworld
The answer is basically no.
There are many ways to construct IO values:
Built in functions like putStrLn
Monad operations like return or >>=
Once you have an IO value there are three ways to break it down:
Set main equal to the value
unsafePerformIO
As the return value of an exported C function
All of these break down into converting an IO a into an a. There is no other way to inspect it to see what it does.
Similarly the only thing you can do with functions is put them in variables or call them (or convert them to C function pointers).
There is no sane way to otherwise inspect a function.
One thing you could do which isn’t compiling but is linking is to have your interpreter main function run on some external c string, build that into a static object, and then your “compiler” could make a new object with this C string of the program in it and link that to what you already have.
There is this theory of partial evaluation that says that if you do partial evaluation of a partial evaluator applied to an interpreter applied to some input then what you get is a compiler but ghc is not a sufficiently advanced partial evaluator.
I’m not sure whether you’re asking how you write a compiler that can take as its input a file such as helloworld.bf, or how you compile a Haskell program that runs helloworld.bf.
In the former case, you would want something a little more fleshed out than this:
import System.Environment (getArgs)
main :: IO ()
main = do
(_:fileName:_) <- getArgs
source <- readFile fileName
interpret source
interpret :: String -> IO ()
interpret = undefined -- You can fill in this piddly little detail yourself.
If you want the latter, there are a few different options. First, you can store the contents of your *.bf file in a string constant (or bettter yet, a Text or strict ByteString), and pass that to your interpreter function. I’d be surprised if GHC is optimistic enough to fully inline and expand that call at compile time, but in principle a Haskell compiler could.
The second is to turn Brainfuck into a domain-specific language with operators you define, so that you can actually write something like
interpret [^<,^+,^>,^.]
If you define (^<) and the other operators, the Brainfuck commands will compile to bytecode representing the Brainfuck program.
In this case, there isn’t an obvious benefit over the first approach, but with a more structured language, you can do an optimization pass, compile the source to stack-based bytecode more suitable for an interpreter to execute, or generate a more complex AST.
You might also express this idea as
interpret
(^< ^+ ^> ^.)
input
Here, if the Brainfuck commands are higher-order functions with right-to-left precedence, and interpret bf input = (bf begin) input, the Brainfuck code would simply compile to a function that the interpreter calls. This has the best chance of being turned into fast native code.
Previous Answer
In certain cases, a compiler can inline a function call (there are pragmas in GHC to tell it to do this). The compiler is also more likely to do what you want if you name the closure, such as:
main = interpret foo
In GHC, you can give the compiler a hint by adding
{-# INLINE main #-}
or even
{-# INLINE interpret #-}
You can check what code GHC generated by compiling the module with -S and looking through the source.

Haskell: Interact use causing error

I'm trying to use the interact function, but I'm having an issue with the following code:
main::IO()
main = interact test
test :: String -> String
test [] = show 0
test a = show 3
I'm using EclipseFP and taking one input it seems like there is an error. Trying to run main again leads to a:
*** Exception: <stdin>: hGetContents: illegal operation (handle is closed)
I'm not sure why this is not working, the type of test is String -> String and show is Show a => a -> String, so it seems like it should be a valid input for interact.
EDIT/UPDATE
I've tried the following and it works fine. How does the use of unlines and lines cause interact to work as expected?
main::IO()
main = interact respondPalindromes
respondPalindromes :: String -> String
respondPalindromes =
unlines .
map (\xs -> if isPal xs then "palindrome" else "not a palindrome") .
lines
isPal :: String -> Bool
isPal xs = xs == reverse xs
GHCi and Unsafe I/O
You can reduce this problem (the exception) to:
main = getContents >> return ()
(interact calls getContents)
The problem is that stdin (getContents is really hGetContents stdin) remains evaluated in GHCi in-between calls to main. If you look up stdin, it's implemented as:
stdin :: Handle
stdin = unsafePerformIO $ ...
To see why this is a problem, you could load this into GHCi:
import System.IO.Unsafe
f :: ()
f = unsafePerformIO $ putStrLn "Hi!"
Then, in GHCi:
*Main> f
Hi!
()
*Main> f
()
Since we've used unsafePerformIO and told the compiler that f is a pure function, it thinks it doesn't need to evaluate it a second time. In the case of stdin, all of the initialization on the handle isn't run a second time and it's still in a semi-closed state (which hGetContents puts it in), which causes the exception. So I think that GHCi is "correct" in this case and the problem lies in the definition of stdin which is a practical convenience for compiled programs that will just evaluate stdin once.
Interact and Lazy I/O
As for why interact quits after a single line of input while the unlines . lines version continues, let's try reducing that as well:
main :: IO ()
main = interact (const "response\n")
If you test the above version, interact won't even wait for input before printing response. Why? Here's the source for interact (in GHC):
interact f = do s <- getContents
putStr (f s)
getContents is lazy I/O, and since f in this case doesn't need s, nothing is read from stdin.
If you change your test program to:
main :: IO ()
main = interact test
test :: String -> String
test [] = show 0
test a = show a
you should notice different behavior. And that suggests that in your original version (test a = show 3), the compiler is smart enough to realize that it only needs enough input to determine if the string read is empty or not (because if it's not empty, it doesn't need to know what a is, it just needs to print "3"). Since the input is presumably line-buffered on a terminal, it reads up until you press the return key.

Haskell GHC Dynamic Compliation Only works on first compile

Following the GHC tutorial posted here and alterations to this code following the advice in a previous stack overflow question I asked, I have created a program which is able to compile and run a module in Test.hs with a function print to print a string to the screen:
import GHC
import GHC.Paths
import DynFlags
import Unsafe.Coerce
main :: IO ()
main =
defaultErrorHandler defaultLogAction $ do
func <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
target <- guessTarget "Test.hs" Nothing
addTarget target
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
m <- findModule (mkModuleName "Test") Nothing
setContext [IIModule m]
value <- compileExpr ("Test.print")
do let value' = (unsafeCoerce value) :: String -> IO ()
return value'
func "Hello"
return ()
The problem with this code, as noted in the comments, is that it only seems to work the first time you run it (When Test.hs has not yet been complied). If you attempt to run the code a second time, the following error appears:
mkTopLevEnv: not interpreted main:Test
I believe this has something to do with the fact that the code has already been compiled. If I delete the .hi and .o files and run the program again, the program runs correctly with the correct output. What am I missing? I am currently using ghc version 7.4.1
(Note: I have tried looking through the GHC API but could not find any references to mkTopLevEnv)
Simon Marlow suggests here that replacing
guessTarget "Test.hs" Nothing
with
guessTarget "*Test.hs" Nothing
should avoid the error you're getting, on the grounds that it tells GHC not to load the .o file.
See the whole thread on a page via nabble
Of course, you could delete the .hi and .o files each time, but that's an ugly workaround.

How to initialize a monad and then use in a function many times in Haskell

Most of this is straight from the hint example. What I'd like to do is initialize the interpreter with modules and imports and such and keep it around somehow. Later on (user events, or whatever), I want to be able to call a function with that initialized state and interpret an expression many times. So at the --split here location in the code, I want to have the code above in init, and the code below that in a new function that takes an expression and interprets it.
module Main where
import Language.Haskell.Interpreter
import Test.SomeModule
main :: IO ()
main = do r <- runInterpreter testHint
case r of
Left err -> printInterpreterError err
Right () -> putStrLn "Done."
-- Right here I want to do something like the following
-- but how do I do testInterpret thing so it uses the
-- pre-initialized interpreter?
case (testInterpret "expression one")
Left err -> printInterpreterError err
Right () -> putStrLn "Done."
case (testInterpret "expression two")
Left err -> printInterpreterError err
Right () -> putStrLn "Done."
testHint :: Interpreter ()
testHint =
do
loadModules ["src/Test/SomeModule.hs"]
setImportsQ [("Prelude", Nothing), ("Test.SomeModule", Just "SM")]
say "loaded"
-- Split here, so what I want is something like this though I know
-- this doesn't make sense as is:
-- testExpr = Interpreter () -> String -> Interpreter ()
-- testExpr hintmonad expr = interpret expr
let expr1 = "let p1o1 = SM.exported undefined; p1o2 = SM.exported undefined; in p1o1"
say $ "e.g. typeOf " ++ expr1
say =<< typeOf expr1
say :: String -> Interpreter ()
say = liftIO . putStrLn
printInterpreterError :: InterpreterError -> IO ()
printInterpreterError e = putStrLn $ "Ups... " ++ (show e)
I'm having trouble understanding your question. Also I am not very familiar with hint. But I'll give it a go.
As far as I can tell, the Interpreter monad is just a simple state wrapper around IO -- it only exists so that you can say eg. setImportsQ [...] and have subsequent computations depend on the "settings" that were modified by that function. So basically you want to share the monadic context of multiple computations. The only way to do that is by staying within the monad -- by building a single computation in Interpreter and running it once. You can't have a "global variable" that escapes and reuses runInterpreter.
Fortunately, Interpreter is an instance of MonadIO, which means you can interleave IO computations and Interpreter computations using liftIO :: IO a -> Interpreter a. Basically you are thinking inside-out (an extremely common mistake for learners of Haskell). Instead of using a function in IO that runs code in your interpreter, use a function in Interpreter that runs code in IO (namely liftIO). So eg.
main = runInterpreter $ do
testHint
expr1 <- liftIO getLine
r1 <- interpret "" expr1
case r1 of
...
expr2 <- liftIO getLine
r2 <- interpret "" expr2
case r2 of
...
And you can easily pull that latter code out into a function if you need to, using the beauty of referential transparency! Just pull it straight out.
runSession :: Interpreter ()
runSession = do
expr1 <- liftIO getLine
r1 <- interpret "" expr1
case interpret expr1 of
...
main = runInterpreter $ do
testHint
runSession
Does that make sense? Your whole program is an Interpreter computation, and only at the last minute do you pull it out into IO.
(That does not mean that every function you write should be in the Interpreter monad. Far from it! As usual, use Interpreter around the edges of your program and keep the core purely functional. Interpreter is the new IO).
If I understand correctly, you want to initialize the compiler once, and run multiple queries, possibly interactively.
There are two main approaches:
lift IO actions into your Interpreter context (see luqui's answer).
use lazy IO to smuggle a stream of data in and out of your program.
I'll describe the second option.
By the magic of lazy IO, you can pass testHint a lazy stream of input, then loop in the body of testHint, interpreting many queries interactively:
main = do
ls <- getContents -- a stream of future input
r <- runInterpreter (testHint (lines input))
case r of
Left err -> printInterpreterError err
Right () -> putStrLn "Done."
testHint input = do
loadModules ["src/Test/SomeModule.hs"]
setImportsQ [("Prelude", Nothing), ("Test.SomeModule", Just "SM")]
say "loaded"
-- loop over the stream of input, interpreting commands
let go (":quit":es) = return ()
(e:es) = do say =<< typeOf e
go es
go
The go function has access to the closed-over environment of the initialized interpreter, so feeding it events will obviously run in the scope of that once-initialized interpreter.
An alternative method would be to extract the interpreter state from the monad, but I'm not sure that is possible in GHC (it would require GHC not to be in the IO monad fundamentally).

Evaluation of Haskell Statements/Expressions using GHC API

For a tool I'm writing ( http://hackage.haskell.org/package/explore ) I need a way to read haskell function definitions at run-time, apply them to values from my tool and retrieve the results of their application.
Can anyone give me a very basic example using GHC (6.10.4 or 6.12.1) API?
example function definition to be read from a file at run-time:
f x = 10**(4/1102*x - 1)
expected program output
--mapM_ print $ map f [428, 410, 389]
3.577165388142748
3.077536885227335
2.5821307011665815
!!UPDATE!!
I posted a quick answer but it creates an object file in the directory of execution, any tips to avoid this and avoid all file IO is most welcome. I want to also see a version that does everything in memory: user provides the function definition in a GUI for example and the compilation / evaluation does not create any object files.
Use hint. It's a GHCi-like wrapper around the GHC API that is not very difficult to use.
If you want an example of its use, I used it in my Yogurt project.
adapted from: http://www.bluishcoder.co.nz/2008/11/dynamic-compilation-and-loading-of.html
f.hs:
module Func (Func.f) where
f :: Double -> Double
f x = 10**(4/1102*x - 1)
main.hs:
import GHC
import GHC.Paths
import DynFlags
import Unsafe.Coerce
import Control.Monad
main :: IO ()
main =
defaultErrorHandler defaultDynFlags $ do
func <- runGhc (Just libdir) $ do
dflags <- getSessionDynFlags
setSessionDynFlags dflags
target <- guessTarget "f.hs" Nothing
addTarget target
r <- load LoadAllTargets
case r of
Failed -> error "Compilation failed"
Succeeded -> do
m <- findModule (mkModuleName "Func") Nothing
setContext [] [m]
value <- compileExpr ("Func.f")
do let value' = (unsafeCoerce value) :: Double -> Double
return value'
let f = func
mapM_ print $ map f [428, 410, 389]
return ()
Nice work getting the API going. I can tell you a little bit about how the code generator works.
GHC uses the system assembler to create a .o file. If there is not an option available to get GHC to clean up after itself, then you should file a feature request against the API, using the bug tracker at http://hackage.haskell.org/trac/ghc/newticket?type=feature+request. In order to file the request, you will need to register an account.
Using the standard code generator, you will not be able to avoid file I/O entirely, just because GHC delegates the work of creating relocatable object code to the assembler. There is an experimental back end based on LLVM that might be able to do everything in memory, but I would be surprised if it is available in anything earlier than 6.13. However it could be worth asking on the GHC developers' list.

Resources