[Haskell-cafe] Disambiguating a Num/RealFrac instance

Adam Gundry adam at well-typed.com
Thu May 28 17:42:30 UTC 2015


On 28/05/15 18:28, Brandon Allbery wrote:
> On Tue, May 26, 2015 at 8:35 PM, <amindfv at gmail.com
> <mailto:amindfv at gmail.com>> wrote:
> 
>     Is there any way (without IncoherentInstances or Rebindablesyntax)
>     that I can let the user write e.g. "giveGPA 4.0" (and "giveGPA 4")
>     and get back "F 4" without getting type errors that "4.0"'s type is
>     ambiguous? I can guarantee there won't be any additional instances
>     to "ToGPA"
> 
> 
> A typeclass with only one instance is nonsensical, and often a symptom
> of trying to use typeclasses as OO classes. All it's doing here is
> hurting you.

Like Brandon, I suspect this probably isn't what you should do. But if
you *really* want to do it, this works:

    {-# LANGUAGE ExtendedDefaultRules, FlexibleInstances #-}

    default (Float)

    data GPA = F Float | Excuse String

    class ToGPA a where
      giveGPA :: a -> GPA

    instance ToGPA Float where
      giveGPA = F

    instance ToGPA String where
      giveGPA = Excuse

    x = giveGPA 4
    y = giveGPA 4.0
    z = giveGPA "Hello"

For more information:
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/interactive-evaluation.html#extended-default-rules

Hope this helps,

Adam


-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/


More information about the ghc-devs mailing list