What happens to missing type variables in Church-style core? - haskell

This is a bit esoteric, but maddening. In an answer to another question, I noted that in this entirely valid program
poo :: String -> a -> a
poo _ = id
qoo :: (a -> a) -> String
qoo _ = ""
roo :: String -> String
roo = qoo . poo
the type variable a is neither solved nor generalized in the process of checking roo. I'm wondering what happens in the translation to GHC's core language, a Church-style variant of System F. Let me spell things out longhand, with explicit type lambdas /\ and type applications #.
poo :: forall a. [Char] -> a -> a
poo = /\ a -> \ s x -> id # a
qoo :: forall a. (a -> a) -> [Char]
qoo = /\ a -> \ f -> [] # Char
roo :: [Char] -> [Char]
roo = (.) # [Char] # (? -> ?) # [Char] (qoo # ?) (poo # ?)
What on earth goes in the ? places? How does roo become a valid core term? Or do we really get a mysterious vacuous quantifier, despite what the type signature says?
roo :: forall a. [Char] -> [Char]
roo = /\ a -> ...
I've just checked that
roo :: forall . String -> String
roo = qoo . poo
goes through ok, which may or may not mean that the thing typechecks with no extra quantification.
What's happening down there?

Here's the core generated by GHC (after adding some NOINLINE pragmas).
qoo_rbu :: forall a_abz. (a_abz -> a_abz) -> GHC.Base.String
[GblId, Arity=1, Caf=NoCafRefs]
qoo_rbu = \ (# a_abN) _ -> GHC.Types.[] # GHC.Types.Char
poo_rbs :: forall a_abA. GHC.Base.String -> a_abA -> a_abA
[GblId, Arity=1]
poo_rbs = \ (# a_abP) _ -> GHC.Base.id # a_abP
roo_rbw :: GHC.Base.String -> GHC.Base.String
[GblId]
roo_rbw =
GHC.Base..
# (GHC.Prim.Any -> GHC.Prim.Any)
# GHC.Base.String
# GHC.Base.String
(qoo_rbu # GHC.Prim.Any)
(poo_rbs # GHC.Prim.Any)
It seems GHC.Prim.Any is used for the polymorphic type.
From the docs (emphasis mine):
The type constructor Any is type to which you can unsafely coerce any
lifted type, and back.
It is lifted, and hence represented by a pointer
It does not claim to
be a data type, and that's important for the code generator, because
the code gen may enter a data value but never enters a function value.
It's also used to instantiate un-constrained type variables after type
checking.
It makes sense to have such a type to insert in place of un-constrained types, as otherwise trivial expressions like length [] would cause an ambiguous type error.

This is a non-problem. In the signature of roo, the type variable a just does not appear as it stands. An easier example would be the expression
const 1 id
where
id :: forall a.a->a

Related

Combining the results of double for loops in Haskell

I am trying to write a function which generates a list of lists and then applies a function to each of those lists and combines the results into one big list. However I am getting an error and would appreciate if someone can point me to the right direction.
The code currently looks like this:
solve_all :: [Constraint] -> Sol -> Sol -> CType -> [(Maybe Typing)]
solve_all c lam_env app_env t2= do
lst <- (simMatch c)
forM lst $ \d -> do
return $ case pleaseUnify d of --ERROR HERE
Right u -> Just substituteTyping u (lam_env .+. app_env, t2)
Left _ -> Nothing
where:
simMatch :: [Constraint] -> [[Constraint]]
pleaseUnify :: [Constraint] -> Either String Unifcation
substituteTyping :: Unifcation -> Typing -> Typing
the error is pointing to the call pleaseUnify d saying I passed just one constraint instead of a list
• Couldn't match expected type ‘[Constraint]’
with actual type ‘Constraint’
But I followed the answer which used forM in this question iterating through a list in haskell
and I am generating a list of lists from (simMatch c). So how come when I iterate I get only one constraint?
Well let's step through it and add comments about the types
solve_all :: [Constraint] -> Sol -> Sol -> CType -> [(Maybe Typing)]
solve_all c lam_env app_env t2 = do
At this point we're in the list monad (the return value is [(Maybe Typing)]).
lst <- (simMatch c :: [[Constraint]])
We bound a variable lst to simMatch in a list monad, so lst :: [Constraint].
forM lst $ \d -> do
For each element of lst named d... so d :: Constraint.
return $ case pleaseUnify d of --ERROR HERE
And we know pleaseUnify :: [Constraint] -> who_cares so we want d :: [Constraint] but have just above seen it must be a type Constraint.
Did you really mean to use the list monad and to name an intermediate value lst? Perhaps you intend:
forM (simMatch c) $ \d ->
return $ case pleaseUnify d of
Right u -> Just (substituteTyping u (lam_env .+. app_env, t2)) -- Notice a fix here too
Left _ -> Nothing

Why do some function calls fail to work without a type application?

I am having trouble understanding how type applications work. Why can sing in refuteRefuteKnockable be used without a type application when the call to sing in knockableOrOpened will fail to type check without a type application?
refuteRefuteKnockable :: SingI s => Refuted (Refuted (Knockable s)) -> Knockable s
refuteRefuteKnockable rrK =
case isKnockable $ sing of
Proved k -> k
Disproved rK -> absurd $ rrK rK
knockableOrOpened :: forall s. SingI s => Or Knockable ((:~:) Opened) s
knockableOrOpened =
case sing #s of
SOpened -> OrRight $ Refl
SClosed -> OrLeft KnockClosed
SLocked -> OrLeft KnockLocked
I am working from the following codebase: https://github.com/mstksg/inCode/blob/master/code-samples/singletons/Door3.hs
Type inference is the cause. This type contains s ...
refuteRefuteKnockable :: SingI s => Refuted (Refuted (Knockable s)) -> Knockable s
^^^^^^^^^^^
So, this
refuteRefuteKnockable rrK =
case isKnockable $ sing of
Proved k -> k
^^^
must have type Knockable s. Hence, the type of Proved k is inferred, probably containing s as well. That is the same type of isKnockable $ sing, from which we infer what type should be applied to sing (exploiting the signature of isKnockable). GHC does all of this for us.
In the latter example, we can't perform the same reasoning.
case sing of
SOpened -> OrRight $ Refl
SClosed -> OrLeft KnockClosed
SLocked -> OrLeft KnockLocked
is ambiguous because, even if the three branches must return a known type, we can still call sing on a different type then s and make everything typecheck. Since there isn't a unique s, inference can not work.
Note that above I had to guess a few things. If you shared the definitions of your types, we could be more accurate. (I.e., where is SOpened defined? What about Knockable, etc.?)

Why does Haskell's Monad implementation fail function result differ from error's result?

I am trying to understand monads and reading it's type class definition:
class Monad m where
.
.
.
fail :: String -> m a
fail msg = error msg
Now, the definition of error is:
error :: [Char] -> a
Shouldn't the type system complain in this case? as
a /= m a
Or does the type system automatically assume that the results from error will be transformed into
m a
somehow?
Thanks in advance
The as in fail's and error's type signatures are a type variables. We can rename them without changing their meaning, e.g.
error :: [Char] -> b
error :: [Char] -> c
error :: [Char] -> d
All those type signatures have the same meaning; we just used alpha conversion on the type level.
Now we set b ~ m a, where m is fixed by fail's context and we see that error can get used:
fail :: String -> m a
fail msg = error msg -- error :: String -> b
-- b ~ m a

Simple example for ImpredicativeTypes

The GHC user's guide describes the impredicative polymorphism extension with reference to the following example:
f :: Maybe (forall a. [a] -> [a]) -> Maybe ([Int], [Char])
f (Just g) = Just (g [3], g "hello")
f Nothing = Nothing
However, when I define this example in a file and try to call it, I get a type error:
ghci> f (Just reverse)
<interactive>:8:9:
Couldn't match expected type `forall a. [a] -> [a]'
with actual type `[a0] -> [a0]'
In the first argument of `Just', namely `reverse'
In the first argument of `f', namely `(Just reverse)'
In the expression: f (Just reverse)
ghci> f (Just id)
<interactive>:9:9:
Couldn't match expected type `forall a. [a] -> [a]'
with actual type `a0 -> a0'
In the first argument of `Just', namely `id'
In the first argument of `f', namely `(Just id)'
In the expression: f (Just id)
Seemingly only undefined, Nothing, or Just undefined satisfies the type-checker.
I have two questions, therefore:
Can the above function be called with Just f for any non-bottom f?
Can someone provide an example of a value only definable with impredicative polymorphism, and usable in a non-trivial way?
The latter is particularly with the HaskellWiki page on Impredicative Polymorphism in mind, which currently makes a decidedly unconvincing case for the existence of the extension.
Here's an example of how one project, const-math-ghc-plugin, uses ImpredicativeTypes to specify a list of matching rules.
The idea is that when we have an expression of the form App (PrimOp nameStr) (Lit litVal), we want to look up the appropriate rule based upon the primop name. A litVal will be either a MachFloat d or MachDouble d (d is a Rational). If we find a rule, we want to apply the function for that rule to d converted to the correct type.
The function mkUnaryCollapseIEEE does this for unary functions.
mkUnaryCollapseIEEE :: (forall a. RealFloat a => (a -> a))
-> Opts
-> CoreExpr
-> CoreM CoreExpr
mkUnaryCollapseIEEE fnE opts expr#(App f1 (App f2 (Lit lit)))
| isDHash f2, MachDouble d <- lit = e d mkDoubleLitDouble
| isFHash f2, MachFloat d <- lit = e d mkFloatLitFloat
where
e d = evalUnaryIEEE opts fnE f1 f2 d expr
The first argument needs to have a Rank-2 type, because it will be instantiated at either Float or Double depending on the literal constructor. The list of rules looks like this:
unarySubIEEE :: String -> (forall a. RealFloat a => a -> a) -> CMSub
unarySubIEEE nm fn = CMSub nm (mkUnaryCollapseIEEE fn)
subs =
[ unarySubIEEE "GHC.Float.exp" exp
, unarySubIEEE "GHC.Float.log" log
, unarySubIEEE "GHC.Float.sqrt" sqrt
-- lines omitted
, unarySubIEEE "GHC.Float.atanh" atanh
]
This is ok, if a bit too much boilerplate for my taste.
However, there's a similar function mkUnaryCollapsePrimIEEE. In this case, the rules are different for different GHC versions. If we want to support multiple GHCs, it gets a bit tricky. If we took the same approach, the subs definition would require a lot of CPP, which can be unmaintainable. Instead, we defined the rules in a separate file for each GHC version. However, mkUnaryCollapsePrimIEEE isn't available in those modules due to circular import issues. We could probably re-structure the modules to make it work, but instead we defined the rulesets as:
unaryPrimRules :: [(String, (forall a. RealFloat a => a -> a))]
unaryPrimRules =
[ ("GHC.Prim.expDouble#" , exp)
, ("GHC.Prim.logDouble#" , log)
-- lines omitted
, ("GHC.Prim.expFloat#" , exp)
, ("GHC.Prim.logFloat#" , log)
]
By using ImpredicativeTypes, we can keep a list of Rank-2 functions, ready to use for the first argument to mkUnaryCollapsePrimIEEE. The alternatives would be much more CPP/boilerplate, changing the module structure (or circular imports), or a lot of code duplication. None of which I would like.
I do seem to recall GHC HQ indicating that they would like to drop support for the extension, but perhaps they've reconsidered. It is quite useful at times.
Isn't it just that ImpredicativeTypes has been quietly dropped with the new typechecker in ghc-7+ ? Note that ideone.com still uses ghc-6.8 and indeed your program use to run fine :
{-# OPTIONS -fglasgow-exts #-}
f :: Maybe (forall a. [a] -> [a]) -> Maybe ([Int], [Char])
f (Just g) = Just (g [3], g "hello")
f Nothing = Nothing
main = print $ f (Just reverse)
prints Just ([3],"olleh") as expected; see http://ideone.com/KMASZy
augustss gives a handsome use case -- some sort of imitation Python dsl -- and a defense of the extension here: http://augustss.blogspot.com/2011/07/impredicative-polymorphism-use-case-in.html referred to in the ticket here http://hackage.haskell.org/trac/ghc/ticket/4295
Note this workaround:
justForF :: (forall a. [a] -> [a]) -> Maybe (forall a. [a] -> [a])
justForF = Just
ghci> f (justForF reverse)
Just ([3],"olleh")
Or this one (which is basically the same thing inlined):
ghci> f $ (Just :: (forall a. [a] -> [a]) -> Maybe (forall a. [a] -> [a])) reverse
Just ([3],"olleh")
Seems like the type inference has problems infering the type of the Just in your case and we have to tell it the type.
I have no clue if it's a bug or if there is a good reason for it.. :)

What to do with “Inferred type is less polymorphic than expected”?

I need the Numeric.FAD library, albeit still being completely puzzled by existential types.
This is the code:
error_diffs :: [Double] -> NetworkState [(Int, Int, Double)]
error_diffs desired_outputs = do diff_error <- (diff_op $ error' $ map FAD.lift desired_outputs)::(NetworkState ([FAD.Dual tag Double] -> FAD.Dual tag Double))
weights <- link_weights
let diffs = FAD.grad (diff_error::([FAD.Dual tag a] -> FAD.Dual tag b)) weights
links <- link_list
return $ zipWith (\link diff ->
(linkFrom link, linkTo link, diff)
) links diffs
error' runs in a Reader monad, ran by diff_op, which in turn generates an anonymous function to take the current NetworkState and the differential inputs from FAD.grad and stuffs them into the Reader.
Haskell confuses me with the following:
Inferred type is less polymorphic than expected
Quantified type variable `tag' is mentioned in the environment:
diff_error :: [FAD.Dual tag Double] -> FAD.Dual tag Double
(bound at Operations.hs:100:33)
In the first argument of `FAD.grad', namely
`(diff_error :: [FAD.Dual tag a] -> FAD.Dual tag b)'
In the expression:
FAD.grad (diff_error :: [FAD.Dual tag a] -> FAD.Dual tag b) weights
In the definition of `diffs':
diffs = FAD.grad
(diff_error :: [FAD.Dual tag a] -> FAD.Dual tag b) weights
this code gives the same error as you get:
test :: Int
test =
(res :: Num a => a)
where
res = 5
The compiler figured that res is always of type Int and is bothered that for some reason you think res is polymorphic.
this code, however, works fine:
test :: Int
test =
res
where
res :: Num a => a
res = 5
here too, res is defined as polymorphic but only ever used as Int. the compiler is only bothered when you type nested expressions this way. in this case res could be reused and maybe one of those uses will not use it as Int, in contrast to when you type a nested expression, which cannot be reused by itself.
If I write,
bigNumber :: (Num a) => a
bigNumber = product [1..100]
then when bigNumber :: Int is evaluated,
it's evaluating (product :: [Int] -> Int) [(1 :: Int) .. (100 :: Int)],
and when bigNumber :: Integer is evaluated,
it's evaluating (product :: [Integer] -> Integer) [(1 :: Integer) .. (100 :: Integer)].
Nothing is shared between the two.
error_diffs has a single type, that is: [Double] -> NetworkState [(Int, Int, Double)]. It must evaluate in exactly one way.
However, what you have inside:
... :: NetworkState ([FAD.Dual tag Double] -> FAD.Dual tag Double)
can be evaluated in different ways, depending on what tag is.
See the problem?

Resources