derive-gadt-0.1.1: Instance deriving for (a subset of) GADTs.Source codeContentsIndex
Language.Haskell.Derive.Gadt.Unify
Description
A clusterfrolick at the moment. Among other things, the Exists con in the Type type isn't handled correctly (or at all really, it's just pretended that it's Forall because I don't know how to handle it).
Synopsis
unify :: Type -> Type -> Q (Either String (Substs, Substs))
type Substs = Map Name [Type]
type SubstMap = Map Name [Name]
type UnifyMap = Map Name [Type]
data UnifyEnv = UnifyEnv {
substMaps :: (SubstMap, SubstMap)
isubstMaps :: (SubstMap, SubstMap)
noDupsMap :: Either String (Map Name (Name, Name))
finalMap :: Either String (Map Name Name)
unifyMap :: (UnifyMap, UnifyMap)
stragglers :: [(Type, Type)]
}
varT :: String -> Type
tupT :: [Type] -> Type
listT :: Type -> Type
invertSubstMap :: SubstMap -> SubstMap
invertSubsts :: SubstMap -> SubstMap -> Map Name ([Name], [Name])
checkForDups :: Map Name ([Name], [Name]) -> Either String (Map Name (Name, Name))
extractSubsts :: UnifyEnv -> Either String (Substs, Substs)
(|.|) :: (Ord a, Ord b) => Map b c -> Map a b -> Map a c
renameT :: Type -> Type
noDupsMapToFinalSubsts :: Map Name (Name, Name) -> Either String (Map Name Name)
buildUMap :: [(Type, Type)] -> ((UnifyMap, UnifyMap), [(Type, Type)])
splitSubsts :: [(Type, Type)] -> Q UnifyEnv
matchTypes :: Type -> Type -> [(Type, Type)]
typeViaT :: ViaT Type Type Type
typeToT :: Type -> T Type
typeFromT :: T Type -> Type
firstNameMap :: Map Name [Name] -> [(Name, Type)]
isInf :: Name -> Type -> Bool
bothVars :: (Type, Type) -> Bool
varOnLeft :: (Type, Type) -> Bool
varOnRight :: (Type, Type) -> Bool
data Name
= NameG String
| NameL String
| NameU String !Int
data Type
= ArrowT
| VarT Name
| ConT Name
| AppT Type Type
| ForallT [Name] Type
| ExistsT [Name] Type
ftvs :: Type -> Set Name
btvs :: Type -> Set Name
closeT :: Type -> Type
openT :: Type -> Type
(.->.) :: Type -> Type -> Type
unwindFunT :: Type -> (Type, [Type])
unwindAppT :: Type -> (Type, [Type])
substT :: [(Name, Type)] -> Type -> Type
listName :: Name
tupName :: Int -> Name
listCon :: Type
tupCon :: Int -> Type
testType0 :: Type
idType :: Type -> Type
testType1 :: Type
testType2 :: Type
pprName :: Name -> Doc
pprType :: Type -> Doc
pprParenType :: Type -> Doc
newtype Q a = Q (IO a)
runQ :: Q a -> IO a
runIO :: IO a -> Q a
unQ :: Q a -> a
newName :: String -> Q Name
mkName :: String -> Name
mkNameG :: String -> Name
mkNameL :: String -> Name
mkNameU :: String -> Int -> Name
newUniq :: Q Int
gensymQ :: IORef Int
tick :: IORef Int -> Q Int
reset :: IORef Int -> Q ()
resetQ :: Q ()
newtype S s a = S {
unS :: forall o. (a -> s -> o) -> s -> o
}
get :: S s s
gets :: (s -> a) -> S s a
set :: s -> S s ()
modify :: (s -> s) -> S s ()
runS :: S s a -> s -> (a, s)
evalS :: S s a -> s -> a
execS :: S s a -> s -> s
type SubstM a = S SubstEnv a
data SubstEnv = SubstEnv {
boundSet :: Set Name
substMap :: Map Name Type
}
initSubstEnv :: [(Name, Type)] -> SubstEnv
runSubstM :: SubstM a -> SubstEnv -> a
bindM :: Name -> SubstM ()
substM :: Name -> SubstM Type
localM :: SubstM a -> SubstM a
data T a
= Tip a
| T (T a) (T a)
toListT :: T a -> [a]
fromListT :: [a] -> [T a]
toTreeT :: (Maybe a -> b) -> T a -> Tree b
foldrT :: (a -> b -> b) -> b -> T a -> b
foldlT :: (a -> b -> a) -> a -> T b -> a
foldl'T :: (a -> b -> a) -> a -> T b -> a
sumT :: Num a => T a -> a
prodT :: Num a => T a -> a
andT :: T Bool -> Bool
orT :: T Bool -> Bool
unifyT :: (Either a (T a) -> c) -> (Either b (T b) -> d) -> (c -> d -> e) -> T a -> T b -> T e
zipT :: (T a -> T b -> c) -> T a -> T b -> T c
matchT :: (a -> T x) -> (b -> T y) -> (T x -> c) -> (T y -> d) -> (c -> d -> e) -> a -> b -> T e
data ViaT a b c = ViaT {
toT :: a -> T b
fromT :: T b -> c
}
match :: ViaT a x c -> ViaT b y d -> (c -> d -> e) -> a -> b -> [e]
Documentation
unify :: Type -> Type -> Q (Either String (Substs, Substs))Source
.
type Substs = Map Name [Type]Source
type SubstMap = Map Name [Name]Source
type UnifyMap = Map Name [Type]Source
data UnifyEnv Source
Constructors
UnifyEnv
substMaps :: (SubstMap, SubstMap)
isubstMaps :: (SubstMap, SubstMap)
noDupsMap :: Either String (Map Name (Name, Name))
finalMap :: Either String (Map Name Name)
unifyMap :: (UnifyMap, UnifyMap)
stragglers :: [(Type, Type)]
show/hide Instances
varT :: String -> TypeSource
tupT :: [Type] -> TypeSource
listT :: Type -> TypeSource
invertSubstMap :: SubstMap -> SubstMapSource
invertSubsts :: SubstMap -> SubstMap -> Map Name ([Name], [Name])Source
checkForDups :: Map Name ([Name], [Name]) -> Either String (Map Name (Name, Name))Source
extractSubsts :: UnifyEnv -> Either String (Substs, Substs)Source
(|.|) :: (Ord a, Ord b) => Map b c -> Map a b -> Map a cSource
renameT :: Type -> TypeSource
noDupsMapToFinalSubsts :: Map Name (Name, Name) -> Either String (Map Name Name)Source
buildUMap :: [(Type, Type)] -> ((UnifyMap, UnifyMap), [(Type, Type)])Source
splitSubsts :: [(Type, Type)] -> Q UnifyEnvSource
matchTypes :: Type -> Type -> [(Type, Type)]Source
typeViaT :: ViaT Type Type TypeSource
typeToT :: Type -> T TypeSource
typeFromT :: T Type -> TypeSource
firstNameMap :: Map Name [Name] -> [(Name, Type)]Source
isInf :: Name -> Type -> BoolSource
bothVars :: (Type, Type) -> BoolSource
varOnLeft :: (Type, Type) -> BoolSource
varOnRight :: (Type, Type) -> BoolSource
data Name Source
Constructors
NameG String
NameL String
NameU String !Int
show/hide Instances
data Type Source
Constructors
ArrowT
VarT Name
ConT Name
AppT Type Type
ForallT [Name] Type
ExistsT [Name] Type
show/hide Instances
ftvs :: Type -> Set NameSource
btvs :: Type -> Set NameSource
closeT :: Type -> TypeSource
openT :: Type -> TypeSource
(.->.) :: Type -> Type -> TypeSource
unwindFunT :: Type -> (Type, [Type])Source
unwindAppT :: Type -> (Type, [Type])Source
substT :: [(Name, Type)] -> Type -> TypeSource
listName :: NameSource
tupName :: Int -> NameSource
listCon :: TypeSource
tupCon :: Int -> TypeSource
testType0 :: TypeSource
idType :: Type -> TypeSource
testType1 :: TypeSource
testType2 :: TypeSource
pprName :: Name -> DocSource
pprType :: Type -> DocSource
pprParenType :: Type -> DocSource
newtype Q a Source
Constructors
Q (IO a)
show/hide Instances
runQ :: Q a -> IO aSource
runIO :: IO a -> Q aSource
unQ :: Q a -> aSource
newName :: String -> Q NameSource
mkName :: String -> NameSource
mkNameG :: String -> NameSource
mkNameL :: String -> NameSource
mkNameU :: String -> Int -> NameSource
newUniq :: Q IntSource
gensymQ :: IORef IntSource
tick :: IORef Int -> Q IntSource
reset :: IORef Int -> Q ()Source
resetQ :: Q ()Source
newtype S s a Source
Constructors
S
unS :: forall o. (a -> s -> o) -> s -> o
show/hide Instances
get :: S s sSource
gets :: (s -> a) -> S s aSource
set :: s -> S s ()Source
modify :: (s -> s) -> S s ()Source
runS :: S s a -> s -> (a, s)Source
evalS :: S s a -> s -> aSource
execS :: S s a -> s -> sSource
type SubstM a = S SubstEnv aSource
data SubstEnv Source
Constructors
SubstEnv
boundSet :: Set Name
substMap :: Map Name Type
show/hide Instances
initSubstEnv :: [(Name, Type)] -> SubstEnvSource
runSubstM :: SubstM a -> SubstEnv -> aSource
bindM :: Name -> SubstM ()Source
substM :: Name -> SubstM TypeSource
localM :: SubstM a -> SubstM aSource
data T a Source
Constructors
Tip a
T (T a) (T a)
show/hide Instances
Functor T
Eq a => Eq (T a)
Ord a => Ord (T a)
Read a => Read (T a)
Show a => Show (T a)
toListT :: T a -> [a]Source
fromListT :: [a] -> [T a]Source
toTreeT :: (Maybe a -> b) -> T a -> Tree bSource
foldrT :: (a -> b -> b) -> b -> T a -> bSource
foldlT :: (a -> b -> a) -> a -> T b -> aSource
foldl'T :: (a -> b -> a) -> a -> T b -> aSource
sumT :: Num a => T a -> aSource
prodT :: Num a => T a -> aSource
andT :: T Bool -> BoolSource
orT :: T Bool -> BoolSource
unifyT :: (Either a (T a) -> c) -> (Either b (T b) -> d) -> (c -> d -> e) -> T a -> T b -> T eSource
zipT :: (T a -> T b -> c) -> T a -> T b -> T cSource
matchT :: (a -> T x) -> (b -> T y) -> (T x -> c) -> (T y -> d) -> (c -> d -> e) -> a -> b -> T eSource
data ViaT a b c Source
Constructors
ViaT
toT :: a -> T b
fromT :: T b -> c
match :: ViaT a x c -> ViaT b y d -> (c -> d -> e) -> a -> b -> [e]Source
Produced by Haddock version 2.4.2