Hi, I'm getting the compile error: Gamgine/Image/PNG/Internal/Parser.hs:14:10: Functional dependencies conflict between instance declarations: instance Monad m => Stream LB.ByteString m Word8 -- Defined at Gamgine/Image/PNG/Internal/Parser.hs:14:10 instance Monad m => Stream LB.ByteString m Char -- Defined in ‘Text.Parsec.Prim’ The relevant stuff from the parsec 3.1.9 code[1] is: {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleContexts, UndecidableInstances #-} ... import qualified Data.ByteString.Lazy.Char8 as CL import qualified Data.ByteString.Char8 as C ... class (Monad m) => Stream s m t | s -> t where uncons :: s -> m (Maybe (t,s)) instance (Monad m) => Stream CL.ByteString m Char where uncons = return . CL.uncons instance (Monad m) => Stream C.ByteString m Char where uncons = return . C.uncons And from my code[2] is: {-# LANGUAGE BangPatterns, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-} ... import qualified Data.ByteString.Lazy as LB ... instance (Monad m) => Stream LB.ByteString m Word8 where uncons = return . LB.uncons As you can see, the instances are for different ByteString types, therefore I don't quite get where GHC sees here any conflicts. Greetings, Daniel [1] https://github.com/aslatter/parsec/blob/master/Text/Parsec/Prim.hs [2] https://github.com/dan-t/Gamgine/blob/master/Gamgine/Image/PNG/Internal/Pars...
Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as Data.ByteString.Lazy. Only functions and instances differ. On 05/04/15 15:19, Daniel Trstenjak wrote:
Hi,
I'm getting the compile error:
Gamgine/Image/PNG/Internal/Parser.hs:14:10: Functional dependencies conflict between instance declarations: instance Monad m => Stream LB.ByteString m Word8 -- Defined at Gamgine/Image/PNG/Internal/Parser.hs:14:10 instance Monad m => Stream LB.ByteString m Char -- Defined in ‘Text.Parsec.Prim’
The relevant stuff from the parsec 3.1.9 code[1] is:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleContexts, UndecidableInstances #-}
...
import qualified Data.ByteString.Lazy.Char8 as CL import qualified Data.ByteString.Char8 as C
...
class (Monad m) => Stream s m t | s -> t where uncons :: s -> m (Maybe (t,s))
instance (Monad m) => Stream CL.ByteString m Char where uncons = return . CL.uncons
instance (Monad m) => Stream C.ByteString m Char where uncons = return . C.uncons
And from my code[2] is:
{-# LANGUAGE BangPatterns, FlexibleInstances, MultiParamTypeClasses, FlexibleContexts #-}
...
import qualified Data.ByteString.Lazy as LB
...
instance (Monad m) => Stream LB.ByteString m Word8 where uncons = return . LB.uncons
As you can see, the instances are for different ByteString types, therefore I don't quite get where GHC sees here any conflicts.
Greetings, Daniel
[1] https://github.com/aslatter/parsec/blob/master/Text/Parsec/Prim.hs [2] https://github.com/dan-t/Gamgine/blob/master/Gamgine/Image/PNG/Internal/Pars... _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
On Sun, Apr 05, 2015 at 03:25:01PM +0300, Roman Cheplyaka wrote:
Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as Data.ByteString.Lazy. Only functions and instances differ.
So my only option in this case is to define a newtype wrapper for Data.ByteString.Lazy and then define a Stream instance on this one? Greetings, Daniel
On 05/04/15 15:54, Daniel Trstenjak wrote:
On Sun, Apr 05, 2015 at 03:25:01PM +0300, Roman Cheplyaka wrote:
Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as Data.ByteString.Lazy. Only functions and instances differ.
So my only option in this case is to define a newtype wrapper for Data.ByteString.Lazy and then define a Stream instance on this one?
You might do that. But if I were you, I'd use attoparsec or even binary/cereal to parse PNG. They are better suited for parsing binary data. Roman
participants (2)
-
Daniel Trstenjak -
Roman Cheplyaka