| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Intensional.Types
Documentation
class Refined t where Source #
Instances
| Refined Guard Source # | |
| Refined ConstraintSet Source # | |
Defined in Intensional.Constraints Methods domain :: ConstraintSet -> Domain Source # rename :: RVar -> RVar -> ConstraintSet -> ConstraintSet Source # | |
| Outputable d => Refined (TypeGen d) Source # | |
| Outputable d => Refined (DataType d) Source # | |
| Refined (K l) Source # | |
| Outputable d => Refined (SchemeGen d) Source # | |
| Refined b => Refined (Map a b) Source # | |
| Refined (Constraint l r) Source # | |
Defined in Intensional.Constraints Methods domain :: Constraint l r -> Domain Source # rename :: RVar -> RVar -> Constraint l r -> Constraint l r Source # | |
Instances
Constructors
| Var Name | |
| App (TypeGen d) (TypeGen d) | |
| Data (DataType d) [TypeGen d] | |
| (TypeGen d) :=> (TypeGen d) | |
| Lit IfaceTyLit | |
| Ambiguous |
Instances
| Functor TypeGen Source # | |
| Foldable TypeGen Source # | |
Defined in Intensional.Types Methods fold :: Monoid m => TypeGen m -> m # foldMap :: Monoid m => (a -> m) -> TypeGen a -> m # foldMap' :: Monoid m => (a -> m) -> TypeGen a -> m # foldr :: (a -> b -> b) -> b -> TypeGen a -> b # foldr' :: (a -> b -> b) -> b -> TypeGen a -> b # foldl :: (b -> a -> b) -> b -> TypeGen a -> b # foldl' :: (b -> a -> b) -> b -> TypeGen a -> b # foldr1 :: (a -> a -> a) -> TypeGen a -> a # foldl1 :: (a -> a -> a) -> TypeGen a -> a # elem :: Eq a => a -> TypeGen a -> Bool # maximum :: Ord a => TypeGen a -> a # minimum :: Ord a => TypeGen a -> a # | |
| Traversable TypeGen Source # | |
| Binary d => Binary (TypeGen d) Source # | |
| Outputable d => Outputable (TypeGen d) Source # | |
| Outputable d => Refined (TypeGen d) Source # | |