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-o

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 t

Re: Rewrite rules involving LHS lambda?

2017-12-02 Thread Edward Kmett
like forall u v. exists x. ... Under that view, the warnings are accurate, and the rewrite is pretty purely syntactic. I don't see how we could write using our current vocabulary that which you want. On Sun, Dec 3, 2017 at 4:50 AM, Conal Elliott wrote: > Is there a written explanation and/or ex

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
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 can also ask for review if

Re: Rewrite rules

2017-01-16 Thread Erik de Castro Lopo
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
> If I 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 goin

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

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 wrote: > HI all, > > I'm having an look at rewrite rules, but something bugs me a little. > How do I tell if my rewrite rules are fi

Rewrite rules

2017-01-12 Thread Erik de Castro Lopo
HI all, I'm having an look at rewrite rules, but something bugs me a little. How do I tell if my rewrite rules are firing or not? Even If I introduce deliberate errors in the function name that is being re-written I still don't get so much as a warning. Cl

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 Data.Word (e.g. GHC.Int.eqIn

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 ; George Colpitts | | Cc: glasgow-haskell-users@haskell.org; Simon Peyton Jones | | Subject: Re: GHC rewrite rules for class operations & laws | | On December 28, 2016 7:27:20 PM EST, Conal Elliott w

Re: GHC rewrite rules for class operations & laws

2016-12-30 Thread George Colpitts
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. The alternative I know (and

Re: GHC rewrite rules for class operations & laws

2016-12-29 Thread Ben Gamari
On December 28, 2016 7:27:20 PM EST, Conal Elliott wrote: >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

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) of

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 wrote: > Conal > > > > Is it possible to apply GHC rewrite rules to class

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 wrote: > Conal > > > > Is it possible to apply GHC rewrite rules to class

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 will

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 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 encapsula

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 insta

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 of

RE: GHC rewrite rules and constructor wrappers?

2014-05-06 Thread Simon Peyton Jones
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:<)`

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 noth

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

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 origi

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 th

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

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" myM

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 (perha

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 __

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=D

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

2012-12-17 Thread Johan Tibell
t; | -Original 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->W

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__) | i

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"

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/737

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 wrote: > Hello, > > I seems to us (my friends and me) that term rewriting rules for > ByteString are not fired in recent GHCs. &g

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: 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). > That is rather defeatist. Degree of simplicity is actually something that > v

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 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 is act

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 Na

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

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,

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

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 mat

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

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

Re: Choosing implementation depending on class instances using rewriting rules

2009-06-03 Thread Dinko Tenev
On Wed, Jun 3, 2009 at 7:43 PM, Daniel Peebles wrote: > An equality-based (n^2) nub > works "fine" on infinite lists, whereas any O(n log n) sort-based nub > must necessarily evaluate the entire list before being able to return > the value. No. You just need to keep anything seen so far in a con

Re: Choosing implementation depending on class instances using rewriting rules

2009-06-03 Thread Daniel Peebles
of their first 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 wrote: > Hi, > > I am interesting in writing a method nub in such

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 http://okmij.org/ftp/Haskell/types.html#class

Choosing implementation depending on class instances using rewriting rules

2009-06-03 Thread Milan Straka
e Eq a => Nub a where nub = nubEq which is of course not valid Haskell. I tried using GHC rewriting rules to achieve this. My first try was {-# NOINLINE nub #-} nub :: Eq a => [a] -> [a] nub xs = ... nubOrd :: Ord a => [a] -> [a] nubOrd xs = ... {-# RULES &quo

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 sketch:

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

Re: optimization and rewrite rules questions

2009-02-26 Thread Max Bolingbroke
2009/2/24 Claus Reinke : > 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 blindspot (it usu

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

Re: optimization and rewrite rules questions

2009-02-25 Thread Claus Reinke
- 3. Finally, the main program, using 'loop' to calculate a simple sum: -- {-# LANGUAGE MagicHash #-} module Main where import Loop import GHC.Prim {-# RULES "re-assoc" [~1] forall

optimization and rewrite rules questions

2009-02-24 Thread Claus Reinke
erstand correctly, -fvia-C is on its way out - is that correct, 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 + con

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 to

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 defaul

Re: desperately seeking RULES help

2008-06-09 Thread 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, y

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 bo

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 to

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 rewr

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 -fgl

Re: desperately seeking RULES help

2008-06-09 Thread Lennart Augustsson
> a -> Int toInt = 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 = fr

RE: desperately seeking RULES help

2008-06-09 Thread Simon Peyton-Jones
EMAIL PROTECTED] 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

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

Re: desperately seeking RULES help

2008-06-09 Thread Claus Reinke
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 rul

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 Simon Peyton-Jones
nt)... So the record selection 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

Re: desperately seeking RULES help

2008-06-07 Thread Conal Elliott
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 it uses rules on global functions, >>

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 us

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 -- | D

Re: desperately seeking RULES help

2008-06-07 Thread Lennart Augustsson
after 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 ap

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] > > {-# INLIN

desperately seeking RULES help

2008-06-06 Thread Conal Elliott
-Wall -fglasgow-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 #-} {-# IN

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 befor

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

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

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

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 #-} &g

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 "

RE: RULES and type classes

2007-09-03 Thread Simon Peyton-Jones
| > 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 bas

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 g

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 obvious

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 dimension

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 and type classes

2007-03-30 Thread Duncan Coutts
tNum Char instance StrictNum Int8 ... instance StrictNum Integer {-# RULES "strict maximum" forall (xs :: SmallStrictAtomic x => [x]). maximum xs = strictMaximum xs #-} This is a whole lot easier and more extensible than adding lots of SPECIALISE pragmas: {-# SPECIALISE maxi

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?

Re: RULES and type classes

2007-03-30 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Neil Mitchell wrote: > Hi > > I was thinking about this, and I think pattern matching with rules and > class context pretty much _guarantees_ a change in semantics. If you > match on a class constraint, the pretty much only reason t

Re: rules

2007-03-30 Thread Tim Chevalier
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 still have questions after reading i

rules

2007-03-30 Thread skaller
I'm curious when and how GHC applies rewrite rules, and how expensive it is. Felix also has rewrite rules. It uses a woefully expensive algorithm to apply them: 1) elide rules that refer to functions that have themselves been elided since they can't be applied. 2) For each rule in tur

Re: RULES and type classes

2007-03-30 Thread Neil Mitchell
Hi I was thinking about this, and I think pattern matching with rules and class context pretty much _guarantees_ a change in semantics. If you match on a class constraint, the pretty much only reason to do so is to exploit that type class. Unfortunately, this isn't safe. The user has cal

RE: Arrows and GHC rewrite rules

2007-03-30 Thread Simon Peyton-Jones
no occurrence of the pattern the rule looks for. You can switch off this (dubious) sharing optimisation with -fno-method-sharing. Would someone care to document this at http://haskell.org/haskellwiki/GHC/Using_rules The second is a plain bug: RULES for class methods are not being expor

RE: RULES and type classes

2007-03-30 Thread Simon Peyton-Jones
| 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: | | RUL

RE: RULES and type classes

2007-03-30 Thread Simon Peyton-Jones
rs@haskell.org | Subject: Re: RULES and type classes | | | 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), an

  1   2   >