Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Flow provides operators for writing more understandable Haskell. It is an
alternative to some common idioms like ($
) for function
application and (.
) for function composition.
Flow is designed to be imported unqualified. It does not export anything that conflicts with the base package.
>>>
import Flow
Rationale
I think that Haskell can be hard to read. It has two operators for applying
functions. Both are not really necessary and only serve to reduce
parentheses. But they make code hard to read. People who do not already
know Haskell have no chance of guessing what foo $ bar
or baz & qux
mean.
Those that do know Haskell are forced to read lines forwards and backwards
at the same time, thanks to function composition. Even something simple,
like finding the minimum element, bounces around: f = head . sort
.
I think we can do better. By using directional operators, we can allow readers to move their eye in only one direction, be that left-to-right or right-to-left. And by using idioms common in other programming languages, we can allow people who aren't familiar with Haskell to guess at the meaning.
So instead of ($
), I propose (<|
). It is a pipe, which anyone
who has touched a Unix system should be familiar with. And it points in the
direction it sends arguments along. Similarly, replace (&
) with
(|>
). And for composition, (<.
) replaces (.
). I would have
preferred <<
, but its counterpart >>
is taken by Haskell's syntax.
So-called "backwards" composition is normally expressed with
(>>>
), which Flow provides as (.>
).
Function application
(<|) :: (a -> b) -> a -> b infixr 0 Source #
Right-associative apply
operator. Read as "apply backward" or "pipe
from". Use this to create long chains of computation that suggest which
direction things move in. You may prefer this operator over (|>
) for
IO
actions since it puts the last function first.
>>>
print <| negate <| recip <| succ <| 3
-0.25
Or use it anywhere you would use ($
).
Note that (<|
) and (|>
) have the same precedence, so they cannot be used
together.
>>>
-- This doesn't work!
>>>
-- print <| 3 |> succ |> recip |> negate
\ x -> (f <| x) == f x
\ x -> (g <| f <| x) == g (f x)
apply :: a -> (a -> b) -> b Source #
Function application. This function usually isn't necessary, but it can be
more readable than some alternatives when used with higher-order functions
like map
.
>>>
map (apply 2) [succ, recip, negate]
[3.0,0.5,-2.0]
In general you should prefer using an explicit lambda or operator section.
>>>
map (\ f -> 2 |> f) [succ, recip, negate]
[3.0,0.5,-2.0]>>>
map (2 |>) [succ, recip, negate]
[3.0,0.5,-2.0]>>>
map (<| 2) [succ, recip, negate]
[3.0,0.5,-2.0]
\ x -> apply x f == f x
Function composition
(.>) :: (a -> b) -> (b -> c) -> a -> c infixl 9 Source #
Left-associative compose
operator. Read as "compose forward" or "and
then". Use this to create long chains of computation that suggest which
direction things move in.
>>>
let f = succ .> recip .> negate
>>>
f 3
-0.25
Or use it anywhere you would use (>>>
).
\ x -> (f .> g) x == g (f x)
\ x -> (f .> g .> h) x == h (g (f x))
(<.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 Source #
Right-associative compose
operator. Read as "compose backward" or "but
first". Use this to create long chains of computation that suggest which
direction things move in. You may prefer this operator over (.>
) for
IO
actions since it puts the last function first.
>>>
let f = print <. negate <. recip <. succ
>>>
f 3
-0.25
Or use it anywhere you would use (.
).
Note that (<.
) and (.>
) have the same precedence, so they cannot be used
together.
>>>
-- This doesn't work!
>>>
-- print <. succ .> recip .> negate
\ x -> (g <. f) x == g (f x)
\ x -> (h <. g <. f) x == h (g (f x))
compose :: (a -> b) -> (b -> c) -> a -> c Source #
Function composition. This function usually isn't necessary, but it can be
more readable than some alternatives when used with higher-order functions
like map
.
>>>
let fs = map (compose succ) [recip, negate]
>>>
map (apply 3) fs
[0.25,-4.0]
In general you should prefer using an explicit lambda or operator section.
>>>
map (\ f -> f 3) (map (\ f -> succ .> f) [recip, negate])
[0.25,-4.0]>>>
map (\ f -> f 3) (map (succ .>) [recip, negate])
[0.25,-4.0]>>>
map (\ f -> f 3) (map (<. succ) [recip, negate])
[0.25,-4.0]
\ x -> compose f g x == g (f x)
Strict function application
(!>) :: a -> (a -> b) -> b infixl 0 Source #
Left-associative apply'
operator. Read as "strict apply forward" or
"strict pipe into". Use this to create long chains of computation that
suggest which direction things move in.
>>>
3 !> succ !> recip !> negate
-0.25
The difference between this and (|>
) is that this evaluates its argument
before passing it to the function.
>>>
undefined |> const True
True>>>
undefined !> const True
*** Exception: Prelude.undefined ...
\ x -> (x !> f) == seq x (f x)
\ x -> (x !> f !> g) == let y = seq x (f x) in seq y (g y)
(<!) :: (a -> b) -> a -> b infixr 0 Source #
Right-associative apply'
operator. Read as "strict apply backward" or
"strict pipe from". Use this to create long chains of computation that
suggest which direction things move in. You may prefer this operator over
(!>
) for IO
actions since it puts the last function first.
>>>
print <! negate <! recip <! succ <! 3
-0.25
The difference between this and (<|
) is that this evaluates its argument
before passing it to the function.
>>>
const True <| undefined
True>>>
const True <! undefined
*** Exception: Prelude.undefined ...
Note that (<!
) and (!>
) have the same precedence, so they cannot be used
together.
>>>
-- This doesn't work!
>>>
-- print <! 3 !> succ !> recip !> negate
\ x -> (f <! x) == seq x (f x)
\ x -> (g <! f <! x) == let y = seq x (f x) in seq y (g y)
apply' :: a -> (a -> b) -> b Source #
Strict function application. This function usually isn't necessary, but it
can be more readable than some alternatives when used with higher-order
functions like map
.
>>>
map (apply' 2) [succ, recip, negate]
[3.0,0.5,-2.0]
The different between this and apply
is that this evaluates its argument
before passing it to the function.
>>>
apply undefined (const True)
True>>>
apply' undefined (const True)
*** Exception: Prelude.undefined ...
In general you should prefer using an explicit lambda or operator section.
>>>
map (\ f -> 2 !> f) [succ, recip, negate]
[3.0,0.5,-2.0]>>>
map (2 !>) [succ, recip, negate]
[3.0,0.5,-2.0]>>>
map (<! 2) [succ, recip, negate]
[3.0,0.5,-2.0]
\ x -> apply' x f == seq x (f x)