mirror of
https://github.com/github/semantic.git
synced 2024-12-21 13:51:44 +03:00
Provide the declaration decorator in Renderer.
This commit is contained in:
parent
d9e21d2ab7
commit
aa45955ca3
@ -6,10 +6,8 @@ import Data.Maybe
|
||||
import Data.Record
|
||||
import Data.String
|
||||
import Info
|
||||
import Language.Ruby.Syntax (decoratorWithAlgebra)
|
||||
import Prologue
|
||||
import Renderer
|
||||
import Renderer.TOC (declarationAlgebra)
|
||||
import Source
|
||||
import Syntax
|
||||
import Term
|
||||
@ -49,7 +47,7 @@ sExpressionDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
sExpressionDiff = DiffArguments (SExpressionDiffRenderer TreeOnly) (const identity)
|
||||
|
||||
tocDiff :: DiffMode -> FilePath -> [FilePath] -> DiffArguments
|
||||
tocDiff = DiffArguments ToCRenderer (decoratorWithAlgebra . declarationAlgebra)
|
||||
tocDiff = DiffArguments ToCRenderer declarationDecorator
|
||||
|
||||
|
||||
data ParseMode = ParseCommit String [FilePath] | ParsePaths [FilePath]
|
||||
|
@ -1,9 +1,10 @@
|
||||
{-# LANGUAGE GADTs, MultiParamTypeClasses #-}
|
||||
{-# LANGUAGE DataKinds, GADTs, MultiParamTypeClasses, TypeOperators #-}
|
||||
module Renderer
|
||||
( DiffRenderer(..)
|
||||
, SExpressionFormat(..)
|
||||
, resolveDiffRenderer
|
||||
, runDiffRenderer
|
||||
, declarationDecorator
|
||||
, ParseTreeRenderer(..)
|
||||
, resolveParseTreeRenderer
|
||||
, runParseTreeRenderer
|
||||
@ -26,7 +27,7 @@ import Renderer.Patch as R
|
||||
import Renderer.SExpression as R
|
||||
import Renderer.Summary as R
|
||||
import Renderer.TOC as R
|
||||
import Source (SourceBlob(..))
|
||||
import Source (SourceBlob(..), Source)
|
||||
import Syntax as S
|
||||
import Term
|
||||
|
||||
@ -50,6 +51,10 @@ runDiffRenderer :: (Monoid output, StringConv output ByteString) => DiffRenderer
|
||||
runDiffRenderer = foldMap . uncurry . resolveDiffRenderer
|
||||
|
||||
|
||||
declarationDecorator :: Source -> Term (Syntax Text) (Record DefaultFields) -> Term (Syntax Text) (Record (Maybe Declaration ': DefaultFields))
|
||||
declarationDecorator = decoratorWithAlgebra . declarationAlgebra
|
||||
|
||||
|
||||
data ParseTreeRenderer fields output where
|
||||
SExpressionParseTreeRenderer :: (HasField fields Category, HasField fields SourceSpan) => SExpressionFormat -> ParseTreeRenderer fields ByteString
|
||||
JSONParseTreeRenderer :: (ToJSONFields (Record fields), HasField fields Range) => ParseTreeRenderer fields [Value]
|
||||
|
Loading…
Reference in New Issue
Block a user