1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 07:55:12 +03:00

Remove some more redundant constraints

This commit is contained in:
Timothy Clem 2018-03-16 10:56:15 -07:00
parent f3fd569a6b
commit fa0c72fb14
12 changed files with 15 additions and 17 deletions

View File

@ -21,7 +21,7 @@ newtype CallGraph = CallGraph { unCallGraph :: G.Graph Name }
deriving (Eq, Graph, Show)
-- | Build the 'CallGraph' for a 'Term' recursively.
buildCallGraph :: (CallGraphAlgebra syntax, Foldable syntax, FreeVariables1 syntax, Functor syntax) => Term syntax ann -> Set Name -> CallGraph
buildCallGraph :: (CallGraphAlgebra syntax, FreeVariables1 syntax, Functor syntax) => Term syntax ann -> Set Name -> CallGraph
buildCallGraph = foldSubterms callGraphAlgebra

View File

@ -31,7 +31,7 @@ newtype CyclomaticComplexity = CyclomaticComplexity Int
-- If youre getting errors about missing a 'CustomHasCyclomaticComplexity' instance for your syntax type, you probably forgot step 1.
--
-- If youre getting 'Nothing' for your syntax node at runtime, you probably forgot step 2.
cyclomaticComplexityAlgebra :: (Foldable syntax, HasCyclomaticComplexity syntax) => TermF syntax ann CyclomaticComplexity -> CyclomaticComplexity
cyclomaticComplexityAlgebra :: HasCyclomaticComplexity syntax => TermF syntax ann CyclomaticComplexity -> CyclomaticComplexity
cyclomaticComplexityAlgebra (In _ syntax) = toCyclomaticComplexity syntax

View File

@ -18,7 +18,7 @@ data Table i a = Table { tableAddresses :: [i], tableBranches :: IntMap a }
singleton :: Enum i => i -> a -> Table i a
singleton i a = Table [i] (IntMap.singleton (fromEnum i) a)
fromListWith :: (Enum i, Ord i) => (a -> a -> a) -> [(i, a)] -> Table i a
fromListWith :: Enum i => (a -> a -> a) -> [(i, a)] -> Table i a
fromListWith with assocs = Table (toEnum <$> IntSet.toList (IntSet.fromList (fromEnum . fst <$> assocs))) (IntMap.fromListWith with (first fromEnum <$> assocs))
toPairs :: Enum i => Table i a -> [(i, a)]

View File

@ -26,11 +26,11 @@ envInsert name value (Environment m) = Environment (Map.insert name value m)
envDelete :: Name -> Environment l a -> Environment l a
envDelete name = Environment . Map.delete name . unEnvironment
bindEnv :: (Ord l, Foldable t) => t Name -> Environment l a -> Environment l a
bindEnv :: Foldable t => t Name -> Environment l a -> Environment l a
bindEnv names env = foldMap envForName names
where envForName name = maybe mempty (curry unit name) (envLookup name env)
bindExports :: (Ord l) => Map Name (Name, Maybe (Address l a)) -> Environment l a -> Environment l a
bindExports :: Map Name (Name, Maybe (Address l a)) -> Environment l a -> Environment l a
bindExports aliases env = Environment pairs
where
pairs = Map.foldrWithKey (\name (alias, address) accum ->

View File

@ -31,7 +31,7 @@ liveMember :: Ord l => Address l v -> Live l v -> Bool
liveMember addr = Set.member addr . unLive
-- | Decompose a 'Live' set into a pair of one member address and the remaining set, or 'Nothing' if empty.
liveSplit :: Ord l => Live l v -> Maybe (Address l v, Live l v)
liveSplit :: Live l v -> Maybe (Address l v, Live l v)
liveSplit = fmap (second Live) . Set.minView . unLive

View File

@ -13,7 +13,7 @@ data SplitPatch a
deriving (Foldable, Eq, Functor, Show, Traversable)
-- | Get the range of a SplitDiff.
getRange :: Functor f => HasField fields Range => SplitDiff f (Record fields) -> Range
getRange :: HasField fields Range => SplitDiff f (Record fields) -> Range
getRange diff = getField $ case diff of
Free annotated -> termFAnnotation annotated
Pure patch -> termAnnotation (splitTerm patch)

View File

@ -98,7 +98,7 @@ defaultP = 0
defaultQ = 3
toKdMap :: Functor syntax => [(Int, Term syntax (Record (FeatureVector ': fields)))] -> KdMap.KdMap Double FeatureVector (Int, Term syntax (Record (FeatureVector ': fields)))
toKdMap :: [(Int, Term syntax (Record (FeatureVector ': fields)))] -> KdMap.KdMap Double FeatureVector (Int, Term syntax (Record (FeatureVector ': fields)))
toKdMap = KdMap.build unFV . fmap (rhead . termAnnotation . snd &&& id)
-- | A `Gram` is a fixed-size view of some portion of a tree, consisting of a `stem` of _p_ labels for parent nodes, and a `base` of _q_ labels of sibling nodes. Collectively, the bag of `Gram`s for each node of a tree (e.g. as computed by `pqGrams`) form a summary of the tree.
@ -134,8 +134,7 @@ pqGramDecorator getLabel p q = cata algebra
gram label = Gram (padToSize p []) (padToSize q (pure (Just label)))
assignParentAndSiblingLabels functor label = (`evalState` (replicate (q `div` 2) Nothing <> siblingLabels functor)) (for functor (assignLabels label))
assignLabels :: Functor f
=> label
assignLabels :: label
-> Term f (Record (Gram label ': fields))
-> State [Maybe label] (Term f (Record (Gram label ': fields)))
assignLabels label (Term.Term (In (gram :. rest) functor)) = do

View File

@ -14,7 +14,7 @@ import Diffing.Algorithm
import Diffing.Algorithm.RWS
-- | Diff two à la carte terms recursively.
diffTerms :: (Diffable syntax, Eq1 syntax, Foldable syntax, Functor syntax, GAlign syntax, Show1 syntax, Traversable syntax)
diffTerms :: (Diffable syntax, Eq1 syntax, GAlign syntax, Show1 syntax, Traversable syntax)
=> Term syntax (Record fields1)
-> Term syntax (Record fields2)
-> Diff syntax (Record fields1) (Record fields2)

View File

@ -600,8 +600,7 @@ infixTerm :: Assignment
infixTerm = infixContext comment
-- | Match a series of terms or comments until a delimiter is matched
manyTermsTill :: Show b
=> Assignment.Assignment [] Grammar Term
manyTermsTill :: Assignment.Assignment [] Grammar Term
-> Assignment.Assignment [] Grammar b
-> Assignment.Assignment [] Grammar [Term]
manyTermsTill step end = manyTill (step <|> comment) end

View File

@ -499,7 +499,7 @@ chainl1Term :: Assignment -> Assignment.Assignment [] Grammar (Term -> Term -> T
chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) expr `chainl1` op
-- | Match a series of terms or comments until a delimiter is matched.
manyTermsTill :: Show b => Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
manyTermsTill step end = manyTill (step <|> comment) end
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.

View File

@ -404,7 +404,7 @@ term :: Assignment -> Assignment
term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)
-- | Match a series of terms or comments until a delimiter is matched.
manyTermsTill :: Show b => Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
manyTermsTill step end = manyTill (step <|> comment) end
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.

View File

@ -20,7 +20,7 @@ renderSExpressionDiff diff = cata printDiffF diff 0 <> "\n"
renderSExpressionTerm :: (ConstrainAll Show fields, Foldable syntax, Functor syntax) => Term syntax (Record fields) -> ByteString
renderSExpressionTerm term = cata (\ term n -> nl n <> replicate (2 * n) ' ' <> printTermF term n) term 0 <> "\n"
printDiffF :: (ConstrainAll Show fields, Foldable syntax, Functor syntax) => DiffF syntax (Record fields) (Record fields) (Int -> ByteString) -> Int -> ByteString
printDiffF :: (ConstrainAll Show fields, Foldable syntax) => DiffF syntax (Record fields) (Record fields) (Int -> ByteString) -> Int -> ByteString
printDiffF diff n = case diff of
Patch (Delete term) -> nl n <> pad (n - 1) <> "{-" <> printTermF term n <> "-}"
Patch (Insert term) -> nl n <> pad (n - 1) <> "{+" <> printTermF term n <> "+}"
@ -28,7 +28,7 @@ printDiffF diff n = case diff of
<> nl (n + 1) <> pad (n - 1) <> "->" <> printTermF term2 n <> " }"
Merge (In (_, ann) syntax) -> nl n <> pad n <> "(" <> showAnnotation ann <> foldMap (\ d -> d (n + 1)) syntax <> ")"
printTermF :: (ConstrainAll Show fields, Foldable syntax, Functor syntax) => TermF syntax (Record fields) (Int -> ByteString) -> Int -> ByteString
printTermF :: (ConstrainAll Show fields, Foldable syntax) => TermF syntax (Record fields) (Int -> ByteString) -> Int -> ByteString
printTermF (In annotation syntax) n = "(" <> showAnnotation annotation <> foldMap (\t -> t (n + 1)) syntax <> ")"
nl :: Int -> ByteString