@@ -66,8 +66,9 @@ import qualified Prelude
66
66
-- prop> \ x -> (x |> f |> g) == g (f x)
67
67
infixl 0 |>
68
68
69
+ {-# INLINE (|>) #-}
69
70
(|>) :: a -> (a -> b ) -> b
70
- (|>) = Prelude. flip (<|)
71
+ (|>) = apply
71
72
72
73
-- | Right-associative 'apply' operator. Read as "apply backward" or "pipe
73
74
-- from". Use this to create long chains of computation that suggest which
@@ -90,8 +91,9 @@ infixl 0 |>
90
91
-- prop> \ x -> (g <| f <| x) == g (f x)
91
92
infixr 0 <|
92
93
94
+ {-# INLINE (<|) #-}
93
95
(<|) :: (a -> b ) -> a -> b
94
- (<|) = Prelude. id
96
+ (<|) f = f
95
97
96
98
-- | Function application. This function usually isn't necessary, but it can be
97
99
-- more readable than some alternatives when used with higher-order functions
@@ -110,8 +112,9 @@ infixr 0 <|
110
112
-- [3.0,0.5,-2.0]
111
113
--
112
114
-- prop> \ x -> apply x f == f x
115
+ {-# INLINE apply #-}
113
116
apply :: a -> (a -> b ) -> b
114
- apply = (|>)
117
+ apply x f = f x
115
118
116
119
-- | Left-associative 'compose' operator. Read as "compose forward" or "and
117
120
-- then". Use this to create long chains of computation that suggest which
@@ -128,8 +131,9 @@ apply = (|>)
128
131
-- prop> \ x -> (f .> g .> h) x == h (g (f x))
129
132
infixl 9 .>
130
133
134
+ {-# INLINE (.>) #-}
131
135
(.>) :: (a -> b ) -> (b -> c ) -> (a -> c )
132
- (.>) = Prelude. flip (<.)
136
+ f .> g = compose f g
133
137
134
138
-- | Right-associative 'compose' operator. Read as "compose backward" or "but
135
139
-- first". Use this to create long chains of computation that suggest which
@@ -153,8 +157,9 @@ infixl 9 .>
153
157
-- prop> \ x -> (h <. g <. f) x == h (g (f x))
154
158
infixr 9 <.
155
159
160
+ {-# INLINE (<.) #-}
156
161
(<.) :: (b -> c ) -> (a -> b ) -> (a -> c )
157
- (<.) = ( Prelude. .)
162
+ g <. f = compose f g
158
163
159
164
-- | Function composition. This function usually isn't necessary, but it can be
160
165
-- more readable than some alternatives when used with higher-order functions
@@ -174,8 +179,9 @@ infixr 9 <.
174
179
-- [0.25,-4.0]
175
180
--
176
181
-- prop> \ x -> compose f g x == g (f x)
182
+ {-# INLINE compose #-}
177
183
compose :: (a -> b ) -> (b -> c ) -> (a -> c )
178
- compose = (.> )
184
+ compose f g = \ x -> g (f x )
179
185
180
186
-- | Left-associative 'apply'' operator. Read as "strict apply forward" or
181
187
-- "strict pipe into". Use this to create long chains of computation that
@@ -198,8 +204,9 @@ compose = (.>)
198
204
-- prop> \ x -> (x !> f !> g) == let y = seq x (f x) in seq y (g y)
199
205
infixl 0 !>
200
206
207
+ {-# INLINE (!>) #-}
201
208
(!>) :: a -> (a -> b ) -> b
202
- (!>) = Prelude. flip (<!)
209
+ (!>) = \ x f -> f <! x
203
210
204
211
-- | Right-associative 'apply'' operator. Read as "strict apply backward" or
205
212
-- "strict pipe from". Use this to create long chains of computation that
@@ -231,6 +238,7 @@ infixl 0 !>
231
238
-- prop> \ x -> (g <! f <! x) == let y = seq x (f x) in seq y (g y)
232
239
infixr 0 <!
233
240
241
+ {-# INLINE (<!) #-}
234
242
(<!) :: (a -> b ) -> a -> b
235
243
(<!) = (Prelude. $!)
236
244
@@ -260,5 +268,6 @@ infixr 0 <!
260
268
-- [3.0,0.5,-2.0]
261
269
--
262
270
-- prop> \ x -> apply' x f == seq x (f x)
271
+ {-# INLINE apply' #-}
263
272
apply' :: a -> (a -> b ) -> b
264
273
apply' = (!>)
0 commit comments