
Hello, I get an error message on the code below with GHC. I can't figure out how to get rid of the error. I'd appreciate suggestions on how to fix this. (BTW, the code may look overly combersome because I stripped out anything unnecessary to demonstrate the error.) {-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception -fallow-undecidable-instances #-} import qualified Prelude import Prelude import Data.Array.IArray class Sequence seq where slength :: (seq e) -> Int snull :: (seq e) -> Bool shead :: (seq e) -> e stail :: (seq e) -> (seq e) instance Sequence [] where slength = length snull = null shead = head stail = tail class From_seq t where from_seq :: (Sequence seq) => (seq e) -> (t e) instance From_seq [] where from_seq seq | snull seq = [] | otherwise = (shead seq) : (from_seq (stail seq)) from_seq' seq | snull seq = (listArray (0,-1) []) | otherwise = listArray (0,fromIntegral (slength seq) -1) (from_seq seq) {- When I uncomment this out, I get the error messages: Error.hs:41:19: Could not deduce (IArray a e) from the context (From_seq (a i), Ix i, Num i, IArray a e1, Sequence seq) arising from a use of `from_seq'' at Error.hs:41:19-31 instance (Ix i, Num i, IArray a e) => From_seq (a i) where from_seq seq = from_seq' seq -} When I load the module above, I can evaluate the folloing in GHCI *Main> from_seq' [0..5] :: Array Int Double array (0,5) [(0,0.0),(1,1.0),(2,2.0),(3,3.0),(4,4.0),(5,5.0)] But, I'd like to do this with the From_seq class. If anyone has suggestions, I'd be grateful. Thanks, Jeff

(sent to the list this time)
The problem is in the type-signature for from_seq:
from_seq :: (Sequence seq) => (seq e) -> (t e)
Neither the From_seq class or the type signature of the from_seq
function place any restrictions on the type of e, so the type can be
rewritten as:
from_seq :: forall e seq . Sequence seq => (seq e) -> (t e)
That is, the class explicitly defines from_seq has having norestrictions on e.
Your from_seq' function requires the type e (in the error, e1) to
inhabit IArray a e.
The IArray constraint isn't compatible with the From_seq class
definition. You may need to explore multi-parameter type classes:
http://en.wikibooks.org/wiki/Haskell/Advanced_type_classes
Does this help?
-Antoine
2008/2/15 Jeff φ
Hello,
I get an error message on the code below with GHC. I can't figure out how to get rid of the error. I'd appreciate suggestions on how to fix this. (BTW, the code may look overly combersome because I stripped out anything unnecessary to demonstrate the error.)
{-# OPTIONS_GHC -fglasgow-exts -fbreak-on-exception -fallow-undecidable-instances #-}
import qualified Prelude import Prelude import Data.Array.IArray
class Sequence seq where slength :: (seq e) -> Int snull :: (seq e) -> Bool shead :: (seq e) -> e stail :: (seq e) -> (seq e)
instance Sequence [] where slength = length snull = null shead = head stail = tail
class From_seq t where from_seq :: (Sequence seq) => (seq e) -> (t e)
instance From_seq [] where from_seq seq | snull seq = [] | otherwise = (shead seq) : (from_seq (stail seq))
from_seq' seq | snull seq = (listArray (0,-1) []) | otherwise = listArray (0,fromIntegral (slength seq) -1) (from_seq seq)
{- When I uncomment this out, I get the error messages:
Error.hs:41:19: Could not deduce (IArray a e) from the context (From_seq (a i), Ix i, Num i, IArray a e1, Sequence seq) arising from a use of `from_seq'' at Error.hs:41:19-31
instance (Ix i, Num i, IArray a e) => From_seq (a i) where from_seq seq = from_seq' seq -}
When I load the module above, I can evaluate the folloing in GHCI
*Main> from_seq' [0..5] :: Array Int Double array (0,5) [(0,0.0),(1,1.0),(2,2.0),(3,3.0),(4,4.0),(5,5.0)]
But, I'd like to do this with the From_seq class. If anyone has suggestions, I'd be grateful.
Thanks,
Jeff
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2008/2/15 Antoine Latter
(sent to the list this time)
The problem is in the type-signature for from_seq:
from_seq :: (Sequence seq) => (seq e) -> (t e)
Neither the From_seq class or the type signature of the from_seq function place any restrictions on the type of e, so the type can be rewritten as:
from_seq :: forall e seq . Sequence seq => (seq e) -> (t e)
That is, the class explicitly defines from_seq has having norestrictions on e.
Your from_seq' function requires the type e (in the error, e1) to inhabit IArray a e.
The IArray constraint isn't compatible with the From_seq class definition. You may need to explore multi-parameter type classes: http://en.wikibooks.org/wiki/Haskell/Advanced_type_classes
Does this help?
Yes, this helped. I added the type variable, e, to my From_seq class and it worked. Thank you for the explanation. Here are the changes I made: class From_seq t e where from_seq :: (Sequence seq) => (seq e) -> (t e) instance From_seq [] e where from_seq seq | snull seq = [] | otherwise = (shead seq) : (from_seq (stail seq)) instance (Ix i, Num i, IArray a e) => From_seq (a i) e where from_seq seq = from_seq' seq
participants (2)
-
Antoine Latter
-
Jeff φ