{-# LANGUAGE CPP #-}
module Skylighting.Format.HTML (
formatHtmlInline
, formatHtmlBlock
, styleToCss
) where
import Data.List (intersperse, sort)
import qualified Data.Map as Map
import qualified Data.Text as Text
import Skylighting.Types
import Text.Blaze.Html
import qualified Text.Blaze.Html5 as H
import qualified Text.Blaze.Html5.Attributes as A
import Data.String (fromString)
#if !MIN_VERSION_base(4,11,0)
import Data.Semigroup
#endif
formatHtmlInline :: FormatOptions -> [SourceLine] -> Html
formatHtmlInline :: FormatOptions -> [SourceLine] -> Html
formatHtmlInline FormatOptions
opts = FormatOptions -> Html -> Html
wrapCode FormatOptions
opts
(Html -> Html) -> ([SourceLine] -> Html) -> [SourceLine] -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Html] -> Html
forall a. Monoid a => [a] -> a
mconcat ([Html] -> Html)
-> ([SourceLine] -> [Html]) -> [SourceLine] -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Html -> [Html] -> [Html]
forall a. a -> [a] -> [a]
intersperse ([Char] -> Html
forall a. ToMarkup a => a -> Html
toHtml [Char]
"\n")
([Html] -> [Html])
-> ([SourceLine] -> [Html]) -> [SourceLine] -> [Html]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceLine -> Html) -> [SourceLine] -> [Html]
forall a b. (a -> b) -> [a] -> [b]
map ((Token -> Html) -> SourceLine -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (FormatOptions -> Token -> Html
tokenToHtml FormatOptions
opts))
formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html
formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html
formatHtmlBlock FormatOptions
opts [SourceLine]
ls =
Html -> Html
H.div (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.class_ ([Char] -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue [Char]
"sourceCode") (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$
Html -> Html
H.pre (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (Text -> AttributeValue) -> Text -> AttributeValue
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
Text.unwords [Text]
classes)
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ FormatOptions -> Html -> Html
wrapCode FormatOptions
opts
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ [Html] -> Html
forall a. Monoid a => [a] -> a
mconcat ([Html] -> Html) -> ([Html] -> [Html]) -> [Html] -> Html
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Html -> [Html] -> [Html]
forall a. a -> [a] -> [a]
intersperse ([Char] -> Html
forall a. ToMarkup a => a -> Html
toHtml [Char]
"\n")
([Html] -> Html) -> [Html] -> Html
forall a b. (a -> b) -> a -> b
$ (LineNo -> SourceLine -> Html)
-> [LineNo] -> [SourceLine] -> [Html]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (FormatOptions -> LineNo -> SourceLine -> Html
sourceLineToHtml FormatOptions
opts) [LineNo
startNum..] [SourceLine]
ls
where classes :: [Text]
classes = [Char] -> Text
Text.pack [Char]
"sourceCode" Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
:
[[Char] -> Text
Text.pack [Char]
"numberSource" | FormatOptions -> Bool
numberLines FormatOptions
opts] [Text] -> [Text] -> [Text]
forall a. [a] -> [a] -> [a]
++
[Text
x | Text
x <- FormatOptions -> [Text]
containerClasses FormatOptions
opts
, Text
x Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char] -> Text
Text.pack [Char]
"sourceCode"]
startNum :: LineNo
startNum = Int -> LineNo
LineNo (Int -> LineNo) -> Int -> LineNo
forall a b. (a -> b) -> a -> b
$ FormatOptions -> Int
startNumber FormatOptions
opts
wrapCode :: FormatOptions -> Html -> Html
wrapCode :: FormatOptions -> Html -> Html
wrapCode FormatOptions
opts Html
h = Html -> Html
H.code (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.class_ (Text -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (Text -> AttributeValue) -> Text -> AttributeValue
forall a b. (a -> b) -> a -> b
$ [Text] -> Text
Text.unwords
([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Char] -> Text
Text.pack [Char]
"sourceCode"
Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: FormatOptions -> [Text]
codeClasses FormatOptions
opts)
(Html -> Html) -> (Bool, Attribute) -> Html -> Html
forall h. Attributable h => h -> (Bool, Attribute) -> h
!? (Int
startZero Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0, AttributeValue -> Attribute
A.style ([Char] -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue [Char]
counterOverride))
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
h
where counterOverride :: [Char]
counterOverride = [Char]
"counter-reset: source-line " [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show Int
startZero [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> [Char]
";"
startZero :: Int
startZero = FormatOptions -> Int
startNumber FormatOptions
opts Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
sourceLineToHtml :: FormatOptions -> LineNo -> SourceLine -> Html
sourceLineToHtml :: FormatOptions -> LineNo -> SourceLine -> Html
sourceLineToHtml FormatOptions
opts LineNo
lno SourceLine
cont =
Html -> Html
H.span (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.id AttributeValue
lineNum
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ do
Html -> Html
H.a (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.href AttributeValue
lineRef
(Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! (if FormatOptions -> Bool
numberLines FormatOptions
opts
then Attribute
forall a. Monoid a => a
mempty
else Tag -> AttributeValue -> Attribute
customAttribute ([Char] -> Tag
forall a. IsString a => [Char] -> a
fromString [Char]
"aria-hidden")
([Char] -> AttributeValue
forall a. IsString a => [Char] -> a
fromString [Char]
"true"))
(Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Html
forall a. Monoid a => a
mempty
(Token -> Html) -> SourceLine -> Html
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (FormatOptions -> Token -> Html
tokenToHtml FormatOptions
opts) SourceLine
cont
where lineNum :: AttributeValue
lineNum = [Char] -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue [Char]
prefixedLineNo
lineRef :: AttributeValue
lineRef = [Char] -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue (Char
'#'Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
:[Char]
prefixedLineNo)
prefixedLineNo :: [Char]
prefixedLineNo = Text -> [Char]
Text.unpack (FormatOptions -> Text
lineIdPrefix FormatOptions
opts) [Char] -> [Char] -> [Char]
forall a. Semigroup a => a -> a -> a
<> Int -> [Char]
forall a. Show a => a -> [Char]
show (LineNo -> Int
lineNo LineNo
lno)
tokenToHtml :: FormatOptions -> Token -> Html
tokenToHtml :: FormatOptions -> Token -> Html
tokenToHtml FormatOptions
_ (TokenType
NormalTok, Text
txt) = Text -> Html
forall a. ToMarkup a => a -> Html
toHtml Text
txt
tokenToHtml FormatOptions
opts (TokenType
toktype, Text
txt) =
if FormatOptions -> Bool
titleAttributes FormatOptions
opts
then Html
sp Html -> Attribute -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.title ([Char] -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue ([Char] -> AttributeValue) -> [Char] -> AttributeValue
forall a b. (a -> b) -> a -> b
$ TokenType -> [Char]
forall a. Show a => a -> [Char]
show TokenType
toktype)
else Html
sp
where sp :: Html
sp = Html -> Html
H.span (Html -> Html) -> Attribute -> Html -> Html
forall h. Attributable h => h -> Attribute -> h
! AttributeValue -> Attribute
A.class_ ([Char] -> AttributeValue
forall a. ToValue a => a -> AttributeValue
toValue ([Char] -> AttributeValue) -> [Char] -> AttributeValue
forall a b. (a -> b) -> a -> b
$ TokenType -> [Char]
short TokenType
toktype) (Html -> Html) -> Html -> Html
forall a b. (a -> b) -> a -> b
$ Text -> Html
forall a. ToMarkup a => a -> Html
toHtml Text
txt
short :: TokenType -> String
short :: TokenType -> [Char]
short TokenType
KeywordTok = [Char]
"kw"
short TokenType
DataTypeTok = [Char]
"dt"
short TokenType
DecValTok = [Char]
"dv"
short TokenType
BaseNTok = [Char]
"bn"
short TokenType
FloatTok = [Char]
"fl"
short TokenType
CharTok = [Char]
"ch"
short TokenType
StringTok = [Char]
"st"
short TokenType
CommentTok = [Char]
"co"
short TokenType
OtherTok = [Char]
"ot"
short TokenType
AlertTok = [Char]
"al"
short TokenType
FunctionTok = [Char]
"fu"
short TokenType
RegionMarkerTok = [Char]
"re"
short TokenType
ErrorTok = [Char]
"er"
short TokenType
ConstantTok = [Char]
"cn"
short TokenType
SpecialCharTok = [Char]
"sc"
short TokenType
VerbatimStringTok = [Char]
"vs"
short TokenType
SpecialStringTok = [Char]
"ss"
short TokenType
ImportTok = [Char]
"im"
short TokenType
DocumentationTok = [Char]
"do"
short TokenType
AnnotationTok = [Char]
"an"
short TokenType
CommentVarTok = [Char]
"cv"
short TokenType
VariableTok = [Char]
"va"
short TokenType
ControlFlowTok = [Char]
"cf"
short TokenType
OperatorTok = [Char]
"op"
short TokenType
BuiltInTok = [Char]
"bu"
short TokenType
ExtensionTok = [Char]
"ex"
short TokenType
PreprocessorTok = [Char]
"pp"
short TokenType
AttributeTok = [Char]
"at"
short TokenType
InformationTok = [Char]
"in"
short TokenType
WarningTok = [Char]
"wa"
short TokenType
NormalTok = [Char]
""
styleToCss :: Style -> String
styleToCss :: Style -> [Char]
styleToCss Style
f = [[Char]] -> [Char]
unlines ([[Char]] -> [Char]) -> [[Char]] -> [Char]
forall a b. (a -> b) -> a -> b
$
[[Char]]
divspec [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]]
numberspec [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]]
colorspec [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++ [[Char]]
linkspec [[Char]] -> [[Char]] -> [[Char]]
forall a. [a] -> [a] -> [a]
++
[[Char]] -> [[Char]]
forall a. Ord a => [a] -> [a]
sort (((TokenType, TokenStyle) -> [Char])
-> [(TokenType, TokenStyle)] -> [[Char]]
forall a b. (a -> b) -> [a] -> [b]
map (TokenType, TokenStyle) -> [Char]
toCss (Map TokenType TokenStyle -> [(TokenType, TokenStyle)]
forall k a. Map k a -> [(k, a)]
Map.toList (Style -> Map TokenType TokenStyle
tokenStyles Style
f)))
where colorspec :: [[Char]]
colorspec = [Char] -> [[Char]]
forall (f :: * -> *) a. Applicative f => a -> f a
pure ([Char] -> [[Char]])
-> ([[Char]] -> [Char]) -> [[Char]] -> [[Char]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Char]] -> [Char]
unwords ([[Char]] -> [[Char]]) -> [[Char]] -> [[Char]]
forall a b. (a -> b) -> a -> b
$ [
[Char]
"div.sourceCode\n {"
, [Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
c -> [Char]
"color: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
";") (Style -> Maybe Color
defaultColor Style
f)
, [Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
c -> [Char]
"background-color: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
";") (Style -> Maybe Color
backgroundColor Style
f)
, [Char]
"}"
]
numberspec :: [[Char]]
numberspec = [
[Char]
"pre.numberSource code"
, [Char]
" { counter-reset: source-line 0; }"
, [Char]
"pre.numberSource code > span"
, [Char]
" { position: relative; left: -4em; counter-increment: source-line; }"
, [Char]
"pre.numberSource code > span > a:first-child::before"
, [Char]
" { content: counter(source-line);"
, [Char]
" position: relative; left: -1em; text-align: right; vertical-align: baseline;"
, [Char]
" border: none; display: inline-block;"
, [Char]
" -webkit-touch-callout: none; -webkit-user-select: none;"
, [Char]
" -khtml-user-select: none; -moz-user-select: none;"
, [Char]
" -ms-user-select: none; user-select: none;"
, [Char]
" padding: 0 4px; width: 4em;"
, [Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
c -> [Char]
" background-color: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
";\n")
(Style -> Maybe Color
lineNumberBackgroundColor Style
f) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
c -> [Char]
" color: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
";\n")
(Style -> Maybe Color
lineNumberColor Style
f) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" }"
, [Char]
"pre.numberSource { margin-left: 3em; " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
c -> [Char]
"border-left: 1px solid " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
c [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"; ") (Style -> Maybe Color
lineNumberColor Style
f) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++
[Char]
" padding-left: 4px; }"
]
divspec :: [[Char]]
divspec = [
[Char]
"pre > code.sourceCode { white-space: pre; position: relative; }"
, [Char]
"pre > code.sourceCode > span { display: inline-block; line-height: 1.25; }"
, [Char]
"pre > code.sourceCode > span:empty { height: 1.2em; }"
, [Char]
"code.sourceCode > span { color: inherit; text-decoration: inherit; }"
, [Char]
"div.sourceCode { margin: 1em 0; }"
, [Char]
"pre.sourceCode { margin: 0; }"
, [Char]
"@media screen {"
, [Char]
"div.sourceCode { overflow: auto; }"
, [Char]
"}"
, [Char]
"@media print {"
, [Char]
"pre > code.sourceCode { white-space: pre-wrap; }"
, [Char]
"pre > code.sourceCode > span { text-indent: -5em; padding-left: 5em; }"
, [Char]
"}"
]
linkspec :: [[Char]]
linkspec = [ [Char]
"@media screen {"
, [Char]
"pre > code.sourceCode > span > a:first-child::before { text-decoration: underline; }"
, [Char]
"}"
]
toCss :: (TokenType, TokenStyle) -> String
toCss :: (TokenType, TokenStyle) -> [Char]
toCss (TokenType
t,TokenStyle
tf) = [Char]
"code span" [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ (if [Char] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (TokenType -> [Char]
short TokenType
t) then [Char]
"" else (Char
'.' Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: TokenType -> [Char]
short TokenType
t)) [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" { "
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
colorspec [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
backgroundspec [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
weightspec [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
stylespec
[Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
decorationspec [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"} /* " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ TokenType -> [Char]
forall a. Show a => a -> [Char]
showTokenType TokenType
t [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" */"
where colorspec :: [Char]
colorspec = [Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
col -> [Char]
"color: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
col [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"; ") (Maybe Color -> [Char]) -> Maybe Color -> [Char]
forall a b. (a -> b) -> a -> b
$ TokenStyle -> Maybe Color
tokenColor TokenStyle
tf
backgroundspec :: [Char]
backgroundspec = [Char] -> (Color -> [Char]) -> Maybe Color -> [Char]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\Color
col -> [Char]
"background-color: " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Color -> [Char]
forall a. FromColor a => Color -> a
fromColor Color
col [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
"; ") (Maybe Color -> [Char]) -> Maybe Color -> [Char]
forall a b. (a -> b) -> a -> b
$ TokenStyle -> Maybe Color
tokenBackground TokenStyle
tf
weightspec :: [Char]
weightspec = if TokenStyle -> Bool
tokenBold TokenStyle
tf then [Char]
"font-weight: bold; " else [Char]
""
stylespec :: [Char]
stylespec = if TokenStyle -> Bool
tokenItalic TokenStyle
tf then [Char]
"font-style: italic; " else [Char]
""
decorationspec :: [Char]
decorationspec = if TokenStyle -> Bool
tokenUnderline TokenStyle
tf then [Char]
"text-decoration: underline; " else [Char]
""
showTokenType :: a -> [Char]
showTokenType a
t' = case [Char] -> [Char]
forall a. [a] -> [a]
reverse (a -> [Char]
forall a. Show a => a -> [Char]
show a
t') of
Char
'k':Char
'o':Char
'T':[Char]
xs -> [Char] -> [Char]
forall a. [a] -> [a]
reverse [Char]
xs
[Char]
_ -> [Char]
""