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

Copyright(c) Grant Weyburne 2019
LicenseBSD-3
Maintainergbwey9@gmail.com
Safe HaskellNone
LanguageHaskell2010

Refined

Description

 
Synopsis

Documentation

data Refined p a Source #

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

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

Defined in Refined

Methods

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

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

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

Read instance for Refined

>>> :set -XOverloadedStrings
>>> reads @(Refined (Between 0 255) Int) "Refined {unRefined = 254}"
[(Refined {unRefined = 254},"")]
>>> reads @(Refined (Between 0 255) Int) "Refined {unRefined = 300}"
[]
Instance details

Defined in Refined

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

Defined in Refined

Methods

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

show :: Refined p a -> String #

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

Generic (Refined p a) Source # 
Instance details

Defined in Refined

Associated Types

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

Methods

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

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

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

Defined in Refined

Methods

lift :: Refined p a -> Q Exp #

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

ToJSON instance for Refined

Instance details

Defined in Refined

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

FromJSON instance for Refined

>>> :set -XOverloadedStrings
>>> eitherDecode' @(Refined (Between 10 14) Int) "13"
Right (Refined {unRefined = 13})
>>> removeAnsiForDocTest $ eitherDecode' @(Refined (Between 10 14) Int) "16"
Error in $: Refined:FalseP
False True && False
|
+- True  16 >= 10
|  |
|  +- P I
|  |
|  `- P '10
|
`- False 16 <= 14
   |
   +- P I
   |
   `- P '14

Instance details

Defined in Refined

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

Binary instance for Refined

>>> import Data.Time
>>> import Control.Lens
>>> import Control.Arrow ((+++))
>>> type K1 = Refined (ReadP Day >> 'True) String
>>> type K2 = Refined (ReadP Day >> Between (ReadP' Day "2019-03-30") (ReadP' Day "2019-06-01")) String
>>> type K3 = Refined (ReadP Day >> Between (ReadP' Day "2019-05-30") (ReadP' Day "2019-06-01")) String
>>> r = unsafeRefined' ol "2019-04-23" :: K1
>>> removeAnsiForDocTest $ (view _3 +++ view _3) $ B.decodeOrFail @K1 (B.encode r)
Refined {unRefined = "2019-04-23"}
>>> removeAnsiForDocTest $ (view _3 +++ view _3) $ B.decodeOrFail @K2 (B.encode r)
Refined {unRefined = "2019-04-23"}
>>> removeAnsiForDocTest $ (view _3 +++ view _3) $ B.decodeOrFail @K3 (B.encode r)
Refined:FalseP
False >> False | 2019-04-23
|
+- P ReadP Day (2019-04-23) 2019-04-23 | 2019-04-23
|  |
|  `- P Id "2019-04-23"
|
`- False False && True
   |
   +- False 2019-04-23 >= 2019-05-30
   |  |
   |  +- P I
   |  |
   |  `- P ReadP Day (2019-05-30) 2019-05-30 | 2019-05-30
   |     |
   |     `- P '2019-05-30
   |
   `- True  2019-04-23 <= 2019-06-01
      |
      +- P I
      |
      `- P ReadP Day (2019-06-01) 2019-06-01 | 2019-06-01
         |
         `- P '2019-06-01

Instance details

Defined in Refined

Methods

put :: Refined p a -> Put #

get :: Get (Refined p a) #

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

type Rep (Refined p a) Source # 
Instance details

Defined in Refined

type Rep (Refined p a) = D1 (MetaData "Refined" "Refined" "predicate-typed-0.1.0.4-FwDbL64GFQGFmDmmgFiEGh" True) (C1 (MetaCons "Refined" PrefixI True) (S1 (MetaSel (Just "unRefined") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

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

the constraints that Refined must adhere to

arbRefined :: forall p a. (Arbitrary a, RefinedC p a) => POpts -> Gen (Refined p a) Source #

arbitrary value for Refined

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

binary operation applied to two RefinedT values

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

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

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

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

convertRefinedT :: forall m p p1 a a1. (RefinedC p1 a1, Monad m) => POpts -> (a -> a1) -> RefinedT m (Refined p a) -> RefinedT m (Refined 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

withRefinedT :: forall p m a b. (Monad m, RefinedC p a) => POpts -> a -> (Refined 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 p m a b. (MonadIO m, RefinedC p a) => POpts -> a -> (Refined p a -> RefinedT m b) -> RefinedT m b Source #

newRefined :: forall p a m. (MonadEval m, RefinedC p a) => POpts -> a -> m ((BoolP, String), Maybe (Refined p a)) Source #

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

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

same as newRefined but prints the results

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

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

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

newtype RefinedT m a Source #

Constructors

RefinedT 
Instances
MonadTrans RefinedT Source # 
Instance details

Defined in Refined

Methods

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

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

Defined in 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 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 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 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 Refined

Methods

liftIO :: IO a -> RefinedT m a #

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

Defined in Refined

Methods

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

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

Defined in 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 Refined

Methods

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

show :: RefinedT m a -> String #

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

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

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

a way to unsafely create a Refined value

unsafeRefined' :: forall p a. RefinedC p a => POpts -> a -> Refined p a Source #

a way to unsafely create a Refined value but run the predicate