{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ViewPatterns #-}
module Dhall.Docs.CodeRenderer
( renderCodeWithHyperLinks
, renderCodeSnippet
, ExprType(..)
) where
import Control.Monad.Trans.Writer.Strict (Writer)
import Data.Text (Text)
import Data.Void (Void)
import Dhall.Context (Context)
import Dhall.Core
( Binding (..)
, Expr (..)
, FieldSelection (..)
, File (..)
, FilePrefix (..)
, FunctionBinding (..)
, Import (..)
, ImportHashed (..)
, ImportType (..)
, RecordField (..)
, Scheme (..)
, URL (..)
, Var (..)
)
import Dhall.Docs.Util
import Dhall.Src (Src (..))
import Lucid
import Text.Megaparsec.Pos (SourcePos (..))
import qualified Control.Monad.Trans.Writer.Strict as Writer
import qualified Data.Maybe as Maybe
import qualified Data.List
import qualified Data.Set as Set
import qualified Data.Text as Text
import qualified Data.Text.Prettyprint.Doc as Pretty
import qualified Data.Text.Prettyprint.Doc.Render.Text as Pretty.Text
import qualified Dhall.Context as Context
import qualified Dhall.Core as Core
import qualified Dhall.Map as Map
import qualified Dhall.Parser
import qualified Dhall.Pretty
import qualified Lens.Family as Lens
import qualified Text.Megaparsec.Pos as SourcePos
getSourceLine, getSourceColumn :: SourcePos -> Int
getSourceLine = SourcePos.unPos . SourcePos.sourceLine
getSourceColumn = SourcePos.unPos . SourcePos.sourceColumn
data JtdInfo
= RecordFields (Set.Set NameDecl)
| NoInfo
deriving (Eq, Ord, Show)
data NameDecl = NameDecl Src Text JtdInfo
deriving (Eq, Ord, Show)
makeHtmlId :: NameDecl -> Text
makeHtmlId (NameDecl Src{srcStart} _ _) =
"var"
<> Text.pack (show $ getSourceLine srcStart) <> "-"
<> Text.pack (show $ getSourceColumn srcStart)
data SourceCodeType
= ImportExpr Import
| NameUse NameDecl
| NameDeclaration NameDecl
data SourceCodeFragment =
SourceCodeFragment
Src
SourceCodeType
fragments :: Expr Src Import -> [SourceCodeFragment]
fragments = Data.List.sortBy sorter . removeUnusedDecls . Writer.execWriter . infer Context.empty
where
sorter (SourceCodeFragment Src{srcStart = srcStart0} _)
(SourceCodeFragment Src{srcStart = srcStart1} _) = pos0 `compare` pos1
where
pos0 = (getSourceLine srcStart0, getSourceColumn srcStart0)
pos1 = (getSourceLine srcStart1, getSourceColumn srcStart1)
removeUnusedDecls sourceCodeFragments = filter isUsed sourceCodeFragments
where
makePosPair Src{srcStart} = (getSourceLine srcStart, getSourceColumn srcStart)
nameUsePos (SourceCodeFragment _ (NameUse (NameDecl src _ _))) =
Just $ makePosPair src
nameUsePos _ = Nothing
usedNames = Set.fromList $ Maybe.mapMaybe nameUsePos sourceCodeFragments
isUsed (SourceCodeFragment _ (NameDeclaration (NameDecl src _ _))) =
makePosPair src `Set.member` usedNames
isUsed _ = True
infer :: Context NameDecl -> Expr Src Import -> Writer [SourceCodeFragment] JtdInfo
infer context = \case
Note src (Embed a) -> Writer.tell [SourceCodeFragment src $ ImportExpr a] >> return NoInfo
Let (Binding
(Just Src { srcEnd = srcEnd0 })
name
(Just Src { srcStart = srcStart1 })
annotation
_
value) expr' -> do
case annotation of
Nothing -> return ()
Just (_, t) -> do
_ <- infer context t
return ()
bindingJtdInfo <- infer context value
let nameSrc = makeSrcForLabel srcEnd0 srcStart1 name
let nameDecl = NameDecl nameSrc name bindingJtdInfo
Writer.tell [SourceCodeFragment nameSrc (NameDeclaration nameDecl)]
infer (Context.insert name nameDecl context) expr'
Note src (Var (V name index)) ->
case Context.lookup name index context of
Nothing -> return NoInfo
Just nameDecl@(NameDecl _ _ t) -> do
Writer.tell [SourceCodeFragment src $ NameUse nameDecl]
return t
Lam (FunctionBinding
(Just Src{srcEnd = srcEnd0})
name
(Just Src{srcStart = srcStart1})
_
t) expr -> do
dhallType <- infer context t
let nameSrc = makeSrcForLabel srcEnd0 srcStart1 name
let nameDecl = NameDecl nameSrc name dhallType
Writer.tell [SourceCodeFragment nameSrc (NameDeclaration nameDecl)]
infer (Context.insert name nameDecl context) expr
Field e (FieldSelection (Just Src{srcEnd=posStart}) label (Just Src{srcStart=posEnd})) -> do
fields <- do
dhallType <- infer context e
case dhallType of
NoInfo -> return mempty
RecordFields s -> return $ Set.toList s
let src = makeSrcForLabel posStart posEnd label
let match (NameDecl _ l _) = l == label
case filter match fields of
x@(NameDecl _ _ t) : _ -> do
Writer.tell [SourceCodeFragment src (NameUse x)]
return t
_ -> return NoInfo
RecordLit (Map.toList -> l) -> handleRecordLike l
Record (Map.toList -> l) -> handleRecordLike l
Note _ e -> infer context e
e -> do
mapM_ (infer context) $ Lens.toListOf Core.subExpressions e
return NoInfo
where
handleRecordLike l = RecordFields . Set.fromList <$> mapM f l
where
f (key, RecordField (Just Src{srcEnd = startPos}) val (Just Src{srcStart = endPos}) _) = do
dhallType <- infer context val
let nameSrc = makeSrcForLabel startPos endPos key
let nameDecl = NameDecl nameSrc key dhallType
Writer.tell [SourceCodeFragment nameSrc (NameDeclaration nameDecl)]
return nameDecl
where
f _ = fileAnIssue "A `RecordField` of type `Expr Src Import` doesn't have `Just src*`"
fileAsText :: File -> Text
fileAsText File{..} = foldr (\d acc -> acc <> "/" <> d) "" (Core.components directory)
<> "/" <> file
makeSrcForLabel
:: SourcePos
-> SourcePos
-> Text
-> Src
makeSrcForLabel srcStart srcEnd name = Src {..}
where
realLength = getSourceColumn srcEnd - getSourceColumn srcStart
srcText =
if Text.length name == realLength then name
else "`" <> name <> "`"
renderSourceCodeFragment :: SourceCodeFragment -> Html ()
renderSourceCodeFragment (SourceCodeFragment Src{..} (ImportExpr import_)) =
renderImport import_ srcText
where
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
renderSourceCodeFragment (SourceCodeFragment Src{..} (NameDeclaration nameDecl)) =
span_ attributes $ toHtml srcText
where
attributes =
[id_ $ makeHtmlId nameDecl
, class_ "name-decl"
, data_ "name" $ makeHtmlId nameDecl ]
renderSourceCodeFragment (SourceCodeFragment Src{..} (NameUse nameDecl)) =
a_ attributes $ toHtml srcText
where
attributes =
[ href_ $ "#" <> makeHtmlId nameDecl
, class_ "name-use"
, data_ "name" $ makeHtmlId nameDecl
]
renderCodeWithHyperLinks :: Text -> Expr Src Import -> Html ()
renderCodeWithHyperLinks contents expr = pre_ $ go (1, 1) (Text.lines contents) imports
where
imports = fragments expr
go :: (Int, Int) -> [Text] -> [SourceCodeFragment] -> Html ()
go _ textLines [] = mapM_ (\t -> toHtml t >> br_ []) textLines
go (currLineNumber, _) (currLine : restLines) scfs@((SourceCodeFragment Src {..} _) : _)
| getSourceLine srcStart /= currLineNumber = do
toHtml currLine
br_ []
go (currLineNumber + 1, 1) restLines scfs
go (_, currCol) currentLines (scf@(SourceCodeFragment Src {..} _) : rest) = do
let importStartLine = getSourceLine srcStart
let importEndLine = getSourceLine srcEnd
let importStartCol = getSourceColumn srcStart
let importEndCol = getSourceColumn srcEnd
let (importLines, suffixLines) = splitAt (importEndLine - importStartLine + 1) currentLines
let (firstImportLine, lastImportLine) = (head importLines, last importLines)
let prefixCols = Text.take (importStartCol - currCol) firstImportLine
let suffixCols = Text.drop (importEndCol - currCol) lastImportLine
toHtml prefixCols
renderSourceCodeFragment scf
if Text.null suffixCols then br_ [] else return ()
let suffix = if Text.null suffixCols then suffixLines else suffixCols : suffixLines
let nextPosition = if 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.removeTrailingWhitespace . Pretty.layoutSmart opts
where
opts = Pretty.defaultLayoutOptions
{ Pretty.layoutPageWidth =
Pretty.Unbounded
}