-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Experiemental library for composable interactive programs
--
-- Experiemental library for composable interactive programs. GLUT
-- backend included.
@package peakachu
@version 0.3.0
-- | In/with newtype functions generation with Template Haskell.
--
-- Example:
--
--
-- {-# LANGUAGE TemplateHaskell #-}
-- import Control.Applicative (Applicative(..), ZipList(..))
-- import Data.Newtype (mkWithNewTypeFuncs)
--
-- $(mkWithNewtypeFuncs [2] ''ZipList)
--
-- > withZipList2 (<*>) [(+3), (*3)] [6, 7]
-- [9, 21]
--
module Data.Newtype
mkInNewtypeFuncs :: [Int] -> Name -> Q [Dec]
mkWithNewtypeFuncs :: [Int] -> Name -> Q [Dec]
-- | ADT getters generation with Template Haskell
--
-- Example:
--
--
-- {-# LANGUAGE TemplateHaskell #-}
-- data Blah a = NoBlah | YesBlah a | ManyBlah a Int
-- $(mkADTGetters ''Blah)
--
--
-- Generates
--
--
-- gNoBlah :: Blah a -> Maybe ()
-- gYesBlah :: Blah a -> Maybe a
-- gManyBlah :: Blah a -> Maybe (a, Int)
--
--
-- Where
--
--
-- gYesBlah (YesBlah a) = Just a
-- gYesBlah _ = Nothing
--
--
-- etc.
module Data.ADT.Getters
mkADTGetters :: Name -> Q [Dec]
-- | ADT getter functions for GLUT data types.
--
-- Useful for filtering GLUT events in the Maybe monad.
module FRP.Peakachu.Backend.GLUT.Getters
gChar :: Key -> Maybe Char
gMouseButton :: Key -> Maybe MouseButton
gSpecialKey :: Key -> Maybe SpecialKey
gDown :: KeyState -> Maybe ()
gUp :: KeyState -> Maybe ()
-- | A FilterCategory is a Category that supports mapMaybeC.
--
-- In Peakachu, both Program and Backend are instances of FilterCategory.
module Control.FilterCategory
class Category cat => FilterCategory cat
flattenC :: FilterCategory cat => cat [a] a
arrC :: FilterCategory cat => (a -> b) -> cat a b
genericFlattenC :: (FilterCategory cat, Foldable f) => cat (f a) a
mapMaybeC :: FilterCategory cat => (a -> Maybe b) -> cat a b
filterC :: FilterCategory cat => (a -> Bool) -> cat a a
module Control.Concurrent.MVar.YC
modifyMVarPure :: MVar a -> (a -> a) -> IO ()
writeMVar :: MVar a -> a -> IO ()
-- | Program a b is a pure representation of a computer program,
-- which accepts inputs of type a, and outputs values of type
-- b. It may also terminate. It can output zero or more
-- b values after each a input.
--
--
-- - A simple stateless input-output-loop can be created from a
-- function with arrC.
-- - A simple stateful input-output-loop can be created using
-- scanlP.
-- - Outputs can be filtered using filterC.
--
--
-- Programs may also be composed together in several ways using common
-- type-classes
--
--
-- - Category: Program a b -> Program b c -> Program a
-- c. One program's outputs are fed to another program as
-- input.
-- - Monoid: Program a b -> Program a b -> Program a
-- b. Both programs run in parallel processing the same input.
-- Resulting Program outputs both's outputs.
-- - Applicative: Program a (b -> c) -> Program a b
-- -> Program a c.
-- - Alternative MonadPlus: AppendProgram is a newtype
-- wrapper whose Monoid instance runs one program after the other
-- finishes (like ZipList offers an alternative
-- Applicative instance for lists). It's also a Monad ant
-- its monadic bind allows us to invoke inner programs based on an outer
-- program's outputs.
--
module FRP.Peakachu.Program
-- | A computer program
data Program a b
Program :: [b] -> Maybe (a -> Program a b) -> Program a b
progVals :: Program a b -> [b]
progMore :: Program a b -> Maybe (a -> Program a b)
newtype AppendProgram a b
AppendProg :: Program a b -> AppendProgram a b
runAppendProg :: AppendProgram a b -> Program a b
-- | Create a stateful input-output-loop from a simple function
scanlP :: (b -> a -> b) -> b -> Program a b
-- | A program that terminates immediately
emptyP :: Program a b
-- | Terminate when a predicate on input fails
takeWhileP :: (a -> Bool) -> Program a a
-- | Feed some outputs of a Program to itself
loopbackP :: Program a (Either a b) -> Program a b
-- | A program that outputs a value and immediately terminates
singleValueP :: Program a ()
-- | Given a partial function (a -> Maybe b), output its most
-- recent result on an input.
lstP :: (a -> Maybe b) -> Program a b
-- | Given a partial function (a -> Maybe b) and a start value,
-- output its most recent result on an input.
lstPs :: Maybe b -> (a -> Maybe b) -> Program a b
-- | Delay the outputs of a Program
delayP :: Integral i => i -> Program a a
withAppendProgram1 :: (AppendProgram a0 b0 -> AppendProgram a1 b1) -> Program a0 b0 -> Program a1 b1
withAppendProgram2 :: (AppendProgram a0 b0 -> AppendProgram a1 b1 -> AppendProgram a2 b2) -> Program a0 b0 -> Program a1 b1 -> Program a2 b2
instance Applicative (AppendProgram a)
instance MonadPlus (AppendProgram a)
instance Monad (AppendProgram a)
instance Monoid (AppendProgram a b)
instance Category AppendProgram
instance FilterCategory AppendProgram
instance Functor (AppendProgram a)
instance Applicative (Program a)
instance Monoid (Program a b)
instance FilterCategory Program
instance Category Program
instance Functor (Program t1)
module FRP.Peakachu.Backend.Internal
data Sink a
Sink :: (a -> IO ()) -> MainLoop -> Sink a
sinkConsume :: Sink a -> a -> IO ()
sinkMainLoop :: Sink a -> MainLoop
data MainLoop
MainLoop :: IO () -> IO () -> Maybe ParallelIO -> MainLoop
mlInit :: MainLoop -> IO ()
mlQuit :: MainLoop -> IO ()
mlRun :: MainLoop -> Maybe ParallelIO
newtype ParallelIO
ParIO :: IO () -> ParallelIO
runParIO :: ParallelIO -> IO ()
instance Monoid (Sink a)
instance Monoid MainLoop
instance Monoid ParallelIO
module FRP.Peakachu.Backend
newtype Backend progToBack backToProg
Backend :: ((backToProg -> IO ()) -> IO (Sink progToBack)) -> Backend progToBack backToProg
runBackend :: Backend progToBack backToProg -> (backToProg -> IO ()) -> IO (Sink progToBack)
instance FilterCategory Backend
instance Category Backend
instance Functor (Backend t1)
instance Monoid (Backend progToBack backToProg)
module FRP.Peakachu.Backend.File
data FileToProgram a
FileData :: String -> a -> FileToProgram a
FileError :: a -> FileToProgram a
data ProgramToFile a
ReadFile :: FilePath -> a -> ProgramToFile a
WriteFile :: FilePath -> String -> a -> ProgramToFile a
fileB :: Backend (ProgramToFile a) (FileToProgram a)
gFileData :: FileToProgram a[ac86] -> Maybe (String, a[ac86])
gFileError :: FileToProgram a[ac86] -> Maybe a[ac86]
module FRP.Peakachu.Backend.GLUT
data GlutToProgram a
IdleEvent :: GlutToProgram a
TimerEvent :: a -> GlutToProgram a
MouseMotionEvent :: GLfloat -> GLfloat -> GlutToProgram a
KeyboardMouseEvent :: Key -> KeyState -> Modifiers -> Position -> GlutToProgram a
data Image
Image :: IO () -> Image
runImage :: Image -> IO ()
data ProgramToGlut a
DrawImage :: Image -> ProgramToGlut a
SetTimer :: Timeout -> a -> ProgramToGlut a
glut :: Backend (ProgramToGlut a) (GlutToProgram a)
gIdleEvent :: GlutToProgram a[ad0W] -> Maybe ()
gTimerEvent :: GlutToProgram a[ad0W] -> Maybe a[ad0W]
gMouseMotionEvent :: GlutToProgram a[ad0W] -> Maybe (GLfloat, GLfloat)
gKeyboardMouseEvent :: GlutToProgram a[ad0W] -> Maybe (Key, KeyState, Modifiers, Position)
instance Monoid Image
-- | A Peakachu backend to write output to the console
module FRP.Peakachu.Backend.StdIO
stdoutB :: Backend String ()
-- | The Peakachu equivalent to interact. Prints all output lines
-- from the program, and feeds input lines from the user to the program.
interactB :: Backend String String
-- | A Peakachu backend to get the time
module FRP.Peakachu.Backend.Time
getTimeB :: Backend a (UTCTime, a)
module FRP.Peakachu
processList :: List l => Program a b -> l a -> l b
-- | Verbose version of processList.
--
-- The program's outputs after each input are grouped together
processListV :: List l => Program a b -> l a -> l [b]
runProgram :: Backend o i -> Program i o -> IO ()