gore-and-ash-lambdacube-0.2.0.0: Core module for Gore&Ash engine that do something.

Copyright(c) Anton Gushcha, 2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.LambdaCube

Contents

Description

The core module contains API for something into main game loop for Gore&Ash.

The module does not depend on any other core modules, so LambdaCubeT could be placed at any place in monad stack.

The module is not pure within first phase (see ModuleStack docs), therefore only IO can be used as end monad.

Example of embedding:

-- | Application monad is monad stack build from given list of modules over base monad (IO)
type AppStack = ModuleStack [LambdaCubeT ... other modules ... ] IO
newtype AppState = AppState (ModuleState AppStack)
  deriving (Generic)

instance NFData AppState 

-- | Wrapper around type family
newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadLambdaCube ... other modules monads ... )

instance GameModule AppMonad AppState where 
  type ModuleState AppMonad = AppState
  runModule (AppMonad m) (AppState s) = do 
    (a, s') <- runModule m s 
    return (a, AppState s')
  newModuleState = AppState $ newModuleState
  withModule _ = withModule (Proxy :: Proxy AppStack)
  cleanupModule (AppState s) = cleanupModule s 

-- | Arrow that is build over the monad stack
type AppWire a b = GameWire AppMonad a b

Synopsis

Low-level

data LambdaCubeState s Source #

Internal state of core module

s
- state of next module, they are chained until bottom, that is usually an empty data type.

Instances

Generic (LambdaCubeState s) Source # 

Associated Types

type Rep (LambdaCubeState s) :: * -> * #

NFData s => NFData (LambdaCubeState s) Source # 

Methods

rnf :: LambdaCubeState s -> () #

Monad m => MonadState (LambdaCubeState s) (LambdaCubeT s m) 
type Rep (LambdaCubeState s) Source # 

data LambdaCubeT s m a Source #

Monad transformer of the core module.

s
- State of next core module in modules chain;
m
- Next monad in modules monad stack;
a
- Type of result value;

How to embed module:

type AppStack = ModuleStack [LambdaCubeT, ... other modules ... ] IO

newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadLambdaCube)

The module is not pure within first phase (see ModuleStack docs), therefore only IO can be used as end monad.

Instances

MonadTrans (LambdaCubeT s) Source # 

Methods

lift :: Monad m => m a -> LambdaCubeT s m a #

Monad m => MonadState (LambdaCubeState s) (LambdaCubeT s m) Source # 
Monad m => Monad (LambdaCubeT s m) Source # 

Methods

(>>=) :: LambdaCubeT s m a -> (a -> LambdaCubeT s m b) -> LambdaCubeT s m b #

(>>) :: LambdaCubeT s m a -> LambdaCubeT s m b -> LambdaCubeT s m b #

return :: a -> LambdaCubeT s m a #

fail :: String -> LambdaCubeT s m a #

Functor m => Functor (LambdaCubeT s m) Source # 

Methods

fmap :: (a -> b) -> LambdaCubeT s m a -> LambdaCubeT s m b #

(<$) :: a -> LambdaCubeT s m b -> LambdaCubeT s m a #

MonadFix m => MonadFix (LambdaCubeT s m) Source # 

Methods

mfix :: (a -> LambdaCubeT s m a) -> LambdaCubeT s m a #

Monad m => Applicative (LambdaCubeT s m) Source # 

Methods

pure :: a -> LambdaCubeT s m a #

(<*>) :: LambdaCubeT s m (a -> b) -> LambdaCubeT s m a -> LambdaCubeT s m b #

(*>) :: LambdaCubeT s m a -> LambdaCubeT s m b -> LambdaCubeT s m b #

(<*) :: LambdaCubeT s m a -> LambdaCubeT s m b -> LambdaCubeT s m a #

MonadIO m => MonadIO (LambdaCubeT s m) Source # 

Methods

liftIO :: IO a -> LambdaCubeT s m a #

MonadMask m => MonadMask (LambdaCubeT s m) Source # 

Methods

mask :: ((forall a. LambdaCubeT s m a -> LambdaCubeT s m a) -> LambdaCubeT s m b) -> LambdaCubeT s m b

uninterruptibleMask :: ((forall a. LambdaCubeT s m a -> LambdaCubeT s m a) -> LambdaCubeT s m b) -> LambdaCubeT s m b

MonadThrow m => MonadThrow (LambdaCubeT s m) Source # 

Methods

throwM :: Exception e => e -> LambdaCubeT s m a

MonadCatch m => MonadCatch (LambdaCubeT s m) Source # 

Methods

catch :: Exception e => LambdaCubeT s m a -> (e -> LambdaCubeT s m a) -> LambdaCubeT s m a

(MonadIO m, MonadThrow m) => MonadLambdaCube (LambdaCubeT s m) Source # 
type ModuleState (LambdaCubeT s m) Source # 
type ModuleState (LambdaCubeT s m) = LambdaCubeState s

class (MonadIO m, MonadThrow m) => MonadLambdaCube m where Source #

Low level monadic API for module.

Methods

lambdacubeUpdateSize :: Word -> Word -> m () Source #

Update viewport size for rendering engine Should be called when window size is changed (or every frame)

lambdacubeAddPipeline :: [FilePath] -> String -> PipelineId -> Writer PipelineSchema a -> m () Source #

Compile and register new pipeline.

Throws: PipeLineCompileFailed or PipeLineAlreadyRegistered when failed.

lambdacubeDeletePipeline :: PipelineId -> m () Source #

Removes pipeline from engine, deallocates all storages for rendering storages

Note: if pipeline with the name doesn't exists, do nothing.

lambdacubeCreateStorage :: PipelineId -> m (StorageId, GLStorage) Source #

Creates new storage (corresponding to one game object)

Note: if pipeline not found, throws PipeLineNotFound

lambdacubeDeleteStorage :: StorageId -> m () Source #

Removes storage for pipeline, deallocates it

Note: if storage with the id doesn't exists, do nothing

lambdacubeGetStorage :: StorageId -> m GLStorage Source #

Getting storage by ID

Throws StorageNotFound if no storage found

lambdacubeRenderStorageLast :: StorageId -> m () Source #

Adds storage to rendering queue

lambdacubeRenderStorageFirst :: StorageId -> m () Source #

Adds storage to rendering queue

lambdacubeStopRendering :: StorageId -> m () Source #

Removes storage from rendering queue

data LambdaCubeException Source #

Exception type that could be thrown by the module

Constructors

PipeLineCompileFailed String PipelineId String

Thrown when a pipeline compilation failed, first is pipeline main module, last is error message

PipeLineAlreadyRegistered PipelineId

Thrown when tries to register the same pipeline twice

PipeLineNotFound PipelineId

Trhown when tries to create storage for unregistered pipeline

StorageNotFound StorageId

Thrown when tries to get unregistered storage

PipeLineIncompatible StorageId String

Thrown when failed to bind pipeline to context, contains pipeline name and error message

Instances

Show LambdaCubeException Source # 
Generic LambdaCubeException Source # 
Exception LambdaCubeException Source # 
type Rep LambdaCubeException Source # 

type PipelineId = Text Source #

ID to uniquely identify LambdaCube rednering pipeline

data StorageId Source #

ID to uniquely identify LambdaCube storage

Instances

Eq StorageId Source # 
Show StorageId Source # 
Generic StorageId Source # 

Associated Types

type Rep StorageId :: * -> * #

NFData StorageId Source # 

Methods

rnf :: StorageId -> () #

Hashable StorageId Source # 
type Rep StorageId Source # 
type Rep StorageId = D1 (MetaData "StorageId" "Game.GoreAndAsh.LambdaCube.State" "gore-and-ash-lambdacube-0.2.0.0-5EhXRpUDsTL23dfGCQjBPt" False) (C1 (MetaCons "StorageId" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "storageId") NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int)) (S1 (MetaSel (Just Symbol "storageScheme") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 PipelineId))))