refined-0.4.3: Refinement types with static and runtime checking

Safe HaskellNone
LanguageHaskell2010

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.

Synopsis

Documentation

newtype Refined p x Source #

A refinement type, which wraps a value of type x, ensuring that it satisfies a type-level predicate p.

Constructors

Refined x 
Instances
Foldable (Refined p) Source # 
Instance details

Defined in Refined.Internal

Methods

fold :: Monoid m => Refined p m -> m #

foldMap :: Monoid m => (a -> m) -> Refined p a -> m #

foldr :: (a -> b -> b) -> b -> Refined p a -> b #

foldr' :: (a -> b -> b) -> b -> Refined p a -> b #

foldl :: (b -> a -> b) -> b -> Refined p a -> b #

foldl' :: (b -> a -> b) -> b -> Refined p a -> b #

foldr1 :: (a -> a -> a) -> Refined p a -> a #

foldl1 :: (a -> a -> a) -> Refined p a -> a #

toList :: Refined p a -> [a] #

null :: Refined p a -> Bool #

length :: Refined p a -> Int #

elem :: Eq a => a -> Refined p a -> Bool #

maximum :: Ord a => Refined p a -> a #

minimum :: Ord a => Refined p a -> a #

sum :: Num a => Refined p a -> a #

product :: Num a => Refined p a -> a #

Eq x => Eq (Refined p x) Source # 
Instance details

Defined in Refined.Internal

Methods

(==) :: Refined p x -> Refined p x -> Bool #

(/=) :: Refined p x -> Refined p x -> Bool #

Ord x => Ord (Refined p x) Source # 
Instance details

Defined in Refined.Internal

Methods

compare :: Refined p x -> Refined p x -> Ordering #

(<) :: Refined p x -> Refined p x -> Bool #

(<=) :: Refined p x -> Refined p x -> Bool #

(>) :: Refined p x -> Refined p x -> Bool #

(>=) :: Refined p x -> Refined p x -> Bool #

max :: Refined p x -> Refined p x -> Refined p x #

min :: Refined p x -> Refined p x -> Refined p x #

(Read x, Predicate p x) => Read (Refined p x) Source #

This instance makes sure to check the refinement.

Instance details

Defined in Refined.Internal

Show x => Show (Refined p x) Source # 
Instance details

Defined in Refined.Internal

Methods

showsPrec :: Int -> Refined p x -> ShowS #

show :: Refined p x -> String #

showList :: [Refined p x] -> ShowS #

Lift x => Lift (Refined p x) Source # 
Instance details

Defined in Refined.Internal

Methods

lift :: Refined p x -> Q Exp #

(Arbitrary a, Typeable a, Typeable p, Predicate p a) => Arbitrary (Refined p a) Source # 
Instance details

Defined in Refined.Orphan.QuickCheck

Methods

arbitrary :: Gen (Refined p a) #

shrink :: Refined p a -> [Refined p a] #

(ToJSON a, Predicate p a) => ToJSON (Refined p a) Source # 
Instance details

Defined in Refined.Orphan.Aeson

(FromJSON a, Predicate p a) => FromJSON (Refined p a) Source # 
Instance details

Defined in Refined.Orphan.Aeson