0

I want to implement a function called output which is overloaded for a scalar and a list:

  • For a scalar x, it executes print x (output 3 should print 3)

  • For a list x, it executes putStr . unlines . map show x (output [1, 2, 3] should print 1\n2\n3)

Currently, I have non-overloaded outputScalar and outputList, both of which work (playground):

module Main where

main :: IO ()
main = do
    outputScalar 3
    outputList [1, 2, 3]

outputScalar :: (Show a, Num a) => a -> IO ()
outputScalar = print

outputList :: (Show a, Num a) => [a] -> IO ()
outputList = putStr . unlines . map show

Now I'd like to group them together to the single output function, using overloading. I tried the code below (playground), but it doesn't even compile.

module Main where

main :: IO ()
main = do
    output 1
    output [1, 2, 3]

class Show a => Output a where
    output :: a -> IO ()

instance (Show a, Num a) => Output a where
    output :: a -> IO ()
    output = print

instance (Show a, Num a) => Output [a] where
    output :: [a] -> IO ()
    output = putStr . unlines . map show

How can I fix the code? Or is it impossible to do that in Haskell?

ynn
  • 3,386
  • 2
  • 19
  • 42
  • 1
    Pleeeease! If "it doesn't even compile", tell us what error messages you're getting. (And in this case, I'd be pretty sure they'll tell you how to start fixing. `Overlapping instances`?) – AntC May 02 '23 at 06:00
  • @AntC Thank you for your suggestion. As seen from the playground link in the OP, the error message is `The constraint ‘Show a’ is no smaller than the instance head ‘Output a’`. – ynn May 02 '23 at 06:33
  • "I'd like to group them together in a single `output` function`". [Why?](https://twitter.com/CompSciFact/status/1649076783315075075) – chepner May 02 '23 at 11:57
  • You only need the list version as long as you just require anyone with a scalar to wrap it in a list themselves: `output [1]` instead of `output 1`. When the scalar version is just a special case of the list version, this makes more sense than if you do somethign *significantly* different in the scalar version. – chepner May 02 '23 at 12:00
  • @chepner Because [this](https://stackoverflow.com/questions/76151612/overload-a-function-which-takes-a-scalar-or-a-list/76154652#comment134296330_76151655). – ynn May 02 '23 at 12:28

3 Answers3

3

It can be done, but it requires turning on a bunch of compiler extensions with scary names.

{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

instance {-# OVERLAPS #-} (Show a, Num a) => Output a where
    output = print

instance {-# INCOHERENT #-} (Show a, Num a) => Output [a] where
    output = putStr . unlines . map show

We need FlexibleInstances (that one is admittedly harmless, and you see it in production code fairly commonly) to allow instance heads that aren't concrete. Then we use UndecidableInstances and INCOHERENT to turn off all of the termination checking on instance resolution. Finally, OVERLAPS tells GHC not to complain about the fact that the two instances are both technically valid for lists.

With all of these Haskell safety checks thrown into the rubbish pile, instance resolution works the way you want it to in this example. But I strongly recommend you do not do this in production code. If the extension names "undecidable" and "incoherent" aren't enough to scare you off, just keep in mind that this is really not how typeclasses are supposed to work. This path only leads to pain, I promise.

Silvio Mayolo
  • 62,821
  • 6
  • 74
  • 116
  • 4
    What in the world are you using `INCOHERENT` for?? `instance {-# OVERLAPPABLE #-} (Show a, Num a) => Output a where ..; instance (Show a, Num a) => Output [a] where ..` is all I'd expect to need (and it appears to work). You are however still right that "don't bother overloading `output`" is the best answer. – HTNW May 02 '23 at 04:12
  • 2
    Thank you. It just worked. If this solution is not recommended (in production code), however, does that mean I should keep implementing`outputScalar` and `outputList` separately as shown in the OP? – ynn May 02 '23 at 04:14
  • 1
    @ynn Yes, functions with different purposes for different types should not be the same function. [Typeclasses should have laws](https://stackoverflow.com/q/15003974/625403), not just be a way to use the same name for two things. – amalloy May 02 '23 at 04:28
  • @ynn What purpose do you have in wanting to group them together with the same name. Is it just for convenience in having a shorter name? If you always know which one you're calling, there's no loss of expressiveness in being explicit by using different names rather than leaving that detail out and making the reader/compiler infer it from the type. If your use case requires calling `output` in polymorphic contexts where you don't know which one applies, there might be a better way, but we might need more details (that's exactly the kind of situation where overlapping instances can go wrong). – Ben May 02 '23 at 04:38
  • @Ben I'm a heavy user of competitive programming and currently I use Rust. In Rust, I can use *macros* to process every type of inputs/outputs by a single macro name. By that, I don't need to change my source code depending on the type of a problem I solve (some problems give me scalars, others give me lists), letting me concentrate on implementing the solve logic. Recently I'm interested in using Haskell in competitive programming, so I wonder if I can do the same thing in Haskell. So, in my situation, how fast I can write a source code is the top priority. – ynn May 02 '23 at 04:42
  • @ynn In that case I'd probably go for `OVERLAPPING` (well, my Haskell skeleton for Code Jam just defined a main function in terms of `readCase`, `solveCase` and `printCase`, and I just implemented each of those for the exercise at hand, so I suppose I wouldn't use something like `output` at all). But if you're not building a larger API out of overlapping instances, just using them in (effectively) single executables, and the type you're applying it to is always fully concretely known, then the pitfalls of overlapping shouldn't come up, so if it saves you some effort then why not. – Ben May 02 '23 at 04:55
  • 3
    `UndecidableInstances` is pretty harmless, in my opinion. The guardrail it removes doesn't actually protect you from all that much in practice (the compiler won't loop or run out of memory, there's a depth limit in instance search so the process is actually still "decidable"). I wouldn't put it in the same category as `OVERLAPS`/`OVERLAPPING` (and *certainly* not in the same category as `INCOHERENT`, which is definitely a footgun to approach cautiously). – Ben May 02 '23 at 04:55
  • 1
    `OVERLAPPABLE` is the pragma I prefer to use: amongst real-sized code, it tells the reader this instance might get gazumped, so look around for other instances. `OVERLAPPING` is ok, but less informative. `OVERLAPS` is little help to the reader. – AntC May 02 '23 at 06:04
  • @AntC That sounds right. I haven't done much overlapping since the days you had to use the whole-module language extension; setting it per-instance is much better, but I haven't had cause to memorize the exact effects of each pragma yet. – Ben May 02 '23 at 06:22
1

Although this can be done as an overlapping instance, I would advise against this, these usually lead to more pain than it's worth.

You should ask yourself why you want this kind of overload in the first place. If the scalar- and list cases are manifestly different, which they kind of seem to be, then writing code that's polymorphic over them only leads to more confusing semantics. It's then better to just write separate outputScalar (or simply use print as-is) and outputList. If you find yourself needing both versions in the same function then you can always just pass a a -> IO () function to avoid code duplication (preferrably wrapped in some abstraction like newtype Printer a = ...).

Having separate functions means you don't need to worry about cramming them in a single class, which means you can easily generalise beyond lists:

outputMany :: (Foldable f, Show a) => f a
outputMany = putStr . unlines . map show . toList

On the other hand, if there is really a legitimate polymorphism case, then notions of list or even foldable shouldn't have such a special status. In this case, they should be only one instance amongst many. It sounds a lot like you want

class PrettyPrint a where
  pprint :: a -> IO ()

This should then have discrete instances, i.e.

instance PrettyPrint Int where pprint = print
instance PrettyPrint Double where pprint = print
...
instance PrettyPrint a => PrettyPrint [a] where
  pprint = mapM_ pprint

If you don't like the boilerplate of many primitive instances that do nothing but redirect to print, you can simply make that the default case:

{-# LANGUAGE DefaultSignatures #-}

class PrettyPrint a where
  pprint :: a -> IO ()
  default pprint :: Show a => a -> IO ()
  pprint = print

...and now the instances are mere heads

instance PrettyPrint Int

For custom types you could even derive them:

{-# LANGUAGE DeriveAnyClass #-}

data Foobar = Foobar { foo :: Int, bar :: Double }
  deriving (Show, PrettyPrint)
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
1

The problem is this: suppose I were to write

instance Num a => Num [a] where {- ...actual implementation is unimportant -}

Now, which of the following two instances should be chosen for calling output on an [Int]?

instance (Show a, Num a) => Output a where
instance (Show a, Num a) => Output [a] where

Both match, and it's not enough to just say "pick whichever one" -- they lead to different behavior! One results in a single line with square brackets and commas, and the other results in multiple lines. Of course instance Num a => Num [a] doesn't exist in the base libraries, but the compiler is not permitted to assume it will never be created by some other library that you import in another part of your program it can't see right now.

One simple solution is to simply expand the Output a instance so that none of the expanded instances match the Output [a] instance. Like this:

instance Show a => Output [a] where output = mapM_ print
instance Output Int where output = print
instance Output Integer where output = print
instance Output () where output = print
-- etc.

It is unfortunate that you must repeat the where output = print bit every time for the latter instances, but that can be eliminated using DefaultSignatures like this:

class Output a where
    output :: a -> IO ()
    default output :: Show a => a -> IO ()
    output = print

instance Show a => Output [a] where output = mapM_ print
instance Output Int
instance Output Integer
instance Output ()
-- etc.

You can go even one step further with TemplateHaskell; with a bit of work, you would be able to write something like this:

outputInstances '[Int, Integer, (){- , etc. -}]

Not sure I'd recommend going that far to remove duplication though.

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • For my note: [playground for the 1st implementation](https://play.haskell.org/saved/r6eJMSqg), [playground for the 2nd implementation](https://play.haskell.org/saved/8nn1nkE0). – ynn May 06 '23 at 03:31