Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
DeFun.List
Description
List type-families.
For term-level reflections see defun-sop package.
Implementation note: It would be great if first-order type families,
like Append
and Concat
, were defined already in base
,
e.g. in Data.Type.List
module.
Higher-order type families, like Map
, obviously cannot be there
as they rely on the defunctorization machinery.
Yet, some first-order type families like Sequence
and Reverse
may also be defined directly, but it's more convenient to define
them as special case of an higher-order type family (Map2
and Foldl
respectively), as that makes working with them more convenient.
Synopsis
- type family Append xs ys where ...
- data AppendSym xs
- data AppendSym1 xs ys
- type family Map f xs where ...
- data MapSym f
- data MapSym1 f xs
- type family Concat xss where ...
- data ConcatSym xss
- type family ConcatMap f xs where ...
- data ConcatMapSym f
- data ConcatMapSym1 f xs
- type family Map2 f xs ys where ...
- data Map2Sym f
- data Map2Sym1 f xs
- data Map2Sym2 f xs ys
- type family Sequence xss where ...
- data SequenceSym xss
- type family Foldr f z xs where ...
- data FoldrSym f
- data FoldrSym1 f z
- data FoldrSym2 f z xs
- type family Foldl f z xs where ...
- data FoldlSym f
- data FoldlSym1 f z
- data FoldlSym2 f z xs
- type family ZipWith f xs ys where ...
- data ZipWithSym f
- data ZipWithSym1 f xs
- data ZipWithSym2 f xs ys
- type family Filter p xs where ...
- data FilterSym p
- data FilterSym1 p xs
- type family Reverse xs where ...
- data ReverseSym xs
Append
type family Append xs ys where ... Source #
List append.
>>>
:kind! Append [1, 2, 3] [4, 5, 6]
Append [1, 2, 3] [4, 5, 6] :: [Natural] = [1, 2, 3, 4, 5, 6]
data AppendSym1 xs ys Source #
Instances
type App (AppendSym1 xs :: FunKind [a] [a] -> Type) (ys :: [a]) Source # | |
Defined in DeFun.List |
Map
type family Map f xs where ... Source #
List map
>>>
:kind! Map NotSym [True, False]
Map NotSym [True, False] :: [Bool] = [False, True]
>>>
:kind! Map (Con1 Just) [1, 2, 3]
Map (Con1 Just) [1, 2, 3] :: [Maybe Natural] = [Just 1, Just 2, Just 3]
Concat
type family Concat xss where ... Source #
List concat
>>>
:kind! Concat [ [1, 2, 3], [4, 5, 6], [7, 8, 9] ]
Concat [ [1, 2, 3], [4, 5, 6], [7, 8, 9] ] :: [Natural] = [1, 2, 3, 4, 5, 6, 7, 8, 9]
ConcatMap
data ConcatMapSym f Source #
Instances
type App (ConcatMapSym :: FunKind (a ~> [b]) ([a] ~> [b]) -> Type) (f :: a ~> [b]) Source # | |
Defined in DeFun.List type App (ConcatMapSym :: FunKind (a ~> [b]) ([a] ~> [b]) -> Type) (f :: a ~> [b]) = ConcatMapSym1 f |
data ConcatMapSym1 f xs Source #
Instances
type App (ConcatMapSym1 f :: FunKind [a] [b] -> Type) (xs :: [a]) Source # | |
Defined in DeFun.List |
Map2
type family Map2 f xs ys where ... Source #
List binary map. I.e. liftA2
for lists.
Note: this is not ZipWith
.
>>>
:kind! Map2 (Con2 '(,)) [1, 2, 3] ['x', 'y']
Map2 (Con2 '(,)) [1, 2, 3] ['x', 'y'] :: [(Natural, Char)] = ['(1, 'x'), '(1, 'y'), '(2, 'x'), '(2, 'y'), '(3, 'x'), '(3, 'y')]
This function is a good example to highlight how to defunctionalize definitions with anonymous functions.
The simple definition can be written using concatMap
and map
from
Prelude:
>>>
import Prelude as P (concatMap, map, (.), flip)
>>>
let map2 f xs ys = P.concatMap (\x -> P.map (f x) ys) xs
>>>
map2 (,) "abc" "xy"
[('a','x'),('a','y'),('b','x'),('b','y'),('c','x'),('c','y')]
However, to make it easier (arguably) to defunctionalize, the concatMap
argument
lambda can be written in point-free form using combinators:
>>>
let map2 f xs ys = P.concatMap (P.flip P.map ys P.. f) xs
>>>
map2 (,) "abc" "xy"
[('a','x'),('a','y'),('b','x'),('b','y'),('c','x'),('c','y')]
Alternatively, we could define a new "top-level" function
>>>
let map2Aux f ys x = P.map (f x) ys
and use it to define @map2:
>>>
let map2 f xs ys = P.concatMap (map2Aux f ys) xs
>>>
map2 (,) "abc" "xy"
[('a','x'),('a','y'),('b','x'),('b','y'),('c','x'),('c','y')]
Sequence
type family Sequence xss where ... Source #
List sequence
>>>
:kind! Sequence [[1,2,3],[4,5,6]]
Sequence [[1,2,3],[4,5,6]] :: [[Natural]] = [[1, 4], [1, 5], [1, 6], [2, 4], [2, 5], [2, 6], [3, 4], [3, 5], [3, 6]]
data SequenceSym xss Source #
Instances
type App (SequenceSym :: FunKind [[a]] [[a]] -> Type) (xss :: [[a]]) Source # | |
Defined in DeFun.List |
Foldr
type family Foldr f z xs where ... Source #
List right fold
Using Foldr
we can define a Curry
type family:
>>>
type Curry args res = Foldr (Con2 (->)) args res
>>>
:kind! Curry String [Int, Bool]
Curry String [Int, Bool] :: * = Int -> Bool -> [Char]
Foldl
ZipWith
type family ZipWith f xs ys where ... Source #
Zip with
>>>
:kind! ZipWith (Con2 '(,)) [1, 2, 3] ['x', 'y']
ZipWith (Con2 '(,)) [1, 2, 3] ['x', 'y'] :: [(Natural, Char)] = ['(1, 'x'), '(2, 'y')]
data ZipWithSym f Source #
data ZipWithSym1 f xs Source #
Instances
type App (ZipWithSym1 f :: FunKind [a] ([b] ~> [c]) -> Type) (xs :: [a]) Source # | |
Defined in DeFun.List |
data ZipWithSym2 f xs ys Source #
Instances
type App (ZipWithSym2 f xs :: FunKind [b] [c] -> Type) (ys :: [b]) Source # | |
Defined in DeFun.List |
Filter
data FilterSym1 p xs Source #
Instances
type App (FilterSym1 p :: FunKind [a] [a] -> Type) (xs :: [a]) Source # | |
Defined in DeFun.List |
Reverse
type family Reverse xs where ... Source #
Reverse list
>>>
:kind! Reverse [1,2,3,4]
Reverse [1,2,3,4] :: [Natural] = [4, 3, 2, 1]
data ReverseSym xs Source #
Instances
type App (ReverseSym :: FunKind [a] [a] -> Type) (xs :: [a]) Source # | |
Defined in DeFun.List |