[Haskell-cafe] Functional dependencies conflict

Ivan Lazar Miljenovic ivan.miljenovic at gmail.com
Sun Apr 5 12:25:58 UTC 2015


On 5 April 2015 at 22:25, Roman Cheplyaka <roma at ro-che.info> wrote:
> Data.ByteString.Lazy.Char8 exports the same lazy bytestring type as
> Data.ByteString.Lazy. Only functions and instances differ.

Well, *instances* can't 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/Parser.hs
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe



-- 
Ivan Lazar Miljenovic
Ivan.Miljenovic at gmail.com
http://IvanMiljenovic.wordpress.com


More information about the Haskell-Cafe mailing list