defun-core-0.1: Defunctionalization helpers: core definitions
Safe HaskellTrustworthy
LanguageHaskell2010

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

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]

Equations

Append '[] ys = ys 
Append (x ': xs) ys = x ': Append xs ys 

data AppendSym xs Source #

Instances

Instances details
type App (AppendSym :: FunKind [a] ([a] ~> [a]) -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (AppendSym :: FunKind [a] ([a] ~> [a]) -> Type) (xs :: [a]) = AppendSym1 xs

data AppendSym1 xs ys Source #

Instances

Instances details
type App (AppendSym1 xs :: FunKind [a] [a] -> Type) (ys :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (AppendSym1 xs :: FunKind [a] [a] -> Type) (ys :: [a]) = Append xs ys

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]

Equations

Map f '[] = '[] 
Map f (x ': xs) = (f @@ x) ': Map f xs 

data MapSym f Source #

Instances

Instances details
type App (MapSym :: FunKind (a ~> b) ([a] ~> [b]) -> Type) (f :: a ~> b) Source # 
Instance details

Defined in DeFun.List

type App (MapSym :: FunKind (a ~> b) ([a] ~> [b]) -> Type) (f :: a ~> b) = MapSym1 f

data MapSym1 f xs Source #

Instances

Instances details
type App (MapSym1 f :: FunKind [a] [b] -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (MapSym1 f :: FunKind [a] [b] -> Type) (xs :: [a]) = Map f xs

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]

Equations

Concat '[] = '[] 
Concat (xs ': xss) = Append xs (Concat xss) 

data ConcatSym xss Source #

Instances

Instances details
type App (ConcatSym :: FunKind [[a]] [a] -> Type) (xss :: [[a]]) Source # 
Instance details

Defined in DeFun.List

type App (ConcatSym :: FunKind [[a]] [a] -> Type) (xss :: [[a]]) = Concat xss

ConcatMap

type family ConcatMap f xs where ... Source #

List concatMap

Equations

ConcatMap f '[] = '[] 
ConcatMap f (x ': xs) = Append (f @@ x) (ConcatMap f xs) 

data ConcatMapSym f Source #

Instances

Instances details
type App (ConcatMapSym :: FunKind (a ~> [b]) ([a] ~> [b]) -> Type) (f :: a ~> [b]) Source # 
Instance details

Defined in DeFun.List

type App (ConcatMapSym :: FunKind (a ~> [b]) ([a] ~> [b]) -> Type) (f :: a ~> [b]) = ConcatMapSym1 f

data ConcatMapSym1 f xs Source #

Instances

Instances details
type App (ConcatMapSym1 f :: FunKind [a] [b] -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (ConcatMapSym1 f :: FunKind [a] [b] -> Type) (xs :: [a]) = ConcatMap f xs

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')]

Equations

Map2 f xs ys = ConcatMap (CompSym2 (FlipSym2 MapSym ys) f) xs 

data Map2Sym f Source #

Instances

Instances details
type App (Map2Sym :: FunKind (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (f :: a ~> (b ~> c)) Source # 
Instance details

Defined in DeFun.List

type App (Map2Sym :: FunKind (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (f :: a ~> (b ~> c)) = Map2Sym1 f

data Map2Sym1 f xs Source #

Instances

Instances details
type App (Map2Sym1 f :: FunKind [a] ([b] ~> [c]) -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (Map2Sym1 f :: FunKind [a] ([b] ~> [c]) -> Type) (xs :: [a]) = Map2Sym2 f xs

data Map2Sym2 f xs ys Source #

Instances

Instances details
type App (Map2Sym2 f xs :: FunKind [b] [c] -> Type) (ys :: [b]) Source # 
Instance details

Defined in DeFun.List

type App (Map2Sym2 f xs :: FunKind [b] [c] -> Type) (ys :: [b]) = Map2 f xs ys

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]]

Equations

Sequence '[] = '['[]] 
Sequence (xs ': xss) = Map2 (Con2 '(:)) xs (Sequence xss) 

data SequenceSym xss Source #

Instances

Instances details
type App (SequenceSym :: FunKind [[a]] [[a]] -> Type) (xss :: [[a]]) Source # 
Instance details

Defined in DeFun.List

type App (SequenceSym :: FunKind [[a]] [[a]] -> Type) (xss :: [[a]]) = Sequence xss

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]

Equations

Foldr f z '[] = z 
Foldr f z (x ': xs) = (f @@ x) @@ Foldr f z xs 

data FoldrSym f Source #

Instances

Instances details
type App (FoldrSym :: FunKind (a ~> (b ~> b)) (b ~> ([a] ~> b)) -> Type) (f :: a ~> (b ~> b)) Source # 
Instance details

Defined in DeFun.List

type App (FoldrSym :: FunKind (a ~> (b ~> b)) (b ~> ([a] ~> b)) -> Type) (f :: a ~> (b ~> b)) = FoldrSym1 f

data FoldrSym1 f z Source #

Instances

Instances details
type App (FoldrSym1 f :: FunKind b ([a] ~> b) -> Type) (z :: b) Source # 
Instance details

Defined in DeFun.List

type App (FoldrSym1 f :: FunKind b ([a] ~> b) -> Type) (z :: b) = FoldrSym2 f z

data FoldrSym2 f z xs Source #

Instances

Instances details
type App (FoldrSym2 f z :: FunKind [a] b -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (FoldrSym2 f z :: FunKind [a] b -> Type) (xs :: [a]) = Foldr f z xs

Foldl

type family Foldl f z xs where ... Source #

List left fold

Equations

Foldl f z '[] = z 
Foldl f z (x ': xs) = Foldl f ((f @@ z) @@ x) xs 

data FoldlSym f Source #

Instances

Instances details
type App (FoldlSym :: FunKind (b ~> (a ~> b)) (b ~> ([a] ~> b)) -> Type) (f :: b ~> (a ~> b)) Source # 
Instance details

Defined in DeFun.List

type App (FoldlSym :: FunKind (b ~> (a ~> b)) (b ~> ([a] ~> b)) -> Type) (f :: b ~> (a ~> b)) = FoldlSym1 f

data FoldlSym1 f z Source #

Instances

Instances details
type App (FoldlSym1 f :: FunKind b ([a] ~> b) -> Type) (z :: b) Source # 
Instance details

Defined in DeFun.List

type App (FoldlSym1 f :: FunKind b ([a] ~> b) -> Type) (z :: b) = FoldlSym2 f z

data FoldlSym2 f z xs Source #

Instances

Instances details
type App (FoldlSym2 f z :: FunKind [a] b -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (FoldlSym2 f z :: FunKind [a] b -> Type) (xs :: [a]) = Foldl f z xs

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')]

Equations

ZipWith f '[] ys = '[] 
ZipWith f (x ': xs) '[] = '[] 
ZipWith f (x ': xs) (y ': ys) = ((f @@ x) @@ y) ': ZipWith f xs ys 

data ZipWithSym f Source #

Instances

Instances details
type App (ZipWithSym :: FunKind (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (f :: a ~> (b ~> c)) Source # 
Instance details

Defined in DeFun.List

type App (ZipWithSym :: FunKind (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (f :: a ~> (b ~> c)) = ZipWithSym1 f

data ZipWithSym1 f xs Source #

Instances

Instances details
type App (ZipWithSym1 f :: FunKind [a] ([b] ~> [c]) -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (ZipWithSym1 f :: FunKind [a] ([b] ~> [c]) -> Type) (xs :: [a]) = ZipWithSym2 f xs

data ZipWithSym2 f xs ys Source #

Instances

Instances details
type App (ZipWithSym2 f xs :: FunKind [b] [c] -> Type) (ys :: [b]) Source # 
Instance details

Defined in DeFun.List

type App (ZipWithSym2 f xs :: FunKind [b] [c] -> Type) (ys :: [b]) = ZipWith f xs ys

Filter

type family Filter p xs where ... Source #

Filter list

Equations

Filter f '[] = '[] 
Filter f (x ': xs) = FilterAux (f @@ x) x f xs 

data FilterSym p Source #

Instances

Instances details
type App (FilterSym :: FunKind (a ~> Bool) ([a] ~> [a]) -> Type) (p :: a ~> Bool) Source # 
Instance details

Defined in DeFun.List

type App (FilterSym :: FunKind (a ~> Bool) ([a] ~> [a]) -> Type) (p :: a ~> Bool) = FilterSym1 p

data FilterSym1 p xs Source #

Instances

Instances details
type App (FilterSym1 p :: FunKind [a] [a] -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (FilterSym1 p :: FunKind [a] [a] -> Type) (xs :: [a]) = Filter p xs

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]

Equations

Reverse xs = Foldl (FlipSym1 (Con2 '(:))) '[] xs 

data ReverseSym xs Source #

Instances

Instances details
type App (ReverseSym :: FunKind [a] [a] -> Type) (xs :: [a]) Source # 
Instance details

Defined in DeFun.List

type App (ReverseSym :: FunKind [a] [a] -> Type) (xs :: [a]) = Reverse xs