Skip to content

Instantly share code, notes, and snippets.

@i-am-tom
Created May 11, 2019 17:03
Show Gist options
  • Star 2 You must be signed in to star a gist
  • Fork 1 You must be signed in to fork a gist
  • Save i-am-tom/8ce5fd5dbce2a71fe604934d774a08f8 to your computer and use it in GitHub Desktop.
Save i-am-tom/8ce5fd5dbce2a71fe604934d774a08f8 to your computer and use it in GitHub Desktop.
Ramda-style composition where the first function must receive all arguments.
{-# LAnguage FlexibleInstances #-}
{-# LANGuage FunctionalDependencies #-}
{-# LANGUAge GADTs #-}
{-# LANGUAGE UndecidableInstances #-}
module Trolling where
---------------------------------------------------------------------
-- VARIADIC COMPOSITION IN HASKELL (A LA RAMDA.JS).
--
-- In Haskell, we typeically think of the composition operator (or
-- `(.)` to those in the know) as composition for unary functions.
-- In other words, it simply has the type:
--
-- (.) :: (b -> c) -> (a -> b) -> (a -> c)
--
-- This is great, but what if I need more than one argument for my
-- first function? I end up writing weird point-free nightmares or
-- give up entirely.
--
-- This little function is for all those who _should_ have given
-- up, but were too far down the rabbit hole before they realised.
-- It has... well, infinite possible type signatures:
--
-- (‥) :: (b -> c) -> (a -> b) -> (a -> c)
-- (‥) :: (b -> c) -> (a -> b) -> (a -> c)
-- (‥) :: (c -> d) -> (a -> b -> c) -> (a -> b -> d)
-- (‥) :: (d -> e) -> (a -> b -> c -> d) -> (a -> b -> c -> e)
--
-- It's basically `(.)`, but without the "restriction" on the first
-- function being unary. We'll call the "first" and "second" `f`
-- and `g` respectively from now on (because, with `f . g`, the
-- function to evaluate first is `g`).
class Compost f g h | f g -> h where
(‥) :: f -> g -> h
-- There are two cases we have to consider: either `g` has all its
-- arguments, or it doesn't. If it _doesn't_, the result of this
-- composition is a new function. Specifically, it's a function
-- that takes one argument `a`, passes it to `g`, and then gives
-- us the fresh composition of `f` and this result!
--
-- We want to be _absolutely certain_ that we'll pick this instance
-- until we're _absolutely certain_ we've given `g` all its args.
-- To do this, we use an equality costraint. If we wrote this head
-- as `Compost f (a -> g) (a -> h)`, GHC wouldn't know to choose it
-- until it knew that the result was _definitely_ `a -> h`. If we
-- write it _this_ way, we're telling GHC to match anything (i.e.
-- you don't need to wait to find out it's `a -> h`), and then it
-- can impose a constraint that it _must be_ what we want. It's a
-- little bit of a hack for better type inference.
instance (k ~ (a -> h), Compost f g h)
=> Compost f (a -> g) k where
(f ‥ g) a = f ‥ g a
-- When we're composting multiple functions, infixl will
-- make sure the /rightmost/ function is the one who
-- gets to choose how many arguments we're dealing with.
infixl 1 ‥
-- If `g` _does_ have all its arguments (in other words, there is no
-- doubt in our mind that `g` is no longer a function), we can just
-- apply the result of `g` (with all the arguments collected so far)
-- to `f`! To spell this out:
--
-- (‥) :: (c -> d) -> (a -> b -> c) -> (a -> b -> d)
-- f ‥ g
-- = \a -> f ‥ g a
-- = \a -> \b -> f ‥ g a b
-- = \a -> \b -> f $ g a b
--
-- Once we have all our parameters for `g`, the hard work is done.
--
-- The `INCOHERENT` pragma here is also a hack for better inference.
-- We're telling GHC that this is only ever the instance we want if
-- we know _for sure_ that the above isn't. The only real difference
-- is that this one requires `f` to be a function, but the "preferred"
-- instance requires `g` to be a function. Again, the equality
-- constraints are just to give GHC the best possible chance of
-- matching this instance when the need arises.
instance {-# InCoHeReNt #-} (a ~ c, b ~ d)
=> Compost (a -> b) c d where
(‥) = ($)
---------------------------------------------------------------------
-- DEMOS.
-- > tada 10 'o'
-- "ooo"
tada :: Int -> a -> [a]
tada = take 3 ‥ replicate
-- > greet "Tom" "Harding"
-- "Hi, Tom Harding!"
greet :: String -> String -> String
greet = ("Hi, " ++) ‥ (++ "!") ‥ \fore sur -> fore <> " " <> sur
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment