[Haskell-cafe] type variable is ambiguous in a non-injective type family
Henry Laxen
nadine.and.henry at pobox.com
Sun Jul 28 11:56:40 UTC 2019
Dear Cafe,
I really don't understand what is going on here. I've searched, but I don't
really understand the links that I found. The closest I've come is:
https://sulzmann.blogspot.com/2013/01/non-injective-type-functions-and.html
but I don't understand it enough to see my way to a solution. Here is a
minimal example of what I'm trying to do:
--------------------------------------------------------------------------------
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
module Ambiguous where
class Ambi a where
type SubAmbi a :: *
toSubAmbi :: a -> SubAmbi a
toBool :: SubAmbi a -> Bool
whatsWrong :: Ambi a => a -> IO ()
whatsWrong a = do
let
s = toSubAmbi a
b = toBool s
if b then print "True" else print "False"
{-
src/Games/Ambiguous.hs:15:16: error: …
• Couldn't match expected type ‘SubAmbi a0’
with actual type ‘SubAmbi a’
NB: ‘SubAmbi’ is a non-injective type family
The type variable ‘a0’ is ambiguous
• In the first argument of ‘toBool’, namely ‘s’
In the expression: toBool s
In an equation for ‘b’: b = toBool s
• Relevant bindings include
s :: SubAmbi a
(bound at /home/henry/nadineloveshenry/bin/nlh/src/Games/Ambiguous.hs:14:5)
a :: a
(bound at /home/henry/nadineloveshenry/bin/nlh/src/Games/Ambiguous.hs:12:12)
whatsWrong :: a -> IO ()
(bound at /home/henry/nadineloveshenry/bin/nlh/src/Games/Ambiguous.hs:12:1)
|
Compilation failed.
-}
--------------------------------------------------------------------------------
Could any of you Haskell sages please explain how to do this?
Best wishes,
Henry Laxen
--
Nadine and Henry Laxen The rest is silence
Villa Alta #6
Calle Gaviota #10 Never try to teach a pig to sing
Chapala It wastes your time
+52 (376) 765-3181 And it annoys the pig
More information about the Haskell-Cafe
mailing list