Why are Partial Functions so prevalent in Prelude?

Why are partial functions so prevalent in Prelude?

The designing of Haskell commenced in 1987, with the first Report being published in 1990 (if you’re interested in learning some more about the origins of Haskell, read A History or Haskell). So Haskell is a language with a 30+ year-old design, and which ought to to explain your (reasonable) list of observations:

  • partial functions
  • inconsistent documentation
  • lack of Maybe producing variants of certain functions
  • and incomplete pattern matching
  • (…amongst others)

As described here:

…merely upgrading GHC alone to or past 9.8 (with the partiality warnings for head and tail) can now cause problems. Trying to apply more recent techniques to older code continues to be a fraught exercise.


Overall I feel that Haskell is the closest to what I would consider my ideal language. Which is why it both confuses and frustrates me that the language does such a fantastic job of tricking me into believing that it’s safe with it’s beautiful, elegant, sophisticated type system and syntax.

well done! I don’t think I’ve ever thought about Haskell quite like that before - the only critiques I can think of which are (somewhat) similar were about Haskell’s current I/O model (which is a topic for a separate thread).

4 Likes

“This function is non-total and will raise a runtime exception if the structure happens to be empty.”, same with pred/succ.

I do not ask to be snarky. If functions are non-total, it should be written in the documentation or the examples coming with the function. I would consider it a bug if they are not clearly marked as such.

I see many people wrote — good! — answers to your question but I want to stress this one: “parsing” over “validating” is something that Haskell is very good at and should be taken advantage of when possible (alas it is not always possible).
It is what makes refactoring — along with a modicum of testing — a pleasure and not feeling you are fighting against a giant squid. Also improvers documentation greatly (documentation that will never go stale).

I am happy that you are learning Haskell, new ideas and perspectives make the community better.

3 Likes

I don’t think you can draw a meaningful distinction, consider this definition of head:

head (x:_) = x
head xs = head xs

Surely this falls under the “result-can-require-an-unlimited-number-of-reductions” (I’ve left out the “next” part because that also doesn’t hold for length, or are you saying we should draw the line between length and filter?).

Like I responded in that thread: this is not new or unique to the head and tail warnings. GHC does not give guarantees about which warnings it generates across compiler versions. So using -Werror means opting into potential breakage every new GHC version.

1 Like

I genuinely don’t see this documentation for pred and succ (this is important for when you’re actively coding and peek at the doc comment for a function via either hover on VS Code or the equivalent in vim/neovim). If I go specifically to the Enum documentation then the Enum class documentation itself mentions runtime errors - but not the individual members. For instance, if I hover over succ in my editor I get the following:

succ :: forall a. Enum a => a -> a

the successor of a value. For numeric types, succ adds 1.


_ :: Bool -> Bool

_ :: forall a. Enum a => a -> a

For minimum you are 100% correct I didn’t spot where in the doc comment for the function itself what causes a runtime exception. Also, for some reason HLS didn’t show me the WARNING tag until I applied the function to something, not sure why.

Don’t worry, I didn’t perceive any of your comments so far as being snarky :slight_smile:

I agree for the most part. Like I stated earlier I definitely agree that parsing upfront is better than validating down the line. I just wish the aforementioned partial functions either forced the user to take either a parsing or validating approach or were more clear in their unsafe nature.

1 Like

I do categorize head xs = head xs as a different sort of thing than length (_:xs) = 1 + length xs, yeah. I don’t know exactly what terms I’d use to describe the distinction, but some relevant differences:

  • The head clause doesn’t dissect its input data at all, whereas when the length clause recurses it does so on a subterm.
  • The head clause doesn’t embed its recursive call under any other application, whereas the length clause embeds its own recursive call under +. This is maybe only relevant if the position of the recursion isn’t strict, as is the case with filter. (This is what I was trying to suggest with ‘next-’.)
  • The head clause is trivial; the LHS and the RHS are identical, so if it ever gets invoked it’s necessarily a black hole. I almost expect GHC to replace it with something that crashes with <<loop>> the same way that dereferencing x = x does.

I imagine there’s something that a brainier person could say about recursion schemes and data and codata that synthesizes these differences nicely, but I’m not that person.

2 Likes

Like I responded in that thread: this is not new or unique to the head and tail warnings.

…I’ll rephrase my previous statement:


…therein lies another problem: what if the data you’re intending to parse or validate is from a source outside the program?

1 Like

Thanks @Helgard, for comparison how do other languages handle things like the below, and would you consider those as deviant operations that ought to be addressed? (Or at least documented.)

  • Divide by zero;
  • Numeric over/underflow on fixed width Int;
  • including overflow on Summing a List or other big-but-not-quite-infinite data structure.

Well yeah – in all programming languages since forever. And I’m not seeing why Prelude functions deserve special treatment when users can readily write any number of dodgy functions for themselves.

It’s great there are safe versions of Prelude functions for people who want high assurance, but making those the default would significantly degrade the learner’s experience, I think.

Or taking examples from intro texts are also likely to generate warnings in 9.8. I find it only annoying. (I suspect learners might write their own versions of head, tail, etc – just to avoid the warnings. Which’ll perhaps land them in a worse position than using Prelude functions.)

These are all documented (the 3rd indirectly via the 2nd).

Numeric operators are a good example of the tension between safety and ergonomics. On the one hand, I would love to statically know that I don’t have any over/underflow or division by zero. On the other hand, there aren’t any good solutions for base, which needs to serve a wide variety of operations.

  1. Returning Maybe is pretty clearly a non-starter in most situations as numeric operations often happen deep in your (pure) callstack where the notion of “failure” is nonsensical. Having all functions return Maybe isn’t helpful, and the performance degradation is likely unacceptable.

  2. Restricting the domain is better, but it needs to be reasonably ergonomic. You can get away with the refined library in simple cases, but it is not flexible enough to serve as a base for your operations because you cannot manipulate proofs.

Thankfully, there does exist an ergonomic solution for much of List's unsafety: NonEmpty. This works well because the single “input is non-empty” invariant fixes many issues, so we can safely rebuild List's API for NonEmpty without cheating or having to manipulate proofs.

This is not the case for numeric operators because even if you start with an n with some proof p, you often need to then prove q. Haskell just can’t do this at the moment. You need dependent types.

So my answer to the question

Why should we care about head when div exists?

is, I think, cost/benefit ratio. The cost of fixing an unsafe usage of List is often low, and the benefit can be very high (read: how many hours have we all lost debugging *** Exception: Prelude.head: empty list?).

The cost of fixing numeric unsafety, however, is very high, certainly too high to be entertained in base. Though I am hopeful that this cost may come down in the future :slight_smile: .


Incidentally, I would love to see a way to at least detect over/underflow at runtime (e.g. gcc’s -ftrapv).

1 Like

But are dependent types by themselves enough?

example1 :: Integer
example1 = 1 `div` (let n = negate n in n)

example2 :: (String -> Integer) -> IO Integer
example2 readZ = (\ n -> div 1 n) . readZ <$> getLine

For dependent types to always be useful for making proofs, totality is essential to prevent ⊥ from being one of the expressions used to define a dependent type. But even Agda, a frequently-presented exemplar of total programming, sometimes requires partiality:

example2 : (String → ℤ) → IO ℤ
example2 readZ = (λ x → 1 / n) ∘ readZ <$> getLine

So unless there’s some major advance in programming-language semantics, a future Haskell will be partial and dependently-typed: that ought to be an “interesting” combination…

I’ll give my newbie perspective.

I too, got a bit of an “allergic” reaction when I first stumbled upon partial functions in Haskell. That’s because I came from Elm, that showed me that I could express programs in a disciplined way, to avoid runtime errors.

However, I since found that there are rare cases where partial functions are useful, and not having them would be a hindrance.

Example 1:

See this algorithm that wants to extract the first and last item of a list in a flip-flop fashion, while still keeping things performant considering the usage of linked lists under the hood.

{- |

>>> arrange []
[]

>>> arrange [1]
[1]

>>> arrange [1,2]
[1,2]

>>> arrange [1,2,3]
[1,3,2]

>>> arrange [1,2,3,4]
[1,4,3,2]

>>> arrange [1,2,3,4,5]
[1,5,4,2,3]

>>> arrange [1,2,3,4,5,6]
[1,6,5,2,3,4]
-}
arrange :: [a] -> [a]
arrange lst = aux lst (reverse lst) (length lst)
  where
    aux fwd bwd len
        | len == 0 = []
        | len == 1 = [head fwd]
        | otherwise = head fwd : head bwd : aux (tail bwd) (tail fwd) (len - 2)

I found this algorithm really cool. While I did find a way to express the same computation without using unsafe functions, if you look at it you have to ask yourself “What’s wrong with it?”.

Well, I don’t think there’s anything “wrong” with it, I think we may have simply reached the limit of a type system.


Example 2:

So you probably know about the function fold, but how about its twin brother unfold, that instead generates a list.

As you can see below, I re-implemented map with unfold + using unsafe/partial functions.

{- |

>>> map' f = unfold null (f . head) tail
>>> map' toUpper "mapping"
"MAPPING"
-}
unfold :: (a -> Bool) -> (a -> b) -> (a -> a) -> a -> [b]
unfold test h t x
    | test x = []
    | otherwise = h x : unfold test h t (t x)

Is the concept of unfolding unsound? Again, I feel here we’re reaching the limit of the type system. Which is something I’ve been wondering about (what does expressing computation with partial functions actually mean?).

So, to sum up, I think partial functions are ok/useful but in closing:

With great power comes great responsibility

Anyhow, hope that helps :laughing:

3 Likes

According to one Conor McBride, it means working in an implicit monadic context:


You might be interested to know that Data.List defines unfoldr:

unfoldr :: (b -> Maybe (a, b)) -> b -> [a]
unfoldr f b0 = build (\c n ->
  let go b = case f b of
               Just (a, new_b) -> a `c` go new_b
               Nothing         -> n
  in go b0)

…which happens to rely on a partial function (but using Maybe a).

It doesn’t come across as ranty at all to me. I think it’s a very understandable issue to raise.

Because Haskell was created 35 years ago, long before people understood that one of its major benefits would be “safety”. Rust and Elm are much newer so they were able to start with this notion of safety in mind.

There’s nothing to stop Haskell providing better documentation, or safe variants of these unsafe Prelude functions, except the time and energy costs of the person doing the work.

Data.NonEmpty.head

Data.Maybe.listToMaybe

2 Likes

As you progress through the language you will find that the problem of unsafe functions is a relatively benign one, as functions cannot return values they were never given. As long as you think about what you’re writing, your chances of falling into one of these traps is near zero. The number of such unsafe functions is pleasantly small as well.

A big part of the base issue, as has been noted, is simply the fact that GHC has not yet figured out versioning, so functions tend to stick around forever in the name of backwards compatibility. This is simply the unfortunate reality of the language and it is guaranteed to not change within the next few years.

That article is more about keeping all of your state proper instead of checking it, throwing an error and then later on assuming the state isn’t garbage. It will make much more sense once you get acquainted with the local parsing ecosystem, the horrors are just around the corner.

To rule out many of the most common errors that are being discussed in this thread? Yes.

Of course Haskell has no totality checker, so we cannot rule out everything. But that’s fine. Even total languages like Agda and Idris have ways to disable the checker.

Others have hinted at the direct answers to your question and provided some context and further reading. To put it plainly, though, base is full of partial functions because it’s around 35 years old and comes out of a tradition that’s even older than that. A lot of ideas have improved since then. The language you are using for comparison, Rust, is almost 20 years younger, and got to pick from a lot of the better ideas that had developed.

But the good ideas exist now—why does Haskell still use the “bad” ones? (Leaving aside the legitimate value of partial functions and all side conversations there.) Well, Rust could jump straight into a sounder standard library because they didn’t have to worry about breaking backward compatibility. There was no Rust code to be compatible with. Haskell, meanwhile, has to slowly navigate through the compatibility story. It’s a matter of maturity. I’m sure the good ideas that are developed in the next 15 years’ time will eventually take just as long to filter into Rust as it matures and continues to have widespread use. See also C++, which is about as old as Haskell and also has to deal with a bunch of backward compatibility. But just like C++, Haskell is also evolving. From a long-term perspective, you might say that Haskell is just in a temporary, vestigial position with respect to the prevalence of partial functions in base.

A call to arms: issues that affect newcomers like patchy documentation are the kind that rely on community support to fix. In a commercial setting, these kinds of problems get papered over quickly when experienced programmers (and an existing codebase) are on hand to provide mentorship. There’s no incentive to spend time fixing the paper cuts when the immediate goal is to build features for customers. Academics have no direct incentive, either. (Teachers do, I suppose, but they also have the competing incentive of keeping their books and materials up-to-date.) And unlike most popular languages, Haskell has no central benefactor with an incentive to improve their influence by improving the fundamentals of the language. So if the state of Prelude bothers you, go fix it!! :slight_smile:

9 Likes

You raise some interesting questions @AntC2

In rust division by zero for integers results in a panic by default. However the compiler will attempt to detect this in code:

int_value / 0     ● this operation will panic at runtime  `#[deny(unconditional_panic)]` on by default

For integer division you have checked_div which returns Option<i8> for signed 8bit integers, Option<i16> for signed 16 bit integers, etc.

Finally, division by zero for floats results in Infinity which can be pattern matched against using std::f64::INFINITY

In rust this will result in a panic when the code is compiled / ran in development mode and will cause overflow in production mode. Yet again the compiler will try its best to determine this before runtime.

I’m not so sure about other languages since my experience with ML based languages is basically null. In rust code is not lazily evaluated.

I heavily disagree here. It’s one thing for you to introduce a dependency written by a third party, and for that dependency to be poorly built (i.e. inconsistent documentation on what causes exceptions at runtime and a lack of Maybe) vs the standard library of the language itself behaving in such a fashion.

I don’t believe that making Haskell safer by default would be a mark against its academic roots or make it less expressive.

I highly recommend you read the official rust book. I have not found such a high quality piece of learning material for any other language that’s officially endorsed by the foundation backing that language. The reason I mention the rust book is because it does not shy away from concepts like panicking and rust’s Option and Result types. I don’t believe making a language safer (either through parsing vs validating as mentioned above) makes it significantly harder to learn.

2 Likes

I just wanted to say thank you for everyone for the detailed answers as well as context provided. I’m planning on reading through A History of Haskell.

Personally, I’m excited to checkout the safe package, also after some further searching I also found out about Liquid Haskell, which I’ll try out when I have some time. I don’t agree with the mind set that it’s OK to just accept partial functions floating around in the ether and that “You’ll barely run into them” - so I’ll see how I can go about configuring Haskell in a way that’s both expressive and practical from my perspective.

3 Likes

GHC does not support arbitrary compilation-time code execution (except for Template Haskell). Just like with base this is not going to get solved unless several people step up and invest five years of their time into solving this particular issue.

This also results in a far more annoying problem: literal overloading typeclasses (Num, Fractional, IsString and IsList) all are literal -> a functions that are forced to throw exceptions at runtime to be useful.

2 Likes

I love safe, have been relying on it for most of my Haskell career. Would love to have it all in Prelude.

3 Likes

even if you start with an n with some proof p, you often need to then prove q. Haskell just can’t do this at the moment.

Ghosts of Departed Proofs is a step in this direction. It requires a little contortion at both the value and type levels, but it’s quite general (for example, it’s the approach underlying justified-containers). The author, Matt Noonan, positions it as an alternative to partial functions and failure conditions (Maybe/ Either wrapping).

OP, I don’t necessarily recommend GDP for everyday use, but I do recommend reading the paper for a fascinating glimpse at just how much information you can pack into a type.

1 Like