Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
- data W l = Window {
- windowStart :: Index l
- windowSize :: Index l
- windowInner :: l
- class Bulk l a => Windowable l a where
- windowed :: Index l -> Index l -> Array l a -> Array (W l) a
- entire :: Bulk l a => Array l a -> Array (W l) a
- tail :: (Windowable l a, Index l ~ Int) => Array l a -> Maybe (Array l a)
- init :: (Windowable l a, Index l ~ Int) => Array l a -> Maybe (Array l a)
Documentation
Window | |
|
Eq (Name l) => Eq (Name (W l)) | |
(Eq l, Eq (Index l)) => Eq (W l) | |
Show (Name l) => Show (Name (W l)) | |
(Show l, Show (Index l)) => Show (W l) | |
Layout l => Layout (W l) | Windowed arrays. |
Bulk l a => Bulk (W l) a | Windowed arrays. |
Bulk l a => Windowable (W l) a | Windows are windowable. |
data Name (W l) = W (Name l) | |
type Index (W l) = Index l | |
data Array (W l) = WArray !(Index l) !(Index l) !(Array l a) |
class Bulk l a => Windowable l a where Source
Class of array representations that can be windowed directly.
The underlying representation can encode the window, without needing to add a wrapper to the existing layout.
Storable a => Windowable S a | |
Windowable B a | Boxed windows. |
Storable a => Windowable F a | Windowing Foreign arrays. |
Unbox a => Windowable U a | Windowing Unboxed arrays. |
Windowable A Char | |
Windowable A Double | |
Windowable A Float | |
Windowable A Int | |
Windowable A Int8 | |
Windowable A Int16 | |
Windowable A Int32 | |
Windowable A Int64 | |
Windowable A Word8 | |
Windowable A Date32 | |
Bulk A a => Windowable A [a] | |
(BulkI l a, Windowable l a) => Windowable N (Array l a) | Windowing Nested arrays. |
(Windowable A a, Windowable A b) => Windowable A (a, b) | |
(Windowable A a, Windowable A b) => Windowable A ((:*:) a b) | |
(Bulk A a, Windowable l a, (~) * (Index l) Int) => Windowable A (Array l a) | |
Bulk l a => Windowable (W l) a | Windows are windowable. |
(Windowable l1 a, Windowable l2 b, (~) * (Index l1) (Index l2)) => Windowable (T2 l1 l2) (a, b) | Tupled windows. |
windowed :: Index l -> Index l -> Array l a -> Array (W l) a Source
Wrap a window around an exiting array.
entire :: Bulk l a => Array l a -> Array (W l) a Source
Wrap a window around an existing array that encompases the entire array.