Skip to content

Instantly share code, notes, and snippets.

@Sam-Serpoosh
Created March 3, 2015 22:39
Show Gist options
  • Save Sam-Serpoosh/4463277597a03b2b4341 to your computer and use it in GitHub Desktop.
Save Sam-Serpoosh/4463277597a03b2b4341 to your computer and use it in GitHub Desktop.
Type Deduction problem in Haskell (type class and instance declarations)
{-# LANGUAGE GeneralizedNewtypeDeriving, FlexibleInstances #-}
module Sized where
import Data.Monoid
newtype Size = Size { getSize :: Int }
deriving (Eq, Ord, Show, Num)
class Sized a where
size :: a -> Size
instance Sized Size where
size = id
instance Monoid Size where
mempty = Size 0
mappend = (+)
data JoinList m a = Empty
| Single m a
| Append m (JoinList m a) (JoinList m a)
deriving (Eq, Show)
testSomething :: (Sized b, Monoid b) => JoinList b a -> JoinList b a
testSomething (Single s value) = let numOfElem = getSize (size s)
newSize = Size (numOfElem + 1)
in Single newSize value
testSomething jl = jl
tree = Single (Size 5) "A"
main :: IO ()
main = putStrLn $ show $ testSomething tree
{-
Produces the following error:
Sized.hs:27:44:
Could not deduce (b ~ Size)
from the context (Sized b, Monoid b)
bound by the type signature for
testSomething :: (Sized b, Monoid b) =>
JoinList b a -> JoinList b a
at Sized.hs:24:18-68
โ€˜bโ€™ is a rigid type variable bound by
the type signature for
testSomething :: (Sized b, Monoid b) =>
JoinList b a -> JoinList b a
at Sized.hs:24:18
Relevant bindings include
s :: b (bound at Sized.hs:25:23)
testSomething :: JoinList b a -> JoinList b a
(bound at Sized.hs:25:1)
In the first argument of โ€˜Singleโ€™, namely โ€˜newSizeโ€™
In the expression: Single newSize value
-}
@Sam-Serpoosh
Copy link
Author

My understanding is that according to the type constraint b MUST be Sized and Monoid, so I'm passing Size which is an instance of both of them BUT because it is a different type then the error Could not deduce (b ~ Size) shows up!

If that is the case, how can I modify the size of the given JoinList and create a new JoinsList with modified size?!

@Gabriella439
Copy link

The error is that your function's real type is not as general as the type you declared. The correct type for your testSomething function is just:

testSomething :: JoinList Size a -> JoinList Size a

The Haskell compiler complains because you gave the following too-general type:

testSomething :: (Sized b, Monoid b) => JoinList b a -> JoinList b a

That type is not correct and it is too general because your testSomething function does not work on any type that implements Sized or Monoid; your function only works on one specific instance of those two classes: Size. If you wanted to generalize your testSomething function to work on any type b that implements Sized and Monoid then you would have to restrict yourself to only using the operations from those two type classes and not using any Size-specific functions like getSize or Size.

@Sam-Serpoosh
Copy link
Author

Thank you so much, I appreciate it. That was kind of my guess as well. I'm passing something more specific than what the type declaration of the function specifies and expects. And your explanation makes total sense.

This issue came up while I was solving Exercise 2, Implementation of dropJ function! While dropping from the tree I need to calculate the size of the new tree which is being returned from the function and I need to work with Size at that point BUT the function declaration that Brent Yorgey provides there is very restrict on:

dropJ :: (Sized b, Monoid b) => Int -> JoinList b a -> JoinList b a

And when I calculate the new size value and use it in construction of the JoinList I get the type deduction error cause of course I'm passing Size and function expects (Sized and Monoid) ONLY! Is there any way around this?! The code for dropJ that I wrote is as following:

dropJ :: (Sized b, Monoid b) => Int -> JoinList b a -> JoinList b a
dropJ 0 list  = list
dropJ _ Empty = Empty
dropJ n (Single s _)   | n >= 1                  = Empty
dropJ n (Append s _ _) | n >= (getSize (size s)) = Empty
dropJ n (Append s left right)
  | n >= (getSize (sizeOf left)) = let remainder = n - (getSize (sizeOf left))
                                       newSize   = Size remainder
                                   in Append newSize Empty (dropJ remainder right)
  | otherwise = Append s (dropJ n left) right

newSize is the root cause of the problem!

@Gabriella439
Copy link

I think the trick here is to use a helper function of this type:

dropJHelper :: (Sized b, Monoid b) => Int -> JoinList b a -> (JoinList b a, b)

This function not only drops the elements but also returns how many elements were left over after the drop. Then you would just make dropJ a thin wrapper around that function:

dropJ n ls = fst (dropJHelper n ls)

@BartoszMilewski
Copy link

This is one possible solution: adding sFromInt to your class. This way you can do your calculation in Int and convert it back to any instance of Sized. This is probably not a very Haskelly solution, but it shows you that it's doable.

class Sized a where
  size :: a -> Size
  sFromInt :: Int -> a

instance Sized Size where
  size = id
  sFromInt s = Size s

testSomething :: (Sized b, Monoid b) => JoinList b a -> JoinList b a
testSomething (Single s value) = let numOfElem = getSize (size s)
                                     newSize = sFromInt (numOfElem + 1)
                                 in Single newSize value

However, for the way you are using it, I would think you'd want your Sized to be a subclass of Monoid. In that case, this would be more direct and convenient:

class Monoid a => Sized a where
  size :: a -> Size
  sFromInt :: Int -> a

instance Sized Size where
  size = id
  sFromInt s = Size s

instance Monoid Size where
  mempty  = Size 0
  mappend = (+)

testSomething :: (Sized b) => JoinList b a -> JoinList b a
testSomething (Single s value) = let newSize = s `mappend` (sFromInt 1)
                                 in Single newSize value

@BartoszMilewski
Copy link

I think I understand your confusion. Let me play the role of an obnoxious compiler (GHC is very polite, and it always assumes that it's some kind of misunderstanding). So you are telling me that testSomething will work for any type b, as long it's Sized and Monoid. Well, you're wrong! Let me give you a counterexample.

data Money = Money Double Int

instance Sized Money where
    size (Money x n) = Size n

instance Monoid Money where
    mempty = Money 0.0 0
    (Money x n) `mappend` (Money x' n') = Money (x + x') (n + n')

moneyTree :: JoinList Money String
moneyTree = Single (Money 29.99 5) "A"

What happens when you call testSomething with moneyTree? You're trying to put Size instead of Money into the result. That won't work. What happened to the $29.99 that I gave you?!

Another way of looking at it is to remove the type signature from testSomething and ask GHCi what type it thinks it is. The answer is:

JoinList Size a -> JoinList Size a

It deduces the first type parameter to be Size, exactly because you're putting newSize of type Size into it.

Notice that this has nothing to do with Haskell. You'd have the same problem with any other language. You're trying to write a generic function that operates on containers of objects that are a subclass of some base B. You can't just replace an item in that container with an element of class B. What if you're called with a container of C, where C inherits from B. You'd return a container with all elements being C except for one that ends up as B. This won't even work in a dynamically typed language, except that you would get a runtime error much later, when you try to apply a method of C to a B, which doesn't support it.

@Sam-Serpoosh
Copy link
Author

That Money example was FANTASTIC, it cleared all the confusion I had about this situation. The problem I had was that I tried to map this to the hierarchy of interface -> concrete implementation like the following Java code for instance:

public interface MyInterface { ... }

public class MyClass implements MyInterface { ... }

public MyInterface testSomething() {
  return new MyClass();
}

But that is the comparison of Apples and Oranges in this situation. In case of the Haskell code, I'm not specifying the return type as something that is Sized and Monoid which makes it ok to return a concrete data type which is an instance of both Monoid and Sized! I'm reaching into the parameterized datatype (e.g JoinList) and replacing the contained item (as you mentioned) with something more specific that it needs to be and I can end up with a situation like the Money example that you drew above! I put Money in the JoinList and get back Size in the JoinList which is not permitted in ANY language of course! That Java interface example distracted me from the root cause of the problem and I could never get out of that rabbit hole ๐Ÿ˜„

Thank you SO MUCH, I highly appreciate it. It was a very interesting discussion and I learned a bunch of cool things actually ๐Ÿ‘

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