Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Monad m => MonadIO (m :: Type -> Type) where
- class HasLightEnv env where
- rendererL :: Lens' env Renderer
- fontCacheL :: Lens' env FontMap
- newtype LightT env m a = LightT {
- runLightT' :: ReaderT env m a
- data LightEnv = LightEnv {}
- type MiniLight = LightT LightEnv IO
- liftMiniLight :: (HasLightEnv env, MonadIO m) => MiniLight a -> LightT env m a
- envLightT :: (env' -> env) -> LightT env m a -> LightT env' m a
- mapLightT :: (m a -> n a) -> LightT env m a -> LightT env n a
- data FontDescriptor = FontDescriptor {}
- data FontStyle = FontStyle {
- _fontStyleBold :: !Bool
- _fontStyleItalic :: !Bool
- loadFontCache :: MonadIO m => m FontMap
- loadFont :: (HasLightEnv env, MonadIO m) => FontDescriptor -> Int -> LightT env m Font
- withFont :: (HasLightEnv env, MonadIO m, MonadMask m) => FontDescriptor -> Int -> (Font -> LightT env m a) -> LightT env m a
Documentation
class Monad m => MonadIO (m :: Type -> Type) where #
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
Instances
class HasLightEnv env where Source #
Instances
HasLightEnv LightEnv Source # | |
Defined in MiniLight.Light |
newtype LightT env m a Source #
LightT | |
|
Instances
Instances
HasLightEnv LightEnv Source # | |
Defined in MiniLight.Light | |
Rendering Figure MiniLight Source # | |
Defined in MiniLight.Figure translate :: V2 Int -> Figure -> Figure Source # clip :: Rectangle Int -> Figure -> Figure Source # rotate :: Double -> Figure -> Figure Source # text :: Font -> V4 Word8 -> Text -> MiniLight Figure Source # picture :: FilePath -> MiniLight Figure Source # fromTexture :: Texture -> MiniLight Figure Source # rectangleOutline :: V4 Word8 -> V2 Int -> MiniLight Figure Source # rectangleFilled :: V4 Word8 -> V2 Int -> MiniLight Figure Source # triangleOutline :: V4 Word8 -> V2 Int -> MiniLight Figure Source # |
liftMiniLight :: (HasLightEnv env, MonadIO m) => MiniLight a -> LightT env m a Source #
data FontDescriptor #
Instances
Eq FontDescriptor | |
Defined in Graphics.Text.TrueType.FontFolders (==) :: FontDescriptor -> FontDescriptor -> Bool # (/=) :: FontDescriptor -> FontDescriptor -> Bool # | |
Ord FontDescriptor | |
Defined in Graphics.Text.TrueType.FontFolders compare :: FontDescriptor -> FontDescriptor -> Ordering # (<) :: FontDescriptor -> FontDescriptor -> Bool # (<=) :: FontDescriptor -> FontDescriptor -> Bool # (>) :: FontDescriptor -> FontDescriptor -> Bool # (>=) :: FontDescriptor -> FontDescriptor -> Bool # max :: FontDescriptor -> FontDescriptor -> FontDescriptor # min :: FontDescriptor -> FontDescriptor -> FontDescriptor # | |
Show FontDescriptor | |
Defined in Graphics.Text.TrueType.FontFolders showsPrec :: Int -> FontDescriptor -> ShowS # show :: FontDescriptor -> String # showList :: [FontDescriptor] -> ShowS # | |
Binary FontDescriptor | |
Defined in Graphics.Text.TrueType.FontFolders | |
Hashable FontDescriptor | |
Defined in MiniLight.Light hashWithSalt :: Int -> FontDescriptor -> Int hash :: FontDescriptor -> Int |
FontStyle | |
|
loadFontCache :: MonadIO m => m FontMap Source #
loadFont :: (HasLightEnv env, MonadIO m) => FontDescriptor -> Int -> LightT env m Font Source #
withFont :: (HasLightEnv env, MonadIO m, MonadMask m) => FontDescriptor -> Int -> (Font -> LightT env m a) -> LightT env m a Source #
Orphan instances
Hashable FontDescriptor Source # | |
hashWithSalt :: Int -> FontDescriptor -> Int hash :: FontDescriptor -> Int |