mirror of
https://github.com/github/semantic.git
synced 2024-12-01 00:33:59 +03:00
Merge branch 'master' into imports,-graphed
This commit is contained in:
commit
85650c06df
@ -225,6 +225,8 @@ language_extensions:
|
||||
- FlexibleContexts
|
||||
- FlexibleInstances
|
||||
- MultiParamTypeClasses
|
||||
- StandaloneDeriving
|
||||
- DataKinds
|
||||
- OverloadedStrings
|
||||
- RecordWildCards
|
||||
- StrictData
|
||||
|
@ -184,14 +184,17 @@ library
|
||||
, tree-sitter-ruby
|
||||
, tree-sitter-typescript
|
||||
default-language: Haskell2010
|
||||
default-extensions: DeriveFoldable
|
||||
default-extensions: DataKinds
|
||||
, DeriveFoldable
|
||||
, DeriveFunctor
|
||||
, DeriveGeneric
|
||||
, DeriveTraversable
|
||||
, FlexibleContexts
|
||||
, FlexibleInstances
|
||||
, MultiParamTypeClasses
|
||||
, OverloadedStrings
|
||||
, RecordWildCards
|
||||
, StandaloneDeriving
|
||||
, StrictData
|
||||
ghc-options: -Wall -Wcompat -Wincomplete-record-updates -Wincomplete-uni-patterns -Wredundant-constraints -fno-warn-name-shadowing -O -j
|
||||
ghc-prof-options: -fprof-auto
|
||||
@ -260,7 +263,15 @@ test-suite test
|
||||
, these
|
||||
ghc-options: -threaded -rtsopts -with-rtsopts=-N -j
|
||||
default-language: Haskell2010
|
||||
default-extensions: DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, OverloadedStrings, RecordWildCards
|
||||
default-extensions: DataKinds
|
||||
, DeriveFunctor
|
||||
, DeriveGeneric
|
||||
, FlexibleContexts
|
||||
, FlexibleInstances
|
||||
, MultiParamTypeClasses
|
||||
, OverloadedStrings
|
||||
, RecordWildCards
|
||||
, StandaloneDeriving
|
||||
|
||||
test-suite doctests
|
||||
type: exitcode-stdio-1.0
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, StandaloneDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Analysis.Abstract.Caching
|
||||
( type Caching
|
||||
) where
|
||||
@ -14,7 +14,7 @@ import Prologue
|
||||
-- | The effects necessary for caching analyses.
|
||||
type CachingEffects term value effects
|
||||
= Fresh -- For 'MonadFresh'.
|
||||
': NonDet -- For 'Alternative' and 'MonadNonDet'.
|
||||
': NonDet -- For 'Alternative' and 'MonadNonDet'.
|
||||
': Reader (CacheFor term value) -- The in-cache used as an oracle while converging on a result.
|
||||
': State (CacheFor term value) -- The out-cache used to record results in each iteration of convergence.
|
||||
': effects
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, StandaloneDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Analysis.Abstract.Collecting
|
||||
( type Collecting
|
||||
) where
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, StandaloneDeriving, TypeFamilies, TypeOperators #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators #-}
|
||||
module Analysis.Abstract.Dead
|
||||
( type DeadCode
|
||||
) where
|
||||
|
@ -22,8 +22,8 @@ newtype Evaluating term value effects a = Evaluating (Eff effects a)
|
||||
|
||||
deriving instance Member Fail effects => MonadFail (Evaluating term value effects)
|
||||
deriving instance Member Fresh effects => MonadFresh (Evaluating term value effects)
|
||||
deriving instance Member NonDet effects => Alternative (Evaluating term value effects)
|
||||
deriving instance Member NonDet effects => MonadNonDet (Evaluating term value effects)
|
||||
deriving instance Member NonDet effects => Alternative (Evaluating term value effects)
|
||||
deriving instance Member NonDet effects => MonadNonDet (Evaluating term value effects)
|
||||
|
||||
-- | Effects necessary for evaluating (whether concrete or abstract).
|
||||
type EvaluatingEffects term value
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, MultiParamTypeClasses, StandaloneDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Analysis.Abstract.Tracing
|
||||
( type Tracing
|
||||
) where
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Analysis.ConstructorName
|
||||
( ConstructorName(..)
|
||||
, ConstructorLabel(..)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, TypeOperators, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
|
||||
{-# LANGUAGE TypeOperators, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
|
||||
module Analysis.Declaration
|
||||
( Declaration(..)
|
||||
, HasDeclaration
|
||||
|
@ -1,17 +1,17 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Analysis.IdentifierName
|
||||
( IdentifierName(..)
|
||||
, IdentifierLabel(..)
|
||||
, identifierLabel
|
||||
) where
|
||||
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Aeson
|
||||
import Data.JSON.Fields
|
||||
import Data.Term
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import Prologue
|
||||
import Data.Abstract.FreeVariables
|
||||
import Data.Aeson
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Syntax
|
||||
import Data.Term
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import Prologue
|
||||
|
||||
-- | Compute a 'IdentifierLabel' label for a 'Term'.
|
||||
identifierLabel :: IdentifierName syntax => TermF syntax a b -> Maybe IdentifierLabel
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
|
||||
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
|
||||
module Analysis.ModuleDef
|
||||
( ModuleDef(..)
|
||||
, HasModuleDef
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies #-}
|
||||
{-# LANGUAGE ScopedTypeVariables, TypeFamilies #-}
|
||||
{-# OPTIONS_GHC -Wno-redundant-constraints #-} -- For runAnalysis
|
||||
module Control.Abstract.Analysis
|
||||
( MonadAnalysis(..)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, TypeFamilies, TypeOperators, UndecidableInstances, ScopedTypeVariables #-}
|
||||
{-# LANGUAGE TypeFamilies, TypeOperators, UndecidableInstances, ScopedTypeVariables #-}
|
||||
module Control.Effect where
|
||||
|
||||
import Control.Monad.Effect as Effect
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, RankNTypes, TypeFamilies, TypeOperators #-}
|
||||
{-# LANGUAGE RankNTypes, TypeFamilies, TypeOperators #-}
|
||||
module Data.Term
|
||||
( Term(..)
|
||||
, termIn
|
||||
|
@ -10,64 +10,48 @@ module Prologue
|
||||
import Data.Bifunctor.Join as X
|
||||
import Data.Bits as X
|
||||
import Data.ByteString as X (ByteString)
|
||||
import Data.Functor.Both as X (Both, runBothWith, both)
|
||||
import Data.Functor.Both as X (Both, both, runBothWith)
|
||||
import Data.IntMap as X (IntMap)
|
||||
import Data.IntSet as X (IntSet)
|
||||
import Data.Ix as X (Ix(..))
|
||||
import Data.Ix as X (Ix (..))
|
||||
import Data.List.NonEmpty as X (NonEmpty (..), nonEmpty, some1)
|
||||
import Data.Map as X (Map)
|
||||
import Data.Monoid (Alt(..))
|
||||
import Data.Maybe as X
|
||||
import Data.Monoid (Alt (..))
|
||||
import Data.Sequence as X (Seq)
|
||||
import Data.Set as X (Set)
|
||||
import Data.Text as X (Text)
|
||||
import Data.These as X
|
||||
import Data.Union as X
|
||||
import Data.List.NonEmpty as X (
|
||||
NonEmpty(..)
|
||||
, nonEmpty
|
||||
, some1
|
||||
)
|
||||
|
||||
import Debug.Trace as X
|
||||
|
||||
import Control.Exception as X hiding (
|
||||
evaluate
|
||||
, throw
|
||||
, throwIO
|
||||
, throwTo
|
||||
, assert
|
||||
, Handler(..)
|
||||
)
|
||||
import Control.Exception as X hiding (Handler (..), assert, evaluate, throw, throwIO, throwTo)
|
||||
|
||||
-- Typeclasses
|
||||
import Control.Applicative as X
|
||||
import Control.Arrow as X ((&&&), (***))
|
||||
import Control.Monad as X hiding (fail, return, unless, when)
|
||||
import Control.Monad.Except as X (MonadError(..))
|
||||
import Control.Monad.Fail as X (MonadFail(..))
|
||||
import Control.Monad.Except as X (MonadError (..))
|
||||
import Control.Monad.Fail as X (MonadFail (..))
|
||||
import Data.Algebra as X
|
||||
import Data.Align.Generic as X (GAlign)
|
||||
import Data.Bifoldable as X
|
||||
import Data.Bifunctor as X (Bifunctor(..))
|
||||
import Data.Bifunctor as X (Bifunctor (..))
|
||||
import Data.Bitraversable as X
|
||||
import Data.Foldable as X hiding (product , sum)
|
||||
import Data.Functor as X (($>), void)
|
||||
import Data.Foldable as X hiding (product, sum)
|
||||
import Data.Function as X (fix, on, (&))
|
||||
import Data.Functor as X (void, ($>))
|
||||
import Data.Functor.Classes as X
|
||||
import Data.Functor.Classes.Generic as X
|
||||
import Data.Functor.Foldable as X (Base, Recursive(..), Corecursive(..))
|
||||
import Data.Functor.Foldable as X (Base, Corecursive (..), Recursive (..))
|
||||
import Data.Hashable as X (Hashable, hash, hashUsing, hashWithSalt)
|
||||
import Data.Mergeable as X (Mergeable)
|
||||
import Data.Monoid as X (Monoid(..), First(..), Last(..))
|
||||
import Data.Proxy as X (Proxy(..))
|
||||
import Data.Semigroup as X (Semigroup(..))
|
||||
import Data.Monoid as X (First (..), Last (..), Monoid (..))
|
||||
import Data.Proxy as X (Proxy (..))
|
||||
import Data.Semigroup as X (Semigroup (..))
|
||||
import Data.Traversable as X
|
||||
import Data.Typeable as X (Typeable)
|
||||
import Data.Hashable as X (
|
||||
Hashable
|
||||
, hash
|
||||
, hashWithSalt
|
||||
, hashUsing
|
||||
)
|
||||
|
||||
-- Generics
|
||||
import GHC.Generics as X hiding (moduleName)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Rendering.Imports
|
||||
( renderToImports
|
||||
, ImportSummary(..)
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
|
||||
module Rendering.Symbol
|
||||
( renderSymbolTerms
|
||||
, renderToSymbols
|
||||
|
@ -36,11 +36,11 @@ spec = parallel $ do
|
||||
|
||||
it "subclasses" $ do
|
||||
res <- evaluate' "subclass.py"
|
||||
fst res `shouldBe` Right (injValue (String "\"bar\""))
|
||||
join (fst res) `shouldBe` Right (injValue (String "\"bar\""))
|
||||
|
||||
it "handles multiple inheritance left-to-right" $ do
|
||||
res <- evaluate' "multiple_inheritance.py"
|
||||
fst res `shouldBe` Right (injValue (String "\"foo!\""))
|
||||
join (fst res) `shouldBe` Right (injValue (String "\"foo!\""))
|
||||
|
||||
where
|
||||
addr = Address . Precise
|
||||
|
@ -28,7 +28,7 @@ spec = parallel $ do
|
||||
|
||||
it "subclass" $ do
|
||||
res <- evaluate' "subclass.rb"
|
||||
fst res `shouldBe` Right (injValue (String "\"<bar>\""))
|
||||
join (fst res) `shouldBe` Right (injValue (String "\"<bar>\""))
|
||||
|
||||
where
|
||||
addr = Address . Precise
|
||||
|
@ -156,7 +156,7 @@ instance Listable1 f => Listable2 (FreeF f) where
|
||||
instance (Listable1 f, Listable a) => Listable1 (FreeF f a) where
|
||||
liftTiers = liftTiers2 tiers
|
||||
|
||||
instance (Functor f, Listable1 f) => Listable1 (Free.Free f) where
|
||||
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
|
||||
|
@ -12,13 +12,16 @@ main = do
|
||||
|
||||
extensions :: [String]
|
||||
extensions =
|
||||
[ "DeriveFoldable"
|
||||
[ "DataKinds"
|
||||
, "DeriveFoldable"
|
||||
, "DeriveFunctor"
|
||||
, "DeriveGeneric"
|
||||
, "DeriveTraversable"
|
||||
, "FlexibleContexts"
|
||||
, "FlexibleInstances"
|
||||
, "MultiParamTypeClasses"
|
||||
, "OverloadedStrings"
|
||||
, "RecordWildCards"
|
||||
, "StandaloneDeriving"
|
||||
, "StrictData"
|
||||
]
|
||||
|
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE DataKinds, GADTs, ScopedTypeVariables, TypeFamilies, TypeOperators, TypeApplications #-}
|
||||
{-# LANGUAGE GADTs, ScopedTypeVariables, TypeFamilies, TypeOperators, TypeApplications #-}
|
||||
module SpecHelpers (
|
||||
module X
|
||||
, diffFilePaths
|
||||
@ -34,6 +34,7 @@ import Data.Functor.Both as X (Both, runBothWith, both)
|
||||
import Data.Maybe as X
|
||||
import Data.Monoid as X (Monoid(..), First(..), Last(..))
|
||||
import Data.Semigroup as X (Semigroup(..))
|
||||
import Control.Monad as X
|
||||
|
||||
import Test.Hspec as X (Spec, SpecWith, context, describe, it, xit, parallel, pendingWith, around, runIO)
|
||||
import Test.Hspec.Expectations.Pretty as X
|
||||
|
Loading…
Reference in New Issue
Block a user