9

After watching a video of a talk by Bret Victor, I was inspired to write a quick hack that was somewhat similar to a development environment he demonstrated in the talk.

Basically the idea is, one has the app running in one window and whenever one saves a change in a source file the program changes.

This works great for small changes except that I can't change the type of the state in my code without shutting down the app and recompiling.

How can I solve the expression problem and have the data type of my state be able to change without causing a recompile?

P.S. Here's the code. I originally didn't want to post because it was really messy and quickly hacked together, but people wanted it so they can get it.

First the display and the idle module, (this was a quick hack so I didn't figure out how to do them as real modules).

Idle.hs

\state -> do
    counter <- readIORef state
    writeIORef state ((counter + 1)`mod`3)
    postRedisplay Nothing

Display.hs

\state -> let
cube w = do 
    renderPrimitive Quads $ do
        vertex $ Vertex3 w w w
        vertex $ Vertex3 w w (-w)
        vertex $ Vertex3 w (-w) (-w)
        vertex $ Vertex3 w (-w) w
        vertex $ Vertex3 w w w
        vertex $ Vertex3 w w (-w)
        vertex $ Vertex3 (-w) w (-w)
        vertex $ Vertex3 (-w) w w
        vertex $ Vertex3 w w w
        vertex $ Vertex3 w (-w) w
        vertex $ Vertex3 (-w) (-w) w
        vertex $ Vertex3 (-w) w w
        vertex $ Vertex3 (-w) w w
        vertex $ Vertex3 (-w) w (-w)
        vertex $ Vertex3 (-w) (-w) (-w)
        vertex $ Vertex3 (-w) (-w) w
        vertex $ Vertex3 w (-w) w
        vertex $ Vertex3 w (-w) (-w)
        vertex $ Vertex3 (-w) (-w) (-w)
        vertex $ Vertex3 (-w) (-w) w
        vertex $ Vertex3 w w (-w)
        vertex $ Vertex3 w (-w) (-w)
        vertex $ Vertex3 (-w) (-w) (-w)
        vertex $ Vertex3 (-w) w (-w)

points :: Integer -> [(GLfloat,GLfloat,GLfloat)]
points n' = let n = fromIntegral n' in map (\k -> let t = 2*pi*k/n in (sin(t),cos(t),0.0))  [1..n]

in do
    clear [ ColorBuffer ]
    counter <- readIORef state
    mapM_ (\(x,y,z) -> preservingMatrix $ do
           color $ Color3 ((x+1.0)/2.0) ((y+1.0)/2.0) ((z+1.0)/2.0)
           translate $ Vector3 x y z
           cube (0.3::GLfloat)
           ) $ points (9 + counter)
    flush

The main module

module Main where

import Control.Monad
import Data.Typeable as Typeable

import System.IO

import Data.IORef

import Graphics.Rendering.OpenGL
import Graphics.UI.GLUT

import Language.Haskell.Interpreter

main :: IO ()
main = do
    (_, _) <- getArgsAndInitialize
    createWindow "Hello World"

    action <- newIORef $ do
    clear [ ColorBuffer ]
    flush

    let imports = ["Prelude", "Data.IORef", "Graphics.Rendering.OpenGL", "Graphics.UI.GLUT"]
    let modules = ["State"]

    runFile (undefined :: IORef Integer -> IO ()) "Display.hs" imports $ \displayCode ->
    runFile (undefined :: IORef Integer -> IO ()) "Idle.hs" imports $ \idleCode -> do

    state <- newIORef 12

    displayCallback $= display displayCode state
    idleCallback $= Just (idle displayCode idleCode state)

    mainLoop

display displayCode state = do
    f <- execute displayCode
    f state

idle displayCode idleCode state = do
    update displayCode
    update idleCode

    f <- execute idleCode
    f state

instance Eq GhcError where
    GhcError s == GhcError t = s == t

instance Eq InterpreterError where
    UnknownError s == UnknownError t = s == t
    WontCompile s == WontCompile t = s == t
    NotAllowed s == NotAllowed t = s == t
    GhcException s == GhcException t = s == t

data V a = V {
    update :: IO (),
    execute :: IO a
 }

runFile :: Typeable a => a -> String -> [String] -> (V a -> IO ()) -> IO ()
runFile theType file imports f = do
    currentError <- newIORef Nothing
    currentAction <- newIORef Nothing

    let v = V {
        update = do
            fileContents <- readFile file

            result <- runInterpreter $ do
                setImports imports
                interpret fileContents theType

                oldError <- readIORef currentError

                case result of
                Right newAction -> do
                    when (oldError /= Nothing) $ do
                        writeIORef currentError Nothing
                        putStrLn (file ++ " Ok!")

                        writeIORef currentAction (Just newAction)

                        Left newError -> do

                            when ((Just newError) /= oldError) $ do
                                writeIORef currentError (Just newError)
                                print newError
                                , execute = do
                                    action <- readIORef currentAction
                                    case action of
                                    Nothing -> do
                                        err <- readIORef currentError
                                        return (error (show err))
                                        Just act -> return act
                                        }

    update v 

    f v
Volker Stolz
  • 7,274
  • 1
  • 32
  • 50
  • 3
    +1 for acting on Bret Victor's talk. It would be great if you could post your code somewhere. I think a statically typechecked language is not very well suitable for an environment like this. If you insist on static types, then the runtime (the debugging development runtime at least) should throw away static types and work with dynamic types. I'm not sure a runtime like this exists for Haskell. – n. m. could be an AI Feb 25 '12 at 19:31
  • 1
    @user990666 could you post the link to the talk? – Matt Fenwick Feb 25 '12 at 20:10
  • 2
    @Matt Fenwick http://vimeo.com/36579366 – n. m. could be an AI Feb 25 '12 at 20:51
  • The code doesn't quite work... there's a syntax error at least at line 28 of main.hs. But the idea is more or less clear. – n. m. could be an AI Feb 26 '12 at 06:01
  • 3
    can't watch the video at the moment, but could you possibly use a `State` type of [`Dynamic`](http://hackage.haskell.org/packages/archive/base/latest/doc/html/Data-Dynamic.html) and would that solve your issue? – jberryman Feb 27 '12 at 16:42
  • jberryman, that seems like it could be a good approach. – Molly Stewart-Gallus Feb 29 '12 at 04:19
  • Some other questions related to the same talk are, ["What was he using?"](http://stackoverflow.com/q/9448215/4794), ["How can I draw a tree in Javascript?"](http://stackoverflow.com/q/9793675/4794), ["Can I do it in Groovy?"](http://stackoverflow.com/q/3231974/4794), and, ["How can I trace Python code to do that?"](http://stackoverflow.com/q/9670931/4794) – Don Kirkby May 20 '12 at 05:58

1 Answers1

2

I'm pretty sure it is impossible in GHC. When Haskell is compiled, the higher level language is desugared into Core, which is also typed. GHC will not initiate the transformation into Core until the program has been typed checked. There's a reason for this, too: as the program type checks it simultaneously proves itself. As jberryman noted, the only work around would be to have a flexible type for State which would allow polymorphism, so a type change might not register as one.

rotskoff
  • 714
  • 3
  • 10