Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)

Hi Beginners. I'm writing a matrix class for a game of life implementation. When I try to compile it I get the error "Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)" for the method vicinityMatrix. However, when I query the type of an identical implementation to vicinityMatrix in ghci it is successful: :t \m x y -> fromRows $ vicinityRows m x y \m x y -> fromRows $ vicinityRows m x y :: forall (m :: * -> *) (m1 :: * -> *) a. (Matrix m (Maybe a), Matrix m1 a) => m1 a -> Integer -> Integer -> m (Maybe a) What might be preventing the class from compiling? Thanks guys. --- My Matrix class definition follows below: module Matrix (Matrix) where import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard) class Matrix m a where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) neighbours :: m a -> Integer -> Integer -> [a] toList m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] return $ at m x y row m n = [at m x n | x <- [0 .. columns m - 1]] column m n = [at m n y | y <- [0 .. rows m - 1]] at = (!!!) (!!!) = at vicinityRows m x y = do x' <- [x - 1 .. x + 1] return $ do y' <- [y - 1 .. y + 1] return cell where cell | x < 0 = Nothing | y < 0 = Nothing | x >= columns m = Nothing | y >= rows m = Nothing | otherwise = Just $ at m x y vicinityMatrix m x y = fromRows $ vicinityRows m x y -- neighbours = catMaybes . toListN . vicinityMatrix toListN :: Matrix m a => m a -> [a] toListN m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] guard $ x /= 1 && y /= 1 return $ at m x y

Am Freitag 29 Januar 2010 09:52:37 schrieb Lyndon Maydwell:
Hi Beginners.
I'm writing a matrix class for a game of life implementation. When I try to compile it I get the error "Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)" for the method vicinityMatrix.
However, when I query the type of an identical implementation to
vicinityMatrix in ghci it is successful: :t \m x y -> fromRows $ vicinityRows m x y
\m x y -> fromRows $ vicinityRows m x y
:: forall (m :: * -> *) (m1 :: * -> *) a.
(Matrix m (Maybe a), Matrix m1 a) => m1 a -> Integer -> Integer -> m (Maybe a)
What might be preventing the class from compiling?
Well, the error says the compiler (the type checker) can't deduce the context (Matrix m (Maybe a)) from the givens. If you supply that information, vicinityMatrix :: Matrix m (Maybe a) => m a -> Integer -> Integer -> m (Maybe a) it'll work.
Thanks guys.
---
My Matrix class definition follows below:
module Matrix (Matrix) where
import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard)
class Matrix m a where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) neighbours :: m a -> Integer -> Integer -> [a]
toList m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] return $ at m x y
row m n = [at m x n | x <- [0 .. columns m - 1]] column m n = [at m n y | y <- [0 .. rows m - 1]]
at = (!!!) (!!!) = at
vicinityRows m x y = do x' <- [x - 1 .. x + 1] return $ do y' <- [y - 1 .. y + 1] return cell where cell
| x < 0 = Nothing | y < 0 = Nothing | x >= columns m = Nothing | y >= rows m = Nothing | otherwise = Just $ at m x y
vicinityMatrix m x y = fromRows $ vicinityRows m x y
-- neighbours = catMaybes . toListN . vicinityMatrix
toListN :: Matrix m a => m a -> [a] toListN m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] guard $ x /= 1 && y /= 1 return $ at m x y

Thanks Daniel.
It works, but I'm a bit confused as to why the extra type information is needed.
On Fri, Jan 29, 2010 at 5:17 PM, Daniel Fischer
Am Freitag 29 Januar 2010 09:52:37 schrieb Lyndon Maydwell:
Hi Beginners.
I'm writing a matrix class for a game of life implementation. When I try to compile it I get the error "Could not deduce (Matrix m (Maybe a)) from the context (Matrix m a)" for the method vicinityMatrix.
However, when I query the type of an identical implementation to
vicinityMatrix in ghci it is successful: :t \m x y -> fromRows $ vicinityRows m x y
\m x y -> fromRows $ vicinityRows m x y
:: forall (m :: * -> *) (m1 :: * -> *) a.
(Matrix m (Maybe a), Matrix m1 a) => m1 a -> Integer -> Integer -> m (Maybe a)
What might be preventing the class from compiling?
Well, the error says the compiler (the type checker) can't deduce the context (Matrix m (Maybe a)) from the givens. If you supply that information,
vicinityMatrix :: Matrix m (Maybe a) => m a -> Integer -> Integer -> m (Maybe a)
it'll work.
Thanks guys.
---
My Matrix class definition follows below:
module Matrix (Matrix) where
import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard)
class Matrix m a where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) neighbours :: m a -> Integer -> Integer -> [a]
toList m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] return $ at m x y
row m n = [at m x n | x <- [0 .. columns m - 1]] column m n = [at m n y | y <- [0 .. rows m - 1]]
at = (!!!) (!!!) = at
vicinityRows m x y = do x' <- [x - 1 .. x + 1] return $ do y' <- [y - 1 .. y + 1] return cell where cell
| x < 0 = Nothing | y < 0 = Nothing | x >= columns m = Nothing | y >= rows m = Nothing | otherwise = Just $ at m x y
vicinityMatrix m x y = fromRows $ vicinityRows m x y
-- neighbours = catMaybes . toListN . vicinityMatrix
toListN :: Matrix m a => m a -> [a] toListN m = do x <- [0 .. columns m - 1] y <- [0 .. rows m - 1] guard $ x /= 1 && y /= 1 return $ at m x y

Am Freitag 29 Januar 2010 10:45:32 schrieb Lyndon Maydwell:
Thanks Daniel.
It works, but I'm a bit confused as to why the extra type information is needed.
Well, you call fromRows on the result of vicinityRows. vicinityRows m x y :: [[Maybe a]] fromRows :: Matrix mat b => [[b]] -> mat b So for fromRows (vicinityRows m x y) to be well typed, you need an instance Matrix matr (Maybe a) where ... for some matrix type matr. That has to come from somewhere. It might come from an instance Matrix m a => Matrix m (Maybe a) where ... or you can supply it as a constraint on the function vicinityMatrix. However, having a look, none of the methods in the class look like they depend on the actual type a, so it might be better to have class Matrix m where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) -- No constraint needed!! neighbours :: m a -> Integer -> Integer -> [a]
On Fri, Jan 29, 2010 at 5:17 PM, Daniel Fischer
wrote: Well, the error says the compiler (the type checker) can't deduce the context (Matrix m (Maybe a)) from the givens. If you supply that information,
vicinityMatrix :: Matrix m (Maybe a) => m a -> Integer -> Integer -> m (Maybe a)
it'll work.
Thanks guys.
---
My Matrix class definition follows below:
module Matrix (Matrix) where
import Data.Array import Data.Maybe (catMaybes) import Control.Monad (guard)
class Matrix m a where fromRows :: [[a]] -> m a
<snip>
vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a)

Ah, yes. That might be just what I'm after!
However, having a look, none of the methods in the class look like they depend on the actual type a, so it might be better to have
class Matrix m where fromRows :: [[a]] -> m a toList :: m a -> [a] rows :: m a -> Integer columns :: m a -> Integer row :: m a -> Integer -> [a] column :: m a -> Integer -> [a] at :: m a -> Integer -> Integer -> a (!!!) :: m a -> Integer -> Integer -> a vicinityRows :: m a -> Integer -> Integer -> [[Maybe a]] vicinityMatrix :: m a -> Integer -> Integer -> m (Maybe a) -- No constraint needed!! neighbours :: m a -> Integer -> Integer -> [a]
participants (2)
-
Daniel Fischer
-
Lyndon Maydwell