Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Refined.Unsafe.Type
Description
This module exports the Refined
type with its
constructor. This is very risky! In particular, the Coercible
instances will be visible throughout the importing module.
It is usually better to build the necessary coercions locally
using the utilities in Refined.Unsafe, but in some cases
it may be more convenient to write a separate module that
imports this one and exports some large coercion.
Documentation
newtype Refined (p :: k) x Source #
A refinement type, which wraps a value of type x
.
Since: 0.1.0.0
Constructors
Refined x | Since: 0.1.0.0 |
Instances
newtype Refined1 (p :: k) f x Source #
A refinement type, which wraps a value of type f x
.
The predicate is applied over the functor f
. Thus, we may safely recover
various Functor
y instances, because no matter what you do to the
values inside the functor, the predicate may not be invalidated.
Constructors
Refined1 (f x) |
Instances
Lift (f a) => Lift (Refined1 p f a :: Type) Source # | |
Foldable f => Foldable (Refined1 p f) Source # | |
Defined in Refined.Unsafe.Type Methods fold :: Monoid m => Refined1 p f m -> m Source # foldMap :: Monoid m => (a -> m) -> Refined1 p f a -> m Source # foldMap' :: Monoid m => (a -> m) -> Refined1 p f a -> m Source # foldr :: (a -> b -> b) -> b -> Refined1 p f a -> b Source # foldr' :: (a -> b -> b) -> b -> Refined1 p f a -> b Source # foldl :: (b -> a -> b) -> b -> Refined1 p f a -> b Source # foldl' :: (b -> a -> b) -> b -> Refined1 p f a -> b Source # foldr1 :: (a -> a -> a) -> Refined1 p f a -> a Source # foldl1 :: (a -> a -> a) -> Refined1 p f a -> a Source # toList :: Refined1 p f a -> [a] Source # null :: Refined1 p f a -> Bool Source # length :: Refined1 p f a -> Int Source # elem :: Eq a => a -> Refined1 p f a -> Bool Source # maximum :: Ord a => Refined1 p f a -> a Source # minimum :: Ord a => Refined1 p f a -> a Source # | |
Traversable f => Traversable (Refined1 p f) Source # | |
Defined in Refined.Unsafe.Type Methods traverse :: Applicative f0 => (a -> f0 b) -> Refined1 p f a -> f0 (Refined1 p f b) Source # sequenceA :: Applicative f0 => Refined1 p f (f0 a) -> f0 (Refined1 p f a) Source # mapM :: Monad m => (a -> m b) -> Refined1 p f a -> m (Refined1 p f b) Source # sequence :: Monad m => Refined1 p f (m a) -> m (Refined1 p f a) Source # | |
Functor f => Functor (Refined1 p f) Source # | |
Show (f x) => Show (Refined1 p f x) Source # | |
NFData (f x) => NFData (Refined1 p f x) Source # | |
Defined in Refined.Unsafe.Type | |
Eq (f x) => Eq (Refined1 p f x) Source # | |
Ord (f x) => Ord (Refined1 p f x) Source # | |
Defined in Refined.Unsafe.Type Methods compare :: Refined1 p f x -> Refined1 p f x -> Ordering Source # (<) :: Refined1 p f x -> Refined1 p f x -> Bool Source # (<=) :: Refined1 p f x -> Refined1 p f x -> Bool Source # (>) :: Refined1 p f x -> Refined1 p f x -> Bool Source # (>=) :: Refined1 p f x -> Refined1 p f x -> Bool Source # max :: Refined1 p f x -> Refined1 p f x -> Refined1 p f x Source # min :: Refined1 p f x -> Refined1 p f x -> Refined1 p f x Source # | |
Hashable (f x) => Hashable (Refined1 p f x) Source # | |