| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Exinst
Description
See the README file for documentation: https://hackage.haskell.org/package/exinst#readme
- data Some1 f1 = Some1 !(Sing a1) !(f1 a1)
- some1 :: forall f1 a1. SingI a1 => f1 a1 -> Some1 f1
- fromSome1 :: forall f1 a1. (SingI a1, SDecide k1) => Some1 f1 -> Maybe (f1 a1)
- _Some1 :: forall f1 a1. (SingI a1, SDecide k1) => Prism' (Some1 f1) (f1 a1)
- withSome1 :: forall f1 r. Some1 f1 -> (forall a1. SingI a1 => f1 a1 -> r) -> r
- withSome1Sing :: forall f1 r. Some1 f1 -> (forall a1. SingI a1 => Sing a1 -> f1 a1 -> r) -> r
- some1SingRep :: SingKind k1 => Some1 (f1 :: k1 -> Type) -> DemoteRep k1
- class Dict1 c f1 where
- data Some2 f2 = Some2 !(Sing a2) !(Sing a1) !(f2 a2 a1)
- some2 :: forall f2 a2 a1. (SingI a2, SingI a1) => f2 a2 a1 -> Some2 f2
- fromSome2 :: forall f2 a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Some2 f2 -> Maybe (f2 a2 a1)
- _Some2 :: forall f2 a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some2 f2) (f2 a2 a1)
- withSome2 :: forall f2 r. Some2 f2 -> (forall a2 a1. (SingI a2, SingI a1) => f2 a2 a1 -> r) -> r
- withSome2Sing :: forall f2 r. Some2 f2 -> (forall a2 a1. (SingI a2, SingI a1) => Sing a2 -> Sing a1 -> f2 a2 a1 -> r) -> r
- some2SingRep :: (SingKind k2, SingKind k1) => Some2 (f2 :: k2 -> k1 -> Type) -> (DemoteRep k2, DemoteRep k1)
- class Dict2 c f2 where
- data Some3 f3 = Some3 !(Sing a3) !(Sing a2) !(Sing a1) !(f3 a3 a2 a1)
- some3 :: forall f3 a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f3 a3 a2 a1 -> Some3 f3
- fromSome3 :: forall f3 a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Some3 f3 -> Maybe (f3 a3 a2 a1)
- _Some3 :: forall f3 a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some3 f3) (f3 a3 a2 a1)
- withSome3 :: forall f3 r. Some3 f3 -> (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => f3 a3 a2 a1 -> r) -> r
- withSome3Sing :: forall f3 r. Some3 f3 -> (forall a3 a2 a1. (SingI a3, SingI a2, SingI a1) => Sing a3 -> Sing a2 -> Sing a1 -> f3 a3 a2 a1 -> r) -> r
- some3SingRep :: (SingKind k3, SingKind k2, SingKind k1) => Some3 (f3 :: k3 -> k2 -> k1 -> Type) -> (DemoteRep k3, DemoteRep k2, DemoteRep k1)
- class Dict3 c f3 where
- data Some4 f4 = Some4 !(Sing a4) !(Sing a3) !(Sing a2) !(Sing a1) !(f4 a4 a3 a2 a1)
- some4 :: forall f4 a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f4 a4 a3 a2 a1 -> Some4 f4
- fromSome4 :: forall f4 a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Some4 f4 -> Maybe (f4 a4 a3 a2 a1)
- _Some4 :: forall f4 a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some4 f4) (f4 a4 a3 a2 a1)
- withSome4 :: forall f4 r. Some4 f4 -> (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => f4 a4 a3 a2 a1 -> r) -> r
- withSome4Sing :: forall f4 r. Some4 f4 -> (forall a4 a3 a2 a1. (SingI a4, SingI a3, SingI a2, SingI a1) => Sing a4 -> Sing a3 -> Sing a2 -> Sing a1 -> f4 a4 a3 a2 a1 -> r) -> r
- some4SingRep :: (SingKind k4, SingKind k3, SingKind k2, SingKind k1) => Some4 (f4 :: k4 -> k3 -> k2 -> k1 -> Type) -> (DemoteRep k4, DemoteRep k3, DemoteRep k2, DemoteRep k1)
- class Dict4 c f4 where
- class Dict0 c where
- data Constraint :: *
- data Dict a :: Constraint -> * where
1 type index
2 type indexes
_Some2 :: forall f2 a2 a1. (SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some2 f2) (f2 a2 a1) Source #
3 type indexes
_Some3 :: forall f3 a3 a2 a1. (SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some3 f3) (f3 a3 a2 a1) Source #
4 type indexes
_Some4 :: forall f4 a4 a3 a2 a1. (SingI a4, SDecide k4, SingI a3, SDecide k3, SingI a2, SDecide k2, SingI a1, SDecide k1) => Prism' (Some4 f4) (f4 a4 a3 a2 a1) Source #
Miscellaneous
Dict0 is a bit different from Dict1, Dict2, etc. in that it looks up
an instance for the singleton type itself, and not for some other type
indexed by said singleton type.
Minimal complete definition
Re-exports
data Constraint :: * #
The kind of constraints, like Show a
Instances
| Category Constraint (:-) | Possible since GHC 7.8, when |
data Dict a :: Constraint -> * where #
Values of type capture a dictionary for a constraint of type Dict pp.
e.g.
Dict::Dict(EqInt)
captures a dictionary that proves we have an:
instance Eq 'Int
Pattern matching on the Dict constructor will bring this instance into scope.
Instances
| a :=> (Read (Dict a)) | |
| a :=> (Monoid (Dict a)) | |
| a :=> (Enum (Dict a)) | |
| a :=> (Bounded (Dict a)) | |
| () :=> (Eq (Dict a)) | |
| () :=> (Ord (Dict a)) | |
| () :=> (Show (Dict a)) | |
| a => Bounded (Dict a) | |
| a => Enum (Dict a) | |
| Eq (Dict a) | |
| (Typeable Constraint p, p) => Data (Dict p) | |
| Ord (Dict a) | |
| a => Read (Dict a) | |
| Show (Dict a) | |
| a => Monoid (Dict a) | |