here is a reduced program that still segfaults:<div><br></div><div><div>{-# LANGUAGE Arrows #-}</div><div><br></div><div>import Control.Arrow</div><div><br></div><div>main :: IO ()</div><div>main = print segfault</div><div>
<br></div><div>segfault :: [()]</div><div>segfault = anythingYouWant ()</div><div><br></div><div>anythingYouWant :: a</div><div>anythingYouWant = testB False (const ()) ()</div><div><br></div><div>testB :: ArrowChoice arrow </div>
<div>      =&gt; bool -&gt; arrow () () -&gt; arrow () anything</div><div>testB bool arrow =</div><div>  proc () -&gt;</div><div>    do if bool then arrow -&lt; ()</div><div>               else arrow -&lt; ()</div><div><br>
</div><div>Sebastian</div><div><br></div><div class="gmail_quote">On Fri, Aug 5, 2011 at 6:20 AM, Brent Yorgey <span dir="ltr">&lt;<a href="mailto:byorgey@seas.upenn.edu">byorgey@seas.upenn.edu</a>&gt;</span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex;">
<div class="im">On Tue, Aug 02, 2011 at 05:08:33PM -0400, bob zhang wrote:<br>
&gt; hi, all<br>
&gt; testB :: (ArrowChoice t1, Num a1, Num a) =&gt; (a -&gt; a1 -&gt; t2) -&gt; t1 a t3<br>
&gt; -&gt; t1 a1 t3 -&gt; t1 (a, a1) t<br>
&gt; testB f g h = proc (x,y) -&gt; do<br>
&gt; if (f x y)then g -&lt; x + 1 else h -&lt; y + 2<br>
&gt;<br>
&gt; it&#39;s very strange that the type of _f_ is (a-&gt;a1-&gt;t2) which I thought<br>
&gt; should be a -&gt; a1 -&gt; Bool,<br>
&gt;<br>
&gt; btw, is there any way to get the output of preprocessing using -XArrow<br>
&gt; extensions,<br>
&gt;<br>
&gt; Thanks a lot<br>
&gt; best, bob<br>
<br>
</div>Congratulations, you have definitely found a GHC bug!  Note there are<br>
actually two things wrong with testB&#39;s type signature: first, t2 ought<br>
to be Bool, as you note.  But even worse, notice that the return type<br>
of the result arrow, t, has nothing to do with any of the other types!<br>
This means that we can use testB along with the (-&gt;) instance for<br>
Arrow to construct elements of arbitrary types:<br>
<br>
  ghci&gt; let anythingYouWant = testB (\x y -&gt; False) (const 3) (const 2) (2,2)<br>
  ghci&gt; :t anythingYouWant<br>
  anythingYouWant :: t<br>
  ghci&gt; anythingYouWant :: Integer<br>
  2<br>
  ghci&gt; anythingYouWant :: Int<br>
  2<br>
  ghci&gt; anythingYouWant :: Double<br>
  1.0e-323<br>
  ghci&gt; anythingYouWant :: Char<br>
  &#39;\STX&#39;<br>
  ghci&gt; (anythingYouWant :: (Double -&gt; Double) -&gt; [Double]) sqrt<br>
  [<br>
  [1]    17391 segmentation fault  ghci<br>
<br>
whoops!<br>
<br>
I&#39;m using GHC 7.0.3, but Daniel Wagner and I also tried it (with the<br>
same results) on GHC 7.2.0rc1 and GHC HEAD.<br>
<br>
I wasn&#39;t able to find a ticket for this on the GHC bug tracker, I<br>
guess we should file one!<br>
<br>
I tried to find a way to get the output of preprocessing using -XArrow<br>
but wasn&#39;t able to find one (other than -ddump-ds which gives you the<br>
unoptimized *GHC core* output, which is quite hard to read).<br>
<font color="#888888"><br>
-Brent<br>
</font><div><div></div><div class="h5"><br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</div></div></blockquote></div><br></div>