predicate-typed-0.7.4.3: Predicates, Refinement types and Dsl
Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Extra

Description

extra promoted functions

Synopsis

list functions

data HeadDef p q Source #

takes the head of a list-like object or uses the given default value

see ConsT for other supported types eg Seq

>>> pz @(HeadDef 444 Id) []
Val 444
>>> pz @(HeadDef 444 Id) [1..5]
Val 1
>>> pz @(HeadDef 444 Id) [1..5]
Val 1
>>> pz @(HeadDef (C "w") Id) (Seq.fromList "abcdef")
Val 'a'
>>> pz @(HeadDef (C "w") Id) Seq.empty
Val 'w'
>>> pz @(HeadDef (MEmptyT _) Id) ([] :: [SG.Sum Int])
Val (Sum {getSum = 0})
>>> pz @(HeadDef (MEmptyT String) '["abc","def","asdfadf"]) ()
Val "abc"
>>> pz @(HeadDef (MEmptyT _) Snd) (123,["abc","def","asdfadf"])
Val "abc"
>>> pz @(HeadDef (MEmptyT _) Snd) (123,[])
Val ()
>>> pl @(HeadDef 9 Fst) ([],True)
Present 9 (JustDef Nothing)
Val 9
>>> pl @(HeadDef 99 Fst) ([10..15],True)
Present 10 (JustDef Just)
Val 10
>>> pl @(HeadDef 12 Fst >> Le 6) ([],True)
False ((>>) False | {12 <= 6})
Val False
>>> pl @(HeadDef 1 Fst >> Le 6) ([],True)
True ((>>) True | {1 <= 6})
Val True
>>> pl @(HeadDef 10 Fst >> Le 6) ([],True)
False ((>>) False | {10 <= 6})
Val False
>>> pl @(HeadDef (MEmptyT _) Id) (map (:[]) ([] :: [Int]))
Present [] (JustDef Nothing)
Val []
>>> pl @(HeadDef (MEmptyT _) Id) (map (:[]) ([10..14] :: [Int]))
Present [10] (JustDef Just)
Val [10]
>>> pl @(HeadDef Fst Snd) (99,[10..14])
Present 10 (JustDef Just)
Val 10
>>> pl @(HeadDef Fst Snd) (99,[] :: [Int])
Present 99 (JustDef Nothing)
Val 99
>>> pl @(HeadDef 43 Snd) (99,[] :: [Int])
Present 43 (JustDef Nothing)
Val 43

Instances

Instances details
P (HeadDefT p q) x => P (HeadDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (HeadDef p q) x Source #

Methods

eval :: MonadEval m => proxy (HeadDef p q) -> POpts -> x -> m (TT (PP (HeadDef p q) x)) Source #

Show (HeadDef p q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> HeadDef p q -> ShowS #

show :: HeadDef p q -> String #

showList :: [HeadDef p q] -> ShowS #

type PP (HeadDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (HeadDef p q :: Type) x

data HeadFail msg q Source #

takes the head of a list or fails with the given message

see ConsT for other supported types eg Seq

>>> pz @(HeadFail "oops" Id) ["abc","def","asdfadf"]
Val "abc"
>>> pz @(HeadFail "empty list" Id) []
Fail "empty list"
>>> pl @(HeadFail "zz" Fst >> Le 6) ([],True)
Error zz (JustFail Nothing)
Fail "zz"
>>> pl @((HeadFail "failed1" Fst >> Le 6) || 'False) ([],True)
Error failed1 (JustFail Nothing | ||)
Fail "failed1"
>>> pl @((Fst >> HeadFail "failed2" Id >> Le (6 -% 1)) || 'False) ([-9],True)
True (True || False)
Val True
>>> pl @(HeadFail "Asdf" Id) ([] :: [()]) -- breaks otherwise
Error Asdf (JustFail Nothing)
Fail "Asdf"
>>> pl @(HeadFail (PrintF "msg=%s def" Fst) Snd) ("Abc",[])
Error msg=Abc def (JustFail Nothing)
Fail "msg=Abc def"

Instances

Instances details
P (HeadFailT msg q) x => P (HeadFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (HeadFail msg q) x Source #

Methods

eval :: MonadEval m => proxy (HeadFail msg q) -> POpts -> x -> m (TT (PP (HeadFail msg q) x)) Source #

Show (HeadFail msg q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> HeadFail msg q -> ShowS #

show :: HeadFail msg q -> String #

showList :: [HeadFail msg q] -> ShowS #

type PP (HeadFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (HeadFail msg q :: Type) x

data HeadMay Source #

similar to headMay

>>> pl @HeadMay []
Present Nothing ((>>) Nothing | {FMap <skipped>})
Val Nothing
>>> pl @HeadMay [99,7,3]
Present Just 99 ((>>) Just 99 | {FMap Fst 99 | (99,[7,3])})
Val (Just 99)

Instances

Instances details
Show HeadMay Source # 
Instance details

Defined in Predicate.Data.Extra

P HeadMayT x => P HeadMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP HeadMay x Source #

Methods

eval :: MonadEval m => proxy HeadMay -> POpts -> x -> m (TT (PP HeadMay x)) Source #

type PP HeadMay x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP HeadMay x

data TailDef p q Source #

takes the tail of a list-like object or uses the given default value

>>> pl @(TailDef '[9,7] Fst) ([],True)
Present [9,7] (JustDef Nothing)
Val [9,7]
>>> pl @(TailDef '[9,7] Fst) ([1..5],True)
Present [2,3,4,5] (JustDef Just)
Val [2,3,4,5]
>>> pl @(TailDef '[3] Fst) ([10..15],True)
Present [11,12,13,14,15] (JustDef Just)
Val [11,12,13,14,15]

Instances

Instances details
P (TailDefT p q) x => P (TailDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (TailDef p q) x Source #

Methods

eval :: MonadEval m => proxy (TailDef p q) -> POpts -> x -> m (TT (PP (TailDef p q) x)) Source #

Show (TailDef p q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> TailDef p q -> ShowS #

show :: TailDef p q -> String #

showList :: [TailDef p q] -> ShowS #

type PP (TailDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (TailDef p q :: Type) x

data TailFail msg q Source #

takes the tail of a list-like object or fails with the given message

>>> pl @(TailFail (PrintT "a=%d b=%s" Snd) Fst) ([]::[()],(4,"someval"))
Error a=4 b=someval (JustFail Nothing)
Fail "a=4 b=someval"

Instances

Instances details
P (TailFailT msg q) x => P (TailFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (TailFail msg q) x Source #

Methods

eval :: MonadEval m => proxy (TailFail msg q) -> POpts -> x -> m (TT (PP (TailFail msg q) x)) Source #

Show (TailFail msg q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> TailFail msg q -> ShowS #

show :: TailFail msg q -> String #

showList :: [TailFail msg q] -> ShowS #

type PP (TailFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (TailFail msg q :: Type) x

data TailMay Source #

similar to tailMay

>>> pz @TailMay "hello"
Val (Just "ello")

Instances

Instances details
Show TailMay Source # 
Instance details

Defined in Predicate.Data.Extra

P TailMayT x => P TailMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP TailMay x Source #

Methods

eval :: MonadEval m => proxy TailMay -> POpts -> x -> m (TT (PP TailMay x)) Source #

type PP TailMay x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP TailMay x

data LastDef p q Source #

takes the last value of a list-like object or a default value

>>> pl @(LastDef 9 Fst) ([],True)
Present 9 (JustDef Nothing)
Val 9
>>> pl @(LastDef 9 Fst) ([1..5],True)
Present 5 (JustDef Just)
Val 5
>>> pl @(LastDef 3 Fst) ([10..15],True)
Present 15 (JustDef Just)
Val 15
>>> pl @(LastDef 0 Id) [1..12]
Present 12 (JustDef Just)
Val 12
>>> pl @(LastDef 0 Id) []
Present 0 (JustDef Nothing)
Val 0

Instances

Instances details
P (LastDefT p q) x => P (LastDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (LastDef p q) x Source #

Methods

eval :: MonadEval m => proxy (LastDef p q) -> POpts -> x -> m (TT (PP (LastDef p q) x)) Source #

Show (LastDef p q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> LastDef p q -> ShowS #

show :: LastDef p q -> String #

showList :: [LastDef p q] -> ShowS #

type PP (LastDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (LastDef p q :: Type) x

data LastFail msg q Source #

takes the init of a list-like object or fails with the given message

Instances

Instances details
P (LastFailT msg q) x => P (LastFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (LastFail msg q) x Source #

Methods

eval :: MonadEval m => proxy (LastFail msg q) -> POpts -> x -> m (TT (PP (LastFail msg q) x)) Source #

Show (LastFail msg q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> LastFail msg q -> ShowS #

show :: LastFail msg q -> String #

showList :: [LastFail msg q] -> ShowS #

type PP (LastFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (LastFail msg q :: Type) x

data LastMay Source #

similar to lastMay

>>> pz @LastMay "hello"
Val (Just 'o')

Instances

Instances details
Show LastMay Source # 
Instance details

Defined in Predicate.Data.Extra

P LastMayT x => P LastMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP LastMay x Source #

Methods

eval :: MonadEval m => proxy LastMay -> POpts -> x -> m (TT (PP LastMay x)) Source #

type PP LastMay x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP LastMay x

data InitDef p q Source #

takes the init of a list-like object or uses the given default value

>>> pl @(InitDef '[9,7] Fst) ([],True)
Present [9,7] (JustDef Nothing)
Val [9,7]
>>> pl @(InitDef '[9,7] Fst) ([1..5],True)
Present [1,2,3,4] (JustDef Just)
Val [1,2,3,4]
>>> pl @(InitDef '[3] Fst) ([10..15],True)
Present [10,11,12,13,14] (JustDef Just)
Val [10,11,12,13,14]

Instances

Instances details
P (InitDefT p q) x => P (InitDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (InitDef p q) x Source #

Methods

eval :: MonadEval m => proxy (InitDef p q) -> POpts -> x -> m (TT (PP (InitDef p q) x)) Source #

Show (InitDef p q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> InitDef p q -> ShowS #

show :: InitDef p q -> String #

showList :: [InitDef p q] -> ShowS #

type PP (InitDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (InitDef p q :: Type) x

data InitFail msg q Source #

takes the init of a list-like object or fails with the given message

Instances

Instances details
P (InitFailT msg q) x => P (InitFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (InitFail msg q) x Source #

Methods

eval :: MonadEval m => proxy (InitFail msg q) -> POpts -> x -> m (TT (PP (InitFail msg q) x)) Source #

Show (InitFail msg q) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> InitFail msg q -> ShowS #

show :: InitFail msg q -> String #

showList :: [InitFail msg q] -> ShowS #

type PP (InitFail msg q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (InitFail msg q :: Type) x

data InitMay Source #

similar to initMay

>>> pz @InitMay "hello"
Val (Just "hell")

Instances

Instances details
Show InitMay Source # 
Instance details

Defined in Predicate.Data.Extra

P InitMayT x => P InitMay x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP InitMay x Source #

Methods

eval :: MonadEval m => proxy InitMay -> POpts -> x -> m (TT (PP InitMay x)) Source #

type PP InitMay x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP InitMay x

primes

data IsPrime Source #

a predicate on prime numbers

>>> pz @IsPrime 2
Val True
>>> pz @(Map '(Id,IsPrime)) [0..12]
Val [(0,False),(1,False),(2,True),(3,True),(4,False),(5,True),(6,False),(7,True),(8,False),(9,False),(10,False),(11,True),(12,False)]

Instances

Instances details
Show IsPrime Source # 
Instance details

Defined in Predicate.Data.Extra

(x ~ a, Show a, Integral a) => P IsPrime x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP IsPrime x Source #

Methods

eval :: MonadEval m => proxy IsPrime -> POpts -> x -> m (TT (PP IsPrime x)) Source #

type PP IsPrime x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP IsPrime x = Bool

data PrimeNext Source #

get the next prime number

>>> pz @PrimeNext 6
Val 7
>>> pz @(ScanN 4 PrimeNext Id) 3
Val [3,5,7,11,13]

Instances

Instances details
Show PrimeNext Source # 
Instance details

Defined in Predicate.Data.Extra

(Show x, Integral x) => P PrimeNext x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP PrimeNext x Source #

Methods

eval :: MonadEval m => proxy PrimeNext -> POpts -> x -> m (TT (PP PrimeNext x)) Source #

type PP PrimeNext x Source # 
Instance details

Defined in Predicate.Data.Extra

data PrimePrev Source #

get the next prime number

>>> pz @PrimePrev 6
Val 5
>>> pz @PrimePrev 5
Val 3
>>> pz @PrimePrev (-206)
Val 2
>>> pz @(ScanN 6 PrimePrev Id) 11
Val [11,7,5,3,2,2,2]

Instances

Instances details
Show PrimePrev Source # 
Instance details

Defined in Predicate.Data.Extra

(Show x, Integral x) => P PrimePrev x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP PrimePrev x Source #

Methods

eval :: MonadEval m => proxy PrimePrev -> POpts -> x -> m (TT (PP PrimePrev x)) Source #

type PP PrimePrev x Source # 
Instance details

Defined in Predicate.Data.Extra

data PrimeFactors n Source #

prime factorisation of positive numbers

>>> pz @(PrimeFactors Id) 17
Val [17]
>>> pz @(PrimeFactors Id) 1
Val [1]
>>> pz @(PrimeFactors Id) 30
Val [2,3,5]
>>> pz @(PrimeFactors Id) 64
Val [2,2,2,2,2,2]
>>> pz @(PrimeFactors Id) (-30)
Fail "PrimeFactors number<=0"

Instances

Instances details
(Integral (PP n x), P n x) => P (PrimeFactors n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (PrimeFactors n) x Source #

Methods

eval :: MonadEval m => proxy (PrimeFactors n) -> POpts -> x -> m (TT (PP (PrimeFactors n) x)) Source #

Show (PrimeFactors n) Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (PrimeFactors n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (PrimeFactors n :: Type) x = [Integer]

data Primes n Source #

get list of n primes

>>> pz @(Primes Id) 5
Val [2,3,5,7,11]

Instances

Instances details
(Integral (PP n x), P n x) => P (Primes n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP (Primes n) x Source #

Methods

eval :: MonadEval m => proxy (Primes n) -> POpts -> x -> m (TT (PP (Primes n) x)) Source #

Show (Primes n) Source # 
Instance details

Defined in Predicate.Data.Extra

Methods

showsPrec :: Int -> Primes n -> ShowS #

show :: Primes n -> String #

showList :: [Primes n] -> ShowS #

type PP (Primes n :: Type) x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP (Primes n :: Type) x = [Integer]

luhn check

data IsLuhn Source #

IsLuhn predicate check on last digit

>>> pz @IsLuhn [1,2,3,0]
Val True
>>> pz @IsLuhn [1,2,3,4]
Val False
>>> pz @(GuardSimple IsLuhn) [15,4,3,1,99]
Fail "(IsLuhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])"
>>> pl @IsLuhn [15,4,3,1,99]
False (IsLuhn map=[90,2,3,8,6] sum=109 ret=9 | [15,4,3,1,99])
Val False

Instances

Instances details
Show IsLuhn Source # 
Instance details

Defined in Predicate.Data.Extra

x ~ [Int] => P IsLuhn x Source # 
Instance details

Defined in Predicate.Data.Extra

Associated Types

type PP IsLuhn x Source #

Methods

eval :: MonadEval m => proxy IsLuhn -> POpts -> x -> m (TT (PP IsLuhn x)) Source #

type PP IsLuhn x Source # 
Instance details

Defined in Predicate.Data.Extra

type PP IsLuhn x = Bool