[Haskell-cafe] Problem on overlapping instances
Jasper Van der Jeugt
jaspervdj at gmail.com
Wed Jan 5 09:33:05 CET 2011
Hello,
{-# LANGUAGE OverlappingInstances, FlexibleInstances #-}
import Data.Binary
instance Binary [String] where
get = undefined
put = undefined
works fine here on GHC 6.12.3. That being said, it would be safer
perhaps to add a newtype around [String] so you can avoid the orphan
instance as well, i.e.
import Data.Binary
newtype MyType = MyType [String]
instance Binary MyType where
get = undefined
put = undefined
Cheers,
Jasper
On Wed, Jan 5, 2011 at 9:24 AM, Magicloud Magiclouds
<magicloud.magiclouds at gmail.com> wrote:
> Hi,
> I am using Data.Binary which defined "instance Binary a => Binary
> [a]". Now I need to define "instance Binary [String]" to make
> something special for string list.
> How to make it work? I looked into the chapter of
> overlappinginstances, nothing works.
> --
> 竹密岂妨流水过
> 山高哪阻野云飞
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
More information about the Haskell-Cafe
mailing list