help understanding error from attempt at CIS 194 : Homework 7 - indexJ

Here's what I have so far for JoinList.hs: ( http://www.seas.upenn.edu/~cis194/spring13/hw/07-folds-monoids.pdf) ==== module JoinList where import Data.Monoid import Sized data JoinList m a = Empty | Single m a | Append m (JoinList m a) (JoinList m a) deriving (Eq, Show) tag :: Monoid m => JoinList m a -> m tag Empty = mempty tag (Single m a) = m tag (Append m _ _) = m (+++) :: Monoid m => JoinList m a -> JoinList m a -> JoinList m a (+++) x y = Append (tag x <> tag y) x y indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a indexJ _ Empty = Nothing indexJ i (Single m a) | i == 0 = Just a | otherwise = Nothing indexJ i (Append m x y) | (getSize (tag x)) >= i = indexJ i x | otherwise = indexJ (i - (getSize (tag x))) y ===== Here is the error I'm getting. Haven't been able to make sense of it yet. *Sized> :load "JoinList.hs" [1 of 2] Compiling Sized ( Sized.hs, interpreted ) [2 of 2] Compiling JoinList ( JoinList.hs, interpreted ) JoinList.hs:50:21: Could not deduce (b ~ Size) from the context (Sized b, Monoid b) bound by the type signature for indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a at JoinList.hs:44:11-63 `b' is a rigid type variable bound by the type signature for indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a at JoinList.hs:44:11 Expected type: JoinList Size a Actual type: JoinList b a In the first argument of `tag', namely `x' In the first argument of `getSize', namely `(tag x)' In the first argument of `(>=)', namely `(getSize (tag x))' Failed, modules loaded: Sized. thanks! -- Dustin Lee qhfgva=rot13(dustin)

Hi Dustin,
(tag x) return something of type b which implements Sized and Monoid.
Where as getSize takes value of type Size.
Hence the error. b might not be equal to Size. Thus compiler is
complaining.
Given b is (Sized b), how one can convert it into Size ?
Thanks
Divyanshu Ranjan
On Fri, Jan 9, 2015 at 12:31 AM, Dustin Lee
Here's what I have so far for JoinList.hs: ( http://www.seas.upenn.edu/~cis194/spring13/hw/07-folds-monoids.pdf)
==== module JoinList
where
import Data.Monoid import Sized
data JoinList m a = Empty | Single m a | Append m (JoinList m a) (JoinList m a) deriving (Eq, Show)
tag :: Monoid m => JoinList m a -> m tag Empty = mempty tag (Single m a) = m tag (Append m _ _) = m
(+++) :: Monoid m => JoinList m a -> JoinList m a -> JoinList m a (+++) x y = Append (tag x <> tag y) x y
indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a indexJ _ Empty = Nothing indexJ i (Single m a) | i == 0 = Just a | otherwise = Nothing indexJ i (Append m x y) | (getSize (tag x)) >= i = indexJ i x | otherwise = indexJ (i - (getSize (tag x))) y
=====
Here is the error I'm getting. Haven't been able to make sense of it yet.
*Sized> :load "JoinList.hs" [1 of 2] Compiling Sized ( Sized.hs, interpreted ) [2 of 2] Compiling JoinList ( JoinList.hs, interpreted )
JoinList.hs:50:21: Could not deduce (b ~ Size) from the context (Sized b, Monoid b) bound by the type signature for indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a at JoinList.hs:44:11-63 `b' is a rigid type variable bound by the type signature for indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a at JoinList.hs:44:11 Expected type: JoinList Size a Actual type: JoinList b a In the first argument of `tag', namely `x' In the first argument of `getSize', namely `(tag x)' In the first argument of `(>=)', namely `(getSize (tag x))' Failed, modules loaded: Sized.
thanks!
-- Dustin Lee qhfgva=rot13(dustin)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Ahhh.... I'm using the size function now and at least I don't get any compile errors anymore..... Now to check the code actually works. Thanks! On Thu, Jan 8, 2015 at 12:26 PM, divyanshu ranjan < idivyanshu.ranjan@gmail.com> wrote:
Hi Dustin,
(tag x) return something of type b which implements Sized and Monoid. Where as getSize takes value of type Size. Hence the error. b might not be equal to Size. Thus compiler is complaining.
Given b is (Sized b), how one can convert it into Size ?
Thanks Divyanshu Ranjan
On Fri, Jan 9, 2015 at 12:31 AM, Dustin Lee
wrote: Here's what I have so far for JoinList.hs: ( http://www.seas.upenn.edu/~cis194/spring13/hw/07-folds-monoids.pdf)
==== module JoinList
where
import Data.Monoid import Sized
data JoinList m a = Empty | Single m a | Append m (JoinList m a) (JoinList m a) deriving (Eq, Show)
tag :: Monoid m => JoinList m a -> m tag Empty = mempty tag (Single m a) = m tag (Append m _ _) = m
(+++) :: Monoid m => JoinList m a -> JoinList m a -> JoinList m a (+++) x y = Append (tag x <> tag y) x y
indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a indexJ _ Empty = Nothing indexJ i (Single m a) | i == 0 = Just a | otherwise = Nothing indexJ i (Append m x y) | (getSize (tag x)) >= i = indexJ i x | otherwise = indexJ (i - (getSize (tag x))) y
=====
Here is the error I'm getting. Haven't been able to make sense of it yet.
*Sized> :load "JoinList.hs" [1 of 2] Compiling Sized ( Sized.hs, interpreted ) [2 of 2] Compiling JoinList ( JoinList.hs, interpreted )
JoinList.hs:50:21: Could not deduce (b ~ Size) from the context (Sized b, Monoid b) bound by the type signature for indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a at JoinList.hs:44:11-63 `b' is a rigid type variable bound by the type signature for indexJ :: (Sized b, Monoid b) => Int -> JoinList b a -> Maybe a at JoinList.hs:44:11 Expected type: JoinList Size a Actual type: JoinList b a In the first argument of `tag', namely `x' In the first argument of `getSize', namely `(tag x)' In the first argument of `(>=)', namely `(getSize (tag x))' Failed, modules loaded: Sized.
thanks!
-- Dustin Lee qhfgva=rot13(dustin)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Dustin Lee qhfgva=rot13(dustin)
participants (2)
-
divyanshu ranjan
-
Dustin Lee