mirror of
https://github.com/github/semantic.git
synced 2024-12-28 09:21:35 +03:00
Merge branch 'master' into fix-hacky-test-slurping
This commit is contained in:
commit
c8b6f0be08
@ -1,38 +0,0 @@
|
||||
---
|
||||
type: cabal
|
||||
name: free
|
||||
version: '5.1'
|
||||
summary: Monads for free
|
||||
homepage: https://github.com/ekmett/free/
|
||||
license: bsd-3-clause
|
||||
---
|
||||
Copyright 2008-2013 Edward Kmett
|
||||
|
||||
All rights reserved.
|
||||
|
||||
Redistribution and use in source and binary forms, with or without
|
||||
modification, are permitted provided that the following conditions
|
||||
are met:
|
||||
|
||||
1. Redistributions of source code must retain the above copyright
|
||||
notice, this list of conditions and the following disclaimer.
|
||||
|
||||
2. Redistributions in binary form must reproduce the above copyright
|
||||
notice, this list of conditions and the following disclaimer in the
|
||||
documentation and/or other materials provided with the distribution.
|
||||
|
||||
3. Neither the name of the author nor the names of his contributors
|
||||
may be used to endorse or promote products derived from this software
|
||||
without specific prior written permission.
|
||||
|
||||
THIS SOFTWARE IS PROVIDED BY THE AUTHORS ``AS IS'' AND ANY EXPRESS OR
|
||||
IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED
|
||||
WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
|
||||
DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE FOR
|
||||
ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
|
||||
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
|
||||
OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
|
||||
HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT,
|
||||
STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
|
||||
ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
|
||||
POSSIBILITY OF SUCH DAMAGE.
|
@ -53,7 +53,6 @@ common dependencies
|
||||
, containers ^>= 0.6.0.1
|
||||
, directory ^>= 1.3.3.0
|
||||
, fastsum ^>= 0.1.1.0
|
||||
, free ^>= 5.1
|
||||
, fused-effects ^>= 0.5.0.0
|
||||
, fused-effects-exceptions ^>= 0.2.0.0
|
||||
, hashable ^>= 1.2.7.0
|
||||
|
@ -11,16 +11,12 @@ module Data.Functor.Listable
|
||||
, cons5
|
||||
, cons6
|
||||
, (\/)
|
||||
, ListableF(..)
|
||||
, addWeight
|
||||
, ofWeight
|
||||
, ListableSyntax
|
||||
) where
|
||||
|
||||
import Analysis.CyclomaticComplexity
|
||||
import Analysis.TOCSummary
|
||||
import Control.Monad.Free as Free
|
||||
import Control.Monad.Trans.Free as FreeF
|
||||
import Data.Abstract.ScopeGraph (AccessControl(..))
|
||||
import Data.Bifunctor.Join
|
||||
import Data.Diff
|
||||
@ -30,20 +26,13 @@ import Data.List.NonEmpty
|
||||
import Data.Patch
|
||||
import Data.Semigroup.App
|
||||
import qualified Data.Syntax as Syntax
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Directive as Directive
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Language.Ruby.Syntax as Ruby.Syntax
|
||||
import qualified Language.Python.Syntax as Python.Syntax
|
||||
import qualified Data.Abstract.Name as Name
|
||||
import Data.Term
|
||||
import Data.Text as T (Text, pack)
|
||||
import Data.These
|
||||
import Data.Sum
|
||||
import Diffing.Algorithm.RWS
|
||||
import Source.Loc
|
||||
import Source.Span
|
||||
import Test.LeanCheck
|
||||
@ -110,18 +99,6 @@ liftCons6 :: [Tier a] -> [Tier b] -> [Tier c] -> [Tier d] -> [Tier e] -> [Tier f
|
||||
liftCons6 tiers1 tiers2 tiers3 tiers4 tiers5 tiers6 f = mapT (uncurry6 f) (tiers1 >< tiers2 >< tiers3 >< tiers4 >< tiers5 >< tiers6) `addWeight` 1
|
||||
where uncurry6 g (a, (b, (c, (d, (e, f))))) = g a b c d e f
|
||||
|
||||
-- | Convenient wrapper for 'Listable1' type constructors and 'Listable' types, where a 'Listable' instance would necessarily be orphaned.
|
||||
newtype ListableF f a = ListableF { unListableF :: f a }
|
||||
deriving Show
|
||||
|
||||
-- | Convenient wrapper for 'Listable2' type constructors and 'Listable' types, where a 'Listable' instance would necessarily be orphaned.
|
||||
newtype ListableF2 f a b = ListableF2 { unListableF2 :: f a b }
|
||||
deriving Show
|
||||
|
||||
instance (Listable2 f, Listable a, Listable b) => Listable (ListableF2 f a b) where
|
||||
tiers = ListableF2 `mapT` tiers2
|
||||
|
||||
|
||||
-- Instances
|
||||
|
||||
instance Listable1 Maybe where
|
||||
@ -149,25 +126,6 @@ instance Listable2 p => Listable1 (Join p) where
|
||||
instance Listable1 Both where
|
||||
liftTiers tiers = liftCons2 tiers tiers Both
|
||||
|
||||
instance Listable2 These where
|
||||
liftTiers2 this that = liftCons1 this This \/ liftCons1 that That \/ liftCons2 this that These
|
||||
|
||||
instance Listable1 f => Listable2 (FreeF f) where
|
||||
liftTiers2 pureTiers recurTiers = liftCons1 pureTiers FreeF.Pure \/ liftCons1 (liftTiers recurTiers) FreeF.Free
|
||||
|
||||
instance (Listable1 f, Listable a) => Listable1 (FreeF f a) where
|
||||
liftTiers = liftTiers2 tiers
|
||||
|
||||
instance Listable1 f => Listable1 (Free.Free f) where
|
||||
liftTiers pureTiers = go
|
||||
where go = liftCons1 (liftTiers2 pureTiers go) free
|
||||
free (FreeF.Free f) = Free.Free f
|
||||
free (FreeF.Pure a) = Free.Pure a
|
||||
|
||||
instance (Listable1 f, Listable a) => Listable (ListableF f a) where
|
||||
tiers = ListableF `mapT` tiers1
|
||||
|
||||
|
||||
instance Listable1 f => Listable2 (TermF f) where
|
||||
liftTiers2 annotationTiers recurTiers = liftCons2 annotationTiers (liftTiers recurTiers) In
|
||||
|
||||
@ -232,9 +190,6 @@ instance Listable1 Declaration.Method where
|
||||
instance Listable1 Statement.If where
|
||||
liftTiers tiers = liftCons3 tiers tiers tiers Statement.If
|
||||
|
||||
instance Listable1 Statement.Return where
|
||||
liftTiers tiers = liftCons1 tiers Statement.Return
|
||||
|
||||
instance Listable1 Syntax.Context where
|
||||
liftTiers tiers = liftCons2 (liftTiers tiers) tiers Syntax.Context
|
||||
|
||||
@ -244,256 +199,6 @@ instance Listable1 Syntax.Empty where
|
||||
instance Listable1 Syntax.Identifier where
|
||||
liftTiers _ = cons1 Syntax.Identifier
|
||||
|
||||
instance Listable1 Literal.KeyValue where
|
||||
liftTiers tiers = liftCons2 tiers tiers Literal.KeyValue
|
||||
|
||||
instance Listable1 Literal.Array where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Literal.Array
|
||||
|
||||
instance Listable1 Literal.Boolean where
|
||||
liftTiers _ = cons1 Literal.Boolean
|
||||
|
||||
instance Listable1 Literal.Hash where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Literal.Hash
|
||||
|
||||
instance Listable1 Literal.Float where
|
||||
liftTiers _ = cons1 Literal.Float
|
||||
|
||||
instance Listable1 Literal.Null where
|
||||
liftTiers _ = cons0 Literal.Null
|
||||
|
||||
instance Listable1 Literal.TextElement where
|
||||
liftTiers _ = cons1 Literal.TextElement
|
||||
|
||||
instance Listable1 Literal.EscapeSequence where
|
||||
liftTiers _ = cons1 Literal.EscapeSequence
|
||||
|
||||
instance Listable1 Literal.InterpolationElement where
|
||||
liftTiers tiers = liftCons1 tiers Literal.InterpolationElement
|
||||
|
||||
instance Listable1 Literal.Character where
|
||||
liftTiers _ = cons1 Literal.Character
|
||||
|
||||
instance Listable1 Statement.Statements where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Statement.Statements
|
||||
|
||||
instance Listable1 Syntax.Error where
|
||||
liftTiers tiers = liftCons4 mempty mempty mempty (liftTiers tiers) Syntax.Error
|
||||
|
||||
instance Listable1 Directive.File where
|
||||
liftTiers _ = cons0 Directive.File
|
||||
|
||||
instance Listable1 Directive.Line where
|
||||
liftTiers _ = cons0 Directive.Line
|
||||
|
||||
instance Listable1 Expression.Plus where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Plus
|
||||
|
||||
instance Listable1 Expression.Minus where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Minus
|
||||
|
||||
instance Listable1 Expression.Times where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Times
|
||||
|
||||
instance Listable1 Expression.DividedBy where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.DividedBy
|
||||
|
||||
instance Listable1 Expression.FloorDivision where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.FloorDivision
|
||||
|
||||
instance Listable1 Expression.Modulo where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Modulo
|
||||
|
||||
instance Listable1 Expression.Power where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Power
|
||||
|
||||
instance Listable1 Expression.Negate where
|
||||
liftTiers tiers = liftCons1 tiers Expression.Negate
|
||||
|
||||
instance Listable1 Expression.BOr where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.BOr
|
||||
|
||||
instance Listable1 Expression.BAnd where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.BAnd
|
||||
|
||||
instance Listable1 Expression.BXOr where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.BXOr
|
||||
|
||||
instance Listable1 Expression.LShift where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.LShift
|
||||
|
||||
instance Listable1 Expression.RShift where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.RShift
|
||||
|
||||
instance Listable1 Expression.UnsignedRShift where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.UnsignedRShift
|
||||
|
||||
instance Listable1 Expression.Complement where
|
||||
liftTiers tiers = liftCons1 tiers Expression.Complement
|
||||
|
||||
instance Listable1 Expression.Or where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Or
|
||||
|
||||
instance Listable1 Expression.And where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.And
|
||||
|
||||
instance Listable1 Expression.Not where
|
||||
liftTiers tiers = liftCons1 tiers Expression.Not
|
||||
|
||||
instance Listable1 Expression.XOr where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.XOr
|
||||
|
||||
instance Listable1 Expression.Call where
|
||||
liftTiers tiers = liftCons4 (liftTiers tiers) tiers (liftTiers tiers) tiers Expression.Call
|
||||
|
||||
instance Listable1 Expression.LessThan where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.LessThan
|
||||
|
||||
instance Listable1 Expression.LessThanEqual where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.LessThanEqual
|
||||
|
||||
instance Listable1 Expression.GreaterThan where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.GreaterThan
|
||||
|
||||
instance Listable1 Expression.GreaterThanEqual where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.GreaterThanEqual
|
||||
|
||||
instance Listable1 Expression.Equal where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Equal
|
||||
|
||||
instance Listable1 Expression.StrictEqual where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.StrictEqual
|
||||
|
||||
instance Listable1 Expression.Comparison where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Comparison
|
||||
|
||||
instance Listable1 Expression.Enumeration where
|
||||
liftTiers tiers = liftCons3 tiers tiers tiers Expression.Enumeration
|
||||
|
||||
instance Listable1 Expression.Matches where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Matches
|
||||
|
||||
instance Listable1 Expression.NotMatches where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.NotMatches
|
||||
|
||||
instance Listable1 Expression.MemberAccess where
|
||||
liftTiers tiers = liftCons2 tiers mempty Expression.MemberAccess
|
||||
|
||||
instance Listable1 Expression.ScopeResolution where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Expression.ScopeResolution
|
||||
|
||||
instance Listable1 Expression.Subscript where
|
||||
liftTiers tiers = liftCons2 tiers (liftTiers tiers) Expression.Subscript
|
||||
|
||||
instance Listable1 Expression.Member where
|
||||
liftTiers tiers = liftCons2 tiers tiers Expression.Member
|
||||
|
||||
instance Listable1 Expression.This where
|
||||
liftTiers _ = cons0 Expression.This
|
||||
|
||||
instance Listable1 Literal.Complex where
|
||||
liftTiers _ = cons1 Literal.Complex
|
||||
|
||||
instance Listable1 Literal.Integer where
|
||||
liftTiers _ = cons1 Literal.Integer
|
||||
|
||||
instance Listable1 Literal.Rational where
|
||||
liftTiers _ = cons1 Literal.Rational
|
||||
|
||||
instance Listable1 Literal.Regex where
|
||||
liftTiers _ = cons1 Literal.Regex
|
||||
|
||||
instance Listable1 Literal.String where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Literal.String
|
||||
|
||||
instance Listable1 Literal.Symbol where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Literal.Symbol
|
||||
|
||||
instance Listable1 Literal.SymbolElement where
|
||||
liftTiers _ = cons1 Literal.SymbolElement
|
||||
|
||||
instance Listable1 Statement.Assignment where
|
||||
liftTiers tiers = liftCons3 (liftTiers tiers) tiers tiers Statement.Assignment
|
||||
|
||||
instance Listable1 Statement.Break where
|
||||
liftTiers tiers = liftCons1 tiers Statement.Break
|
||||
|
||||
instance Listable1 Statement.Catch where
|
||||
liftTiers tiers = liftCons2 tiers tiers Statement.Catch
|
||||
|
||||
instance Listable1 Statement.Continue where
|
||||
liftTiers tiers = liftCons1 tiers Statement.Continue
|
||||
|
||||
instance Listable1 Statement.Else where
|
||||
liftTiers tiers = liftCons2 tiers tiers Statement.Else
|
||||
|
||||
instance Listable1 Statement.Finally where
|
||||
liftTiers tiers = liftCons1 tiers Statement.Finally
|
||||
|
||||
instance Listable1 Statement.ForEach where
|
||||
liftTiers tiers = liftCons3 tiers tiers tiers Statement.ForEach
|
||||
|
||||
instance Listable1 Statement.Match where
|
||||
liftTiers tiers = liftCons2 tiers tiers Statement.Match
|
||||
|
||||
instance Listable1 Statement.Pattern where
|
||||
liftTiers tiers = liftCons2 tiers tiers Statement.Pattern
|
||||
|
||||
instance Listable1 Statement.Retry where
|
||||
liftTiers tiers = liftCons1 tiers Statement.Retry
|
||||
|
||||
instance Listable1 Statement.ScopeEntry where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Statement.ScopeEntry
|
||||
|
||||
instance Listable1 Statement.ScopeExit where
|
||||
liftTiers tiers = liftCons1 (liftTiers tiers) Statement.ScopeExit
|
||||
|
||||
instance Listable1 Statement.Try where
|
||||
liftTiers tiers = liftCons2 tiers (liftTiers tiers) Statement.Try
|
||||
|
||||
instance Listable1 Statement.While where
|
||||
liftTiers tiers = liftCons2 tiers tiers Statement.While
|
||||
|
||||
instance Listable1 Statement.Yield where
|
||||
liftTiers tiers = liftCons1 tiers Statement.Yield
|
||||
|
||||
instance Listable1 Ruby.Syntax.Assignment where
|
||||
liftTiers tiers = liftCons3 (liftTiers tiers) tiers tiers Ruby.Syntax.Assignment
|
||||
|
||||
instance Listable1 Ruby.Syntax.Class where
|
||||
liftTiers tiers = liftCons3 tiers (liftTiers tiers) tiers Ruby.Syntax.Class
|
||||
|
||||
instance Listable1 Ruby.Syntax.Load where
|
||||
liftTiers tiers = liftCons2 tiers (liftTiers tiers) Ruby.Syntax.Load
|
||||
|
||||
instance Listable1 Ruby.Syntax.LowPrecedenceOr where
|
||||
liftTiers tiers = liftCons2 tiers tiers Ruby.Syntax.LowPrecedenceOr
|
||||
|
||||
instance Listable1 Ruby.Syntax.LowPrecedenceAnd where
|
||||
liftTiers tiers = liftCons2 tiers tiers Ruby.Syntax.LowPrecedenceAnd
|
||||
|
||||
instance Listable1 Ruby.Syntax.Module where
|
||||
liftTiers tiers = liftCons2 tiers (liftTiers tiers) Ruby.Syntax.Module
|
||||
|
||||
instance Listable1 Ruby.Syntax.Require where
|
||||
liftTiers tiers' = liftCons2 tiers tiers' Ruby.Syntax.Require
|
||||
|
||||
instance Listable1 Ruby.Syntax.ZSuper where
|
||||
liftTiers _ = cons0 Ruby.Syntax.ZSuper
|
||||
|
||||
instance Listable1 Ruby.Syntax.Send where
|
||||
liftTiers tiers = liftCons4 (liftTiers tiers) (liftTiers tiers) (liftTiers tiers) (liftTiers tiers) Ruby.Syntax.Send
|
||||
|
||||
instance Listable Python.Syntax.QualifiedName where
|
||||
tiers = liftCons1 tiers1 Python.Syntax.QualifiedName \/ liftCons2 tiers tiers1 Python.Syntax.RelativeQualifiedName
|
||||
|
||||
instance Listable1 Python.Syntax.Import where
|
||||
liftTiers tiers' = liftCons2 tiers (liftTiers tiers') Python.Syntax.Import
|
||||
|
||||
instance Listable1 Python.Syntax.Alias where
|
||||
liftTiers tiers = liftCons2 tiers tiers Python.Syntax.Alias
|
||||
|
||||
|
||||
type ListableSyntax = Sum
|
||||
'[ Comment.Comment
|
||||
, Declaration.Function
|
||||
@ -508,13 +213,6 @@ type ListableSyntax = Sum
|
||||
instance Listable Name.Name where
|
||||
tiers = cons1 Name.name
|
||||
|
||||
instance Listable1 Gram where
|
||||
liftTiers tiers = liftCons2 (liftTiers (liftTiers tiers)) (liftTiers (liftTiers tiers)) Gram
|
||||
|
||||
instance Listable a => Listable (Gram a) where
|
||||
tiers = tiers1
|
||||
|
||||
|
||||
instance Listable Text where
|
||||
tiers = pack `mapT` tiers
|
||||
|
||||
@ -524,9 +222,6 @@ instance Listable Declaration where
|
||||
\/ cons4 FunctionDeclaration
|
||||
\/ cons3 (\ a b c -> ErrorDeclaration a b c Language.Unknown)
|
||||
|
||||
instance Listable CyclomaticComplexity where
|
||||
tiers = cons1 CyclomaticComplexity
|
||||
|
||||
instance Listable Language.Language where
|
||||
tiers
|
||||
= cons0 Language.Go
|
||||
|
Loading…
Reference in New Issue
Block a user