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

Add language extensions to everything.

This commit is contained in:
Rob Rix 2019-10-30 12:49:23 -04:00
parent 298c37feff
commit 7262484a57
No known key found for this signature in database
GPG Key ID: F188A01508EA1CF7
137 changed files with 250 additions and 231 deletions

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeOperators #-}
{-# LANGUAGE DeriveFunctor, FlexibleContexts, GeneralizedNewtypeDeriving, TypeApplications, TypeOperators #-}
module Analysis.Abstract.Caching.FlowInsensitive
( cachingTerms
, convergingModules

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ConstraintKinds, GADTs, GeneralizedNewtypeDeriving, TypeOperators #-}
{-# LANGUAGE ConstraintKinds, FlexibleContexts, GADTs, GeneralizedNewtypeDeriving, TypeApplications, TypeOperators #-}
module Analysis.Abstract.Caching.FlowSensitive
( Cache
, cachingTerms

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeOperators #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, StandaloneDeriving #-}
module Analysis.Abstract.Dead
( Dead(..)
, revivingTerms

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DerivingVia, LambdaCase, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DerivingVia, FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, OverloadedStrings, RankNTypes, RecordWildCards, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
module Analysis.Abstract.Graph
( Graph(..)
, ControlFlowVertex(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
module Analysis.Abstract.Tracing
( tracingTerms
, tracing

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DataKinds, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Analysis.ConstructorName
( ConstructorName(..)
) where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, DefaultSignatures, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
{-# LANGUAGE DataKinds, DefaultSignatures, FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, TypeApplications, TypeFamilies, UndecidableInstances #-}
module Analysis.CyclomaticComplexity
( CyclomaticComplexity(..)
, HasCyclomaticComplexity
@ -103,8 +103,8 @@ type family CyclomaticComplexityStrategy syntax where
CyclomaticComplexityStrategy Statement.If = 'Custom
CyclomaticComplexityStrategy Statement.Pattern = 'Custom
CyclomaticComplexityStrategy Statement.While = 'Custom
CyclomaticComplexityStrategy (Sum fs) = 'Custom
CyclomaticComplexityStrategy a = 'Default
CyclomaticComplexityStrategy (Sum _) = 'Custom
CyclomaticComplexityStrategy _ = 'Default
-- | The 'Default' strategy takes the sum without incrementing.

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts, TypeFamilies #-}
module Analysis.Decorator
( decoratorWithAlgebra
) where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DataKinds, FlexibleInstances, MultiParamTypeClasses, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Analysis.HasTextElement
( HasTextElement(..)
) where
@ -29,8 +29,8 @@ class HasTextElementWithStrategy (strategy :: Strategy) syntax where
type family TextElementStrategy syntax where
TextElementStrategy Literal.TextElement = 'Custom
TextElementStrategy (Sum fs) = 'Custom
TextElementStrategy a = 'Default
TextElementStrategy (Sum _) = 'Custom
TextElementStrategy _ = 'Default
instance HasTextElementWithStrategy 'Default syntax where
isTextElementWithStrategy _ _ = False

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
{-# LANGUAGE DataKinds, FlexibleInstances, MultiParamTypeClasses, RecordWildCards, ScopedTypeVariables, TypeApplications, TypeFamilies, UndecidableInstances #-}
module Analysis.PackageDef
( PackageDef(..)
, HasPackageDef
@ -15,7 +15,7 @@ import Prologue
import Source.Loc
newtype PackageDef = PackageDef { moduleDefIdentifier :: T.Text }
deriving (Eq, Generic, Show)
deriving (Eq, Show)
-- | An r-algebra producing 'Just' a 'PackageDef' for syntax nodes corresponding to high-level declarations, or 'Nothing' otherwise.
--
@ -80,8 +80,8 @@ class HasPackageDefWithStrategy (strategy :: Strategy) syntax where
-- If youre seeing errors about missing a 'CustomHasPackageDef' instance for a given type, youve probably listed it in here but not defined a 'CustomHasPackageDef' instance for it, or else youve listed the wrong type in here. Conversely, if your 'customHasPackageDef' method is never being called, you may have forgotten to list the type in here.
type family PackageDefStrategy syntax where
PackageDefStrategy Language.Go.Syntax.Package = 'Custom
PackageDefStrategy (Sum fs) = 'Custom
PackageDefStrategy a = 'Default
PackageDefStrategy (Sum _) = 'Custom
PackageDefStrategy _ = 'Default
-- | The 'Default' strategy produces 'Nothing'.

View File

@ -1,4 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes, LambdaCase, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances, ViewPatterns #-}
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses, OverloadedStrings, RankNTypes, RecordWildCards, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances, ViewPatterns #-}
module Analysis.TOCSummary
( Declaration(..)
, formatIdentifier
@ -151,5 +151,5 @@ type family DeclarationStrategy syntax where
DeclarationStrategy Declaration.Method = 'Custom
DeclarationStrategy Markdown.Heading = 'Custom
DeclarationStrategy Syntax.Error = 'Custom
DeclarationStrategy (Sum fs) = 'Custom
DeclarationStrategy a = 'Default
DeclarationStrategy (Sum _) = 'Custom
DeclarationStrategy _ = 'Default

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GADTs, InstanceSigs, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, StandaloneDeriving, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, GADTs, InstanceSigs, MultiParamTypeClasses, RankNTypes, RecordWildCards, ScopedTypeVariables, StandaloneDeriving, TypeFamilies, TypeOperators #-}
{-# OPTIONS_GHC -Wno-redundant-constraints #-} -- For HasCallStack
-- | Assignment of AST onto some other structure (typically terms).
--

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DeriveGeneric, DeriveTraversable, DerivingVia, RecordWildCards #-}
module Assigning.Assignment.Table
( Table(tableAddresses)
, singleton

View File

@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleContexts #-}
module Control.Abstract.Context
( ModuleInfo
, currentModule

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, ScopedTypeVariables, TypeApplications, TypeOperators, UndecidableInstances #-}
module Control.Abstract.Evaluator
( Evaluator(..)
, raiseHandler

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GADTs, GeneralizedNewtypeDeriving, KindSignatures, RankNTypes, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor, DeriveGeneric, FlexibleContexts, GADTs, GeneralizedNewtypeDeriving, KindSignatures, RankNTypes, RecordWildCards, ScopedTypeVariables, StandaloneDeriving, TypeOperators, UndecidableInstances #-}
module Control.Abstract.Heap
( Heap
, HeapError(..)
@ -420,15 +420,17 @@ reachable roots heap = go mempty roots
data Deref value (m :: * -> *) k
= DerefCell (Set value) (Maybe value -> m k)
| AssignCell value (Set value) (Set value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Deref value)
instance Effect (Deref value)
runDeref :: Evaluator term address value (DerefC address value m) a
-> Evaluator term address value m a
runDeref = raiseHandler runDerefC
newtype DerefC address value m a = DerefC { runDerefC :: m a }
deriving newtype (Alternative, Applicative, Functor, Monad)
deriving (Alternative, Applicative, Functor, Monad)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GADTs, GeneralizedNewtypeDeriving, KindSignatures, RankNTypes, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, GADTs, GeneralizedNewtypeDeriving, KindSignatures, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, StandaloneDeriving, TypeOperators, UndecidableInstances #-}
module Control.Abstract.Modules
( ModuleResult
, lookupModule
@ -65,8 +65,10 @@ data Modules address value (m :: * -> *) k
| Lookup ModulePath (Maybe (ModuleResult address value) -> m k)
| Resolve [FilePath] (Maybe ModulePath -> m k)
| List FilePath ([ModulePath] -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Modules address value)
instance Effect (Modules address value)
sendModules :: ( Member (Modules address value) sig
@ -81,7 +83,7 @@ runModules :: Set ModulePath
runModules paths = raiseHandler (runReader paths . runModulesC)
newtype ModulesC address value m a = ModulesC { runModulesC :: ReaderC (Set ModulePath) m a }
deriving newtype (Alternative, Applicative, Functor, Monad, MonadIO)
deriving (Alternative, Applicative, Functor, Monad, MonadIO)
instance ( Member (Reader (ModuleTable (Module (ModuleResult address value)))) sig
, Member (Resumable (BaseError (LoadError address value))) sig

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleContexts, RecordWildCards, TupleSections #-}
module Control.Abstract.Primitive
( defineClass
, defineNamespace

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, OverloadedStrings, UndecidableInstances #-}
module Control.Abstract.PythonPackage
( runPythonPackaging, Strategy(..) ) where

View File

@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleContexts, MultiParamTypeClasses #-}
module Control.Abstract.Roots
( ValueRoots(..)
, Live

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GADTs, GeneralizedNewtypeDeriving, KindSignatures, RankNTypes, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor, DeriveGeneric, FlexibleContexts, GADTs, GeneralizedNewtypeDeriving, KindSignatures, RankNTypes, RecordWildCards, ScopedTypeVariables, StandaloneDeriving, TypeApplications, TypeOperators, UndecidableInstances #-}
module Control.Abstract.ScopeGraph
( lookup
, declare
@ -367,15 +367,17 @@ alloc = send . flip Alloc pure
data Allocator address (m :: * -> *) k
= Alloc Name (address -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Allocator address)
instance Effect (Allocator address)
runAllocator :: Evaluator term address value (AllocatorC address m) a
-> Evaluator term address value m a
runAllocator = raiseHandler runAllocatorC
newtype AllocatorC address m a = AllocatorC { runAllocatorC :: m a }
deriving newtype (Alternative, Applicative, Functor, Monad)
deriving (Alternative, Applicative, Functor, Monad)
runScopeErrorWith :: (forall resume . BaseError (ScopeError address) resume -> Evaluator term address value m resume)
-> Evaluator term address value (ResumableWithC (BaseError (ScopeError address)) m) a

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GADTs, GeneralizedNewtypeDeriving, KindSignatures, Rank2Types, ScopedTypeVariables, TypeOperators #-}
{-# LANGUAGE DeriveFunctor, DeriveGeneric, FlexibleContexts, GADTs, GeneralizedNewtypeDeriving, KindSignatures, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, TypeOperators #-}
module Control.Abstract.Value
( AbstractValue(..)
, AbstractIntro(..)
@ -133,9 +133,10 @@ data Function term address value (m :: * -> *) k
| BuiltIn address BuiltIn (value -> m k) -- ^ A built-in is parameterized by its parent scope, BuiltIn type, and returns a value.
| Call value [value] (value -> m k) -- ^ A Call takes a set of values as parameters and returns a ValueRef.
| Bind value value (value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Function term address value)
instance Effect (Function term address value)
runFunction :: (term -> Evaluator term address value (FunctionC term address value m) value)
-> Evaluator term address value (FunctionC term address value m) a
@ -143,7 +144,7 @@ runFunction :: (term -> Evaluator term address value (FunctionC term address val
runFunction eval = raiseHandler (runReader (runEvaluator . eval) . runFunctionC)
newtype FunctionC term address value m a = FunctionC { runFunctionC :: ReaderC (term -> FunctionC term address value m value) m a }
deriving newtype (Alternative, Applicative, Functor, Monad)
deriving (Alternative, Applicative, Functor, Monad)
-- | Construct a boolean value in the abstract domain.
boolean :: (Member (Boolean value) sig, Carrier sig m) => Bool -> m value
@ -160,16 +161,17 @@ ifthenelse v t e = asBool v >>= \ c -> if c then t else e
data Boolean value (m :: * -> *) k
= Boolean Bool (value -> m k)
| AsBool value (Bool -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Boolean value)
instance Effect (Boolean value)
runBoolean :: Evaluator term address value (BooleanC value m) a
-> Evaluator term address value m a
runBoolean = raiseHandler runBooleanC
newtype BooleanC value m a = BooleanC { runBooleanC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
-- | The fundamental looping primitive, built on top of 'ifthenelse'.
@ -209,7 +211,7 @@ forLoop initial cond step body = initial *> while cond (withLexicalScopeAndFrame
data While value m k
= While (m value) (m value) (value -> m k)
deriving stock (Functor, Generic1)
deriving (Functor, Generic1)
instance HFunctor (While value) where
hmap f (While cond body k) = While (f cond) (f body) (f . k)
@ -219,8 +221,7 @@ runWhile :: Evaluator term address value (WhileC value m) a
runWhile = raiseHandler runWhileC
newtype WhileC value m a = WhileC { runWhileC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
-- | Construct an abstract unit value.
unit :: (Carrier sig m, Member (Unit value) sig) => Evaluator term address value m value
@ -228,16 +229,17 @@ unit = send (Unit pure)
newtype Unit value (m :: * -> *) k
= Unit (value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Unit value)
instance Effect (Unit value)
runUnit :: Evaluator term address value (UnitC value m) a
-> Evaluator term address value m a
runUnit = raiseHandler runUnitC
newtype UnitC value m a = UnitC { runUnitC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
-- | Construct a String value in the abstract domain.
string :: (Member (String value) sig, Carrier sig m) => Text -> m value
@ -250,12 +252,13 @@ asString v = send (AsString v pure)
data String value (m :: * -> *) k
= String Text (value -> m k)
| AsString value (Text -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (String value)
instance Effect (String value)
newtype StringC value m a = StringC { runStringC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
runString :: Evaluator term address value (StringC value m) a
-> Evaluator term address value m a
@ -302,12 +305,13 @@ data Numeric value (m :: * -> *) k
| Rational Rational (value -> m k)
| LiftNumeric NumericFunction value (value -> m k)
| LiftNumeric2 Numeric2Function value value (value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Numeric value)
instance Effect (Numeric value)
newtype NumericC value m a = NumericC { runNumericC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
runNumeric :: Evaluator term address value (NumericC value m) a
-> Evaluator term address value m a
@ -350,16 +354,17 @@ data Bitwise value (m :: * -> *) k
| LiftBitwise BitwiseFunction value (value -> m k)
| LiftBitwise2 Bitwise2Function value value (value -> m k)
| UnsignedRShift value value (value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Bitwise value)
instance Effect (Bitwise value)
runBitwise :: Evaluator term address value (BitwiseC value m) a
-> Evaluator term address value m a
runBitwise = raiseHandler runBitwiseC
newtype BitwiseC value m a = BitwiseC { runBitwiseC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
object :: (Member (Object address value) sig, Carrier sig m) => address -> m value
object address = send (Object address pure)
@ -378,12 +383,13 @@ data Object address value m k
= Object address (value -> m k)
| ScopedEnvironment value (Maybe address -> m k)
| Klass Declaration address (value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Object address value)
instance Effect (Object address value)
newtype ObjectC address value m a = ObjectC { runObjectC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
runObject :: Evaluator term address value (ObjectC address value m) a
-> Evaluator term address value m a
@ -399,12 +405,13 @@ asArray v = send (AsArray v pure)
data Array value (m :: * -> *) k
= Array [value] (value -> m k)
| AsArray value ([value] -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Array value)
instance Effect (Array value)
newtype ArrayC value m a = ArrayC { runArrayC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
runArray :: Evaluator term address value (ArrayC value m) a
-> Evaluator term address value m a
@ -421,12 +428,13 @@ kvPair v1 v2 = send (KvPair v1 v2 pure)
data Hash value (m :: * -> *) k
= Hash [(value, value)] (value -> m k)
| KvPair value value (value -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Hash value)
instance Effect (Hash value)
newtype HashC value m a = HashC { runHashC :: m a }
deriving stock Functor
deriving newtype (Alternative, Applicative, Monad)
deriving (Alternative, Applicative, Functor, Monad)
runHash :: Evaluator term address value (HashC value m) a
-> Evaluator term address value m a

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, GeneralizedNewtypeDeriving, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, GeneralizedNewtypeDeriving, MultiParamTypeClasses, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
-- | A carrier for 'Parse' effects suitable for use in production.
module Control.Carrier.Parse.Measured
( -- * Parse effect
@ -21,7 +21,6 @@ import Data.Blob
import qualified Data.Error as Error
import qualified Data.Flag as Flag
import qualified Data.Syntax as Syntax
import Data.Typeable
import Parsing.CMark
import Parsing.Parser
import Parsing.TreeSitter
@ -74,7 +73,7 @@ runParser blob@Blob{..} parser = case parser of
where languageTag = [("language" :: String, show (blobLanguage blob))]
data ParserCancelled = ParserTimedOut | AssignmentTimedOut
deriving (Show, Typeable)
deriving (Show)
instance Exception ParserCancelled

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, GeneralizedNewtypeDeriving, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, GeneralizedNewtypeDeriving, MultiParamTypeClasses, RecordWildCards, TypeOperators, UndecidableInstances #-}
-- | A carrier for 'Parse' effects suitable for use in the repl, tests, etc.
module Control.Carrier.Parse.Simple
( -- * Parse effect
@ -18,7 +18,6 @@ import Control.Effect.Reader
import Control.Exception
import Control.Monad.IO.Class
import Data.Blob
import Data.Typeable
import Parsing.CMark
import Parsing.Parser
import Parsing.TreeSitter
@ -64,6 +63,6 @@ runParser timeout blob@Blob{..} parser = case parser of
in length term `seq` pure term
newtype ParseFailure = ParseFailure String
deriving (Show, Typeable)
deriving (Show)
instance Exception ParseFailure

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ExistentialQuantification, GeneralizedNewtypeDeriving, KindSignatures, RankNTypes, StandaloneDeriving, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor, ExistentialQuantification, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, KindSignatures, MultiParamTypeClasses, RankNTypes, StandaloneDeriving, TypeOperators, UndecidableInstances #-}
module Control.Effect.Interpose
( Interpose(..)
, interpose

View File

@ -1,4 +1,4 @@
{-# LANGUAGE ConstraintKinds, ExistentialQuantification, GADTs, RankNTypes #-}
{-# LANGUAGE ConstraintKinds, DeriveFunctor, ExistentialQuantification, FlexibleContexts, GADTs, RankNTypes, StandaloneDeriving #-}
module Control.Effect.Parse
( -- * Parse effect
Parse(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingStrategies, GeneralizedNewtypeDeriving, KindSignatures, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, KindSignatures, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
module Control.Effect.REPL
( REPL (..)
@ -18,8 +18,10 @@ import qualified Data.Text as T
data REPL (m :: * -> *) k
= Prompt Text (Maybe Text -> m k)
| Output Text (m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor REPL
instance Effect REPL
prompt :: (Member REPL sig, Carrier sig m) => Text -> m (Maybe Text)
prompt p = send (Prompt p pure)
@ -31,7 +33,7 @@ runREPL :: Prefs -> Settings IO -> REPLC m a -> m a
runREPL prefs settings = runReader (prefs, settings) . runREPLC
newtype REPLC m a = REPLC { runREPLC :: ReaderC (Prefs, Settings IO) m a }
deriving newtype (Functor, Applicative, Monad, MonadIO)
deriving (Functor, Applicative, Monad, MonadIO)
instance (Carrier sig m, MonadIO m) => Carrier (REPL :+: sig) (REPLC m) where
eff (L op) = do

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, TypeOperators #-}
{-# LANGUAGE FlexibleContexts, GADTs, TypeOperators #-}
-- | This module provides 'Rewrite', a monadic DSL that abstracts the
-- details of rewriting a given datum into another type, supporting

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings, RecordWildCards #-}
module Data.AST
( Node (..)
, nodeSpan

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, UndecidableInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, TypeApplications, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans -Wno-missing-export-lists #-}
module Data.Abstract.AccessControls.Instances where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DeriveTraversable, FlexibleInstances, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Address.Hole
( Hole(..)
, toMaybe

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Address.Monovariant
( Monovariant(..)
) where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Address.Precise
( Precise(..)
) where

View File

@ -1,5 +1,4 @@
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE FlexibleContexts, KindSignatures, RecordWildCards #-}
module Data.Abstract.BaseError (
BaseError(..)
, throwBaseError

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, UndecidableInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving, StandaloneDeriving, TypeApplications, UndecidableInstances #-}
module Data.Abstract.Declarations
( Declarations (..)
, Declarations1 (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, KindSignatures, RankNTypes, TypeOperators, UndecidableInstances, InstanceSigs #-}
{-# LANGUAGE DataKinds, FlexibleContexts, GADTs, KindSignatures, OverloadedStrings, RankNTypes, StandaloneDeriving, TypeApplications, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Evaluatable
( module X
, Evaluatable(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DefaultSignatures, GeneralizedNewtypeDeriving, UndecidableInstances #-}
{-# LANGUAGE DefaultSignatures, GeneralizedNewtypeDeriving, StandaloneDeriving, TypeApplications, UndecidableInstances #-}
module Data.Abstract.FreeVariables
( FreeVariables (..)
, FreeVariables1 (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, RecordWildCards #-}
module Data.Abstract.Heap
( Heap(..)
, Frame(..)
@ -52,11 +52,11 @@ data Frame scopeAddress frameAddress value = Frame
, slots :: IntMap (Set value)
-- ^ An IntMap of values that are declared in the frame.
}
deriving (Eq, Ord, Show, Generic)
deriving (Eq, Ord, Show)
-- | A Heap is a Map from frame addresses to frames.
newtype Heap scopeAddress frameAddress value = Heap { unHeap :: Map frameAddress (Frame scopeAddress frameAddress value) }
deriving (Eq, Generic, Lower, Ord)
deriving (Eq, Lower, Ord)
-- | Look up the frame for an 'address' in a 'Heap', if any.

View File

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveTraversable, RecordWildCards #-}
module Data.Abstract.Module
( Module(..)
, moduleForBlob
@ -14,7 +15,7 @@ import Prologue
import System.FilePath.Posix
data Module body = Module { moduleInfo :: ModuleInfo, moduleBody :: body }
deriving (Eq, Foldable, Functor, Ord, Traversable, Generic)
deriving (Eq, Foldable, Functor, Ord, Traversable)
instance Show body => Show (Module body) where
showsPrec d Module{..} = showsBinaryWith showsPrec showsPrec "Module" d (modulePath moduleInfo) moduleBody
@ -33,7 +34,7 @@ moduleForBlob rootDir b = Module info
type ModulePath = FilePath
data ModuleInfo = ModuleInfo { modulePath :: ModulePath, moduleLanguage :: Language, moduleOid :: Text }
deriving (Eq, Ord, Generic)
deriving (Eq, Ord)
instance Lower ModuleInfo where
lowerBound = ModuleInfo mempty Unknown mempty

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable, GeneralizedNewtypeDeriving #-}
module Data.Abstract.ModuleTable
( ModulePath
, ModuleTable (..)
@ -15,13 +15,12 @@ module Data.Abstract.ModuleTable
import Data.Abstract.Module
import qualified Data.Map as Map
import GHC.Generics (Generic1)
import Prelude hiding (lookup)
import Prologue
import System.FilePath.Posix
newtype ModuleTable a = ModuleTable { unModuleTable :: Map.Map ModulePath a }
deriving (Eq, Foldable, Functor, Generic1, Generic, Lower, Monoid, Ord, Semigroup, Traversable)
deriving (Eq, Foldable, Functor, Lower, Monoid, Ord, Semigroup, Traversable)
singleton :: ModulePath -> a -> ModuleTable a
singleton name = ModuleTable . Map.singleton name

View File

@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleContexts, OverloadedStrings #-}
module Data.Abstract.Name
( Name
-- * Constructors
@ -19,7 +20,7 @@ import Prologue
data Name
= Name Text
| I Int
deriving (Eq, Ord, Generic)
deriving (Eq, Ord)
-- | Generate a fresh (unused) name for use in synthesized variables/closures/etc.
gensym :: (Member Fresh sig, Carrier sig m) => m Name

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, StandaloneDeriving, Rank2Types #-}
{-# LANGUAGE GADTs, StandaloneDeriving, RankNTypes, TypeApplications #-}
module Data.Abstract.Number
( Number (..)

View File

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveFunctor #-}
module Data.Abstract.Package
( Package (..)
, PackageInfo (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DuplicateRecordFields, LambdaCase, TupleSections #-}
{-# LANGUAGE DeriveAnyClass, DeriveFunctor, DeriveGeneric, DuplicateRecordFields, LambdaCase, OverloadedStrings, RecordWildCards, TupleSections #-}
module Data.Abstract.ScopeGraph
( Slot(..)
, Info(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, OverloadedStrings, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Value.Abstract
( Abstract (..)
, runFunction

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, LambdaCase, RankNTypes, ScopedTypeVariables, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, LambdaCase, MultiParamTypeClasses, RankNTypes, ScopedTypeVariables, StandaloneDeriving, TypeApplications, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Value.Concrete
( Value (..)
, ValueError (..)
@ -44,7 +44,7 @@ data Value term address
| Hash [Value term address]
| Null
| Hole
deriving (Eq, Ord, Show, Generic)
deriving (Eq, Ord, Show)
instance ValueRoots address (Value term address) where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, LambdaCase, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, GADTs, LambdaCase, MultiParamTypeClasses, OverloadedStrings, RankNTypes, ScopedTypeVariables, StandaloneDeriving, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Data.Abstract.Value.Type
( Type (..)
, TypeError (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveGeneric, DeriveTraversable, RankNTypes #-}
module Data.Algebra
( FAlgebra
, RAlgebra

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, ExplicitNamespaces, PatternSynonyms #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, ExplicitNamespaces, FlexibleContexts, FlexibleInstances, OverloadedStrings, RecordWildCards #-}
module Data.Blob
( File(..)
, fileForPath
@ -41,7 +41,7 @@ import qualified System.Path.PartClass as Path.PartClass
data File = File
{ filePath :: FilePath
, fileLanguage :: Language
} deriving (Show, Eq, Generic)
} deriving (Show, Eq)
-- | Prefer 'fileForTypedPath' if at all possible.
fileForPath :: FilePath -> File
@ -55,7 +55,7 @@ data Blob = Blob
{ blobSource :: Source -- ^ The UTF-8 encoded source text of the blob.
, blobFile :: File -- ^ Path/language information for this blob.
, blobOid :: Text -- ^ Git OID for this blob, mempty if blob is not from a git db.
} deriving (Show, Eq, Generic)
} deriving (Show, Eq)
blobLanguage :: Blob -> Language
blobLanguage = fileLanguage . blobFile
@ -92,7 +92,7 @@ decodeBlobs = fmap blobs <$> eitherDecode
-- | An exception indicating that weve tried to diff or parse a blob of unknown language.
newtype NoLanguageForBlob = NoLanguageForBlob FilePath
deriving (Eq, Exception, Ord, Show, Typeable)
deriving (Eq, Exception, Ord, Show)
noLanguageForBlob :: (Member (Error SomeException) sig, Carrier sig m) => FilePath -> m a
noLanguageForBlob blobPath = throwError (SomeException (NoLanguageForBlob blobPath))

View File

@ -1,5 +1,3 @@
{-# LANGUAGE RankNTypes #-}
-- | These are primitive file IO methods for use in ghci and as internal functions.
-- Instead of using these, consider if you can use the Files DSL instead.
module Data.Blob.IO
@ -20,7 +18,7 @@ import qualified Source.Source as Source
import qualified System.Path as Path
-- | Read a utf8-encoded file to a 'Blob'.
readBlobFromFile :: forall m. MonadIO m => File -> m (Maybe Blob)
readBlobFromFile :: MonadIO m => File -> m (Maybe Blob)
readBlobFromFile (File "/dev/null" _) = pure Nothing
readBlobFromFile (File path language) = do
raw <- liftIO $ B.readFile path

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, LambdaCase, RankNTypes, TypeFamilies, TypeOperators, ScopedTypeVariables, UndecidableInstances #-}
{-# LANGUAGE DataKinds, LambdaCase, OverloadedStrings, RankNTypes, TypeFamilies, TypeOperators, ScopedTypeVariables, UndecidableInstances #-}
module Data.Diff
( Diff(..)
, DiffF(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveGeneric, DeriveTraversable, LambdaCase #-}
module Data.Edit
( Edit(..)
, edit

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, RankNTypes #-}
{-# LANGUAGE DeriveFunctor, FlexibleInstances, GADTs, RankNTypes, RecordWildCards #-}
module Data.Error
( Error (..)
, formatError
@ -34,7 +34,7 @@ data Error grammar = Error
, errorExpected :: [grammar]
, errorActual :: Maybe grammar
, errorCallStack :: CallStack
} deriving (Show, Functor, Typeable)
} deriving (Show, Functor)
-- | This instance does not take into account the call stack.
instance Eq grammar => Eq (Error grammar) where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TypeOperators, RankNTypes, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, TypeOperators, RankNTypes, UndecidableInstances #-}
module Data.Functor.Classes.Generic
( Eq1(..)
, genericLiftEq

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts, GeneralizedNewtypeDeriving, OverloadedStrings, ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}
module Data.Graph
( Graph(..)
, overlay

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, EmptyCase, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, EmptyCase, FlexibleInstances, MultiParamTypeClasses, OverloadedStrings, RecordWildCards, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
module Data.Graph.ControlFlowVertex
( ControlFlowVertex (..)
, packageVertex

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, GADTs #-}
{-# LANGUAGE DataKinds, DeriveAnyClass, GADTs, StandaloneDeriving #-}
module Data.Handle
( Handle (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric #-}
module Data.ImportPath (IsRelative(..), ImportPath(..), importPath, toName, defaultAlias) where
import Prologue

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DefaultSignatures, MultiParamTypeClasses, TypeOperators, UndecidableInstances, GADTs #-}
{-# LANGUAGE DefaultSignatures, FlexibleContexts, FlexibleInstances, GADTs, MultiParamTypeClasses, OverloadedStrings, RecordWildCards, TypeApplications, TypeOperators, UndecidableInstances #-}
module Data.JSON.Fields
( JSONFields (..)
, JSONFields1 (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, KindSignatures, LambdaCase #-}
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, KindSignatures, LambdaCase, OverloadedStrings #-}
module Data.Language
( Language (..)
, SLanguage (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable, GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
-- | This module defines a 'Map' type whose 'Monoid' and 'Reducer' instances merge values using the 'Semigroup' instance for the underlying type.
module Data.Map.Monoidal
( Map

View File

@ -24,7 +24,7 @@ data Project = Project
, projectBlobs :: [Blob]
, projectLanguage :: Language
, projectExcludeDirs :: [FilePath]
} deriving (Eq, Show, Generic)
} deriving (Eq, Show)
projectName :: Project -> Text
projectName = T.pack . dropExtensions . takeFileName . projectRootDir

View File

@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
module Data.Scientific.Exts
( module Data.Scientific
, attemptUnsafeArithmetic

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable, GeneralizedNewtypeDeriving #-}
module Data.Semigroup.App
( App(..)
, AppMerge(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE AllowAmbiguousTypes, ConstraintKinds, DeriveAnyClass, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE AllowAmbiguousTypes, ConstraintKinds, DataKinds, DeriveAnyClass, DeriveGeneric, DeriveTraversable, FlexibleContexts, FlexibleInstances, MultiParamTypeClasses, OverloadedStrings, RankNTypes, RecordWildCards, ScopedTypeVariables, TypeApplications, TypeFamilies, TypeOperators, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists -Wno-redundant-constraints #-} -- For HasCallStack
module Data.Syntax where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, MultiParamTypeClasses #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DerivingVia, MultiParamTypeClasses #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Comment where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, MultiParamTypeClasses, ScopedTypeVariables, TupleSections, UndecidableInstances #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, FlexibleContexts, MultiParamTypeClasses, RecordWildCards, ScopedTypeVariables, TypeApplications, TupleSections, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Declaration where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Directive where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, MultiParamTypeClasses, ScopedTypeVariables, UndecidableInstances #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, FlexibleContexts, MultiParamTypeClasses, OverloadedStrings, RecordWildCards, ScopedTypeVariables, TypeApplications, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Expression where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, ScopedTypeVariables #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, OverloadedStrings, RecordWildCards, ScopedTypeVariables, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Literal where
@ -16,8 +16,7 @@ import Text.Read (readMaybe)
-- Boolean
newtype Boolean a = Boolean { booleanContent :: Bool }
deriving stock (Foldable, Traversable, Functor, Generic1)
deriving anyclass (Hashable1, Diffable, FreeVariables1, Declarations1, ToJSONFields1)
deriving (Declarations1, Diffable, Foldable, FreeVariables1, Functor, Generic1, Hashable1, ToJSONFields1, Traversable)
instance Eq1 Boolean where liftEq = genericLiftEq
instance Ord1 Boolean where liftCompare = genericLiftCompare

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, ScopedTypeVariables, UndecidableInstances, ViewPatterns, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, RecordWildCards, ScopedTypeVariables, TypeApplications, UndecidableInstances, ViewPatterns #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Statement where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, DeriveAnyClass, DerivingVia, DuplicateRecordFields, DeriveGeneric, MultiParamTypeClasses, UndecidableInstances #-}
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, DeriveGeneric, MultiParamTypeClasses, RecordWildCards, UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Data.Syntax.Type where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE FunctionalDependencies, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DeriveGeneric, DeriveTraversable, FlexibleContexts, FlexibleInstances, FunctionalDependencies, RankNTypes, ScopedTypeVariables, TypeFamilies, TypeOperators #-}
module Data.Term
( Term(..)
, TermF(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DefaultSignatures, DerivingStrategies, GeneralizedNewtypeDeriving, KindSignatures, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE DefaultSignatures, DeriveFunctor, DeriveGeneric, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, KindSignatures, MultiParamTypeClasses, TypeApplications, TypeOperators, UndecidableInstances #-}
module Diffing.Algorithm
( Diff (..)
, Algorithm(..)
@ -37,12 +37,13 @@ data Diff term1 term2 diff (m :: * -> *) k
| Insert term2 (diff -> m k)
-- | Replace one term with another.
| Replace term1 term2 (diff -> m k)
deriving stock (Functor, Generic1)
deriving anyclass (HFunctor, Effect)
deriving (Functor, Generic1)
instance HFunctor (Diff term1 term2 diff)
instance Effect (Diff term1 term2 diff)
newtype Algorithm term1 term2 diff m a = Algorithm { runAlgorithm :: m a }
deriving newtype (Applicative, Alternative, Functor, Monad)
deriving (Applicative, Alternative, Functor, Monad)
instance Carrier sig m => Carrier sig (Algorithm term1 term2 diff m) where
eff = Algorithm . eff . handleCoercible

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GADTs, DataKinds, DeriveAnyClass, RankNTypes, TypeOperators #-}
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric, GADTs, RankNTypes, RecordWildCards, TypeOperators #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-} -- FIXME
module Diffing.Algorithm.RWS
( rws

View File

@ -1,4 +1,4 @@
{-# LANGUAGE GeneralizedNewtypeDeriving, TypeOperators, UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-}
module Diffing.Interpreter
( diffTerms
, DiffTerms(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, RankNTypes, TypeFamilies, TypeOperators #-}
module Language.Go.Assignment
( assignment
, Go.Syntax

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, FlexibleContexts, RecordWildCards, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Go.Syntax where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, RecordWildCards, TypeFamilies #-}
module Language.Go.Term
( Syntax
, Term(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Go.Type where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, RankNTypes, RecordWildCards, TypeFamilies, TypeOperators #-}
module Language.Markdown.Assignment
( assignment
, Markdown.Syntax

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Markdown.Syntax where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, RecordWildCards, TypeFamilies #-}
module Language.Markdown.Term
( Syntax
, Term(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, RankNTypes, TypeFamilies, TypeOperators #-}
module Language.PHP.Assignment
( assignment
, PHP.Syntax

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, FlexibleContexts #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.PHP.Syntax where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, RecordWildCards, TypeFamilies #-}
module Language.PHP.Term
( Syntax
, Term(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, RankNTypes, TypeFamilies, TypeOperators #-}
module Language.Python.Assignment
( assignment
, Python.Syntax

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, FlexibleContexts, RecordWildCards, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Python.Syntax where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, RecordWildCards, TypeFamilies #-}
module Language.Python.Term
( Syntax
, Term(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, OverloadedStrings, RankNTypes, TypeFamilies, TypeOperators #-}
module Language.Ruby.Assignment
( assignment
, Ruby.Syntax

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, TupleSections #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, FlexibleContexts, OverloadedStrings, RecordWildCards, TupleSections, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.Ruby.Syntax where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, RecordWildCards, TypeFamilies #-}
module Language.Ruby.Term
( Syntax
, Term(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, OverloadedStrings, RankNTypes, TypeFamilies, TypeOperators #-}
module Language.TSX.Assignment
( assignment
, TSX.Syntax

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TSX.Syntax.JSX where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, TypeFamilies #-}
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving, RecordWildCards, TypeFamilies #-}
module Language.TSX.Term
( Syntax
, Term(..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DataKinds, RankNTypes, TypeFamilies, TypeOperators #-}
{-# LANGUAGE DataKinds, FlexibleContexts, OverloadedStrings, RankNTypes, TypeFamilies, TypeOperators #-}
module Language.TypeScript.Assignment
( assignment
, TypeScript.Syntax

View File

@ -1,3 +1,4 @@
{-# LANGUAGE FlexibleContexts, RecordWildCards #-}
module Language.TypeScript.Resolution
( ImportPath (..)
, IsRelative (..)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, OverloadedStrings, RecordWildCards, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Syntax.Import where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, RecordWildCards, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Syntax.JavaScript where

View File

@ -1,4 +1,4 @@
{-# LANGUAGE DeriveAnyClass, DerivingVia, DuplicateRecordFields, TupleSections #-}
{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DeriveTraversable, DuplicateRecordFields, FlexibleContexts, RecordWildCards, TupleSections, TypeApplications #-}
{-# OPTIONS_GHC -Wno-missing-export-lists #-}
module Language.TypeScript.Syntax.TypeScript where

Some files were not shown because too many files have changed in this diff Show More