Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data CSeq a
- cseq :: Seq a -> a -> Seq a -> CSeq a
- singleton :: a -> CSeq a
- fromNonEmpty :: NonEmpty a -> CSeq a
- fromList :: [a] -> CSeq a
- toNonEmpty :: CSeq a -> NonEmpty a
- focus :: CSeq a -> a
- index :: CSeq a -> Int -> a
- adjust :: (a -> a) -> Int -> CSeq a -> CSeq a
- item :: Int -> Lens' (CSeq a) a
- rotateL :: CSeq a -> CSeq a
- rotateR :: CSeq a -> CSeq a
- rotateNL :: Int -> CSeq a -> CSeq a
- rotateNR :: Int -> CSeq a -> CSeq a
- rightElements :: CSeq a -> Seq a
- leftElements :: CSeq a -> Seq a
- asSeq :: CSeq a -> Seq a
- reverseDirection :: CSeq a -> CSeq a
- allRotations :: CSeq a -> CSeq (CSeq a)
- findRotateTo :: (a -> Bool) -> CSeq a -> Maybe (CSeq a)
- rotateTo :: Eq a => a -> CSeq a -> Maybe (CSeq a)
- zipLWith :: (a -> b -> c) -> CSeq a -> CSeq b -> CSeq c
- zipL :: CSeq a -> CSeq b -> CSeq (a, b)
- zip3LWith :: (a -> b -> c -> d) -> CSeq a -> CSeq b -> CSeq c -> CSeq d
- insertOrd :: Ord a => a -> CSeq a -> CSeq a
- insertOrdBy :: (a -> a -> Ordering) -> a -> CSeq a -> CSeq a
- isShiftOf :: Eq a => CSeq a -> CSeq a -> Bool
Documentation
Nonempty circular sequence
fromNonEmpty :: NonEmpty a -> CSeq a Source #
builds a CSeq
toNonEmpty :: CSeq a -> NonEmpty a Source #
index :: CSeq a -> Int -> a Source #
Access the i^th item (w.r.t the focus) in the CSeq (indices modulo n).
running time: \(O(\log (i \mod n))\)
>>>
index (fromList [0..5]) 1
1>>>
index (fromList [0..5]) 2
2>>>
index (fromList [0..5]) 5
5>>>
index (fromList [0..5]) 10
4>>>
index (fromList [0..5]) 6
0>>>
index (fromList [0..5]) (-1)
5>>>
index (fromList [0..5]) (-6)
0
adjust :: (a -> a) -> Int -> CSeq a -> CSeq a Source #
Adjusts the i^th element w.r.t the focus in the CSeq
running time: \(O(\log (i \mod n))\)
>>>
adjust (const 1000) 2 (fromList [0..5])
CSeq [0,1,1000,3,4,5]
rotateL :: CSeq a -> CSeq a Source #
rotates the focus to the left
running time: O(1) (amortized)
>>>
rotateL $ fromList [3,4,5,1,2]
CSeq [2,3,4,5,1]>>>
mapM_ print . take 5 $ iterate rotateL $ fromList [1..5]
CSeq [1,2,3,4,5] CSeq [5,1,2,3,4] CSeq [4,5,1,2,3] CSeq [3,4,5,1,2] CSeq [2,3,4,5,1]
rotateR :: CSeq a -> CSeq a Source #
rotates one to the right
running time: O(1) (amortized)
>>>
rotateR $ fromList [3,4,5,1,2]
CSeq [4,5,1,2,3]
rotateNL :: Int -> CSeq a -> CSeq a Source #
Rotates i elements to the left.
pre: 0 <= i < n
running time: \(O(\log i)\) amoritzed
>>>
rotateNL 0 $ fromList [1..5]
CSeq [1,2,3,4,5]>>>
rotateNL 1 $ fromList [1..5]
CSeq [5,1,2,3,4]>>>
rotateNL 2 $ fromList [1..5]
CSeq [4,5,1,2,3]>>>
rotateNL 3 $ fromList [1..5]
CSeq [3,4,5,1,2]>>>
rotateNL 4 $ fromList [1..5]
CSeq [2,3,4,5,1]
rotateNR :: Int -> CSeq a -> CSeq a Source #
Rotates i elements to the right.
pre: 0 <= i < n
running time: \(O(\log i)\) amortized
>>>
rotateNR 0 $ fromList [1..5]
CSeq [1,2,3,4,5]>>>
rotateNR 1 $ fromList [1..5]
CSeq [2,3,4,5,1]>>>
rotateNR 4 $ fromList [1..5]
CSeq [5,1,2,3,4]
rightElements :: CSeq a -> Seq a Source #
All elements, starting with the focus, going to the right
leftElements :: CSeq a -> Seq a Source #
All elements, starting with the focus, going to the left
>>>
leftElements $ fromList [3,4,5,1,2]
fromList [3,2,1,5,4]
reverseDirection :: CSeq a -> CSeq a Source #
Reversres the direction of the CSeq
running time: \(O(n)\)
>>>
reverseDirection $ fromList [1..5]
CSeq [1,5,4,3,2]
allRotations :: CSeq a -> CSeq (CSeq a) Source #
All rotations, the input CSeq is the focus.
>>>
mapM_ print . allRotations $ fromList [1..5]
CSeq [1,2,3,4,5] CSeq [2,3,4,5,1] CSeq [3,4,5,1,2] CSeq [4,5,1,2,3] CSeq [5,1,2,3,4]
findRotateTo :: (a -> Bool) -> CSeq a -> Maybe (CSeq a) Source #
Finds an element in the CSeq
>>>
findRotateTo (== 3) $ fromList [1..5]
Just (CSeq [3,4,5,1,2])>>>
findRotateTo (== 7) $ fromList [1..5]
Nothing
zipLWith :: (a -> b -> c) -> CSeq a -> CSeq b -> CSeq c Source #
"Left zip": zip the two CLists, pairing up every element in the *left* list with its corresponding element in the right list. If there are more items in the right clist they are discarded.
zip3LWith :: (a -> b -> c -> d) -> CSeq a -> CSeq b -> CSeq c -> CSeq d Source #
same as zipLWith but with three items
insertOrd :: Ord a => a -> CSeq a -> CSeq a Source #
Given a circular seq, whose elements are in increasing order, insert the new element into the Circular seq in its sorted order.
>>>
insertOrd 1 $ fromList [2]
CSeq [2,1]>>>
insertOrd 2 $ fromList [1,3]
CSeq [1,2,3]>>>
insertOrd 31 ordList
CSeq [5,6,10,20,30,31,1,2,3]>>>
insertOrd 1 ordList
CSeq [5,6,10,20,30,1,1,2,3]>>>
insertOrd 4 ordList
CSeq [5,6,10,20,30,1,2,3,4]>>>
insertOrd 11 ordList
CSeq [5,6,10,11,20,30,1,2,3]
running time: \(O(n)\)