Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Synopsis
- data Nat
- type N0 = Z
- type N1 = S N0
- type N2 = S N1
- type N3 = S N2
- type N4 = S N3
- type N5 = S N4
- type N6 = S N5
- type N7 = S N6
- type N8 = S N7
- type N9 = S N8
- type N10 = S N9
- data SNat :: Nat -> * where
- type family n1 + n2 where ...
- plus_id_r :: SNat n -> (n + Z) :~: n
- plus_succ_r :: SNat n1 -> Proxy n2 -> (n1 + S n2) :~: S (n1 + n2)
- gcastWith :: (a :~: b) -> ((a ~ b) -> r) -> r
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
- type LitNat = Nat
- type family U (n :: Nat) :: Nat where ...
Documentation
Instances
Eq Nat Source # | |
Data Nat Source # | |
Defined in Numerical.Nat gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Nat -> c Nat # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Nat # dataTypeOf :: Nat -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Nat) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nat) # gmapT :: (forall b. Data b => b -> b) -> Nat -> Nat # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nat -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nat -> r # gmapQ :: (forall d. Data d => d -> u) -> Nat -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Nat -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Nat -> m Nat # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Nat -> m Nat # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Nat -> m Nat # | |
Read Nat Source # | |
Show Nat Source # | |
gcastWith :: (a :~: b) -> ((a ~ b) -> r) -> r #
Generalized form of type-safe cast using propositional equality
data Proxy (t :: k) :: forall k. k -> Type #
Proxy
is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically,
is a safer alternative to the
Proxy
:: Proxy
a'undefined :: a'
idiom.
>>>
Proxy :: Proxy (Void, Int -> Int)
Proxy
Proxy can even hold types of higher kinds,
>>>
Proxy :: Proxy Either
Proxy
>>>
Proxy :: Proxy Functor
Proxy
>>>
Proxy :: Proxy complicatedStructure
Proxy
Instances
Generic1 (Proxy :: k -> Type) | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Foldable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Eq1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Ord1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
Bounded (Proxy t) | Since: base-4.7.0.0 |
Enum (Proxy s) | Since: base-4.7.0.0 |
Eq (Proxy s) | Since: base-4.7.0.0 |
Data t => Data (Proxy t) | Since: base-4.7.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) # toConstr :: Proxy t -> Constr # dataTypeOf :: Proxy t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) # gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r # gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) # | |
Ord (Proxy s) | Since: base-4.7.0.0 |
Read (Proxy t) | Since: base-4.7.0.0 |
Show (Proxy s) | Since: base-4.7.0.0 |
Ix (Proxy s) | Since: base-4.7.0.0 |
Generic (Proxy t) | |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
type Rep (Proxy t) | Since: base-4.6.0.0 |