Skip to content

Instantly share code, notes, and snippets.

@harpocrates
Last active May 8, 2017 03:16
Show Gist options
  • Star 5 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save harpocrates/aa40fe9668bd1571f7c3942f1fd8344d to your computer and use it in GitHub Desktop.
Save harpocrates/aa40fe9668bd1571f7c3942f1fd8344d to your computer and use it in GitHub Desktop.

In a recent discussion I had with a friend about Haskell and Scala, they brought up the fact that they sometimes miss Scala's partial functions. In Scala, these are a trait of their own somewhat different from what Haskellers usually understand by "partial function". In particular, you can check if a value is in the domain of the partial function before applying it to the function.

Interestingly enough, partial functions are also supported in Haskell - they just happen to be hidden away in some more obscure parts of the base library. What follows is my attempt to make a module that brings this functionality out and makes it more accessible. Since this is meant to be a literate Haskell source, let's start with some preamble.

{-# LANGUAGE TypeOperators, NoImplicitPrelude, GeneralizedNewtypeDeriving #-}

module Data.Function.Partial where

import Prelude hiding (id, (.), ($))

import Control.Category
import Control.Arrow

import Data.Coerce (coerce)
import Data.Maybe (fromMaybe, isJust)

Here is the core data-type equivalent to PartialFunction[A,B]. Note that it is just a newtype - I'm doing nothing more than wrapping stuff already defined elsewhere.

newtype a ~> b = Partial { runPartial :: Kleisli Maybe a b }
  deriving (Category, Arrow, ArrowZero, ArrowPlus, ArrowChoice, ArrowApply, ArrowLoop)

Most of the functionality in PartialFunction[A,A] comes for free directly from the classes whose instances we automatically derived using GeneralizedNewtypeDeriving.

Haskell doesn't have subtyping, so we can't have a -> b <: a ~> b, but we at least get the embeding operation for free via arr :: (a -> b) -> (a ~> b) from Arrow. And even if Scala does have subtyping, they somehow managed to screw up and get the hierarchy of functions backwards by making PartialFunction[A, B] <: A => B.

All this is nice and well, but what use is a partial function if it cannot be applied? Unlike Scala, Haskell has no means of overloading the syntax for function application, so the next best thing to do is to define an explicit function application like ($).

Note that one could quite easily shadow ($) with a more general version of itself that also has an (->) instance (as is done for (.) and id in Control.Category). That would require defining a typeclass and enabling TypeFamilies (to define the output type). However, the point of this exercise is to show that Haskell already has all this basic functionality.

($) :: (a ~> b) -> a -> Maybe b
($) = coerce

partial :: (a -> Maybe b) -> (a ~> b)
partial = coerce

Now, we add to our arsenal all the remaining functionality of PartialFunction, although this time some shuffling of arguments is necessary.

  • lift is just $ (f.lift is (f $))
  • condOpt is just $ (condOpt(x)(pf) is pf $ x)
  • applyOrElse is just $ with fromMaybe (pf.applyOrElse(x,g) is fromMaybe (g x) (pf $ x))
  • apply is also just $ with fromMaybe (pf.apply(x) is fromMaybe (error "not in domain") (pf $ x))
  • isDefinedAt is just $ with isJust (pf.isDefinedAt(x) is isJust (pf $ x))

The other "feature" of Scala's PartialFunction is that it has a quaint literal syntax. Haskell doesn't have this syntax, but case expressions work almost perfectly as a substitute (if we wanted, LambdaCase could make this even shorter by cutting out the \x -> case x of ... in faviour of \case ...). For example, the Scala snippet

val func: PartialFunction[List[Int], Int] = {
  case 1 :: x :: 3 if x % 2 == 0 => x + 1
  case Nil => 0
}

translates cleanly to Haskell as

func :: [Int] ~> Int
func = partial (\x -> case x of
                       [1, x, 3] | x `mod` 2 == 0 -> pure (x + 1)
                       [] -> pure 0
                       _ -> Nothing)

Finally, but not to be taken lightly, Haskell has a very powerful toolset of syntactic sugar for arrows available under the Arrows language extension, for which Scala has no equivalent.

@tomjaguarpaw
Copy link

It seems far more useful to use a -> Maybe b directly.

@puffnfresh
Copy link

@tomjaguarpaw composition doesn't compose through Maybe. This is what Kleisli gives.

@johntyree
Copy link

What about monadic composition?

@tomjaguarpaw
Copy link

@puffnfresh Do you mean

arr (f . g) = arr f . arr g

? Agreed, you don't have that with a -> m b, but you do have

return . (f . g) = (return . f) <=< (return . g)

which is morally the same thing.

@harpocrates
Copy link
Author

@tomjaguarpaw It breaks a bit of the symmetry with normal functions and you don't get to use arrow syntax. Note that all of (>>>), (<<<), and (.) also work on regular functions, while (>=>) and (<=<) won't That aside, you still get a lot of stuff for free with type a ~> b = a -> Maybe b:

  • andThen is just (>=>)
  • compose is just (<=<)
  • orElse is just (<|>)
  • empty is just empty

Since anyways newtype a ~> b = Partial { runPartial :: Kleisli Maybe a b } is no different from type a ~> b = a -> Maybe b at runtime, my preference is to have an extra newtype.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment