Useful Haskell one-liners

What are some of your favorite “useful” Haskell oneliners? There are some really well-known elegant ones such as the lazy fibonacci sequence:

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

But I don’t need that sequence often in my day job…

So one I particularly like is when you have a HashMap with Maybe a values. Data.HashMap.Strict does not provide a catMaybes to throw away the Nothings, but you can use:

HMS.mapMaybe id

Which is a really cool example of how the id function is useful!

7 Likes

Apply a function to both bits of a tuple:

both :: (a -> b) -> (a, a) -> (b, b)
both = join (***)

Transform a probability density into a cumulative density:

cdf :: (Num a) => [a] -> [a]
cdf = drop 2 . (scanl (+) 0) . ((:) 0)

Compute the cartesian product of two lists:

cartesian :: [a] -> [a] -> [[a]]
cartesian = (sequence .) . (\x y -> [x, y])

(those are the most impressive of some examples here).

Some neat stuff on the Haskell wiki as well.

6 Likes
-- | Helper-Function for pipelines with 2 input-variables.
--   Turns g :: c -> d and f :: a -> b -> c into
--   g ... f :: a -> b -> d
--
--   Useful for chaining:
--   a . b . c ... d
infixl 8 ...
(...) :: (c -> d) -> (a -> b -> c) -> a -> b -> d
(...) = (.).(.)

:slight_smile:

1 Like

Anything using the Semigroup instance for functions is pretty
neato:

sortLexicallyThenByLength :: (Ord (t a), Foldable t) => [t a] -> 
[t a]
sortLexicallyThenByLength = sortBy (compare <> comparing length)

sortTuplesBySndThenFst :: (Ord a, Ord b) => [(a,b)] -> [(a,b)]
sortTuplesBySndThenFst = sortBy (comparing snd <> comparing fst)
3 Likes

I remember this one from the old ‘Blow my mind, in one line’ thread from reddit that I really liked but never got to use:

readMany = unfoldr $ listToMaybe . concatMap reads . tails

Example usage:

Prelude> readMany "This string contains the numbers 7, 11, and 42." :: [Int] 
[7,11,42]
4 Likes

Currently, my favorite Haskell one liner isn’t actually Haskell. :slight_smile:

$ nix-shell -p 'haskellPackages.ghcWithPackages (p: with p; [ QuickCheck lens your-favorite-library ... ])'

It’s really a mouthful, but it gives me a custom environment with whatever packages I need straightaway, without needing to create a cabal or stack project or worry about cabal hell.

3 Likes

Can you give an example where two values are lexically equal but differ in length?

p ^.. _HTML' . to allNodes . traverse
    . named "a" . traverse
    . ix "href" . filtered isLocal
    . to trimSpaces

from https://skillsmatter.com/skillscasts/4251-lenses-compositional-data-access-and-manipulation

1 Like

One of my favorite one-liners is the default implementation of the foldr function using foldMap.

foldr f z t = appEndo (foldMap (Endo . f) t) z

When I was learning Haskell it was really strange to me that in order to implement a Foldable instance it’s enough to implement either foldMap or foldr. The default implementation of foldMap via foldr is quite obvious, however it was completely unclear how to implement foldr having only foldMap. Now it makes sense, of course, and the solution is nice :slight_smile:

3 Likes

To acquire and release resources in Haskell is common to use the bracket pattern. Eg.

withFile :: FilePath -> (Handle -> IO r) -> IO r

Now, I found myself with a list of file paths and to do something with a list of handles.
Here’s the one liner:

nest :: [(r -> a) -> a] -> ([r] -> a) -> a
nest xs = runCont . traverse cont

And I can get obtain the handlers I needed like this

nest (map withFile filepaths) $ \handles -> ...
4 Likes

If you only need a repl you can use the cabal new-repl command:

$ cabal new-repl -b QuickCheck -b lens -b your-fav-package
1 Like

You don’t need to create a Stack project. Just use:

stack repl --package QuickCheck --package lens [–resolver=lts-10.6]

If you don’t specify a resolver, the one configured in ~/.stack/global-project/stack.yaml is used.

2 Likes

Nice! If you need something more comprehensive than a oneliner, Gabriel’s managed library also tackles this problem.

1 Like

Hmm. I suppose I can’t, so that’s a rather dull one. The other way around

sortByLengthThenLexically = sortBy (comparing length <> compare)

actually does something.

@sjakobi @jhenahan
The following are a bit made up examples or might tell more about design issues:

  • something like bucket sort for certain prefix length of e.g. texts, and each bucket sorted then by length
  • histogram interval handling for more complex types (this is somewhat similar to the previous one)
  • a record with values and functions (and e.g. the equality is based on function similarity and length on values)

Each of the above probably need own-defined instances instead of stock defined ones for Eq, Foldable and/or Ord. E.g. comparing functions is hard but defining and using comparable names for functions helps etc.

A crude way of throttling a mapConcurrently from the “async” package:

\level f xs -> newQSem level >>= \sem -> mapConcurrently (bracket_ (waitQSem sem) (signalQSem sem) . f) xs

It can create a lot of threads though, so it isn’t suitable for very big containers.

1 Like