Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- class IndexedListLiterals (input :: Type) (length :: Nat) (output :: Type) | output length -> input, input -> output length where
- type ILL = IndexedListLiterals
- module Data.Tuple.Only
- data ZeroTuple a = ZeroTuple
- len :: Proxy a
- fromList :: forall input (length :: Nat) output. (KnownNat length, ILL input length output) => [output] -> Maybe input
- fromListP :: forall input (length :: Nat) output len. (KnownNat length, ILL input length output) => len length -> [output] -> Maybe input
Documentation
class IndexedListLiterals (input :: Type) (length :: Nat) (output :: Type) | output length -> input, input -> output length where Source #
A type class which allows you to write tuples which can be transformed to and from a list the length of the list is also provided as a Nat
toList :: input -> [output] Source #
> toList (Only 1) [1]
> toList (1,2,3) [1,2,3]
> toList ZeroTuple []
fromList' :: [output] -> input Source #
a partial fromList with bad error messages
IndexedListLiterals (Only a) 1 a Source # | |
IndexedListLiterals (a, a) 2 a Source # | |
IndexedListLiterals (ZeroTuple Type a) 0 a Source # | |
IndexedListLiterals (a, a, a) 3 a Source # | |
IndexedListLiterals (a, a, a, a) 4 a Source # | |
IndexedListLiterals (a, a, a, a, a) 5 a Source # | |
IndexedListLiterals (a, a, a, a, a, a) 6 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a) 7 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a) 8 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a) 9 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a) 10 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a) 11 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a) 12 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a) 13 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a) 14 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) 15 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) 16 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) 17 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) 18 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) 19 a Source # | |
IndexedListLiterals (a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a, a) 20 a Source # | |
type ILL = IndexedListLiterals Source #
An alias for IndexedListLiterals
module Data.Tuple.Only
Intuitively the zero tuple is () or Void but this breaks the Functional Dependency "input -> output length" stopping reliable inference, so this constructor is used to preserve type information
IndexedListLiterals (ZeroTuple Type a) 0 a Source # | |
fromList :: forall input (length :: Nat) output. (KnownNat length, ILL input length output) => [output] -> Maybe input Source #
> fromList [1,2,3] :: Maybe (Int, Int, Int) Just (1,2,3)
> fromList ["word","up"] :: Maybe (String, String, String) Nothing
> fromList ['z'] :: Maybe (Only Char) Just (Only 'z')
fromListP :: forall input (length :: Nat) output len. (KnownNat length, ILL input length output) => len length -> [output] -> Maybe input Source #
the fromList variants take a list and convert it into a tuple it's sort of the inverse of toList
> fromListP (len @3) [1,2,3] Just (1,2,3)
> fromListP (len @3) ["word","up"] Nothing
> fromListP (len @1) ['z'] Just (Only 'z') @