1. I wrote this:
-----8<----- test.hs ---
  module Main where
  import qualified Graphics.UI.GLFW as GLFW
  main = do
    True <- GLFW.initialize
    print =<< GLFW.openGLProfile
    print =<< GLFW.getGlfwVersion
    print =<< GLFW.getGlVersion
    print "Trying to open the window"
    result <- GLFW.openWindow GLFW.defaultDisplayOptions
    print result
-----8<-----

2. Compiled like this: ghc --make -o test test.hs
3. Executed: ./test
  DefaultProfile
  Version {versionBranch = [2,7,2], versionTags = []}
  Version {versionBranch = [0,0,0], versionTags = []}
  "Trying to open the window"
  True
4. Window appeared.

2'. Executed in GHCI like this:
  ghci -fno-ghci-sandbox
  Prelude> :l test.hs
  Prelude> main
3'. Get (random numbers as GLVersion):
  Loading package GLFW-b-0.1.0.2 ... linking ... done.
  DefaultProfile
  Version {versionBranch = [2,7,2], versionTags = []}
  Version {versionBranch = *[34972080,-1323041296,-1334802519]*,
versionTags = []}
  "Trying to open the window"
  False
4'. Window didn't appear.

What should I do to get GLFW window in ghci too?
What do I do wrong?
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to