Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How can I return a non-concrete value from a function that supports some API?

Tags:

haskell

I'm building an API between two models. I don't care if it returns a [] or Seq or anything Foldable is fine. But if I try to do that, I get errors.

module Main where
import Prelude hiding (foldr)
import Data.Foldable
import Data.Sequence

data Struct = Struct

main = do
  print $ foldr (+) 0 $ list Struct
  print $ foldr (+) 0 $ listFree Struct


listFree :: Foldable f => a -> f Int
listFree s = singleton 10

class TestClass a where
  list :: Foldable f => a -> f Int

instance TestClass Struct where
  list s = singleton 10

Both the listFree and the list definitions give the same error:

TestFoldable.hs:19:12:
Could not deduce (f ~ [])
from the context (Foldable f)
  bound by the type signature for
             list :: Foldable f => Struct -> f Int
  at TestFoldable.hs:19:3-15
  `f' is a rigid type variable bound by
      the type signature for list :: Foldable f => Struct -> f Int
      at TestFoldable.hs:19:3
In the expression: [10]
In an equation for `list': list s = [10]
In the instance declaration for `TestClass Struct'

Why is that? And what is the "right" way to accomplish what I'm trying to do here?

What I'm trying to accomplish is to hide the implementation from the caller. The actual data structure might be a Seq, IntMap, or anything else and most likely is not a list.

I'm getting responses that say "just return a list". But that means conversion, doesn't it? What if it's a 1,000,000 element structure? Converting it to an intermediate data structure just because of limitations of the API seems a poor solution.

And this is a general problem. How does one have a return value that conforms to some API? To hide the concrete implementation so the implementer is free to choose whatever structure is best for them and can change it without having to change the users of the API.

Another way of putting it is: how can I return an interface instead of a concrete type?

Closing Note:

The Haskell community on StackOverflow is (SuperlativeCompliment c => forall c. c)

Existential quantification seems like the general solution to this situation.

Another possibility to consider, which is not a general solution but might have worked for this specific case, that might avoid the extra wrapper value required by existential solution is to return a closure of the fold for the client:

list :: a -> ((Int -> b -> b) -> b -> b)
list = \f a0 -> foldr f a0 (singleton 10)
like image 318
mentics Avatar asked Nov 16 '11 17:11

mentics


2 Answers

Why is that?

The type Foldable f => a -> f Int does not mean that the function might return any foldable it wants. It means that the function will return whichever type the user wants. I.e. if the user uses the function in a context where a list is required that should work and if he uses it in a context where a Seq is required that should also work. Since this is clearly not the case with your definition, it doesn't match its type.

And what is the "right" way to accomplish what I'm trying to do here?

The easiest way would be to just make your function return a list.

However if you do need to hide the fact that you're using lists from your users, the easiest way would be to create a wrapper type around the list and not export that type's constructor. I.e. something like:

module Bla (ListResult(), list) where
data ListResult a = ListResult [a]

instance Foldable (ListResult a) where
    foldr op s (ListResult xs) = foldr op s xs

list s = ListResult [10]

Now if the user imports your module, it can fold over a ListResult because it's foldable, but it can't unpack it to get at the list because the constructor is not exported. So if you later change ListResult's definition to data ListResult a = ListResult (Seq a) and list to also use a Seq instead of a list, that change will be completely invisible to the user.

like image 84
sepp2k Avatar answered Oct 17 '22 14:10

sepp2k


sepp2k already provided a good answer, but allow me to take a similar but slightly different angle. What you have done is provide result-type polymorphism. You wrote:

listFree :: Foldable f => a -> f Int

What this does is promise that you can produce any foldable that the user may need. You, of course, could never keep this promise because Foldable doesn't provide any constructor-like functions.

So what you're trying to do deals with generics. You want to make a weak promise: the function listFree will produce some Foldable, but in the future, it may change. You might implement it with a regular list today, but later, you might re-implement it with something else. And you want this implementation detail to be just that: an implementation detail. You want the contract for that function (the type signature) to remain the same.

Sounds like a job for yet another weird and confusing Haskell extension! Existential Quantification!

{-# LANGUAGE ExistentialQuantification #-}

import Prelude hiding (foldr, foldl, foldr1, foldl1)
import Data.Foldable

data SomeFoldable a = forall f. Foldable f => F (f a)

foo :: SomeFoldable Int
foo = F [1,2,3]

Here I've provide a value foo, but it has the type SomeFoldable Int. I'm not telling you which Foldable it is, simply that it is some foldable. SomeFoldable can easily be made an instance of Foldable, for convenience.

instance Foldable SomeFoldable where
  fold (F xs) = fold xs
  foldMap f (F xs) = foldMap f xs
  foldr step z (F xs) = foldr step z xs
  foldl step z (F xs) = foldl step z xs
  foldr1 step (F xs) = foldr1 step xs
  foldl1 step (F xs) = foldl1 step xs

Now we can do Foldable things with foo, for example:

> Data.Foldable.sum foo
6

But we can't do anything with it besides what Foldable exposes:

> print foo
No instance for (Show (SomeFoldable Int)) blah blah blah

It's easy to adapt your code to work as desired:

data Struct = Struct

main = do
  print $ foldr (+) 0 $ list Struct
  print $ foldr (+) 0 $ listFree Struct


listFree :: a -> SomeFoldable Int
listFree s = F [10]

class TestClass a where
  list :: a -> SomeFoldable Int

instance TestClass Struct where
  list s = F [10]

But remember, Existential Quantification has its drawbacks. There is no way to unwrap SomeFoldable to get the concrete Foldable underneath. The reason for this is the same reason that your function signature was wrong at the beginning: it promises result-type polymorphism: a promise it cannot keep.

unwrap :: Foldable f => SomeFoldable a -> f a   -- impossible!
unwrap (F xs) = xs    -- Nope. Keep dreaming. This won't work.
like image 43
Dan Burton Avatar answered Oct 17 '22 15:10

Dan Burton