Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data types for marshalling dhall configs into Haskell.
Synopsis
- type AutomatonState = Text
- stateDecoder :: Decoder AutomatonState
- type AutomatonAddress = Text
- automatonAddressDecoder :: Decoder AutomatonAddress
- type Scope = Text
- type VariableName = Text
- type Value = Text
- type ImageContents = Text
- type ImageId = Text
- data Marquee = Marquee {
- _mqFramesPerChar :: Int
- _mqWidth :: Int
- _mqShouldWrap :: Bool
- mqWidth :: Lens' Marquee Int
- mqShouldWrap :: Lens' Marquee Bool
- mqFramesPerChar :: Lens' Marquee Int
- marqueeDecoder :: Decoder Marquee
- data Direction
- directionDecoder :: Decoder Direction
- data VerticalDirection
- verticalDirectionDecoder :: Decoder VerticalDirection
- data Assertion
- assertionDecoder :: Decoder Assertion
- data Check = Check {}
- chMessage :: Lens' Check Text
- chAssertion :: Lens' Check Assertion
- checkDecoder :: Decoder Check
- data Button
- buttonDecoder :: Decoder Button
- newtype Event = Event Text
- eventDecoder :: Decoder Event
- data Fade = Fade {}
- fadePixelHeight :: Lens' Fade Int
- fadeFrameCount :: Lens' Fade Int
- fadeDirection :: Lens' Fade VerticalDirection
- fadeDecoder :: Decoder Fade
- data Slider = Slider {}
- sliderDelay :: Lens' Slider Int
- fadeOut :: Lens' Slider Fade
- fadeIn :: Lens' Slider Fade
- sliderDecoder :: Decoder Slider
- data Hook = Hook {
- _hookCommand :: [Text]
- _hookInput :: Text
- hookInput :: Lens' Hook Text
- hookCommand :: Lens' Hook [Text]
- hookDecoder :: Decoder Hook
- newtype StateTransitionTable = STT {
- unSTT :: HashMap (Scope, Event, AutomatonState) (AutomatonState, [Hook])
- stateTransitionTableDecoder :: Decoder StateTransitionTable
- _scope :: Lens' (Scope, Event, AutomatonState) Scope
- newtype Color = Color Text
- colorDecoder :: Decoder Color
- data AbsolutePosition = AbsolutePosition {}
- apY :: Lens' AbsolutePosition Int
- apX :: Lens' AbsolutePosition Int
- absolutePositionDecoder :: Decoder AbsolutePosition
- data Position
- positionDecoder :: Decoder Position
- data ClickableArea = ClickableArea {
- _caButton :: Button
- _caCommand :: Text
- caCommand :: Lens' ClickableArea Text
- caButton :: Lens' ClickableArea Button
- clickableAreaDecoder :: Decoder ClickableArea
- data Padding
- paddingDecoder :: Decoder Padding
- data OpeningTag
- openingTagDecoder :: Decoder OpeningTag
- data BarSettings = BarSettings {
- _bsMonitor :: Int
- _bsExtraArgs :: [String]
- _bsUpdateInterval :: Int
- _bsFont :: Maybe String
- _bsFontWidth :: Int
- bsUpdateInterval :: Lens' BarSettings Int
- bsMonitor :: Lens' BarSettings Int
- bsFontWidth :: Lens' BarSettings Int
- bsFont :: Lens' BarSettings (Maybe String)
- bsExtraArgs :: Lens' BarSettings [String]
- barSettingsDecoder :: Decoder BarSettings
- data ShapeSize = ShapeSize {
- _shapeSizeW :: Int
- _shapeSizeH :: Int
- shapeSizeW :: Lens' ShapeSize Int
- shapeSizeH :: Lens' ShapeSize Int
- shapeSizeDecoder :: Decoder ShapeSize
- data Variable = Variable {}
- varValue :: Lens' Variable Text
- varName :: Lens' Variable Text
- variableDecoder :: Decoder Variable
- data Token
- tokenDecoder :: Decoder Token
- stateMapDecoder :: Decoder (HashMap Text [Token])
- data Source = Source {}
- sourceSettingsDecoder :: Decoder Source
- data Configuration = Configuration {}
- cfgBarTokens :: Lens' Configuration [Token]
- cfgBarSettings :: Lens' Configuration BarSettings
- configurationDecoder :: Decoder Configuration
- data PluginMeta = PluginMeta {
- _pmName :: Text
- _pmAuthor :: Text
- _pmEmail :: Maybe Text
- _pmHomePage :: Maybe Text
- _pmUpstream :: Maybe Text
- _pmDescription :: Text
- _pmUsage :: Text
- _pmApiVersion :: Int
- pmUsage :: Lens' PluginMeta Text
- pmUpstream :: Lens' PluginMeta (Maybe Text)
- pmName :: Lens' PluginMeta Text
- pmHomePage :: Lens' PluginMeta (Maybe Text)
- pmEmail :: Lens' PluginMeta (Maybe Text)
- pmDescription :: Lens' PluginMeta Text
- pmAuthor :: Lens' PluginMeta Text
- pmApiVersion :: Lens' PluginMeta Int
- pluginMetaDecoder :: Decoder PluginMeta
Documentation
type AutomatonState = Text Source #
type AutomatonAddress = Text Source #
type VariableName = Text Source #
type ImageContents = Text Source #
Marquee | |
|
Instances
Eq Marquee Source # | |
Show Marquee Source # | |
Generic Marquee Source # | |
type Rep Marquee Source # | |
Defined in DzenDhall.Config type Rep Marquee = D1 (MetaData "Marquee" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Marquee" PrefixI True) (S1 (MetaSel (Just "_mqFramesPerChar") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: (S1 (MetaSel (Just "_mqWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "_mqShouldWrap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) |
data VerticalDirection Source #
Instances
Eq VerticalDirection Source # | |
Defined in DzenDhall.Config (==) :: VerticalDirection -> VerticalDirection -> Bool # (/=) :: VerticalDirection -> VerticalDirection -> Bool # | |
Show VerticalDirection Source # | |
Defined in DzenDhall.Config showsPrec :: Int -> VerticalDirection -> ShowS # show :: VerticalDirection -> String # showList :: [VerticalDirection] -> ShowS # | |
Generic VerticalDirection Source # | |
Defined in DzenDhall.Config type Rep VerticalDirection :: Type -> Type # from :: VerticalDirection -> Rep VerticalDirection x # to :: Rep VerticalDirection x -> VerticalDirection # | |
type Rep VerticalDirection Source # | |
Instances
Eq Assertion Source # | |
Show Assertion Source # | |
Generic Assertion Source # | |
type Rep Assertion Source # | |
Defined in DzenDhall.Config type Rep Assertion = D1 (MetaData "Assertion" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "BinaryInPath" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) :+: C1 (MetaCons "SuccessfulExit" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
Check | |
|
Instances
Eq Check Source # | |
Show Check Source # | |
Generic Check Source # | |
type Rep Check Source # | |
Defined in DzenDhall.Config type Rep Check = D1 (MetaData "Check" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Check" PrefixI True) (S1 (MetaSel (Just "_chMessage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_chAssertion") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Assertion))) |
Instances
Eq Button Source # | |
Ord Button Source # | |
Show Button Source # | |
Generic Button Source # | |
Hashable Button Source # | |
Defined in DzenDhall.Config | |
Renderable Button Source # | |
type Rep Button Source # | |
Defined in DzenDhall.Config type Rep Button = D1 (MetaData "Button" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) ((C1 (MetaCons "MouseLeft" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "MouseMiddle" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MouseRight" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "MouseScrollUp" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MouseScrollDown" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "MouseScrollLeft" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "MouseScrollRight" PrefixI False) (U1 :: Type -> Type)))) |
Instances
Eq Fade Source # | |
Show Fade Source # | |
Generic Fade Source # | |
type Rep Fade Source # | |
Defined in DzenDhall.Config type Rep Fade = D1 (MetaData "Fade" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Fade" PrefixI True) (S1 (MetaSel (Just "_fadeDirection") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VerticalDirection) :*: (S1 (MetaSel (Just "_fadeFrameCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "_fadePixelHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) |
Instances
Eq Slider Source # | |
Show Slider Source # | |
Generic Slider Source # | |
type Rep Slider Source # | |
Defined in DzenDhall.Config type Rep Slider = D1 (MetaData "Slider" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Slider" PrefixI True) (S1 (MetaSel (Just "_fadeIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fade) :*: (S1 (MetaSel (Just "_fadeOut") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Fade) :*: S1 (MetaSel (Just "_sliderDelay") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) |
Hook | |
|
Instances
Eq Hook Source # | |
Show Hook Source # | |
Generic Hook Source # | |
type Rep Hook Source # | |
Defined in DzenDhall.Config type Rep Hook = D1 (MetaData "Hook" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Hook" PrefixI True) (S1 (MetaSel (Just "_hookCommand") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]) :*: S1 (MetaSel (Just "_hookInput") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
newtype StateTransitionTable Source #
STT | |
|
Instances
data AbsolutePosition Source #
Instances
Specify position that will be passed to ^p()
.
XY (Int, Int) |
|
P_RESET_Y |
|
P_LOCK_X |
|
P_UNLOCK_X |
|
P_LEFT |
|
P_RIGHT |
|
P_TOP |
|
P_CENTER |
|
P_BOTTOM |
|
Instances
Eq Position Source # | |
Show Position Source # | |
Generic Position Source # | |
type Rep Position Source # | |
Defined in DzenDhall.Config type Rep Position = D1 (MetaData "Position" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (((C1 (MetaCons "XY" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int, Int))) :+: C1 (MetaCons "P_RESET_Y" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "P_LOCK_X" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "P_UNLOCK_X" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "P_LEFT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "P_RIGHT" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "P_TOP" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "P_CENTER" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "P_BOTTOM" PrefixI False) (U1 :: Type -> Type))))) |
data ClickableArea Source #
Instances
data OpeningTag Source #
Instances
data BarSettings Source #
BarSettings | |
|
Instances
bsExtraArgs :: Lens' BarSettings [String] Source #
ShapeSize | |
|
Instances
Eq ShapeSize Source # | |
Show ShapeSize Source # | |
Generic ShapeSize Source # | |
type Rep ShapeSize Source # | |
Defined in DzenDhall.Config type Rep ShapeSize = D1 (MetaData "ShapeSize" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "ShapeSize" PrefixI True) (S1 (MetaSel (Just "_shapeSizeW") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "_shapeSizeH") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
Instances
Eq Variable Source # | |
Show Variable Source # | |
Generic Variable Source # | |
type Rep Variable Source # | |
Defined in DzenDhall.Config type Rep Variable = D1 (MetaData "Variable" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Variable" PrefixI True) (S1 (MetaSel (Just "_varName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "_varValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) |
TokOpen OpeningTag | |
TokClose | |
TokSeparator | |
TokTxt Text | |
TokSource Source | |
TokMarkup Text | |
TokI Text | |
TokR ShapeSize | |
TokRO ShapeSize | |
TokC Int | |
TokCO Int | |
TokCheck Check | |
TokDefine Variable |
Instances
Instances
Eq Source Source # | |
Show Source Source # | |
Generic Source Source # | |
Hashable Source Source # | |
Defined in DzenDhall.Config | |
type Rep Source Source # | |
Defined in DzenDhall.Config type Rep Source = D1 (MetaData "Source" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Source" PrefixI True) ((S1 (MetaSel (Just "updateInterval") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Int)) :*: S1 (MetaSel (Just "command") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Just "input") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Just "escape") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) |
data Configuration Source #
Instances
Eq Configuration Source # | |
Defined in DzenDhall.Config (==) :: Configuration -> Configuration -> Bool # (/=) :: Configuration -> Configuration -> Bool # | |
Show Configuration Source # | |
Defined in DzenDhall.Config showsPrec :: Int -> Configuration -> ShowS # show :: Configuration -> String # showList :: [Configuration] -> ShowS # | |
Generic Configuration Source # | |
Defined in DzenDhall.Config type Rep Configuration :: Type -> Type # from :: Configuration -> Rep Configuration x # to :: Rep Configuration x -> Configuration # | |
type Rep Configuration Source # | |
Defined in DzenDhall.Config type Rep Configuration = D1 (MetaData "Configuration" "DzenDhall.Config" "dzen-dhall-1.0.2-1DjeyjLENUgKHKuAgVFJmg" False) (C1 (MetaCons "Configuration" PrefixI True) (S1 (MetaSel (Just "_cfgBarTokens") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Token]) :*: S1 (MetaSel (Just "_cfgBarSettings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BarSettings))) |
data PluginMeta Source #
PluginMeta | |
|
Instances
pmUpstream :: Lens' PluginMeta (Maybe Text) Source #
pmHomePage :: Lens' PluginMeta (Maybe Text) Source #