| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Haskus.Utils.Tuple
Description
Tuple helpers
Synopsis
- uncurry3 :: (a -> b -> c -> r) -> (a, b, c) -> r
- uncurry4 :: (a -> b -> c -> d -> r) -> (a, b, c, d) -> r
- uncurry5 :: (a -> b -> c -> d -> e -> r) -> (a, b, c, d, e) -> r
- uncurry6 :: (a -> b -> c -> d -> e -> f -> r) -> (a, b, c, d, e, f) -> r
- uncurry7 :: (a -> b -> c -> d -> e -> f -> g -> r) -> (a, b, c, d, e, f, g) -> r
- take4 :: [a] -> (a, a, a, a)
- fromTuple4 :: (a, a, a, a) -> [a]
- module Data.Tuple
- data Unit a = Unit a
- type family Tuple xs = t | t -> xs where ...
- type family Tuple# xs = (t :: TYPE (TupleRep (TypeReps xs))) | t -> xs where ...
- type family TypeReps xs where ...
- class ExtractTuple (n :: Nat) xs where
- class TupleCon xs where
- tupleHead :: forall xs. ExtractTuple 0 xs => Tuple xs -> Index 0 xs
- class TupleTail ts ts' | ts -> ts' where- tupleTail :: ts -> ts'
 
- class TupleCons t ts ts' | t ts -> ts' where- tupleCons :: t -> ts -> ts'
 
- class ReorderTuple t1 t2 where- tupleReorder :: t1 -> t2
 
Documentation
fromTuple4 :: (a, a, a, a) -> [a] Source #
toList for quadruple
module Data.Tuple
Constructors
| Unit a | 
Instances
| TupleCons a (Unit b) (a, b) Source # | |
| Defined in Haskus.Utils.Tuple | |
| ReorderTuple (Unit a) (Unit a) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: Unit a -> Unit a Source # | |
| TupleTail (a, b) (Unit b) Source # | |
| Defined in Haskus.Utils.Tuple | |
type family Tuple xs = t | t -> xs where ... Source #
Boxed tuple
TODO: put this family into GHC
Equations
| Tuple '[] = () | |
| Tuple '[a] = Unit a | |
| Tuple '[a, b] = (a, b) | |
| Tuple '[a, b, c] = (a, b, c) | |
| Tuple '[a, b, c, d] = (a, b, c, d) | |
| Tuple '[a, b, c, d, e] = (a, b, c, d, e) | |
| Tuple '[a, b, c, d, e, f] = (a, b, c, d, e, f) | |
| Tuple '[a, b, c, d, e, f, g] = (a, b, c, d, e, f, g) | |
| Tuple '[a, b, c, d, e, f, g, h] = (a, b, c, d, e, f, g, h) | |
| Tuple '[a, b, c, d, e, f, g, h, i] = (a, b, c, d, e, f, g, h, i) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j] = (a, b, c, d, e, f, g, h, i, j) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k] = (a, b, c, d, e, f, g, h, i, j, k) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l] = (a, b, c, d, e, f, g, h, i, j, k, l) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m] = (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) | |
| Tuple '[a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z] = (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) | 
type family Tuple# xs = (t :: TYPE (TupleRep (TypeReps xs))) | t -> xs where ... Source #
Unboxed tuple
TODO: put this family into GHC
Equations
| Tuple# '[] = (##) | |
| Tuple# '[a] = (#a#) | |
| Tuple# '[a, b] = (#a, b#) | |
| Tuple# '[a, b, c] = (#a, b, c#) | |
| Tuple# '[a, b, c, d] = (#a, b, c, d#) | |
| Tuple# '[a, b, c, d, e] = (#a, b, c, d, e#) | |
| Tuple# '[a, b, c, d, e, f] = (#a, b, c, d, e, f#) | |
| Tuple# '[a, b, c, d, e, f, g] = (#a, b, c, d, e, f, g#) | |
| Tuple# '[a, b, c, d, e, f, g, h] = (#a, b, c, d, e, f, g, h#) | |
| Tuple# '[a, b, c, d, e, f, g, h, i] = (#a, b, c, d, e, f, g, h, i#) | 
class ExtractTuple (n :: Nat) xs where Source #
Extract a tuple value statically
Instances
| ExtractTuple 0 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 0 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 0 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': ([] :: [Type]))))))) Source # | |
| ExtractTuple 0 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': ([] :: [Type])))))) Source # | |
| ExtractTuple 0 (e0 ': (e1 ': (e2 ': (e3 ': ([] :: [Type]))))) Source # | |
| ExtractTuple 0 (e0 ': (e1 ': (e2 ': ([] :: [Type])))) Source # | |
| ExtractTuple 0 (e0 ': (e1 ': ([] :: [Type]))) Source # | |
| ExtractTuple 0 (a ': ([] :: [Type])) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': ([] :: [Type]))))))) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': ([] :: [Type])))))) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': (e2 ': (e3 ': ([] :: [Type]))))) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': (e2 ': ([] :: [Type])))) Source # | |
| ExtractTuple 1 (e0 ': (e1 ': ([] :: [Type]))) Source # | |
| ExtractTuple 2 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 2 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 2 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': ([] :: [Type]))))))) Source # | |
| ExtractTuple 2 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': ([] :: [Type])))))) Source # | |
| ExtractTuple 2 (e0 ': (e1 ': (e2 ': (e3 ': ([] :: [Type]))))) Source # | |
| ExtractTuple 2 (e0 ': (e1 ': (e2 ': ([] :: [Type])))) Source # | |
| ExtractTuple 3 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 3 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 3 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': ([] :: [Type]))))))) Source # | |
| ExtractTuple 3 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': ([] :: [Type])))))) Source # | |
| ExtractTuple 3 (e0 ': (e1 ': (e2 ': (e3 ': ([] :: [Type]))))) Source # | |
| ExtractTuple 4 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 4 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 4 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': ([] :: [Type]))))))) Source # | |
| ExtractTuple 4 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': ([] :: [Type])))))) Source # | |
| ExtractTuple 5 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 5 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 5 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': ([] :: [Type]))))))) Source # | |
| ExtractTuple 6 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
| ExtractTuple 6 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': ([] :: [Type])))))))) Source # | |
| ExtractTuple 7 (e0 ': (e1 ': (e2 ': (e3 ': (e4 ': (e5 ': (e6 ': (e7 ': ([] :: [Type]))))))))) Source # | |
class TupleCon xs where Source #
Create a Tuple
Instances
| TupleCon ([] :: [Type]) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCon (a ': (b ': (c ': (d ': (e ': (f ': ([] :: [Type]))))))) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCon (a ': (b ': (c ': (d ': (e ': ([] :: [Type])))))) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCon (a ': (b ': (c ': (d ': ([] :: [Type]))))) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCon (a ': (b ': (c ': ([] :: [Type])))) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCon (a ': (b ': ([] :: [Type]))) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCon (a ': ([] :: [Type])) Source # | |
| Defined in Haskus.Utils.Tuple | |
tupleHead :: forall xs. ExtractTuple 0 xs => Tuple xs -> Index 0 xs Source #
Get first element of the tuple
class TupleTail ts ts' | ts -> ts' where Source #
Instances
| TupleTail (a, b) (Unit b) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleTail (a, b, c) (b, c) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleTail (a, b, c, d) (b, c, d) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleTail (a, b, c, d, e) (b, c, d, e) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleTail (a, b, c, d, e, f) (b, c, d, e, f) Source # | |
| Defined in Haskus.Utils.Tuple | |
class TupleCons t ts ts' | t ts -> ts' where Source #
Instances
| TupleCons a (Unit b) (a, b) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCons a (b, c) (a, b, c) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCons a (b, c, d) (a, b, c, d) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCons a (b, c, d, e) (a, b, c, d, e) Source # | |
| Defined in Haskus.Utils.Tuple | |
| TupleCons a (b, c, d, e, f) (a, b, c, d, e, f) Source # | |
| Defined in Haskus.Utils.Tuple | |
class ReorderTuple t1 t2 where Source #
Reorder tuple elements
Instances
| ReorderTuple (Unit a) (Unit a) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: Unit a -> Unit a Source # | |
| ReorderTuple (a, b) (b, a) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b) -> (b, a) Source # | |
| ReorderTuple (a, b) (a, b) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b) -> (a, b) Source # | |
| ReorderTuple (a, b, c) (c, b, a) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c) -> (c, b, a) Source # | |
| ReorderTuple (a, b, c) (c, a, b) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c) -> (c, a, b) Source # | |
| ReorderTuple (a, b, c) (b, c, a) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c) -> (b, c, a) Source # | |
| ReorderTuple (a, b, c) (b, a, c) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c) -> (b, a, c) Source # | |
| ReorderTuple (a, b, c) (a, c, b) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c) -> (a, c, b) Source # | |
| ReorderTuple (a, b, c) (a, b, c) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c) -> (a, b, c) Source # | |
| ReorderTuple (a, b, c) (x, y, z) => ReorderTuple (a, b, c, d) (x, y, z, d) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d) -> (x, y, z, d) Source # | |
| ReorderTuple (a, b, d) (x, y, z) => ReorderTuple (a, b, c, d) (x, y, c, z) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d) -> (x, y, c, z) Source # | |
| ReorderTuple (a, c, d) (x, y, z) => ReorderTuple (a, b, c, d) (x, b, y, z) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d) -> (x, b, y, z) Source # | |
| ReorderTuple (b, c, d) (x, y, z) => ReorderTuple (a, b, c, d) (a, x, y, z) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d) -> (a, x, y, z) Source # | |
| ReorderTuple (a, b, c, d) (a, b, c, d) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d) -> (a, b, c, d) Source # | |
| ReorderTuple (a, b, c, d) (x, y, z, w) => ReorderTuple (a, b, c, d, e) (x, y, z, w, e) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e) -> (x, y, z, w, e) Source # | |
| ReorderTuple (a, b, c, e) (x, y, z, w) => ReorderTuple (a, b, c, d, e) (x, y, z, d, w) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e) -> (x, y, z, d, w) Source # | |
| ReorderTuple (a, b, d, e) (x, y, z, w) => ReorderTuple (a, b, c, d, e) (x, y, c, z, w) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e) -> (x, y, c, z, w) Source # | |
| ReorderTuple (a, c, d, e) (x, y, z, w) => ReorderTuple (a, b, c, d, e) (x, b, y, z, w) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e) -> (x, b, y, z, w) Source # | |
| ReorderTuple (b, c, d, e) (x, y, z, w) => ReorderTuple (a, b, c, d, e) (a, x, y, z, w) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e) -> (a, x, y, z, w) Source # | |
| ReorderTuple (a, b, c, d, e) (a, b, c, d, e) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e) -> (a, b, c, d, e) Source # | |
| ReorderTuple (a, b, c, d, e) (x, y, z, w, v) => ReorderTuple (a, b, c, d, e, f) (x, y, z, w, v, f) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (x, y, z, w, v, f) Source # | |
| ReorderTuple (a, b, c, d, f) (x, y, z, w, v) => ReorderTuple (a, b, c, d, e, f) (x, y, z, w, e, v) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (x, y, z, w, e, v) Source # | |
| ReorderTuple (a, b, c, e, f) (x, y, z, w, v) => ReorderTuple (a, b, c, d, e, f) (x, y, z, d, w, v) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (x, y, z, d, w, v) Source # | |
| ReorderTuple (a, b, d, e, f) (x, y, z, w, v) => ReorderTuple (a, b, c, d, e, f) (x, y, c, z, w, v) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (x, y, c, z, w, v) Source # | |
| ReorderTuple (a, c, d, e, f) (x, y, z, w, v) => ReorderTuple (a, b, c, d, e, f) (x, b, y, z, w, v) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (x, b, y, z, w, v) Source # | |
| ReorderTuple (b, c, d, e, f) (x, y, z, w, v) => ReorderTuple (a, b, c, d, e, f) (a, x, y, z, w, v) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (a, x, y, z, w, v) Source # | |
| ReorderTuple (a, b, c, d, e, f) (a, b, c, d, e, f) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source # | |
| ReorderTuple (a, b, c, d, e, f) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (x, y, z, w, v, u, g) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, w, v, u, g) Source # | |
| ReorderTuple (a, b, c, d, e, g) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (x, y, z, w, v, f, u) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, w, v, f, u) Source # | |
| ReorderTuple (a, b, c, d, f, g) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (x, y, z, w, e, v, u) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, w, e, v, u) Source # | |
| ReorderTuple (a, b, c, e, f, g) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (x, y, z, d, w, v, u) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, z, d, w, v, u) Source # | |
| ReorderTuple (a, b, d, e, f, g) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (x, y, c, z, w, v, u) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (x, y, c, z, w, v, u) Source # | |
| ReorderTuple (a, c, d, e, f, g) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (x, b, y, z, w, v, u) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (x, b, y, z, w, v, u) Source # | |
| ReorderTuple (b, c, d, e, f, g) (x, y, z, w, v, u) => ReorderTuple (a, b, c, d, e, f, g) (a, x, y, z, w, v, u) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (a, x, y, z, w, v, u) Source # | |
| ReorderTuple (a, b, c, d, e, f, g) (a, b, c, d, e, f, g) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source # | |
| ReorderTuple (a, b, c, d, e, f, g, h) (a, b, c, d, e, f, g, h) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source # | |
| ReorderTuple (a, b, c, d, e, f, g, h, i) (a, b, c, d, e, f, g, h, i) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source # | |
| ReorderTuple (a, b, c, d, e, f, g, h, i, j) (a, b, c, d, e, f, g, h, i, j) Source # | |
| Defined in Haskus.Utils.Tuple Methods tupleReorder :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source # | |