Re: Rewrite rules involving LHS lambda?

2017-12-03 Thread Emil Axelsson
Den 2017-12-02 kl. 21:56, skrev Joachim Breitner: With a wee bit of higher-order matching, one might make `u` and `v` functions and instead write: foo (\ x -> fmap (u x) (v x)) = bar u v In that case I'd expect `u` and `v` to be synthesized rather than literally matched. For instance, `foo

Re: Rewrite rules involving LHS lambda?

2017-12-02 Thread Joachim Breitner
Hi, Am Samstag, den 02.12.2017, 12:59 -0800 schrieb Conal Elliott: > Thanks for the reply, Ed. > > > I'd assume that `x` didn't occur in either `u` or `v` > > This is exactly the issue I'm wondering about. Since rewrite rules > admit lambdas and only first-order matching,

Re: Rewrite rules involving LHS lambda?

2017-12-02 Thread Conal Elliott
Thanks for the reply, Ed. > I'd assume that `x` didn't occur in either `u` or `v` This is exactly the issue I'm wondering about. Since rewrite rules admit lambdas and only first-order matching, I'm wondering whether they're interpreted as you did (and I'd tend to), namely that `x` doesn't oc

Re: Rewrite rules involving LHS lambda?

2017-12-02 Thread Edward Kmett
examples of rewrite rules involving > a LHS lambda? Since rule matching is first-order, I'm wondering how terms > with lambda are matched on the LHS and substituted into on the RHS. For > instance, I want to restructure a lambda term as follows: > > > foo (\ x -> fmap u v) =

Rewrite rules involving LHS lambda?

2017-12-02 Thread Conal Elliott
Is there a written explanation and/or examples of rewrite rules involving a LHS lambda? Since rule matching is first-order, I'm wondering how terms with lambda are matched on the LHS and substituted into on the RHS. For instance, I want to restructure a lambda term as follows: > foo (\ x ->

Re: Rewrite rules

2017-01-16 Thread David Feuer
d track > down any instances of failed rewriting that you learn about. > > You might also be able to set up your code so that it fails (at > runtime, with error) if the desired rules did not fire. This would be > nicer if we had https://ghc.haskell.org/trac/ghc/ticket/9180. > > You

Re: Rewrite rules

2017-01-16 Thread Erik de Castro Lopo
nd then hope for the best. And track > down any instances of failed rewriting that you learn about. > > You might also be able to set up your code so that it fails (at > runtime, with error) if the desired rules did not fire. This would be > nicer if we had https://ghc.haskell.org/trac/ghc/tic

Re: Rewrite rules

2017-01-13 Thread Joachim Breitner
write a library that includes rewrite rules, how can I ensure > that they fire in client code that someone else writes? What > guarantees (however loose) are there? very little. The best one can do right now is to know enough about Core and the inliner to predict when things are going to be in

Re: Rewrite rules

2017-01-13 Thread Erik de Castro Lopo
Michael Snoyman wrote: > Could be I'm misunderstanding, but are you looking for -ddump-rule-firings? Wasn't aware of that, but my question was a little more general. If I write a library that includes rewrite rules, how can I ensure that they fire in client code that someone else writes? W

Re: Rewrite rules

2017-01-12 Thread Michael Snoyman
Could be I'm misunderstanding, but are you looking for -ddump-rule-firings? On Thu, Jan 12, 2017 at 10:46 AM, Erik de Castro Lopo <mle...@mega-nerd.com> wrote: > HI all, > > I'm having an look at rewrite rules, but something bugs me a little. > How do I tell if my rewrit

RE: GHC rewrite rules for class operations & laws

2017-01-04 Thread Ben Gamari
Welcome back, Simon! Simon Peyton Jones writes: > | Indeed, we could eliminate several hundred lines of boilerplate in GHC if > we > | could lift this restriction. > > Can you be more specific? Which hundreds of lines? > In particular the bindings in Data.Int and

RE: GHC rewrite rules for class operations & laws

2017-01-04 Thread Simon Peyton Jones via Glasgow-haskell-users
[mailto:b...@smart-cactus.org] | Sent: 29 December 2016 14:50 | To: Conal Elliott <co...@conal.net>; George Colpitts | <george.colpi...@gmail.com> | Cc: glasgow-haskell-users@haskell.org; Simon Peyton Jones | <simo...@microsoft.com> | Subject: Re: GHC rewrite rules for class

Re: GHC rewrite rules for class operations & laws

2016-12-30 Thread George Colpitts
to serve as a > conversation anchor until the issues and path forward are clearer. From my > perspective, class methods are among the most natural and useful candidates > for rewrite rules, since they tend to have associated laws, many (but not > all) of which are helpful in optimization. T

Re: GHC rewrite rules for class operations & laws

2016-12-29 Thread Ben Gamari
and useful candidates for >rewrite >rules, since they tend to have associated laws, many (but not all) of >which >are helpful in optimization. The alternative I know (and am using) is >fairly inconvenient: replicating entire APIs just in order to delay >inlining long enough to ap

Re: GHC rewrite rules for class operations & laws

2016-12-28 Thread Conal Elliott
Hi, George. Yes, please do add a task, hopefully to serve as a conversation anchor until the issues and path forward are clearer. From my perspective, class methods are among the most natural and useful candidates for rewrite rules, since they tend to have associated laws, many (but not all

Re: GHC rewrite rules for class operations & laws

2016-12-11 Thread George Colpitts
Do you want me to add a task ticket to remove this restriction that rewrite rules can't be used for class methods? On Tue, Nov 22, 2016 at 8:06 AM Simon Peyton Jones via Glasgow-haskell-users <glasgow-haskell-users@haskell.org> wrote: > Conal > > > > Is it possible to ap

Re: GHC rewrite rules for class operations & laws

2016-11-24 Thread Conal Elliott
Thanks, Simon. For now, I've added a module with aliases for all of my class methods and law-based rewrite rules in terms of those aliases. - Conal On Tue, Nov 22, 2016 at 4:06 AM, Simon Peyton Jones <simo...@microsoft.com> wrote: > Conal > > > > Is it possible to ap

RE: GHC rewrite rules for class operations & laws

2016-11-22 Thread Simon Peyton Jones via Glasgow-haskell-users
Conal Is it possible to apply GHC rewrite rules to class methods? Not currently. See https://ghc.haskell.org/trac/ghc/ticket/11688, esp comment:7 which gives links to similar examples. https://ghc.haskell.org/trac/ghc/ticket/10528 comment:13 gives more background. It’d be great if someone

Re: GHC rewrite rules for class operations & laws

2016-11-17 Thread David Feuer
The containers package uses the awkward double name approach. See, for example, the way that Data.Map and Data.Sequence fuse (indexed) maps and indexed) traversals. I know that Edward Kmett is very much opposed to class-based rules as found in Control.Arrow because non-law-abiding instances

GHC rewrite rules for class operations & laws

2016-11-17 Thread Conal Elliott
Is it possible to apply GHC rewrite rules to class methods? From what I’ve read and seen, class methods get eliminated early by automatically-generated rules. Is there really no way to postpone such inlining until a later simplifier stage? The GHC Users Guide docs say no <ht

Re: Rules for class methods and Safe Haskell

2014-11-13 Thread Wolfgang Jeltsch
Am Freitag, den 15.08.2014, 23:10 +0300 schrieb Wolfgang Jeltsch: Hi, the module Control.Arrow declares a set of rules for the Arrow class. It is marked “Trustworthy”, probably to allow these rules to actually fire. Now these rules are only correct for class instances that actually

Re: Rules for class methods and Safe Haskell

2014-11-13 Thread David Feuer
That's an interesting question. I'm not even close to an expert, but I *think* that parametricity prevents those particular rules from breaking Safe Haskell guarantees. The laws may not *hold* for a broken instance, but I don't *think* that lets you break type safety or IO encapsulation. On Nov 13

Rules for class methods and Safe Haskell

2014-08-15 Thread Wolfgang Jeltsch
Hi, the module Control.Arrow declares a set of rules for the Arrow class. It is marked “Trustworthy”, probably to allow these rules to actually fire. Now these rules are only correct for class instances that actually satisfy the arrow laws. If the author of another module defines an instance

RE: GHC rewrite rules and constructor wrappers?

2014-05-06 Thread Simon Peyton Jones
, but it might be. The usual solution to the interaction between RULES and inlining is to delay inlining until the rule has had a chance to fire. But in this case the inlining isn’t under your control: it’s the wrapper for MkT. Something very similar happens for the wrappers after strictness analysis

GHC rewrite rules and constructor wrappers?

2014-04-29 Thread Conal Elliott
I'm trying to sort out the relationship of GHC rewrite rules and constructor wrappers. I have rules like reify/(:) reifyEP (:) = kPrim VecSP This rule seems to fire for `reifyEP ($W:)` rather than `reifyEP (:)`. If I'm tracking (uncertain), `($W:)` inlines to `(:)`. Sometimes I'm able

RE: GHC-7.8 warning on rules that may not fire

2014-03-17 Thread Simon Peyton Jones
[mailto:lemm...@henning-thielemann.de] | Sent: 14 March 2014 17:27 | To: Simon Peyton Jones; GHC Users List | Subject: Re: GHC-7.8 warning on rules that may not fire | | Am 14.03.2014 18:05, schrieb Simon Peyton Jones: | | You may think they are fragile, but not as fragile as saying nothing

GHC-7.8 warning on rules that may not fire

2014-03-14 Thread Henning Thielemann
With GHC-7.8 I get lots of warnings like src/Foo/Bar.hs:215:6: Warning: Rule foo may never fire because ‘bar’ might inline first Probable fix: add an INLINE[n] or NOINLINE[n] pragma on ‘bar’ So far I thought that rewrite RULES always have precedence to INLINE. Has this changed? I

RE: GHC-7.8 warning on rules that may not fire

2014-03-14 Thread Simon Peyton Jones
You may think they are fragile, but not as fragile as saying nothing and hoping for the best, which is *super*-fragile. You can't rely on rules to take priority, because the rule only fires if it matches, and it may only match if some other inlining has taken place. (We tried that originally

Re: GHC-7.8 warning on rules that may not fire

2014-03-14 Thread Henning Thielemann
Am 14.03.2014 18:05, schrieb Simon Peyton Jones: You may think they are fragile, but not as fragile as saying nothing and hoping for the best, which is *super*-fragile. You can't rely on rules to take priority, because the rule only fires if it matches, and it may only match if some other

RE: RULES map (\x - x) = id

2013-01-18 Thread Simon Peyton-Jones
| So I wonder: Why is rule map id2 not enough here? Compile with -ddump-rules. What you see is below. * The rule map id actually has an LHS like this: myMap a (id a) where the (id a) is a type application. It'll ONLY match a term that looks like myMap ty (id ty) where ty

RULES map (\x - x) = id

2013-01-17 Thread Joachim Breitner
Hi, I am experimenting with rewrite rules, but found that they do not fire as often as I wanted them. Here is a small example: module MapId where myMap f [] = [] myMap f (x:xs) = f x : myMap f xs {-# RULES map id myMap id = id

RE: Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-18 Thread Simon Peyton-Jones
| Turns out that I need a larger example to trigger the bug. I can | reliable trigger it using the unordered-containers library. I won't bore | you with the details. The workaround I need is this: | | forall x. integerToWord (smallInteger x) = int2Word# x So why not just add that rule

RE: Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-17 Thread Simon Peyton-Jones
| To: glasgow-haskell-users | Subject: Need workaround for lack of fromIntegral/Int-Word rules in | 7.4.2 | | I'm trying to work around the lack of some fromIntegral/Int-Word rules | in 7.4.2. I tried something like: | | int2Word :: Int - Word | #if defined(__GLASGOW_HASKELL__) | int2Word (I# i#) = W

Re: Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-17 Thread Johan Tibell
Message- | From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell- | users-boun...@haskell.org] On Behalf Of Johan Tibell | Sent: 14 December 2012 23:17 | To: glasgow-haskell-users | Subject: Need workaround for lack of fromIntegral/Int-Word rules in | 7.4.2 | | I'm trying

Re: Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-17 Thread Daniel Fischer
On Montag, 17. Dezember 2012, 07:07:21, Johan Tibell wrote: This compiles badly in 7.4.2: f :: Int - Word f = fromIntegral I need a workaround. Mine produces (with optimisations, of course) Convert.f :: GHC.Types.Int - GHC.Word.Word [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType

Re: Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-17 Thread Johan Tibell
Hi, Turns out that I need a larger example to trigger the bug. I can reliable trigger it using the unordered-containers library. I won't bore you with the details. The workaround I need is this: forall x. integerToWord (smallInteger x) = int2Word# x

Need workaround for lack of fromIntegral/Int-Word rules in 7.4.2

2012-12-14 Thread Johan Tibell
I'm trying to work around the lack of some fromIntegral/Int-Word rules in 7.4.2. I tried something like: int2Word :: Int - Word #if defined(__GLASGOW_HASKELL__) int2Word (I# i#) = W# (int2Word# i#) #else int2Word = fromIntegral #endif {-# RULES fromIntegral/Int-Word fromIntegral = int2Word

Re: RULES for ByteString are not fired

2012-10-28 Thread Ian Lynagh
Hi Kazu, On Tue, Aug 28, 2012 at 01:37:32PM +0900, Kazu Yamamoto wrote: I seems to us (my friends and me) that term rewriting rules for ByteString are not fired in recent GHCs. Thanks for the report. I've filed a ticket here: http://hackage.haskell.org/trac/ghc/ticket/7374 Thanks Ian

RULES for ByteString are not fired

2012-08-27 Thread 山本和彦
Hello, I seems to us (my friends and me) that term rewriting rules for ByteString are not fired in recent GHCs. 6.12.3OK 7.0.4 NG 7.4.1 NG 7.6.1RC1 NG For example, with the example from this ticket http://hackage.haskell.org/trac/ghc/ticket

Re: RULES for ByteString are not fired

2012-08-27 Thread Thomas DuBuisson
Another data point: The bytestring 'break' rule fired fine for me (GHC 7.4.1 Linux x86-64). On Mon, Aug 27, 2012 at 9:37 PM, Kazu Yamamoto k...@iij.ad.jp wrote: Hello, I seems to us (my friends and me) that term rewriting rules for ByteString are not fired in recent GHCs. 6.12.3

Re: simple extension to ghc's record disambiguation rules

2012-02-19 Thread AntC
Hi, I'd like to propose an extremely simple extension to ghc's record disambiguation rules, I wonder if John is teasing us? Nothing wrt to records is simple (IMHO). John seems to be unaware of the threads on 'Records in Haskell' (ghc-users) or 'Type-Directed Name Resolution' (cafe) that have

Re: simple extension to ghc's record disambiguation rules

2012-02-19 Thread John Meacham
On Sun, Feb 19, 2012 at 4:21 PM, AntC anthony_clay...@clear.net.nz wrote: Hi, I'd like to propose an extremely simple extension to ghc's record disambiguation rules, I wonder if John is teasing us? Nothing wrt to records is simple (IMHO). That is rather defeatist. Degree of simplicity

simple extension to ghc's record disambiguation rules

2012-02-17 Thread John Meacham
Hi, I'd like to propose an extremely simple extension to ghc's record disambiguation rules, my motivation is that I often have record types with multiple constructors but common fields. so the handy idiom of f Rec { .. } = do blah return Rec { .. } won't work, because I don't

Re: simple extension to ghc's record disambiguation rules

2012-02-17 Thread Anthony Clayden
Hi, I'd like to propose an extremely simple extension to ghc's record disambiguation rules, John, I've just posted a proposal on the 'Records in Haskell' wiki that I think will do the job for you. Declared Overloaded Record Fields (DORF). I'd appreciate feedback. my motivation is that I

my RULES don't fire

2011-02-09 Thread Sebastian Fischer
Hello, I want to use the RULES pragma and cannot get my rules to fire. Here is a simplified example of what I'm trying. I define my own version of foldMap for lists: fold :: Monoid m = (a - m) - [a] - m fold f = foldr mappend mempty . map f -- alternative, trying to avoid

Re: my RULES don't fire

2011-02-09 Thread Daniel Fischer
On Wednesday 09 February 2011 16:23:15, Sebastian Fischer wrote: Why don't the rules fire, what can I change such that they do, and what to get rid of the warning for the second rule (which I think is the one I should use)? Didn't spot that, sorry. Best regards, Sebastian Here

Re: my RULES don't fire

2011-02-09 Thread Daniel Fischer
On Wednesday 09 February 2011 16:23:15, Sebastian Fischer wrote: Why don't the rules fire, Because the 'match' is at the wrong type. In main, idGen appears as idGen_anJ :: ([()] - [[()]]) - [[()]] - [[()]] at some point (yay for ghc -v4), so it doesn't match g's polymorphic type. what can I

Re: my RULES don't fire

2011-02-09 Thread Sebastian Fischer
Why don't the rules fire, Because the 'match' is at the wrong type. This was the correct hint, thanks! what can I change such that they do, Type signatures. Initially, I thought that just leaving out the polymorphic signature should fix the problem. But I think it cannot be fixed

Re: Choosing implementation depending on class instances using rewriting rules

2009-06-03 Thread Niklas Broberg
Hi Milan, Is there a way to write such a rewriting rule or there is no way of acquiring the Ord dictionary in rewrite rule? Or does anyone know any other way of implementing such a nub without explicitly listing all Ord instances? Have a look at

Re: Choosing implementation depending on class instances using rewriting rules

2009-06-03 Thread Daniel Peebles
appearance rather than sorted order. Of course, you may not care about this and just be experimenting with rewrite rules, in which case I can't help you :) Dan On Wed, Jun 3, 2009 at 5:58 AM, Milan Straka f...@ucw.cz wrote: Hi, I am interesting in writing a method nub in such a way, that it will use

RE: optimization and rewrite rules questions

2009-02-26 Thread Simon Peyton-Jones
| II is where I'd like to be able to distinguish variables, constants, | and complex expressions in the left-hand sides of RULES, and | I and III are where I'd like control over the rewrite strategy, as | in strategy combinators. I'm deep in icfp submissions, so no time to reply properly. You

Re: optimization and rewrite rules questions

2009-02-26 Thread Max Bolingbroke
2009/2/24 Claus Reinke claus.rei...@talk21.com: In the recently burried haskell-cafe thread speed: ghc vs gcc, Bulat pointed out some of the optimizations that GHC doesn't do, such as loop unrolling. I suggested a way of experimenting with loop unrolling, using template haskell to bypass GHC's

Re: optimization and rewrite rules questions

2009-02-26 Thread Claus Reinke
| II is where I'd like to be able to distinguish variables, constants, | and complex expressions in the left-hand sides of RULES, and | I and III are where I'd like control over the rewrite strategy, as | in strategy combinators. I'm deep in icfp submissions, so no time to reply properly

Re: optimization and rewrite rules questions

2009-02-26 Thread Claus Reinke
but if we unfold a loop combinator at compile time, GHC's normal optimizations can take over from there): http://www.haskell.org/pipermail/haskell-cafe/2009-February/056241.html Just a note - there is a solution that doesn't require Template Haskell which I use in my own code. Here is a

Re: optimization and rewrite rules questions

2009-02-25 Thread Claus Reinke
#-} module Main where import Loop import GHC.Prim {-# RULES re-assoc [~1] forall v x y z. (x+#y)+#(z+#v) = ((x+#y)+#z)+#v collect1 [1] forall x y. (x+#y)+#x = (2#*#x)+#y collect2 [1] forall n x y. ((n*#x)+#y)+#x = ((n+#1#)*#x)+#y collect3 [1] forall n x y z. ((n*#x)+#y)+#z = (n*#x)+#(y

optimization and rewrite rules questions

2009-02-24 Thread Claus Reinke
, and what plans are there for recovering the optimizations previously left to GCC? The next thing I was looking at was rewrite rules, the obvious GHC tool for implementing this kind of rule (var+const1)+(var+const2) == 2*var + const3 and I ran into more questions: - can RULES left-hand sides

Type binders in rules

2008-09-19 Thread Simon Peyton-Jones
Friends This is a message for people who use RULES, to ask your opinion. Have a look at http://hackage.haskell.org/trac/ghc/ticket/2600 and add your comments if you want. The intro to the ticket appears below, so you can get an idea of whether you are interested. Simon Roman writes

Confusing flags for RULES in GHC

2008-08-11 Thread Simon Peyton-Jones
Friends The use of flags to control rewrite rules in GHC is very confusing. Several bug reports arise from this. There is a summary here: http://hackage.haskell.org/trac/ghc/ticket/2497 The final comment is a proposal, which I append below. This email is just to allow others

RE: desperately seeking RULES help

2008-06-09 Thread Simon Peyton-Jones
is duplicated. It shouldn't make much difference, but of course it *does* when rules are involved, because there are no rules for fint (it's a fresh, local function). Simon From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Conal Elliott Sent: 07 June 2008 17:26 To: glasgow-haskell-users

Re: desperately seeking RULES help

2008-06-09 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote: The -fno-method-sharing flag was supposed to be a bit experimental, which is why it takes the cheap-and-cheerful route of being a static flag. (Only dynamic flags can go in OPTIONS_GHC.) It's dynamic in the HEAD, see Mon May 19 19:59:56 PDT 2008 Roman Leshchinskiy

Re: desperately seeking RULES help

2008-06-09 Thread Claus Reinke
something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired). -- Lennart module F where -- | Domain of a linear map. class

Re: desperately seeking RULES help

2008-06-09 Thread Conal Elliott
How does method sharing interact with the ability of the rules engine to look through lets? Wouldn't an f rule kick in when fint is seen, by looking through the fint binding? I've been wondering: will pattern matching look through a let even when the let-bound variable is used more than once? I

RE: desperately seeking RULES help

2008-06-09 Thread Simon Peyton-Jones
] On Behalf Of Conal Elliott Sent: 09 June 2008 16:28 To: Simon Peyton-Jones Cc: glasgow-haskell-users@haskell.org Subject: Re: desperately seeking RULES help How does method sharing interact with the ability of the rules engine to look through lets? Wouldn't an f rule kick in when fint is seen

Re: desperately seeking RULES help

2008-06-09 Thread Lennart Augustsson
= toInt' {-# INLINE[1] fromInt #-} fromInt :: (AsInt a) = Int - a fromInt = fromInt' {-# RULES toInt/fromInt forall m . toInt (fromInt m) = m #-} {-# INLINE onInt #-} onInt :: AsInt a = (Int - Int) - (a - a) onInt f x = fromInt (f (toInt x)) test :: AsInt a = (Int - Int) - (Int - Int

Re: desperately seeking RULES help

2008-06-09 Thread Claus Reinke
Here it is: {-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl #-} -- compile with: ghc -fno-method-sharing -c F.hs thanks! it seems i misread the users guide (or is this a bug?). i used -frewrite-rules (Switch on all rewrite rules), which does not(!) work, instead of -fglasgow-exts, which

Re: desperately seeking RULES help

2008-06-09 Thread Don Stewart
claus.reinke: Here it is: {-# OPTIONS_GHC -O2 -Wall -fglasgow-exts -ddump-simpl #-} -- compile with: ghc -fno-method-sharing -c F.hs thanks! it seems i misread the users guide (or is this a bug?). i used -frewrite-rules (Switch on all rewrite rules), which does not(!) work, instead

Re: desperately seeking RULES help

2008-06-09 Thread Claus Reinke
Right. There are two things here: 1) -frewrite-rules enables rules to fire. 2) -fglasgow-exts enables parsing of RULES pragmas, and their interpretation. You need both if you wish to both write your own rules, and have them fire. nope!-) -fglasgow-exts is sufficient for the RULE

Re: desperately seeking RULES help

2008-06-09 Thread Don Stewart
claus.reinke: Right. There are two things here: 1) -frewrite-rules enables rules to fire. 2) -fglasgow-exts enables parsing of RULES pragmas, and their interpretation. You need both if you wish to both write your own rules, and have them fire. nope!-) -fglasgow-exts

Re: desperately seeking RULES help

2008-06-09 Thread Don Stewart
claus.reinke: nope!-) -fglasgow-exts is sufficient for the RULE to be parsed and applied in Lennart's code, -frewrite-rules doesn't seem to serve any noticable purpose. Well, if -O is on, -frewrite-rules is already on by default. Try -fno-rewrite-rules with -O to turn them off specifically

Re: desperately seeking RULES help

2008-06-07 Thread Johan Tibell
2008/6/7 Conal Elliott [EMAIL PROTECTED]: I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code below (which is simplified from fusion on linear maps). I've tried every variation I can think of, and always something prevents the fusion. [snip] {-# INLINE onInt

Re: desperately seeking RULES help

2008-06-07 Thread Lennart Augustsson
toInt and fromInt have been inlined you can no longer write rules that apply, since the types involve dictionaries and the terms pattern match on dictionaries. -- Lennart 2008/6/7 Conal Elliott [EMAIL PROTECTED]: I'm trying to do some fusion in ghc, and I'd greatly appreciate help with the code

Re: desperately seeking RULES help

2008-06-07 Thread Lennart Augustsson
Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired). -- Lennart module F where -- | Domain

Re: desperately seeking RULES help

2008-06-07 Thread Conal Elliott
Thanks a million, Lennart! -fno-method-sharing was the missing piece. - Conal On Sat, Jun 7, 2008 at 5:07 AM, Lennart Augustsson [EMAIL PROTECTED] wrote: Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods

Re: desperately seeking RULES help

2008-06-07 Thread Conal Elliott
, Lennart Augustsson [EMAIL PROTECTED] wrote: Here's something that actually works. You need to pass -fno-method-sharing on the command line. Instead of using rules on methods it uses rules on global functions, and these global functions don't get inlined until late (after the rule has fired

desperately seeking RULES help

2008-06-06 Thread Conal Elliott
-exts -ddump-simpl -ddump-simpl-stats #-} -- {-# OPTIONS_GHC -ddump-simpl-iterations #-} module F where -- | Domain of a linear map. class AsInt a where toInt :: a - Int fromInt :: Int - a {-# RULES toInt/fromInt forall m. toInt (fromInt m) = m #-} {-# INLINE onInt #-} onInt :: AsInt

RE: GHC rewrite rules pragma

2008-05-30 Thread Simon Peyton-Jones
| This is the main wibble people forget when writing rules -- inlining. | In your example, 'gen' is so cheap, it is immediately | inlined, so it won't be available to match on in your rule. I'll add a note in the user manual about this. In general, GHC tries RULES before inlining

GHC rewrite rules pragma

2008-05-27 Thread Jan Jakubuv
Hi, I'm trying to find out how the GHC rewrite rules pragma work, but I'm not able to make it working. I have this simple example, where I would like to specialize the function gen to spec on strings: {-# OPTIONS -O2 -fglasgow-exts #-} gen :: [a] - a gen = head {-# RULES gen/Char gen=spec

Re: GHC rewrite rules pragma

2008-05-27 Thread Don Stewart
jakubuv: Hi, I'm trying to find out how the GHC rewrite rules pragma work, but I'm not able to make it working. I have this simple example, where I would like to specialize the function gen to spec on strings: {-# OPTIONS -O2 -fglasgow-exts #-} gen :: [a] - a gen = head {-# RULES

Re: GHC rewrite rules pragma

2008-05-27 Thread Jan Jakubuv
Thanks lot, it works now. Now, I have just a simple question: Is there any chance to make rewriting working in ghci ? jan. 2008/5/27 Don Stewart [EMAIL PROTECTED]: jakubuv: Hi, I'm trying to find out how the GHC rewrite rules pragma work, but I'm not able to make it working. I have

Re: GHC rewrite rules pragma

2008-05-27 Thread Don Stewart
jakubuv: Thanks lot, it works now. Now, I have just a simple question: Is there any chance to make rewriting working in ghci ? I think you can actually enable them by putting: {-# OPTIONS -frewrite-rules #-} at the top of the file to be interpreted. Works for me, anyway. -- Don

Re: GHC rewrite rules pragma

2008-05-27 Thread Jan Jakubuv
thanks, it works fine now. 2008/5/27 Don Stewart [EMAIL PROTECTED]: jakubuv: Thanks lot, it works now. Now, I have just a simple question: Is there any chance to make rewriting working in ghci ? I think you can actually enable them by putting: {-# OPTIONS -frewrite-rules #-} at the top

RULES and type classes

2007-09-02 Thread Andreas Schropp
// In particular, it would be nice to be able to specialise based on the instances, as we do for [a] -- [Int], e.g. RULES sum = sumInt :: [Int] - Int is fine in the current system. So I could imagine some nice specialisations based on say, the good old Ord: RULES nub = nubOrd

RE: specialization using RULES

2007-06-05 Thread Simon Peyton-Jones
| The rules do not fire. They only seem to fire if the specialized | function is called directly, such as | | doSomethingWith ( zipWith (-) (u :: Vec Three Double) v ) That's probably because to fire distance must be inlined but sumV and mapV must not which is obviously a bit

specialization using RULES

2007-06-04 Thread Scott Dillard
dimensionality of the vectors at the type level, so you could not add a two-vector to a three-vector, even though both functions are just zipWith (+). After trying to tune my library I came across the SPECIALIZATION/RULES pagmas in the GHC manual, and thought that this phantom dimensionality type

Re: Arrows and GHC rewrite rules

2007-03-31 Thread Eric Cheng
On 3/30/07, Simon Peyton-Jones [EMAIL PROTECTED] wrote: Would someone care to document this at http://haskell.org/haskellwiki/GHC/Using_rules Thanks! I added a section at http://haskell.org/haskellwiki/GHC/Using_rules#Rules_and_method_sharing . Eric

Re: rules

2007-03-30 Thread skaller
On Fri, 2007-03-30 at 13:04 -0700, Tim Chevalier wrote: On 3/30/07, skaller [EMAIL PROTECTED] wrote: I'm curious when and how GHC applies rewrite rules, and how expensive it is. Have you seen the Playing By Rules paper? http://research.microsoft.com/~simonpj/Papers/rules.htm If you

Re: RULES and type classes

2007-03-29 Thread Donald Bruce Stewart
haskell: Is there any way to use RULES substitutions with type classes? I'm writing a reactive programming arrow (same idea as Yampa, different design goals), and it would help performance (and not just in the speed sense) to be able to tell when a value derived with arr hasn't changed. So

Re: RULES and type classes

2007-03-29 Thread Pepe Iborra
On 29/03/2007, at 11:38, Mike Hamburg wrote: Is there any way to use RULES substitutions with type classes? I'm writing a reactive programming arrow (same idea as Yampa, different design goals), and it would help performance (and not just in the speed sense) to be able to tell when

Re: RULES and strictness

2006-12-01 Thread Kirsten Chevalier
in the deforestation papers that rules can change the sharing properties of code and we are okay with that. I was wondering if they could safely change the strictness or abscence properties of code as well? Given the example above, I think it's fairly safe to say that rules can safely change

RULES and strictness

2006-11-30 Thread John Meacham
or producing bad code in some way, rather than the obvious trouble of changing the meaning of const. it is noted in the deforestation papers that rules can change the sharing properties of code and we are okay with that. I was wondering if they could safely change the strictness or abscence

Re: [Haskell-cafe] Debugging partial functions by the rules

2006-11-17 Thread Neil Mitchell
Hi To see at a glance the various bug reports about fromJust you can search the bug database: http://bugs.darcs.net/[EMAIL PROTECTED]@sort=activity@group=priority@search_text=fromJust I count 7 bugs. I would be interested to see the results of static analysis tools (Catch?) or applying

RE: Debugging partial functions by the rules

2006-11-15 Thread Simon Peyton-Jones
. Could this be done | with TH? Or could we arrange for asserts in rewrite rules not to be expanded | till later? That's difficult. Trouble is, the assert expansion happens right at the front, before any desugaring or program transformation. But rewrite rules fire much, much later

Re: Debugging partial functions by the rules

2006-11-15 Thread Claus Reinke
[deleted cc to haskell-cafe; RULES and discussion details are GHC-specific] That's difficult. Trouble is, the assert expansion happens right at the front, before any desugaring or program transformation. But rewrite rules fire much, much later, in the simplifier. and there doesn't seem

Re: Debugging partial functions by the rules

2006-11-15 Thread Claus Reinke
Sounds useful to me (though one might occasionally want to have access to just the current location, without context - suggesting perhaps a list/stack of strings rather than a pre-concatenated string). actually, there's a bit about your proposal (on the wiki page) that I don't quite follow,

Debugging partial functions by the rules

2006-11-14 Thread Donald Bruce Stewart
So all this talk of locating head [] and fromJust failures got me thinking: Couldn't we just use rewrite rules to rewrite *transparently* all uses of fromJust to safeFromJust, tagging the call site with a location? To work this requires a few things to go right: * a rewrite rule

RE: RULES pragmas

2006-07-14 Thread Simon Peyton-Jones
I've started a Wiki page, attached to GHC's collaborative documentation, as a place to collect advice about RULES. http://haskell.org/haskellwiki/GHC/Using_Rules Please feel free to elaborate it. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED

Re: RULES pragmas

2006-07-12 Thread Malcolm Wallace
[EMAIL PROTECTED] (Donald Bruce Stewart) wrote: So what am I doing wrong? And is there any way to ask the compiler to give a warning if the RULES pragma contains errors? In this case, it's because it's missing -fglasgow-exts, I think. Ah, thank you. The missing (and undocumented) option

Re: RULES pragmas

2006-07-12 Thread Malcolm Wallace
Malcolm Wallace [EMAIL PROTECTED] wrote: Ah, thank you. The missing (and undocumented) option. Actually, now I came to submit a patch to the manual, I discover that it /is/ documented, but at the beginning of section 7. (But on the index page on the web, the link to section 7 is two whole

Re: RULES pragmas

2006-07-12 Thread Simon Marlow
activated by -fglasgow-exts? I believe RULES is the only pragma that requires -fglasgow-exts, the reason being that the syntax inside RULES uses the 'forall' keyword, which is only enabled by -fglasgow-exts. If you could submit a doc patch, that would be great. Cheers, Simon

Re: RULES pragmas

2006-07-11 Thread Donald Bruce Stewart
Malcolm.Wallace: I have a question about {-# RULES #-} pragmas. Here is a very simple attempt to use them: module Simplest where {-# RULES simplestRule forall x. id (id x) = x #-} myDefn = id (id 42) I want to verify whether ghc-6.4.1 does actually fire

  1   2   >