module Rasa.Internal.Styles
( fg
, bg
, flair
, Color(..)
, Flair(..)
, Style(..)
, Styles
, addStyleProvider
, getStyles
) where
import Eve
import Rasa.Internal.Range
import Rasa.Internal.Buffer
import Rasa.Internal.BufActions
import Control.Applicative
import Data.Default
data Color =
Black
| Red
| Green
| Yellow
| Blue
| Magenta
| Cyan
| White
| DefColor
deriving (Show, Eq)
data Flair =
Standout
| Underline
| ReverseVideo
| Blink
| Dim
| Bold
| DefFlair
deriving (Show, Eq)
newtype Style = Style (Maybe Color, Maybe Color, Maybe Flair)
deriving (Show, Eq)
instance Default Style where
def = Style (Just DefColor, Just DefColor, Just DefFlair)
instance Monoid Style where
Style (a, b, c) `mappend` Style (a', b', c') = Style (a' <|> a, b' <|> b, c' <|> c)
mempty = Style (Nothing, Nothing, Nothing)
type Styles = [Span CrdRange Style]
newtype StyleMap =
StyleMap Styles
deriving (Show, Eq, Monoid)
instance Default StyleMap where
def = StyleMap []
fg :: Color -> Style
fg a = Style (Just a, Nothing, Nothing)
bg :: Color -> Style
bg a = Style (Nothing, Just a, Nothing)
flair :: Flair -> Style
flair a = Style (Nothing, Nothing, Just a)
data ComputeStyles = ComputeStyles
addStyleProvider :: BufAction Styles -> BufAction ListenerId
addStyleProvider provider = addBufListener (const provider :: ComputeStyles -> BufAction Styles)
getStyles :: BufAction Styles
getStyles = dispatchBufEvent ComputeStyles