[Haskell-cafe] Readable Haskell

Viktor Dukhovni ietf-dane at dukhovni.org
Sat Sep 19 20:57:27 UTC 2020


On Sat, Sep 19, 2020 at 07:07:38PM +0200, Misja Alma wrote:

> But I wonder how well it works in Haskell, because unlike Java, in Haskell
> a lot of stuff can happen in a single line.

One idiom for making "a lot of stuff in a single line" easier to read is
seen in:

    https://hackage.haskell.org/package/streaming-attoparsec-1.0.0.1/docs/Data-Attoparsec-ByteString-Streaming.html

    ...
    import Data.Function ((&))

    main :: IO ()
    main = Q.getContents           -- raw bytes
           & AS.parsed lineParser  -- stream of parsed `Maybe Int`s; blank lines are `Nothing`
           & void                  -- drop any unparsed nonsense at the end -- [1]
           & S.split Nothing       -- split on blank lines
           & S.maps S.concat       -- keep `Just x` values in the sub-streams (cp. catMaybes)
           & S.mapped S.sum        -- sum each substream
           & S.print               -- stream results to stdout

    lineParser = Just <$> A.scientific <* A.endOfLine <|> Nothing <$ A.endOfLine

Here, the function composition flows from left to right, in fact top
to bottom, rather than right to left (bottom to top over multiple
lines).  The key ingredient is the (&) operator which puts the
argument on the left and the function on the right.

I've also seen (the first borrowed from F#):

    (|>):   a -> (a -> b) -> b
    (|.>):  (a -> b) -> (b -> c) -> c
    (|$>)   f a -> (a -> b) -> f b
    (|*>)   f a -> f (a -> b) -> f b

And of course Conduit's (.|) is another instance of left-to-right 
style for expressing long composition chains.

Returning to the streaming example, since in `streaming` transformations
of streams are performed via function application (no new operator like
Conduit's (.|)), the left-to-right style uses (&).

Of course even with the flow made clear, and names well chosen, one
still has to come to grips with some rather powerful, highly polymorphic
idioms, whose purpose in each context may warrant a comment in code that
is to be accessible to those still learning the ropes.  The somewhat
non-obvious "void" here is but a mild example.

-- 
    Viktor.

[1] One slightly non-obvious thing at first blush about streams is that
    "void" does not perturb the content of the stream, it only drops the
    stream's terminal value.  Streams are functors in that terminal value,
    so it turns out, surprisingly at first, that the two variants of
    "print the stream" below are identical.

        s :: Show a => Stream (Of a) IO r
        s = ...

        -- The relevant functor here is: F r = (Stream (Of a) IO) r
        -- thus, void s :: Stream (Of a) IO ()

        S.print . void $ s
        -- same as
        void . S.print $ s

    So, for a reader not steeped in the streaming library, one might even
    comment on the role of "void" in more detail:

           ...
           & AS.parsed lineParser  -- stream of parsed `Maybe Int`s; blank lines are `Nothing`
           & void                  -- Replace the stream `Return` value `r` with `()`
                                   -- discarding parser errors, see 'AS.parsed'.
           ...

    So that nobody is left wondering at stream processing continuing
    past "void", which in more mundate contexts one expects to not
    return anything useful to be further processed.

    This briefly caught me by surprise in the "all in one line"
    right-to-left example at the end of the document:

        S.print . void $ AS.parsed (A.scientific <* A.many' A.space) "12.3 4.56  78.9"



More information about the Haskell-Cafe mailing list