{-# LANGUAGE StrictData #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-}
module Skylighting.Types (
ContextName
, KeywordAttr(..)
, WordSet(..)
, makeWordSet
, inWordSet
, ListItem(..)
, Matcher(..)
, Rule(..)
, Context(..)
, ContextSwitch(..)
, Syntax(..)
, SyntaxMap
, Token
, TokenType(..)
, SourceLine
, LineNo(..)
, TokenStyle(..)
, defStyle
, Color(..)
, ToColor(..)
, FromColor(..)
, Style(..)
, ANSIColorLevel(..)
, FormatOptions(..)
, defaultFormatOpts
) where
import Control.Monad (mplus)
import Data.Aeson
import Data.Aeson.Types (toJSONKeyText)
import Data.Binary (Binary)
import Data.Bits
import Data.CaseInsensitive (FoldCase (..))
import Data.Colour.SRGB (Colour, sRGB24, toSRGB24)
import qualified Data.Colour.SRGB as Colour
import Data.Data (Data)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Typeable (Typeable)
import Data.Word
import GHC.Generics (Generic)
import Safe (readMay)
import Skylighting.Regex
import Text.Printf
type ContextName = (Text, Text)
data KeywordAttr =
KeywordAttr { KeywordAttr -> Bool
keywordCaseSensitive :: !Bool
, KeywordAttr -> Set Char
keywordDelims :: !(Set.Set Char)
}
deriving (Int -> KeywordAttr -> ShowS
[KeywordAttr] -> ShowS
KeywordAttr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [KeywordAttr] -> ShowS
$cshowList :: [KeywordAttr] -> ShowS
show :: KeywordAttr -> String
$cshow :: KeywordAttr -> String
showsPrec :: Int -> KeywordAttr -> ShowS
$cshowsPrec :: Int -> KeywordAttr -> ShowS
Show, ReadPrec [KeywordAttr]
ReadPrec KeywordAttr
Int -> ReadS KeywordAttr
ReadS [KeywordAttr]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [KeywordAttr]
$creadListPrec :: ReadPrec [KeywordAttr]
readPrec :: ReadPrec KeywordAttr
$creadPrec :: ReadPrec KeywordAttr
readList :: ReadS [KeywordAttr]
$creadList :: ReadS [KeywordAttr]
readsPrec :: Int -> ReadS KeywordAttr
$creadsPrec :: Int -> ReadS KeywordAttr
Read, KeywordAttr -> KeywordAttr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeywordAttr -> KeywordAttr -> Bool
$c/= :: KeywordAttr -> KeywordAttr -> Bool
== :: KeywordAttr -> KeywordAttr -> Bool
$c== :: KeywordAttr -> KeywordAttr -> Bool
Eq, Eq KeywordAttr
KeywordAttr -> KeywordAttr -> Bool
KeywordAttr -> KeywordAttr -> Ordering
KeywordAttr -> KeywordAttr -> KeywordAttr
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: KeywordAttr -> KeywordAttr -> KeywordAttr
$cmin :: KeywordAttr -> KeywordAttr -> KeywordAttr
max :: KeywordAttr -> KeywordAttr -> KeywordAttr
$cmax :: KeywordAttr -> KeywordAttr -> KeywordAttr
>= :: KeywordAttr -> KeywordAttr -> Bool
$c>= :: KeywordAttr -> KeywordAttr -> Bool
> :: KeywordAttr -> KeywordAttr -> Bool
$c> :: KeywordAttr -> KeywordAttr -> Bool
<= :: KeywordAttr -> KeywordAttr -> Bool
$c<= :: KeywordAttr -> KeywordAttr -> Bool
< :: KeywordAttr -> KeywordAttr -> Bool
$c< :: KeywordAttr -> KeywordAttr -> Bool
compare :: KeywordAttr -> KeywordAttr -> Ordering
$ccompare :: KeywordAttr -> KeywordAttr -> Ordering
Ord, Typeable KeywordAttr
KeywordAttr -> DataType
KeywordAttr -> Constr
(forall b. Data b => b -> b) -> KeywordAttr -> KeywordAttr
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> KeywordAttr -> u
forall u. (forall d. Data d => d -> u) -> KeywordAttr -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KeywordAttr
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KeywordAttr -> c KeywordAttr
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KeywordAttr)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KeywordAttr)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> KeywordAttr -> m KeywordAttr
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KeywordAttr -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> KeywordAttr -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> KeywordAttr -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> KeywordAttr -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> KeywordAttr -> r
gmapT :: (forall b. Data b => b -> b) -> KeywordAttr -> KeywordAttr
$cgmapT :: (forall b. Data b => b -> b) -> KeywordAttr -> KeywordAttr
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KeywordAttr)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c KeywordAttr)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KeywordAttr)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c KeywordAttr)
dataTypeOf :: KeywordAttr -> DataType
$cdataTypeOf :: KeywordAttr -> DataType
toConstr :: KeywordAttr -> Constr
$ctoConstr :: KeywordAttr -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KeywordAttr
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c KeywordAttr
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KeywordAttr -> c KeywordAttr
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> KeywordAttr -> c KeywordAttr
Data, Typeable, forall x. Rep KeywordAttr x -> KeywordAttr
forall x. KeywordAttr -> Rep KeywordAttr x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep KeywordAttr x -> KeywordAttr
$cfrom :: forall x. KeywordAttr -> Rep KeywordAttr x
Generic)
instance Binary KeywordAttr
data WordSet a = CaseSensitiveWords !(Set.Set a)
| CaseInsensitiveWords !(Set.Set a)
deriving (Int -> WordSet a -> ShowS
forall a. Show a => Int -> WordSet a -> ShowS
forall a. Show a => [WordSet a] -> ShowS
forall a. Show a => WordSet a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WordSet a] -> ShowS
$cshowList :: forall a. Show a => [WordSet a] -> ShowS
show :: WordSet a -> String
$cshow :: forall a. Show a => WordSet a -> String
showsPrec :: Int -> WordSet a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> WordSet a -> ShowS
Show, ReadPrec [WordSet a]
ReadPrec (WordSet a)
ReadS [WordSet a]
forall a. (Read a, Ord a) => ReadPrec [WordSet a]
forall a. (Read a, Ord a) => ReadPrec (WordSet a)
forall a. (Read a, Ord a) => Int -> ReadS (WordSet a)
forall a. (Read a, Ord a) => ReadS [WordSet a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [WordSet a]
$creadListPrec :: forall a. (Read a, Ord a) => ReadPrec [WordSet a]
readPrec :: ReadPrec (WordSet a)
$creadPrec :: forall a. (Read a, Ord a) => ReadPrec (WordSet a)
readList :: ReadS [WordSet a]
$creadList :: forall a. (Read a, Ord a) => ReadS [WordSet a]
readsPrec :: Int -> ReadS (WordSet a)
$creadsPrec :: forall a. (Read a, Ord a) => Int -> ReadS (WordSet a)
Read, WordSet a -> WordSet a -> Bool
forall a. Eq a => WordSet a -> WordSet a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: WordSet a -> WordSet a -> Bool
$c/= :: forall a. Eq a => WordSet a -> WordSet a -> Bool
== :: WordSet a -> WordSet a -> Bool
$c== :: forall a. Eq a => WordSet a -> WordSet a -> Bool
Eq, WordSet a -> WordSet a -> Bool
WordSet a -> WordSet a -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a}. Ord a => Eq (WordSet a)
forall a. Ord a => WordSet a -> WordSet a -> Bool
forall a. Ord a => WordSet a -> WordSet a -> Ordering
forall a. Ord a => WordSet a -> WordSet a -> WordSet a
min :: WordSet a -> WordSet a -> WordSet a
$cmin :: forall a. Ord a => WordSet a -> WordSet a -> WordSet a
max :: WordSet a -> WordSet a -> WordSet a
$cmax :: forall a. Ord a => WordSet a -> WordSet a -> WordSet a
>= :: WordSet a -> WordSet a -> Bool
$c>= :: forall a. Ord a => WordSet a -> WordSet a -> Bool
> :: WordSet a -> WordSet a -> Bool
$c> :: forall a. Ord a => WordSet a -> WordSet a -> Bool
<= :: WordSet a -> WordSet a -> Bool
$c<= :: forall a. Ord a => WordSet a -> WordSet a -> Bool
< :: WordSet a -> WordSet a -> Bool
$c< :: forall a. Ord a => WordSet a -> WordSet a -> Bool
compare :: WordSet a -> WordSet a -> Ordering
$ccompare :: forall a. Ord a => WordSet a -> WordSet a -> Ordering
Ord, WordSet a -> DataType
WordSet a -> Constr
forall {a}. (Data a, Ord a) => Typeable (WordSet a)
forall a. (Data a, Ord a) => WordSet a -> DataType
forall a. (Data a, Ord a) => WordSet a -> Constr
forall a.
(Data a, Ord a) =>
(forall b. Data b => b -> b) -> WordSet a -> WordSet a
forall a u.
(Data a, Ord a) =>
Int -> (forall d. Data d => d -> u) -> WordSet a -> u
forall a u.
(Data a, Ord a) =>
(forall d. Data d => d -> u) -> WordSet a -> [u]
forall a r r'.
(Data a, Ord a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WordSet a -> r
forall a r r'.
(Data a, Ord a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WordSet a -> r
forall a (m :: * -> *).
(Data a, Ord a, Monad m) =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
forall a (m :: * -> *).
(Data a, Ord a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
forall a (c :: * -> *).
(Data a, Ord a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WordSet a)
forall a (c :: * -> *).
(Data a, Ord a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WordSet a -> c (WordSet a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (WordSet a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WordSet a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WordSet a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WordSet a -> c (WordSet a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (WordSet a))
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, Ord a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, Ord a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Ord a, Monad m) =>
(forall d. Data d => d -> m d) -> WordSet a -> m (WordSet a)
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> WordSet a -> u
$cgmapQi :: forall a u.
(Data a, Ord a) =>
Int -> (forall d. Data d => d -> u) -> WordSet a -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> WordSet a -> [u]
$cgmapQ :: forall a u.
(Data a, Ord a) =>
(forall d. Data d => d -> u) -> WordSet a -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WordSet a -> r
$cgmapQr :: forall a r r'.
(Data a, Ord a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> WordSet a -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WordSet a -> r
$cgmapQl :: forall a r r'.
(Data a, Ord a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> WordSet a -> r
gmapT :: (forall b. Data b => b -> b) -> WordSet a -> WordSet a
$cgmapT :: forall a.
(Data a, Ord a) =>
(forall b. Data b => b -> b) -> WordSet a -> WordSet a
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WordSet a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (WordSet a))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (WordSet a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Ord a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (WordSet a))
dataTypeOf :: WordSet a -> DataType
$cdataTypeOf :: forall a. (Data a, Ord a) => WordSet a -> DataType
toConstr :: WordSet a -> Constr
$ctoConstr :: forall a. (Data a, Ord a) => WordSet a -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WordSet a)
$cgunfold :: forall a (c :: * -> *).
(Data a, Ord a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (WordSet a)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WordSet a -> c (WordSet a)
$cgfoldl :: forall a (c :: * -> *).
(Data a, Ord a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> WordSet a -> c (WordSet a)
Data, Typeable, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (WordSet a) x -> WordSet a
forall a x. WordSet a -> Rep (WordSet a) x
$cto :: forall a x. Rep (WordSet a) x -> WordSet a
$cfrom :: forall a x. WordSet a -> Rep (WordSet a) x
Generic)
instance Binary a => Binary (WordSet a)
makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a
makeWordSet :: forall a. (FoldCase a, Ord a) => Bool -> [a] -> WordSet a
makeWordSet Bool
True [a]
ws = forall a. Set a -> WordSet a
CaseSensitiveWords (forall a. Ord a => [a] -> Set a
Set.fromList [a]
ws)
makeWordSet Bool
False [a]
ws = forall a. Set a -> WordSet a
CaseInsensitiveWords (forall a. Ord a => [a] -> Set a
Set.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall s. FoldCase s => s -> s
foldCase [a]
ws)
inWordSet :: (FoldCase a, Ord a) => a -> WordSet a -> Bool
inWordSet :: forall a. (FoldCase a, Ord a) => a -> WordSet a -> Bool
inWordSet a
w (CaseInsensitiveWords Set a
ws) = forall s. FoldCase s => s -> s
foldCase a
w forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
ws
inWordSet a
w (CaseSensitiveWords Set a
ws) = a
w forall a. Ord a => a -> Set a -> Bool
`Set.member` Set a
ws
data Matcher =
DetectChar !Char
| Detect2Chars !Char !Char
| AnyChar !(Set.Set Char)
| RangeDetect !Char !Char
| StringDetect !Text
| WordDetect !Text
| RegExpr !RE
| Keyword !KeywordAttr (Either Text (WordSet Text))
| Int
| Float
| HlCOct
| HlCHex
| HlCStringChar
| HlCChar
| LineContinue
| IncludeRules !ContextName
| DetectSpaces
| DetectIdentifier
deriving (Int -> Matcher -> ShowS
[Matcher] -> ShowS
Matcher -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Matcher] -> ShowS
$cshowList :: [Matcher] -> ShowS
show :: Matcher -> String
$cshow :: Matcher -> String
showsPrec :: Int -> Matcher -> ShowS
$cshowsPrec :: Int -> Matcher -> ShowS
Show, ReadPrec [Matcher]
ReadPrec Matcher
Int -> ReadS Matcher
ReadS [Matcher]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Matcher]
$creadListPrec :: ReadPrec [Matcher]
readPrec :: ReadPrec Matcher
$creadPrec :: ReadPrec Matcher
readList :: ReadS [Matcher]
$creadList :: ReadS [Matcher]
readsPrec :: Int -> ReadS Matcher
$creadsPrec :: Int -> ReadS Matcher
Read, Matcher -> Matcher -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Matcher -> Matcher -> Bool
$c/= :: Matcher -> Matcher -> Bool
== :: Matcher -> Matcher -> Bool
$c== :: Matcher -> Matcher -> Bool
Eq, Eq Matcher
Matcher -> Matcher -> Bool
Matcher -> Matcher -> Ordering
Matcher -> Matcher -> Matcher
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Matcher -> Matcher -> Matcher
$cmin :: Matcher -> Matcher -> Matcher
max :: Matcher -> Matcher -> Matcher
$cmax :: Matcher -> Matcher -> Matcher
>= :: Matcher -> Matcher -> Bool
$c>= :: Matcher -> Matcher -> Bool
> :: Matcher -> Matcher -> Bool
$c> :: Matcher -> Matcher -> Bool
<= :: Matcher -> Matcher -> Bool
$c<= :: Matcher -> Matcher -> Bool
< :: Matcher -> Matcher -> Bool
$c< :: Matcher -> Matcher -> Bool
compare :: Matcher -> Matcher -> Ordering
$ccompare :: Matcher -> Matcher -> Ordering
Ord, Typeable Matcher
Matcher -> DataType
Matcher -> Constr
(forall b. Data b => b -> b) -> Matcher -> Matcher
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Matcher -> u
forall u. (forall d. Data d => d -> u) -> Matcher -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Matcher -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Matcher -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Matcher
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Matcher -> c Matcher
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Matcher)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Matcher)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Matcher -> m Matcher
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Matcher -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Matcher -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Matcher -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Matcher -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Matcher -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Matcher -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Matcher -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Matcher -> r
gmapT :: (forall b. Data b => b -> b) -> Matcher -> Matcher
$cgmapT :: (forall b. Data b => b -> b) -> Matcher -> Matcher
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Matcher)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Matcher)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Matcher)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Matcher)
dataTypeOf :: Matcher -> DataType
$cdataTypeOf :: Matcher -> DataType
toConstr :: Matcher -> Constr
$ctoConstr :: Matcher -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Matcher
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Matcher
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Matcher -> c Matcher
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Matcher -> c Matcher
Data, Typeable, forall x. Rep Matcher x -> Matcher
forall x. Matcher -> Rep Matcher x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Matcher x -> Matcher
$cfrom :: forall x. Matcher -> Rep Matcher x
Generic)
instance Binary Matcher
data ContextSwitch =
Pop | Push !ContextName
deriving (Int -> ContextSwitch -> ShowS
[ContextSwitch] -> ShowS
ContextSwitch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ContextSwitch] -> ShowS
$cshowList :: [ContextSwitch] -> ShowS
show :: ContextSwitch -> String
$cshow :: ContextSwitch -> String
showsPrec :: Int -> ContextSwitch -> ShowS
$cshowsPrec :: Int -> ContextSwitch -> ShowS
Show, ReadPrec [ContextSwitch]
ReadPrec ContextSwitch
Int -> ReadS ContextSwitch
ReadS [ContextSwitch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ContextSwitch]
$creadListPrec :: ReadPrec [ContextSwitch]
readPrec :: ReadPrec ContextSwitch
$creadPrec :: ReadPrec ContextSwitch
readList :: ReadS [ContextSwitch]
$creadList :: ReadS [ContextSwitch]
readsPrec :: Int -> ReadS ContextSwitch
$creadsPrec :: Int -> ReadS ContextSwitch
Read, ContextSwitch -> ContextSwitch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ContextSwitch -> ContextSwitch -> Bool
$c/= :: ContextSwitch -> ContextSwitch -> Bool
== :: ContextSwitch -> ContextSwitch -> Bool
$c== :: ContextSwitch -> ContextSwitch -> Bool
Eq, Eq ContextSwitch
ContextSwitch -> ContextSwitch -> Bool
ContextSwitch -> ContextSwitch -> Ordering
ContextSwitch -> ContextSwitch -> ContextSwitch
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ContextSwitch -> ContextSwitch -> ContextSwitch
$cmin :: ContextSwitch -> ContextSwitch -> ContextSwitch
max :: ContextSwitch -> ContextSwitch -> ContextSwitch
$cmax :: ContextSwitch -> ContextSwitch -> ContextSwitch
>= :: ContextSwitch -> ContextSwitch -> Bool
$c>= :: ContextSwitch -> ContextSwitch -> Bool
> :: ContextSwitch -> ContextSwitch -> Bool
$c> :: ContextSwitch -> ContextSwitch -> Bool
<= :: ContextSwitch -> ContextSwitch -> Bool
$c<= :: ContextSwitch -> ContextSwitch -> Bool
< :: ContextSwitch -> ContextSwitch -> Bool
$c< :: ContextSwitch -> ContextSwitch -> Bool
compare :: ContextSwitch -> ContextSwitch -> Ordering
$ccompare :: ContextSwitch -> ContextSwitch -> Ordering
Ord, Typeable ContextSwitch
ContextSwitch -> DataType
ContextSwitch -> Constr
(forall b. Data b => b -> b) -> ContextSwitch -> ContextSwitch
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ContextSwitch -> u
forall u. (forall d. Data d => d -> u) -> ContextSwitch -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ContextSwitch
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ContextSwitch -> c ContextSwitch
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ContextSwitch)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ContextSwitch)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ContextSwitch -> m ContextSwitch
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ContextSwitch -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ContextSwitch -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ContextSwitch -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ContextSwitch -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ContextSwitch -> r
gmapT :: (forall b. Data b => b -> b) -> ContextSwitch -> ContextSwitch
$cgmapT :: (forall b. Data b => b -> b) -> ContextSwitch -> ContextSwitch
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ContextSwitch)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ContextSwitch)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ContextSwitch)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ContextSwitch)
dataTypeOf :: ContextSwitch -> DataType
$cdataTypeOf :: ContextSwitch -> DataType
toConstr :: ContextSwitch -> Constr
$ctoConstr :: ContextSwitch -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ContextSwitch
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ContextSwitch
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ContextSwitch -> c ContextSwitch
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ContextSwitch -> c ContextSwitch
Data, Typeable, forall x. Rep ContextSwitch x -> ContextSwitch
forall x. ContextSwitch -> Rep ContextSwitch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ContextSwitch x -> ContextSwitch
$cfrom :: forall x. ContextSwitch -> Rep ContextSwitch x
Generic)
instance Binary ContextSwitch
data Rule = Rule{
Rule -> Matcher
rMatcher :: !Matcher
, Rule -> TokenType
rAttribute :: !TokenType
, Rule -> Bool
rIncludeAttribute :: !Bool
, Rule -> Bool
rDynamic :: !Bool
, Rule -> Bool
rCaseSensitive :: !Bool
, Rule -> [Rule]
rChildren :: ![Rule]
, Rule -> Bool
rLookahead :: !Bool
, Rule -> Bool
rFirstNonspace :: !Bool
, Rule -> Maybe Int
rColumn :: !(Maybe Int)
, Rule -> [ContextSwitch]
rContextSwitch :: ![ContextSwitch]
} deriving (Int -> Rule -> ShowS
[Rule] -> ShowS
Rule -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Rule] -> ShowS
$cshowList :: [Rule] -> ShowS
show :: Rule -> String
$cshow :: Rule -> String
showsPrec :: Int -> Rule -> ShowS
$cshowsPrec :: Int -> Rule -> ShowS
Show, ReadPrec [Rule]
ReadPrec Rule
Int -> ReadS Rule
ReadS [Rule]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Rule]
$creadListPrec :: ReadPrec [Rule]
readPrec :: ReadPrec Rule
$creadPrec :: ReadPrec Rule
readList :: ReadS [Rule]
$creadList :: ReadS [Rule]
readsPrec :: Int -> ReadS Rule
$creadsPrec :: Int -> ReadS Rule
Read, Rule -> Rule -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Rule -> Rule -> Bool
$c/= :: Rule -> Rule -> Bool
== :: Rule -> Rule -> Bool
$c== :: Rule -> Rule -> Bool
Eq, Eq Rule
Rule -> Rule -> Bool
Rule -> Rule -> Ordering
Rule -> Rule -> Rule
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Rule -> Rule -> Rule
$cmin :: Rule -> Rule -> Rule
max :: Rule -> Rule -> Rule
$cmax :: Rule -> Rule -> Rule
>= :: Rule -> Rule -> Bool
$c>= :: Rule -> Rule -> Bool
> :: Rule -> Rule -> Bool
$c> :: Rule -> Rule -> Bool
<= :: Rule -> Rule -> Bool
$c<= :: Rule -> Rule -> Bool
< :: Rule -> Rule -> Bool
$c< :: Rule -> Rule -> Bool
compare :: Rule -> Rule -> Ordering
$ccompare :: Rule -> Rule -> Ordering
Ord, Typeable Rule
Rule -> DataType
Rule -> Constr
(forall b. Data b => b -> b) -> Rule -> Rule
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Rule -> u
forall u. (forall d. Data d => d -> u) -> Rule -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rule
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rule -> c Rule
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rule)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Rule -> m Rule
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rule -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Rule -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Rule -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Rule -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Rule -> r
gmapT :: (forall b. Data b => b -> b) -> Rule -> Rule
$cgmapT :: (forall b. Data b => b -> b) -> Rule -> Rule
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Rule)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rule)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Rule)
dataTypeOf :: Rule -> DataType
$cdataTypeOf :: Rule -> DataType
toConstr :: Rule -> Constr
$ctoConstr :: Rule -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rule
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Rule
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rule -> c Rule
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Rule -> c Rule
Data, Typeable, forall x. Rep Rule x -> Rule
forall x. Rule -> Rep Rule x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Rule x -> Rule
$cfrom :: forall x. Rule -> Rep Rule x
Generic)
instance Binary Rule
data ListItem = Item !Text | IncludeList !(Text, Text)
deriving (Int -> ListItem -> ShowS
[ListItem] -> ShowS
ListItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListItem] -> ShowS
$cshowList :: [ListItem] -> ShowS
show :: ListItem -> String
$cshow :: ListItem -> String
showsPrec :: Int -> ListItem -> ShowS
$cshowsPrec :: Int -> ListItem -> ShowS
Show, ListItem -> ListItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListItem -> ListItem -> Bool
$c/= :: ListItem -> ListItem -> Bool
== :: ListItem -> ListItem -> Bool
$c== :: ListItem -> ListItem -> Bool
Eq, Eq ListItem
ListItem -> ListItem -> Bool
ListItem -> ListItem -> Ordering
ListItem -> ListItem -> ListItem
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ListItem -> ListItem -> ListItem
$cmin :: ListItem -> ListItem -> ListItem
max :: ListItem -> ListItem -> ListItem
$cmax :: ListItem -> ListItem -> ListItem
>= :: ListItem -> ListItem -> Bool
$c>= :: ListItem -> ListItem -> Bool
> :: ListItem -> ListItem -> Bool
$c> :: ListItem -> ListItem -> Bool
<= :: ListItem -> ListItem -> Bool
$c<= :: ListItem -> ListItem -> Bool
< :: ListItem -> ListItem -> Bool
$c< :: ListItem -> ListItem -> Bool
compare :: ListItem -> ListItem -> Ordering
$ccompare :: ListItem -> ListItem -> Ordering
Ord, ReadPrec [ListItem]
ReadPrec ListItem
Int -> ReadS ListItem
ReadS [ListItem]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListItem]
$creadListPrec :: ReadPrec [ListItem]
readPrec :: ReadPrec ListItem
$creadPrec :: ReadPrec ListItem
readList :: ReadS [ListItem]
$creadList :: ReadS [ListItem]
readsPrec :: Int -> ReadS ListItem
$creadsPrec :: Int -> ReadS ListItem
Read, Typeable ListItem
ListItem -> DataType
ListItem -> Constr
(forall b. Data b => b -> b) -> ListItem -> ListItem
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> ListItem -> u
forall u. (forall d. Data d => d -> u) -> ListItem -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListItem -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListItem -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListItem
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListItem -> c ListItem
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListItem)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListItem)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> ListItem -> m ListItem
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListItem -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> ListItem -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ListItem -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ListItem -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListItem -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ListItem -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListItem -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ListItem -> r
gmapT :: (forall b. Data b => b -> b) -> ListItem -> ListItem
$cgmapT :: (forall b. Data b => b -> b) -> ListItem -> ListItem
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListItem)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ListItem)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListItem)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ListItem)
dataTypeOf :: ListItem -> DataType
$cdataTypeOf :: ListItem -> DataType
toConstr :: ListItem -> Constr
$ctoConstr :: ListItem -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListItem
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ListItem
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListItem -> c ListItem
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ListItem -> c ListItem
Data, Typeable, forall x. Rep ListItem x -> ListItem
forall x. ListItem -> Rep ListItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListItem x -> ListItem
$cfrom :: forall x. ListItem -> Rep ListItem x
Generic)
instance Binary ListItem
data Syntax = Syntax{
Syntax -> Text
sName :: !Text
, Syntax -> String
sFilename :: !String
, Syntax -> Text
sShortname :: !Text
, Syntax -> Map Text [ListItem]
sLists :: !(Map.Map Text [ListItem])
, Syntax -> Map Text Context
sContexts :: !(Map.Map Text Context)
, Syntax -> Text
sAuthor :: !Text
, Syntax -> Text
sVersion :: !Text
, Syntax -> Text
sLicense :: !Text
, Syntax -> [String]
sExtensions :: ![String]
, Syntax -> Text
sStartingContext :: !Text
} deriving (Int -> Syntax -> ShowS
[Syntax] -> ShowS
Syntax -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Syntax] -> ShowS
$cshowList :: [Syntax] -> ShowS
show :: Syntax -> String
$cshow :: Syntax -> String
showsPrec :: Int -> Syntax -> ShowS
$cshowsPrec :: Int -> Syntax -> ShowS
Show, ReadPrec [Syntax]
ReadPrec Syntax
Int -> ReadS Syntax
ReadS [Syntax]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Syntax]
$creadListPrec :: ReadPrec [Syntax]
readPrec :: ReadPrec Syntax
$creadPrec :: ReadPrec Syntax
readList :: ReadS [Syntax]
$creadList :: ReadS [Syntax]
readsPrec :: Int -> ReadS Syntax
$creadsPrec :: Int -> ReadS Syntax
Read, Syntax -> Syntax -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Syntax -> Syntax -> Bool
$c/= :: Syntax -> Syntax -> Bool
== :: Syntax -> Syntax -> Bool
$c== :: Syntax -> Syntax -> Bool
Eq, Eq Syntax
Syntax -> Syntax -> Bool
Syntax -> Syntax -> Ordering
Syntax -> Syntax -> Syntax
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Syntax -> Syntax -> Syntax
$cmin :: Syntax -> Syntax -> Syntax
max :: Syntax -> Syntax -> Syntax
$cmax :: Syntax -> Syntax -> Syntax
>= :: Syntax -> Syntax -> Bool
$c>= :: Syntax -> Syntax -> Bool
> :: Syntax -> Syntax -> Bool
$c> :: Syntax -> Syntax -> Bool
<= :: Syntax -> Syntax -> Bool
$c<= :: Syntax -> Syntax -> Bool
< :: Syntax -> Syntax -> Bool
$c< :: Syntax -> Syntax -> Bool
compare :: Syntax -> Syntax -> Ordering
$ccompare :: Syntax -> Syntax -> Ordering
Ord, Typeable Syntax
Syntax -> DataType
Syntax -> Constr
(forall b. Data b => b -> b) -> Syntax -> Syntax
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Syntax -> u
forall u. (forall d. Data d => d -> u) -> Syntax -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Syntax
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Syntax -> c Syntax
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Syntax)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Syntax)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Syntax -> m Syntax
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Syntax -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Syntax -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Syntax -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Syntax -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Syntax -> r
gmapT :: (forall b. Data b => b -> b) -> Syntax -> Syntax
$cgmapT :: (forall b. Data b => b -> b) -> Syntax -> Syntax
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Syntax)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Syntax)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Syntax)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Syntax)
dataTypeOf :: Syntax -> DataType
$cdataTypeOf :: Syntax -> DataType
toConstr :: Syntax -> Constr
$ctoConstr :: Syntax -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Syntax
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Syntax
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Syntax -> c Syntax
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Syntax -> c Syntax
Data, Typeable, forall x. Rep Syntax x -> Syntax
forall x. Syntax -> Rep Syntax x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Syntax x -> Syntax
$cfrom :: forall x. Syntax -> Rep Syntax x
Generic)
instance Binary Syntax
type SyntaxMap = Map.Map Text Syntax
data Context = Context{
Context -> Text
cName :: !Text
, Context -> Text
cSyntax :: !Text
, Context -> [Rule]
cRules :: ![Rule]
, Context -> TokenType
cAttribute :: !TokenType
, Context -> [ContextSwitch]
cLineEmptyContext :: ![ContextSwitch]
, Context -> [ContextSwitch]
cLineEndContext :: ![ContextSwitch]
, Context -> [ContextSwitch]
cLineBeginContext :: ![ContextSwitch]
, Context -> Bool
cFallthrough :: !Bool
, Context -> [ContextSwitch]
cFallthroughContext :: ![ContextSwitch]
, Context -> Bool
cDynamic :: !Bool
} deriving (Int -> Context -> ShowS
[Context] -> ShowS
Context -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Context] -> ShowS
$cshowList :: [Context] -> ShowS
show :: Context -> String
$cshow :: Context -> String
showsPrec :: Int -> Context -> ShowS
$cshowsPrec :: Int -> Context -> ShowS
Show, ReadPrec [Context]
ReadPrec Context
Int -> ReadS Context
ReadS [Context]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Context]
$creadListPrec :: ReadPrec [Context]
readPrec :: ReadPrec Context
$creadPrec :: ReadPrec Context
readList :: ReadS [Context]
$creadList :: ReadS [Context]
readsPrec :: Int -> ReadS Context
$creadsPrec :: Int -> ReadS Context
Read, Context -> Context -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Context -> Context -> Bool
$c/= :: Context -> Context -> Bool
== :: Context -> Context -> Bool
$c== :: Context -> Context -> Bool
Eq, Eq Context
Context -> Context -> Bool
Context -> Context -> Ordering
Context -> Context -> Context
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Context -> Context -> Context
$cmin :: Context -> Context -> Context
max :: Context -> Context -> Context
$cmax :: Context -> Context -> Context
>= :: Context -> Context -> Bool
$c>= :: Context -> Context -> Bool
> :: Context -> Context -> Bool
$c> :: Context -> Context -> Bool
<= :: Context -> Context -> Bool
$c<= :: Context -> Context -> Bool
< :: Context -> Context -> Bool
$c< :: Context -> Context -> Bool
compare :: Context -> Context -> Ordering
$ccompare :: Context -> Context -> Ordering
Ord, Typeable Context
Context -> DataType
Context -> Constr
(forall b. Data b => b -> b) -> Context -> Context
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Context -> u
forall u. (forall d. Data d => d -> u) -> Context -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Context -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Context -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Context -> m Context
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Context -> m Context
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Context
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Context -> c Context
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Context)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Context)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Context -> m Context
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Context -> m Context
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Context -> m Context
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Context -> m Context
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Context -> m Context
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Context -> m Context
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Context -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Context -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Context -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Context -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Context -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Context -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Context -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Context -> r
gmapT :: (forall b. Data b => b -> b) -> Context -> Context
$cgmapT :: (forall b. Data b => b -> b) -> Context -> Context
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Context)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Context)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Context)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Context)
dataTypeOf :: Context -> DataType
$cdataTypeOf :: Context -> DataType
toConstr :: Context -> Constr
$ctoConstr :: Context -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Context
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Context
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Context -> c Context
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Context -> c Context
Data, Typeable, forall x. Rep Context x -> Context
forall x. Context -> Rep Context x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Context x -> Context
$cfrom :: forall x. Context -> Rep Context x
Generic)
instance Binary Context
type Token = (TokenType, Text)
data TokenType = KeywordTok
| DataTypeTok
| DecValTok
| BaseNTok
| FloatTok
| ConstantTok
| CharTok
| SpecialCharTok
| StringTok
| VerbatimStringTok
| SpecialStringTok
| ImportTok
|
| DocumentationTok
| AnnotationTok
|
| OtherTok
| FunctionTok
| VariableTok
| ControlFlowTok
| OperatorTok
| BuiltInTok
| ExtensionTok
| PreprocessorTok
| AttributeTok
| RegionMarkerTok
| InformationTok
| WarningTok
| AlertTok
| ErrorTok
| NormalTok
deriving (ReadPrec [TokenType]
ReadPrec TokenType
Int -> ReadS TokenType
ReadS [TokenType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TokenType]
$creadListPrec :: ReadPrec [TokenType]
readPrec :: ReadPrec TokenType
$creadPrec :: ReadPrec TokenType
readList :: ReadS [TokenType]
$creadList :: ReadS [TokenType]
readsPrec :: Int -> ReadS TokenType
$creadsPrec :: Int -> ReadS TokenType
Read, Int -> TokenType -> ShowS
[TokenType] -> ShowS
TokenType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenType] -> ShowS
$cshowList :: [TokenType] -> ShowS
show :: TokenType -> String
$cshow :: TokenType -> String
showsPrec :: Int -> TokenType -> ShowS
$cshowsPrec :: Int -> TokenType -> ShowS
Show, TokenType -> TokenType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenType -> TokenType -> Bool
$c/= :: TokenType -> TokenType -> Bool
== :: TokenType -> TokenType -> Bool
$c== :: TokenType -> TokenType -> Bool
Eq, Eq TokenType
TokenType -> TokenType -> Bool
TokenType -> TokenType -> Ordering
TokenType -> TokenType -> TokenType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TokenType -> TokenType -> TokenType
$cmin :: TokenType -> TokenType -> TokenType
max :: TokenType -> TokenType -> TokenType
$cmax :: TokenType -> TokenType -> TokenType
>= :: TokenType -> TokenType -> Bool
$c>= :: TokenType -> TokenType -> Bool
> :: TokenType -> TokenType -> Bool
$c> :: TokenType -> TokenType -> Bool
<= :: TokenType -> TokenType -> Bool
$c<= :: TokenType -> TokenType -> Bool
< :: TokenType -> TokenType -> Bool
$c< :: TokenType -> TokenType -> Bool
compare :: TokenType -> TokenType -> Ordering
$ccompare :: TokenType -> TokenType -> Ordering
Ord, Int -> TokenType
TokenType -> Int
TokenType -> [TokenType]
TokenType -> TokenType
TokenType -> TokenType -> [TokenType]
TokenType -> TokenType -> TokenType -> [TokenType]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType]
$cenumFromThenTo :: TokenType -> TokenType -> TokenType -> [TokenType]
enumFromTo :: TokenType -> TokenType -> [TokenType]
$cenumFromTo :: TokenType -> TokenType -> [TokenType]
enumFromThen :: TokenType -> TokenType -> [TokenType]
$cenumFromThen :: TokenType -> TokenType -> [TokenType]
enumFrom :: TokenType -> [TokenType]
$cenumFrom :: TokenType -> [TokenType]
fromEnum :: TokenType -> Int
$cfromEnum :: TokenType -> Int
toEnum :: Int -> TokenType
$ctoEnum :: Int -> TokenType
pred :: TokenType -> TokenType
$cpred :: TokenType -> TokenType
succ :: TokenType -> TokenType
$csucc :: TokenType -> TokenType
Enum, TokenType
forall a. a -> a -> Bounded a
maxBound :: TokenType
$cmaxBound :: TokenType
minBound :: TokenType
$cminBound :: TokenType
Bounded, Typeable TokenType
TokenType -> DataType
TokenType -> Constr
(forall b. Data b => b -> b) -> TokenType -> TokenType
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TokenType -> u
forall u. (forall d. Data d => d -> u) -> TokenType -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenType -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenType -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenType
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenType -> c TokenType
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenType)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenType -> m TokenType
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TokenType -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TokenType -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> TokenType -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TokenType -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenType -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenType -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenType -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenType -> r
gmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType
$cgmapT :: (forall b. Data b => b -> b) -> TokenType -> TokenType
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenType)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenType)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenType)
dataTypeOf :: TokenType -> DataType
$cdataTypeOf :: TokenType -> DataType
toConstr :: TokenType -> Constr
$ctoConstr :: TokenType -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenType
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenType
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenType -> c TokenType
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenType -> c TokenType
Data, Typeable, forall x. Rep TokenType x -> TokenType
forall x. TokenType -> Rep TokenType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TokenType x -> TokenType
$cfrom :: forall x. TokenType -> Rep TokenType x
Generic)
instance Binary TokenType
instance ToJSON TokenType where
toEncoding :: TokenType -> Encoding
toEncoding = forall a. ToJSON a => a -> Encoding
toEncoding forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Maybe Text
Text.stripSuffix Text
"Tok" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show
instance ToJSONKey TokenType where
toJSONKey :: ToJSONKeyFunction TokenType
toJSONKey = forall a. (a -> Text) -> ToJSONKeyFunction a
toJSONKeyText
(forall a. a -> Maybe a -> a
fromMaybe Text
"Unknown" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Maybe Text
Text.stripSuffix Text
"Tok" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show)
instance FromJSON TokenType where
parseJSON :: Value -> Parser TokenType
parseJSON (String Text
t) =
case forall a. Read a => String -> Maybe a
readMay (Text -> String
Text.unpack Text
t forall a. [a] -> [a] -> [a]
++ String
"Tok") of
Just TokenType
tt -> forall (m :: * -> *) a. Monad m => a -> m a
return TokenType
tt
Maybe TokenType
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Not a token type"
parseJSON Value
_ = forall a. Monoid a => a
mempty
instance FromJSONKey TokenType where
fromJSONKey :: FromJSONKeyFunction TokenType
fromJSONKey = forall a. (Text -> Parser a) -> FromJSONKeyFunction a
FromJSONKeyTextParser (\Text
t ->
case forall a. Read a => String -> Maybe a
readMay (Text -> String
Text.unpack Text
t forall a. [a] -> [a] -> [a]
++ String
"Tok") of
Just TokenType
tt -> forall (m :: * -> *) a. Monad m => a -> m a
return TokenType
tt
Maybe TokenType
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Not a token type")
type SourceLine = [Token]
newtype LineNo = LineNo { LineNo -> Int
lineNo :: Int } deriving (Int -> LineNo -> ShowS
[LineNo] -> ShowS
LineNo -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LineNo] -> ShowS
$cshowList :: [LineNo] -> ShowS
show :: LineNo -> String
$cshow :: LineNo -> String
showsPrec :: Int -> LineNo -> ShowS
$cshowsPrec :: Int -> LineNo -> ShowS
Show, Int -> LineNo
LineNo -> Int
LineNo -> [LineNo]
LineNo -> LineNo
LineNo -> LineNo -> [LineNo]
LineNo -> LineNo -> LineNo -> [LineNo]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: LineNo -> LineNo -> LineNo -> [LineNo]
$cenumFromThenTo :: LineNo -> LineNo -> LineNo -> [LineNo]
enumFromTo :: LineNo -> LineNo -> [LineNo]
$cenumFromTo :: LineNo -> LineNo -> [LineNo]
enumFromThen :: LineNo -> LineNo -> [LineNo]
$cenumFromThen :: LineNo -> LineNo -> [LineNo]
enumFrom :: LineNo -> [LineNo]
$cenumFrom :: LineNo -> [LineNo]
fromEnum :: LineNo -> Int
$cfromEnum :: LineNo -> Int
toEnum :: Int -> LineNo
$ctoEnum :: Int -> LineNo
pred :: LineNo -> LineNo
$cpred :: LineNo -> LineNo
succ :: LineNo -> LineNo
$csucc :: LineNo -> LineNo
Enum)
data TokenStyle = TokenStyle {
TokenStyle -> Maybe Color
tokenColor :: !(Maybe Color)
, TokenStyle -> Maybe Color
tokenBackground :: !(Maybe Color)
, TokenStyle -> Bool
tokenBold :: !Bool
, TokenStyle -> Bool
tokenItalic :: !Bool
, TokenStyle -> Bool
tokenUnderline :: !Bool
} deriving (Int -> TokenStyle -> ShowS
[TokenStyle] -> ShowS
TokenStyle -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenStyle] -> ShowS
$cshowList :: [TokenStyle] -> ShowS
show :: TokenStyle -> String
$cshow :: TokenStyle -> String
showsPrec :: Int -> TokenStyle -> ShowS
$cshowsPrec :: Int -> TokenStyle -> ShowS
Show, ReadPrec [TokenStyle]
ReadPrec TokenStyle
Int -> ReadS TokenStyle
ReadS [TokenStyle]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TokenStyle]
$creadListPrec :: ReadPrec [TokenStyle]
readPrec :: ReadPrec TokenStyle
$creadPrec :: ReadPrec TokenStyle
readList :: ReadS [TokenStyle]
$creadList :: ReadS [TokenStyle]
readsPrec :: Int -> ReadS TokenStyle
$creadsPrec :: Int -> ReadS TokenStyle
Read, Eq TokenStyle
TokenStyle -> TokenStyle -> Bool
TokenStyle -> TokenStyle -> Ordering
TokenStyle -> TokenStyle -> TokenStyle
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TokenStyle -> TokenStyle -> TokenStyle
$cmin :: TokenStyle -> TokenStyle -> TokenStyle
max :: TokenStyle -> TokenStyle -> TokenStyle
$cmax :: TokenStyle -> TokenStyle -> TokenStyle
>= :: TokenStyle -> TokenStyle -> Bool
$c>= :: TokenStyle -> TokenStyle -> Bool
> :: TokenStyle -> TokenStyle -> Bool
$c> :: TokenStyle -> TokenStyle -> Bool
<= :: TokenStyle -> TokenStyle -> Bool
$c<= :: TokenStyle -> TokenStyle -> Bool
< :: TokenStyle -> TokenStyle -> Bool
$c< :: TokenStyle -> TokenStyle -> Bool
compare :: TokenStyle -> TokenStyle -> Ordering
$ccompare :: TokenStyle -> TokenStyle -> Ordering
Ord, TokenStyle -> TokenStyle -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenStyle -> TokenStyle -> Bool
$c/= :: TokenStyle -> TokenStyle -> Bool
== :: TokenStyle -> TokenStyle -> Bool
$c== :: TokenStyle -> TokenStyle -> Bool
Eq, Typeable TokenStyle
TokenStyle -> DataType
TokenStyle -> Constr
(forall b. Data b => b -> b) -> TokenStyle -> TokenStyle
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TokenStyle -> u
forall u. (forall d. Data d => d -> u) -> TokenStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenStyle -> c TokenStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenStyle)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> TokenStyle -> m TokenStyle
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TokenStyle -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TokenStyle -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> TokenStyle -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> TokenStyle -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenStyle -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TokenStyle -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenStyle -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TokenStyle -> r
gmapT :: (forall b. Data b => b -> b) -> TokenStyle -> TokenStyle
$cgmapT :: (forall b. Data b => b -> b) -> TokenStyle -> TokenStyle
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TokenStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenStyle)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c TokenStyle)
dataTypeOf :: TokenStyle -> DataType
$cdataTypeOf :: TokenStyle -> DataType
toConstr :: TokenStyle -> Constr
$ctoConstr :: TokenStyle -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c TokenStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenStyle -> c TokenStyle
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TokenStyle -> c TokenStyle
Data, Typeable, forall x. Rep TokenStyle x -> TokenStyle
forall x. TokenStyle -> Rep TokenStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TokenStyle x -> TokenStyle
$cfrom :: forall x. TokenStyle -> Rep TokenStyle x
Generic)
instance Binary TokenStyle
instance FromJSON TokenStyle where
parseJSON :: Value -> Parser TokenStyle
parseJSON (Object Object
v) = do
Maybe Color
tcolor <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"text-color"
Maybe Color
bg <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"background-color"
Bool
tbold <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"bold" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Bool
titalic <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"italic" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
Bool
tunderline <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"underline" forall a. Parser (Maybe a) -> a -> Parser a
.!= Bool
False
forall (m :: * -> *) a. Monad m => a -> m a
return TokenStyle{
tokenColor :: Maybe Color
tokenColor = Maybe Color
tcolor
, tokenBackground :: Maybe Color
tokenBackground = Maybe Color
bg
, tokenBold :: Bool
tokenBold = Bool
tbold
, tokenItalic :: Bool
tokenItalic = Bool
titalic
, tokenUnderline :: Bool
tokenUnderline = Bool
tunderline }
parseJSON Value
_ = forall a. Monoid a => a
mempty
instance ToJSON TokenStyle where
toJSON :: TokenStyle -> Value
toJSON TokenStyle
ts = [Pair] -> Value
object [ Key
"text-color" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TokenStyle -> Maybe Color
tokenColor TokenStyle
ts
, Key
"background-color" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TokenStyle -> Maybe Color
tokenBackground TokenStyle
ts
, Key
"bold" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TokenStyle -> Bool
tokenBold TokenStyle
ts
, Key
"italic" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TokenStyle -> Bool
tokenItalic TokenStyle
ts
, Key
"underline" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= TokenStyle -> Bool
tokenUnderline TokenStyle
ts ]
defStyle :: TokenStyle
defStyle :: TokenStyle
defStyle = TokenStyle {
tokenColor :: Maybe Color
tokenColor = forall a. Maybe a
Nothing
, tokenBackground :: Maybe Color
tokenBackground = forall a. Maybe a
Nothing
, tokenBold :: Bool
tokenBold = Bool
False
, tokenItalic :: Bool
tokenItalic = Bool
False
, tokenUnderline :: Bool
tokenUnderline = Bool
False
}
data Color = RGB Word8 Word8 Word8
deriving (Int -> Color -> ShowS
[Color] -> ShowS
Color -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Color] -> ShowS
$cshowList :: [Color] -> ShowS
show :: Color -> String
$cshow :: Color -> String
showsPrec :: Int -> Color -> ShowS
$cshowsPrec :: Int -> Color -> ShowS
Show, ReadPrec [Color]
ReadPrec Color
Int -> ReadS Color
ReadS [Color]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Color]
$creadListPrec :: ReadPrec [Color]
readPrec :: ReadPrec Color
$creadPrec :: ReadPrec Color
readList :: ReadS [Color]
$creadList :: ReadS [Color]
readsPrec :: Int -> ReadS Color
$creadsPrec :: Int -> ReadS Color
Read, Eq Color
Color -> Color -> Bool
Color -> Color -> Ordering
Color -> Color -> Color
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Color -> Color -> Color
$cmin :: Color -> Color -> Color
max :: Color -> Color -> Color
$cmax :: Color -> Color -> Color
>= :: Color -> Color -> Bool
$c>= :: Color -> Color -> Bool
> :: Color -> Color -> Bool
$c> :: Color -> Color -> Bool
<= :: Color -> Color -> Bool
$c<= :: Color -> Color -> Bool
< :: Color -> Color -> Bool
$c< :: Color -> Color -> Bool
compare :: Color -> Color -> Ordering
$ccompare :: Color -> Color -> Ordering
Ord, Color -> Color -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Color -> Color -> Bool
$c/= :: Color -> Color -> Bool
== :: Color -> Color -> Bool
$c== :: Color -> Color -> Bool
Eq, Typeable Color
Color -> DataType
Color -> Constr
(forall b. Data b => b -> b) -> Color -> Color
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Color -> u
forall u. (forall d. Data d => d -> u) -> Color -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Color -> m Color
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Color
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Color -> c Color
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Color)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Color -> m Color
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Color -> m Color
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Color -> m Color
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Color -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Color -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Color -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Color -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Color -> r
gmapT :: (forall b. Data b => b -> b) -> Color -> Color
$cgmapT :: (forall b. Data b => b -> b) -> Color -> Color
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Color)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Color)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Color)
dataTypeOf :: Color -> DataType
$cdataTypeOf :: Color -> DataType
toConstr :: Color -> Constr
$ctoConstr :: Color -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Color
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Color
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Color -> c Color
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Color -> c Color
Data, Typeable, forall x. Rep Color x -> Color
forall x. Color -> Rep Color x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Color x -> Color
$cfrom :: forall x. Color -> Rep Color x
Generic)
instance Binary Color
class ToColor a where
toColor :: a -> Maybe Color
instance ToColor String where
toColor :: String -> Maybe Color
toColor [Char
'#',Char
r1,Char
r2,Char
g1,Char
g2,Char
b1,Char
b2] =
case forall a. Read a => ReadS a
reads [Char
'(',Char
'0',Char
'x',Char
r1,Char
r2,Char
',',Char
'0',Char
'x',Char
g1,Char
g2,Char
',',Char
'0',Char
'x',Char
b1,Char
b2,Char
')'] of
((Word8
r,Word8
g,Word8
b),String
_) : [((Word8, Word8, Word8), String)]
_ -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word8 -> Color
RGB Word8
r Word8
g Word8
b
[((Word8, Word8, Word8), String)]
_ -> forall a. Maybe a
Nothing
toColor String
_ = forall a. Maybe a
Nothing
instance ToColor Int where
toColor :: Int -> Maybe Color
toColor Int
x = forall a. ToColor a => a -> Maybe Color
toColor (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x1 :: Word8,
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x2 :: Word8,
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
x3 :: Word8)
where x1 :: Int
x1 = (forall a. Bits a => a -> Int -> a
shiftR Int
x Int
16) forall a. Bits a => a -> a -> a
.&. Int
0xFF
x2 :: Int
x2 = (forall a. Bits a => a -> Int -> a
shiftR Int
x Int
8 ) forall a. Bits a => a -> a -> a
.&. Int
0xFF
x3 :: Int
x3 = Int
x forall a. Bits a => a -> a -> a
.&. Int
0xFF
instance ToColor (Word8, Word8, Word8) where
toColor :: (Word8, Word8, Word8) -> Maybe Color
toColor (Word8
r,Word8
g,Word8
b) = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word8 -> Color
RGB Word8
r Word8
g Word8
b
instance ToColor (Double, Double, Double) where
toColor :: (Double, Double, Double) -> Maybe Color
toColor (Double
r,Double
g,Double
b) | Double
r forall a. Ord a => a -> a -> Bool
>= Double
0 Bool -> Bool -> Bool
&& Double
g forall a. Ord a => a -> a -> Bool
>= Double
0 Bool -> Bool -> Bool
&& Double
b forall a. Ord a => a -> a -> Bool
>= Double
0 Bool -> Bool -> Bool
&& Double
r forall a. Ord a => a -> a -> Bool
<= Double
1 Bool -> Bool -> Bool
&& Double
g forall a. Ord a => a -> a -> Bool
<= Double
1 Bool -> Bool -> Bool
&& Double
b forall a. Ord a => a -> a -> Bool
<= Double
1 =
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Word8 -> Word8 -> Word8 -> Color
RGB (forall a b. (RealFrac a, Integral b) => a -> b
floor forall a b. (a -> b) -> a -> b
$ Double
r forall a. Num a => a -> a -> a
* Double
255) (forall a b. (RealFrac a, Integral b) => a -> b
floor forall a b. (a -> b) -> a -> b
$ Double
g forall a. Num a => a -> a -> a
* Double
255) (forall a b. (RealFrac a, Integral b) => a -> b
floor forall a b. (a -> b) -> a -> b
$ Double
b forall a. Num a => a -> a -> a
* Double
255)
toColor (Double, Double, Double)
_ = forall a. Maybe a
Nothing
instance (RealFrac a, Floating a) => ToColor (Colour a) where
toColor :: Colour a -> Maybe Color
toColor Colour a
c = let (Colour.RGB Word8
r Word8
g Word8
b) = forall b. (RealFrac b, Floating b) => Colour b -> RGB Word8
toSRGB24 Colour a
c in forall a. ToColor a => a -> Maybe Color
toColor (Word8
r, Word8
g, Word8
b)
instance FromJSON Color where
parseJSON :: Value -> Parser Color
parseJSON (String Text
t) = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Monoid a => a
mempty forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. ToColor a => a -> Maybe Color
toColor (Text -> String
Text.unpack Text
t)
parseJSON Value
_ = forall a. Monoid a => a
mempty
instance ToJSON Color where
toJSON :: Color -> Value
toJSON Color
color = Text -> Value
String (String -> Text
Text.pack (forall a. FromColor a => Color -> a
fromColor Color
color :: String))
class FromColor a where
fromColor :: Color -> a
instance FromColor String where
fromColor :: Color -> String
fromColor (RGB Word8
r Word8
g Word8
b) = forall r. PrintfType r => String -> r
printf String
"#%02x%02x%02x" Word8
r Word8
g Word8
b
instance FromColor (Double, Double, Double) where
fromColor :: Color -> (Double, Double, Double)
fromColor (RGB Word8
r Word8
g Word8
b) = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
r forall a. Fractional a => a -> a -> a
/ Double
255, forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
g forall a. Fractional a => a -> a -> a
/ Double
255, forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b forall a. Fractional a => a -> a -> a
/ Double
255)
instance FromColor (Word8, Word8, Word8) where
fromColor :: Color -> (Word8, Word8, Word8)
fromColor (RGB Word8
r Word8
g Word8
b) = (Word8
r, Word8
g, Word8
b)
instance (Ord a, Floating a) => FromColor (Colour a) where
fromColor :: Color -> Colour a
fromColor (RGB Word8
r Word8
g Word8
b) = forall b.
(Ord b, Floating b) =>
Word8 -> Word8 -> Word8 -> Colour b
sRGB24 Word8
r Word8
g Word8
b
data Style = Style {
Style -> Map TokenType TokenStyle
tokenStyles :: !(Map.Map TokenType TokenStyle)
, Style -> Maybe Color
defaultColor :: !(Maybe Color)
, Style -> Maybe Color
backgroundColor :: !(Maybe Color)
, Style -> Maybe Color
lineNumberColor :: !(Maybe Color)
, Style -> Maybe Color
lineNumberBackgroundColor :: !(Maybe Color)
} deriving (ReadPrec [Style]
ReadPrec Style
Int -> ReadS Style
ReadS [Style]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Style]
$creadListPrec :: ReadPrec [Style]
readPrec :: ReadPrec Style
$creadPrec :: ReadPrec Style
readList :: ReadS [Style]
$creadList :: ReadS [Style]
readsPrec :: Int -> ReadS Style
$creadsPrec :: Int -> ReadS Style
Read, Int -> Style -> ShowS
[Style] -> ShowS
Style -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Style] -> ShowS
$cshowList :: [Style] -> ShowS
show :: Style -> String
$cshow :: Style -> String
showsPrec :: Int -> Style -> ShowS
$cshowsPrec :: Int -> Style -> ShowS
Show, Style -> Style -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Style -> Style -> Bool
$c/= :: Style -> Style -> Bool
== :: Style -> Style -> Bool
$c== :: Style -> Style -> Bool
Eq, Eq Style
Style -> Style -> Bool
Style -> Style -> Ordering
Style -> Style -> Style
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Style -> Style -> Style
$cmin :: Style -> Style -> Style
max :: Style -> Style -> Style
$cmax :: Style -> Style -> Style
>= :: Style -> Style -> Bool
$c>= :: Style -> Style -> Bool
> :: Style -> Style -> Bool
$c> :: Style -> Style -> Bool
<= :: Style -> Style -> Bool
$c<= :: Style -> Style -> Bool
< :: Style -> Style -> Bool
$c< :: Style -> Style -> Bool
compare :: Style -> Style -> Ordering
$ccompare :: Style -> Style -> Ordering
Ord, Typeable Style
Style -> DataType
Style -> Constr
(forall b. Data b => b -> b) -> Style -> Style
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
forall u. (forall d. Data d => d -> u) -> Style -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Style -> m Style
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Style -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Style -> [u]
gmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Style -> r
gmapT :: (forall b. Data b => b -> b) -> Style -> Style
$cgmapT :: (forall b. Data b => b -> b) -> Style -> Style
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Style)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Style)
dataTypeOf :: Style -> DataType
$cdataTypeOf :: Style -> DataType
toConstr :: Style -> Constr
$ctoConstr :: Style -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Style
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Style -> c Style
Data, Typeable, forall x. Rep Style x -> Style
forall x. Style -> Rep Style x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Style x -> Style
$cfrom :: forall x. Style -> Rep Style x
Generic)
instance Binary Style
instance FromJSON Style where
parseJSON :: Value -> Parser Style
parseJSON (Object Object
v) = do
(Map Text TokenStyle
tokstyles :: Map.Map Text TokenStyle) <- Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"text-styles"
(Map Text Color
editorColors :: Map.Map Text Color) <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"editor-colors" forall a. Parser (Maybe a) -> a -> Parser a
.!= forall a. Monoid a => a
mempty
Maybe Color
mbBackgroundColor <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"background-color"
Maybe Color
mbLineNumberColor <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"line-number-color"
Maybe Color
mbDefaultColor <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"text-color"
Maybe Color
mbLineNumberBackgroundColor <- Object
v forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"line-number-background-color"
forall (m :: * -> *) a. Monad m => a -> m a
return Style{ defaultColor :: Maybe Color
defaultColor = Maybe Color
mbDefaultColor forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
(case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"Normal" Map Text TokenStyle
tokstyles of
Maybe TokenStyle
Nothing -> forall a. Maybe a
Nothing
Just TokenStyle
ts -> TokenStyle -> Maybe Color
tokenColor TokenStyle
ts)
, backgroundColor :: Maybe Color
backgroundColor = Maybe Color
mbBackgroundColor forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"background-color" Map Text Color
editorColors
, lineNumberColor :: Maybe Color
lineNumberColor = Maybe Color
mbLineNumberColor forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"line-numbers" Map Text Color
editorColors
, lineNumberBackgroundColor :: Maybe Color
lineNumberBackgroundColor =
Maybe Color
mbLineNumberBackgroundColor forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus`
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"background-color" Map Text Color
editorColors
, tokenStyles :: Map TokenType TokenStyle
tokenStyles =
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (\Text
s -> forall b a. b -> (a -> b) -> Maybe a -> b
maybe TokenType
OtherTok forall a. a -> a
id forall a b. (a -> b) -> a -> b
$
forall a. Read a => String -> Maybe a
readMay (Text -> String
Text.unpack Text
s forall a. [a] -> [a] -> [a]
++ String
"Tok")) Map Text TokenStyle
tokstyles }
parseJSON Value
_ = forall a. Monoid a => a
mempty
instance ToJSON Style where
toJSON :: Style -> Value
toJSON Style
s = [Pair] -> Value
object [ Key
"text-styles" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON (Style -> Map TokenType TokenStyle
tokenStyles Style
s)
, Key
"background-color" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON (Style -> Maybe Color
backgroundColor Style
s)
, Key
"text-color" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON (Style -> Maybe Color
defaultColor Style
s)
, Key
"line-number-color" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= forall a. ToJSON a => a -> Value
toJSON (Style -> Maybe Color
lineNumberColor Style
s)
, Key
"line-number-background-color" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.=
forall a. ToJSON a => a -> Value
toJSON (Style -> Maybe Color
lineNumberBackgroundColor Style
s)
]
data ANSIColorLevel = ANSI16Color
| ANSI256Color
| ANSITrueColor
deriving (Int -> ANSIColorLevel -> ShowS
[ANSIColorLevel] -> ShowS
ANSIColorLevel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ANSIColorLevel] -> ShowS
$cshowList :: [ANSIColorLevel] -> ShowS
show :: ANSIColorLevel -> String
$cshow :: ANSIColorLevel -> String
showsPrec :: Int -> ANSIColorLevel -> ShowS
$cshowsPrec :: Int -> ANSIColorLevel -> ShowS
Show, ReadPrec [ANSIColorLevel]
ReadPrec ANSIColorLevel
Int -> ReadS ANSIColorLevel
ReadS [ANSIColorLevel]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ANSIColorLevel]
$creadListPrec :: ReadPrec [ANSIColorLevel]
readPrec :: ReadPrec ANSIColorLevel
$creadPrec :: ReadPrec ANSIColorLevel
readList :: ReadS [ANSIColorLevel]
$creadList :: ReadS [ANSIColorLevel]
readsPrec :: Int -> ReadS ANSIColorLevel
$creadsPrec :: Int -> ReadS ANSIColorLevel
Read, ANSIColorLevel -> ANSIColorLevel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ANSIColorLevel -> ANSIColorLevel -> Bool
$c/= :: ANSIColorLevel -> ANSIColorLevel -> Bool
== :: ANSIColorLevel -> ANSIColorLevel -> Bool
$c== :: ANSIColorLevel -> ANSIColorLevel -> Bool
Eq, Eq ANSIColorLevel
ANSIColorLevel -> ANSIColorLevel -> Bool
ANSIColorLevel -> ANSIColorLevel -> Ordering
ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel
$cmin :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel
max :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel
$cmax :: ANSIColorLevel -> ANSIColorLevel -> ANSIColorLevel
>= :: ANSIColorLevel -> ANSIColorLevel -> Bool
$c>= :: ANSIColorLevel -> ANSIColorLevel -> Bool
> :: ANSIColorLevel -> ANSIColorLevel -> Bool
$c> :: ANSIColorLevel -> ANSIColorLevel -> Bool
<= :: ANSIColorLevel -> ANSIColorLevel -> Bool
$c<= :: ANSIColorLevel -> ANSIColorLevel -> Bool
< :: ANSIColorLevel -> ANSIColorLevel -> Bool
$c< :: ANSIColorLevel -> ANSIColorLevel -> Bool
compare :: ANSIColorLevel -> ANSIColorLevel -> Ordering
$ccompare :: ANSIColorLevel -> ANSIColorLevel -> Ordering
Ord, Int -> ANSIColorLevel
ANSIColorLevel -> Int
ANSIColorLevel -> [ANSIColorLevel]
ANSIColorLevel -> ANSIColorLevel
ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
ANSIColorLevel
-> ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ANSIColorLevel
-> ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
$cenumFromThenTo :: ANSIColorLevel
-> ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
enumFromTo :: ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
$cenumFromTo :: ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
enumFromThen :: ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
$cenumFromThen :: ANSIColorLevel -> ANSIColorLevel -> [ANSIColorLevel]
enumFrom :: ANSIColorLevel -> [ANSIColorLevel]
$cenumFrom :: ANSIColorLevel -> [ANSIColorLevel]
fromEnum :: ANSIColorLevel -> Int
$cfromEnum :: ANSIColorLevel -> Int
toEnum :: Int -> ANSIColorLevel
$ctoEnum :: Int -> ANSIColorLevel
pred :: ANSIColorLevel -> ANSIColorLevel
$cpred :: ANSIColorLevel -> ANSIColorLevel
succ :: ANSIColorLevel -> ANSIColorLevel
$csucc :: ANSIColorLevel -> ANSIColorLevel
Enum, ANSIColorLevel
forall a. a -> a -> Bounded a
maxBound :: ANSIColorLevel
$cmaxBound :: ANSIColorLevel
minBound :: ANSIColorLevel
$cminBound :: ANSIColorLevel
Bounded, Typeable ANSIColorLevel
ANSIColorLevel -> DataType
ANSIColorLevel -> Constr
(forall b. Data b => b -> b) -> ANSIColorLevel -> ANSIColorLevel
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ANSIColorLevel -> u
forall u. (forall d. Data d => d -> u) -> ANSIColorLevel -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ANSIColorLevel
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ANSIColorLevel -> c ANSIColorLevel
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ANSIColorLevel)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ANSIColorLevel)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ANSIColorLevel -> m ANSIColorLevel
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ANSIColorLevel -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ANSIColorLevel -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> ANSIColorLevel -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> ANSIColorLevel -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ANSIColorLevel -> r
gmapT :: (forall b. Data b => b -> b) -> ANSIColorLevel -> ANSIColorLevel
$cgmapT :: (forall b. Data b => b -> b) -> ANSIColorLevel -> ANSIColorLevel
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ANSIColorLevel)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c ANSIColorLevel)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ANSIColorLevel)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c ANSIColorLevel)
dataTypeOf :: ANSIColorLevel -> DataType
$cdataTypeOf :: ANSIColorLevel -> DataType
toConstr :: ANSIColorLevel -> Constr
$ctoConstr :: ANSIColorLevel -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ANSIColorLevel
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c ANSIColorLevel
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ANSIColorLevel -> c ANSIColorLevel
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ANSIColorLevel -> c ANSIColorLevel
Data, Typeable, forall x. Rep ANSIColorLevel x -> ANSIColorLevel
forall x. ANSIColorLevel -> Rep ANSIColorLevel x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ANSIColorLevel x -> ANSIColorLevel
$cfrom :: forall x. ANSIColorLevel -> Rep ANSIColorLevel x
Generic)
instance Binary ANSIColorLevel
data FormatOptions = FormatOptions{
FormatOptions -> Bool
numberLines :: !Bool
, FormatOptions -> Int
startNumber :: !Int
, FormatOptions -> Bool
lineAnchors :: !Bool
, FormatOptions -> Bool
titleAttributes :: !Bool
, FormatOptions -> [Text]
codeClasses :: ![Text]
, FormatOptions -> [Text]
containerClasses :: ![Text]
, FormatOptions -> Text
lineIdPrefix :: !Text
, FormatOptions -> ANSIColorLevel
ansiColorLevel :: !ANSIColorLevel
} deriving (Int -> FormatOptions -> ShowS
[FormatOptions] -> ShowS
FormatOptions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FormatOptions] -> ShowS
$cshowList :: [FormatOptions] -> ShowS
show :: FormatOptions -> String
$cshow :: FormatOptions -> String
showsPrec :: Int -> FormatOptions -> ShowS
$cshowsPrec :: Int -> FormatOptions -> ShowS
Show, ReadPrec [FormatOptions]
ReadPrec FormatOptions
Int -> ReadS FormatOptions
ReadS [FormatOptions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FormatOptions]
$creadListPrec :: ReadPrec [FormatOptions]
readPrec :: ReadPrec FormatOptions
$creadPrec :: ReadPrec FormatOptions
readList :: ReadS [FormatOptions]
$creadList :: ReadS [FormatOptions]
readsPrec :: Int -> ReadS FormatOptions
$creadsPrec :: Int -> ReadS FormatOptions
Read, FormatOptions -> FormatOptions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FormatOptions -> FormatOptions -> Bool
$c/= :: FormatOptions -> FormatOptions -> Bool
== :: FormatOptions -> FormatOptions -> Bool
$c== :: FormatOptions -> FormatOptions -> Bool
Eq, Eq FormatOptions
FormatOptions -> FormatOptions -> Bool
FormatOptions -> FormatOptions -> Ordering
FormatOptions -> FormatOptions -> FormatOptions
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: FormatOptions -> FormatOptions -> FormatOptions
$cmin :: FormatOptions -> FormatOptions -> FormatOptions
max :: FormatOptions -> FormatOptions -> FormatOptions
$cmax :: FormatOptions -> FormatOptions -> FormatOptions
>= :: FormatOptions -> FormatOptions -> Bool
$c>= :: FormatOptions -> FormatOptions -> Bool
> :: FormatOptions -> FormatOptions -> Bool
$c> :: FormatOptions -> FormatOptions -> Bool
<= :: FormatOptions -> FormatOptions -> Bool
$c<= :: FormatOptions -> FormatOptions -> Bool
< :: FormatOptions -> FormatOptions -> Bool
$c< :: FormatOptions -> FormatOptions -> Bool
compare :: FormatOptions -> FormatOptions -> Ordering
$ccompare :: FormatOptions -> FormatOptions -> Ordering
Ord, Typeable FormatOptions
FormatOptions -> DataType
FormatOptions -> Constr
(forall b. Data b => b -> b) -> FormatOptions -> FormatOptions
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> FormatOptions -> u
forall u. (forall d. Data d => d -> u) -> FormatOptions -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormatOptions -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormatOptions -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormatOptions
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormatOptions -> c FormatOptions
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormatOptions)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormatOptions)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> FormatOptions -> m FormatOptions
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FormatOptions -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> FormatOptions -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> FormatOptions -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> FormatOptions -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormatOptions -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> FormatOptions -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormatOptions -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> FormatOptions -> r
gmapT :: (forall b. Data b => b -> b) -> FormatOptions -> FormatOptions
$cgmapT :: (forall b. Data b => b -> b) -> FormatOptions -> FormatOptions
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormatOptions)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c FormatOptions)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormatOptions)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c FormatOptions)
dataTypeOf :: FormatOptions -> DataType
$cdataTypeOf :: FormatOptions -> DataType
toConstr :: FormatOptions -> Constr
$ctoConstr :: FormatOptions -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormatOptions
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c FormatOptions
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormatOptions -> c FormatOptions
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> FormatOptions -> c FormatOptions
Data, Typeable, forall x. Rep FormatOptions x -> FormatOptions
forall x. FormatOptions -> Rep FormatOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FormatOptions x -> FormatOptions
$cfrom :: forall x. FormatOptions -> Rep FormatOptions x
Generic)
instance Binary FormatOptions
defaultFormatOpts :: FormatOptions
defaultFormatOpts :: FormatOptions
defaultFormatOpts = FormatOptions{
numberLines :: Bool
numberLines = Bool
False
, startNumber :: Int
startNumber = Int
1
, lineAnchors :: Bool
lineAnchors = Bool
False
, titleAttributes :: Bool
titleAttributes = Bool
False
, codeClasses :: [Text]
codeClasses = []
, containerClasses :: [Text]
containerClasses = []
, lineIdPrefix :: Text
lineIdPrefix = Text
""
, ansiColorLevel :: ANSIColorLevel
ansiColorLevel = ANSIColorLevel
ANSI16Color
}