{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Dhall.Docs.CodeRenderer
( renderCodeWithHyperLinks
, renderCodeSnippet
, ExprType(..)
) where
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Core
( Expr (..)
, File (..)
, FilePrefix (..)
, Import (..)
, ImportHashed (..)
, ImportType (..)
, Scheme (..)
, URL (..)
)
import Dhall.Docs.Util
import Dhall.Src (Src (..))
import Lucid
import qualified Data.Text
import qualified Data.Text.Prettyprint.Doc as Pretty
import qualified Data.Text.Prettyprint.Doc.Render.Text as Pretty.Text
import qualified Dhall.Core as Core
import qualified Dhall.Parser
import qualified Dhall.Pretty
import qualified Lens.Family as Lens
import qualified Text.Megaparsec.Pos as SourcePos
getImports :: Expr Src Import -> [(Src, Import)]
getImports (Note src (Embed a)) = [(src, a)]
getImports expr = concatMap getImports $ Lens.toListOf Core.subExpressions expr
fileAsText :: File -> Text
fileAsText File{..} = foldr (\d acc -> acc <> "/" <> d) "" (Core.components directory)
<> "/" <> file
renderImport :: Import -> Text -> Html ()
renderImport (Import {importHashed = ImportHashed { importType }}) =
case importType of
Remote URL {..} -> a_ [href_ href, target_ "_blank"] . toHtml
where
scheme_ = case scheme of
HTTP -> "http"
HTTPS -> "https"
path_ = fileAsText path
query_ = case query of
Nothing -> ""
Just d -> "?" <> d
href = scheme_ <> "://" <> authority <> path_ <> query_
Local Here file -> a_ [href_ href] . toHtml
where
href = "." <> fileAsText file <> ".html"
Local Parent file -> a_ [href_ href] . toHtml
where
href = ".." <> fileAsText file <> ".html"
_ -> toHtml
renderCodeWithHyperLinks :: Text -> Expr Src Import -> Html ()
renderCodeWithHyperLinks contents expr = pre_ $ go (1, 1) (Data.Text.lines contents) imports
where
imports = getImports expr
go :: (Int, Int) -> [Text] -> [(Src, Import)] -> Html ()
go _ textLines [] = mapM_ (\t -> toHtml t >> br_ []) textLines
go (currLine, currCol) currentLines ((Src {..}, import_) : rest) = do
let sourceLine = SourcePos.unPos . SourcePos.sourceLine
let sourceColumn = SourcePos.unPos . SourcePos.sourceColumn
let importStartLine = sourceLine srcStart
let importEndLine = sourceLine srcEnd
let importStartCol = sourceColumn srcStart
let importEndCol = sourceColumn srcEnd
let (prefixLines, restLines) = splitAt (importStartLine - currLine) currentLines
let (importLines, suffixLines) = splitAt (importStartLine - importStartLine + 1) restLines
let (firstImportLine, lastImportLine) = (head importLines, last importLines)
let prefixCols = Data.Text.take (importStartCol - currCol) firstImportLine
let suffixCols = Data.Text.drop (importEndCol - currCol) lastImportLine
mapM_ (\t -> toHtml t >> br_ []) prefixLines
toHtml prefixCols
renderImport import_ srcText
if Data.Text.null suffixCols then br_ [] else return ()
let suffix = if Data.Text.null suffixCols then suffixLines else suffixCols : suffixLines
let nextPosition = if Data.Text.null suffixCols then
(importEndLine + 1, 1)
else (importEndLine, importEndCol)
go nextPosition suffix rest
data ExprType = TypeAnnotation | AssertionExample
renderCodeSnippet :: Dhall.Pretty.CharacterSet -> ExprType -> Expr Void Import -> Html ()
renderCodeSnippet characterSet exprType expr = renderCodeWithHyperLinks formattedFile expr'
where
layout = case exprType of
AssertionExample -> Dhall.Pretty.layout
TypeAnnotation -> typeLayout
formattedFile = Pretty.Text.renderStrict
$ layout
$ Dhall.Pretty.prettyCharacterSet characterSet (Core.denote expr)
expr' = case Dhall.Parser.exprFromText "" formattedFile of
Right e -> e
Left _ -> fileAnIssue "A failure has occurred while parsing a formatted file"
typeLayout :: Pretty.Doc ann -> Pretty.SimpleDocStream ann
typeLayout = Pretty.removeTrailingWhitespace . Pretty.layoutSmart opts
where
opts :: Pretty.LayoutOptions
opts = Pretty.defaultLayoutOptions
{ Pretty.layoutPageWidth =
Pretty.Unbounded
}