<html>
<head>
<meta http-equiv="Content-Type" content="text/html; charset=us-ascii">
<meta name="Generator" content="Microsoft Exchange Server">
<!-- converted from text --><style><!-- .EmailQuote { margin-left: 1pt; padding-left: 4pt; border-left: #800000 2px solid; } --></style>
</head>
<body>
<div>
<div>I feel so unbelievably ignorant now. I thought with all the IORefs in the type checking process that zonking did this in these refs. Somehow I started thinking that some of these remained in SDocs, not thinking showSDoc is pure and results in a String,
 which holds no IORefs.</div>
<div><br>
</div>
<div>Does this mean that for the idType to come out correctly I should also zonk (AND BIND) the Id-value I return?</div>
<div><br>
</div>
<div>Ph.</div>
<div><br>
</div>
<div><br>
</div>
<div><br>
</div>
<div><br>
</div>
<div>
<div style="font-size:75%; color:#575757">Sent from Samsung Mobile</div>
</div>
<br>
<br>
<br>
-------- Original message --------<br>
From: Simon Peyton-Jones &lt;simonpj@microsoft.com&gt; <br>
Date: 30/08/2013 18:25 (GMT&#43;01:00) <br>
To: &quot;Holzenspies, P.K.F. (EWI)&quot; &lt;p.k.f.holzenspies@utwente.nl&gt;,glasgow-haskell-users@haskell.org
<br>
Subject: RE: Question about correct GHC-API use for type checking (or zonking, or tidying)
<br>
<br>
<br>
</div>
<font size="2"><span style="font-size:10pt;">
<div class="PlainText">Haskell is a *functional* language.&nbsp; Consider<br>
<br>
&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; pre-zonk:&nbsp; &quot; &#43;&#43; pp all_expr_ty<br>
&nbsp;&nbsp;&nbsp; zonkTcType all_expr_ty<br>
&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; post-zonk: &quot; &#43;&#43; pp all_expr_ty<br>
<br>
pp is a pure function; it is given the same input both times, so of course it produces the same output.<br>
<br>
If you collect the result of zonkTcType you might have better luck, thus:<br>
<br>
&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; pre-zonk:&nbsp; &quot; &#43;&#43; pp all_expr_ty<br>
&nbsp;&nbsp;&nbsp; zonked_expr_ty &lt;- zonkTcType all_expr_ty<br>
&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; post-zonk: &quot; &#43;&#43; pp zonked_expr_ty<br>
<br>
Zonking walks over a type, returning a new type in which unification variables are replaced by the types they unified to.<br>
<br>
Hope this helps<br>
<br>
Simon<br>
<br>
| -----Original Message-----<br>
| From: Glasgow-haskell-users [<a href=""></a>mailto:glasgow-haskell-users-<br>
| bounces@haskell.org] On Behalf Of p.k.f.holzenspies@utwente.nl<br>
| Sent: 29 August 2013 14:42<br>
| To: glasgow-haskell-users@haskell.org<br>
| Subject: Question about correct GHC-API use for type checking (or<br>
| zonking, or tidying)<br>
| <br>
| Dear GHC-ers,<br>
| <br>
| I'm working on building an interactive environment around the<br>
| composition of expressions. Users can type in (i.e. give strings of)<br>
| expressions and can then use these expressions to produce other<br>
| expressions. I'm close to having a working GHC-API binding for this. The<br>
| resulting types, however, still contain some things I don't quite<br>
| understand. Any help would be appreciated.<br>
| <br>
| Below, I've included the function exprFromString which should parse,<br>
| rename and typecheck strings to Id-things and give their type (although,<br>
| ideally, the idType of said Id-thing should be the same as the type<br>
| returned). This function lives in the IA (InterActive) monad; a monad<br>
| that is a GhcMonad and can lift monadic computations in TcM into itself<br>
| using liftTcM (which uses the initTcPrintErrors and<br>
| setInteractiveContext functions similarly to TcRnDriver.tcRnExpr).<br>
| <br>
| Near the end of the function, debugging output is produced. This output<br>
| confuses me slightly. Here is the output for the three inputs &quot;map (&#43;1)<br>
| [1..10]&quot;, &quot;5&quot; and &quot;\\x -&gt; x&quot;:<br>
| <br>
| <br>
| map (&#43;1) [1..10]<br>
|&nbsp;&nbsp; pre-zonk:&nbsp; forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) =&gt; [b_i]<br>
|&nbsp;&nbsp; post-zonk: forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) =&gt; [b_i]<br>
|&nbsp;&nbsp; idType:&nbsp;&nbsp;&nbsp; [b_c]<br>
|&nbsp;&nbsp; tidied:&nbsp;&nbsp;&nbsp; forall b. (GHC.Enum.Enum b_i, GHC.Num.Num b_i) =&gt; [b_i]<br>
| 5<br>
|&nbsp;&nbsp; pre-zonk:&nbsp; forall a. GHC.Num.Num a_d =&gt; t_c<br>
|&nbsp;&nbsp; post-zonk: forall a. GHC.Num.Num a_d =&gt; t_c<br>
|&nbsp;&nbsp; idType:&nbsp;&nbsp;&nbsp; a_b<br>
|&nbsp;&nbsp; tidied:&nbsp;&nbsp;&nbsp; forall a. GHC.Num.Num a_d =&gt; t_c<br>
| \x -&gt; x<br>
|&nbsp;&nbsp; pre-zonk:&nbsp; forall t. t_e<br>
|&nbsp;&nbsp; post-zonk: forall t. t_e<br>
|&nbsp;&nbsp; idType:&nbsp;&nbsp;&nbsp; forall t. t -&gt; t<br>
|&nbsp;&nbsp; tidied:&nbsp;&nbsp;&nbsp; forall t. t_e<br>
| <br>
| <br>
| The zonking and tidying part of the type-checking process are still a<br>
| bit unclear to me and I suspect the problems arise there. It looks to me<br>
| that the type variables in the quantifications are different ones from<br>
| those in the pi/rho-types. I had expected the types to only contain the<br>
| variables over which they are quantified, so e.g. in the map-example, I<br>
| had expected &quot;forall b . (GHC.Enum.Enum b, GHC.Num.Num b) =&gt; [b]&quot;<br>
| <br>
| Can anyone explain what I'm missing?<br>
| <br>
| Regards,<br>
| Philip<br>
| <br>
| <br>
| <br>
| <br>
| <br>
| exprFromString :: String -&gt; IA (Id,Type)<br>
| exprFromString str = do<br>
|&nbsp;&nbsp; dfs &lt;- getDynFlags<br>
|&nbsp;&nbsp; let pp&nbsp; = showSDoc dfs . ppr<br>
|&nbsp;&nbsp; pst &lt;- mkPState dfs buf &lt;$&gt; newRealSrcLoc<br>
| <br>
| {- Parse -}<br>
|&nbsp;&nbsp; (loc,rdr_expr) &lt;- case unP parseStmt pst of<br>
|&nbsp;&nbsp;&nbsp;&nbsp; PFailed span err -&gt; throwOneError (mkPlainErrMsg dfs span err)<br>
|&nbsp;&nbsp;&nbsp;&nbsp; POk pst' (Just (L l (ExprStmt rdr_expr _ _ _))) -&gt; do<br>
|&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; logWarningsReportErrors (getMessages pst')<br>
|&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; return (l,rdr_expr)<br>
|&nbsp;&nbsp;&nbsp;&nbsp; POk pst' thing -&gt; throw $ maybe EmptyParse (const<br>
| NonExpressionParse) thing<br>
|&nbsp;&nbsp; liftTcM $ do<br>
|&nbsp;&nbsp;&nbsp;&nbsp; fresh_it &lt;- freshName loc str<br>
| <br>
| {- Rename -}<br>
|&nbsp;&nbsp;&nbsp;&nbsp; (rn_expr, fvs) &lt;- checkNoErrs $ rnLExpr rdr_expr<br>
| <br>
| {- Typecheck -}<br>
|&nbsp;&nbsp;&nbsp;&nbsp; let binds = mkBinds fresh_it rn_expr fvs<br>
| <br>
|&nbsp;&nbsp;&nbsp;&nbsp; (((_bnds,((_tc_expr,res_ty),id)),untch),lie) &lt;- captureConstraints .<br>
| captureUntouchables $<br>
|&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; tcLocalBinds binds ((,) &lt;$&gt; tcInferRho rn_expr &lt;*&gt; tcLookupId<br>
| fresh_it)<br>
|&nbsp;&nbsp;&nbsp;&nbsp; ((qtvs, dicts, _bool, _evbinds), lie_top) &lt;- captureConstraints $<br>
|&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; simplifyInfer True False [(fresh_it, res_ty)] (untch,lie)<br>
| <br>
|&nbsp;&nbsp;&nbsp;&nbsp; let all_expr_ty = mkForAllTys qtvs (mkPiTypes dicts res_ty)<br>
|&nbsp;&nbsp;&nbsp;&nbsp; say str<br>
|&nbsp;&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; pre-zonk:&nbsp; &quot; &#43;&#43; pp all_expr_ty<br>
|&nbsp;&nbsp;&nbsp;&nbsp; zonkTcType all_expr_ty<br>
|&nbsp;&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; post-zonk: &quot; &#43;&#43; pp all_expr_ty<br>
|&nbsp;&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; idType:&nbsp;&nbsp;&nbsp; &quot; &#43;&#43; pp (idType id)<br>
|&nbsp;&nbsp;&nbsp;&nbsp; say $ &quot;&nbsp; tidied:&nbsp;&nbsp;&nbsp; &quot; &#43;&#43; pp (tidyTopType all_expr_ty)<br>
| <br>
|&nbsp;&nbsp;&nbsp;&nbsp; return (id,all_expr_ty)<br>
|&nbsp;&nbsp; where<br>
|&nbsp;&nbsp; say = liftIO . putStrLn<br>
|&nbsp;&nbsp; buf = stringToStringBuffer str<br>
|&nbsp;&nbsp; freshName loc str = (\u -&gt; mkInternalName u name loc) &lt;$&gt; newUnique<br>
|&nbsp;&nbsp;&nbsp;&nbsp; where<br>
|&nbsp;&nbsp;&nbsp;&nbsp; name = mkOccNameFS varName $ fsLit $ &quot;it&quot; &#43;&#43; show (lineOf loc)<br>
|&nbsp;&nbsp;&nbsp;&nbsp; isVarChar c = isAlphaNum c || c == '_' || c == '\''<br>
|&nbsp;&nbsp;&nbsp;&nbsp; lineOf (RealSrcSpan s) = srcSpanStartLine s<br>
|&nbsp;&nbsp;&nbsp;&nbsp; lineOf _ = -1<br>
| <br>
|&nbsp;&nbsp; mkBinds :: Name -&gt; LHsExpr Name -&gt; FreeVars -&gt; HsLocalBinds Name<br>
|&nbsp;&nbsp; mkBinds nm e@(L l _) fvs = HsValBinds $ ValBindsOut [(NonRecursive,<br>
| unitBag the_bind)] []<br>
|&nbsp;&nbsp;&nbsp;&nbsp; where<br>
|&nbsp;&nbsp;&nbsp;&nbsp; the_bind = L l (mkTopFunBind (L l nm) [mkMatch [] e<br>
| emptyLocalBinds]) { bind_fvs = fvs }<br>
| <br>
| <br>
| <br>
| _______________________________________________<br>
| Glasgow-haskell-users mailing list<br>
| Glasgow-haskell-users@haskell.org<br>
| <a href="http://www.haskell.org/mailman/listinfo/glasgow-haskell-users">http://www.haskell.org/mailman/listinfo/glasgow-haskell-users</a><br>
</div>
</span></font>
</body>
</html>