Skip to content

Commit

Permalink
Merge pull request #14 from dbaynard/feat/line-numbers
Browse files Browse the repository at this point in the history
Wrap source lines and re-implement line numbers
  • Loading branch information
jgm authored Sep 9, 2017
2 parents 88142fa + 8496843 commit 9ff873c
Show file tree
Hide file tree
Showing 3 changed files with 82 additions and 41 deletions.
15 changes: 15 additions & 0 deletions changelog.md
Original file line number Diff line number Diff line change
@@ -1,5 +1,20 @@
# Revision history for skylighting

## Next version

* Wrap lines of source code in a `div` with `display` set to `inline-block`.
The `div`s make per-line processing easier. They cannot be set as
`display: block` as that introduces extra new lines when copying and pasting.
* Render line numbers in html using css pseudo elements rather than a table.
The line numbers are always produced, as `data-line-number` attributes, and
css to display them as `::before` elements are always produced. The option to
switch on line numbering only toggles a class; this means it is possible to toggle
line numbering without re-running skylighting.
* If the `linkAnchors` option is set, wrap with an `a` element rather than a `div`,
set so that clicking the line number (and only the line number) will jump to that
line.
* Code wraps by default when html is printed, with wrapped lines indented.

## 0.3.3.1 -- 2017-06-26

* Updated xml syntax definitions and clojure test.
Expand Down
102 changes: 62 additions & 40 deletions src/Skylighting/Format/HTML.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@ module Skylighting.Format.HTML (
) where

import Data.List (intersperse)
import Data.String (fromString)
import qualified Data.Text as Text
import Skylighting.Types
import Text.Blaze.Html
Expand Down Expand Up @@ -50,7 +51,8 @@ formatHtmlInline opts = (H.code ! A.class_ (toValue $ Text.unwords
$ Text.pack "sourceCode"
: codeClasses opts))
. mconcat . intersperse (toHtml "\n")
. map (sourceLineToHtml opts)
. zipWith (sourceLineToHtml opts) [startNum..]
where startNum = LineNo $ startNumber opts

tokenToHtml :: FormatOptions -> Token -> Html
tokenToHtml _ (NormalTok, txt) = toHtml txt
Expand Down Expand Up @@ -93,67 +95,87 @@ short InformationTok = "in"
short WarningTok = "wa"
short NormalTok = ""

sourceLineToHtml :: FormatOptions -> SourceLine -> Html
sourceLineToHtml opts cont = mapM_ (tokenToHtml opts) cont
-- | Each line of source is wrapped in an (inline-block) div that makes
-- subsequent per-line processing (e.g. adding line numnbers) possible.
sourceLineToHtml :: FormatOptions -> LineNo -> SourceLine -> Html
sourceLineToHtml opts lno cont = wrapElement ! A.class_ sourceLine
! A.id lineNum
! A.href lineRef
! H.dataAttribute (fromString "line-number") lineNum $
mapM_ (tokenToHtml opts) cont
where sourceLine = toValue "sourceLine"
lineNum = toValue . show . lineNo $ lno
lineRef = toValue . ('#':) . show . lineNo $ lno
wrapElement = if lineAnchors opts
then H.a
else H.div

formatHtmlBlockPre :: FormatOptions -> [SourceLine] -> Html
formatHtmlBlockPre opts = H.pre . formatHtmlInline opts

-- | Format tokens as an HTML @pre@ block. If line numbering is
-- selected, this is put into a table row with line numbers in the
-- left cell. The whole code block is wrapped in a @div@ element
-- to aid styling (e.g. the overflow-x property). See the
-- documentation for 'formatHtmlInline' for information about how
-- | Format tokens as an HTML @pre@ block. Each line is wrapped in a div
-- with the class ‘source-line’. The whole code block is wrapped in a @div@
-- element to aid styling (e.g. the overflow-x property). If line numbering
-- is selected, this surrounding div is given the class ‘number-source’,
-- and the resulting html will display line numbers thanks to the included
-- css. Note that the html produced will always include the line numbers as
-- the 'data-line-number' attribute.
-- See the documentation for 'formatHtmlInline' for information about how
-- tokens are encoded.
formatHtmlBlock :: FormatOptions -> [SourceLine] -> Html
formatHtmlBlock opts ls = H.div ! A.class_ sourceCode $
container ! A.class_ (toValue $ Text.unwords classes)
where container = if numberLines opts
then H.table $ H.tr ! A.class_ sourceCode $
nums >> source
else pre
sourceCode = toValue "sourceCode"
pre ! A.class_ (toValue $ Text.unwords classes)
where sourceCode = toValue . Text.unwords $ Text.pack "sourceCode" :
if numberLines opts
then [Text.pack "numberSource"]
else []
classes = Text.pack "sourceCode" :
[x | x <- containerClasses opts, x /= Text.pack "sourceCode"]
pre = formatHtmlBlockPre opts ls
source = H.td ! A.class_ sourceCode $ pre
startNum = startNumber opts
nums = H.td ! A.class_ (toValue "lineNumbers")
$ H.pre
$ mapM_ lineNum [startNum..(startNum + length ls - 1)]
lineNum n = if lineAnchors opts
then (H.a ! A.id (toValue nStr) ! A.href (toValue $ "#" ++ nStr) $ toHtml $ show n)
>> toHtml "\n"
else toHtml $ show n ++ "\n"
where nStr = show n

-- | Returns CSS for styling highlighted code according to the given style.
styleToCss :: Style -> String
styleToCss f = unlines $ divspec ++ tablespec ++ colorspec ++ map toCss (tokenStyles f)
styleToCss f = unlines $ divspec ++ numberspec ++ colorspec ++ linkspec ++ map toCss (tokenStyles f)
where colorspec = case (defaultColor f, backgroundColor f) of
(Nothing, Nothing) -> []
(Just c, Nothing) -> ["pre, code { color: " ++ fromColor c ++ "; }"]
(Nothing, Just c) -> ["pre, code { background-color: " ++ fromColor c ++ "; }"]
(Just c1, Just c2) -> ["pre, code { color: " ++ fromColor c1 ++ "; background-color: " ++
fromColor c2 ++ "; }"]
tablespec = [
"table.sourceCode, tr.sourceCode, td.lineNumbers, td.sourceCode {"
," margin: 0; padding: 0; vertical-align: baseline; border: none; }"
,"table.sourceCode { width: 100%; line-height: 100%; " ++
maybe "" (\c -> "background-color: " ++ fromColor c ++ "; ") (backgroundColor f) ++
maybe "" (\c -> "color: " ++ fromColor c ++ "; ") (defaultColor f) ++
"}"
,"td.lineNumbers { text-align: right; padding-right: 4px; padding-left: 4px; " ++
maybe "" (\c -> "background-color: " ++ fromColor c ++ "; ") (lineNumberBackgroundColor f) ++
maybe "" (\c -> "color: " ++ fromColor c ++ "; ") (lineNumberColor f) ++
maybe "" (\c -> "border-right: 1px solid " ++ fromColor c ++ "; ") (lineNumberColor f) ++
"}"
,"td.sourceCode { padding-left: 5px; }"
numberspec = [
".numberSource div.sourceLine, .numberSource a.sourceLine"
, " { position: relative; }"
, ".numberSource div.sourceLine::before, .numberSource a.sourceLine::before"
, " { content: attr(data-line-number);"
, " position: absolute; left: -5em; text-align: right; vertical-align: baseline;"
, " border: none; pointer-events: all; "
, " -webkit-touch-callout: none; -webkit-user-select: none;"
, " -khtml-user-select: none; -moz-user-select: none;"
, " -ms-user-select: none; user-select: none;"
, " padding: 0 4px; width: 4em; }"
, ".numberSource pre.sourceCode { margin-left: 3em;" ++
maybe "" (\c -> "border-left: 1px solid " ++ fromColor c ++ "; ") (lineNumberColor f) ++
maybe "" (\c -> "background-color: " ++ fromColor c ++ "; ") (lineNumberBackgroundColor f) ++
maybe "" (\c -> "color: " ++ fromColor c ++ "; ") (lineNumberColor f) ++
" padding-left: 4px; }"
]
divspec = [ "div.sourceCode { overflow-x: auto; }"
, "div.sourceLine, a.sourceLine { display: inline-block; min-height: 1.25em; }"
, "a.sourceLine { pointer-events: none; color: inherit; text-decoration: inherit; }"
, ".sourceCode { overflow: visible; }"
, "code.sourceCode { white-space: pre; }"
, "@media print {"
, "code.sourceCode { white-space: pre-wrap; }"
, "div.sourceLine, a.sourceLine { text-indent: -1em; padding-left: 1em; }"
, "}"
]
linkspec = [ "@media screen {"
, "a.sourceLine::before { text-decoration: underline; color = initial; }"
, "}"
]
divspec = [ "div.sourceCode { overflow-x: auto; }" ]

toCss :: (TokenType, TokenStyle) -> String
toCss (t,tf) = "code > span." ++ short t ++ " { "
toCss (t,tf) = "code span." ++ short t ++ " { "
++ colorspec ++ backgroundspec ++ weightspec ++ stylespec
++ decorationspec ++ "} /* " ++ showTokenType t ++ " */"
where colorspec = maybe "" (\col -> "color: " ++ fromColor col ++ "; ") $ tokenColor tf
Expand Down
6 changes: 5 additions & 1 deletion src/Skylighting/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-- | Basic types for Skylighting.
module Skylighting.Types (
Expand All @@ -23,6 +24,7 @@ module Skylighting.Types (
, Token
, TokenType(..)
, SourceLine
, LineNo(..)
-- * Styles
, TokenStyle(..)
, defStyle
Expand Down Expand Up @@ -216,6 +218,9 @@ instance FromJSON TokenType where
-- | A line of source: a list of labeled tokens.
type SourceLine = [Token]

-- | Line numbers
newtype LineNo = LineNo { lineNo :: Int } deriving (Show, Enum)

-- | A 'TokenStyle' determines how a token is to be rendered.
data TokenStyle = TokenStyle {
tokenColor :: Maybe Color
Expand Down Expand Up @@ -345,7 +350,6 @@ data FormatOptions = FormatOptions{
, titleAttributes :: Bool -- ^ Html titles with token types
, codeClasses :: [Text] -- ^ Additional classes for Html code tag
, containerClasses :: [Text] -- ^ Additional classes for Html container tag
-- (pre or table depending on numberLines)
} deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)

instance Binary FormatOptions
Expand Down

0 comments on commit 9ff873c

Please sign in to comment.