oh, btw I am using GHC 6.10.1 (on Linux x86_64)<br><br><div class="gmail_quote">2008/12/18 Cetin Sert <span dir="ltr">&lt;<a href="mailto:cetin.sert@gmail.com">cetin.sert@gmail.com</a>&gt;</span><br><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">
<div><div></div><div class="Wj3C7c">Hi,<br><br>I tested the following, why does the rewrite rules not fire
when using tuples also in testRewrite2, testRewriteReverse2? compiling:
<span style="font-family: courier new,monospace;">rm *.o; ghc -fglasgow-exts -ddump-simpl-stats -O9 --make rules.hs</span><br>
<br><span style="font-family: courier new,monospace;">module Main where</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">main :: IO ()</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">main = do</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; print $ test&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; 0</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; print $ test2&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; 0</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; print $ testRewrite&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; 0</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; print $ testRewriteReverse&nbsp; 0</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; print $ testRewrite2&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; 0</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; print $ testRewriteReverse2 0</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">test :: a → Bool</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">test x = pi</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; f&nbsp; = replicate 2000 x</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; i&nbsp; = repeat&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; x</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pf = lenGT f 300</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pi = lenGT i 300</span><br style="font-family: courier new,monospace;">


<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">test2 :: a → (Bool,Bool)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">test2 x = (pf,pi)</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; f&nbsp; = replicate 2000 x</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; i&nbsp; = repeat&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; x</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pf = lenGT f 300</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pi = lenGT i 300</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">testRewrite :: a → Bool</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">testRewrite x = pi</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; f&nbsp; = replicate 2000 x</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; i&nbsp; = repeat&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; x</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; lf = length f</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; li = length i</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pf = lf &gt; 300</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pi = li &gt; 300</span><br style="font-family: courier new,monospace;">


<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">testRewriteReverse :: a → Bool</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">testRewriteReverse x = pi</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; f&nbsp; = replicate 2000 x</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; i&nbsp; = repeat&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; x</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; lf = length f</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; li = length i</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pf = 300 &lt;= lf</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pi = 300 &lt;= li</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">testRewrite2 :: a → (Bool,Bool)</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">testRewrite2 x = (pf,pi)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; f&nbsp; = replicate 2000 x</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; i&nbsp; = repeat&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; x</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; lf = length f</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; li = length i</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pf = lf &gt; 300</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pi = li &gt; 300</span><br style="font-family: courier new,monospace;">


<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">testRewriteReverse2 :: a → (Bool,Bool)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">testRewriteReverse2 x = (pf,pi)</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; f&nbsp; = replicate 2000 x</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; i&nbsp; = repeat&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; x</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; lf = length f</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; li = length i</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pf = 300 &lt;= lf</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; pi = 300 &lt;= li</span></div></div><div><br style="font-family: courier new,monospace;"><div class="Ih2E3d"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">lengthOP v (⊜) []&nbsp; n = 0 ⊜ n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lengthOP v (⊜) xxs n = co xxs 0</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;"></div></div><div class="Ih2E3d"><div><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; co (_:xs) c | n &gt; c&nbsp;&nbsp;&nbsp;&nbsp; = co xs (c+1)</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; | otherwise = v</span><br style="font-family: courier new,monospace;"></div></div><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; co []&nbsp;&nbsp;&nbsp;&nbsp; c = c ⊜ n</span><div class="Ih2E3d">
<div>
<br style="font-family: courier new,monospace;">
<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lenEQ = lengthOP False (==)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lenLT = lengthOP False (&lt;)</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">lenLE = lengthOP False (&lt;=)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lenGT = lengthOP True&nbsp; (&gt;)</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">lenGE = lengthOP True&nbsp; (&gt;=)</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">{-# RULES</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">-- | length</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenEQ_LHS&quot; forall xs n.&nbsp; (length xs) == n = lenEQ xs n</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&quot;lenLT_LHS&quot; forall xs n.&nbsp; (length xs) &lt;&nbsp; n = lenLT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenLE_LHS&quot; forall xs n.&nbsp; (length xs) &lt;= n = lenLE xs n</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&quot;lenGT_LHS&quot; forall xs n.&nbsp; (length xs) &gt;&nbsp; n = lenGT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenGE_LHS&quot; forall xs n.&nbsp; (length xs) &gt;= n = lenGE xs n</span><br style="font-family: courier new,monospace;">


<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenEQ_RHS&quot; forall xs n.&nbsp; n == (length xs) = lenEQ xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenLT_RHS&quot; forall xs n.&nbsp; n &lt;&nbsp; (length xs) = lenGE xs n</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&quot;lenLE_RHS&quot; forall xs n.&nbsp; n &lt;= (length xs) = lenGT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenGT_RHS&quot; forall xs n.&nbsp; n &gt;&nbsp; (length xs) = lenLE xs n</span><br style="font-family: courier new,monospace;">


<span style="font-family: courier new,monospace;">&quot;lenGE_RHS&quot; forall xs n.&nbsp; n &gt;= (length xs) = lenLT xs n</span><br style="font-family: courier new,monospace;"></div></div><span style="font-family: courier new,monospace;">&nbsp; #-}</span><br>


<br>Best Regards,<br>Cetin Sert<br><br><div class="gmail_quote"><div class="Ih2E3d">2008/12/18 Luke Palmer <span dir="ltr">&lt;<a href="mailto:lrpalmer@gmail.com" target="_blank">lrpalmer@gmail.com</a>&gt;</span><br></div>
<blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;">
This does not answer your question, but you can solve this problem without rewrite rules by having length return a lazy natural:<div><div></div><div class="Wj3C7c"><br><br>&nbsp;&nbsp; data Nat = Zero | Succ Nat<br><br>And defining lazy comparison operators on it.<br>


<br>Of course you cannot replace usages of Prelude.length.&nbsp; But I am really not in favor of rules which change semantics, even if they only make things less strict.&nbsp; My argument is the following.&nbsp; I may come to rely on such nonstrictness as in:<br>


<br>&nbsp; bad xs = (length xs &gt; 10, length xs &gt; 20)<br><br>bad [1..] will return (True,True).&nbsp; However, if I do an obviously semantics-preserving refactor:<br><br>&nbsp; bad xs = (l &gt; 10, l &gt; 20)<br>&nbsp; where<br>&nbsp; l = length xs<br>


<br>My semantics are not preserved: bad [1..] = (_|_, _|_)&nbsp;&nbsp; (if/unless the compiler is clever, in which case my semantics depend on the compiler&#39;s cleverness which is even worse)<br><br>Luke<br><br>2008/12/18 Cetin Sert <span dir="ltr">&lt;<a href="mailto:cetin.sert@gmail.com" target="_blank">cetin.sert@gmail.com</a>&gt;</span><br>


<div class="gmail_quote"><blockquote class="gmail_quote" style="border-left: 1px solid rgb(204, 204, 204); margin: 0pt 0pt 0pt 0.8ex; padding-left: 1ex;"><div><div></div><div>Hi *^o^*,<br><br>With the following rewrite rules:<br>

<br><span style="font-family: courier new,monospace;">lengthOP :: (Num a, Ord a) ⇒ Bool → (a → a → Bool) → [b] → a → Bool</span><br style="font-family: courier new,monospace;">

<span style="font-family: courier new,monospace;">lengthOP v (⊜) []&nbsp; n = 0 ⊜ n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lengthOP v (⊜) xxs n = co xxs 0</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp; where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; co []&nbsp;&nbsp;&nbsp;&nbsp; c = c ⊜ n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; co (_:xs) c | n &gt; c&nbsp;&nbsp;&nbsp;&nbsp; = co xs (c+1)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; | otherwise = v</span><br style="font-family: courier new,monospace;">



<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lenEQ = lengthOP False (==)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lenLT = lengthOP False (&lt;)</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">lenLE = lengthOP False (&lt;=)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">lenGT = lengthOP True&nbsp; (&gt;)</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">lenGE = lengthOP True&nbsp; (&gt;=)</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">{-# RULES</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">-- | length</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenEQ_LHS&quot; forall xs n.&nbsp; (length xs) == n = lenEQ xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;lenLT_LHS&quot; forall xs n.&nbsp; (length xs) &lt;&nbsp; n = lenLT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenLE_LHS&quot; forall xs n.&nbsp; (length xs) &lt;= n = lenLE xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;lenGT_LHS&quot; forall xs n.&nbsp; (length xs) &gt;&nbsp; n = lenGT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenGE_LHS&quot; forall xs n.&nbsp; (length xs) &gt;= n = lenGE xs n</span><br style="font-family: courier new,monospace;">



<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenEQ_RHS&quot; forall xs n.&nbsp; n == (length xs) = lenEQ xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenLT_RHS&quot; forall xs n.&nbsp; n &lt;&nbsp; (length xs) = lenGE xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;lenLE_RHS&quot; forall xs n.&nbsp; n &lt;= (length xs) = lenGT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;lenGT_RHS&quot; forall xs n.&nbsp; n &gt;&nbsp; (length xs) = lenLE xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;lenGE_RHS&quot; forall xs n.&nbsp; n &gt;= (length xs) = lenLT xs n</span><br style="font-family: courier new,monospace;"><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">-- | genericLength</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;glenEQ_LHS&quot; forall xs n.&nbsp; (genericLength xs) == n = lenEQ xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;glenLT_LHS&quot; forall xs n.&nbsp; (genericLength xs) &lt;&nbsp; n = lenLT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;glenLE_LHS&quot; forall xs n.&nbsp; (genericLength xs) &lt;= n = lenLE xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;glenGT_LHS&quot; forall xs n.&nbsp; (genericLength xs) &gt;&nbsp; n = lenGT xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;glenGE_LHS&quot; forall xs n.&nbsp; (genericLength xs) &gt;= n = lenGE xs n</span><br style="font-family: courier new,monospace;">



<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;glenEQ_RHS&quot; forall xs n.&nbsp; n == (genericLength xs) = lenEQ xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;glenLT_RHS&quot; forall xs n.&nbsp; n &lt;&nbsp; (genericLength xs) = lenGE xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;glenLE_RHS&quot; forall xs n.&nbsp; n &lt;= (genericLength xs) = lenGT xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&quot;glenGT_RHS&quot; forall xs n.&nbsp; n &gt;&nbsp; (genericLength xs) = lenLE xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&quot;glenGE_RHS&quot; forall xs n.&nbsp; n &gt;= (genericLength xs) = lenLT xs n</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp; #-}</span><br style="font-family: courier new,monospace;"><br>1) Is there a way to tell where &#39;length&#39; is mentioned, what is meant is for example &#39;Prelude.length&#39; or any length that works on lists?<br>



2) How can I avoid the following error messages?<br><br><span style="font-family: courier new,monospace;">module Main where</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">import Data.List</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">main :: IO Int</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; print $ length (repeat 0) &gt; 200</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp; print $ 200 &lt; length (repeat 0)</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; print $ genericLength (repeat 0) &gt; 200</span><span style="font-family: courier new,monospace;"> -- error</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp; print $ 200 &lt; genericLength (repeat 0) -- error</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp; return 0</span><br style="font-family: courier new,monospace;">



<br>########:<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; Could not deduce (Ord i) from the context (Eq i, Num i)</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; arising from a use of `lenEQ&#39; at </span>########<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; Possible fix: add (Ord i) to the context of the RULE &quot;glenEQ_LHS&quot;</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; In the expression: lenEQ xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; When checking the transformation rule &quot;glenEQ_LHS&quot;</span><br style="font-family: courier new,monospace;">



<br style="font-family: courier new,monospace;">########<span style="font-family: courier new,monospace;">:</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; Could not deduce (Ord a) from the context (Eq a, Num a)</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; arising from a use of `lenEQ&#39; at </span>########<br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; Possible fix: add (Ord a) to the context of the RULE &quot;glenEQ_RHS&quot;</span><br style="font-family: courier new,monospace;">



<span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; In the expression: lenEQ xs n</span><br style="font-family: courier new,monospace;"><span style="font-family: courier new,monospace;">&nbsp;&nbsp;&nbsp; When checking the transformation rule &quot;glenEQ_RHS&quot;</span><br style="font-family: courier new,monospace;">



<br>3) What speaks for/against broad usage of such rewrite rules involving list lengths?<br><br>Best Regards,<br><font color="#888888">Cetin Sert<br>
</font><br></div></div>_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org" target="_blank">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>
<br></blockquote></div><br>
</div></div></blockquote></div><br>
</blockquote></div><br>