Re: [Haskell-cafe] Human-friendly compiler errors for GHC
Max Bolingbroke wrote: Agreed: I've implemented this too. I've also added fuzzy matching to package search: """ $ stage2/ghc-inplace --make ../Test1.hs ../Test1.hs:3:7: Could not find module `Data.Lost': Use -v to see a list of the files searched for. Maybe you meant `Data.List' $ stage2/ghc-inplace --make ../Test2.hs [1 of 1] Compiling Main ( ../Test2.hs, ../Test2.o ) ../Test2.hs:7:14: Not in scope: `isSpace' Maybe you meant `Char.isSpace' """ In terms of making error messages more helpful, I don't find general typos are much of an issue, but this part would be really nice! I've always been annoyed that GHC just says "no" rather than offering suggestions (-v is rarely helpful), especially since it knows about what modules are installed et al. Granted it's still an easy class of bugs to fix, but this is a much friendlier way of fixing them. -- Live well, ~wren ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Re: QuickCheck [Architecturally flawed]
I think you can use the duality of Writer/Reader to help you here; you have the law that, for suitable "dual" computations r and w, run_reader r (run_writer (w x)) == x Then you can build up a list of rules specifying which computations are dual; read64 is dual to write64, for example. You can then have some laws like: if r1 is dual to w1, and r2 is dual to w2, then r1 >>= \x -> r2 >>= \y -> (x,y) is dual to \(x,y) -> w1 x >> w2 y if r1 is dual to w1, and r2 is dual to w2, then read1 >>= \b -> case b of True -> liftM Left r1 ; False -> liftM Right r2 is dual to \x -> case x of Left l -> w1 l; Right r -> w2 r You can then use these to build up more complicated reader/writer duals and verify that the main "identity" law holds. It's a little bit tricky; QuickCheck is not good at dealing with polymorphic data, but you could generalize this to a simple term ADT: data SimpleTerm = Leaf Word8 Word32 | Pair SimpleTerm SimpleTerm | Switch (Either SimpleTerm SimpleTerm) deriving Eq and make a suitable "arbitrary" instance for SimpleTerm to test your reader/writer. Leaf would test readN/writeN, or you can make custom leaves to test the other operations. -- ryan On Fri, Jul 11, 2008 at 11:10 AM, Andrew Coppin <[EMAIL PROTECTED]> wrote: > Andrew Coppin wrote: >> >> After many hours of effort, I came up with these: >> >> data Writer x >> instance Monad Writer >> run_writer :: Writer () -> ByteString >> write1 :: Bool -> Writer () >> write8 :: Word8 -> Writer () >> write16 :: Word16 -> Writer () >> write32 :: Word32 -> Writer () >> write64 :: Word64 -> Writer () >> writeN :: Word8 -> Word32 -> Writer () >> >> data Reader x >> instance Monad Reader >> run_reader :: Reader x -> ByteString -> x >> is_EOF :: Reader Bool >> read1 :: Reader Bool >> read8 :: Reader Word8 >> read16 :: Reader Word16 >> read32 :: Reader Word32 >> read64 :: Reader Word64 >> readN :: Word8 -> Reader Word32 > > How would you write QuickCheck properties for these? > > For starters, what would be a good set of properties to confirm that any > monad is actually working correctly? More particularly, how about a state > monad? It's easy to screw up the implementation and pass the wrong state > around. How would you catch that? > > Secondly, the monads themselves. I started writing things like "if X has the > lowest bit set then the lowest bit of the final byte of the output should be > set"... but then all I'm really doing is reimplementing the algorithm as a > property rather than a monad! If a property fails, is the program wrong or > is the property wrong? > > In the end, what I opted to do was define various properties where I take > some arbitrary data, write it with the Writer monad, then read it back with > the Reader monad and confirm that the data stays identical. (This actually > fails for writeN, which writes the N least-significant bits of the supplied > data, so you need to apply some masking before doing equity. Or, > equivilently, reject some test values...) > > Looking at the QuickCheck paper, it seems I should probably have done some > checking that the size of the output is correct. I didn't actually bother > because it's really easy to get right, whereas strickiness with bit-shifts > and indexing is all too easy to screw up. > > What I finally did was try writing/reading with each primitive (to check > that actually works properly), and then again with a random number of > individual bits packed on each side to give random alignment (to check that > the index adjustments actually work right). It's easy to make the code work > correctly with a certain alignment, but fail spectacularly otherwise. It's > packed at *both* ends because it's also quite easy to make it write out the > correct bit pattern, but leave the bit pointer with the wrong value, causing > subsequent writes to screw up. > > How would you approach this one? All hints welcomed. > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Human-friendly compiler errors for GHC
> That's pretty cool. Unfortunately in my early Haskell days the 'not > in scope' errors were the only ones I _did_ understand. Heh :-) > It would be > nice to human-friendlify the other types of errors. I'm not judging > your work though, this is helpful, and the other types of errors are > of course much harder to friendlify. Yep, this would only be one small step forward in error message quality. > On the topic of things that aren't stupid complaints by me, a typo is > the most likely cause for not in scope errors. As Evan points out, I > think it would be more helpful to search for matching names in > imported modules to see if the name was accidentally not qualified or > exported. Agreed: I've implemented this too. I've also added fuzzy matching to package search: """ $ stage2/ghc-inplace --make ../Test1.hs ../Test1.hs:3:7: Could not find module `Data.Lost': Use -v to see a list of the files searched for. Maybe you meant `Data.List' $ stage2/ghc-inplace --make ../Test2.hs [1 of 1] Compiling Main ( ../Test2.hs, ../Test2.o ) ../Test2.hs:7:14: Not in scope: `isSpace' Maybe you meant `Char.isSpace' """ > I don't know about this fuzzy matching business, since when > I go to the line of the error message, I'm going to see my typo and > what I meant. I don't think I'd ever use the suggestions... I can think of a few times it would have helped me out, with identifiers that may or may not be pluralized or have suprising capitalisation. I don't know though, I guess you'd have to work with the feature turned on for a while to work out if it really was useful. I think this feature has shaped up pretty nicely after the helpful suggestions I recieved. I don't know if I'll be able to get the patch into GHC proper, though.. Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Galois Tech Talks: Stream Fusion for Haskell Arrays
johan.tibell: > On Sat, Jul 12, 2008 at 12:13 AM, Don Stewart <[EMAIL PROTECTED]> wrote: > > > > Just a quick note about next week's Galois Tech Talk. Now that Galois > > has completed its move into downtown Portland, and a shiny new, centrally > > located, office space, we're opening up our tech talk series a bit more > > widely. If you're in Portland, and interested in functional programming > > and formal methods, drop by! > > Any possibility of you guys taping the talk? Unlikely next week, but soon, yes! -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANNOUNCE: vector 0.1 (efficient arrays with lots of fusion)
bulat.ziganshin: > Hello Roman, > > Saturday, July 12, 2008, 7:01:05 PM, you wrote: > > > the vector library will eventually provide fast, Int-indexed arrays with > > a powerful fusion framework. > > GREAT! doom4 would be written in Haskell! Did you know about Cheplyaka's Summer of Code project to build a physics engine using fusible arrays? http://physics-dph.blogspot.com/ :) -- Don ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Profiling nested case
Hi! > My guess is that it was premature optimization that created this bug. It is the root of all evil. ;-) > Unboxed tuples are not the best answer for every situation. They are > evaluated strictly! Then I have not understood the last paragraph correctly: http://www.haskell.org/ghc/docs/latest/html/users_guide/primitives.html Oh, no. It is like you say. I also use -funbox-strict-fields and Q is defined with strict fields. But I tried also without the switch and is it the same (it takes forever). But then qN and qN' does not have unboxed types. So it should be lazy? > If you are in that phase where you are doing performance tweaks and > you think GHC's strictness analysis might not be picking up on some > strict behavior in your program, add the annotation. If it makes it > faster, great; if it doesn't change things, take it out! Best to > underconstrain your program. I completely agree. I am also a firm believer in the clean and pure code where I would leave all optimization to compiler and just write semantics into a program. But this project just showed me that there is still a long way of compiler development before that would be possible (and usable). That some simple refactoring of code which is not really changing semantics have a big influence on a performance because compiler uses it differently (polymorphic types instead of hardcoded types, passing function as an parameter instead of hardcode it). For example I have now defined my types as: type BasicReal = Double data Quaternion = Q !BasicReal !BasicReal !BasicReal !BasicReal deriving (Eq,Show) So that I can easily change the type everywhere. But it would be much nicer to write: data Quaternion a = Q !a !a !a !a deriving (Eq,Show) Only the performance of Num instance functions of Quaternion is then quite worse. Mitar ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Profiling nested case
On Sat, Jul 12, 2008 at 8:57 PM, Mitar <[EMAIL PROTECTED]> wrote: > julia4DFractal :: BasicReal -> World > julia4DFractal param (x,y,z) = julia4D (Q (x / scale) (y / scale) (z / > scale) param) iterations > where c = (Q (-0.08) 0.0 (-0.8) (-0.03)) >alphaBlue = VoxelColor 0 0 (2 / scale) (2 / scale) >scale = fromIntegral sceneHeight / 1.8 >threshold = 16 >iterations = 100 :: Int >julia4D _ 0= (# alphaBlue, > 1 #) -- point is (probably) not in the set >julia4D q it | qMagnitudeSquared q > threshold = (# noColor, 1 > #) -- point is in the set > | otherwise = julia4D > (qSquared q + c) (it - 1) > where distance = scale * (qMagnitude qN) / (2 * > (qMagnitude qN')) * log (qMagnitude qN) >(# qN, qN' #) = disIter q (Q 1 0 0 0) iterations > where disIter qn qn' 0 > = (# qn, qn' #) >disIter qn qn' i | qMagnitudeSquared qn > > threshold = (# qn, qn' #) > | otherwise > = disIter (qSquared qn + c) (2 * qn * qn') (i - 1) > > Please observe that distance is never used. And this is also what GHC > warns. But the trick is that with having this part of a code in there, > the program virtually never finishes (I killed it after 15 minutes). > If I remove everything on and after the "where distance" line it > finishes in 30 seconds. OK, the problem is with (# qN, qN' #), if this > is changed to normal (qN, qN'), then it works. But to notice this ... > This is something you have to spend a day for. My guess is that it was premature optimization that created this bug. Unboxed tuples are not the best answer for every situation. They are evaluated strictly! Which means: unboxedBottom x | False = (# 0, 0 #) | otherwise = unboxedBottom x let (# x, y #) = unboxedBottom 0 in 42 Is an infinite loop, not 42 as you would expect. So when you write: where (# ... #) = something You are requiring your program to evaluate 'something' regardless of whether it is needed. Unboxed tuples should be taken in the same vain as explicit strictness annotations: almost never use them, and let GHC do the work for you. If you are in that phase where you are doing performance tweaks and you think GHC's strictness analysis might not be picking up on some strict behavior in your program, add the annotation. If it makes it faster, great; if it doesn't change things, take it out! Best to underconstrain your program. But these days I try to make my programs fast by making the structure of my program apparent to the compiler, not by forcing it to do things in a certain way. Admittedly making the structure of a program apparent to the compiler is a rather subtle and brittle process. I'm sure people have at least brainstormed ways to help the compiler more. Luke ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Profiling nested case
Hi! (I will reply propely later, I have a project to finish and GHC is playing me around and does not want to cooperate.) This project of mine is getting really interesting. Is like playing table tennis with GHC. Some time it gives a nice ball, sometimes I have to run around after it. But I just wanted to make a simple raycasting engine. Not debug GHC. But it is interesting - just I do not have time just know for playing the change code - compile - run on known input - check if time elapsed increased (I have to do this even when I am thinking that I am optimizing things or even when I am thinking that I am just refactoring code - moving constants to definitions...). And this is a slow process because every iteration runs for a few minutes. The next beautiful example in this series is this function for computing 4D Julia set fractal: julia4DFractal :: BasicReal -> World julia4DFractal param (x,y,z) = julia4D (Q (x / scale) (y / scale) (z / scale) param) iterations where c = (Q (-0.08) 0.0 (-0.8) (-0.03)) alphaBlue = VoxelColor 0 0 (2 / scale) (2 / scale) scale = fromIntegral sceneHeight / 1.8 threshold = 16 iterations = 100 :: Int julia4D _ 0= (# alphaBlue, 1 #) -- point is (probably) not in the set julia4D q it | qMagnitudeSquared q > threshold = (# noColor, 1 #) -- point is in the set | otherwise = julia4D (qSquared q + c) (it - 1) where distance = scale * (qMagnitude qN) / (2 * (qMagnitude qN')) * log (qMagnitude qN) (# qN, qN' #) = disIter q (Q 1 0 0 0) iterations where disIter qn qn' 0 = (# qn, qn' #) disIter qn qn' i | qMagnitudeSquared qn > threshold = (# qn, qn' #) | otherwise = disIter (qSquared qn + c) (2 * qn * qn') (i - 1) Please observe that distance is never used. And this is also what GHC warns. But the trick is that with having this part of a code in there, the program virtually never finishes (I killed it after 15 minutes). If I remove everything on and after the "where distance" line it finishes in 30 seconds. OK, the problem is with (# qN, qN' #), if this is changed to normal (qN, qN'), then it works. But to notice this ... This is something you have to spend a day for. Mitar ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Human-friendly compiler errors for GHC
On Sat, Jul 12, 2008 at 10:44 AM, Max Bolingbroke <[EMAIL PROTECTED]> wrote: > I had some free time this afternoon so I put together an > (experimental) patch for GHC that implements helpful errors messages. > Have a look at this GHCi session to see what I mean: > > "" > $ stage2/ghc-inplace --interactive -fhelpful-errors > GHCi, version 6.9.20080711: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer ... linking ... done. > Loading package base ... linking ... done. > Prelude> let foo = 10 > Prelude> foa > > :1:0: >Not in scope: `foa' >Maybe you meant one of: > `foo' > `fst' > `not' -- Maybe the matching threshold could stand to be tweaked That's pretty cool. Unfortunately in my early Haskell days the 'not in scope' errors were the only ones I _did_ understand. It would be nice to human-friendlify the other types of errors. I'm not judging your work though, this is helpful, and the other types of errors are of course much harder to friendlify. On the topic of things that aren't stupid complaints by me, a typo is the most likely cause for not in scope errors. As Evan points out, I think it would be more helpful to search for matching names in imported modules to see if the name was accidentally not qualified or exported. I don't know about this fuzzy matching business, since when I go to the line of the error message, I'm going to see my typo and what I meant. I don't think I'd ever use the suggestions... Luke ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Template Haskell and haskell-src-exts
> Can one represent the ''Type template Haskell syntax of > > $( makeMergeable ''FileDescriptorProto ) > > in haskell-src.exts Language.Haskell.Exts.Syntax ? > > And what are the HsReify data (e.g. HsReifyType and HsReifyDecl and > HsReifyFixity )? > > I don't see any pretty print capability to produce the ''Type so I am > wondering what else I might use... Hi Chris, like Jeremy said the support for TH in haskell-src-exts is legacy from GHC pre-6.4 (iirc) and needs updating. So don't look too closely at the things that are in there right now. It shouldn't be hard to fix to work with 6.8, I just need to find the time to sit down and do it. I'll try to get it fixed this week. Cheers, /Niklas ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Human-friendly compiler errors for GHC
2008/7/12 Evan Laforge <[EMAIL PROTECTED]>: >> What do you think about this feature? Would it be genuinely helpful or >> annoying? > > It could be handy if it understands qualified names. Occasionally > typos e.g. just now Confg.default_x are surprisingly hard to see and I > go around making sure Config is imported, making sure it exports > default_x, etc. before finally figuring it out. Good point. It turns out that actually since my implementation doesn't include module names in the match at all, this works without writing more code on my part. But perhaps I should make it module-aware as I think that will allow more accurate matching. I've also changed the output format and tweaked the match threshold algorithm, with this result: "" [EMAIL PROTECTED] ~/Programming/Checkouts/ghc.working/compiler $ stage2/ghc-inplace --interactive -fhelpful-errors GHCi, version 6.9.20080711: http://www.haskell.org/ghc/ :? for help Prelude> let foo = 10 Prelude> foa :1:0: Not in scope: `foa' Maybe you meant `foo' Prelude> fts :1:0: Not in scope: `fts' Maybe you meant `fst' Prelude> let foa = 20 Prelude> fof :1:0: Not in scope: `fof' Maybe you meant `foo' or `foa' Prelude> import Data.Lost Could not find module `Data.Lost': -- Maybe it should do something better here.. Use -v to see a list of the files searched for. Prelude> :q $ stage2/ghc-inplace --make Test.hs [1 of 1] Compiling Main ( Test.hs, Test.o ) Test.hs:5:14: Not in scope: `Chbr.isSpoce' Maybe you meant `Char.isSpace' """ Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANNOUNCE: vector 0.1 (efficient arrays with lots of fusion)
Sebastian Sylvan wrote: Is there any more (easily-digested, like a paper) information available about this? Specifically what things can happen in-place, and future extensions... Apart from the stream fusion papers, unfortunately no, it's all very much work in progress. Basically, at the moment it will avoid allocating some unnecessary arrays even if no loop fusion happens. So for instance, in something like map f (xs // us) the two loops can't be fused ((//) is the same update operation as in Data.Array). Usually, you'd allocate one array for (xs // us) and then another one for the map. This library will do the map in-place if f doesn't change the type of the elements. This is pretty important at least for data-parallel code. I'll have to see how far this scales. In the future, the fusion system will also be able to handle multiple directions of traversals and permutations (it can only do left-to-right traversals at the moment). The "Rewriting Haskell Strings" paper talks a bit about that but DPH has much more complex requirements so I'll have to use a different approach which I haven't implemented so far. Roman ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Human-friendly compiler errors for GHC
> What do you think about this feature? Would it be genuinely helpful or > annoying? It could be handy if it understands qualified names. Occasionally typos e.g. just now Confg.default_x are surprisingly hard to see and I go around making sure Config is imported, making sure it exports default_x, etc. before finally figuring it out. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Human-friendly compiler errors for GHC
> Personally, I would suggest make it take up less space. A newline for each > match may be alright if there are only 3 suggestions, but past that it begins > to take up too much of the screen. Columns are nice, or perhaps a limit on > how many matches will be displayed (with more available if the user asks?). I've actually limited it to 3 matches displayed in the current implementation, but indeed it would probably be good to display the matches in columns instead. Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Human-friendly compiler errors for GHC
I had some free time this afternoon so I put together an (experimental) patch for GHC that implements helpful errors messages. Have a look at this GHCi session to see what I mean: "" $ stage2/ghc-inplace --interactive -fhelpful-errors GHCi, version 6.9.20080711: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer ... linking ... done. Loading package base ... linking ... done. Prelude> let foo = 10 Prelude> foa :1:0: Not in scope: `foa' Maybe you meant one of: `foo' `fst' `not' -- Maybe the matching threshold could stand to be tweaked a bit, e.g. scaled with identifier string length.. Prelude> let myIdentifier = 10 Prelude> myIdentfiier :1:0: Not in scope: `myIdentfiier' Maybe you meant `myIdentifier' Prelude> "" The feature was inspired by the equivalent feature in the Boo programming language (http://boo.codehaus.org/). I use the restricted Damerau–Levenshtein distance to do the fuzzy match (http://en.wikipedia.org/wiki/Damerau-Levenshtein_distance). What do you think about this feature? Would it be genuinely helpful or annoying? Max ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANNOUNCE: vector 0.1 (efficient arrays with lots of fusion)
On 7/12/08, Roman Leshchinskiy <[EMAIL PROTECTED]> wrote: > > Hi all, > > the vector library will eventually provide fast, Int-indexed arrays with a > powerful fusion framework. It's very immature at the moment (I haven't > tested most of the code) and implements just a few combinators but I > thought releasing early wouldn't hurt. Use at your own risk and expect > things to break horribly! > > What it provides: > > * Boxed and unboxed arrays with a generic interface and a very basic >set of combinators. > > * A powerful loop fusion framework. It is based on stream fusion but >already goes beyond that (in particular, it can do some things >in-place) and will be significantly extended in the future. > (moving to cafe) Is there any more (easily-digested, like a paper) information available about this? Specifically what things can happen in-place, and future extensions... -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862 ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANNOUNCE: vector 0.1 (efficient arrays with lots of fusion)
Hello Roman, Saturday, July 12, 2008, 7:01:05 PM, you wrote: > the vector library will eventually provide fast, Int-indexed arrays with > a powerful fusion framework. GREAT! doom4 would be written in Haskell! -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] ANNOUNCE: vector 0.1 (efficient arrays with lots of fusion)
Hi all, the vector library will eventually provide fast, Int-indexed arrays with a powerful fusion framework. It's very immature at the moment (I haven't tested most of the code) and implements just a few combinators but I thought releasing early wouldn't hurt. Use at your own risk and expect things to break horribly! What it provides: * Boxed and unboxed arrays with a generic interface and a very basic set of combinators. * A powerful loop fusion framework. It is based on stream fusion but already goes beyond that (in particular, it can do some things in-place) and will be significantly extended in the future. * Extensibility. * Rudimentary documentation. * Bugs. The code is based on the DPH libraries but is much more generic and a *lot* simpler. This has only been made possible by the tremendous progress in GHC's simplifier in the recent months/years (thanks Simon!). Consequently, you'll need a recent development version of GHC to build this, 6.8 won't work. It might be able to compile the library but you'll get terrible code, much worse than with lists. If you want to try it out, compile with -O2 -fno-spec-constr-count and please don't forget to let me know about things that didn't work (or, miraculously, did). Grab it from http://hackage.haskell.org/cgi-bin/hackage-scripts/package/vector or darcs get http://darcs.haskell.org/vector Again, special thanks to Simon for doing such a wonderful job with the optimiser. Enjoy, Roman ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
RE: [Haskell-cafe] FPGA / Lava and haskell
Hello, Here are some more references relevant to ForSyDe, which looks very interesting! The following paper describes the first version of Hydra, a functional hardware description language which has gone through many versions, using several different functional languages. Hydra uses streams for modelling synchronous circuits, and the paper contains references to the first work on streams for hardware description, by Steve Johnson. Note that the syntax in this paper isn't Haskell; after all, Hydra was initially implemented in 1982, and Haskell didn't exist then! www.dcs.gla.ac.uk/~jtod/publications/1987-HDRE/ The mid 80s version of Hydra had multiple semantics, including both behaviour and netlist generation, and it used observable sharing to implement the netlists. That's described in the following paper, which also shows how Hydra can (optionally) use combinators to express layout and wiring. The geometric combinators are based on Mary Sheeran's Ruby language, although the actual combinators in Hydra are a bit different. The main difference between Hydra and Ruby is that Hydra is functional, it's based on streams, and the geometric combinators are optional: you can just use connect the streams together if all you want is a simulation and netlist but not a layout. www.dcs.gla.ac.uk/~jtod/publications/1988-HydraCombinators The netlists are represented as a data structure, and can be converted to a particular netlist notation with a suitable "show" function. The paper doesn't use the term "observable sharing" -- that name for the technique was introduced in Lava -- but the technique was already implemented and published in 1988. Lava is essentially a clone of Hydra the way it was from around 1985 to about 1992. However, there are a number of drawbacks to using observable sharing for generating netlists, and some of these are discussed in the following paper, which also proposes an alternative approach based on program transformation. www.dcs.gla.ac.uk/~jtod/publications/1992-Netlist The program transformation approach to netlist generation has been implemented using Template Haskell to perform the transformations automatically, as described in the next paper. Currently, Hydra uses this, and it avoids observable sharing. www.dcs.gla.ac.uk/~jtod/publications/2004-EmbedHDLinTH/ Here are a few more papers that give an overview of Hydra with some examples,: www.dcs.gla.ac.uk/~jtod/publications/1995-Hydra-FPLE/ www.dcs.gla.ac.uk/~jtod/publications/2002-Hydra-PDSECA/ www.dcs.gla.ac.uk/~jtod/publications/2004-DeriveFastAdder/ John O'Donnell -Original Message- From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Alfonso Acosta Sent: 09 July 2008 03:27 To: Marc Weber; haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] FPGA / Lava and haskell We'll soon (before september, hopefully) relase a deep-embedded version of ForSyDe[1] which, among other things, has a VHDL backend (with specific support for Altera's Modelsim and Quartus). ForSyDe's new implementation is internally based upon the same concept as Lava (Observable Sharing). However, it has quite a few differences: * ForSyDe is behavioural (computations are expressed in plain haskell) * It has support for components * Is not barely targeted at synchrounous hardware systems (although the VHDL backend is obviously aimed at them). It has suport for other MoCs (Models of Computation). [1] http://www.imit.kth.se/info/FOFU/ForSyDe/ On Tue, Jul 8, 2008 at 7:43 PM, Marc Weber <[EMAIL PROTECTED]> wrote: > Is Haskell still used (in industry as well ?) to write (V)HDL code to > program FPGAs and create circuits on chips? > The Chalmers Lava homepage tells abouta Xilinx version which should be > merged in soon. But on the xilinx homepage there was no reference to > neither Lava nor haskell.. > I'm thinking about designing a similar tool to www.combimouse.com. > > Sincerly > Marc > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe