predicate-typed-0.7.0.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Refined

Contents

Description

Simple refinement type with only one type and a predicate

Synopsis

Refined

data Refined (opts :: OptT) p a Source #

a simple refinement type that ensures the predicate 'p' holds for the type 'a'

>>> prtRefinedIO @'OZ @(Between 10 14 Id) 13
Right (Refined 13)
>>> prtRefinedIO @'OZ @(Between 10 14 Id) 99
Left FalseP
>>> prtRefinedIO @'OZ @(Last Id >> Len == 4) ["one","two","three","four"]
Right (Refined ["one","two","three","four"])
>>> prtRefinedIO @'OZ @(Re "^\\d{1,3}\\.\\d{1,3}\\.\\d{1,3}\\.\\d{1,3}$" Id) "141.213.1.99"
Right (Refined "141.213.1.99")
>>> prtRefinedIO @'OZ @(Re "^\\d{1,3}\\.\\d{1,3}\\.\\d{1,3}\\.\\d{1,3}$" Id) "141.213.1"
Left FalseP
>>> prtRefinedIO @'OZ @(Map (ReadP Int Id) (Resplit "\\." Id) >> Guard (PrintF "bad length: found %d" Len) (Len == 4) >> 'True) "141.213.1"
Left (FailP "bad length: found 3")
>>> prtRefinedIO @'OZ @(Map (ReadP Int Id) (Resplit "\\." Id) >> Guard (PrintF "bad length: found %d" Len) (Len == 4) >> GuardsN (PrintT "octet %d out of range %d" Id) 4 (Between 0 255 Id) >> 'True) "141.213.1.444"
Left (FailP "octet 3 out of range 444")
>>> prtRefinedIO @'OZ @(Map (ReadP Int Id) (Resplit "\\." Id) >> Guard (PrintF "bad length: found %d" Len) (Len == 4) >> GuardsN (PrintT "octet %d out of range %d" Id) 4 (Between 0 255 Id) >> 'True) "141.213.1x34.444"
Left (FailP "ReadP Int (1x34)")
>>> prtRefinedIO @'OZ @(Map ('[Id] >> ReadP Int Id) Id >> Luhn Id) "12344"
Right (Refined "12344")
>>> prtRefinedIO @'OZ @(Map ('[Id] >> ReadP Int Id) Id >> Luhn Id) "12340"
Left FalseP
>>> prtRefinedIO @'OZ @(Any (Prime Id) Id) [11,13,17,18]
Right (Refined [11,13,17,18])
>>> prtRefinedIO @'OZ @(All (Prime Id) Id) [11,13,17,18]
Left FalseP
>>> prtRefinedIO @'OZ @(Snd Id !! Fst Id >> Len > 5) (2,["abc","defghij","xyzxyazsfd"])
Right (Refined (2,["abc","defghij","xyzxyazsfd"]))
>>> prtRefinedIO @'OZ @(Snd Id !! Fst Id >> Len > 5) (27,["abc","defghij","xyzxyazsfd"])
Left (FailP "(!!) index not found")
>>> prtRefinedIO @'OZ @(Snd Id !! Fst Id >> Len <= 5) (2,["abc","defghij","xyzxyazsfd"])
Left FalseP
Instances
Eq a => Eq (Refined opts p a) Source # 
Instance details

Defined in Predicate.Refined

Methods

(==) :: Refined opts p a -> Refined opts p a -> Bool #

(/=) :: Refined opts p a -> Refined opts p a -> Bool #

(RefinedC opts p a, Read a) => Read (Refined opts p a) Source #

Read instance for Refined

>>> reads @(Refined 'OZ (Between 0 255 Id) Int) "Refined 254"
[(Refined 254,"")]
>>> reads @(Refined 'OZ (Between 0 255 Id) Int) "Refined 300"
[]
>>> reads @(Refined 'OZ 'True Int) "Refined (-123)xyz"
[(Refined (-123),"xyz")]
Instance details

Defined in Predicate.Refined

Methods

readsPrec :: Int -> ReadS (Refined opts p a) #

readList :: ReadS [Refined opts p a] #

readPrec :: ReadPrec (Refined opts p a) #

readListPrec :: ReadPrec [Refined opts p a] #

Show a => Show (Refined opts p a) Source # 
Instance details

Defined in Predicate.Refined

Methods

showsPrec :: Int -> Refined opts p a -> ShowS #

show :: Refined opts p a -> String #

showList :: [Refined opts p a] -> ShowS #

RefinedC opts p String => IsString (Refined opts p String) Source # 
Instance details

Defined in Predicate.Refined

Methods

fromString :: String -> Refined opts p String #

Generic (Refined opts p a) Source # 
Instance details

Defined in Predicate.Refined

Associated Types

type Rep (Refined opts p a) :: Type -> Type #

Methods

from :: Refined opts p a -> Rep (Refined opts p a) x #

to :: Rep (Refined opts p a) x -> Refined opts p a #

Lift a => Lift (Refined opts p a) Source # 
Instance details

Defined in Predicate.Refined

Methods

lift :: Refined opts p a -> Q Exp #

(Arbitrary a, RefinedC opts p a, Show a) => Arbitrary (Refined opts p a) Source # 
Instance details

Defined in Predicate.Refined

Methods

arbitrary :: Gen (Refined opts p a) #

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

(RefinedC opts p a, Hashable a) => Hashable (Refined opts p a) Source #

Hashable instance for Refined

Instance details

Defined in Predicate.Refined

Methods

hashWithSalt :: Int -> Refined opts p a -> Int #

hash :: Refined opts p a -> Int #

ToJSON a => ToJSON (Refined opts p a) Source #

ToJSON instance for Refined

Instance details

Defined in Predicate.Refined

Methods

toJSON :: Refined opts p a -> Value #

toEncoding :: Refined opts p a -> Encoding #

toJSONList :: [Refined opts p a] -> Value #

toEncodingList :: [Refined opts p a] -> Encoding #

(RefinedC opts p a, FromJSON a) => FromJSON (Refined opts p a) Source #

FromJSON instance for Refined

>>> :set -XOverloadedStrings
>>> import qualified Data.Aeson as A
>>> A.eitherDecode' @(Refined 'OZ (Between 10 14 Id) Int) "13"
Right (Refined 13)
>>> removeAnsi $ A.eitherDecode' @(Refined 'OAN (Between 10 14 Id) Int) "16"
Error in $: Refined(FromJSON:parseJSON):FalseT (16 <= 14)
False 16 <= 14
|
+- P Id 16
|
+- P '10
|
`- P '14

Instance details

Defined in Predicate.Refined

Methods

parseJSON :: Value -> Parser (Refined opts p a) #

parseJSONList :: Value -> Parser [Refined opts p a] #

(RefinedC opts p a, Binary a) => Binary (Refined opts p a) Source #

Binary instance for Refined

>>> import Data.Time
>>> import Control.Lens
>>> import Control.Arrow ((+++))
>>> type K1 = Refined 'OZ (ReadP Day Id >> 'True) String
>>> type K2 = Refined 'OAN (Between (ReadP Day "2019-05-30") (ReadP Day "2019-06-01") (ReadP Day Id)) String
>>> r = unsafeRefined' @'OZ "2019-04-23" :: K1
>>> removeAnsi $ (view _3 +++ view _3) $ B.decodeOrFail @K1 (B.encode r)
Refined "2019-04-23"
>>> removeAnsi $ (view _3 +++ view _3) $ B.decodeOrFail @K2 (B.encode r)
Refined(Binary:get):FalseT (2019-05-30 <= 2019-04-23)
False 2019-05-30 <= 2019-04-23
|
+- P ReadP Day 2019-04-23
|  |
|  `- P Id "2019-04-23"
|
+- P ReadP Day 2019-05-30
|  |
|  `- P '2019-05-30
|
`- P ReadP Day 2019-06-01
   |
   `- P '2019-06-01

Instance details

Defined in Predicate.Refined

Methods

put :: Refined opts p a -> Put #

get :: Get (Refined opts p a) #

putList :: [Refined opts p a] -> Put #

type Rep (Refined opts p a) Source # 
Instance details

Defined in Predicate.Refined

type Rep (Refined opts p a) = D1 (MetaData "Refined" "Predicate.Refined" "predicate-typed-0.7.0.0-9zIXwd1Xbt13UmNvrtEi6S" True) (C1 (MetaCons "Refined" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

unRefined :: forall k (opts :: OptT) (p :: k) a. Refined opts p a -> a Source #

extract the value from Refined

type RefinedC opts p a = (OptTC opts, PP p a ~ Bool, P p a) Source #

the constraints that Refined must adhere to

newRefined :: forall opts p a. RefinedC opts p a => a -> Either String (Refined opts p a) Source #

returns a Refined value if 'a' is valid for the predicate 'p'

>>> newRefined @'OL @(ReadP Int Id > 99) "123"
Right (Refined "123")
>>> newRefined @'OL @(ReadP Int Id > 99) "12"
Left "FalseT (12 > 99)"

newRefinedM :: forall opts p a m. (MonadEval m, RefinedC opts p a) => a -> m ((String, (String, String)), Maybe (Refined opts p a)) Source #

newtype RefinedT m a Source #

effect wrapper for the refinement value

Constructors

RefinedT 
Instances
MonadTrans RefinedT Source # 
Instance details

Defined in Predicate.Refined

Methods

lift :: Monad m => m a -> RefinedT m a #

Monad m => MonadError String (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

throwError :: String -> RefinedT m a #

catchError :: RefinedT m a -> (String -> RefinedT m a) -> RefinedT m a #

Monad m => Monad (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

(>>=) :: RefinedT m a -> (a -> RefinedT m b) -> RefinedT m b #

(>>) :: RefinedT m a -> RefinedT m b -> RefinedT m b #

return :: a -> RefinedT m a #

fail :: String -> RefinedT m a #

Functor m => Functor (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

fmap :: (a -> b) -> RefinedT m a -> RefinedT m b #

(<$) :: a -> RefinedT m b -> RefinedT m a #

Monad m => Applicative (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

pure :: a -> RefinedT m a #

(<*>) :: RefinedT m (a -> b) -> RefinedT m a -> RefinedT m b #

liftA2 :: (a -> b -> c) -> RefinedT m a -> RefinedT m b -> RefinedT m c #

(*>) :: RefinedT m a -> RefinedT m b -> RefinedT m b #

(<*) :: RefinedT m a -> RefinedT m b -> RefinedT m a #

MonadIO m => MonadIO (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

liftIO :: IO a -> RefinedT m a #

MonadCont m => MonadCont (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

callCC :: ((a -> RefinedT m b) -> RefinedT m a) -> RefinedT m a #

Monad m => MonadWriter [String] (RefinedT m) Source # 
Instance details

Defined in Predicate.Refined

Methods

writer :: (a, [String]) -> RefinedT m a #

tell :: [String] -> RefinedT m () #

listen :: RefinedT m a -> RefinedT m (a, [String]) #

pass :: RefinedT m (a, [String] -> [String]) -> RefinedT m a #

(Show1 m, Show a) => Show (RefinedT m a) Source # 
Instance details

Defined in Predicate.Refined

Methods

showsPrec :: Int -> RefinedT m a -> ShowS #

show :: RefinedT m a -> String #

showList :: [RefinedT m a] -> ShowS #

print methods

prtRefinedIO :: forall opts p a. RefinedC opts p a => a -> IO (Either BoolP (Refined opts p a)) Source #

same as newRefined but prints the results

prtRefinedTIO :: (MonadIO m, Show a) => RefinedT m a -> m () Source #

create methods

withRefinedT :: forall opts p m a b. (Monad m, RefinedC opts p a) => a -> (Refined opts p a -> RefinedT m b) -> RefinedT m b Source #

invokes the callback with the Refined value if 'a' is valid for the predicate 'p'

withRefinedTIO :: forall opts p m a b. (MonadIO m, RefinedC opts p a) => a -> (Refined opts p a -> RefinedT m b) -> RefinedT m b Source #

IO version of withRefinedT

newRefinedT :: forall m opts p a. (RefinedC opts p a, Monad m) => a -> RefinedT m (Refined opts p a) Source #

returns a wrapper RefinedT around a possible Refined value if 'a' is valid for the predicate 'p'

newRefinedTIO :: forall opts p a m. (RefinedC opts p a, MonadIO m) => a -> RefinedT m (Refined opts p a) Source #

IO version of newRefinedT

QuickCheck method

genRefined :: forall opts p a. RefinedC opts p a => Gen a -> Gen (Refined opts p a) Source #

arbitrary value for Refined

manipulate RefinedT values

convertRefinedT :: forall m opts p a p1 a1. (RefinedC opts p1 a1, Monad m) => (a -> a1) -> RefinedT m (Refined opts p a) -> RefinedT m (Refined opts p1 a1) Source #

attempts to lift a refinement type to another refinement type by way of transformation function you can control both the predicate and the type

unRavelT :: RefinedT m a -> m (Either String a, [String]) Source #

unwrap the RefinedT value

rapply :: forall m opts p a. (RefinedC opts p a, Monad m) => (a -> a -> a) -> RefinedT m (Refined opts p a) -> RefinedT m (Refined opts p a) -> RefinedT m (Refined opts p a) Source #

binary operation applied to two RefinedT values

rapply0 :: forall opts p a m. (RefinedC opts p a, Monad m) => (a -> a -> a) -> a -> a -> RefinedT m (Refined opts p a) Source #

takes two values and lifts them into RefinedT and then applies the binary operation

rapplyLift :: forall m opts p a. (RefinedC opts p a, Monad m) => (a -> a -> a) -> Refined opts p a -> Refined opts p a -> RefinedT m (Refined opts p a) Source #

same as rapply except we already have valid Refined values as input

unsafe create methods

unsafeRefined :: forall opts p a. a -> Refined opts p a Source #

create an unsafe Refined value without running the predicate

unsafeRefined' :: forall opts p a. (RefinedC opts p a, HasCallStack) => a -> Refined opts p a Source #

create an unsafe Refined value and also run the predicate

type family ReplaceOptT (o :: OptT) t where ... Source #

Equations

ReplaceOptT o (Refined _ p a) = Refined o p a 

type family AppendOptT (o :: OptT) t where ... Source #

Equations

AppendOptT o (Refined o' p a) = Refined (o' :# o) p a