Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | GHC2021 |
HGeometry.Cyclic
Description
Representing Cyclic Sequences
Synopsis
- newtype Cyclic (v :: k -> Type) (a :: k) = Cyclic (v a)
- class HasDirectedTraversals (v :: Type -> Type) where
- traverseRightFrom :: Index (v a) -> IndexedTraversal1' (Index (v a)) (v a) a
- traverseLeftFrom :: Index (v a) -> IndexedTraversal1' (Index (v a)) (v a) a
- class ShiftedEq t where
- type ElemCyclic t
- isShiftOf :: t -> t -> Bool
- groupWith :: (Foldable1 cyclic, Eq b) => (a -> b) -> cyclic a -> Cyclic NonEmpty (b, NonEmpty a)
- withCyclicSuccessor :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, a) b
- withCyclicPredecessor :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, a) b
- withCyclicNeighbours :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, V2 a) b
- iWithCyclicSuccessor :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, i) (cyclic a) (cyclic b) (a, a) b
- iWithCyclicPredecessor :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, i) (cyclic a) (cyclic b) (a, a) b
- iWithCyclicNeighbours :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, V2 i) (cyclic a) (cyclic b) (a, V2 a) b
- data V2 a = V2 !a !a
Documentation
newtype Cyclic (v :: k -> Type) (a :: k) Source #
A cyclic sequence type
Constructors
Cyclic (v a) |
Instances
class HasDirectedTraversals (v :: Type -> Type) where Source #
Class that models that some type has a cyclic traversal starting from a particular index.
Methods
traverseRightFrom :: Index (v a) -> IndexedTraversal1' (Index (v a)) (v a) a Source #
A rightward-traversal over all elements starting from the given one. Indices are taken modulo the length.
running time : \(O(n)\)
traverseLeftFrom :: Index (v a) -> IndexedTraversal1' (Index (v a)) (v a) a Source #
A rightward-traversal over all elements starting from the given one. Indices are taken modulo the length.
running time : \(O(n)\)
Instances
HasDirectedTraversals NonEmpty Source # | |
Defined in HGeometry.Cyclic Methods traverseRightFrom :: Index (NonEmpty a) -> IndexedTraversal1' (Index (NonEmpty a)) (NonEmpty a) a Source # traverseLeftFrom :: Index (NonEmpty a) -> IndexedTraversal1' (Index (NonEmpty a)) (NonEmpty a) a Source # | |
HasDirectedTraversals ViewL1 Source # | |
Defined in HGeometry.Cyclic Methods traverseRightFrom :: Index (ViewL1 a) -> IndexedTraversal1' (Index (ViewL1 a)) (ViewL1 a) a Source # traverseLeftFrom :: Index (ViewL1 a) -> IndexedTraversal1' (Index (ViewL1 a)) (ViewL1 a) a Source # | |
HasDirectedTraversals NonEmptyVector Source # | |
Defined in HGeometry.Cyclic Methods traverseRightFrom :: Index (NonEmptyVector a) -> IndexedTraversal1' (Index (NonEmptyVector a)) (NonEmptyVector a) a Source # traverseLeftFrom :: Index (NonEmptyVector a) -> IndexedTraversal1' (Index (NonEmptyVector a)) (NonEmptyVector a) a Source # | |
HasDirectedTraversals v => HasDirectedTraversals (Cyclic v) Source # | |
Defined in HGeometry.Cyclic Methods traverseRightFrom :: Index (Cyclic v a) -> IndexedTraversal1' (Index (Cyclic v a)) (Cyclic v a) a Source # traverseLeftFrom :: Index (Cyclic v a) -> IndexedTraversal1' (Index (Cyclic v a)) (Cyclic v a) a Source # |
class ShiftedEq t where Source #
Class for types that have an Equality test up to cyclic shifts
Methods
isShiftOf :: t -> t -> Bool Source #
Given a and b, test if a is a shifted version of the other.
Instances
Foldable1 v => ShiftedEq (Cyclic v a) Source # | |||||
Defined in HGeometry.Cyclic Associated Types
|
groupWith :: (Foldable1 cyclic, Eq b) => (a -> b) -> cyclic a -> Cyclic NonEmpty (b, NonEmpty a) Source #
Groups the elements of a cyclic. Note in particular that this may join the first and last group, thereby changing the indices of the individual elements.
the items are reported in the same order as before.
withCyclicSuccessor :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, a) b Source #
A traversal that associates every elemnt with its successor
withCyclicPredecessor :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, a) b Source #
A traversal that associates every elemnt with its predecessor
withCyclicNeighbours :: forall (cyclic :: Type -> Type) a b. Traversable1 cyclic => Traversal1 (cyclic a) (cyclic b) (a, V2 a) b Source #
Traverse a cyclic structure together with both its neighbors
iWithCyclicSuccessor :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, i) (cyclic a) (cyclic b) (a, a) b Source #
An indexed version of withCyclicSuccessor
iWithCyclicPredecessor :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, i) (cyclic a) (cyclic b) (a, a) b Source #
An indexed traversal that associates every elemnt with its predecessor
iWithCyclicNeighbours :: forall (cyclic :: Type -> Type) i a b. (Traversable1 cyclic, TraversableWithIndex i cyclic) => IndexedTraversal1 (i, V2 i) (cyclic a) (cyclic b) (a, V2 a) b Source #
An indexed traversal that associates every elemnt with its neighbours
A 2-dimensional vector
>>>
pure 1 :: V2 Int
V2 1 1
>>>
V2 1 2 + V2 3 4
V2 4 6
>>>
V2 1 2 * V2 3 4
V2 3 8
>>>
sum (V2 1 2)
3
Constructors
V2 !a !a |
Instances
Representable V2 | |||||
MonadZip V2 | |||||
Foldable1 V2 | |||||
Defined in Linear.V2 Methods fold1 :: Semigroup m => V2 m -> m # foldMap1 :: Semigroup m => (a -> m) -> V2 a -> m # foldMap1' :: Semigroup m => (a -> m) -> V2 a -> m # toNonEmpty :: V2 a -> NonEmpty a # maximum :: Ord a => V2 a -> a # minimum :: Ord a => V2 a -> a # foldrMap1 :: (a -> b) -> (a -> b -> b) -> V2 a -> b # foldlMap1' :: (a -> b) -> (b -> a -> b) -> V2 a -> b # foldlMap1 :: (a -> b) -> (b -> a -> b) -> V2 a -> b # foldrMap1' :: (a -> b) -> (a -> b -> b) -> V2 a -> b # | |||||
Eq1 V2 | |||||
Ord1 V2 | |||||
Read1 V2 | |||||
Show1 V2 | |||||
Serial1 V2 | |||||
Distributive V2 | |||||
Applicative V2 | |||||
Functor V2 | |||||
Monad V2 | |||||
MonadFix V2 | |||||
Foldable V2 | |||||
Defined in Linear.V2 Methods fold :: Monoid m => V2 m -> m # foldMap :: Monoid m => (a -> m) -> V2 a -> m # foldMap' :: Monoid m => (a -> m) -> V2 a -> m # foldr :: (a -> b -> b) -> b -> V2 a -> b # foldr' :: (a -> b -> b) -> b -> V2 a -> b # foldl :: (b -> a -> b) -> b -> V2 a -> b # foldl' :: (b -> a -> b) -> b -> V2 a -> b # foldr1 :: (a -> a -> a) -> V2 a -> a # foldl1 :: (a -> a -> a) -> V2 a -> a # elem :: Eq a => a -> V2 a -> Bool # maximum :: Ord a => V2 a -> a # | |||||
Traversable V2 | |||||
Hashable1 V2 | |||||
Affine V2 | |||||
Metric V2 | |||||
Trace V2 | |||||
Finite V2 | |||||
R1 V2 | |||||
R2 V2 | |||||
Additive V2 | |||||
Defined in Linear.V2 | |||||
Apply V2 | |||||
Bind V2 | |||||
Traversable1 V2 | |||||
Generic1 V2 | |||||
Defined in Linear.V2 Associated Types
| |||||
Num r => Coalgebra r (E V2) | |||||
Lift a => Lift (V2 a :: Type) | |||||
Unbox a => Vector Vector (V2 a) | |||||
Defined in Linear.V2 Methods basicUnsafeFreeze :: Mutable Vector s (V2 a) -> ST s (Vector (V2 a)) Source # basicUnsafeThaw :: Vector (V2 a) -> ST s (Mutable Vector s (V2 a)) Source # basicLength :: Vector (V2 a) -> Int Source # basicUnsafeSlice :: Int -> Int -> Vector (V2 a) -> Vector (V2 a) Source # basicUnsafeIndexM :: Vector (V2 a) -> Int -> Box (V2 a) Source # basicUnsafeCopy :: Mutable Vector s (V2 a) -> Vector (V2 a) -> ST s () Source # | |||||
Unbox a => MVector MVector (V2 a) | |||||
Defined in Linear.V2 Methods basicLength :: MVector s (V2 a) -> Int Source # basicUnsafeSlice :: Int -> Int -> MVector s (V2 a) -> MVector s (V2 a) Source # basicOverlaps :: MVector s (V2 a) -> MVector s (V2 a) -> Bool Source # basicUnsafeNew :: Int -> ST s (MVector s (V2 a)) Source # basicInitialize :: MVector s (V2 a) -> ST s () Source # basicUnsafeReplicate :: Int -> V2 a -> ST s (MVector s (V2 a)) Source # basicUnsafeRead :: MVector s (V2 a) -> Int -> ST s (V2 a) Source # basicUnsafeWrite :: MVector s (V2 a) -> Int -> V2 a -> ST s () Source # basicClear :: MVector s (V2 a) -> ST s () Source # basicSet :: MVector s (V2 a) -> V2 a -> ST s () Source # basicUnsafeCopy :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source # basicUnsafeMove :: MVector s (V2 a) -> MVector s (V2 a) -> ST s () Source # basicUnsafeGrow :: MVector s (V2 a) -> Int -> ST s (MVector s (V2 a)) Source # | |||||
Binary a => Binary (V2 a) | |||||
Serial a => Serial (V2 a) | |||||
Serialize a => Serialize (V2 a) | |||||
NFData a => NFData (V2 a) | |||||
Monoid a => Monoid (V2 a) | |||||
Semigroup a => Semigroup (V2 a) | |||||
Data a => Data (V2 a) | |||||
Defined in Linear.V2 Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> V2 a -> c (V2 a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (V2 a) # dataTypeOf :: V2 a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (V2 a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (V2 a)) # gmapT :: (forall b. Data b => b -> b) -> V2 a -> V2 a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> V2 a -> r # gmapQ :: (forall d. Data d => d -> u) -> V2 a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> V2 a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> V2 a -> m (V2 a) # | |||||
Bounded a => Bounded (V2 a) | |||||
Floating a => Floating (V2 a) | |||||
Storable a => Storable (V2 a) | |||||
Generic (V2 a) | |||||
Defined in Linear.V2 Associated Types
| |||||
Ix a => Ix (V2 a) | |||||
Num a => Num (V2 a) | |||||
Read a => Read (V2 a) | |||||
Fractional a => Fractional (V2 a) | |||||
Show a => Show (V2 a) | |||||
Eq a => Eq (V2 a) | |||||
Ord a => Ord (V2 a) | |||||
Hashable a => Hashable (V2 a) | |||||
Ixed (V2 a) | |||||
Epsilon a => Epsilon (V2 a) | |||||
Random a => Random (V2 a) | |||||
Uniform a => Uniform (V2 a) | |||||
UniformRange a => UniformRange (V2 a) | |||||
Unbox a => Unbox (V2 a) | |||||
Defined in Linear.V2 | |||||
FoldableWithIndex (E V2) V2 | |||||
Defined in Linear.V2 Methods ifoldMap :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source # ifoldMap' :: Monoid m => (E V2 -> a -> m) -> V2 a -> m Source # ifoldr :: (E V2 -> a -> b -> b) -> b -> V2 a -> b Source # ifoldl :: (E V2 -> b -> a -> b) -> b -> V2 a -> b Source # | |||||
FunctorWithIndex (E V2) V2 | |||||
TraversableWithIndex (E V2) V2 | |||||
Each (V2 a) (V2 b) a b | |||||
Field1 (V2 a) (V2 a) a a | |||||
Field2 (V2 a) (V2 a) a a | |||||
type Rep V2 | |||||
type Diff V2 | |||||
Defined in Linear.Affine | |||||
type Size V2 | |||||
type Rep1 V2 | |||||
Defined in Linear.V2 type Rep1 V2 = D1 ('MetaData "V2" "Linear.V2" "linear-1.23.1-4d1e410d44f205bb3e41019c738988ce2ab4eb665f04e18eaa3a1d1856e2566c" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) Par1)) | |||||
data MVector s (V2 a) | |||||
type Rep (V2 a) | |||||
Defined in Linear.V2 type Rep (V2 a) = D1 ('MetaData "V2" "Linear.V2" "linear-1.23.1-4d1e410d44f205bb3e41019c738988ce2ab4eb665f04e18eaa3a1d1856e2566c" 'False) (C1 ('MetaCons "V2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) | |||||
type Index (V2 a) | |||||
type IxValue (V2 a) | |||||
data Vector (V2 a) | |||||