module Graphics.LambdaCanvas ( -- * Drawing types Point , Graphics.Rendering.OpenGL.PrimitiveMode(..) -- * Drawing functions , animate , draw , put -- * Utility functions , stepOf ) where import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime) import Graphics.Rendering.OpenGL import Graphics.UI.GLUT hiding (initialize) type Point = (GLfloat, GLfloat) vertex2 :: Point -> IO () vertex2 (x, y) = vertex $ Vertex2 x y -- | Draw a primitive from a set of a vertices on screen. put :: PrimitiveMode -> [Point] -> IO () put mode pts = renderPrimitive mode $ mapM_ vertex2 pts initialize :: String -> IO () initialize title = do _ <- getArgsAndInitialize initialWindowSize $= Size 500 500 initialDisplayMode $= [DoubleBuffered, WithAlphaComponent] _ <- createWindow title reshapeCallback $= Just reshape -- | Create a canvas suitable for drawing a static picture. -- The drawing block is invoked on each redisplay. draw :: String -> IO () -> IO () draw title actions = do initialize title displayCallback $= do clear [ColorBuffer] actions swapBuffers mainLoop -- | Create a canvas suitable for animation. -- The drawing block is invoked on each redisplay -- and is passed the current timestamp. animate :: String -> (POSIXTime -> IO ()) -> IO () animate title actions = do initialize title displayCallback $= do clear [ColorBuffer] time <- getPOSIXTime actions time swapBuffers idleCallback $= Just (postRedisplay Nothing) mainLoop reshape :: Size -> IO () reshape size = do viewport $= (Position 0 0, size) postRedisplay Nothing -- | Given an amount of steps and a timestamp, calculate current step number. -- Step numbers begin with 0. stepOf :: Num a => Integer -> POSIXTime -> a stepOf total = fromIntegral . (`mod` total) . truncate . (*1000)