minilight-0.1.0: A SDL2-based graphics library, batteries-included.

Safe HaskellNone
LanguageHaskell2010

MiniLight.Component.Loader

Synopsis

Documentation

data ComponentConfig Source #

Constructors

ComponentConfig 

Fields

Instances
Generic ComponentConfig Source # 
Instance details

Defined in MiniLight.Component.Loader

Associated Types

type Rep ComponentConfig :: Type -> Type #

FromJSON ComponentConfig Source # 
Instance details

Defined in MiniLight.Component.Loader

Methods

parseJSON :: Value -> Parser ComponentConfig

parseJSONList :: Value -> Parser [ComponentConfig]

type Rep ComponentConfig Source # 
Instance details

Defined in MiniLight.Component.Loader

type Rep ComponentConfig = D1 (MetaData "ComponentConfig" "MiniLight.Component.Loader" "minilight-0.1.0-inplace" False) (C1 (MetaCons "ComponentConfig" PrefixI True) (S1 (MetaSel (Just "name") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "properties") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Value)))

data AppConfig Source #

Constructors

AppConfig 

Fields

Instances
Generic AppConfig Source # 
Instance details

Defined in MiniLight.Component.Loader

Associated Types

type Rep AppConfig :: Type -> Type #

FromJSON AppConfig Source # 
Instance details

Defined in MiniLight.Component.Loader

Methods

parseJSON :: Value -> Parser AppConfig

parseJSONList :: Value -> Parser [AppConfig]

type Rep AppConfig Source # 
Instance details

Defined in MiniLight.Component.Loader

type Rep AppConfig = D1 (MetaData "AppConfig" "MiniLight.Component.Loader" "minilight-0.1.0-inplace" False) (C1 (MetaCons "AppConfig" PrefixI True) (S1 (MetaSel (Just "app") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [ComponentConfig])))

loadAppConfig Source #

Arguments

:: (HasLightEnv env, MonadIO m) 
=> FilePath

Filepath to the yaml file.

-> (Text -> Value -> LightT env m Component)

Specify any resolver.

-> LightT env m [Component] 

Load an config file and construct components.

data Expr Source #

Constructors

None 
Ref Text

reference syntax: ${ref:...}

Var Text

variable syntax: ${var:...}

Op Text Expr Expr

expr operator: +, -, *, /

Constant Value

constants (string or number or null)

Instances
Eq Expr Source # 
Instance details

Defined in MiniLight.Component.Loader

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Show Expr Source # 
Instance details

Defined in MiniLight.Component.Loader

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

parser :: Parser Expr Source #

data Context Source #

Constructors

Context 

Fields

getAt :: Value -> [Either Int Text] -> Value Source #

pattern Arithmetic :: Text -> Scientific -> Scientific -> Expr Source #

eval :: Context -> Expr -> Value Source #

convert :: Context -> Text -> Value Source #

parseText :: Parser a -> Text -> Result a Source #

resolve :: Value -> Value Source #