1
1
mirror of https://github.com/github/semantic.git synced 2025-01-07 07:58:12 +03:00

Rename DefaultFields to HasDefaultFields.

This commit is contained in:
Rob Rix 2017-03-31 15:18:27 -04:00
parent 46fe5ed705
commit f52894d2e8
4 changed files with 17 additions and 17 deletions

View File

@ -164,7 +164,7 @@ diffFiles parse sourceBlobs = do
_ -> Nothing)
-- | Returns a rendered diff given arguments and two source blobs.
renderDiff :: (ToJSON (Record fields), NFData (Record fields), DefaultFields fields) => Arguments -> Both SourceBlob -> SyntaxDiff Text fields -> Output
renderDiff :: (ToJSON (Record fields), NFData (Record fields), HasDefaultFields fields) => Arguments -> Both SourceBlob -> SyntaxDiff Text fields -> Output
renderDiff args = case format args of
Split -> split
Patch -> patch
@ -174,7 +174,7 @@ renderDiff args = case format args of
TOC -> toc
-- | Prints a rendered diff to stdio or a filepath given a parser, arguments and two source blobs.
printDiff :: (ToJSON (Record fields), NFData (Record fields), DefaultFields fields) => Parser (Syntax Text) (Record fields) -> Arguments -> Both SourceBlob -> IO ByteString
printDiff :: (ToJSON (Record fields), NFData (Record fields), HasDefaultFields fields) => Parser (Syntax Text) (Record fields) -> Arguments -> Both SourceBlob -> IO ByteString
printDiff parser args sources = do
diff <- diffFiles parser sources
pure $! concatOutputs [renderDiff args sources diff]

View File

@ -1,6 +1,6 @@
{-# LANGUAGE ConstraintKinds, DataKinds, GeneralizedNewtypeDeriving #-}
module Info
( DefaultFields
( HasDefaultFields
, Range(..)
, byteRange
, setCharacterRange
@ -24,7 +24,7 @@ import SourceSpan
import Data.Aeson
-- | A type alias for HasField constraints commonly used throughout semantic-diff.
type DefaultFields fields = (HasField fields Category, HasField fields Range, HasField fields SourceSpan)
type HasDefaultFields fields = (HasField fields Category, HasField fields Range, HasField fields SourceSpan)
newtype SourceText = SourceText { unText :: Text }
deriving (Show, ToJSON)

View File

@ -8,7 +8,7 @@ import Prologue
import Diff
import Patch
import Term
import Info (DefaultFields, category, byteRange)
import Info (HasDefaultFields, category, byteRange)
import Range
import Syntax as S
import Category as C
@ -101,7 +101,7 @@ data DiffSummary a = DiffSummary {
parentAnnotation :: [Either (Category, Text) (Category, Text)]
} deriving (Eq, Functor, Show, Generic)
summary :: (DefaultFields fields) => Renderer (Record fields)
summary :: (HasDefaultFields fields) => Renderer (Record fields)
summary blobs diff = SummaryOutput $ Map.fromList [
("changes", changes),
("errors", errors)
@ -114,7 +114,7 @@ summary blobs diff = SummaryOutput $ Map.fromList [
summaries = diffSummaries blobs diff
-- Returns a list of diff summary texts given two source blobs and a diff.
diffSummaries :: (StringConv leaf Text, DefaultFields fields) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary Text SourceSpans]
diffSummaries :: (StringConv leaf Text, HasDefaultFields fields) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary Text SourceSpans]
diffSummaries blobs diff = summaryToTexts =<< diffToDiffSummaries (source <$> blobs) diff
-- Takes a 'DiffSummary DiffInfo' and returns a list of JSON Summaries whose text summaries represent the LeafInfo summaries of the 'DiffSummary'.
@ -124,7 +124,7 @@ summaryToTexts DiffSummary{..} = appendParentContexts <$> jsonDocSummaries diffS
jsonSummary { info = show $ info jsonSummary <+> parentContexts parentAnnotation }
-- Returns a list of 'DiffSummary' given two source blobs and a diff.
diffToDiffSummaries :: (StringConv leaf Text, DefaultFields fields) => Both Source -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo]
diffToDiffSummaries :: (StringConv leaf Text, HasDefaultFields fields) => Both Source -> SyntaxDiff leaf fields -> [DiffSummary DiffInfo]
diffToDiffSummaries sources = para $ \diff ->
let
diff' = free (Prologue.fst <$> diff)
@ -204,7 +204,7 @@ toLeafInfos LeafInfo{..} = pure $ JSONSummary (summary leafCategory termName) so
vowels = Text.singleton <$> ("aeiouAEIOU" :: [Char])
-- Returns a text representing a specific term given a source and a term.
toTermName :: forall leaf fields. (StringConv leaf Text, DefaultFields fields) => Source -> SyntaxTerm leaf fields -> Text
toTermName :: forall leaf fields. (StringConv leaf Text, HasDefaultFields fields) => Source -> SyntaxTerm leaf fields -> Text
toTermName source term = case unwrap term of
S.Send _ _ -> termNameFromSource term
S.Ty _ -> termNameFromSource term
@ -344,7 +344,7 @@ parentContexts contexts = hsep $ either identifiableDoc annotatableDoc <$> conte
toDoc :: Text -> Doc
toDoc = string . toS
termToDiffInfo :: (StringConv leaf Text, DefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffInfo
termToDiffInfo :: (StringConv leaf Text, HasDefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffInfo
termToDiffInfo blob term = case unwrap term of
S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term) BIndexed
S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term) BFixed
@ -361,7 +361,7 @@ termToDiffInfo blob term = case unwrap term of
-- | For a DiffSummary without a parentAnnotation, we append a parentAnnotation with the first identifiable term.
-- | For a DiffSummary with a parentAnnotation, we append the next annotatable term to the extant parentAnnotation.
-- | If a DiffSummary already has a parentAnnotation, and a (grand) parentAnnotation, then we return the summary without modification.
appendSummary :: (StringConv leaf Text, DefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffSummary DiffInfo -> DiffSummary DiffInfo
appendSummary :: (StringConv leaf Text, HasDefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffSummary DiffInfo -> DiffSummary DiffInfo
appendSummary source term summary =
case (parentAnnotation summary, identifiable term, annotatable term) of
([], Identifiable _, _) -> appendParentAnnotation Left

View File

@ -51,7 +51,7 @@ data Summarizable = Summarizable { summarizableCategory :: Category, summarizabl
data SummarizableTerm a = SummarizableTerm a | NotSummarizableTerm a
toc :: (DefaultFields fields) => Renderer (Record fields)
toc :: (HasDefaultFields fields) => Renderer (Record fields)
toc blobs diff = TOCOutput $ Map.fromList [
("changes", changes),
("errors", errors)
@ -63,7 +63,7 @@ toc blobs diff = TOCOutput $ Map.fromList [
summaryKey = toSummaryKey (path <$> blobs)
summaries = diffTOC blobs diff
diffTOC :: (StringConv leaf Text, DefaultFields fields) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary]
diffTOC :: (StringConv leaf Text, HasDefaultFields fields) => Both SourceBlob -> SyntaxDiff leaf fields -> [JSONSummary]
diffTOC blobs diff = removeDupes (diffToTOCSummaries (source <$> blobs) diff) >>= toJSONSummaries
where
removeDupes :: [TOCSummary DiffInfo] -> [TOCSummary DiffInfo]
@ -83,7 +83,7 @@ diffTOC blobs diff = removeDupes (diffToTOCSummaries (source <$> blobs) diff) >>
(Summarizable catA nameA _ _, Summarizable catB nameB _ _) -> catA == catB && toLower nameA == toLower nameB
(_, _) -> False
diffToTOCSummaries :: (StringConv leaf Text, DefaultFields fields) => Both Source -> SyntaxDiff leaf fields -> [TOCSummary DiffInfo]
diffToTOCSummaries :: (StringConv leaf Text, HasDefaultFields fields) => Both Source -> SyntaxDiff leaf fields -> [TOCSummary DiffInfo]
diffToTOCSummaries sources = para $ \diff ->
let
diff' = free (Prologue.fst <$> diff)
@ -118,7 +118,7 @@ toLeafInfos' :: DiffInfo -> [DiffInfo]
toLeafInfos' BranchInfo{..} = branches >>= toLeafInfos'
toLeafInfos' leaf = [leaf]
mapToInSummarizable :: forall leaf fields. DefaultFields fields => Both Source -> SyntaxDiff leaf fields -> [TOCSummary DiffInfo] -> [TOCSummary DiffInfo]
mapToInSummarizable :: forall leaf fields. HasDefaultFields fields => Both Source -> SyntaxDiff leaf fields -> [TOCSummary DiffInfo] -> [TOCSummary DiffInfo]
mapToInSummarizable sources diff children = case (beforeTerm diff, afterTerm diff) of
(_, Just diff') -> mapToInSummarizable' (Both.snd sources) diff' <$> children
(Just diff', _) -> mapToInSummarizable' (Both.fst sources) diff' <$> children
@ -150,7 +150,7 @@ toJSONSummaries TOCSummary{..} = case afterOrBefore summaryPatch of
NotSummarizable -> []
_ -> pure $ JSONSummary parentInfo
termToDiffInfo :: forall leaf fields. (StringConv leaf Text, DefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffInfo
termToDiffInfo :: forall leaf fields. (StringConv leaf Text, HasDefaultFields fields) => Source -> SyntaxTerm leaf fields -> DiffInfo
termToDiffInfo source term = case unwrap term of
S.Indexed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term)
S.Fixed children -> BranchInfo (termToDiffInfo' <$> children) (category $ extract term)
@ -163,7 +163,7 @@ termToDiffInfo source term = case unwrap term of
termToDiffInfo' = termToDiffInfo source
toLeafInfo term = LeafInfo (category $ extract term) (toTermName' term) (getField $ extract term)
toTermName :: forall leaf fields. DefaultFields fields => Int -> Source -> SyntaxTerm leaf fields -> Text
toTermName :: forall leaf fields. HasDefaultFields fields => Int -> Source -> SyntaxTerm leaf fields -> Text
toTermName parentOffset parentSource term = case unwrap term of
S.Function identifier _ _ -> toTermName' identifier
S.Method _ identifier Nothing _ _ -> toTermName' identifier