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

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

Refined3

Description

see Refined3 contains Json and Read instances and arbitrary functions

Synopsis

Documentation

data Refined3 ip op fmt i Source #

Refinement type that differentiates the input type from output type

'i' is the input type
'ip' converts i to PP ip i which is the internal type
'op' validates that internal type using PP op (PP ip i) ~ Bool
'fmt' outputs the internal type PP fmt (PP ip i) ~ i
PP fmt (PP ip i) should be valid input to Refined3

If we fix the input type to String then it looks similar to: 1. read into an internal type 2. validate internal type with a predicate function 3. show/format the internal type

Although the most common scenario is String as input, you are free to choose any input type you like

>>> :m + Data.Time.Calendar.WeekDate
>>> prtEval3 @(ReadBase Int 16) @(Lt 255) @(Printf "%x" Id) ol "00fe"
Right (Refined3 {r3In = 254, r3Out = "fe"})
>>> prtEval3 @(ReadBase Int 16) @(Lt 253) @(Printf "%x" Id) ol "00fe"
Left Step 2. False Boolean Check(op) | FalseP
>>> prtEval3 @(ReadBase Int 16) @(Lt 255) @(Printf "%x" Id) ol "00fg"
Left Step 1. Initial Conversion(ip) Failed | invalid base 16
>>> prtEval3 @(Map (ReadP Int) (Resplit "\\." Id)) @(Guard (Printf "found length=%d" Len) (Len >> Id == 4) >> 'True) @(Printfnt 4 "%03d.%03d.%03d.%03d") ol "198.162.3.1.5"
Left Step 2. Failed Boolean Check(op) | found length=5
>>> prtEval3 @(Map (ReadP Int) (Resplit "\\." Id)) @(Guard (Printf "found length=%d" Len) (Len >> Id == 4) >> 'True) @(Printfnt 4 "%03d.%03d.%03d.%03d") ol "198.162.3.1"
Right (Refined3 {r3In = [198,162,3,1], r3Out = "198.162.003.001"})
>>> prtEval3 @(MkDay >> 'Just Id) @(Guard "expected a Sunday" (Thd Id == 7) >> 'True) @(UnMkDay (Fst Id)) ol (2019,10,13)
Right (Refined3 {r3In = (2019-10-13,41,7), r3Out = (2019,10,13)})
>>> prtEval3 @(MkDay' (Fst Id) (Snd Id) (Thd Id) >> 'Just Id) @(Guard "expected a Sunday" (Thd Id == 7) >> 'True) @(UnMkDay (Fst Id)) ol (2019,10,12)
Left Step 2. Failed Boolean Check(op) | expected a Sunday
>>> type T4 k = '(MkDay >> 'Just Id, Guard "expected a Sunday" (Thd Id == 7) >> 'True, UnMkDay (Fst Id), k)
>>> prtEval3P (Proxy @(T4 _)) ol (2019,10,12)
Left Step 2. Failed Boolean Check(op) | expected a Sunday
>>> prtEval3P (Proxy @(T4 _)) ol (2019,10,13)
Right (Refined3 {r3In = (2019-10-13,41,7), r3Out = (2019,10,13)})
Instances
(Eq i, Eq (PP ip i), Eq (PP fmt (PP ip i))) => Eq (Refined3 ip op fmt i) Source # 
Instance details

Defined in Refined3

Methods

(==) :: Refined3 ip op fmt i -> Refined3 ip op fmt i -> Bool #

(/=) :: Refined3 ip op fmt i -> Refined3 ip op fmt i -> Bool #

(Eq i, Show i, Show (PP ip i), Refined3C ip op fmt i, Read (PP ip i), Read (PP fmt (PP ip i))) => Read (Refined3 ip op fmt i) Source #

Read instance for Refined3

>>> :set -XOverloadedStrings
>>> reads @(Refined3 (ReadBase Int 16) (Between 0 255) (ShowBase 16) String) "Refined3 {r3In = 254, r3Out = \"fe\"}"
[(Refined3 {r3In = 254, r3Out = "fe"},"")]
>>> reads @(Refined3 (ReadBase Int 16) (Between 0 255) (ShowBase 16) String) "Refined3 {r3In = 300, r3Out = \"12c\"}"
[]
>>> reads @(Refined3 (ReadBase Int 16) (Id < 0) (ShowBase 16) String) "Refined3 {r3In = -1234, r3Out = \"-4d2\"}"
[(Refined3 {r3In = -1234, r3Out = "-4d2"},"")]
>>> reads @(Refined3 (Map (ReadP Int) (Resplit "\\." Id)) (Guard "len/=4" (Len == 4) >> 'True) (Printfnt 4 "%d.%d.%d.%d") String) "Refined3 {r3In = [192,168,0,1], r3Out = \"192.168.0.1\"}"
[(Refined3 {r3In = [192,168,0,1], r3Out = "192.168.0.1"},"")]
Instance details

Defined in Refined3

Methods

readsPrec :: Int -> ReadS (Refined3 ip op fmt i) #

readList :: ReadS [Refined3 ip op fmt i] #

readPrec :: ReadPrec (Refined3 ip op fmt i) #

readListPrec :: ReadPrec [Refined3 ip op fmt i] #

(Show i, Show (PP ip i), Show (PP fmt (PP ip i))) => Show (Refined3 ip op fmt i) Source # 
Instance details

Defined in Refined3

Methods

showsPrec :: Int -> Refined3 ip op fmt i -> ShowS #

show :: Refined3 ip op fmt i -> String #

showList :: [Refined3 ip op fmt i] -> ShowS #

(Lift (PP ip i), Lift (PP fmt (PP ip i))) => Lift (Refined3 ip op fmt i) Source # 
Instance details

Defined in Refined3

Methods

lift :: Refined3 ip op fmt i -> Q Exp #

ToJSON (PP fmt (PP ip i)) => ToJSON (Refined3 ip op fmt i) Source #

ToJSON instance for Refined3

>>> :set -XOverloadedStrings
>>> encode (unsafeRefined3 @(ReadBase Int 16) @(Between 0 255) @(ShowBase 16) 254 "fe")
"\"fe\""
>>> encode (unsafeRefined3 @Id @'True @Id 123 123)
"123"
Instance details

Defined in Refined3

Methods

toJSON :: Refined3 ip op fmt i -> Value #

toEncoding :: Refined3 ip op fmt i -> Encoding #

toJSONList :: [Refined3 ip op fmt i] -> Value #

toEncodingList :: [Refined3 ip op fmt i] -> Encoding #

(Show (PP fmt (PP ip i)), Show (PP ip i), Refined3C ip op fmt i, FromJSON i) => FromJSON (Refined3 ip op fmt i) Source #

FromJSON instance for Refined3

>>> :set -XOverloadedStrings
>>> eitherDecode' @(Refined3 (ReadBase Int 16) (Id > 10 && Id < 256) (ShowBase 16) String) "\"00fe\""
Right (Refined3 {r3In = 254, r3Out = "fe"})
>>> removeAnsiForDocTest $ eitherDecode' @(Refined3 (ReadBase Int 16) (Id > 10 && Id < 256) (ShowBase 16) String) "\"00fe443a\""
Error in $: Refined3:Step 2. False Boolean Check(op) | FalseP

*** Step 1. Success Initial Conversion(ip) [16663610] ***

P ReadBase(Int,16) 16663610 | "00fe443a"
|
`- P Id "00fe443a"

*** Step 2. False Boolean Check(op) ***

False True && False
|
+- True  16663610 > 10
|  |
|  +- P Id 16663610
|  |
|  `- P '10
|
`- False 16663610 < 256
   |
   +- P Id 16663610
   |
   `- P '256

Instance details

Defined in Refined3

Methods

parseJSON :: Value -> Parser (Refined3 ip op fmt i) #

parseJSONList :: Value -> Parser [Refined3 ip op fmt i] #

(Show (PP fmt (PP ip i)), Show (PP ip i), Refined3C ip op fmt i, Binary i) => Binary (Refined3 ip op fmt i) Source #

Binary instance for Refined3

>>> import Control.Arrow ((+++))
>>> import Control.Lens
>>> import Data.Time
>>> type K1 = MakeR3 '(ReadP Day, 'True, ShowP Id, String)
>>> type K2 = MakeR3 '(ReadP Day, Between (ReadP' Day "2019-03-30") (ReadP' Day "2019-06-01"), ShowP Id, String)
>>> type K3 = MakeR3 '(ReadP Day, Between (ReadP' Day "2019-05-30") (ReadP' Day "2019-06-01"), ShowP Id, String)
>>> r = unsafeRefined3' ol "2019-04-23" :: K1
>>> removeAnsiForDocTest $ (view _3 +++ view _3) $ B.decodeOrFail @K1 (B.encode r)
Refined3 {r3In = 2019-04-23, r3Out = "2019-04-23"}
>>> removeAnsiForDocTest $ (view _3 +++ view _3) $ B.decodeOrFail @K2 (B.encode r)
Refined3 {r3In = 2019-04-23, r3Out = "2019-04-23"}
>>> removeAnsiForDocTest $ (view _3 +++ view _3) $ B.decodeOrFail @K3 (B.encode r)
Refined3:Step 2. False Boolean Check(op) | FalseP

*** Step 1. Success Initial Conversion(ip) [2019-04-23] ***

P ReadP Day (2019-04-23) 2019-04-23 | 2019-04-23
|
`- P Id "2019-04-23"

*** Step 2. False Boolean Check(op) ***

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 Refined3

Methods

put :: Refined3 ip op fmt i -> Put #

get :: Get (Refined3 ip op fmt i) #

putList :: [Refined3 ip op fmt i] -> Put #

type Refined3C ip op fmt i = (P ip i, P op (PP ip i), PP op (PP ip i) ~ Bool, P fmt (PP ip i), PP fmt (PP ip i) ~ i) Source #

Provides the constraints on Refined3

mkProxy3 :: forall ip op fmt i. Refined3C ip op fmt i => Proxy '(ip, op, fmt, i) Source #

wraps the parameters for Refined3 in a 4-tuple for use with methods such as withRefined3TP and newRefined3TP

mkProxy3P :: forall z ip op fmt i. (z ~ '(ip, op, fmt, i), Refined3C ip op fmt i) => Proxy '(ip, op, fmt, i) Source #

use type application to set the parameters then it will be wrapped into a 4-tuple checks to make sure the proxy is consistent with Refined3C use for passing into eval3P you can pass in a promoted 4 tuple to other methods

type family MkProxy3T p where ... Source #

convenience type family for converting from a 4-tuple '(ip,op,fmt,i) to a Proxy

Equations

MkProxy3T '(ip, op, fmt, i) = Proxy '(ip, op, fmt, i) 

withRefined3TIO :: forall ip op fmt i m b. (MonadIO m, Refined3C ip op fmt i, Show (PP ip i), Show i) => POpts -> i -> (Refined3 ip op fmt i -> RefinedT m b) -> RefinedT m b Source #

withRefined3T :: forall ip op fmt i m b. (Monad m, Refined3C ip op fmt i, Show (PP ip i), Show i) => POpts -> i -> (Refined3 ip op fmt i -> RefinedT m b) -> RefinedT m b Source #

withRefined3TP :: forall ip op fmt i m b proxy. (Monad m, Refined3C ip op fmt i, Show (PP ip i), Show i) => proxy '(ip, op, fmt, i) -> POpts -> i -> (Refined3 ip op fmt i -> RefinedT m b) -> RefinedT m b Source #

newRefined3T :: forall m ip op fmt i. (Refined3C ip op fmt i, Monad m, Show (PP ip i), Show i) => POpts -> i -> RefinedT m (Refined3 ip op fmt i) Source #

newRefined3TP :: forall m ip op fmt i proxy. (Refined3C ip op fmt i, Monad m, Show (PP ip i), Show i) => proxy '(ip, op, fmt, i) -> POpts -> i -> RefinedT m (Refined3 ip op fmt i) Source #

newRefined3TPIO :: forall m ip op fmt i proxy. (Refined3C ip op fmt i, MonadIO m, Show (PP ip i), Show i) => proxy '(ip, op, fmt, i) -> POpts -> i -> RefinedT m (Refined3 ip op fmt i) Source #

convertRefined3T :: forall m ip op fmt i ip1 op1 fmt1 i1. (Refined3C ip1 op1 fmt1 i1, Monad m, Show (PP ip i), PP ip i ~ PP ip1 i1, Show i1) => POpts -> RefinedT m (Refined3 ip op fmt i) -> RefinedT m (Refined3 ip1 op1 fmt1 i1) Source #

convertRefined3TP :: forall m ip op fmt i ip1 op1 fmt1 i1. (Refined3C ip1 op1 fmt1 i1, Monad m, Show (PP ip i), PP ip i ~ PP ip1 i1, Show i1) => Proxy '(ip, op, fmt, i) -> Proxy '(ip1, op1, fmt1, i1) -> POpts -> RefinedT m (Refined3 ip op fmt i) -> RefinedT m (Refined3 ip1 op1 fmt1 i1) Source #

rapply3 :: forall m ip op fmt i. (Refined3C ip op fmt i, Monad m, Show (PP ip i), Show i) => POpts -> (PP ip i -> PP ip i -> PP ip i) -> RefinedT m (Refined3 ip op fmt i) -> RefinedT m (Refined3 ip op fmt i) -> RefinedT m (Refined3 ip op fmt i) Source #

rapply3P :: forall m ip op fmt i proxy. (Refined3C ip op fmt i, Monad m, Show (PP ip i), Show i) => proxy '(ip, op, fmt, i) -> POpts -> (PP ip i -> PP ip i -> PP ip i) -> RefinedT m (Refined3 ip op fmt i) -> RefinedT m (Refined3 ip op fmt i) -> RefinedT m (Refined3 ip op fmt i) Source #

prtEval3P :: forall ip op fmt i proxy. (Refined3C ip op fmt i, Show (PP ip i), Show i) => proxy '(ip, op, fmt, i) -> POpts -> i -> Either Msg3 (Refined3 ip op fmt i) Source #

prtEval3PIO :: forall ip op fmt i proxy. (Refined3C ip op fmt i, Show (PP ip i), Show i) => proxy '(ip, op, fmt, i) -> POpts -> i -> IO (Either String (Refined3 ip op fmt i)) Source #

prtEval3 :: forall ip op fmt i. (Refined3C ip op fmt i, Show (PP ip i), Show i) => POpts -> i -> Either Msg3 (Refined3 ip op fmt i) Source #

eval3P :: forall ip op fmt i proxy. Refined3C ip op fmt i => proxy '(ip, op, fmt, i) -> POpts -> i -> (RResults (PP ip i) (PP fmt (PP ip i)), Maybe (Refined3 ip op fmt i)) Source #

eval3 :: forall ip op fmt i. Refined3C ip op fmt i => POpts -> i -> (RResults (PP ip i) (PP fmt (PP ip i)), Maybe (Refined3 ip op fmt i)) Source #

eval3M :: forall m ip op fmt i. (MonadEval m, Refined3C ip op fmt i) => POpts -> i -> m (RResults (PP ip i) (PP fmt (PP ip i)), Maybe (Refined3 ip op fmt i)) Source #

eval3PX :: forall ip op fmt i proxy. Refined3C ip op fmt i => proxy '(ip, op, fmt, i) -> POpts -> i -> (RResults (PP ip i) (PP fmt (PP ip i)), Maybe (Refined op (PP ip i), PP fmt (PP ip i))) Source #

emulates Refined3 but uses Refined reuses the mkProxy3 but returns Refined vs Refined3 using plain Refined to emulate Refined3 sort of we just output fmt instead of embedding it in Refined3 so 'ip' predicate gets us started: we store that 'PP ip i' in Refined then we run the boolean predicate 'op' which is successful if true then we run 'fmt' against 'PP ip i' and output both the Refined (PP p i) and the PP fmt (PP (ip i)) ie 'fmt' run against PP ip i if any of the three steps fails the process stops immediately and dumps out RResults

eval3X :: forall ip op fmt i. Refined3C ip op fmt i => POpts -> i -> (RResults (PP ip i) (PP fmt (PP ip i)), Maybe (Refined op (PP ip i), PP fmt (PP ip i))) Source #

prt3IO :: (Show a, Show b) => POpts -> (RResults a b, Maybe r) -> IO (Either String r) Source #

prt3 :: (Show a, Show b) => POpts -> (RResults a b, Maybe r) -> Either Msg3 r Source #

arbRefined3 :: forall ip op fmt i. (Arbitrary (PP ip i), Refined3C ip op fmt i) => Proxy '(ip, op, fmt, i) -> POpts -> Gen (Refined3 ip op fmt i) Source #

arbRefined3With :: forall ip op fmt i. (Arbitrary (PP ip i), Refined3C ip op fmt i) => Proxy '(ip, op, fmt, i) -> POpts -> (PP ip i -> PP ip i) -> Gen (Refined3 ip op fmt i) Source #

data Msg3 Source #

Constructors

Msg3 
Instances
Eq Msg3 Source # 
Instance details

Defined in Refined3

Methods

(==) :: Msg3 -> Msg3 -> Bool #

(/=) :: Msg3 -> Msg3 -> Bool #

Show Msg3 Source # 
Instance details

Defined in Refined3

Methods

showsPrec :: Int -> Msg3 -> ShowS #

show :: Msg3 -> String #

showList :: [Msg3] -> ShowS #

prt3Impl :: (Show a, Show b) => POpts -> RResults a b -> Msg3 Source #

type family MakeR3 p where ... Source #

convenience type family for converting from a 4-tuple '(ip,op,fmt,i) to a Refined3 signature

Equations

MakeR3 '(ip, op, fmt, i) = Refined3 ip op fmt i 

data Results a b Source #

Constructors

XF String 
XTF a String 
XTFalse a 
XTTrueF a String 
XTTrueT a b 
Instances
(Eq a, Eq b) => Eq (Results a b) Source # 
Instance details

Defined in Refined3

Methods

(==) :: Results a b -> Results a b -> Bool #

(/=) :: Results a b -> Results a b -> Bool #

(Show a, Show b) => Show (Results a b) Source # 
Instance details

Defined in Refined3

Methods

showsPrec :: Int -> Results a b -> ShowS #

show :: Results a b -> String #

showList :: [Results a b] -> ShowS #

data RResults a b Source #

Constructors

RF String (Tree PE) 
RTF a (Tree PE) String (Tree PE) 
RTFalse a (Tree PE) (Tree PE) 
RTTrueF a (Tree PE) (Tree PE) String (Tree PE) 
RTTrueT a (Tree PE) (Tree PE) b (Tree PE) 
Instances
(Show a, Show b) => Show (RResults a b) Source # 
Instance details

Defined in Refined3

Methods

showsPrec :: Int -> RResults a b -> ShowS #

show :: RResults a b -> String #

showList :: [RResults a b] -> ShowS #

unsafeRefined3 :: forall ip op fmt i. PP ip i -> PP fmt (PP ip i) -> Refined3 ip op fmt i Source #

directly load values into Refined3 without any checking

unsafeRefined3' :: forall ip op fmt i. (Show i, Show (PP ip i), Refined3C ip op fmt i) => POpts -> i -> Refined3 ip op fmt i Source #

directly load values into Refined3. It still checks to see that those values are valid