{-# Language DeriveDataTypeable, FlexibleContexts, FlexibleInstances, LambdaCase, MultiParamTypeClasses,
OverloadedStrings, RankNTypes, ScopedTypeVariables, StandaloneDeriving,
TypeFamilies, TypeOperators, UndecidableInstances #-}
module Language.Haskell.Binder (
withBindings, unboundNames,
Binder, BindingVerifier,
Attributes, Environment, LocalEnvironment, ModuleEnvironment, WithEnvironment,
Binding(ErroneousBinding, TypeBinding, ValueBinding, TypeAndValueBinding),
BindingError(ClashingBindings, DuplicateInfixDeclaration, DuplicateRecordField),
TypeBinding(TypeClass), ValueBinding(InfixDeclaration, RecordConstructor, RecordField),
lookupType, lookupValue,
onMap, preludeName, baseName, unqualifiedName) where
import Control.Applicative ((<|>))
import Control.Exception (assert)
import Data.Data (Data, Typeable)
import Data.Foldable (fold, toList)
import Data.Functor (($>))
import Data.Functor.Compose (Compose(..))
import Data.Functor.Const (Const(Const))
import Data.Kind (Type)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe (fromMaybe)
import Data.Semigroup.Union (UnionWith(..))
import Data.Map.Lazy (Map)
import qualified Data.Map.Lazy as Map
import qualified Data.Set as Set
import qualified Rank2
import Transformation (Transformation)
import qualified Transformation
import qualified Transformation.AG.Dimorphic as Di
import qualified Transformation.Deep as Deep
import qualified Transformation.Full as Full
import qualified Transformation.Rank2
import qualified Language.Haskell.Abstract as Abstract
import qualified Language.Haskell.AST as AST hiding (Declaration(..))
import qualified Language.Haskell.Extensions as Extensions
import Language.Haskell.Extensions (Extension)
import qualified Language.Haskell.Extensions.AST as ExtAST
import qualified Language.Haskell.Extensions.AST as AST (Declaration(..))
type Environment l = UnionWith (Map (AST.QualifiedName l)) (Binding l)
type LocalEnvironment l = UnionWith (Map (AST.Name l)) (Binding l)
type ModuleEnvironment l = UnionWith (Map (AST.ModuleName l)) (LocalEnvironment l)
type Attributes l = Di.Atts (Environment l) (LocalEnvironment l)
type WithEnvironment l = Compose ((,) (Attributes l))
type FromEnvironment l f = Compose ((->) (Environment l)) (WithEnvironment l f)
data Binding l = ErroneousBinding (BindingError l)
| TypeBinding (TypeBinding l)
| ValueBinding (ValueBinding l)
| TypeAndValueBinding (TypeBinding l) (ValueBinding l)
| PatternBinding
deriving (Typeable, Typeable (Binding l)
Typeable (Binding l) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding l -> c (Binding l))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Binding l))
-> (Binding l -> Constr)
-> (Binding l -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Binding l)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Binding l)))
-> ((forall b. Data b => b -> b) -> Binding l -> Binding l)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r)
-> (forall u. (forall d. Data d => d -> u) -> Binding l -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Binding l -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l))
-> Data (Binding l)
Binding l -> Constr
Binding l -> DataType
(forall b. Data b => b -> b) -> Binding l -> Binding l
forall l. Data l => Typeable (Binding l)
forall l. Data l => Binding l -> Constr
forall l. Data l => Binding l -> DataType
forall l.
Data l =>
(forall b. Data b => b -> b) -> Binding l -> Binding l
forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> Binding l -> u
forall l u.
Data l =>
(forall d. Data d => d -> u) -> Binding l -> [u]
forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Binding l)
forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding l -> c (Binding l)
forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Binding l))
forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Binding l))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Binding l -> u
forall u. (forall d. Data d => d -> u) -> Binding l -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Binding l)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding l -> c (Binding l)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Binding l))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Binding l))
$cgfoldl :: forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding l -> c (Binding l)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Binding l -> c (Binding l)
$cgunfold :: forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Binding l)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Binding l)
$ctoConstr :: forall l. Data l => Binding l -> Constr
toConstr :: Binding l -> Constr
$cdataTypeOf :: forall l. Data l => Binding l -> DataType
dataTypeOf :: Binding l -> DataType
$cdataCast1 :: forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Binding l))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Binding l))
$cdataCast2 :: forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Binding l))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Binding l))
$cgmapT :: forall l.
Data l =>
(forall b. Data b => b -> b) -> Binding l -> Binding l
gmapT :: (forall b. Data b => b -> b) -> Binding l -> Binding l
$cgmapQl :: forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
$cgmapQr :: forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Binding l -> r
$cgmapQ :: forall l u.
Data l =>
(forall d. Data d => d -> u) -> Binding l -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Binding l -> [u]
$cgmapQi :: forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> Binding l -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Binding l -> u
$cgmapM :: forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
$cgmapMp :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
$cgmapMo :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Binding l -> m (Binding l)
Data, Binding l -> Binding l -> Bool
(Binding l -> Binding l -> Bool)
-> (Binding l -> Binding l -> Bool) -> Eq (Binding l)
forall l. Binding l -> Binding l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall l. Binding l -> Binding l -> Bool
== :: Binding l -> Binding l -> Bool
$c/= :: forall l. Binding l -> Binding l -> Bool
/= :: Binding l -> Binding l -> Bool
Eq, Int -> Binding l -> ShowS
[Binding l] -> ShowS
Binding l -> String
(Int -> Binding l -> ShowS)
-> (Binding l -> String)
-> ([Binding l] -> ShowS)
-> Show (Binding l)
forall l. Int -> Binding l -> ShowS
forall l. [Binding l] -> ShowS
forall l. Binding l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall l. Int -> Binding l -> ShowS
showsPrec :: Int -> Binding l -> ShowS
$cshow :: forall l. Binding l -> String
show :: Binding l -> String
$cshowList :: forall l. [Binding l] -> ShowS
showList :: [Binding l] -> ShowS
Show)
data BindingError l = ClashingBindings (Binding l) (Binding l)
| DuplicateInfixDeclaration (ValueBinding l) (ValueBinding l)
| DuplicateRecordField
| NoBindings
deriving (Typeable, Typeable (BindingError l)
Typeable (BindingError l) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BindingError l -> c (BindingError l))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (BindingError l))
-> (BindingError l -> Constr)
-> (BindingError l -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (BindingError l)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (BindingError l)))
-> ((forall b. Data b => b -> b)
-> BindingError l -> BindingError l)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r)
-> (forall u.
(forall d. Data d => d -> u) -> BindingError l -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> BindingError l -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l))
-> Data (BindingError l)
BindingError l -> Constr
BindingError l -> DataType
(forall b. Data b => b -> b) -> BindingError l -> BindingError l
forall l. Data l => Typeable (BindingError l)
forall l. Data l => BindingError l -> Constr
forall l. Data l => BindingError l -> DataType
forall l.
Data l =>
(forall b. Data b => b -> b) -> BindingError l -> BindingError l
forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> BindingError l -> u
forall l u.
Data l =>
(forall d. Data d => d -> u) -> BindingError l -> [u]
forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (BindingError l)
forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BindingError l -> c (BindingError l)
forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (BindingError l))
forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (BindingError l))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> BindingError l -> u
forall u. (forall d. Data d => d -> u) -> BindingError l -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (BindingError l)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BindingError l -> c (BindingError l)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (BindingError l))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (BindingError l))
$cgfoldl :: forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BindingError l -> c (BindingError l)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> BindingError l -> c (BindingError l)
$cgunfold :: forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (BindingError l)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (BindingError l)
$ctoConstr :: forall l. Data l => BindingError l -> Constr
toConstr :: BindingError l -> Constr
$cdataTypeOf :: forall l. Data l => BindingError l -> DataType
dataTypeOf :: BindingError l -> DataType
$cdataCast1 :: forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (BindingError l))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (BindingError l))
$cdataCast2 :: forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (BindingError l))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (BindingError l))
$cgmapT :: forall l.
Data l =>
(forall b. Data b => b -> b) -> BindingError l -> BindingError l
gmapT :: (forall b. Data b => b -> b) -> BindingError l -> BindingError l
$cgmapQl :: forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
$cgmapQr :: forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> BindingError l -> r
$cgmapQ :: forall l u.
Data l =>
(forall d. Data d => d -> u) -> BindingError l -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> BindingError l -> [u]
$cgmapQi :: forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> BindingError l -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> BindingError l -> u
$cgmapM :: forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
$cgmapMp :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
$cgmapMo :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> BindingError l -> m (BindingError l)
Data, BindingError l -> BindingError l -> Bool
(BindingError l -> BindingError l -> Bool)
-> (BindingError l -> BindingError l -> Bool)
-> Eq (BindingError l)
forall l. BindingError l -> BindingError l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall l. BindingError l -> BindingError l -> Bool
== :: BindingError l -> BindingError l -> Bool
$c/= :: forall l. BindingError l -> BindingError l -> Bool
/= :: BindingError l -> BindingError l -> Bool
Eq, Int -> BindingError l -> ShowS
[BindingError l] -> ShowS
BindingError l -> String
(Int -> BindingError l -> ShowS)
-> (BindingError l -> String)
-> ([BindingError l] -> ShowS)
-> Show (BindingError l)
forall l. Int -> BindingError l -> ShowS
forall l. [BindingError l] -> ShowS
forall l. BindingError l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall l. Int -> BindingError l -> ShowS
showsPrec :: Int -> BindingError l -> ShowS
$cshow :: forall l. BindingError l -> String
show :: BindingError l -> String
$cshowList :: forall l. [BindingError l] -> ShowS
showList :: [BindingError l] -> ShowS
Show)
data TypeBinding l = TypeClass (LocalEnvironment l)
| DataType (LocalEnvironment l)
| UnknownType
deriving (Typeable, Typeable (TypeBinding l)
Typeable (TypeBinding l) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeBinding l -> c (TypeBinding l))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (TypeBinding l))
-> (TypeBinding l -> Constr)
-> (TypeBinding l -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (TypeBinding l)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (TypeBinding l)))
-> ((forall b. Data b => b -> b) -> TypeBinding l -> TypeBinding l)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r)
-> (forall u. (forall d. Data d => d -> u) -> TypeBinding l -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> TypeBinding l -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l))
-> Data (TypeBinding l)
TypeBinding l -> Constr
TypeBinding l -> DataType
(forall b. Data b => b -> b) -> TypeBinding l -> TypeBinding l
forall l. Data l => Typeable (TypeBinding l)
forall l. Data l => TypeBinding l -> Constr
forall l. Data l => TypeBinding l -> DataType
forall l.
Data l =>
(forall b. Data b => b -> b) -> TypeBinding l -> TypeBinding l
forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> TypeBinding l -> u
forall l u.
Data l =>
(forall d. Data d => d -> u) -> TypeBinding l -> [u]
forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (TypeBinding l)
forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeBinding l -> c (TypeBinding l)
forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (TypeBinding l))
forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (TypeBinding l))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> TypeBinding l -> u
forall u. (forall d. Data d => d -> u) -> TypeBinding l -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (TypeBinding l)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeBinding l -> c (TypeBinding l)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (TypeBinding l))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (TypeBinding l))
$cgfoldl :: forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeBinding l -> c (TypeBinding l)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> TypeBinding l -> c (TypeBinding l)
$cgunfold :: forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (TypeBinding l)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (TypeBinding l)
$ctoConstr :: forall l. Data l => TypeBinding l -> Constr
toConstr :: TypeBinding l -> Constr
$cdataTypeOf :: forall l. Data l => TypeBinding l -> DataType
dataTypeOf :: TypeBinding l -> DataType
$cdataCast1 :: forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (TypeBinding l))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (TypeBinding l))
$cdataCast2 :: forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (TypeBinding l))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (TypeBinding l))
$cgmapT :: forall l.
Data l =>
(forall b. Data b => b -> b) -> TypeBinding l -> TypeBinding l
gmapT :: (forall b. Data b => b -> b) -> TypeBinding l -> TypeBinding l
$cgmapQl :: forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
$cgmapQr :: forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> TypeBinding l -> r
$cgmapQ :: forall l u.
Data l =>
(forall d. Data d => d -> u) -> TypeBinding l -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> TypeBinding l -> [u]
$cgmapQi :: forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> TypeBinding l -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> TypeBinding l -> u
$cgmapM :: forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
$cgmapMp :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
$cgmapMo :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> TypeBinding l -> m (TypeBinding l)
Data, TypeBinding l -> TypeBinding l -> Bool
(TypeBinding l -> TypeBinding l -> Bool)
-> (TypeBinding l -> TypeBinding l -> Bool) -> Eq (TypeBinding l)
forall l. TypeBinding l -> TypeBinding l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall l. TypeBinding l -> TypeBinding l -> Bool
== :: TypeBinding l -> TypeBinding l -> Bool
$c/= :: forall l. TypeBinding l -> TypeBinding l -> Bool
/= :: TypeBinding l -> TypeBinding l -> Bool
Eq, Int -> TypeBinding l -> ShowS
[TypeBinding l] -> ShowS
TypeBinding l -> String
(Int -> TypeBinding l -> ShowS)
-> (TypeBinding l -> String)
-> ([TypeBinding l] -> ShowS)
-> Show (TypeBinding l)
forall l. Int -> TypeBinding l -> ShowS
forall l. [TypeBinding l] -> ShowS
forall l. TypeBinding l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall l. Int -> TypeBinding l -> ShowS
showsPrec :: Int -> TypeBinding l -> ShowS
$cshow :: forall l. TypeBinding l -> String
show :: TypeBinding l -> String
$cshowList :: forall l. [TypeBinding l] -> ShowS
showList :: [TypeBinding l] -> ShowS
Show)
data ValueBinding l = InfixDeclaration (AST.Associativity l) Int (Maybe (ValueBinding l))
| DataConstructor
| RecordConstructor (LocalEnvironment l)
| RecordField
| DefinedValue
| RecordFieldAndValue
deriving (Typeable, Typeable (ValueBinding l)
Typeable (ValueBinding l) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ValueBinding l -> c (ValueBinding l))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ValueBinding l))
-> (ValueBinding l -> Constr)
-> (ValueBinding l -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ValueBinding l)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ValueBinding l)))
-> ((forall b. Data b => b -> b)
-> ValueBinding l -> ValueBinding l)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r)
-> (forall u.
(forall d. Data d => d -> u) -> ValueBinding l -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> ValueBinding l -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l))
-> Data (ValueBinding l)
ValueBinding l -> Constr
ValueBinding l -> DataType
(forall b. Data b => b -> b) -> ValueBinding l -> ValueBinding l
forall l. Data l => Typeable (ValueBinding l)
forall l. Data l => ValueBinding l -> Constr
forall l. Data l => ValueBinding l -> DataType
forall l.
Data l =>
(forall b. Data b => b -> b) -> ValueBinding l -> ValueBinding l
forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> ValueBinding l -> u
forall l u.
Data l =>
(forall d. Data d => d -> u) -> ValueBinding l -> [u]
forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ValueBinding l)
forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ValueBinding l -> c (ValueBinding l)
forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ValueBinding l))
forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ValueBinding l))
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> ValueBinding l -> u
forall u. (forall d. Data d => d -> u) -> ValueBinding l -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ValueBinding l)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ValueBinding l -> c (ValueBinding l)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ValueBinding l))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ValueBinding l))
$cgfoldl :: forall l (c :: * -> *).
Data l =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ValueBinding l -> c (ValueBinding l)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> ValueBinding l -> c (ValueBinding l)
$cgunfold :: forall l (c :: * -> *).
Data l =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ValueBinding l)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (ValueBinding l)
$ctoConstr :: forall l. Data l => ValueBinding l -> Constr
toConstr :: ValueBinding l -> Constr
$cdataTypeOf :: forall l. Data l => ValueBinding l -> DataType
dataTypeOf :: ValueBinding l -> DataType
$cdataCast1 :: forall l (t :: * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (ValueBinding l))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (ValueBinding l))
$cdataCast2 :: forall l (t :: * -> * -> *) (c :: * -> *).
(Data l, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ValueBinding l))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (ValueBinding l))
$cgmapT :: forall l.
Data l =>
(forall b. Data b => b -> b) -> ValueBinding l -> ValueBinding l
gmapT :: (forall b. Data b => b -> b) -> ValueBinding l -> ValueBinding l
$cgmapQl :: forall l r r'.
Data l =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
$cgmapQr :: forall l r r'.
Data l =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> ValueBinding l -> r
$cgmapQ :: forall l u.
Data l =>
(forall d. Data d => d -> u) -> ValueBinding l -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> ValueBinding l -> [u]
$cgmapQi :: forall l u.
Data l =>
Int -> (forall d. Data d => d -> u) -> ValueBinding l -> u
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> ValueBinding l -> u
$cgmapM :: forall l (m :: * -> *).
(Data l, Monad m) =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
$cgmapMp :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
$cgmapMo :: forall l (m :: * -> *).
(Data l, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> ValueBinding l -> m (ValueBinding l)
Data, ValueBinding l -> ValueBinding l -> Bool
(ValueBinding l -> ValueBinding l -> Bool)
-> (ValueBinding l -> ValueBinding l -> Bool)
-> Eq (ValueBinding l)
forall l. ValueBinding l -> ValueBinding l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall l. ValueBinding l -> ValueBinding l -> Bool
== :: ValueBinding l -> ValueBinding l -> Bool
$c/= :: forall l. ValueBinding l -> ValueBinding l -> Bool
/= :: ValueBinding l -> ValueBinding l -> Bool
Eq, Int -> ValueBinding l -> ShowS
[ValueBinding l] -> ShowS
ValueBinding l -> String
(Int -> ValueBinding l -> ShowS)
-> (ValueBinding l -> String)
-> ([ValueBinding l] -> ShowS)
-> Show (ValueBinding l)
forall l. Int -> ValueBinding l -> ShowS
forall l. [ValueBinding l] -> ShowS
forall l. ValueBinding l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall l. Int -> ValueBinding l -> ShowS
showsPrec :: Int -> ValueBinding l -> ShowS
$cshow :: forall l. ValueBinding l -> String
show :: ValueBinding l -> String
$cshowList :: forall l. [ValueBinding l] -> ShowS
showList :: [ValueBinding l] -> ShowS
Show)
data Unbound l = Unbound {forall l. Unbound l -> [QualifiedName l]
types :: [AST.QualifiedName l],
forall l. Unbound l -> [QualifiedName l]
values :: [AST.QualifiedName l],
forall l. Unbound l -> [QualifiedName l]
constructors :: [AST.QualifiedName l]}
deriving (Unbound l -> Unbound l -> Bool
(Unbound l -> Unbound l -> Bool)
-> (Unbound l -> Unbound l -> Bool) -> Eq (Unbound l)
forall l. Unbound l -> Unbound l -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall l. Unbound l -> Unbound l -> Bool
== :: Unbound l -> Unbound l -> Bool
$c/= :: forall l. Unbound l -> Unbound l -> Bool
/= :: Unbound l -> Unbound l -> Bool
Eq, Int -> Unbound l -> ShowS
[Unbound l] -> ShowS
Unbound l -> String
(Int -> Unbound l -> ShowS)
-> (Unbound l -> String)
-> ([Unbound l] -> ShowS)
-> Show (Unbound l)
forall l. Int -> Unbound l -> ShowS
forall l. [Unbound l] -> ShowS
forall l. Unbound l -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall l. Int -> Unbound l -> ShowS
showsPrec :: Int -> Unbound l -> ShowS
$cshow :: forall l. Unbound l -> String
show :: Unbound l -> String
$cshowList :: forall l. [Unbound l] -> ShowS
showList :: [Unbound l] -> ShowS
Show)
instance Semigroup (Unbound l) where
Unbound l
a <> :: Unbound l -> Unbound l -> Unbound l
<> Unbound l
b = Unbound{types :: [QualifiedName l]
types= Unbound l -> [QualifiedName l]
forall l. Unbound l -> [QualifiedName l]
types Unbound l
a [QualifiedName l] -> [QualifiedName l] -> [QualifiedName l]
forall a. Semigroup a => a -> a -> a
<> Unbound l -> [QualifiedName l]
forall l. Unbound l -> [QualifiedName l]
types Unbound l
b,
values :: [QualifiedName l]
values= Unbound l -> [QualifiedName l]
forall l. Unbound l -> [QualifiedName l]
values Unbound l
a [QualifiedName l] -> [QualifiedName l] -> [QualifiedName l]
forall a. Semigroup a => a -> a -> a
<> Unbound l -> [QualifiedName l]
forall l. Unbound l -> [QualifiedName l]
values Unbound l
b,
constructors :: [QualifiedName l]
constructors= Unbound l -> [QualifiedName l]
forall l. Unbound l -> [QualifiedName l]
constructors Unbound l
a [QualifiedName l] -> [QualifiedName l] -> [QualifiedName l]
forall a. Semigroup a => a -> a -> a
<> Unbound l -> [QualifiedName l]
forall l. Unbound l -> [QualifiedName l]
constructors Unbound l
b}
instance Monoid (Unbound l) where
mempty :: Unbound l
mempty = [QualifiedName l]
-> [QualifiedName l] -> [QualifiedName l] -> Unbound l
forall l.
[QualifiedName l]
-> [QualifiedName l] -> [QualifiedName l] -> Unbound l
Unbound [QualifiedName l]
forall a. Monoid a => a
mempty [QualifiedName l]
forall a. Monoid a => a
mempty [QualifiedName l]
forall a. Monoid a => a
mempty
unboundNames :: Full.Foldable (BindingVerifier l p) g
=> WithEnvironment l p (g (WithEnvironment l p) (WithEnvironment l p)) -> Unbound l
unboundNames :: forall l (p :: * -> *) (g :: (* -> *) -> (* -> *) -> *).
Foldable (BindingVerifier l p) g =>
WithEnvironment l p (g (WithEnvironment l p) (WithEnvironment l p))
-> Unbound l
unboundNames = BindingVerifier l p
-> Domain
(BindingVerifier l p)
(g (Domain (BindingVerifier l p)) (Domain (BindingVerifier l p)))
-> Unbound l
forall m.
(Codomain (BindingVerifier l p) ~ Const m, Monoid m) =>
BindingVerifier l p
-> Domain
(BindingVerifier l p)
(g (Domain (BindingVerifier l p)) (Domain (BindingVerifier l p)))
-> m
forall t (g :: (* -> *) -> (* -> *) -> *) m.
(Foldable t g, Codomain t ~ Const m, Monoid m) =>
t -> Domain t (g (Domain t) (Domain t)) -> m
Full.foldMap BindingVerifier l p
forall l (f :: * -> *). BindingVerifier l f
BindingVerifier
lookupType :: AST.QualifiedName l -> Environment l -> Maybe (TypeBinding l)
lookupType :: forall l. QualifiedName l -> Environment l -> Maybe (TypeBinding l)
lookupType QualifiedName l
name (UnionWith Map (QualifiedName l) (Binding l)
env) = QualifiedName l
-> Map (QualifiedName l) (Binding l) -> Maybe (Binding l)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup QualifiedName l
name Map (QualifiedName l) (Binding l)
env Maybe (Binding l)
-> (Binding l -> Maybe (TypeBinding l)) -> Maybe (TypeBinding l)
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
TypeBinding TypeBinding l
t -> TypeBinding l -> Maybe (TypeBinding l)
forall a. a -> Maybe a
Just TypeBinding l
t
TypeAndValueBinding TypeBinding l
t ValueBinding l
_ -> TypeBinding l -> Maybe (TypeBinding l)
forall a. a -> Maybe a
Just TypeBinding l
t
Binding l
_ -> Maybe (TypeBinding l)
forall a. Maybe a
Nothing
lookupValue :: AST.QualifiedName l -> Environment l -> Maybe (ValueBinding l)
lookupValue :: forall l.
QualifiedName l -> Environment l -> Maybe (ValueBinding l)
lookupValue QualifiedName l
name (UnionWith Map (QualifiedName l) (Binding l)
env) = QualifiedName l
-> Map (QualifiedName l) (Binding l) -> Maybe (Binding l)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup QualifiedName l
name Map (QualifiedName l) (Binding l)
env Maybe (Binding l)
-> (Binding l -> Maybe (ValueBinding l)) -> Maybe (ValueBinding l)
forall a b. Maybe a -> (a -> Maybe b) -> Maybe b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
ValueBinding ValueBinding l
v -> ValueBinding l -> Maybe (ValueBinding l)
forall a. a -> Maybe a
Just ValueBinding l
v
TypeAndValueBinding TypeBinding l
_ ValueBinding l
v -> ValueBinding l -> Maybe (ValueBinding l)
forall a. a -> Maybe a
Just ValueBinding l
v
Binding l
_ -> Maybe (ValueBinding l)
forall a. Maybe a
Nothing
deriving instance (Ord k, Data k, Data v) => Data (UnionWith (Map k) v)
deriving instance (Ord k, Eq v) => Eq (UnionWith (Map k) v)
deriving instance (Show k, Show v) => Show (UnionWith (Map k) v)
instance Semigroup (Binding l) where
ValueBinding ValueBinding l
v <> :: Binding l -> Binding l -> Binding l
<> TypeBinding TypeBinding l
t = TypeBinding l -> ValueBinding l -> Binding l
forall l. TypeBinding l -> ValueBinding l -> Binding l
TypeAndValueBinding TypeBinding l
t ValueBinding l
v
TypeBinding TypeBinding l
t <> ValueBinding ValueBinding l
v = TypeBinding l -> ValueBinding l -> Binding l
forall l. TypeBinding l -> ValueBinding l -> Binding l
TypeAndValueBinding TypeBinding l
t ValueBinding l
v
b :: Binding l
b@ErroneousBinding{} <> Binding l
_ = Binding l
b
Binding l
_ <> b :: Binding l
b@ErroneousBinding{} = Binding l
b
ValueBinding a :: ValueBinding l
a@InfixDeclaration{} <> ValueBinding b :: ValueBinding l
b@InfixDeclaration{} =
BindingError l -> Binding l
forall l. BindingError l -> Binding l
ErroneousBinding (ValueBinding l -> ValueBinding l -> BindingError l
forall l. ValueBinding l -> ValueBinding l -> BindingError l
DuplicateInfixDeclaration ValueBinding l
a ValueBinding l
b)
ValueBinding (InfixDeclaration Associativity l
assoc Int
fixity Maybe (ValueBinding l)
Nothing) <> ValueBinding ValueBinding l
b =
ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
forall l.
Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
InfixDeclaration Associativity l
assoc Int
fixity (Maybe (ValueBinding l) -> ValueBinding l)
-> Maybe (ValueBinding l) -> ValueBinding l
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Maybe (ValueBinding l)
forall a. a -> Maybe a
Just ValueBinding l
b)
ValueBinding (InfixDeclaration Associativity l
assoc Int
fixity (Just ValueBinding l
b1)) <> ValueBinding ValueBinding l
b2 =
ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
forall l.
Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
InfixDeclaration Associativity l
assoc Int
fixity Maybe (ValueBinding l)
forall a. Maybe a
Nothing) Binding l -> Binding l -> Binding l
forall a. Semigroup a => a -> a -> a
<> (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
b1 Binding l -> Binding l -> Binding l
forall a. Semigroup a => a -> a -> a
<> ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
b2)
ValueBinding ValueBinding l
b <> ValueBinding (InfixDeclaration Associativity l
assoc Int
fixity Maybe (ValueBinding l)
Nothing) =
ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
forall l.
Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
InfixDeclaration Associativity l
assoc Int
fixity (Maybe (ValueBinding l) -> ValueBinding l)
-> Maybe (ValueBinding l) -> ValueBinding l
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Maybe (ValueBinding l)
forall a. a -> Maybe a
Just ValueBinding l
b)
ValueBinding ValueBinding l
b1 <> ValueBinding (InfixDeclaration Associativity l
assoc Int
fixity (Just ValueBinding l
b2)) =
(ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
b1 Binding l -> Binding l -> Binding l
forall a. Semigroup a => a -> a -> a
<> ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
b2) Binding l -> Binding l -> Binding l
forall a. Semigroup a => a -> a -> a
<> ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
forall l.
Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
InfixDeclaration Associativity l
assoc Int
fixity Maybe (ValueBinding l)
forall a. Maybe a
Nothing)
ValueBinding ValueBinding l
RecordField <> ValueBinding ValueBinding l
RecordField = BindingError l -> Binding l
forall l. BindingError l -> Binding l
ErroneousBinding BindingError l
forall l. BindingError l
DuplicateRecordField
ValueBinding ValueBinding l
RecordField <> ValueBinding ValueBinding l
DefinedValue = ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
RecordFieldAndValue
ValueBinding ValueBinding l
DefinedValue <> ValueBinding ValueBinding l
RecordField = ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
RecordFieldAndValue
Binding l
a <> Binding l
b
| Binding l
a Binding l -> Binding l -> Bool
forall a. Eq a => a -> a -> Bool
== Binding l
b = Binding l
a
| Bool
otherwise = BindingError l -> Binding l
forall l. BindingError l -> Binding l
ErroneousBinding (Binding l -> Binding l -> BindingError l
forall l. Binding l -> Binding l -> BindingError l
ClashingBindings Binding l
a Binding l
b)
instance Monoid (Binding l) where
mempty :: Binding l
mempty = BindingError l -> Binding l
forall l. BindingError l -> Binding l
ErroneousBinding BindingError l
forall l. BindingError l
NoBindings
withBindings :: (Full.Traversable (Di.Keep (Binder l p)) g, q ~ WithEnvironment l p)
=> Map Extension Bool -> ModuleEnvironment l -> Environment l -> p (g p p) -> q (g q q)
withBindings :: forall l (p :: * -> *) (g :: (* -> *) -> (* -> *) -> *)
(q :: * -> *).
(Traversable (Keep (Binder l p)) g, q ~ WithEnvironment l p) =>
Map Extension Bool
-> ModuleEnvironment l -> Environment l -> p (g p p) -> q (g q q)
withBindings Map Extension Bool
extensions ModuleEnvironment l
modEnv = (p (g p p) -> Environment l -> q (g q q))
-> Environment l -> p (g p p) -> q (g q q)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Keep (Binder l p)
-> Domain
(Keep (Binder l p))
(g (Domain (Keep (Binder l p))) (Domain (Keep (Binder l p))))
-> Environment l
-> WithEnvironment
l p (g (WithEnvironment l p) (WithEnvironment l p))
forall t (g :: (* -> *) -> (* -> *) -> *) (m :: * -> *)
(f :: * -> *).
(Traversable t g, Codomain t ~ Compose m f) =>
t -> Domain t (g (Domain t) (Domain t)) -> m (f (g f f))
forall (m :: * -> *) (f :: * -> *).
(Codomain (Keep (Binder l p)) ~ Compose m f) =>
Keep (Binder l p)
-> Domain
(Keep (Binder l p))
(g (Domain (Keep (Binder l p))) (Domain (Keep (Binder l p))))
-> m (f (g f f))
Full.traverse (Binder l p -> Keep (Binder l p)
forall t. t -> Keep t
Di.Keep (Binder l p -> Keep (Binder l p))
-> Binder l p -> Keep (Binder l p)
forall a b. (a -> b) -> a -> b
$ Map Extension Bool -> ModuleEnvironment l -> Binder l p
forall l (f :: * -> *).
Map Extension Bool -> ModuleEnvironment l -> Binder l f
Binder Map Extension Bool
extensions ModuleEnvironment l
modEnv))
onMap :: (Map.Map j a -> Map.Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap :: forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap Map j a -> Map k b
f (UnionWith Map j a
x) = Map k b -> UnionWith (Map k) b
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map j a -> Map k b
f Map j a
x)
data Binder l (f :: Type -> Type) = Binder {
forall l (f :: * -> *). Binder l f -> Map Extension Bool
extensions :: Map Extension Bool,
forall l (f :: * -> *). Binder l f -> ModuleEnvironment l
modules :: ModuleEnvironment l}
data BindingVerifier l (f :: Type -> Type) = BindingVerifier
instance Transformation (Di.Keep (Binder l f)) where
type Domain (Di.Keep (Binder l f)) = f
type Codomain (Di.Keep (Binder l f)) = FromEnvironment l f
instance Transformation (BindingVerifier l f) where
type Domain (BindingVerifier l f) = WithEnvironment l f
type Codomain (BindingVerifier l f) = Const (Unbound l)
instance {-# OVERLAPS #-}
(Abstract.Haskell l, Abstract.TypeLHS l ~ ExtAST.TypeLHS l, Abstract.EquationLHS l ~ AST.EquationLHS l,
Abstract.Pattern l ~ ExtAST.Pattern l, Abstract.FieldPattern l ~ ExtAST.FieldPattern l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(AST.Declaration l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))
node Attributes l
atts = Attributes l
atts{Di.syn= foldMap export node, Di.inh= bequest}
where bequeath :: AST.Declaration l l (FromEnvironment l f) (FromEnvironment l f) -> Environment l
export :: AST.Declaration l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: Declaration l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (AST.FixityDeclaration Associativity l
associativity Maybe Int
precedence NonEmpty (Name l)
names) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith ([(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Name l
name,
ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (ValueBinding l -> Binding l) -> ValueBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
forall l.
Associativity l -> Int -> Maybe (ValueBinding l) -> ValueBinding l
InfixDeclaration Associativity l
associativity (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
9 Maybe Int
precedence) Maybe (ValueBinding l)
forall a. Maybe a
Nothing)
| Name l
name <- NonEmpty (Name l) -> [Name l]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty (Name l)
NonEmpty (Name l)
names])
export (ExtAST.ClassDeclaration FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
_ FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs [FromEnvironment
l f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))]
decls)
| [Name l
name] <- (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l])
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> [Name l]
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
forall {l} {λ} {t :: * -> *} {t}.
(TypeLHS l ~ TypeLHS λ, Foldable t, Monoid t) =>
TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Environment l
forall a. Monoid a => a
mempty)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding (TypeBinding l -> Binding l) -> TypeBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> TypeBinding l
forall l. LocalEnvironment l -> TypeBinding l
TypeClass (LocalEnvironment l -> TypeBinding l)
-> LocalEnvironment l -> TypeBinding l
forall a b. (a -> b) -> a -> b
$ Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
export (ExtAST.InstanceDeclaration [TypeVarBinding l l (FromEnvironment l f) (FromEnvironment l f)]
_vars FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
_context FromEnvironment
l
f
(ClassInstanceLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs [FromEnvironment
l f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))]
decls) =
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((Binding l -> Maybe (Binding l))
-> Map (Name l) (Binding l) -> Map (Name l) (Binding l)
forall a b k. (a -> Maybe b) -> Map k a -> Map k b
Map.mapMaybe Binding l -> Maybe (Binding l)
forall {l}. Binding l -> Maybe (Binding l)
constructorOrField) (Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
where constructorOrField :: Binding l -> Maybe (Binding l)
constructorOrField b :: Binding l
b@(ValueBinding DataConstructor{}) = Binding l -> Maybe (Binding l)
forall a. a -> Maybe a
Just Binding l
b
constructorOrField b :: Binding l
b@(ValueBinding RecordConstructor{}) = Binding l -> Maybe (Binding l)
forall a. a -> Maybe a
Just Binding l
b
constructorOrField b :: Binding l
b@(ValueBinding RecordField{}) = Binding l -> Maybe (Binding l)
forall a. a -> Maybe a
Just Binding l
b
constructorOrField b :: Binding l
b@(ValueBinding RecordFieldAndValue{}) =
Binding l -> Maybe (Binding l)
forall a. a -> Maybe a
Just (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
RecordFieldAndValue)
constructorOrField (TypeAndValueBinding TypeBinding l
_ ValueBinding l
v) = Binding l -> Maybe (Binding l)
constructorOrField (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
v)
constructorOrField Binding l
_ = Maybe (Binding l)
forall a. Maybe a
Nothing
export (AST.EquationDeclaration FromEnvironment
l f (EquationLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs FromEnvironment
l f (EquationRHS l l (FromEnvironment l f) (FromEnvironment l f))
_ [FromEnvironment
l f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))]
_) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith
(Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList
([(Name l, Binding l)] -> Map (Name l) (Binding l))
-> [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ ((,) (Name l -> Binding l -> (Name l, Binding l))
-> Binding l -> Name l -> (Name l, Binding l)
forall a b c. (a -> b -> c) -> b -> a -> c
`flip` ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DefinedValue) (Name l -> (Name l, Binding l))
-> [Name l] -> [(Name l, Binding l)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (EquationLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l])
-> Compose
((,) (Attributes l))
f
(EquationLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> [Name l]
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap EquationLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l]
EquationLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l]
forall {l} {λ} {λ} {t :: * -> *} {t}.
(Pattern l ~ Pattern λ, FieldPattern l ~ FieldPattern λ,
EquationLHS l ~ EquationLHS λ, Foldable t, Monoid t) =>
EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ]
getBindingNames (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(EquationLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(EquationLHS l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose FromEnvironment
l f (EquationLHS l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(EquationLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Environment l
forall a. Monoid a => a
mempty)
export (AST.DataDeclaration FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
_context FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind [FromEnvironment
l
f
(DataConstructor l l (FromEnvironment l f) (FromEnvironment l f))]
_constructors [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings)
| [Name l
name] <- (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l])
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> [Name l]
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
forall {l} {λ} {t :: * -> *} {t}.
(TypeLHS l ~ TypeLHS λ, Foldable t, Monoid t) =>
TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Environment l
forall a. Monoid a => a
mempty)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding (TypeBinding l -> Binding l) -> TypeBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> TypeBinding l
forall l. LocalEnvironment l -> TypeBinding l
DataType (LocalEnvironment l -> TypeBinding l)
-> LocalEnvironment l -> TypeBinding l
forall a b. (a -> b) -> a -> b
$ Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
export (AST.NewtypeDeclaration FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
_context FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind FromEnvironment
l
f
(DataConstructor l l (FromEnvironment l f) (FromEnvironment l f))
_constructor [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings)
| [Name l
name] <- (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l])
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> [Name l]
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
forall {l} {λ} {t :: * -> *} {t}.
(TypeLHS l ~ TypeLHS λ, Foldable t, Monoid t) =>
TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Environment l
forall a. Monoid a => a
mempty)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding (TypeBinding l -> Binding l) -> TypeBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> TypeBinding l
forall l. LocalEnvironment l -> TypeBinding l
DataType (LocalEnvironment l -> TypeBinding l)
-> LocalEnvironment l -> TypeBinding l
forall a b. (a -> b) -> a -> b
$ Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
export (AST.GADTDeclaration FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind [FromEnvironment
l
f
(GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f))]
_constructors [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings)
| [Name l
name] <- (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l])
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> [Name l]
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
forall {l} {λ} {t :: * -> *} {t}.
(TypeLHS l ~ TypeLHS λ, Foldable t, Monoid t) =>
TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Environment l
forall a. Monoid a => a
mempty)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding (TypeBinding l -> Binding l) -> TypeBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> TypeBinding l
forall l. LocalEnvironment l -> TypeBinding l
DataType (LocalEnvironment l -> TypeBinding l)
-> LocalEnvironment l -> TypeBinding l
forall a b. (a -> b) -> a -> b
$ Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
export (AST.GADTNewtypeDeclaration FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind FromEnvironment
l
f
(GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f))
_constructor [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings)
| [Name l
name] <- (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> [Name l])
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> [Name l]
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
TypeLHS l l (FromEnvironment l f) (FromEnvironment l f) -> [Name l]
forall {l} {λ} {t :: * -> *} {t}.
(TypeLHS l ~ TypeLHS λ, Foldable t, Monoid t) =>
TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose FromEnvironment
l f (TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(TypeLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Environment l
forall a. Monoid a => a
mempty)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding (TypeBinding l -> Binding l) -> TypeBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> TypeBinding l
forall l. LocalEnvironment l -> TypeBinding l
DataType (LocalEnvironment l -> TypeBinding l)
-> LocalEnvironment l -> TypeBinding l
forall a b. (a -> b) -> a -> b
$ Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
export (AST.DataFamilyInstance [TypeVarBinding l l (FromEnvironment l f) (FromEnvironment l f)]
_vars FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
context FromEnvironment
l
f
(ClassInstanceLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind [FromEnvironment
l
f
(DataConstructor l l (FromEnvironment l f) (FromEnvironment l f))]
_constructors [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings) = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export (AST.NewtypeFamilyInstance [TypeVarBinding l l (FromEnvironment l f) (FromEnvironment l f)]
_vars FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
context FromEnvironment
l
f
(ClassInstanceLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind FromEnvironment
l
f
(DataConstructor l l (FromEnvironment l f) (FromEnvironment l f))
_constructors [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings) = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export (AST.GADTDataFamilyInstance [TypeVarBinding l l (FromEnvironment l f) (FromEnvironment l f)]
_vars FromEnvironment
l
f
(ClassInstanceLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind [FromEnvironment
l
f
(GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f))]
_constructors [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings) = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export (AST.GADTNewtypeFamilyInstance [TypeVarBinding l l (FromEnvironment l f) (FromEnvironment l f)]
_vars FromEnvironment
l
f
(ClassInstanceLHS l l (FromEnvironment l f) (FromEnvironment l f))
lhs Maybe
(FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f)))
_kind FromEnvironment
l
f
(GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f))
_constructors [FromEnvironment
l
f
(DerivingClause l l (FromEnvironment l f) (FromEnvironment l f))]
_derivings) = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export (AST.TypeSignature NonEmpty (Name l)
names FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
_context FromEnvironment
l f (Type l l (FromEnvironment l f) (FromEnvironment l f))
_type)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith ([(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Name l, Binding l)] -> Map (Name l) (Binding l))
-> [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ (Name l -> Binding l -> (Name l, Binding l))
-> Binding l -> Name l -> (Name l, Binding l)
forall a b c. (a -> b -> c) -> b -> a -> c
flip (,) (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DefinedValue) (Name l -> (Name l, Binding l))
-> [Name l] -> [(Name l, Binding l)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> NonEmpty (Name l) -> [Name l]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty (Name l)
NonEmpty (Name l)
names)
export (AST.KindSignature Name l
name FromEnvironment
l f (Kind l l (FromEnvironment l f) (FromEnvironment l f))
_type)
= Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding TypeBinding l
forall l. TypeBinding l
UnknownType)
export ExtAST.ImplicitPatternSynonym{} = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export ExtAST.ExplicitPatternSynonym{} = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export ExtAST.UnidirectionalPatternSynonym{} = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
export Declaration l l (FromEnvironment l f) (FromEnvironment l f)
_ = LocalEnvironment l
forall a. Monoid a => a
mempty
getBindingNames :: EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ]
getBindingNames (AST.InfixLHS Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
_ Name λ
name Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
_) = [Name λ
name]
getBindingNames (AST.PrefixLHS Compose
((->) t)
t
(EquationLHS l l (Compose ((->) t) t) (Compose ((->) t) t))
lhs NonEmpty
(Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t)))
_) = (EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ])
-> t (EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ]
getBindingNames (Compose
((->) t)
t
(EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t
-> t (EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t)
t
(EquationLHS l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t)
t
(EquationLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
lhs t
forall a. Monoid a => a
mempty)
getBindingNames (AST.VariableLHS Name λ
name) = [Name λ
name]
getBindingNames (AST.PatternLHS Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p) = (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
forall {l} {λ} {λ} {t :: * -> *} {t}.
(FieldPattern l ~ FieldPattern λ, Pattern l ~ Pattern λ,
Foldable t, Monoid t) =>
Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getPatternVariables :: Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (ExtAST.AsPattern Name λ
name Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p) = Name λ
name Name λ -> [Name λ] -> [Name λ]
forall a. a -> [a] -> [a]
: (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getPatternVariables (ExtAST.ConstructorPattern Compose
((->) t)
t
(Constructor l l (Compose ((->) t) t) (Compose ((->) t) t))
_ [Compose
((->) t) t (Type l l (Compose ((->) t) t) (Compose ((->) t) t))]
_ [Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
args) =
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> [Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
-> [Name λ]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> t
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall a b c. (a -> b -> c) -> b -> a -> c
flip Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose t
forall a. Monoid a => a
mempty) [Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
[Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
args
getPatternVariables (ExtAST.InfixPattern Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
left QualifiedName λ
_ Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
right) =
(Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
left t
forall a. Monoid a => a
mempty)
[Name λ] -> [Name λ] -> [Name λ]
forall a. Semigroup a => a -> a -> a
<> (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
right t
forall a. Monoid a => a
mempty)
getPatternVariables (ExtAST.IrrefutablePattern Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p) = (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getPatternVariables (ExtAST.ListPattern [Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
items) =
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> [Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
-> [Name λ]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> t
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall a b c. (a -> b -> c) -> b -> a -> c
flip Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose t
forall a. Monoid a => a
mempty) [Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
[Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
items
getPatternVariables ExtAST.LiteralPattern{} = []
getPatternVariables (ExtAST.RecordPattern QualifiedName λ
_ [Compose
((->) t)
t
(FieldPattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
fields) =
(Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> [Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
-> [Name λ]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ])
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ]
getFieldPatternVariables (t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> (Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> t
-> Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall a b c. (a -> b -> c) -> b -> a -> c
flip Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose t
forall a. Monoid a => a
mempty) [Compose
((->) t)
t
(FieldPattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
[Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
fields
getPatternVariables (ExtAST.WildcardRecordPattern SupportFor 'RecordWildCards λ
_ QualifiedName λ
_ [Compose
((->) t)
t
(FieldPattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
fields) =
(Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> [Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
-> [Name λ]
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ])
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ]
getFieldPatternVariables (t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> (Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> t
-> Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall a b c. (a -> b -> c) -> b -> a -> c
flip Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t
-> t (FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose t
forall a. Monoid a => a
mempty) [Compose
((->) t)
t
(FieldPattern l l (Compose ((->) t) t) (Compose ((->) t) t))]
[Compose
((->) t)
t
(FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t))]
fields
getPatternVariables (ExtAST.TypedPattern Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p Compose
((->) t) t (Type l l (Compose ((->) t) t) (Compose ((->) t) t))
_) = (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getPatternVariables (ExtAST.InvisibleTypePattern SupportFor 'TypeAbstractions λ
_ Compose
((->) t) t (Type l l (Compose ((->) t) t) (Compose ((->) t) t))
_ty) = []
getPatternVariables (ExtAST.ExplicitTypePattern SupportFor 'ExplicitNamespaces λ
_ Compose
((->) t) t (Type l l (Compose ((->) t) t) (Compose ((->) t) t))
_ty) = []
getPatternVariables (ExtAST.BangPattern SupportFor 'BangPatterns λ
_ Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p) = (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getPatternVariables (ExtAST.TuplePattern NonEmpty
(Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t)))
items) =
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> NonEmpty
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> t
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall a b c. (a -> b -> c) -> b -> a -> c
flip Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose t
forall a. Monoid a => a
mempty) NonEmpty
(Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t)))
NonEmpty
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
items
getPatternVariables (ExtAST.UnboxedTuplePattern SupportFor 'UnboxedTuples λ
_ NonEmpty
(Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t)))
items) =
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> NonEmpty
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> NonEmpty a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ])
-> (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
-> t
-> Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall a b c. (a -> b -> c) -> b -> a -> c
flip Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose t
forall a. Monoid a => a
mempty) NonEmpty
(Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t)))
NonEmpty
(Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)))
items
getPatternVariables (ExtAST.VariablePattern Name λ
name) = [Name λ
name]
getPatternVariables (ExtAST.ViewPattern SupportFor 'ViewPatterns λ
_ Compose
((->) t)
t
(Expression l l (Compose ((->) t) t) (Compose ((->) t) t))
view Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p) = (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getPatternVariables (ExtAST.NPlusKPattern SupportFor 'NPlusKPatterns λ
_ Name λ
n Integer
_) = [Name λ
n]
getPatternVariables Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t)
ExtAST.WildcardPattern = []
getFieldPatternVariables :: FieldPattern λ l (Compose ((->) t) t) (Compose ((->) t) t)
-> [Name λ]
getFieldPatternVariables (ExtAST.FieldPattern QualifiedName λ
_ Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
p) = (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getPatternVariables (Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (Pattern l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (Pattern λ l (Compose ((->) t) t) (Compose ((->) t) t))
p t
forall a. Monoid a => a
mempty)
getFieldPatternVariables ExtAST.PunnedFieldPattern{} = []
getTypeName :: TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (ExtAST.SimpleTypeLHS Name λ
name [TypeVarBinding λ l (Compose ((->) t) t) (Compose ((->) t) t)]
_) = [Name λ
name]
getTypeName (ExtAST.TypeLHSApplication Compose
((->) t) t (TypeLHS l l (Compose ((->) t) t) (Compose ((->) t) t))
lhs TypeVarBinding λ l (Compose ((->) t) t) (Compose ((->) t) t)
_) = (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) t) t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (TypeLHS l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
lhs t
forall a. Monoid a => a
mempty)
getTypeName (ExtAST.TypeLHSTypeApplication SupportFor 'TypeAbstractions λ
_support Compose
((->) t) t (TypeLHS l l (Compose ((->) t) t) (Compose ((->) t) t))
lhs TypeVarBinding λ l (Compose ((->) t) t) (Compose ((->) t) t)
_) = (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ])
-> t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> [Name λ]
forall m a. Monoid m => (a -> m) -> t a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t) -> [Name λ]
getTypeName (Compose
((->) t) t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
-> t -> t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) t) t (TypeLHS l l (Compose ((->) t) t) (Compose ((->) t) t))
Compose
((->) t) t (TypeLHS λ l (Compose ((->) t) t) (Compose ((->) t) t))
lhs t
forall a. Monoid a => a
mempty)
bequeath :: Declaration l l (FromEnvironment l f) (FromEnvironment l f)
-> Environment l
bequeath AST.EquationDeclaration{} = UnionWith (Map (Name l)) (Binding l)
-> UnionWith (Map (QualifiedName l)) (Binding l)
forall l a.
Haskell l =>
UnionWith (Map (Name l)) a -> UnionWith (Map (QualifiedName l)) a
unqualified (Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts) Environment l -> Environment l -> Environment l
forall a. Semigroup a => a -> a -> a
<> Attributes l -> Environment l
forall a b. Atts a b -> a
Di.inh Attributes l
atts
bequeath Declaration l l (FromEnvironment l f) (FromEnvironment l f)
_ = Attributes l -> Environment l
forall a b. Atts a b -> a
Di.inh Attributes l
atts
bequest :: Environment l
bequest = (Declaration l l (FromEnvironment l f) (FromEnvironment l f)
-> Environment l)
-> f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Declaration l l (FromEnvironment l f) (FromEnvironment l f)
-> Environment l
bequeath f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))
node
instance {-# OVERLAPS #-}
(Abstract.Haskell l, Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Abstract.Module l l ~ AST.Module l l, Abstract.ModuleName l ~ AST.ModuleName l,
Abstract.Export l l ~ ExtAST.Export l l, Abstract.Import l l ~ ExtAST.Import l l,
Abstract.ImportSpecification l l ~ AST.ImportSpecification l l,
Abstract.ImportItem l l ~ ExtAST.ImportItem l l,
BindingMembers l,
Ord (Abstract.QualifiedName l), Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(AST.Module l l)
(FromEnvironment l f) f
where
attribution :: Keep (Binder l f)
-> f (Module l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution (Di.Keep (Binder Map Extension Bool
exts ModuleEnvironment l
modEnv)) f (Module l l (FromEnvironment l f) (FromEnvironment l f))
node Attributes l
atts = (Module l l (FromEnvironment l f) (FromEnvironment l f)
-> Attributes l)
-> f (Module l l (FromEnvironment l f) (FromEnvironment l f))
-> Attributes l
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Module l l (FromEnvironment l f) (FromEnvironment l f)
-> Attributes l
moduleAttribution f (Module l l (FromEnvironment l f) (FromEnvironment l f))
node
where moduleAttribution :: AST.Module l l (FromEnvironment l f) (FromEnvironment l f) -> Attributes l
moduleAttribution :: Module l l (FromEnvironment l f) (FromEnvironment l f)
-> Attributes l
moduleAttribution (AST.ExtendedModule [ExtensionSwitch]
modExts FromEnvironment
l f (Module l l (FromEnvironment l f) (FromEnvironment l f))
body) = Bool -> Rule (Environment l) (LocalEnvironment l)
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Set ExtensionSwitch -> Bool
forall a. Set a -> Bool
Set.null Set ExtensionSwitch
contradictions) Attributes l
atts''
where (Set ExtensionSwitch
contradictions, Map Extension Bool
extensionMap) = Set ExtensionSwitch -> (Set ExtensionSwitch, Map Extension Bool)
Extensions.partitionContradictory ([ExtensionSwitch] -> Set ExtensionSwitch
forall a. Ord a => [a] -> Set a
Set.fromList [ExtensionSwitch]
modExts)
exts' :: Map Extension Bool
exts' = Map Extension Bool -> Map Extension Bool
Extensions.withImplications (Map Extension Bool
extensionMap Map Extension Bool -> Map Extension Bool -> Map Extension Bool
forall a. Semigroup a => a -> a -> a
<> Map Extension Bool
exts)
atts' :: Attributes l
atts' = Keep (Binder l (ZonkAny 0))
-> Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(Module l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
forall t a b (g :: (* -> *) -> (* -> *) -> *) (deep :: * -> *)
(shallow :: * -> *).
Attribution t a b g deep shallow =>
t -> shallow (g deep deep) -> Rule a b
Di.attribution (Binder l (ZonkAny 0) -> Keep (Binder l (ZonkAny 0))
forall t. t -> Keep t
Di.Keep (Binder l (ZonkAny 0) -> Keep (Binder l (ZonkAny 0)))
-> Binder l (ZonkAny 0) -> Keep (Binder l (ZonkAny 0))
forall a b. (a -> b) -> a -> b
$ Map Extension Bool -> ModuleEnvironment l -> Binder l (ZonkAny 0)
forall l (f :: * -> *).
Map Extension Bool -> ModuleEnvironment l -> Binder l f
Binder Map Extension Bool
exts' ModuleEnvironment l
modEnv) FromEnvironment
l f (Module l l (FromEnvironment l f) (FromEnvironment l f))
Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(Module l l (FromEnvironment l f) (FromEnvironment l f))
body Attributes l
atts
atts'' :: Attributes l
atts'' = case Extension -> Map Extension Bool -> Maybe Bool
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Extension
Extensions.FieldSelectors Map Extension Bool
exts' of
Just Bool
False -> Attributes l
atts'{Di.syn = onMap (Map.mapMaybe noFieldSelector) (Di.syn atts')}
Maybe Bool
_ -> Attributes l
atts'
noFieldSelector :: Binding l -> Maybe (Binding l)
noFieldSelector (ValueBinding ValueBinding l
RecordField) = Maybe (Binding l)
forall a. Maybe a
Nothing
noFieldSelector (ValueBinding ValueBinding l
RecordFieldAndValue) = Binding l -> Maybe (Binding l)
forall a. a -> Maybe a
Just (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DefinedValue)
noFieldSelector Binding l
x = Binding l -> Maybe (Binding l)
forall a. a -> Maybe a
Just Binding l
x
moduleAttribution (AST.AnonymousModule [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports [FromEnvironment
l f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))]
body) =
Di.Atts{
inh :: Environment l
Di.inh= Environment l
moduleGlobalScope,
syn :: LocalEnvironment l
Di.syn= (QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv (QualifiedName l -> QualifiedName l -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName l
mainName) Environment l
moduleGlobalScope}
where moduleGlobalScope :: Environment l
moduleGlobalScope = [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> Environment l
importedScope [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
[FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports Environment l -> Environment l -> Environment l
forall a. Semigroup a => a -> a -> a
<> UnionWith (Map (Name l)) (Binding l)
-> UnionWith (Map (QualifiedName l)) (Binding l)
forall l a.
Haskell l =>
UnionWith (Map (Name l)) a -> UnionWith (Map (QualifiedName l)) a
unqualified (Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
mainName :: QualifiedName l
mainName = Maybe (ModuleName l) -> Name l -> QualifiedName l
forall λ.
Haskell λ =>
Maybe (ModuleName λ) -> Name λ -> QualifiedName λ
Abstract.qualifiedName Maybe (ModuleName l)
forall a. Maybe a
Nothing (Text -> Name l
forall λ. Haskell λ => Text -> Name λ
Abstract.name Text
"main")
moduleAttribution (AST.NamedModule ModuleName l
moduleName Maybe
[FromEnvironment
l f (Export l l (FromEnvironment l f) (FromEnvironment l f))]
exports [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports [FromEnvironment
l f (Declaration l l (FromEnvironment l f) (FromEnvironment l f))]
body) =
Attributes l
atts{Di.syn= exportedScope, Di.inh= moduleGlobalScope}
where exportedScope :: LocalEnvironment l
moduleGlobalScope :: Environment l
exportedScope :: LocalEnvironment l
exportedScope = LocalEnvironment l
-> ([Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(Export l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l)
-> Maybe
[Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(Export l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (ModuleName l -> LocalEnvironment l
reexportModule ModuleName l
ModuleName l
moduleName) ((Export l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l)
-> [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(Export l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l
forall a (g :: * -> *) m.
(Foldable g, Monoid m) =>
(a -> m)
-> g (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a)
-> m
foldMapWrapped Export l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
itemExports) Maybe
[FromEnvironment
l f (Export l l (FromEnvironment l f) (FromEnvironment l f))]
Maybe
[Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(Export l l (FromEnvironment l f) (FromEnvironment l f))]
exports
reexportModule :: ModuleName l -> LocalEnvironment l
reexportModule ModuleName l
modName
| ModuleName l
modName ModuleName l -> ModuleName l -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName l
ModuleName l
moduleName = Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts
| Bool
otherwise = (Map (QualifiedName l) (Binding l) -> Map (Name l) (Binding l))
-> Environment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((QualifiedName l -> Name l)
-> Map (QualifiedName l) (Binding l) -> Map (Name l) (Binding l)
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys QualifiedName l -> Name l
forall l. QualifiedName l -> Name l
baseName) (Environment l -> LocalEnvironment l)
-> Environment l -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> ModuleName l -> LocalEnvironment l -> Environment l
importsFrom [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
[FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports ModuleName l
ModuleName l
modName (Maybe (LocalEnvironment l) -> LocalEnvironment l
forall m. Monoid m => Maybe m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold (Maybe (LocalEnvironment l) -> LocalEnvironment l)
-> Maybe (LocalEnvironment l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ ModuleName l
-> Map (ModuleName l) (LocalEnvironment l)
-> Maybe (LocalEnvironment l)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup ModuleName l
modName (Map (ModuleName l) (LocalEnvironment l)
-> Maybe (LocalEnvironment l))
-> Map (ModuleName l) (LocalEnvironment l)
-> Maybe (LocalEnvironment l)
forall a b. (a -> b) -> a -> b
$ ModuleEnvironment l -> Map (ModuleName l) (LocalEnvironment l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith ModuleEnvironment l
modEnv)
fromModule :: ModuleName λ -> QualifiedName λ -> Bool
fromModule ModuleName λ
modName (AST.QualifiedName Maybe (ModuleName λ)
modName' Name λ
_) = Maybe (ModuleName λ)
modName' Maybe (ModuleName λ) -> Maybe (ModuleName λ) -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName λ -> Maybe (ModuleName λ)
forall a. a -> Maybe a
Just ModuleName λ
modName
itemExports :: ExtAST.Export l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
itemExports :: Export l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
itemExports (ExtAST.ReExportModule ModuleName l
modName) = ModuleName l -> LocalEnvironment l
reexportModule ModuleName l
ModuleName l
modName
itemExports (ExtAST.ExportVar QualifiedName l
qn) = (QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv (QualifiedName l -> QualifiedName l -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName l
qn) Environment l
moduleGlobalScope
itemExports (ExtAST.ExportPattern QualifiedName l
qn) = (QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv (QualifiedName l -> QualifiedName l -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName l
qn) Environment l
moduleGlobalScope
itemExports (ExtAST.ExportClassOrType QualifiedName l
qn Maybe (Members l)
Nothing) = (QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv (QualifiedName l -> QualifiedName l -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName l
qn) Environment l
moduleGlobalScope
itemExports (ExtAST.ExportClassOrType QualifiedName l
parent (Just Members l
members)) =
case QualifiedName l
-> Map (QualifiedName l) (Binding l) -> Maybe (Binding l)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup QualifiedName l
QualifiedName l
parent (Environment l -> Map (QualifiedName l) (Binding l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith Environment l
moduleGlobalScope)
of Just b :: Binding l
b@(TypeBinding (TypeClass LocalEnvironment l
env)) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (QualifiedName l -> Name l
forall l. QualifiedName l -> Name l
baseName QualifiedName l
QualifiedName l
parent) Binding l
b) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Just (TypeAndValueBinding b :: TypeBinding l
b@(TypeClass LocalEnvironment l
env) ValueBinding l
_) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (QualifiedName l -> Name l
forall l. QualifiedName l -> Name l
baseName QualifiedName l
QualifiedName l
parent) (TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding TypeBinding l
b)) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Just b :: Binding l
b@(TypeBinding (DataType LocalEnvironment l
env)) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (QualifiedName l -> Name l
forall l. QualifiedName l -> Name l
baseName QualifiedName l
QualifiedName l
parent) Binding l
b) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Just (TypeAndValueBinding b :: TypeBinding l
b@(DataType LocalEnvironment l
env) ValueBinding l
_) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert (QualifiedName l -> Name l
forall l. QualifiedName l -> Name l
baseName QualifiedName l
QualifiedName l
parent) (TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding TypeBinding l
b)) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Maybe (Binding l)
_ -> (QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv (QualifiedName l -> QualifiedName l -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName l
parent) Environment l
moduleGlobalScope
moduleGlobalScope :: Environment l
moduleGlobalScope = [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> Environment l
importedScope [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
[FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports
Environment l -> Environment l -> Environment l
forall a. Semigroup a => a -> a -> a
<> ModuleName l -> LocalEnvironment l -> Environment l
forall l a.
ModuleName l
-> UnionWith (Map (Name l)) a
-> UnionWith (Map (QualifiedName l)) a
qualifiedWith ModuleName l
ModuleName l
moduleName (Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
Environment l -> Environment l -> Environment l
forall a. Semigroup a => a -> a -> a
<> UnionWith (Map (Name l)) (Binding l)
-> UnionWith (Map (QualifiedName l)) (Binding l)
forall l a.
Haskell l =>
UnionWith (Map (Name l)) a -> UnionWith (Map (QualifiedName l)) a
unqualified (Attributes l -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Attributes l
atts)
importedScope :: [FromEnvironment l f (ExtAST.Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> Environment l
importedScope :: [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> Environment l
importedScope [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports = Map (ModuleName l) (Environment l) -> Environment l
forall m. Monoid m => Map (ModuleName l) m -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
fold ((ModuleName l -> LocalEnvironment l -> Environment l)
-> Map (ModuleName l) (LocalEnvironment l)
-> Map (ModuleName l) (Environment l)
forall k a b. (k -> a -> b) -> Map k a -> Map k b
Map.mapWithKey ([FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> ModuleName l -> LocalEnvironment l -> Environment l
importsFrom [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports) (Map (ModuleName l) (LocalEnvironment l)
-> Map (ModuleName l) (Environment l))
-> Map (ModuleName l) (LocalEnvironment l)
-> Map (ModuleName l) (Environment l)
forall a b. (a -> b) -> a -> b
$ ModuleEnvironment l -> Map (ModuleName l) (LocalEnvironment l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith ModuleEnvironment l
modEnv)
importsFrom :: [FromEnvironment l f (ExtAST.Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> Abstract.ModuleName l
-> UnionWith (Map (AST.Name l)) (Binding l)
-> Environment l
importsFrom :: [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> ModuleName l -> LocalEnvironment l -> Environment l
importsFrom [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports ModuleName l
moduleName LocalEnvironment l
moduleExports
| [Import l l (FromEnvironment l f) (FromEnvironment l f)] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Import l l (FromEnvironment l f) (FromEnvironment l f)]
matchingImports Bool -> Bool -> Bool
&& ModuleName l
ModuleName l
moduleName ModuleName l -> ModuleName l -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName l
ModuleName l
forall l. Haskell l => ModuleName l
preludeName = UnionWith (Map (Name l)) (Binding l)
-> UnionWith (Map (QualifiedName l)) (Binding l)
forall l a.
Haskell l =>
UnionWith (Map (Name l)) a -> UnionWith (Map (QualifiedName l)) a
unqualified UnionWith (Map (Name l)) (Binding l)
LocalEnvironment l
moduleExports
| Bool
otherwise = (Import l l (FromEnvironment l f) (FromEnvironment l f)
-> Environment l)
-> [Import l l (FromEnvironment l f) (FromEnvironment l f)]
-> Environment l
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (LocalEnvironment l
-> Import l l (FromEnvironment l f) (FromEnvironment l f)
-> Environment l
importsFromModule LocalEnvironment l
moduleExports) [Import l l (FromEnvironment l f) (FromEnvironment l f)]
matchingImports
where matchingImports :: [Import l l (FromEnvironment l f) (FromEnvironment l f)]
matchingImports = (Import l l (FromEnvironment l f) (FromEnvironment l f)
-> [Import l l (FromEnvironment l f) (FromEnvironment l f)])
-> [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
-> [Import l l (FromEnvironment l f) (FromEnvironment l f)]
forall a (g :: * -> *) m.
(Foldable g, Monoid m) =>
(a -> m)
-> g (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a)
-> m
foldMapWrapped Import l l (FromEnvironment l f) (FromEnvironment l f)
-> [Import l l (FromEnvironment l f) (FromEnvironment l f)]
matchingImport [FromEnvironment
l f (Import l l (FromEnvironment l f) (FromEnvironment l f))]
modImports
matchingImport :: Import l l (FromEnvironment l f) (FromEnvironment l f)
-> [Import l l (FromEnvironment l f) (FromEnvironment l f)]
matchingImport i :: Import l l (FromEnvironment l f) (FromEnvironment l f)
i@(ExtAST.Import Bool
_ Bool
_ Maybe Text
_ ModuleName l
name Maybe (ModuleName l)
_ Maybe
(FromEnvironment
l
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
_)
| ModuleName l
ModuleName l
name ModuleName l -> ModuleName l -> Bool
forall a. Eq a => a -> a -> Bool
== ModuleName l
ModuleName l
moduleName = [Import l l (FromEnvironment l f) (FromEnvironment l f)
i]
| Bool
otherwise = []
importsFromModule :: UnionWith (Map (AST.Name l)) (Binding l)
-> ExtAST.Import l l (FromEnvironment l f) (FromEnvironment l f) -> Environment l
importsFromModule :: LocalEnvironment l
-> Import l l (FromEnvironment l f) (FromEnvironment l f)
-> Environment l
importsFromModule LocalEnvironment l
moduleExports (ExtAST.Import Bool
_ Bool
qualified Maybe Text
_ ModuleName l
name Maybe (ModuleName l)
alias Maybe
(FromEnvironment
l
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
spec)
| Bool
qualified = ModuleName l -> LocalEnvironment l -> Environment l
forall l a.
ModuleName l
-> UnionWith (Map (Name l)) a
-> UnionWith (Map (QualifiedName l)) a
qualifiedWith (ModuleName l -> Maybe (ModuleName l) -> ModuleName l
forall a. a -> Maybe a -> a
fromMaybe ModuleName l
ModuleName l
name Maybe (ModuleName l)
Maybe (ModuleName l)
alias) (Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
-> LocalEnvironment l
imports Maybe
(FromEnvironment
l
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
spec)
| Bool
otherwise = UnionWith (Map (Name l)) (Binding l)
-> UnionWith (Map (QualifiedName l)) (Binding l)
forall l a.
Haskell l =>
UnionWith (Map (Name l)) a -> UnionWith (Map (QualifiedName l)) a
unqualified (Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
-> LocalEnvironment l
imports Maybe
(FromEnvironment
l
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
spec)
Environment l -> Environment l -> Environment l
forall a. Semigroup a => a -> a -> a
<> Environment l
-> (ModuleName l -> Environment l)
-> Maybe (ModuleName l)
-> Environment l
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Environment l
forall a. Monoid a => a
mempty (ModuleName l -> LocalEnvironment l -> Environment l
forall l a.
ModuleName l
-> UnionWith (Map (Name l)) a
-> UnionWith (Map (QualifiedName l)) a
`qualifiedWith` Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
-> LocalEnvironment l
imports Maybe
(FromEnvironment
l
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
spec) Maybe (ModuleName l)
Maybe (ModuleName l)
alias
where imports :: Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
-> LocalEnvironment l
imports (Just Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f))
spec) = (ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l)
-> Compose
((,) (Attributes l))
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f))
-> LocalEnvironment l
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ImportSpecification l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
specImports (Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f))
-> Environment l
-> Compose
((,) (Attributes l))
f
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f))
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f))
spec Environment l
forall a. Monoid a => a
mempty)
imports Maybe
(Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportSpecification
l l (FromEnvironment l f) (FromEnvironment l f)))
Nothing = LocalEnvironment l
allImports
specImports :: ImportSpecification l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
specImports (ExtAST.ImportSpecification Bool
True [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
items) = [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l
itemsImports [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
[Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
items
specImports (ExtAST.ImportSpecification Bool
False [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
items) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (LocalEnvironment l -> Map (Name l) (Binding l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith LocalEnvironment l
allImports Map (Name l) (Binding l)
-> Map (Name l) (Binding l) -> Map (Name l) (Binding l)
forall k a b. Ord k => Map k a -> Map k b -> Map k a
`Map.difference` LocalEnvironment l -> Map (Name l) (Binding l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith ([Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l
itemsImports [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
[Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
items))
allImports :: LocalEnvironment l
allImports = LocalEnvironment l
moduleExports
itemsImports :: [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l
itemsImports = (ImportItem l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l)
-> [Compose
((->) (Environment l))
(Compose ((,) (Attributes l)) f)
(ImportItem l l (FromEnvironment l f) (FromEnvironment l f))]
-> LocalEnvironment l
forall a (g :: * -> *) m.
(Foldable g, Monoid m) =>
(a -> m)
-> g (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a)
-> m
foldMapWrapped ImportItem l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
itemImports
itemImports :: ImportItem l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
itemImports (ExtAST.ImportClassOrType Name l
name Maybe (Members l)
Nothing) = Name l -> LocalEnvironment l -> LocalEnvironment l
forall {k} {m}.
(Ord k, Monoid m) =>
k -> UnionWith (Map k) m -> UnionWith (Map k) m
nameImport Name l
Name l
name LocalEnvironment l
allImports
itemImports (ExtAST.ImportClassOrType Name l
parent (Just Members l
members)) =
case Name l -> Map (Name l) (Binding l) -> Maybe (Binding l)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Name l
Name l
parent (LocalEnvironment l -> Map (Name l) (Binding l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith LocalEnvironment l
allImports)
of Just b :: Binding l
b@(TypeBinding (TypeClass LocalEnvironment l
env)) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Name l
Name l
parent Binding l
b) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Just (TypeAndValueBinding b :: TypeBinding l
b@(TypeClass LocalEnvironment l
env) ValueBinding l
_) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Name l
Name l
parent (Binding l -> Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding TypeBinding l
b) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Just b :: Binding l
b@(TypeBinding (DataType LocalEnvironment l
env)) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Name l
Name l
parent Binding l
b) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Just (TypeAndValueBinding b :: TypeBinding l
b@(DataType LocalEnvironment l
env) ValueBinding l
_) ->
(Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> LocalEnvironment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Name l
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Name l
Name l
parent (Binding l -> Map (Name l) (Binding l) -> Map (Name l) (Binding l))
-> Binding l
-> Map (Name l) (Binding l)
-> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ TypeBinding l -> Binding l
forall l. TypeBinding l -> Binding l
TypeBinding TypeBinding l
b) (Members l -> LocalEnvironment l -> LocalEnvironment l
forall l.
BindingMembers l =>
Members l -> LocalEnvironment l -> LocalEnvironment l
filterMembers Members l
members LocalEnvironment l
env)
Maybe (Binding l)
_ -> Name l -> LocalEnvironment l -> LocalEnvironment l
forall {k} {m}.
(Ord k, Monoid m) =>
k -> UnionWith (Map k) m -> UnionWith (Map k) m
nameImport Name l
Name l
parent LocalEnvironment l
allImports
itemImports (ExtAST.ImportPattern Name l
name) = Name l -> LocalEnvironment l -> LocalEnvironment l
forall {k} {m}.
(Ord k, Monoid m) =>
k -> UnionWith (Map k) m -> UnionWith (Map k) m
nameImport Name l
Name l
name LocalEnvironment l
allImports
itemImports (ExtAST.ImportVar Name l
name) = Name l -> LocalEnvironment l -> LocalEnvironment l
forall {k} {m}.
(Ord k, Monoid m) =>
k -> UnionWith (Map k) m -> UnionWith (Map k) m
nameImport Name l
Name l
name LocalEnvironment l
allImports
filterEnv :: (AST.QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv :: (QualifiedName l -> Bool) -> Environment l -> LocalEnvironment l
filterEnv QualifiedName l -> Bool
f Environment l
env = (Map (QualifiedName l) (Binding l) -> Map (Name l) (Binding l))
-> Environment l -> LocalEnvironment l
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((QualifiedName l -> Name l)
-> Map (QualifiedName l) (Binding l) -> Map (Name l) (Binding l)
forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeysMonotonic QualifiedName l -> Name l
forall l. QualifiedName l -> Name l
baseName (Map (QualifiedName l) (Binding l) -> Map (Name l) (Binding l))
-> (Map (QualifiedName l) (Binding l)
-> Map (QualifiedName l) (Binding l))
-> Map (QualifiedName l) (Binding l)
-> Map (Name l) (Binding l)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (QualifiedName l -> Binding l -> Bool)
-> Map (QualifiedName l) (Binding l)
-> Map (QualifiedName l) (Binding l)
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey (Bool -> Binding l -> Bool
forall a b. a -> b -> a
const (Bool -> Binding l -> Bool)
-> (QualifiedName l -> Bool)
-> QualifiedName l
-> Binding l
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. QualifiedName l -> Bool
f)) Environment l
env
foldMapWrapped :: forall a g m. (Foldable g, Monoid m)
=> (a -> m)
-> g (Compose ((->) (Environment l)) (WithEnvironment l f) a)
-> m
foldMapWrapped :: forall a (g :: * -> *) m.
(Foldable g, Monoid m) =>
(a -> m)
-> g (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a)
-> m
foldMapWrapped a -> m
f = (Compose ((->) (Environment l)) (Compose ((,) (Attributes l)) f) a
-> m)
-> g (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a)
-> m
forall m a. Monoid m => (a -> m) -> g a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall m a.
Monoid m =>
(a -> m) -> Compose ((,) (Attributes l)) f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f (Compose ((,) (Attributes l)) f a -> m)
-> (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a
-> Compose ((,) (Attributes l)) f a)
-> Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a
-> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Environment l -> Compose ((,) (Attributes l)) f a)
-> Environment l -> Compose ((,) (Attributes l)) f a
forall a b. (a -> b) -> a -> b
$ Environment l
forall a. Monoid a => a
mempty) ((Environment l -> Compose ((,) (Attributes l)) f a)
-> Compose ((,) (Attributes l)) f a)
-> (Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a
-> Environment l -> Compose ((,) (Attributes l)) f a)
-> Compose
((->) (Environment l)) (Compose ((,) (Attributes l)) f) a
-> Compose ((,) (Attributes l)) f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Compose ((->) (Environment l)) (Compose ((,) (Attributes l)) f) a
-> Environment l -> Compose ((,) (Attributes l)) f a
forall {k1} {k2} (f :: k1 -> *) (g :: k2 -> k1) (a :: k2).
Compose f g a -> f (g a)
getCompose)
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(AST.DataConstructor l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (DataConstructor
l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (DataConstructor l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: AST.DataConstructor l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: DataConstructor l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (AST.Constructor Name l
name [FromEnvironment
l f (Type l l (FromEnvironment l f) (FromEnvironment l f))]
_types) = Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DataConstructor)
export (AST.RecordConstructor Name l
name [FromEnvironment
l
f
(FieldDeclaration l l (FromEnvironment l f) (FromEnvironment l f))]
_flds) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (ValueBinding l -> Binding l) -> ValueBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> ValueBinding l
forall l. LocalEnvironment l -> ValueBinding l
RecordConstructor (LocalEnvironment l -> ValueBinding l)
-> LocalEnvironment l -> ValueBinding l
forall a b. (a -> b) -> a -> b
$ Atts (Environment l) (LocalEnvironment l) -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Atts (Environment l) (LocalEnvironment l)
atts)
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(ExtAST.DataConstructor l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (DataConstructor
l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (DataConstructor l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: ExtAST.DataConstructor l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: DataConstructor l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (ExtAST.Constructor Name l
name [FromEnvironment
l f (Type l l (FromEnvironment l f) (FromEnvironment l f))]
_types) = Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DataConstructor)
export (ExtAST.RecordConstructor Name l
name [FromEnvironment
l
f
(FieldDeclaration l l (FromEnvironment l f) (FromEnvironment l f))]
_fields) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (ValueBinding l -> Binding l) -> ValueBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> ValueBinding l
forall l. LocalEnvironment l -> ValueBinding l
RecordConstructor (LocalEnvironment l -> ValueBinding l)
-> LocalEnvironment l -> ValueBinding l
forall a b. (a -> b) -> a -> b
$ Atts (Environment l) (LocalEnvironment l) -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Atts (Environment l) (LocalEnvironment l)
atts)
export ExtAST.ExistentialConstructor{} = LocalEnvironment l
forall a. Monoid a => a
mempty
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(ExtAST.GADTConstructor l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (GADTConstructor
l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: ExtAST.GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: GADTConstructor l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (ExtAST.GADTConstructors NonEmpty (Name l)
names [TypeVarBinding l l (FromEnvironment l f) (FromEnvironment l f)]
vars FromEnvironment
l f (Context l l (FromEnvironment l f) (FromEnvironment l f))
_ctx FromEnvironment
l f (Type l l (FromEnvironment l f) (FromEnvironment l f))
t)
| Map (Name l) (Binding l) -> Bool
forall k a. Map k a -> Bool
Map.null (LocalEnvironment l -> Map (Name l) (Binding l)
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith (LocalEnvironment l -> Map (Name l) (Binding l))
-> LocalEnvironment l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ Atts (Environment l) (LocalEnvironment l) -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Atts (Environment l) (LocalEnvironment l)
atts)
= Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Name l
name, ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DataConstructor) | Name l
name <- NonEmpty (Name l) -> [Name l]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty (Name l)
NonEmpty (Name l)
names]
| Bool
otherwise
= Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Name l
name, ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (ValueBinding l -> Binding l) -> ValueBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> ValueBinding l
forall l. LocalEnvironment l -> ValueBinding l
RecordConstructor (LocalEnvironment l -> ValueBinding l)
-> LocalEnvironment l -> ValueBinding l
forall a b. (a -> b) -> a -> b
$ Atts (Environment l) (LocalEnvironment l) -> LocalEnvironment l
forall a b. Atts a b -> b
Di.syn Atts (Environment l) (LocalEnvironment l)
atts) | Name l
name <- NonEmpty (Name l) -> [Name l]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty (Name l)
NonEmpty (Name l)
names]
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(AST.FieldDeclaration l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (FieldDeclaration
l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (FieldDeclaration
l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: AST.FieldDeclaration l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: FieldDeclaration l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (AST.ConstructorFields NonEmpty (Name l)
names FromEnvironment
l f (Type l l (FromEnvironment l f) (FromEnvironment l f))
t) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Name l
name, ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
RecordField) | Name l
name <- NonEmpty (Name l) -> [Name l]
forall a. NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList NonEmpty (Name l)
NonEmpty (Name l)
names]
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(ExtAST.PatternLHS l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (PatternLHS l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (PatternLHS l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: ExtAST.PatternLHS l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: PatternLHS l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (ExtAST.RecordPatternLHS Name l
con [Name l]
fields) =
Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
con (Binding l -> Map (Name l) (Binding l))
-> Binding l -> Map (Name l) (Binding l)
forall a b. (a -> b) -> a -> b
$ ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding (ValueBinding l -> Binding l) -> ValueBinding l -> Binding l
forall a b. (a -> b) -> a -> b
$ LocalEnvironment l -> ValueBinding l
forall l. LocalEnvironment l -> ValueBinding l
RecordConstructor LocalEnvironment l
fieldEnv) LocalEnvironment l -> LocalEnvironment l -> LocalEnvironment l
forall a. Semigroup a => a -> a -> a
<> LocalEnvironment l
fieldEnv
where fieldEnv :: LocalEnvironment l
fieldEnv = Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ [(Name l, Binding l)] -> Map (Name l) (Binding l)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Name l
name, ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
RecordField) | Name l
name <- [Name l]
fields]
export PatternLHS l l (FromEnvironment l f) (FromEnvironment l f)
_ = LocalEnvironment l
forall a. Monoid a => a
mempty
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(AST.Pattern l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (Pattern l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (Pattern l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: AST.Pattern l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: Pattern l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (AST.VariablePattern Name l
name) = Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DefinedValue)
export Pattern l l (FromEnvironment l f) (FromEnvironment l f)
_ = LocalEnvironment l
forall a. Monoid a => a
mempty
instance {-# OVERLAPS #-}
(Abstract.Haskell l,
Abstract.QualifiedName l ~ AST.QualifiedName l, Abstract.Name l ~ AST.Name l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l),
Show (Abstract.ModuleName l), Show (Abstract.Name l),
Foldable f) =>
Di.Attribution
(Di.Keep (Binder l f))
(Environment l)
(LocalEnvironment l)
(ExtAST.Pattern l l)
(FromEnvironment l f)
f
where
attribution :: Keep (Binder l f)
-> f (Pattern l l (FromEnvironment l f) (FromEnvironment l f))
-> Rule (Environment l) (LocalEnvironment l)
attribution Keep (Binder l f)
_ f (Pattern l l (FromEnvironment l f) (FromEnvironment l f))
node Atts (Environment l) (LocalEnvironment l)
atts = Atts (Environment l) (LocalEnvironment l)
atts{Di.syn= foldMap export node <> Di.syn atts, Di.inh= Di.inh atts}
where export :: ExtAST.Pattern l l (FromEnvironment l f) (FromEnvironment l f) -> LocalEnvironment l
export :: Pattern l l (FromEnvironment l f) (FromEnvironment l f)
-> LocalEnvironment l
export (ExtAST.VariablePattern Name l
name) = Map (Name l) (Binding l) -> LocalEnvironment l
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map (Name l) (Binding l) -> LocalEnvironment l)
-> Map (Name l) (Binding l) -> LocalEnvironment l
forall a b. (a -> b) -> a -> b
$ Name l -> Binding l -> Map (Name l) (Binding l)
forall k a. k -> a -> Map k a
Map.singleton Name l
Name l
name (ValueBinding l -> Binding l
forall l. ValueBinding l -> Binding l
ValueBinding ValueBinding l
forall l. ValueBinding l
DefinedValue)
export Pattern l l (FromEnvironment l f) (FromEnvironment l f)
_ = LocalEnvironment l
forall a. Monoid a => a
mempty
instance {-# OVERLAPPABLE #-} BindingVerifier l f `Transformation.At` g where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain (BindingVerifier l f) g
-> Codomain (BindingVerifier l f) g
$ Domain (BindingVerifier l f) g
_ = Const (Unbound l) g
Codomain (BindingVerifier l f) g
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.Export l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Export l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Export l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Export l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Export l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Export l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Export l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.ExportClassOrType QualifiedName l
q Maybe (Members l)
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify (AST.ExportVar QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify Export l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Export l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.Declaration l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Declaration l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Declaration l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Declaration l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Declaration l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Declaration l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Declaration l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.TypeRoleDeclaration QualifiedName l
q [TypeRole l]
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify Declaration l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Declaration l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (ClassInstanceLHS
l l (WithEnvironment l f) (WithEnvironment l f))
node) = (ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (ClassInstanceLHS
l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
verify f (ClassInstanceLHS
l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.TypeClassInstanceLHS QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` ExtAST.ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (ClassInstanceLHS
l l (WithEnvironment l f) (WithEnvironment l f))
node) = (ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (ClassInstanceLHS
l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
verify f (ClassInstanceLHS
l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
verify (ExtAST.TypeClassInstanceLHS QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.ClassReferenceInstanceLHS QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.InfixTypeClassInstanceLHS WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_ QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(ClassInstanceLHS l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.Context l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Context l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Context l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Context l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Context l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Context l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Context l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.ClassConstraint QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify Context l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` ExtAST.Context l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Context l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Context l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Context l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Context l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Context l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Context l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
verify (ExtAST.ClassConstraint QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify Context l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Context l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` ExtAST.Type l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Type l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Type l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Type l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Type l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Type l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Type l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Type l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Type l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f))
verify (ExtAST.InfixTypeApplication WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_ QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.PromotedInfixTypeApplication WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_ QualifiedName l
q WithEnvironment
l f (Type l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
verify Type l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l) (Type l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.DerivingClause l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
node) = (DerivingClause l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (DerivingClause
l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap DerivingClause l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
verify f (DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: DerivingClause l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.SimpleDerive QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(DerivingClause l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
QualifiedName l
q Environment l
env
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.FieldBinding l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
node) = (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
verify f (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.FieldBinding QualifiedName l
q WithEnvironment
l f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` ExtAST.FieldBinding l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
node) = (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
verify f (FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: FieldBinding l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
verify (ExtAST.FieldBinding QualifiedName l
q WithEnvironment
l f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.PunnedFieldBinding QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(FieldBinding l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.FieldPattern l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
node) = (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
verify f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.FieldPattern QualifiedName l
q WithEnvironment
l f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` ExtAST.FieldPattern l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
node) = (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
verify f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: FieldPattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
verify (ExtAST.FieldPattern QualifiedName l
q WithEnvironment
l f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.PunnedFieldPattern QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.Expression l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Expression l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Expression l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Expression l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.ReferenceExpression QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (AST.LeftSectionExpression WithEnvironment
l f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
_ QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (AST.RightSectionExpression QualifiedName l
q WithEnvironment
l f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify Expression l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` ExtAST.Expression l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Expression l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Expression l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Expression l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
verify (ExtAST.ReferenceExpression QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.LeftSectionExpression WithEnvironment
l f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
_ QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (ExtAST.RightSectionExpression QualifiedName l
q WithEnvironment
l f (Expression l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify Expression l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Expression l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.Pattern l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Pattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Pattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Pattern l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.InfixPattern WithEnvironment
l f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
_ QualifiedName l
q WithEnvironment
l f (Pattern l l (WithEnvironment l f) (WithEnvironment l f))
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
QualifiedName l
q Environment l
env
verify (AST.RecordPattern QualifiedName l
q [WithEnvironment
l f (FieldPattern l l (WithEnvironment l f) (WithEnvironment l f))]
_) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyConstructorName QualifiedName l
QualifiedName l
q Environment l
env
verify Pattern l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Pattern l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Abstract.QualifiedName l ~ AST.QualifiedName l,
Ord (Abstract.ModuleName l), Ord (Abstract.Name l)) =>
BindingVerifier l f `Transformation.At` AST.Constructor l l (WithEnvironment l f) (WithEnvironment l f) where
BindingVerifier l f
_ $ :: BindingVerifier l f
-> Domain
(BindingVerifier l f)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
-> Codomain
(BindingVerifier l f)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
$ Compose (Di.Atts{inh :: forall a b. Atts a b -> a
Di.inh= Environment l
env}, f (Constructor l l (WithEnvironment l f) (WithEnvironment l f))
node) = (Constructor l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f)))
-> f (Constructor l l (WithEnvironment l f) (WithEnvironment l f))
-> Const
(Unbound l)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
forall m a. Monoid m => (a -> m) -> f a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap Constructor l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
verify f (Constructor l l (WithEnvironment l f) (WithEnvironment l f))
node
where verify :: Constructor l l (WithEnvironment l f) (WithEnvironment l f)
-> Const
(Unbound l)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
verify (AST.ConstructorReference QualifiedName l
q) = QualifiedName l
-> Environment l
-> Const
(Unbound l)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
forall {l} {b}.
QualifiedName l -> Environment l -> Const (Unbound l) b
verifyConstructorName QualifiedName l
QualifiedName l
q Environment l
env
verify Constructor l l (WithEnvironment l f) (WithEnvironment l f)
_ = Const
(Unbound l)
(Constructor l l (WithEnvironment l f) (WithEnvironment l f))
forall a. Monoid a => a
mempty
instance (Foldable f, Rank2.Foldable (g (WithEnvironment l f)), Deep.Foldable (BindingVerifier l f) g,
Transformation.At (BindingVerifier l f) (g (WithEnvironment l f) (WithEnvironment l f))) =>
Full.Foldable (BindingVerifier l f) g where
foldMap :: forall m.
(Codomain (BindingVerifier l f) ~ Const m, Monoid m) =>
BindingVerifier l f
-> Domain
(BindingVerifier l f)
(g (Domain (BindingVerifier l f)) (Domain (BindingVerifier l f)))
-> m
foldMap = BindingVerifier l f
-> Domain
(BindingVerifier l f)
(g (Domain (BindingVerifier l f)) (Domain (BindingVerifier l f)))
-> m
forall t (g :: (* -> *) -> (* -> *) -> *) m.
(At t (g (Domain t) (Domain t)), Foldable t g,
Codomain t ~ Const m, Foldable (Domain t), Monoid m) =>
t -> Domain t (g (Domain t) (Domain t)) -> m
Full.foldMapDownDefault
verifyConstructorName :: QualifiedName l -> Environment l -> Const (Unbound l) b
verifyConstructorName QualifiedName l
q Environment l
env = case QualifiedName l -> Environment l -> Maybe (TypeBinding l)
forall l. QualifiedName l -> Environment l -> Maybe (TypeBinding l)
lookupType QualifiedName l
q Environment l
env Maybe (TypeBinding l) -> () -> Maybe ()
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> () Maybe () -> Maybe () -> Maybe ()
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> QualifiedName l -> Environment l -> Maybe (ValueBinding l)
forall l.
QualifiedName l -> Environment l -> Maybe (ValueBinding l)
lookupValue QualifiedName l
q Environment l
env Maybe (ValueBinding l) -> () -> Maybe ()
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> () of
Maybe ()
Nothing -> Unbound l -> Const (Unbound l) b
forall {k} a (b :: k). a -> Const a b
Const Unbound{types :: [QualifiedName l]
types= [], constructors :: [QualifiedName l]
constructors= [QualifiedName l
q], values :: [QualifiedName l]
values= []}
Maybe ()
_ -> Const (Unbound l) b
forall a. Monoid a => a
mempty
verifyTypeName :: QualifiedName l -> Environment l -> Const (Unbound l) b
verifyTypeName QualifiedName l
q Environment l
env = case QualifiedName l -> Environment l -> Maybe (TypeBinding l)
forall l. QualifiedName l -> Environment l -> Maybe (TypeBinding l)
lookupType QualifiedName l
q Environment l
env of
Maybe (TypeBinding l)
Nothing -> Unbound l -> Const (Unbound l) b
forall {k} a (b :: k). a -> Const a b
Const Unbound{types :: [QualifiedName l]
types= [QualifiedName l
q], constructors :: [QualifiedName l]
constructors= [], values :: [QualifiedName l]
values= []}
Maybe (TypeBinding l)
_ -> Const (Unbound l) b
forall a. Monoid a => a
mempty
verifyValueName :: QualifiedName l -> Environment l -> Const (Unbound l) b
verifyValueName QualifiedName l
q Environment l
env = case QualifiedName l -> Environment l -> Maybe (ValueBinding l)
forall l.
QualifiedName l -> Environment l -> Maybe (ValueBinding l)
lookupValue QualifiedName l
q Environment l
env of
Maybe (ValueBinding l)
Nothing -> Unbound l -> Const (Unbound l) b
forall {k} a (b :: k). a -> Const a b
Const Unbound{types :: [QualifiedName l]
types= [], constructors :: [QualifiedName l]
constructors= [], values :: [QualifiedName l]
values= [QualifiedName l
q]}
Maybe (ValueBinding l)
_ -> Const (Unbound l) b
forall a. Monoid a => a
mempty
class Abstract.Haskell l => BindingMembers l where
filterMembers :: Abstract.Members l -> LocalEnvironment l -> LocalEnvironment l
instance BindingMembers AST.Language where
filterMembers :: Members Language
-> LocalEnvironment Language -> LocalEnvironment Language
filterMembers Members Language
Members Language
AST.AllMembers LocalEnvironment Language
env = LocalEnvironment Language
env
filterMembers (AST.MemberList [Name Language]
names) LocalEnvironment Language
env = (Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language))
-> LocalEnvironment Language -> LocalEnvironment Language
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Map (Name Language) (Binding Language)
-> Set (Name Language) -> Map (Name Language) (Binding Language)
forall k a. Ord k => Map k a -> Set k -> Map k a
`Map.restrictKeys` [Name Language] -> Set (Name Language)
forall a. Ord a => [a] -> Set a
Set.fromList [Name Language]
names) LocalEnvironment Language
env
instance BindingMembers ExtAST.Language where
filterMembers :: Members Language
-> LocalEnvironment Language -> LocalEnvironment Language
filterMembers Members Language
Members Language
ExtAST.AllMembers LocalEnvironment Language
env = LocalEnvironment Language
env
filterMembers ExtAST.AllMembersPlus{} LocalEnvironment Language
env = LocalEnvironment Language
env
filterMembers (ExtAST.MemberList [Name Language]
names) LocalEnvironment Language
env = (Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language))
-> LocalEnvironment Language -> LocalEnvironment Language
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Map (Name Language) (Binding Language)
-> Set (Name Language) -> Map (Name Language) (Binding Language)
forall k a. Ord k => Map k a -> Set k -> Map k a
`Map.restrictKeys` [Name Language] -> Set (Name Language)
forall a. Ord a => [a] -> Set a
Set.fromList [Name Language]
names) LocalEnvironment Language
env
filterMembers (ExtAST.ExplicitlyNamespacedMemberList SupportFor 'ExplicitNamespaces Language
_support [ModuleMember Language]
members) LocalEnvironment Language
env = (ModuleMember Language -> LocalEnvironment Language)
-> [ModuleMember Language] -> LocalEnvironment Language
forall m a. Monoid m => (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ModuleMember Language -> LocalEnvironment Language
memberImport [ModuleMember Language]
members
where memberImport :: ModuleMember Language -> LocalEnvironment Language
memberImport (ExtAST.DefaultMember Name Language
name) = (Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language))
-> LocalEnvironment Language -> LocalEnvironment Language
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap (Map (Name Language) (Binding Language)
-> Set (Name Language) -> Map (Name Language) (Binding Language)
forall k a. Ord k => Map k a -> Set k -> Map k a
`Map.restrictKeys` Name Language -> Set (Name Language)
forall a. a -> Set a
Set.singleton Name Language
name) LocalEnvironment Language
env
memberImport (ExtAST.PatternMember Name Language
name) = (Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language))
-> LocalEnvironment Language -> LocalEnvironment Language
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((Name Language -> Binding Language -> Bool)
-> Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language)
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey Name Language -> Binding Language -> Bool
namedPattern) LocalEnvironment Language
env
where namedPattern :: Name Language -> Binding Language -> Bool
namedPattern Name Language
name' PatternBinding{} = Name Language
name Name Language -> Name Language -> Bool
forall a. Eq a => a -> a -> Bool
== Name Language
name'
namedPattern Name Language
_ Binding Language
_ = Bool
False
memberImport (ExtAST.TypeMember Name Language
name) = (Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language))
-> LocalEnvironment Language -> LocalEnvironment Language
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((Name Language -> Binding Language -> Bool)
-> Map (Name Language) (Binding Language)
-> Map (Name Language) (Binding Language)
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey Name Language -> Binding Language -> Bool
namedType) LocalEnvironment Language
env
where namedType :: Name Language -> Binding Language -> Bool
namedType Name Language
name' TypeBinding{} = Name Language
name Name Language -> Name Language -> Bool
forall a. Eq a => a -> a -> Bool
== Name Language
name'
namedType Name Language
_ Binding Language
_ = Bool
False
nameImport :: k -> UnionWith (Map k) m -> UnionWith (Map k) m
nameImport k
name UnionWith (Map k) m
imports = (m -> UnionWith (Map k) m) -> Maybe m -> UnionWith (Map k) m
forall m a. Monoid m => (a -> m) -> Maybe a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Map k m -> UnionWith (Map k) m
forall (f :: * -> *) m. f m -> UnionWith f m
UnionWith (Map k m -> UnionWith (Map k) m)
-> (m -> Map k m) -> m -> UnionWith (Map k) m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. k -> m -> Map k m
forall k a. k -> a -> Map k a
Map.singleton k
name) (k -> Map k m -> Maybe m
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup k
name (Map k m -> Maybe m) -> Map k m -> Maybe m
forall a b. (a -> b) -> a -> b
$ UnionWith (Map k) m -> Map k m
forall (f :: * -> *) m. UnionWith f m -> f m
getUnionWith UnionWith (Map k) m
imports)
qualifiedWith :: AST.ModuleName l -> UnionWith (Map (AST.Name l)) a -> UnionWith (Map (AST.QualifiedName l)) a
qualifiedWith :: forall l a.
ModuleName l
-> UnionWith (Map (Name l)) a
-> UnionWith (Map (QualifiedName l)) a
qualifiedWith ModuleName l
moduleName = (Map (Name l) a -> Map (QualifiedName l) a)
-> UnionWith (Map (Name l)) a
-> UnionWith (Map (QualifiedName l)) a
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((Name l -> QualifiedName l)
-> Map (Name l) a -> Map (QualifiedName l) a
forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeysMonotonic ((Name l -> QualifiedName l)
-> Map (Name l) a -> Map (QualifiedName l) a)
-> (Name l -> QualifiedName l)
-> Map (Name l) a
-> Map (QualifiedName l) a
forall a b. (a -> b) -> a -> b
$ Maybe (ModuleName l) -> Name l -> QualifiedName l
forall λ. Maybe (ModuleName λ) -> Name λ -> QualifiedName λ
AST.QualifiedName (Maybe (ModuleName l) -> Name l -> QualifiedName l)
-> Maybe (ModuleName l) -> Name l -> QualifiedName l
forall a b. (a -> b) -> a -> b
$ ModuleName l -> Maybe (ModuleName l)
forall a. a -> Maybe a
Just ModuleName l
moduleName)
unqualified :: Abstract.Haskell l => UnionWith (Map (Abstract.Name l)) a -> UnionWith (Map (Abstract.QualifiedName l)) a
unqualified :: forall l a.
Haskell l =>
UnionWith (Map (Name l)) a -> UnionWith (Map (QualifiedName l)) a
unqualified = (Map (Name l) a -> Map (QualifiedName l) a)
-> UnionWith (Map (Name l)) a
-> UnionWith (Map (QualifiedName l)) a
forall j a k b.
(Map j a -> Map k b) -> UnionWith (Map j) a -> UnionWith (Map k) b
onMap ((Name l -> QualifiedName l)
-> Map (Name l) a -> Map (QualifiedName l) a
forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeysMonotonic Name l -> QualifiedName l
forall l. Haskell l => Name l -> QualifiedName l
unqualifiedName)
baseName :: AST.QualifiedName l -> AST.Name l
baseName :: forall l. QualifiedName l -> Name l
baseName (AST.QualifiedName Maybe (ModuleName l)
_ Name l
name) = Name l
name
unqualifiedName :: Abstract.Haskell l => Abstract.Name l -> Abstract.QualifiedName l
unqualifiedName :: forall l. Haskell l => Name l -> QualifiedName l
unqualifiedName = Maybe (ModuleName l) -> Name l -> QualifiedName l
forall λ.
Haskell λ =>
Maybe (ModuleName λ) -> Name λ -> QualifiedName λ
Abstract.qualifiedName Maybe (ModuleName l)
forall a. Maybe a
Nothing
preludeName :: Abstract.Haskell l => Abstract.ModuleName l
preludeName :: forall l. Haskell l => ModuleName l
preludeName = NonEmpty (Name l) -> ModuleName l
forall λ. Haskell λ => NonEmpty (Name λ) -> ModuleName λ
Abstract.moduleName (Text -> Name l
forall λ. Haskell λ => Text -> Name λ
Abstract.name Text
"Prelude" Name l -> [Name l] -> NonEmpty (Name l)
forall a. a -> [a] -> NonEmpty a
:| [])