module Skylighting.Types (
ContextName
, KeywordAttr(..)
, WordSet
, makeWordSet
, inWordSet
, Matcher(..)
, Rule(..)
, Context(..)
, ContextSwitch(..)
, Syntax(..)
, SyntaxMap
, Token
, TokenType(..)
, SourceLine
, LineNo(..)
, TokenStyle(..)
, defStyle
, Color(..)
, ToColor(..)
, FromColor(..)
, Style(..)
, FormatOptions(..)
, defaultFormatOpts
) where
import Control.Monad (mplus)
import Data.Aeson.Types (toJSONKeyText)
import Data.Aeson
import Data.Bits
import Data.CaseInsensitive (FoldCase(..))
import Data.Binary (Binary)
import Data.Data (Data)
import Data.Maybe (fromMaybe)
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as Text
import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Data.Word
import Safe (readMay)
import Skylighting.Regex
import Text.Printf
type ContextName = (Text, Text)
data KeywordAttr =
KeywordAttr { keywordCaseSensitive :: Bool
, keywordDelims :: Set.Set Char
}
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary KeywordAttr
data WordSet a = CaseSensitiveWords (Set.Set a)
| CaseInsensitiveWords (Set.Set a)
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary a => Binary (WordSet a)
makeWordSet :: (FoldCase a, Ord a) => Bool -> [a] -> WordSet a
makeWordSet True ws = CaseSensitiveWords (Set.fromList ws)
makeWordSet False ws = CaseInsensitiveWords (Set.fromList $ map foldCase ws)
inWordSet :: (FoldCase a, Ord a) => a -> WordSet a -> Bool
inWordSet w (CaseInsensitiveWords ws) = foldCase w `Set.member` ws
inWordSet w (CaseSensitiveWords ws) = w `Set.member` ws
data Matcher =
DetectChar Char
| Detect2Chars Char Char
| AnyChar [Char]
| RangeDetect Char Char
| StringDetect Text
| WordDetect Text
| RegExpr RE
| Keyword KeywordAttr (WordSet Text)
| Int
| Float
| HlCOct
| HlCHex
| HlCStringChar
| HlCChar
| LineContinue
| IncludeRules ContextName
| DetectSpaces
| DetectIdentifier
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary Matcher
data ContextSwitch =
Pop | Push ContextName
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary ContextSwitch
data Rule = Rule{
rMatcher :: Matcher
, rAttribute :: TokenType
, rIncludeAttribute :: Bool
, rDynamic :: Bool
, rCaseSensitive :: Bool
, rChildren :: [Rule]
, rLookahead :: Bool
, rFirstNonspace :: Bool
, rColumn :: Maybe Int
, rContextSwitch :: [ContextSwitch]
} deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary Rule
data Syntax = Syntax{
sName :: Text
, sFilename :: String
, sShortname :: Text
, sContexts :: Map.Map Text Context
, sAuthor :: Text
, sVersion :: Text
, sLicense :: Text
, sExtensions :: [String]
, sStartingContext :: Text
} deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary Syntax
type SyntaxMap = Map.Map Text Syntax
data Context = Context{
cName :: Text
, cSyntax :: Text
, cRules :: [Rule]
, cAttribute :: TokenType
, cLineEmptyContext :: [ContextSwitch]
, cLineEndContext :: [ContextSwitch]
, cLineBeginContext :: [ContextSwitch]
, cFallthrough :: Bool
, cFallthroughContext :: [ContextSwitch]
, cDynamic :: Bool
} deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary Context
type Token = (TokenType, Text)
data TokenType = KeywordTok
| DataTypeTok
| DecValTok
| BaseNTok
| FloatTok
| ConstantTok
| CharTok
| SpecialCharTok
| StringTok
| VerbatimStringTok
| SpecialStringTok
| ImportTok
| CommentTok
| DocumentationTok
| AnnotationTok
| CommentVarTok
| OtherTok
| FunctionTok
| VariableTok
| ControlFlowTok
| OperatorTok
| BuiltInTok
| ExtensionTok
| PreprocessorTok
| AttributeTok
| RegionMarkerTok
| InformationTok
| WarningTok
| AlertTok
| ErrorTok
| NormalTok
deriving (Read, Show, Eq, Ord, Enum, Data, Typeable, Generic)
instance Binary TokenType
instance ToJSON TokenType where
toEncoding = toEncoding . Text.stripSuffix "Tok" . Text.pack . show
instance ToJSONKey TokenType where
toJSONKey = toJSONKeyText
(fromMaybe "Unknown" . Text.stripSuffix "Tok" . Text.pack . show)
instance FromJSON TokenType where
parseJSON (String t) =
case readMay (Text.unpack t ++ "Tok") of
Just tt -> return tt
Nothing -> fail "Not a token type"
parseJSON _ = mempty
instance FromJSONKey TokenType where
fromJSONKey = FromJSONKeyTextParser (\t ->
case readMay (Text.unpack t ++ "Tok") of
Just tt -> return tt
Nothing -> fail "Not a token type")
type SourceLine = [Token]
newtype LineNo = LineNo { lineNo :: Int } deriving (Show, Enum)
data TokenStyle = TokenStyle {
tokenColor :: Maybe Color
, tokenBackground :: Maybe Color
, tokenBold :: Bool
, tokenItalic :: Bool
, tokenUnderline :: Bool
} deriving (Show, Read, Ord, Eq, Data, Typeable, Generic)
instance Binary TokenStyle
instance FromJSON TokenStyle where
parseJSON (Object v) = do
tcolor <- v .:? "text-color"
bg <- v .:? "background-color"
tbold <- v .:? "bold" .!= False
titalic <- v .:? "italic" .!= False
tunderline <- v .:? "underline" .!= False
return TokenStyle{
tokenColor = tcolor
, tokenBackground = bg
, tokenBold = tbold
, tokenItalic = titalic
, tokenUnderline = tunderline }
parseJSON _ = mempty
instance ToJSON TokenStyle where
toJSON ts = object [ "text-color" .= tokenColor ts
, "background-color" .= tokenBackground ts
, "bold" .= tokenBold ts
, "italic" .= tokenItalic ts
, "underline" .= tokenUnderline ts ]
defStyle :: TokenStyle
defStyle = TokenStyle {
tokenColor = Nothing
, tokenBackground = Nothing
, tokenBold = False
, tokenItalic = False
, tokenUnderline = False
}
data Color = RGB Word8 Word8 Word8
deriving (Show, Read, Ord, Eq, Data, Typeable, Generic)
instance Binary Color
class ToColor a where
toColor :: a -> Maybe Color
instance ToColor String where
toColor ['#',r1,r2,g1,g2,b1,b2] =
case reads ['(','0','x',r1,r2,',','0','x',g1,g2,',','0','x',b1,b2,')'] of
((r,g,b),_) : _ -> Just $ RGB r g b
_ -> Nothing
toColor _ = Nothing
instance ToColor Int where
toColor x = toColor (fromIntegral x1 :: Word8,
fromIntegral x2 :: Word8,
fromIntegral x3 :: Word8)
where x1 = (shiftR x 16) .&. 0xFF
x2 = (shiftR x 8 ) .&. 0xFF
x3 = x .&. 0xFF
instance ToColor (Word8, Word8, Word8) where
toColor (r,g,b) = Just $ RGB r g b
instance ToColor (Double, Double, Double) where
toColor (r,g,b) | r >= 0 && g >= 0 && b >= 0 && r <= 1 && g <= 1 && b <= 1 =
Just $ RGB (floor $ r * 255) (floor $ g * 255) (floor $ b * 255)
toColor _ = Nothing
instance FromJSON Color where
parseJSON (String t) = maybe mempty return $ toColor (Text.unpack t)
parseJSON _ = mempty
instance ToJSON Color where
toJSON color = String (Text.pack (fromColor color :: String))
class FromColor a where
fromColor :: Color -> a
instance FromColor String where
fromColor (RGB r g b) = printf "#%02x%02x%02x" r g b
instance FromColor (Double, Double, Double) where
fromColor (RGB r g b) = (fromIntegral r / 255, fromIntegral g / 255, fromIntegral b / 255)
instance FromColor (Word8, Word8, Word8) where
fromColor (RGB r g b) = (r, g, b)
data Style = Style {
tokenStyles :: Map.Map TokenType TokenStyle
, defaultColor :: Maybe Color
, backgroundColor :: Maybe Color
, lineNumberColor :: Maybe Color
, lineNumberBackgroundColor :: Maybe Color
} deriving (Read, Show, Eq, Ord, Data, Typeable, Generic)
instance Binary Style
instance FromJSON Style where
parseJSON (Object v) = do
(tokstyles :: Map.Map Text TokenStyle) <- v .: "text-styles"
(editorColors :: Map.Map Text Color) <- v .:? "editor-colors" .!= mempty
mbBackgroundColor <- v .:? "background-color"
mbLineNumberColor <- v .:? "line-number-color"
mbDefaultColor <- v .:? "text-color"
mbLineNumberBackgroundColor <- v .:? "line-number-background-color"
return Style{ defaultColor = mbDefaultColor `mplus`
(case Map.lookup "Normal" tokstyles of
Nothing -> Nothing
Just ts -> tokenColor ts)
, backgroundColor = mbBackgroundColor `mplus`
Map.lookup "background-color" editorColors
, lineNumberColor = mbLineNumberColor `mplus`
Map.lookup "line-numbers" editorColors
, lineNumberBackgroundColor =
mbLineNumberBackgroundColor `mplus`
Map.lookup "background-color" editorColors
, tokenStyles =
Map.mapKeys (\s -> maybe OtherTok id $
readMay (Text.unpack s ++ "Tok")) tokstyles }
parseJSON _ = mempty
instance ToJSON Style where
toJSON s = object [ "text-styles" .= toJSON (tokenStyles s)
, "background-color" .= toJSON (backgroundColor s)
, "text-color" .= toJSON (defaultColor s)
, "line-number-color" .= toJSON (lineNumberColor s)
, "line-number-background-color" .=
toJSON (lineNumberBackgroundColor s)
]
data FormatOptions = FormatOptions{
numberLines :: Bool
, startNumber :: Int
, lineAnchors :: Bool
, titleAttributes :: Bool
, codeClasses :: [Text]
, containerClasses :: [Text]
, lineIdPrefix :: Text
} deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
instance Binary FormatOptions
defaultFormatOpts :: FormatOptions
defaultFormatOpts = FormatOptions{
numberLines = False
, startNumber = 1
, lineAnchors = False
, titleAttributes = False
, codeClasses = []
, containerClasses = []
, lineIdPrefix = ""
}