FunGEn-0.1: FUNctional Game ENgineSource codeContentsIndex
Graphics.UI.FunGEn
Documentation
type WindowConfig = ((Int, Int), (Int, Int), String)Source
type Point2D = (GLdouble, GLdouble)Source
type ColorList3 = [(GLubyte, GLubyte, GLubyte)]Source
type AwbfBitmap = (GLsizei, GLsizei, PixelData GLubyte)Source
type InvList = Maybe [(Int, Int, Int)]Source
texCoord2 :: GLdouble -> GLdouble -> IO ()Source
vertex3 :: GLdouble -> GLdouble -> GLdouble -> IO ()Source
texStuff :: [TextureObject] -> [AwbfBitmap] -> IO ()Source
toRad :: Float -> FloatSource
randInt :: (Int, Int) -> IO IntSource
randFloat :: (Float, Float) -> IO FloatSource
randDouble :: (Double, Double) -> IO DoubleSource
shiftLeft :: String -> Int -> StringSource
toDecimal :: String -> GLsizeiSource
pow2 :: GLsizei -> GLsizeiSource
toBinary :: Int -> StringSource
make0 :: Int -> StringSource
dropGLsizei :: GLsizei -> [a] -> [a]Source
ord2 :: Char -> GLubyteSource
addNoInvisibility :: [FilePath] -> [(FilePath, Maybe ColorList3)]Source
racMod :: GLdouble -> GLdouble -> GLdoubleSource
matrixToList :: [[a]] -> [a]Source
matrixSize :: [[a]] -> (Int, Int)Source
inv2color3 :: InvList -> Maybe ColorList3Source
pathAndInv2color3List :: (FilePath, InvList) -> (FilePath, Maybe ColorList3)Source
point2DtoVertex3 :: [Point2D] -> [Vertex3 GLdouble]Source
isEmpty :: [a] -> BoolSource
when :: Monad m => Bool -> m () -> m ()Source
unless :: Monad m => Bool -> m () -> m ()Source
bindTexture :: TextureTarget -> TextureObject -> IO ()Source
loadBitmap :: FilePath -> Maybe ColorList3 -> IO AwbfBitmapSource
loadBitmapList :: [(FilePath, Maybe ColorList3)] -> IO [AwbfBitmap]Source
type FilePictureList = [(FilePath, InvList)]Source
data GameObject t Source
getGameObjectId :: GameObject t -> IntegerSource
getGameObjectName :: GameObject t -> StringSource
getGameObjectManagerName :: GameObject t -> StringSource
getGameObjectAsleep :: GameObject t -> BoolSource
getGameObjectPosition :: GameObject t -> (Double, Double)Source
getGameObjectSize :: GameObject t -> (Double, Double)Source
getGameObjectSpeed :: GameObject t -> (Double, Double)Source
getGameObjectAttribute :: GameObject t -> tSource
getObjectManagerName :: ObjectManager t -> StringSource
getObjectManagerCounter :: ObjectManager t -> IntegerSource
getObjectManagerObjects :: ObjectManager t -> [GameObject t]Source
data ObjectPicture Source
Constructors
Tex (Double, Double) Int
Basic Primitive
data Primitive Source
Constructors
Polyg [Point2D] Float Float Float FillMode
Circle Double Float Float Float FillMode
data FillMode Source
Constructors
Filled
Unfilled
show/hide Instances
object :: String -> ObjectPicture -> Bool -> (Double, Double) -> (Double, Double) -> t -> GameObject tSource
drawGameObjects :: [ObjectManager t] -> QuadricPrimitive -> [TextureObject] -> IO ()Source
drawGameObject :: GameObject t -> QuadricPrimitive -> [TextureObject] -> IO ()Source
objectGroup :: String -> [GameObject t] -> ObjectManager tSource
data ObjectManager t Source
findObjectFromId :: GameObject t -> [ObjectManager t] -> GameObject tSource
searchObjectManager :: String -> [ObjectManager t] -> ObjectManager tSource
searchGameObject :: String -> ObjectManager t -> GameObject tSource
updateObject :: (GameObject t -> GameObject t) -> Integer -> String -> [ObjectManager t] -> [ObjectManager t]Source
updateObjectAsleep :: Bool -> GameObject t -> GameObject tSource
updateObjectSize :: (Double, Double) -> GameObject t -> GameObject tSource
updateObjectPosition :: (Double, Double) -> GameObject t -> GameObject tSource
updateObjectSpeed :: (Double, Double) -> GameObject t -> GameObject tSource
updateObjectAttribute :: t -> GameObject t -> GameObject tSource
updateObjectPicture :: Int -> Int -> GameObject t -> GameObject tSource
addObjectsToManager :: [GameObject t] -> String -> [ObjectManager t] -> [ObjectManager t]Source
moveGameObjects :: [ObjectManager t] -> [ObjectManager t]Source
destroyGameObject :: String -> String -> [ObjectManager t] -> [ObjectManager t]Source
data GameMap t Source
type Tile t = (Int, Bool, Float, t)Source
type TileMatrix t = [[Tile t]]Source
getTilePictureIndex :: Tile t -> IntSource
getTileBlocked :: Tile t -> BoolSource
getTileMoveCost :: Tile t -> FloatSource
getTileSpecialAttribute :: Tile t -> tSource
colorMap :: Float -> Float -> Float -> Double -> Double -> GameMap tSource
textureMap :: Int -> Double -> Double -> Double -> Double -> GameMap tSource
tileMap :: TileMatrix t -> Double -> Double -> GameMap tSource
multiMap :: [GameMap t] -> Int -> GameMap tSource
getMapSize :: GameMap t -> Point2DSource
isTileMap :: GameMap t -> BoolSource
getTileMapTileMatrix :: GameMap t -> TileMatrix tSource
getTileMapScroll :: GameMap t -> Point2DSource
getTileMapSize :: GameMap t -> Point2DSource
getTileMapTileSize :: GameMap t -> Point2DSource
getCurrentMap :: GameMap t -> GameMap tSource
updateCurrentMap :: GameMap t -> GameMap t -> GameMap tSource
updateCurrentIndex :: GameMap t -> Int -> GameMap tSource
isMultiMap :: GameMap t -> BoolSource
drawGameMap :: GameMap t -> Point2D -> [TextureObject] -> IO ()Source
clearGameScreen :: Float -> Float -> Float -> IO ()Source
data Game t s u v Source
data IOGame t s u v a Source
show/hide Instances
Monad (IOGame t s u v)
runIOGame :: IOGame t s u v a -> Game t s u v -> IO (Game t s u v, a)Source
runIOGameM :: IOGame t s u v a -> Game t s u v -> IO ()Source
liftIOtoIOGame :: IO a -> IOGame t s u v aSource
liftIOtoIOGame' :: (a -> IO ()) -> a -> IOGame t s u v ()Source
getGameState :: IOGame t s u v uSource
setGameState :: u -> IOGame t s u v ()Source
getGameFlags :: IOGame t s u v GameFlagsSource
setGameFlags :: GameFlags -> IOGame t s u v ()Source
enableGameFlags :: IOGame t s u v ()Source
disableGameFlags :: IOGame t s u v ()Source
enableMapDrawing :: IOGame t s u v ()Source
disableMapDrawing :: IOGame t s u v ()Source
enableObjectsDrawing :: IOGame t s u v ()Source
disableObjectsDrawing :: IOGame t s u v ()Source
enableObjectsMoving :: IOGame t s u v ()Source
disableObjectsMoving :: IOGame t s u v ()Source
getObjectManagers :: IOGame t s u v [ObjectManager s]Source
setObjectManagers :: [ObjectManager s] -> IOGame t s u v ()Source
getGameAttribute :: IOGame t s u v tSource
setGameAttribute :: t -> IOGame t s u v ()Source
createGame :: GameMap v -> [ObjectManager s] -> WindowConfig -> u -> t -> FilePictureList -> IO (Game t s u v)Source
funExit :: IOGame t s u v ()Source
drawMap :: IOGame t s u v ()Source
clearScreen :: Float -> Float -> Float -> IOGame t s u v ()Source
getTileFromIndex :: (Int, Int) -> IOGame t s u v (Tile v)Source
getTileFromWindowPosition :: (Double, Double) -> IOGame t s u v (Tile v)Source
setCurrentMapIndex :: Int -> IOGame t s u v ()Source
drawAllObjects :: IOGame t s u v ()Source
drawObject :: GameObject s -> IOGame t s u v ()Source
moveAllObjects :: IOGame t s u v ()Source
destroyObjects :: [GameObject s] -> IOGame t s u v ()Source
destroyObject :: GameObject s -> IOGame t s u v ()Source
getObjectsFromGroup :: String -> IOGame t s u v [GameObject s]Source
addObjectsToGroup :: [GameObject s] -> String -> IOGame t s u v ()Source
addObjectsToNewGroup :: [GameObject s] -> String -> IOGame t s u v ()Source
findObjectManager :: String -> IOGame t s u v (ObjectManager s)Source
findObject :: String -> String -> IOGame t s u v (GameObject s)Source
getObjectName :: GameObject s -> IOGame t s u v StringSource
getObjectGroupName :: GameObject s -> IOGame t s u v StringSource
getObjectAsleep :: GameObject s -> IOGame t s u v BoolSource
getObjectSize :: GameObject s -> IOGame t s u v (Double, Double)Source
getObjectPosition :: GameObject s -> IOGame t s u v (Double, Double)Source
getObjectSpeed :: GameObject s -> IOGame t s u v (Double, Double)Source
getObjectAttribute :: GameObject s -> IOGame t s u v sSource
setObjectPosition :: (Double, Double) -> GameObject s -> IOGame t s u v ()Source
setObjectAsleep :: Bool -> GameObject s -> IOGame t s u v ()Source
setObjectSpeed :: (Double, Double) -> GameObject s -> IOGame t s u v ()Source
setObjectCurrentPicture :: Int -> GameObject s -> IOGame t s u v ()Source
setObjectAttribute :: s -> GameObject s -> IOGame t s u v ()Source
replaceObject :: GameObject s -> (GameObject s -> GameObject s) -> IOGame t s u v ()Source
reverseXSpeed :: GameObject s -> IOGame t s u v ()Source
reverseYSpeed :: GameObject s -> IOGame t s u v ()Source
objectsCollision :: GameObject s -> GameObject s -> IOGame t s u v BoolSource
objectsFutureCollision :: GameObject s -> GameObject s -> IOGame t s u v BoolSource
objectListObjectCollision :: [GameObject s] -> GameObject s -> IOGame t s u v BoolSource
objectListObjectFutureCollision :: [GameObject s] -> GameObject s -> IOGame t s u v BoolSource
objectTopMapCollision :: GameObject s -> IOGame t s u v BoolSource
objectBottomMapCollision :: GameObject s -> IOGame t s u v BoolSource
objectRightMapCollision :: GameObject s -> IOGame t s u v BoolSource
objectLeftMapCollision :: GameObject s -> IOGame t s u v BoolSource
pointsObjectCollision :: Double -> Double -> Double -> Double -> GameObject s -> IOGame t s u v BoolSource
pointsObjectListCollision :: Double -> Double -> Double -> Double -> [GameObject s] -> IOGame t s u v BoolSource
objectTopMapFutureCollision :: GameObject s -> IOGame t s u v BoolSource
objectBottomMapFutureCollision :: GameObject s -> IOGame t s u v BoolSource
objectRightMapFutureCollision :: GameObject s -> IOGame t s u v BoolSource
objectLeftMapFutureCollision :: GameObject s -> IOGame t s u v BoolSource
printOnPrompt :: Show a => a -> IOGame t s u v ()Source
printOnScreen :: String -> BitmapFont -> (Double, Double) -> Float -> Float -> Float -> IOGame t s u v ()Source
printText :: IOGame t s u v ()Source
randomFloat :: (Float, Float) -> IOGame t s u v FloatSource
randomInt :: (Int, Int) -> IOGame t s u v IntSource
randomDouble :: (Double, Double) -> IOGame t s u v DoubleSource
showFPS :: BitmapFont -> (Double, Double) -> Float -> Float -> Float -> IOGame t s u v ()Source
wait :: Int -> IOGame t s u v ()Source
display :: Game t s u v -> IOGame t s u v () -> DisplayCallbackSource
type InputConfig t s u v = (Key, KeyEvent, IOGame t s u v ())Source
Key (Char, SpecialKey, MouseButton)
data KeyEvent Source
Constructors
Press
StillDown
Release
show/hide Instances
SpecialKey (KeyF1, KeyF2, KeyF3, KeyF4, KeyF5, KeyF6, KeyF7, KeyF8, KeyF9, KeyF10, KeyF11, KeyF12, KeyLeft, KeyUp, KeyRight, KeyDown, KeyPageUp, KeyPageDown, KeyHome, KeyEnd, KeyInsert)
MouseButton (LeftButton, MiddleButton, RightButton, WheelUp, WheelDown)
funBinding :: [InputConfig t s u v] -> Game t s u v -> IO (KeyBinder, StillDownHandler)Source
data RefreshType Source
Constructors
Idle
Timer Int
setRefresh :: RefreshType -> StillDownHandler -> IO ()Source
type Text = (String, BitmapFont, (GLdouble, GLdouble), GLfloat, GLfloat, GLfloat)Source
BitmapFont (Fixed8By13, Fixed9By15, TimesRoman10, TimesRoman24, Helvetica10, Helvetica12, Helvetica18)
putGameText :: [Text] -> IO ()Source
funInit :: WindowConfig -> GameMap v -> [ObjectManager s] -> u -> t -> [InputConfig t s u v] -> IOGame t s u v () -> RefreshType -> FilePictureList -> IO ()Source
Produced by Haddock version 2.4.2