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/Parser.hs
_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users

Reply via email to