I am currently working on a haskell program which takes a users input from a text box, then compiles and loads it using the System.Plugins library in order to extract a picture to draw to the screen. The user can edit the code in the text box, then reload their new image by clicking a compile button. Here is the code which is fired when the compile button is clicked:
compileText :: SourceView -> SOE.Window -> IO ()
compileText tview w = do
txtBuff <- textViewGetBuffer tview
startIt <- textBufferGetStartIter txtBuff
endIt <- textBufferGetEndIter txtBuff
compTime <- getClockTime
srcString <- textBufferGetByteString txtBuff startIt endIt False
BS.writeFile "Test.hs" srcString
mkStat <- make "Test.hs" []
case mkStat of
MakeSuccess cd fp -> print fp
MakeFailure (er1:er2:errs) -> error er2
loadResult <- getModule
case loadResult of
Right (md, pic) -> do
runGraphics $ do
draw3 "gtk test" pic w
unload md
Left errors -> print errors
return ()
getModule :: IO (Either [String] (Module, Picture))
getModule = do
mv <- load "Test.o" ["."] [] "pic"
case mv of
LoadFailure messages -> return (Left messages)
LoadSuccess x y -> return (Right (x, y))
And here is some example code that the user has entered into the text box:
module Test where
import Picture
r1,r2,r3,r4 :: Region
r1 = Shape(Rectangle 2 1)
r2 = Shape(Ellipse 2 1.5)
r3 = Shape(RtTriangle 3 2)
r4 = Shape(Polygon [(-2.5, 2.5), (-3.0,0), (-1.7,-1.0), (-1.1,0.2),(-1.5,2.0)])
p1,p2,p3,p4 :: Picture
p1 = Region Red r1
p2 = Region Green r2
p3 = Region Blue r3
p4 = Region Yellow r4
pics :: Picture
pics = foldl Over EmptyPic [p1,p2,p3,p4]
This all works as intended provided the user writes code that correctly compiles and loads each time. When the user writes a piece of code which fails to load however (The example i have been playing with is changing 'pic' to 'pics' so that it cannot find the pic function to load) The intended behaviour is that the program will print the load error to the screen so that the user can presumably correct their code and try clicking the compile button again.
However, what actually happens is that once the program encounters a LoadFailure once, all subsequent attempts at clicking the compile button result in a load failure message, regardless of whether the code is correct or not!
I'm not really sure what is going on under the hood here, but it appears as if the program is keeping some memory of the previous result from evaluation to evaluation. How do I get the behaviour I am looking for?
EDIT: I have tried to isolate the problem by writing a small test case which illustrates the problem I am having without using gtk
import Control.Monad
import System.Time
import System.IO
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BSC
import System.Plugins.Make
import System.Plugins.Load
import System.Eval.Haskell
testCaseCorrect :: String
testCaseCorrect = "module Test where\n printGreeting :: String -> IO ()\n printGreeting greeting = print greeting"
-- This should cause load to fail as it will not be able to find the
-- printGreeting function
testCaseIncorrect :: String
testCaseIncorrect = "module Test where\n printGurting :: String -> IO ()\n printGurting greeting = print greeting"
main :: IO ()
main = do
BS.writeFile "Test.hs" (BSC.pack testCaseCorrect)
mkStat <- make "Test.hs" []
case mkStat of
MakeSuccess cd fp -> print fp
MakeFailure (er1:er2:errs) -> error er2
loadResult <- getModule
case loadResult of
Right (md, greeter) -> do
greeter "Hi there"
unload md
Left errors -> print errors
BS.writeFile "Test.hs" (BSC.pack testCaseIncorrect)
mkStat2 <- make "Test.hs" []
case mkStat2 of
MakeSuccess cd fp -> print fp
MakeFailure (er1:er2:errs) -> error er2
loadResult2 <- getModule
case loadResult2 of
Right (md, greeter) -> do
greeter "Hi there"
unload md
Left errors -> print errors
BS.writeFile "Test.hs" (BSC.pack testCaseCorrect)
mkStat3 <- make "Test.hs" []
case mkStat3 of
MakeSuccess cd fp -> print fp
MakeFailure (er1:er2:errs) -> error er2
loadResult3 <- getModule
case loadResult3 of
Right (md, greeter) -> do
greeter "Hi there"
unload md
Left errors -> print errors
getModule :: IO (Either [String] (Module, String -> IO()))
getModule = do
mv <- load "Test.o" ["."] [] "printGreeting"
case mv of
LoadFailure messages -> return (Left messages)
LoadSuccess x y -> return (Right (x, y))
This code produces the result:
"Test.o"
"Hi there"
"Test.o"
["load: couldn't find symbol <<printGreeting>>"]
"Test.o"
["load: couldn't find symbol <<printGreeting>>"]
I.e it manages to replicate the error
EDIT 2: It seems on some runs of this exact same code It also produces the output:
"Test.o"
"Hi there"
"Test.o"
"Hi there"
"Test.o"
"Hi there"
But I think this may be due to the fact that the consecutive compiles are run so quickly together.
I replicated the problem using my updated version of the plugins library and I isolated three causes.
Firstly, the getModificationTime function used to check if a module needs to be recompiled has insufficient precision (seconds).
Secondly, GHC appears to make the same mistake.
Thirdly, as Don Stewart said, the module needs to be unloaded, which can't be easily done because the API doesn't give you a direct reference to it.
I fixed the third problem in my repository by automatically unloading the module when the symbol lookup fails. The right way to fix the other two is probably to patch upstream.
If you love us? You can donate to us via Paypal or buy me a coffee so we can maintain and grow! Thank you!
Donate Us With