2727--
2828-- So instead of ('Prelude.$'), I propose ('<|'). It is a pipe, which anyone
2929-- who has touched a Unix system should be familiar with. And it points in the
30- -- direction it sends arguments along. Similarly, replace ('Prelude. &') with
31- -- ('|>'). And for composition, ('<.') replaces ('Prelude..'). I would have
32- -- preferred @<<@, but its counterpart @>>@ is taken by Haskell's syntax.
30+ -- direction it sends arguments along. Similarly, replace ('Data.Function. &')
31+ -- with ('|>'). And for composition, ('<.') replaces ('Prelude..'). I would
32+ -- have preferred @<<@, but its counterpart @>>@ is taken by Haskell's syntax.
3333-- So-called "backwards" composition is normally expressed with
3434-- ('Control.Category.>>>'), which Flow provides as ('.>').
3535module Flow
@@ -50,7 +50,7 @@ module Flow
5050 )
5151where
5252
53- import Prelude ( seq )
53+ import qualified Prelude
5454
5555-- | Left-associative 'apply' operator. Read as "apply forward" or "pipe into".
5656-- Use this to create long chains of computation that suggest which direction
@@ -59,15 +59,16 @@ import Prelude (seq)
5959-- >>> 3 |> succ |> recip |> negate
6060-- -0.25
6161--
62- -- Or use it anywhere you would use ('Prelude .&').
62+ -- Or use it anywhere you would use ('Data.Function .&').
6363--
6464-- prop> \ x -> (x |> f) == f x
6565--
6666-- prop> \ x -> (x |> f |> g) == g (f x)
6767infixl 0 |>
6868
69+ {-# INLINE (|>) #-}
6970(|>) :: a -> (a -> b ) -> b
70- x |> f = apply x f
71+ (|>) = apply
7172
7273-- | Right-associative 'apply' operator. Read as "apply backward" or "pipe
7374-- from". Use this to create long chains of computation that suggest which
@@ -90,8 +91,9 @@ x |> f = apply x f
9091-- prop> \ x -> (g <| f <| x) == g (f x)
9192infixr 0 <|
9293
94+ {-# INLINE (<|) #-}
9395(<|) :: (a -> b ) -> a -> b
94- f <| x = apply x f
96+ (<|) f = f
9597
9698-- | Function application. This function usually isn't necessary, but it can be
9799-- more readable than some alternatives when used with higher-order functions
@@ -110,6 +112,7 @@ f <| x = apply x f
110112-- [3.0,0.5,-2.0]
111113--
112114-- prop> \ x -> apply x f == f x
115+ {-# INLINE apply #-}
113116apply :: a -> (a -> b ) -> b
114117apply x f = f x
115118
@@ -128,6 +131,7 @@ apply x f = f x
128131-- prop> \ x -> (f .> g .> h) x == h (g (f x))
129132infixl 9 .>
130133
134+ {-# INLINE (.>) #-}
131135(.>) :: (a -> b ) -> (b -> c ) -> (a -> c )
132136f .> g = compose f g
133137
@@ -153,6 +157,7 @@ f .> g = compose f g
153157-- prop> \ x -> (h <. g <. f) x == h (g (f x))
154158infixr 9 <.
155159
160+ {-# INLINE (<.) #-}
156161(<.) :: (b -> c ) -> (a -> b ) -> (a -> c )
157162g <. f = compose f g
158163
@@ -174,8 +179,9 @@ g <. f = compose f g
174179-- [0.25,-4.0]
175180--
176181-- prop> \ x -> compose f g x == g (f x)
182+ {-# INLINE compose #-}
177183compose :: (a -> b ) -> (b -> c ) -> (a -> c )
178- compose f g x = g (f x)
184+ compose f g = \ x -> g (f x)
179185
180186-- | Left-associative 'apply'' operator. Read as "strict apply forward" or
181187-- "strict pipe into". Use this to create long chains of computation that
@@ -198,8 +204,9 @@ compose f g x = g (f x)
198204-- prop> \ x -> (x !> f !> g) == let y = seq x (f x) in seq y (g y)
199205infixl 0 !>
200206
207+ {-# INLINE (!>) #-}
201208(!>) :: a -> (a -> b ) -> b
202- x !> f = apply' x f
209+ (!>) = \ x f -> f <! x
203210
204211-- | Right-associative 'apply'' operator. Read as "strict apply backward" or
205212-- "strict pipe from". Use this to create long chains of computation that
@@ -209,6 +216,8 @@ x !> f = apply' x f
209216-- >>> print <! negate <! recip <! succ <! 3
210217-- -0.25
211218--
219+ -- Or use it anywhere you would use ('Prelude.$!').
220+ --
212221-- The difference between this and ('<|') is that this evaluates its argument
213222-- before passing it to the function.
214223--
@@ -229,8 +238,9 @@ x !> f = apply' x f
229238-- prop> \ x -> (g <! f <! x) == let y = seq x (f x) in seq y (g y)
230239infixr 0 <!
231240
241+ {-# INLINE (<!) #-}
232242(<!) :: (a -> b ) -> a -> b
233- f <! x = apply' x f
243+ (<!) = ( Prelude. $!)
234244
235245-- | Strict function application. This function usually isn't necessary, but it
236246-- can be more readable than some alternatives when used with higher-order
@@ -258,5 +268,6 @@ f <! x = apply' x f
258268-- [3.0,0.5,-2.0]
259269--
260270-- prop> \ x -> apply' x f == seq x (f x)
271+ {-# INLINE apply' #-}
261272apply' :: a -> (a -> b ) -> b
262- apply' x f = seq x (apply x f )
273+ apply' = (!> )
0 commit comments