refined-0.3.0.0: Refinement types with static and runtime checking

Safe HaskellNone
LanguageHaskell2010

Refined.Unsafe

Contents

Description

This module exposes unsafe refinements. An unsafe refinement is one which either does not make the guarantee of totality in construction of the Refined value or does not perform a check of the refinement predicate. It is recommended only to use this when you can manually prove that the refinement predicate holds.

Synopsis

Refined

data Refined p x Source #

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

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 #

Creation

reallyUnsafeRefine :: x -> Refined p x Source #

Constructs a Refined value, completely ignoring any refinements! Use this only when you can manually prove that the refinement holds.

unsafeRefine :: Predicate p x => x -> Refined p x Source #

Constructs a Refined value at run-time, calling error if the value does not satisfy the predicate.

WARNING: this function is not total!

Coercion

reallyUnsafeUnderlyingRefined :: Coercion x (Refined p x) Source #

A coercion between a type and any refinement of that type. See Data.Type.Coercion for functions manipulating coercions.

reallyUnsafePredEquiv :: Coercion (Refined p x) (Refined q x) Source #

A coercion between two Refined types, magicking up the claim that one predicate is entirely equivalent to another.