Re: [Haskell-cafe] type variable is ambiguous in a non-injective type family

First, thank you Li-yao Xia for your clear and helpful response. I was able to continue thanks to you. Thanks for the question Anthony, I look forward to learning something. I hope I'll be explain this clearly. I am writing some games, which can share some code, such as logging in, and broadcasting messages to players. I started by writing just one game, with no consideration for how and what to share. This let to a gamestate which contained things like: newtype GameId = GameId Int data Game1 { _game1TimeStarted :: UTCTime, _game1PlayerId :: GameId, ... _game1RandomGen :: StdGen, _game1Commands :: [Game1Command] } the actual state is a more complicated than this, because I split it into a Static part and a Mutable part that is in a TVar (Map GameId Game1MutableState) Next I start writing Game2, which I discover will do the same kind of broadcasting of messages (Commands) as Game1. So I would like to use the same code in Game2 as in Game1 that handles the broadcasting. I came up with: (this is part of the actual class I am using) class Game a where type Command a :: * type Mutable a :: * type Static a :: * toGameId :: a -> GameId toMutable :: a -> IO (Maybe (Mutable a)) everyone :: Mutable a -> [Sink] instance Game Game1State where type Command Game1State = Game1Command type Mutable Game1State = Game1Mutable type Static Game1State = Game1Static toGameId ss = ss ^. game1Static . game1GameId toMutable ss = do let tVar = ss ^. game1Mutable gId = toGameId ss gm <- liftIO (readTVarIO tVar) return $ M.lookup gId (unGameMap gm) everyone = mapMaybe _game1Sink . M.elems . _game1SPMap similarly, I make Game2State an instance of Game. Now in the code that broadcasts commands I have: sendBroadCasts :: (Show (Command a) , Game a) => [BroadCast a] -> a -> IO () ... sendOneCommand :: (Show (Command a) , Game a) => a -> BroadCastReceiver -> Command a -> IO () sendOneCommand ss BroadCastToEveryone command = do mbMut <- toMutable ss case mbMut of Nothing -> return () Just mut -> do let sinks = everyone mut mapM_ (`sendCommand` command) sinks but GHC scolds me with: src/Games/BroadCasts.hs:53:12-23: error: … • Couldn't match type ‘Mutable a’ with ‘Mutable a0’ Expected type: IO (Maybe (Mutable a0)) Actual type: IO (Maybe (Mutable a)) NB: ‘Mutable’ is a non-injective type family The type variable ‘a0’ is ambiguous • In a stmt of a 'do' block: mbMut <- toMutable ss In the expression: ... After incorporating Li-yao Xia's suggestion, the code becomes: sendOneCommand :: forall a. (Show (Command a) , Game a) => ----------------- ^^^^^^^^^ this is added a -> BroadCastReceiver -> Command a -> IO () sendOneCommand _ (BroadCastToSome sinks) command = mapM_ (`sendCommand` command) sinks sendOneCommand ss BroadCastToEveryone command = do mbMut <- toMutable ss case mbMut of Nothing -> return () Just mut -> do let sinks = everyone @a mut -------------------------- ^^ this is added mapM_ (`sendCommand` command) sinks and GHC is happy. I hope I have explained this sufficiently clearly. I look forward to your insights. Best wishes, Henry Laxen
"Anthony" == Anthony Clayden
writes:
Anthony> Hi Henry, both replies you've received are excellent, I won't expand on them. Anthony> I am interested in how you got into such a pickle in the first place: Anthony> Why set `AllowAmbiguousTypes`? Did you understand what that means? ----------------------^^^^^^^^^^^^^^^^^^^^ I read https://stackoverflow.com/questions/49684655/how-dangerous-is-allowambiguous... which seems to indicate that using it is "a perfectly reasonable thing" Anthony> Did you think it odd that despite having that set, you get error Anthony> `type variable ... is ambiguous`? Anthony> There are ways to achieve what you want without Anthony> `AllowAmbiguousTypes` nor `TypeApplications`, but that would need Anthony> a rather different design. So what lead you into this design? Anthony> AntC -- 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

Hi Henry, I'm not sure if this is suitable for your use case, but maybe simple multi parameter type classes would be an alternative? Especially because then you could use FunDeps if more dependencies turn up. Like this: class Game gameState command mutable static | gameState -> mutable,static where toGameId :: static -> GameId toMutable :: gameState -> IO (Maybe mutable) everyone :: mutable -> [Sink] instance Game Chess ChessCommand ChessMutable ChessStatic where … Admittedly, the type looks a bit long. But maybe more unification is possible to reduce that. Yet another idea is that instead of sprinkling TypeApplications, you could also try a bit of refactoring: class Game g where data Command g :: * data Mutable g :: * data Static g :: * toGameId :: g -> GameId toMutable :: g -> IO (Maybe (Mutable a)) everyone :: Mutable g -> [Sink] instance Game Chess where data Command Chess = MovePiece { movedPiece :: ChessField, moveTarget :: ChessField } | Castling { withLeftRook :: Bool } | Promote { promotedPiece :: ChessField, promotedTo :: ChessPiece } | EnPassant { enPassantFrom :: ChessField } | GiveUp …
participants (2)
-
Henry Laxen
-
MarLinn