1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 01:47:01 +03:00

remove vestigial dependencies

This commit is contained in:
Patrick Thomson 2020-06-24 15:31:23 -04:00
parent 27d5650489
commit 65fba3ecc6
4 changed files with 1 additions and 30 deletions

View File

@ -59,7 +59,6 @@ common dependencies
, fused-effects-resumable ^>= 0.1
, hashable >= 1.2.7 && < 1.4
, tree-sitter ^>= 0.9.0.1
, mtl ^>= 2.2.2
, network ^>= 2.8.0.0
, pathtype ^>= 0.8.1
, process ^>= 1.6.3.0
@ -206,7 +205,6 @@ test-suite test
type: exitcode-stdio-1.0
hs-source-dirs: test
main-is: Spec.hs
ghc-options: -Werror
other-modules: Data.Functor.Classes.Generic.Spec
, Data.Functor.Listable
, Data.Graph.Spec

View File

@ -23,7 +23,6 @@ import Data.Duration
import Data.Maybe.Exts
import Source.Loc
import qualified Source.Source as Source
import Source.Span
import qualified System.Timeout as System
import qualified TreeSitter.Cursor as TS

View File

@ -7,9 +7,7 @@
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-missing-signatures -Wno-missing-exported-signatures -Wno-partial-type-signatures -O0 #-}
module Semantic.Util
( mergeErrors
, reassociate
, parseFile
( parseFile
, parseFileQuiet
) where
@ -17,12 +15,10 @@ import Prelude hiding (readFile)
import Analysis.File
import Control.Carrier.Parse.Simple
import Control.Carrier.Resumable.Either (SomeError (..))
import Control.Effect.Reader
import Control.Exception hiding (evaluate)
import Control.Monad
import qualified Data.Language as Language
import Data.Sum
import Parsing.Parser
import Semantic.Config
import Semantic.Task
@ -40,9 +36,3 @@ fileForPath (Path.absRel -> p) = File p (point (Pos 1 1)) (Language.forPath p)
runTask', runTaskQuiet :: ParseC TaskC a -> IO a
runTask' task = runTaskWithOptions debugOptions (asks configTreeSitterParseTimeout >>= \ timeout -> runParse timeout task) >>= either (die . displayException) pure
runTaskQuiet task = runTaskWithOptions defaultOptions (asks configTreeSitterParseTimeout >>= \ timeout -> runParse timeout task) >>= either (die . displayException) pure
mergeErrors :: Either (SomeError (Sum errs)) (Either (SomeError err) result) -> Either (SomeError (Sum (err ': errs))) result
mergeErrors = either (\ (SomeError sum) -> Left (SomeError (weaken sum))) (either (\ (SomeError err) -> Left (SomeError (inject err))) Right)
reassociate :: Either (SomeError err1) (Either (SomeError err2) (Either (SomeError err3) (Either (SomeError err4) (Either (SomeError err5) (Either (SomeError err6) (Either (SomeError err7) (Either (SomeError err8) result))))))) -> Either (SomeError (Sum '[err8, err7, err6, err5, err4, err3, err2, err1])) result
reassociate = mergeErrors . mergeErrors . mergeErrors . mergeErrors . mergeErrors . mergeErrors . mergeErrors . mergeErrors . Right

View File

@ -21,7 +21,6 @@ import Data.Edit
import qualified Data.Language as Language
import Data.List.NonEmpty
import Data.Text as T (Text, pack)
import Data.Sum
import Source.Loc
import Source.Span
import Test.LeanCheck
@ -33,11 +32,6 @@ class Listable1 l where
-- | The tiers for @l :: * -> *@, parameterized by the tiers for @a :: *@.
liftTiers :: [Tier a] -> [Tier (l a)]
-- | A suitable definition of 'tiers' for 'Listable1' type constructors parameterized by 'Listable' types.
tiers1 :: (Listable a, Listable1 l) => [Tier (l a)]
tiers1 = liftTiers tiers
-- | Lifting of 'Listable' to @* -> * -> *@.
class Listable2 l where
-- | The tiers for @l :: * -> * -> *@, parameterized by the tiers for @a :: *@ & @b :: *@.
@ -91,16 +85,6 @@ instance (Listable a, Listable b) => Listable (Edit a b) where
tiers = tiers2
instance (Listable1 f, Listable1 (Sum (g ': fs))) => Listable1 (Sum (f ': g ': fs)) where
liftTiers tiers = (inject `mapT` ((liftTiers :: [Tier a] -> [Tier (f a)]) tiers)) \/ (weaken `mapT` ((liftTiers :: [Tier a] -> [Tier (Sum (g ': fs) a)]) tiers))
instance Listable1 f => Listable1 (Sum '[f]) where
liftTiers tiers = inject `mapT` ((liftTiers :: [Tier a] -> [Tier (f a)]) tiers)
instance (Listable1 (Sum fs), Listable a) => Listable (Sum fs a) where
tiers = tiers1
instance Listable Name.Name where
tiers = cons1 Name.name