Safe Haskell | None |
---|---|
Language | Haskell2010 |
extra promoted functions
Synopsis
- data HeadDef p q
- data HeadFail msg q
- data TailDef p q
- data TailFail msg q
- data LastDef p q
- data LastFail msg q
- data InitDef p q
- data InitFail msg q
- data HeadMay
- data LastMay
- data TailMay
- data InitMay
- data PartitionsBy p q r
- data IMap p q
- data IList
- data IsPrime
- data PrimeNext
- data PrimePrev
- data PrimeFactors n
- data Primes n
- data IsLuhn
list functions
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
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"
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]
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"
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
takes the init of a list-like object or fails with the given message
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]
takes the init of a list-like object or fails with the given message
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)
similar to lastMay
>>>
pz @LastMay "hello"
Val (Just 'o')
similar to tailMay
>>>
pz @TailMay "hello"
Val (Just "ello")
similar to initMay
>>>
pz @InitMay "hello"
Val (Just "hell")
data PartitionsBy p q r #
experimental: sorts then partitions and then sorts each partitions based on the leftmost occurring value in the original list
if the existing order of data is fine then use GroupBy
as you do not need this
>>>
pz @(PartitionsBy (Fst ==! Snd) (L11 == L21) Id) [10,9,9,1,9]
Val [[10],[9,9,9],[1]]
>>>
pz @(PartitionsBy OrdA (L11 < L21) Id) "efaffabec"
Val ["a","f","f","abce","ef"]
>>>
pz @(PartitionsBy 'GT 'True Id) "efaffabec"
Val ["cebaffafe"]
>>>
pz @(PartitionsBy 'GT 'False Id) "efaffabec"
Val ["e","f","a","f","f","a","b","e","c"]
>>>
pz @(PartitionsBy (Fst ==! Snd) (L12 > L22) Id) [10,9,9,1,9,4]
Val [[9],[1],[9,10],[4,9]]
>>>
pz @(PartitionsBy (L11 ==! L21) (L12 > L22) Id) "eddadc"
Val ["d","a","de","cd"]
>>>
pz @(PartitionsBy (L11 ==! L21) (L11 < L21) Id) [10,9,9,1,9,4]
Val [[9],[1,4,9],[9,10]]
Instances
P (PartitionsByT p q r) x => P (PartitionsBy p q r :: Type) x # | |
Defined in Predicate.Data.Extra type PP (PartitionsBy p q r) x :: Type # eval :: MonadEval m => proxy (PartitionsBy p q r) -> POpts -> x -> m (TT (PP (PartitionsBy p q r) x)) # | |
Show (PartitionsBy p q r) # | |
Defined in Predicate.Data.Extra showsPrec :: Int -> PartitionsBy p q r -> ShowS # show :: PartitionsBy p q r -> String # showList :: [PartitionsBy p q r] -> ShowS # | |
type PP (PartitionsBy p q r :: Type) x # | |
Defined in Predicate.Data.Extra |
add an index to map
>>>
pz @(Rescan "^(\\d+)\\.(\\d+)\\.(\\d+)\\.(\\d+)$" >> Map (Snd >> IMap (GuardBool (PrintT "bad value=%d %s" Id) (Snd >> ReadP Int Id < 255)) Id)) "123.222.999.3"
Fail "bad value=2 999"
>>>
pz @(Rescan "^(\\d+)\\.(\\d+)\\.(\\d+)\\.(\\d+)$" >> Map (Snd >> IMap (GuardBool (PrintT "bad value=%d %s" Id) (Snd >> ReadP Int Id < 255)) Id)) "123.222.99.3"
Val [[True,True,True,True]]
add an index to list
>>>
pz @IList "abcdef"
Val [(0,'a'),(1,'b'),(2,'c'),(3,'d'),(4,'e'),(5,'f')]
primes
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)]
get the next prime number
>>>
pz @PrimeNext 6
Val 7
>>>
pz @(ScanN 4 PrimeNext Id) 3
Val [3,5,7,11,13]
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]
data PrimeFactors n #
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
(Integral (PP n x), P n x) => P (PrimeFactors n :: Type) x # | |
Defined in Predicate.Data.Extra type PP (PrimeFactors n) x :: Type # eval :: MonadEval m => proxy (PrimeFactors n) -> POpts -> x -> m (TT (PP (PrimeFactors n) x)) # | |
Show (PrimeFactors n) # | |
Defined in Predicate.Data.Extra showsPrec :: Int -> PrimeFactors n -> ShowS # show :: PrimeFactors n -> String # showList :: [PrimeFactors n] -> ShowS # | |
type PP (PrimeFactors n :: Type) x # | |
Defined in Predicate.Data.Extra |
get list of n
primes
>>>
pz @(Primes Id) 5
Val [2,3,5,7,11]
luhn check
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