Skip to content

Commit 81e01f9

Browse files
authored
Simplify and add INLINE pragmas with the appropriate LHS arity (#46)
1 parent bced4eb commit 81e01f9

File tree

1 file changed

+16
-7
lines changed

1 file changed

+16
-7
lines changed

source/library/Flow.hs

Lines changed: 16 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -66,8 +66,9 @@ import qualified Prelude
6666
-- prop> \ x -> (x |> f |> g) == g (f x)
6767
infixl 0 |>
6868

69+
{-# INLINE (|>) #-}
6970
(|>) :: a -> (a -> b) -> b
70-
(|>) = Prelude.flip (<|)
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 @@ infixl 0 |>
9091
-- prop> \ x -> (g <| f <| x) == g (f x)
9192
infixr 0 <|
9293

94+
{-# INLINE (<|) #-}
9395
(<|) :: (a -> b) -> a -> b
94-
(<|) = Prelude.id
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,8 +112,9 @@ infixr 0 <|
110112
-- [3.0,0.5,-2.0]
111113
--
112114
-- prop> \ x -> apply x f == f x
115+
{-# INLINE apply #-}
113116
apply :: a -> (a -> b) -> b
114-
apply = (|>)
117+
apply x f = f x
115118

116119
-- | Left-associative 'compose' operator. Read as "compose forward" or "and
117120
-- then". Use this to create long chains of computation that suggest which
@@ -128,8 +131,9 @@ apply = (|>)
128131
-- prop> \ x -> (f .> g .> h) x == h (g (f x))
129132
infixl 9 .>
130133

134+
{-# INLINE (.>) #-}
131135
(.>) :: (a -> b) -> (b -> c) -> (a -> c)
132-
(.>) = Prelude.flip (<.)
136+
f .> g = compose f g
133137

134138
-- | Right-associative 'compose' operator. Read as "compose backward" or "but
135139
-- first". Use this to create long chains of computation that suggest which
@@ -153,8 +157,9 @@ infixl 9 .>
153157
-- prop> \ x -> (h <. g <. f) x == h (g (f x))
154158
infixr 9 <.
155159

160+
{-# INLINE (<.) #-}
156161
(<.) :: (b -> c) -> (a -> b) -> (a -> c)
157-
(<.) = (Prelude..)
162+
g <. f = compose f g
158163

159164
-- | Function composition. This function usually isn't necessary, but it can be
160165
-- more readable than some alternatives when used with higher-order functions
@@ -174,8 +179,9 @@ infixr 9 <.
174179
-- [0.25,-4.0]
175180
--
176181
-- prop> \ x -> compose f g x == g (f x)
182+
{-# INLINE compose #-}
177183
compose :: (a -> b) -> (b -> c) -> (a -> c)
178-
compose = (.>)
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 = (.>)
198204
-- prop> \ x -> (x !> f !> g) == let y = seq x (f x) in seq y (g y)
199205
infixl 0 !>
200206

207+
{-# INLINE (!>) #-}
201208
(!>) :: a -> (a -> b) -> b
202-
(!>) = Prelude.flip (<!)
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
@@ -231,6 +238,7 @@ infixl 0 !>
231238
-- prop> \ x -> (g <! f <! x) == let y = seq x (f x) in seq y (g y)
232239
infixr 0 <!
233240

241+
{-# INLINE (<!) #-}
234242
(<!) :: (a -> b) -> a -> b
235243
(<!) = (Prelude.$!)
236244

@@ -260,5 +268,6 @@ infixr 0 <!
260268
-- [3.0,0.5,-2.0]
261269
--
262270
-- prop> \ x -> apply' x f == seq x (f x)
271+
{-# INLINE apply' #-}
263272
apply' :: a -> (a -> b) -> b
264273
apply' = (!>)

0 commit comments

Comments
 (0)