How do I specify a type variable used in an inline type, is the same as a type variable used in a function definition? - haskell

(Apologies if my terminology is wrong).
I'm trying to write a wrapper function that handles exceptions: if the given IO action throws, it returns Nothing (inside an IO context of course), but if the given IO action succeeds, it returns Just v.
tryMaybe :: IO a -> IO (Maybe a)
tryMaybe action = do
result <- (try action) :: IO (Either SomeException a)
return $ case result of
Left _ -> Nothing
Right v -> Just v
This results in the compiler error message:
Couldn't match type `a' with `a1'
`a' is a rigid type variable bound by
the type signature for tryMaybe :: IO a -> IO (Maybe a)
at src/Database.hs:33:13
`a1' is a rigid type variable bound by
an expression type signature: IO (Either SomeException a1)
at src/Database.hs:35:15
Expected type: IO a1
Actual type: IO a
In the first argument of `try', namely `action'
I'm guessing that the type variable a in the first line isn't the same as the a in the third line - they just happen to have the same name in the source code, and the compiler has renamed it a1 in the error message.
So how do I tell Haskell that these are the same types?

You need to enable the ScopedTypeVariables extension, and the change the type signature of the top-level function to start with forall a .:
{-# LANGUAGE ScopedTypeVariables #-}
...
tryMaybe :: forall a . IO a -> IO (Maybe a)
...
The forall syntax brings the type variable a into scope for the entire body of tryMaybe, rather than it being limited to the type signature which is the default. This is mainly a historical anomaly rather than a deliberate design.

Related

Ad hoc polymorphic functions

I have some data that I'd like to print (some is Maybe and some is not), and I'm trying to create a generic showField function as follows:
showField :: (Show a) => a -> Text
showField x
| isJust x = Text.pack $ show $ fromJust x
| isNothing x = "None"
| otherwise = Text.pack $ show x
This is throwing a rigid type error:
• Couldn't match expected type ‘Maybe a0’ with actual type ‘a’
‘a’ is a rigid type variable bound by
the type signature for:
showField :: forall a. Show a => a -> Text
at /data/users/jkozyra/fbsource/fbcode/experimental/jkozyra/hs/holdout_cleanup/HoldoutReaper.hs:244:18
• In the first argument of ‘isNothing’, namely ‘x’
In the expression: isNothing x
In a stmt of a pattern guard for
an equation for ‘showField’:
isNothing x
I generally understand this error, but I don't understand if there's a way to achieve what I'd like to. I've also tried pattern matching rather than guards, but can't quite work that out either. Is there something that I could construct in this format that would work?
It looks like you're trying to construct an adhoc polymorphic function - a function whose definition varies according to its type.
A parametric polymorphic function does the same thing to all data types:
both :: a -> (a,a)
both a = (a,a)
In Haskell, adhoc polymorphism is implemented using type classes:
class ShowField a where
showField :: a -> Text
instance Show a => ShowField (Maybe a) where
showField Nothing = "None"
showField (Just a) = Text.pack $ show a
However there's no way to define an instance for "all other types other than Maybe a" with type classes, so you just have to define instances for the types you actually care about:
class ShowField Int where
showField = Text.pack . show
class ShowField Float where
showField = Text.pack . show
You can cut down on boilerplate by using -XDefaultSignatures:
class ShowField' a where
showField :: a -> Text
default showField :: Show a => a -> Text
showField = Text.pack . show
instance ShowField' Int where
instance ShowField' Float where
The error tells us:
‘a’ is a rigid type variable bound by
the type signature for:
showField :: forall a. Show a => a -> Text
Basically, this tells us that according to the type signature you provided, the type of the first parameter is forall a. Show a (the 'forall a.' bit is implied by the signature), which means that the first parameter can be any type that is an instance of Show. It is a rigid type variable because it is defined by an explicit type signature.
It also tells us:
Couldn't match expected type ‘Maybe a0’ with actual type ‘a’
By applying the functions isJust and isNothing — both of type Maybe a -> Bool — to the first parameter you are also claiming the type of the first parameter is Maybe a which is obviously not the same type as forall a. Show a => a -> Text.
You can turn this into a correct program simply by removing the type signature for showField, but that won't have the behavior you desire — the inferred type signature will be (Show a) => Maybe a -> Text which obviously only accepts values of Maybe a (where a is also an instance of Show).
In Haskell, you can't have a function that accepts values of both a and Maybe a¹. Without more context, it's unclear what your actual goal is, but there is almost certainly a more idiomatic way to achieve it.
¹ Unless you have a type class that has instances for both a and Maybe a.

Why does this function that uses a scoped type variable in a where clause not typecheck?

I have a function that has a value defined in a where clause, and I want to give it an explicit type annotation. The annotation needs to use a type variable from the top-level function, so it was my understanding that I needed to use ScopedTypeVariables. Here is a minimal reduction of the problem:
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Monad.Trans.Except
import Data.Functor.Identity
f :: ExceptT String Identity a -> Maybe a
f m = Nothing
where x :: Identity (Either String a)
x = runExceptT m
This code does not typecheck. It fails with the following error message:
Couldn't match type ‘a’ with ‘a1’
‘a’ is a rigid type variable bound by
the type signature for f :: ExceptT String Identity a -> Maybe a
at src/Lib.hs:20:6
‘a1’ is a rigid type variable bound by
the type signature for x :: Identity (Either String a1)
at src/Lib.hs:22:14
Expected type: ExceptT String Identity a1
Actual type: ExceptT String Identity a
Relevant bindings include
x :: Identity (Either String a1) (bound at src/Lib.hs:23:9)
m :: ExceptT String Identity a (bound at src/Lib.hs:21:3)
f :: ExceptT String Identity a -> Maybe a
(bound at src/Lib.hs:21:1)
In the first argument of ‘runExceptT’, namely ‘m’
In the expression: runExceptT m
Why does this fail? I do not understand why this would cause problems—it seems like a textbook use of scoped type variables. For reference, I am using GHC 7.10.3.
You need an explicit forall:
{-# LANGUAGE ScopedTypeVariables #-}
import Control.Monad.Trans.Except
import Data.Functor.Identity
f :: forall a. ExceptT String Identity a -> Maybe a
f m = Nothing
where x :: Identity (Either String a)
x = runExceptT m
but why
That is a great question. This appears to be a rule of ScopedTypeVariables. We know in GHC Haskell that all top-level variables are implicitly forall'd, as documented here. One would suspect that the GHC devs added this behavior for backwards compatibility: without this rule, a file without the extension turned on could stop type-checking once the extension was turned on. We can easily imagine a scenario where helper functions declared in the where block to inadvertently reuse the common type variable names a, b, c, t, so on. It would be great if someone could find the exact spot in the GHC source code where this distinction between explicit and implicit forall'd variables arose.
update
Here we go (although this is all guesswork from the comments and grepping):
While type-checking user signatures, the function tcUserTypeSig invokes findScopedTyVars. TcBinds.hs:ef44606:L1786
findScopedTyVars in TcRnTypes filters for foralls by calling tcSplitForAllTys. TcRnTypes.hs:ef44606:L1221
Which is a wrapper around splitForAllTys, which folds over a type's subtypes to build up a list of type variables introduced by foralls. Types/Type.hs:ef44606:L1361

Unwrapping the STT monad in a transformer stack?

This question is apparently related to the problem discussed here and here. Unfortunately, my requirement is slightly different to those questions, and the answers given don't apply to me. I also don't really understand why runST fails to type check in these cases, which doesn't help.
My problem is this, I have one section of code that uses one monad stack, or rather a single monad:
import Control.Monad.Except
type KErr a = Except KindError a
Another section of code needs to integrate with this that wraps this within the STT monad:
type RunM s a = STT s (Except KindError) a
At the interface between these sections, I clearly need to wrap and unwrap the outer layer. I've got the following function to work in the KErr -> RunM direction:
kerrToRun :: KErr a -> RunM s a
kerrToRun e = either throwError return $ runExcept e
but for some reason I just can't get the converse to type check:
runToKErr :: RunM s a -> KErr a
runToKErr r = runST r
I'm working on the assumption that as the RunM's inner monad has the same structure as KErr, I can just return it once I've unwrapped the STT layer, but I don't seem to be able to get that far, as runST complains about its type arguments:
src/KindLang/Runtime/Eval.hs:18:21:
Couldn't match type ‘s’ with ‘s1’
‘s’ is a rigid type variable bound by
the type signature for runToKErr :: RunM s a -> KErr a
at src/KindLang/Runtime/Eval.hs:17:14
‘s1’ is a rigid type variable bound by
a type expected by the context:
STT s1 (ExceptT KindError Data.Functor.Identity.Identity) a
at src/KindLang/Runtime/Eval.hs:18:15
Expected type: STT
s1 (ExceptT KindError Data.Functor.Identity.Identity) a
Actual type: RunM s a
I've also tried:
runToKErr r = either throwError return $ runExcept $ runST r
in order to more strongly isolate runST from its expected return type, in case that was the cause of the issue, but the results are the same.
Where is this s1 type coming from, and how do I persuade ghc that it's the same type as s?
(The below talks about ST s a but applies just the same as STT s m a; I've just avoided the unnecessary complication of talking about the transformer version below)
The problem you are seeing is that runST has type (forall s. ST s a) -> a to isolate any potential (STRef-changing) effects of the computation from the outside, pure world. The whole point of the s phantom type that all ST computations, STRefs, etc. are tagged with, is to track which "ST-domain" they belong to; and the type of runST ensures that nothing can pass between domains.
You can write runToKErr by enforcing the same invariant:
{-# language Rank2Types #-}
runToKErr :: (forall s. RunM s a) -> KErr a
runToKErr = runST
(of course, you might realize further down the road that this restriction is too strong for the program you hope to write; at that point you'll need to lose hope, sorry, I mean you'll need to redesign your program.)
As for the error message, the reason you can't "convince the type checker that s1 and s are the same type" is because if I pass you an ST s a for a given choice of s and a, that is not the same as giving you something which allows you to choose your own s. GHC chose s1 (a Skolemized variable) as s and so tries to unify ST s a with ST s1 a

Type inference with GADTs - a0 is untouchable

Lets say I have this program
{-# LANGUAGE GADTs #-}
data My a where
A :: Int -> My Int
B :: Char -> My Char
main :: IO ()
main = do
let x = undefined :: My a
case x of
A v -> print v
-- print x
compiles fine.
But when I comment in the print x, I get:
gadt.hs: line 13, column 12:
Couldn't match type ‘a0’ with ‘()’
‘a0’ is untouchable
inside the constraints (a1 ~ GHC.Types.Int)
bound by a pattern with constructor
Main.A :: GHC.Types.Int -> Main.My GHC.Types.Int,
in a case alternative
at /home/niklas/src/hs/gadt-binary.hs:13:5-7
Expected type: GHC.Types.IO a0
Actual type: GHC.Types.IO ()
In the expression: System.IO.print v
In a case alternative: Main.A v -> System.IO.print v
Why do I get this error in line 13 (A v -> print v) instead of only in the print x line?
I thought the first occurrence should determine the type.
Please enlighten me :)
Well, first note that this has nothing to do with the particular print x: you get the same error when ending main with e.g. putStrLn "done".
So the problem is indeed in the case block, namely in that only the last statement of a do is required to have the type of the do block's signature. The other statements merely have to be in the same monad, i.e. IO a0 rather than IO ().
Now, usually this a0 is inferred from the statement itself, so for instance you can write
do getLine
putStrLn "discarded input"
though getLine :: IO String rather than IO (). However, in your example the information print :: ... -> IO () comes from inside the case block, from a GADT match. And such GADT matches behave differently from other Haskell statements: basically, they don't let any type information escape its scope, because if the information came from the GADT constructor then it's not correct outside of the case.
In that particular example, it seems obvious enough that a0 ~ () has nothing at all to do with the a1 ~ Int from the GADT match, but in general, such a fact could only be proven if GHC traced for all type information where it came from. I don't know if that's even possible, it would certainly be more complicated than Haskell's Hindley-Milner system, which heavily relies on unifying type information, which essentially assumes that it doesn't matter where the information came from.
Therefore, GADT matches simply act as a rigid “type information diode”: the stuff inside can never be used to determine types on the outside, like that the case block as a whole should be IO ().
However, you can manually assert that, with the rather ugly
(case x of
A v -> print v
) :: IO ()
or by writing
() <- case x of
A v -> print v

Haskell - Ambiguous type variable

I am having trouble with ambiguous types in Haskell. I started out with the following:
module GameState
( GameState(..)
, GameStateMonad
, module Control.Monad.Trans
, module Control.Monad.Trans.State.Lazy
, Blank(..)
) where
import Control.Monad.Trans
import Control.Monad.Trans.State.Lazy
type GameStateMonad a b = StateT a IO b
class GameState a where
update :: Double -> GameStateMonad a ()
update deltaTime = return ()
draw :: GameStateMonad a ()
draw = return ()
getNextState :: GameState b => GameStateMonad a (Maybe b)
getNextState = return Nothing
isStateFinished :: GameStateMonad a Bool
isStateFinished = return True
-- This is just a dummy data and instance declaration to demonstrate the error
data Blank = Blank
instance GameState Blank
Then when I try to run the following in ghci:
runStateT getNextState Blank
I get:
Ambiguous type variable `b0' in the constraint:
(GameState b0) arising from a use of `getNextState'
Probable fix: add a type signature that fixes these type variable(s)
...
I thought it was complaining that my default implementation of the getNextState function didn't specify a concrete type, so I tried the following:
getNextState :: GameState b => GameStateMonad a (Maybe b)
getNextState = return (Nothing :: Maybe Blank)
Unfortunately I got this error while compiling:
Could not deduce (b ~ Blank)
from the context (GameState a)
bound by the class declaration for `GameState'
at GameState.hs:(14,1)-(25,33)
or from (GameState b)
bound by the type signature for
getNextState :: GameState b => GameStateMonad a (Maybe b)
at GameState.hs:22:5-50
`b' is a rigid type variable bound by
the type signature for
getNextState :: GameState b => GameStateMonad a (Maybe b)
at GameState.hs:22:5
...
But I found that adding a type signature when I call getNext state allows the code to run:
runStateT (getNextState :: GameStateMonad Blank (Maybe Blank)) Blank
Unfortunately this stops me from making generic code to handle game states. It also makes little sense to me. What's the point in returning a polymorphic type if you have to give it an explicit type after it's returned? The original issue is also really confusing to me because I can make a function as follows:
test :: Num a => Maybe a
test = Nothing
And have no problems running it. Shouldn't this complain about ambiguous types like my original code? Also when giving the return value an explicit type I cannot compile it, like before:
test :: Num a => Maybe a
test = Nothing :: Maybe Int
I don't see why this is a problem. Int is an instance of type Num so the type of the function is correct.
I have four questions:
Why does giving an explicit type when returning an element of a typeclass cause a compile error?
Why does returning an ambiguous Maybe value inside of getNextState cause an error but inside test it does not?
Why does this error occur without me calling a function on the returned polymorphic data, as explained here?
In the link above, the answer mentions that "[you get this error] because you have something that produces a polymorphic result, then apply a function that takes a polymorphic argument to that result, such that the intermediate value's type is unknown". Doesn't this mean that functions that return a polymorphic result are essentially useless?
Thanks.
Cat Plus Plus has already explained why
getNextState :: GameState b => GameStateMonad a (Maybe b)
getNextState = return (Nothing :: Maybe Blank)
doesn't work, so I can be short on that. The type signature promises that getNextState can deliver a value of type Maybe b for whatever type b the caller demands. It's the caller of the function who decides what type it shall return if a function has polymorphic return type. So the signature promises "whatever you want, as long as it's a GameState instance", but the implementation says "No, I don't care what you ordered, I return a Blank".
Ambiguous type variable `b0' in the constraint:
(GameState b0) arising from a use of `getNextState'
Probable fix: add a type signature that fixes these type variable(s)
from typing
runStateT getNextState Blank
at the ghci prompt. If you ask ghci for the type of that, it will tell you
runStateT getNextState Blank :: GameState b => IO (Maybe b)
(no guarantees about the choice of type variable). But there is no context, so ghci doesn't know which type to instantiate b with. And so it doesn't know which implementation of getNextState it should call [or, which dictionary it should pass, if we look at GHC's implementation of type classes]. It has no way of resolving that ambiguity, so it tells you about it and suggests how you could resolve it.
test :: Num a => Maybe a
test = Nothing
Yes, that's in principle the same problem, when you type test at the ghci prompt. But there are special rules for resolving ambiguous type variables when there is one numeric class involved (where ambiguities are most frequent, literals are already ambiguous), and all involved constraints are simple and concern classes of the Prelude or the standard libraries. In that case, ambiguous type variables are instantiated by defaulting, so ghci would choose to instantiate a with Integer and print the Nothing of the type Maybe Integer.
Your GameState class is not defaultable, that's the difference between these examples.
Why does this error occur without me calling a function on the returned polymorphic data, as explained here?
Because you're not calling any function that would determine the type. If you had a function of type
foo :: Blank -> Int
and typed
runStateT getNextState Blank >>= print . maybe 0 foo
the use of foo would determine b and all would be swell.
The problem would however not be solved but exacerbated, if you called a polymorphic function (whose argument type cannot be inferred from its result type), as in the linked example. Then the ambiguous type is no longer reachable from the outside, and it can never be resolved. Then the only way is to provide a type signature that resolves the ambiguity.
Doesn't this mean that functions that return a polymorphic result are essentially useless?
Oh no, they are immensely useful. Look at read, or fromInteger, realToFrac, ...
The point is, that the type at which they shall be used must somehow be determined where they are used. Most of the time that is done by the calling context, but sometimes an explicit type signature is necessary.
I'm not sure what you're trying to achieve by making GameState a typeclass. You might be too much in OOP mindset here — typeclasses are not OOP classes. A set of game states will probably be closed, so it might make more sense to just make it a single ADT.
Why does giving an explicit type when returning an element of a typeclass cause a compile error?
Look at your function's signature: GameState b => GameStateMonad a (Maybe b). Now remember that this implies forall b. GameState b => GameStateMonad a (Maybe b).
Implementation of the function cannot decide what b is — it must work for all of them (as long as they fit in constraints), because it's up for the caller to decide.
That's why return (Nothing :: Maybe Blank) is an error — it doesn't work for all types b — it only works for Blank. "Could not deduce (b ~ Blank)" means GHC can't prove type equality here. Same thing goes for Nothing :: Maybe Int. And that's also why adding type signature in the call site works.
I'll write something on ambiguities later maybe. I'm still pretty sure you're overengineering this code anyway, so the solution is to not do that.

Resources