| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Tuple
Description
promoted tuple functions
arrows
duplicate a value into a tuple
>>>pl @Dup 4Present (4,4) ('(4,4)) Val (4,4)
>>>pl @(Dup >> Id) 4Present (4,4) ((>>) (4,4) | {Id (4,4)}) Val (4,4)
>>>pl @(Dup << Fst * Snd) (4,5)Present (20,20) ((>>) (20,20) | {'(20,20)}) Val (20,20)
>>>pl @(Fst * Snd >> Dup) (4,5)Present (20,20) ((>>) (20,20) | {'(20,20)}) Val (20,20)
applies a function against the first part of a tuple: similar to first
>>>pz @(First Succ) (12,True)Val (13,True)
applies a function against the second part of a tuple: similar to second
>>>pz @(Second Succ) (12,False)Val (12,True)
data p &&& q infixr 3 Source #
similar to &&&
>>>pl @(Min &&& Max >> Id >> Fst < Snd) [10,4,2,12,14]True ((>>) True | {2 < 14}) Val True
>>>pl @((123 &&& Id) >> Fst + Snd) 4Present 127 ((>>) 127 | {123 + 4 = 127}) Val 127
>>>pl @(4 &&& "sadf" &&& 'LT) ()Present (4,("sadf",LT)) ('(4,("sadf",LT))) Val (4,("sadf",LT))
>>>pl @(Id &&& '() &&& ()) (Just 10)Present (Just 10,((),())) ('(Just 10,((),()))) Val (Just 10,((),()))
>>>pl @(Fst &&& Snd &&& Thd &&& ()) (1,'x',True)Present (1,('x',(True,()))) ('(1,('x',(True,())))) Val (1,('x',(True,())))
>>>pl @(Fst &&& Snd &&& Thd &&& ()) (1,'x',True)Present (1,('x',(True,()))) ('(1,('x',(True,())))) Val (1,('x',(True,())))
>>>pl @(Fst &&& Snd &&& Thd &&& ()) (1,1.4,"aaa")Present (1,(1.4,("aaa",()))) ('(1,(1.4,("aaa",())))) Val (1,(1.4,("aaa",())))
data p *** q infixr 3 Source #
similar to ***
>>>pz @(Pred *** ShowP Id) (13, True)Val (12,"True")
>>>pl @(FlipT (***) Len (Id * 12)) (99,"cdef")Present (1188,4) ((***) (1188,4) | (99,"cdef")) Val (1188,4)
>>>pl @(4 *** "sadf" *** 'LT) ('x',("abv",[1]))Present (4,("sadf",LT)) ((***) (4,("sadf",LT)) | ('x',("abv",[1]))) Val (4,("sadf",LT))
applies p to the first and second slot of an n-tuple (similar to ***)
>>>pl @(Fst >> Both Len) (("abc",[10..17]),True)Present (3,8) ((>>) (3,8) | {Both}) Val (3,8)
>>>pl @(Lift (Both Pred) Fst) ((12,'z'),True)Present (11,'y') ((>>) (11,'y') | {Both}) Val (11,'y')
>>>pl @(Both Succ) (4,'a')Present (5,'b') (Both) Val (5,'b')
>>>import Data.Time>>>pl @(Both (ReadP Day Id)) ("1999-01-01","2001-02-12")Present (1999-01-01,2001-02-12) (Both) Val (1999-01-01,2001-02-12)
>>>pz @(Both (Id * Id) >> ((Fst + Snd) ** (DivI Double 1 2))) (3,4)Val 5.0
data On (p :: Type -> Type -> k2) q Source #
similar to on: may require kind signatures: Both is a better choice
>>>pz @('(4,2) >> On (**) (FromIntegral _)) ()Val 16.0
>>>pz @('(4,2) >> Both (FromIntegral _) >> Fst ** Snd) () -- equivalent to the above but easier on ghcVal 16.0
>>>pz @(On (+) (Id * Id) >> Id ** (1 % 2 >> FromRational _)) (3,4)Val 5.0
>>>pz @(Both (Id * Id) >> ((Fst + Snd) ** (1 % 2 >> FromRational _))) (3,4) -- equivalent to the above but easier on ghcVal 5.0
flat tuples
data Tuple (n :: Nat) Source #
create a n tuple from a list or fail
>>>pz @(Tuple 4) "abcdefg"Val ('a','b','c','d')
>>>pz @(Tuple 4) "abc"Fail "Tuple(4) not enough elements(3)"
>>>pz @(Fst >> Tuple 3) ([1..5],True)Val (1,2,3)
>>>pz @(Lift (Tuple 3) Fst) ([1..5],True)Val (1,2,3)
data Tuple' (n :: Nat) Source #
create a n tuple from a list and return as an Either
>>>pz @(Tuple' 4) "abcdefg"Val (Right ('a','b','c','d'))
>>>pz @(Tuple' 4) "abc"Val (Left "abc")
>>>pz @(Tuple' 4) []Val (Left [])
>>>pl @(Tuple' 4) "abc"Present Left "abc" (Tuple'(4) not enough elements(3)) Val (Left "abc")
>>>:set -XPolyKinds>>>type F n i = ChunksOf' n i Id >> Map (Tuple' n) >> PartitionEithers>>>pz @(F 3 1) [1..7]Val ([[6,7],[7]],[(1,2,3),(2,3,4),(3,4,5),(4,5,6),(5,6,7)])
creates a list of overlapping pairs of elements. requires two or more elements
>>>pz @Pairs [1,2,3,4]Val [(1,2),(2,3),(3,4)]
>>>pz @Pairs []Val []
>>>pz @Pairs [1]Val []
>>>pl @Pairs [1,2]Present [(1,2)] (Pairs [(1,2)] | [1,2]) Val [(1,2)]
>>>pl @Pairs [1,2,3]Present [(1,2),(2,3)] (Pairs [(1,2),(2,3)] | [1,2,3]) Val [(1,2),(2,3)]
>>>pl @Pairs [1,2,3,4]Present [(1,2),(2,3),(3,4)] (Pairs [(1,2),(2,3),(3,4)] | [1,2,3,4]) Val [(1,2),(2,3),(3,4)]
>>>pan @(Pairs >> Len >> 'True >> 'False >> FailT _ "xyzzy") "abcde"[Error xyzzy] False | +- P Pairs [('a','b'),('b','c'),('c','d'),('d','e')] | +- P Len 4 | +- True 'True | +- False 'False | `- [Error xyzzy] Fail "xyzzy"
boolean
applies p to lhs of the tuple and q to the rhs and then ands them together: see &*
>>>pl @(AndA (Gt 3) (Lt 10) Id) (1,2)False (False (&*) True | (1 > 3)) Val False
applies p to lhs of the tuple and q to the rhs and then Ands them together
>>>pl @(SplitAt 4 "abcdefg" >> Len > 4 &* Len < 5) ()False ((>>) False | {False (&*) True | (4 > 4)}) Val False
applies p to lhs of the tuple and q to the rhs and then ors them together: see |+
>>>pl @(OrA (Gt 3) (Lt 10) Id) (1,2)True (False (|+) True) Val True
applies p to lhs of the tuple and q to the rhs and then Ors them together
>>>pl @(Sum > 44 |+ Id < 2) ([5,6,7,8,14,44],9)True (True (|+) False) Val True
>>>pl @(Sum > 44 |+ Id < 2) ([5,6,7,14],9)False (False (|+) False | (32 > 44) (|+) (9 < 2)) Val False
>>>pl @(Sum > 44 |+ Id < 2) ([5,6,7,14],1)True (False (|+) True) Val True
inductive tuples
data EachITuple p Source #
run p with inductive tuples
>>>pz @(EachITuple Succ) (False,(2,(LT,('c',()))))Val (True,(3,(EQ,('d',()))))
>>>pz @(EachITuple (Id + (4 >> FromIntegral _))) (1,(1/4,(5%6,())))Val (5 % 1,(17 % 4,(29 % 6,())))
>>>pz @(ToITuple >> EachITuple (Id + (4 >> FromIntegral _))) (1000,1/4,5%6)Val (1004 % 1,(17 % 4,(29 % 6,())))
>>>pz @(ToITuple >> EachITuple ((Id >> FromIntegral _) + (4 >> FromIntegral _))) (1000::Integer,17::Int)Val (1004,(21,()))
>>>pz @(ToITuple >> EachITuple (Dup >> Fst<>Snd)) (SG.Min 1,SG.First 'x',"abcd")Val (Min {getMin = 1},(First {getFirst = 'x'},("abcdabcd",())))
Instances
| P (EachITuple p :: Type) () Source # | |
Defined in Predicate.Data.Tuple Associated Types type PP (EachITuple p) () Source # Methods eval :: MonadEval m => proxy (EachITuple p) -> POpts -> () -> m (TT (PP (EachITuple p) ())) Source # | |
| (P p b, P (EachITuple p) bs) => P (EachITuple p :: Type) (b, bs) Source # | |
Defined in Predicate.Data.Tuple Associated Types type PP (EachITuple p) (b, bs) Source # Methods eval :: MonadEval m => proxy (EachITuple p) -> POpts -> (b, bs) -> m (TT (PP (EachITuple p) (b, bs))) Source # | |
| Show (EachITuple p) Source # | |
Defined in Predicate.Data.Tuple Methods showsPrec :: Int -> EachITuple p -> ShowS # show :: EachITuple p -> String # showList :: [EachITuple p] -> ShowS # | |
| type PP (EachITuple p :: Type) () Source # | |
Defined in Predicate.Data.Tuple | |
| type PP (EachITuple p :: Type) (b, bs) Source # | |
Defined in Predicate.Data.Tuple | |
create inductive tuples from flat tuples
>>>pz @(ToITuple >> EachITuple Succ) (1,2,False,'x')Val (2,(3,(True,('y',()))))
data ReverseITuple Source #
reverse an inductive tuple
>>>pz @ReverseITuple (1.4,(1,(2,(False,('x',())))))Val ('x',(False,(2,(1,(1.4,())))))
Instances
| Show ReverseITuple Source # | |
Defined in Predicate.Data.Tuple Methods showsPrec :: Int -> ReverseITuple -> ShowS # show :: ReverseITuple -> String # showList :: [ReverseITuple] -> ShowS # | |
| P ReverseITuple () Source # | |
Defined in Predicate.Data.Tuple Associated Types type PP ReverseITuple () Source # Methods eval :: MonadEval m => proxy ReverseITuple -> POpts -> () -> m (TT (PP ReverseITuple ())) Source # | |
| ReverseITupleC x xs () => P ReverseITuple (x, xs) Source # | |
Defined in Predicate.Data.Tuple Associated Types type PP ReverseITuple (x, xs) Source # Methods eval :: MonadEval m => proxy ReverseITuple -> POpts -> (x, xs) -> m (TT (PP ReverseITuple (x, xs))) Source # | |
| type PP ReverseITuple () Source # | |
Defined in Predicate.Data.Tuple | |
| type PP ReverseITuple (x, xs) Source # | |
Defined in Predicate.Data.Tuple | |
data ToITupleList (n :: Nat) Source #
create inductive tuples from a list of the exact size n
>>>pz @(ToITupleList 4 >> EachITuple Succ) ['a','c','y','B']Val ('b',('d',('z',('C',()))))
>>>pz @(ToITupleList 4) ['a','c','y','B']Val ('a',('c',('y',('B',()))))
>>>pz @(Take 10 Id >> ToITupleList 10) ['a'..'z']Val ('a',('b',('c',('d',('e',('f',('g',('h',('i',('j',()))))))))))
Instances
| Show (ToITupleList n) Source # | |
Defined in Predicate.Data.Tuple Methods showsPrec :: Int -> ToITupleList n -> ShowS # show :: ToITupleList n -> String # showList :: [ToITupleList n] -> ShowS # | |
| (KnownNat n, FailWhenT (n <=? 0) ('Text "ToITupleList:n cannot be 0"), ToITupleListC n a, xs ~ [a]) => P (ToITupleList n :: Type) xs Source # | |
Defined in Predicate.Data.Tuple Associated Types type PP (ToITupleList n) xs Source # Methods eval :: MonadEval m => proxy (ToITupleList n) -> POpts -> xs -> m (TT (PP (ToITupleList n) xs)) Source # | |
| type PP (ToITupleList n :: Type) xs Source # | |
Defined in Predicate.Data.Tuple | |