-- A collection of Themes.
module Yi.Style.Library where

import Yi.Style
import Data.Prototype

type Theme = Proto UIStyle

-- | Abstract theme that provides useful defaults.
defaultTheme :: Theme
defaultTheme :: Theme
defaultTheme = (UIStyle -> UIStyle) -> Theme
forall a. (a -> a) -> Proto a
Proto ((UIStyle -> UIStyle) -> Theme) -> (UIStyle -> UIStyle) -> Theme
forall a b. (a -> b) -> a -> b
$ UIStyle -> UIStyle -> UIStyle
forall a b. a -> b -> a
const UIStyle :: Attributes
-> Style
-> Attributes
-> Style
-> Style
-> Attributes
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> Style
-> UIStyle
UIStyle
  { modelineAttributes :: Attributes
modelineAttributes = Attributes
emptyAttributes { foreground :: Color
foreground = Color
white, background :: Color
background = Color
grey }
  , modelineFocusStyle :: Style
modelineFocusStyle = Color -> Style
withFg Color
brightwhite

  , tabBarAttributes :: Attributes
tabBarAttributes   = Attributes
emptyAttributes
  , tabInFocusStyle :: Style
tabInFocusStyle    = Color -> Style
withFg Color
black Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
white
  , tabNotFocusedStyle :: Style
tabNotFocusedStyle = Style
forall a. Monoid a => a
mempty

  , baseAttributes :: Attributes
baseAttributes     = Attributes
emptyAttributes

  , selectedStyle :: Style
selectedStyle      = Color -> Style
withFg Color
white Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
purple
  , eofStyle :: Style
eofStyle           = Color -> Style
withFg Color
blue
  , errorStyle :: Style
errorStyle         = Color -> Style
withBg Color
red
  , hintStyle :: Style
hintStyle          = Color -> Style
withFg Color
black Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
cyan
  , strongHintStyle :: Style
strongHintStyle    = Color -> Style
withFg Color
black Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
magenta

  , commentStyle :: Style
commentStyle       = Color -> Style
withFg Color
purple
  , blockCommentStyle :: Style
blockCommentStyle  = Color -> Style
withFg Color
purple
  , keywordStyle :: Style
keywordStyle       = Color -> Style
withFg Color
darkblue
  , numberStyle :: Style
numberStyle        = Color -> Style
withFg Color
darkred
  , preprocessorStyle :: Style
preprocessorStyle  = Color -> Style
withFg Color
red
  , stringStyle :: Style
stringStyle        = Color -> Style
withFg Color
darkcyan
  , longStringStyle :: Style
longStringStyle    = Style
forall a. Monoid a => a
mempty
  , typeStyle :: Style
typeStyle          = Color -> Style
withFg Color
darkgreen
  , dataConstructorStyle :: Style
dataConstructorStyle
                       = Bool -> Style
withBd Bool
True Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withFg Color
darkgreen
  , importStyle :: Style
importStyle        = Color -> Style
withFg Color
blue
  , builtinStyle :: Style
builtinStyle       = Color -> Style
withFg Color
blue
  , regexStyle :: Style
regexStyle         = Color -> Style
withFg Color
red
  , variableStyle :: Style
variableStyle      = Style
forall a. Monoid a => a
mempty
  , operatorStyle :: Style
operatorStyle      = Color -> Style
withFg Color
brown
  , makeFileRuleHead :: Style
makeFileRuleHead   = Color -> Style
withFg Color
blue
  , makeFileAction :: Style
makeFileAction     = Color -> Style
withFg Color
grey
  , quoteStyle :: Style
quoteStyle         = Color -> Style
withFg Color
grey
  }

-- | A Theme inspired by the darkblue colorscheme of Vim.
darkBlueTheme :: Theme
darkBlueTheme :: Theme
darkBlueTheme = Theme
defaultTheme Theme -> (UIStyle -> UIStyle -> UIStyle) -> Theme
forall a. Proto a -> (a -> a -> a) -> Proto a
`override` \UIStyle
super UIStyle
_ -> UIStyle
super
  { modelineAttributes :: Attributes
modelineAttributes = Attributes
emptyAttributes { foreground :: Color
foreground = Color
darkblue, background :: Color
background = Color
white }
  , modelineFocusStyle :: Style
modelineFocusStyle = Color -> Style
withBg Color
brightwhite

  , tabBarAttributes :: Attributes
tabBarAttributes   = Attributes
emptyAttributes { foreground :: Color
foreground = Color
darkblue, background :: Color
background = Color
brightwhite }
  , tabInFocusStyle :: Style
tabInFocusStyle    = Color -> Style
withFg Color
grey Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
white
  , tabNotFocusedStyle :: Style
tabNotFocusedStyle = Color -> Style
withFg Color
lightGrey Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
white

  , baseAttributes :: Attributes
baseAttributes     = Attributes
emptyAttributes { foreground :: Color
foreground = Color
white,    background :: Color
background = Color
black }

  , selectedStyle :: Style
selectedStyle      = Color -> Style
withFg Color
white Style -> Style -> Style
forall a. Monoid a => a -> a -> a
`mappend` Color -> Style
withBg Color
blue
  , eofStyle :: Style
eofStyle           = Color -> Style
withFg Color
red
  , hintStyle :: Style
hintStyle          = Color -> Style
withBg Color
darkblue
  , strongHintStyle :: Style
strongHintStyle    = Color -> Style
withBg Color
blue

  , commentStyle :: Style
commentStyle       = Color -> Style
withFg Color
darkred
  , keywordStyle :: Style
keywordStyle       = Color -> Style
withFg Color
brown
  , stringStyle :: Style
stringStyle        = Color -> Style
withFg Color
purple
  , variableStyle :: Style
variableStyle      = Color -> Style
withFg Color
cyan
  , operatorStyle :: Style
operatorStyle      = Color -> Style
withFg Color
brown
  }