/ src / Generics / Pointless /
src/Generics/Pointless/Combinators.hs
1
2 -----------------------------------------------------------------------------
3 -- |
4 -- Module : Generics.Pointless.Combinators
5 -- Copyright : (c) 2008 University of Minho
6 -- License : BSD3
7 --
8 -- Maintainer : hpacheco@di.uminho.pt
9 -- Stability : experimental
10 -- Portability : non-portable
11 --
12 -- Pointless Haskell:
13 -- point-free programming with recursion patterns as hylomorphisms
14 --
15 -- This module defines many standard combinators used for point-free programming.
16 --
17 -----------------------------------------------------------------------------
18
19 module Generics.Pointless.Combinators where
20
21 -- * Terminal object
22
23 -- | The bottom value for any type.
24 -- It is many times used just for type annotations.
25 _L :: a
26 _L = undefined
27
28 -- | The final object.
29 -- The only possible value of type 'One' is '_L'.
30 data One
31
32 instance Show One where
33 show _ = "_L"
34
35 instance Eq One where
36 (==) _ _ = True
37
38 -- * Points
39
40 -- | Creates a point to the terminal object.
41 bang :: a -> One
42 bang = const _L
43
44 -- | Converts elements into points.
45 pnt :: a -> One -> a
46 pnt = const
47
48 -- * Products
49
50 infix 6 /\
51 -- | The infix split combinator.
52 (/\) :: (a -> b) -> (a -> c) -> a -> (b,c)
53 (/\) f g x = (f x, g x)
54
55 infix 7 ><
56 -- The infix product combinator.
57 (><) :: (a -> b) -> (c -> d) -> (a,c) -> (b,d)
58 f >< g = f . fst /\ g . snd
59
60 -- * Sums
61
62 -- | Injects a value to the left of a sum.
63 inl :: a -> Either a b
64 inl = Left
65
66 -- | Injects a value to the right of a sum.
67 inr :: b -> Either a b
68 inr = Right
69
70 infix 4 \/
71 -- | The infix either combinator.
72 (\/) :: (b -> a) -> (c -> a) -> Either b c -> a
73 (\/) = either
74
75 infix 5 -|-
76 -- | The infix sum combinator.
77 (-|-) :: (a -> b) -> (c -> d) -> Either a c -> Either b d
78 f -|- g = inl . f \/ inr . g
79
80 infix 5 <>
81 -- | Alias for the infix sum combinator.
82 (<>) :: (a -> b) -> (c -> d) -> Either a c -> Either b d
83 (<>) = (-|-)
84
85 -- * Exponentials
86
87 -- | The application combinator.
88 app :: (a -> b, a) -> b
89 app (f,x) = f x
90
91 infix 0 !
92 -- | The infix combinator for a constant point.
93 (!) :: a -> b -> a
94 (!) = const
95
96 -- * Guards
97
98 -- | Guard combinator that operates on Haskell booleans.
99 grd :: (a -> Bool) -> a -> Either a a
100 grd p x = if p x then inl x else inr x
101
102 -- | Infix guarc combinator that simulates the postfix syntax.
103 (?) :: (a -> Bool) -> a -> Either a a
104 (?) = grd
105
106 -- * Point-free definitions of uncurried versions of the basic combinators
107
108 -- | The uncurried split combinator.
109 split :: (a -> b, a -> c) -> (a -> (b,c))
110 split = curry ((app >< app) . ((fst >< id) /\ (snd >< id)))
111
112 -- | The uncurried either combinator.
113 eithr :: (a -> c, b -> c) -> Either a b -> c
114 eithr = curry ((app \/ app) . (fst >< id -|- snd >< id) . distr)
115
116 -- | The uncurried composition combinator.
117 comp :: (b -> c, a -> b) -> (a -> c)
118 comp = curry (app . (id >< app) . assocr)
119
120 -- * Point-free isomorphic combinators
121
122 -- | Swap the elements of a product.
123 swap :: (a,b) -> (b,a)
124 swap = snd /\ fst
125
126 -- | Swap the elements of a sum.
127 coswap :: Either a b -> Either b a
128 coswap = inr \/ inl
129
130 -- | Distribute products over the left of sums.
131 distl :: (Either a b, c) -> Either (a,c) (b,c)
132 distl = app . ((curry inl \/ curry inr) >< id)
133
134 -- | Distribute sums over the left of products.
135 undistl :: Either (a,c) (b,c) -> (Either a b, c)
136 undistl = inl >< id \/ inr >< id
137
138 -- | Distribute products over the right of sums.
139 distr :: (c, Either a b) -> Either (c,a) (c,b)
140 distr = (swap -|- swap) . distl . swap
141
142 -- | Distribute sums over the right of products.
143 undistr :: Either (c,a) (c,b) -> (c, Either a b)
144 undistr = (id >< inl) \/ (id >< inr)
145
146 -- | Associate nested products to the left.
147 assocl :: (a,(b,c)) -> ((a,b),c)
148 assocl = id >< fst /\ snd . snd
149
150 -- | Associates nested products to the right.
151 assocr :: ((a,b),c) -> (a,(b,c))
152 assocr = fst . fst /\ snd >< id
153
154 -- | Associates nested sums to the left.
155 coassocl :: Either a (Either b c) -> Either (Either a b) c
156 coassocl = (inl . inl) \/ (inr -|- id)
157
158 -- | Associates nested sums to the right.
159 coassocr :: Either (Either a b) c -> Either a (Either b c)
160 coassocr = (id -|- inl) \/ (inr . inr)
161