Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote: | I remember a similar discussion a few years ago. The question of whether | or not overloading list literals a good idea notwithstanding, the problem | with this is that fromList for vectors is highly inefficient. So if | something like this gets implemented

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote: | pointer to the actual data somewhere in memory and use that. This is | more or less what happens for strings at the moment, even though you | have to use rewrite rules to get at the pointer which, in my opinion, is | neither ideal nor really necessary. IMO, the

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Roman Leshchinskiy
Michael Snoyman wrote: The simplest example I can think of is allowing easier usage of Vector: [1, 2, 3] :: Vector Int In order to allow this, we could use a typeclass approach similar to how OverloadedStrings works: class IsList a where fromList :: [b] - a b

Re: [Haskell-cafe] Dynamic Programming with Data.Vector

2012-09-18 Thread Roman Leshchinskiy
Myles C. Maxfield wrote: Aha there it is! Thanks so much. I didn't see it because it's under the Unfolding section instead of the Construction section. You're quite right, having a separate Unfolding section isn't the best idea. I'll fix this. Roman On Mon, Sep 17, 2012 at 6:07 AM, Roman

Re: [Haskell-cafe] Dynamic Programming with Data.Vector

2012-09-17 Thread Roman Leshchinskiy
Myles C. Maxfield wrote: Overall, I'm looking for a function, similar to Data.Vector's 'generate' function, but instead of the generation function taking the destination index, I'd like it to take the elements that have previously been constructed. Is there such a function? If there isn't

Re: [Haskell-cafe] Performance with do notation, mwc-random and unboxed vector

2012-06-13 Thread Roman Leshchinskiy
On 12 Jun 2012, at 12:52, Dmitry Dzhus d...@dzhus.org wrote: 12.06.2012, 01:08, Roman Leshchinskiy r...@cse.unsw.edu.au: perhaps the state hack is getting in the way. I don't quite understand the internals of this yet, but `-fno-state-hack` leads to great performance in both cases! How

Re: [Haskell-cafe] vector operations

2012-06-11 Thread Roman Leshchinskiy
On 11/06/2012, at 18:52, Evan Laforge wrote: On Tue, May 29, 2012 at 12:52 PM, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: Vector should definitely fuse this, if it doesn't it's a bug. Please report if it doesn't for you. To verify, just count the number of letrecs in the optimised

Re: [Haskell-cafe] Performance with do notation, mwc-random and unboxed vector

2012-06-11 Thread Roman Leshchinskiy
On 11/06/2012, at 10:38, Dmitry Dzhus wrote: Consider this simple source where we generate an unboxed vector with million pseudo-random numbers: 8 - import qualified Data.Vector.Unboxed as VU import System.Random.MWC import System.Random.MWC.Distributions (standard) count =

Re: [Haskell-cafe] vector operations

2012-05-29 Thread Roman Leshchinskiy
On 29/05/2012, at 19:49, Evan Laforge wrote: Good question.. I copied both to a file and tried ghc-core, but it inlines big chunks of Data.Vector and I can't read it very well, but it looks like the answer is no, it still builds the the list of sums. I guess the next step is to benchmark and

Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-30 Thread Roman Leshchinskiy
Marc Weber wrote: Replying to all replies at once: Malcolm Wallace At work, we have a strict version of Haskell :-) which proofs that it is worth thinking about it. But doesn't necessarily prove that it's a good idea. Just (Item id ua t k v) -

Re: [Haskell-cafe] strict version of Haskell - does it exist?

2012-01-30 Thread Roman Leshchinskiy
Marc Weber wrote: Replying to all replies at once: Malcolm Wallace At work, we have a strict version of Haskell :-) which proofs that it is worth thinking about it. But doesn't necessarily prove that it's a good idea. Just (Item id ua t k v) -

Re: [Haskell-cafe] Unboxed Rationals?

2012-01-12 Thread Roman Leshchinskiy
On 12/01/2012, at 21:01, Artyom Kazak wrote: Yves Parès limestr...@gmail.com писал(а) в своём письме Thu, 12 Jan 2012 13:14:16 +0200: uvector is deprecated, its functionnalities has been ported into vector. Yes, but a Ratio a instance hasn't been ported. FWIW, vector isn't a port of

Re: [Haskell-cafe] Unboxed Rationals?

2012-01-11 Thread Roman Leshchinskiy
On 11/01/2012, at 17:00, Artyom Kazak wrote: In fact, I am surprised that Data.Vector doesn't have a Ratio instance, but has a Complex instance. Any ideas, why? Nobody has asked for it so far. Roman ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Documenting strictness properties for Data.Map.Strict

2011-11-18 Thread Roman Leshchinskiy
Johan Tibell wrote: map (\ v - undefined)  ==  undefined mapKeys (\ k - undefined)  ==  undefined Not really related to the question but I don't really understand how these properties can possibly hold. Shouldn't it be: map (\v - undefined) x = undefined And even then, does

Re: [Haskell-cafe] Stream fusion

2011-11-18 Thread Roman Leshchinskiy
Yves Parès wrote: While re-reading RealWorldHaskell, chapter 25, I saw that -- unlike I believed -- loop fusion wasn't activated by default under GHC for lists (but that module Data.List.Stream from package stream-fusion could provide it). Note that stream fusion is only one way to do

Re: [Haskell-cafe] Data.Vector.Mutable.mapM

2011-10-23 Thread Roman Leshchinskiy
Joachim Breitner wrote: Hi, I’m consdering to change some performance critical code from Vector to MVector, hopefully avoiding a lot of copying and garbage collecting. But it seems that the Data.Vector.Mutable interface at

Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-19 Thread Roman Leshchinskiy
Conrad Parker wrote: On 15 October 2011 23:18, Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote: On 16 October 2011 01:15, Bas van Dijk v.dijk@gmail.com wrote: I agree that you shouldn't use ByteStrings or Vectors of Word8s for Unicode strings. However I can imagine that for quick

Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-19 Thread Roman Leshchinskiy
Ivan Lazar Miljenovic wrote: On 19 October 2011 22:09, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: So it seems that (1) people have very different requirements and (2) the Show instance only really matters for debugging in ghci. Here is a thought. What if ghci allowed Show instances

Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-17 Thread Roman Leshchinskiy
Michael Snoyman wrote: On Mon, Oct 17, 2011 at 12:14 PM, Bas van Dijk v.dijk@gmail.com wrote: My idea is that when vector-bytestring is as fast as bytestring, it can replace it. When that happens it doesn't matter if users use the vector interface. I would even recommend it over using

Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Roman Leshchinskiy
On 14/10/2011, at 12:37, Bas van Dijk wrote: If there's need for a specific Show instance for Vectors of Word8s we can always add one directly to vector. (Roman, what are your thoughts on this?) Personally, I think that ByteString and especially Vector Word8 aren't strings and shouldn't be

Re: [Haskell-cafe] ANNOUNCE: vector-bytestring-0.0.0.0

2011-10-15 Thread Roman Leshchinskiy
On 15/10/2011, at 12:26, Roman Leshchinskiy wrote: On 14/10/2011, at 12:37, Bas van Dijk wrote: If there's need for a specific Show instance for Vectors of Word8s we can always add one directly to vector. (Roman, what are your thoughts on this?) Personally, I think that ByteString

Re: [Haskell-cafe] Combining stream and list fusion

2011-10-12 Thread Roman Leshchinskiy
Bas van Dijk wrote: Hello, I'm trying to make the following faster: Data.Vector.Generic.fromList list where 'list' is some expression yielding a list. Unfortunately, I don't think that's possible. The problem is that you 'list' will be expressed in terms of foldr/build and fromList would

Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-28 Thread Roman Leshchinskiy
On 25/09/2011, at 18:20, Chris Smith wrote: class Ord a = Range a where rangeFromTo :: a - a - [a] -- subsumes Ix.range / Enum.enumFromTo rangeFromThenTo :: a - a - a - [a] inRange :: (a, a) - a - Bool -- Does have instances for Float/Double. List ranges desugar to this. -- Also

Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-28 Thread Roman Leshchinskiy
On 28/09/2011, at 23:23, Ivan Lazar Miljenovic wrote: On 29 September 2011 07:56, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: On 25/09/2011, at 18:20, Chris Smith wrote: class Ord a = Range a where rangeFromTo :: a - a - [a] -- subsumes Ix.range / Enum.enumFromTo rangeFromThenTo

Re: [Haskell-cafe] Data.IArray rant

2011-09-06 Thread Roman Leshchinskiy
Jon Fairbairn wrote: Roman Leshchinskiy r...@cse.unsw.edu.au writes: No, arrays were not considered to be bad, they were designed with parallelism in mind. I'm not sure how this can be the case if, as discussed below, most array operations have to go through lists, an inherently sequential

Re: [Haskell-cafe] Idiomatic usage of the fixpoint library

2011-09-05 Thread Roman Leshchinskiy
Roman Cheplyaka wrote: {-# LANGUAGE TypeFamilies, FlexibleContexts, UndecidableInstances, FlexibleInstances #-} import Data.Fixpoint newtype Expr = Expr { unExpr :: Pre Expr Expr } instance Functor (Pre Expr) = Fixpoint Expr where data Pre Expr a = Add

Re: [Haskell-cafe] Data.IArray rant

2011-09-03 Thread Roman Leshchinskiy
On 03/09/2011, at 03:04, Ivan Lazar Miljenovic wrote: On 3 September 2011 11:38, Evan Laforge qdun...@gmail.com wrote: The result is that my first contact with haskell arrays left me with the impression that they were complicated, hard to use, and designed for someone with different

Re: [Haskell-cafe] attoparsec and vectors

2011-06-29 Thread Roman Leshchinskiy
Gregory Collins wrote: On Tue, Jun 28, 2011 at 6:20 PM, Eric Rasmussen ericrasmus...@gmail.com wrote: It runs quickly, but I naively thought I could outperform it by reworking many to build a vector directly, instead of having to build a list first and then convert it to a vector: manyVec

Re: [Haskell-cafe] Is fusion overrated?

2011-05-18 Thread Roman Leshchinskiy
Roman Cheplyaka wrote: Of course I don't claim that fusion is useless -- just trying to understand the problem it solves. Are we saving a few closures and cons cells here? In addition to what everyone else said, fusion can be a big win when it allows further optimisations. For instance,

Re: [Haskell-cafe] ANN: unordered-containers - a new, faster hashing-based containers library

2011-02-23 Thread Roman Leshchinskiy
Johan Tibell wrote: I'm working on a patch that provides O(1) size right now. The trick is to define HashMap as: data HashMap k v = HM {-# UNPACK #-} !Int !(Tree k v) Another possibility is: data HashMap k v = HM Int !(Tree k v) hashMap t = HM (treeSize t) t That way size is O(n) on first

Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote: 2011/2/15 Simon Peyton-Jones simo...@microsoft.com: but currently any pragmas in a class decl are treated as attaching to the *default method*, not to the method selector: I see. I didn't realise that that was what was happening. Personally I find this a bit

Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote: On 15 February 2011 11:23, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: I wouldn't necessarily expect this to guarantee inlining for the same reason that the following code doesn't guarantee that foo gets rewritten to big: foo = bar {-# INLINE bar #-} bar = big

Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote: On 15 February 2011 15:12, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: Ah, but you assume that bar won't be inlined into foo first. Consider that it is perfectly acceptable for GHC to generate this: foo = big {-# INLINE bar #-} bar = big We did ask to inline bar

Re: [Haskell-cafe] rewrite rules to specialize function according to type class?

2011-02-15 Thread Roman Leshchinskiy
Max Bolingbroke wrote: On 15 February 2011 16:45, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: Only if foo has an INLINE pragma. Otherwise, GHC uses whatever RHS is available when it wants to inline. Ah, I see! Well yes, in that case my workaround is indeed broken in the way you describe

Re: [Haskell-cafe] Vector library

2011-02-14 Thread Roman Leshchinskiy
Pierre-Etienne Meunier wrote: This is mostly a question for Roman : how do you use your vector library with multi-dimensional arrays ? I mean, the array library from the standard libraries does something more intelligent than the C-like solution with indirections. Vector doesn't include any

Re: [Haskell-cafe] ghc/dph

2010-12-15 Thread Roman Leshchinskiy
On 14/12/2010, at 13:35, Johannes Waldmann wrote: I want to use dph (data parallel haskell) for a presentation. (Nothing fancy, just compile and run some demos.) What ghc version should I use and where do I get it? That's a tricky question. We are currently working on getting DPH to work

Re: [Haskell-cafe] Type families again

2010-12-02 Thread Roman Leshchinskiy
On 2 Dec 2010, at 21:29, Andrew Coppin andrewcop...@btinternet.com wrote: Does anybody have any suggestions? class Mappable t a b where type Rebind t a b map :: (a - b) - t - Rebind a b This is based on an old C++ trick. Roman ___

Re: [Haskell-cafe] Eta-expansion and existentials (or: types destroy my laziness)

2010-10-17 Thread Roman Leshchinskiy
On 16/10/2010, at 12:36, Max Bolingbroke wrote: On 16 October 2010 12:16, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: eta :: Stream a - Stream a eta s = Stream s next where next (Stream s next') = case next' s of Just (x,s') - Just (x,Stream s' next

Re: [Haskell-cafe] Eta-expansion and existentials (or: types destroy my laziness)

2010-10-16 Thread Roman Leshchinskiy
On 16/10/2010, at 12:00, Max Bolingbroke wrote: Hi Cafe, I've run across a problem with my use of existential data types, whereby programs using them are forced to become too strict, and I'm looking for possible solutions to the problem. I'm going to explain what I mean by using a

Re: [Haskell-cafe] Construction of short vectors

2010-06-27 Thread Roman Leshchinskiy
On 25/06/2010, at 06:41, Alexey Khudyakov wrote: Then constructor like one below arise naturally. And I don't know how to write them properly. It's possible to use fromList but then list could be allocated which is obviously wasteful. vector2 :: Double - Double - Vec2D vector2 x y = ...

Re: [Haskell-cafe] The mother of all functors/monads/categories

2010-06-27 Thread Roman Leshchinskiy
On 27/06/2010, at 19:54, Max Bolingbroke wrote: Q: What is the mother of all X, where X is some type class? A: It is a data type D such that: 1. There exist total functions: lift :: X d = d a - D a lower :: X d = D a - d a Are those universally quantified over d? If so, then none of

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Roman Leshchinskiy
On 19/05/2010, at 19:24, Dmitry Olshansky wrote: Prelude [1,1+2/3..10]

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Roman Leshchinskiy
On 19/05/2010, at 20:36, Ivan Lazar Miljenovic wrote: Roman Leshchinskiy r...@cse.unsw.edu.au writes: Personally, I consider the Enum class itself to be broken. Oh? In what sense? Firstly, the enumFrom* family of functions shouldn't be methods and the class itself should provide enough

Re: [Haskell-cafe] Bug with [Double]

2010-05-19 Thread Roman Leshchinskiy
On 19/05/2010, at 23:44, Ben Millwood wrote: On Wed, May 19, 2010 at 10:57 AM, Serguey Zefirov sergu...@gmail.com wrote: PS Rationals: Prelude [1,1+2/3..10] :: [Rational] [1 % 1,5 % 3,7 % 3,3 % 1,11 % 3,13 % 3,5 % 1,17 % 3,19 % 3,7 % 1,23 % 3,25 % 3,9 % 1,29 % 3,31 % 3] Same result.

Re: [Haskell-cafe] Numerical Analysis

2010-05-17 Thread Roman Leshchinskiy
On 17/05/2010, at 05:17, Gregory Crosswhite wrote: As an aside, while there are advantages to writing numerical analysis routines in Haskell, it might be better strategy to instead link in something like LAPACK and provide nice wrappers to it in Haskell, since this way you can harness the

Re: [Haskell-cafe] Numerical Analysis

2010-05-17 Thread Roman Leshchinskiy
On 17/05/2010, at 02:52, Pierre-Etienne Meunier wrote: You are quite right that vector only supports nested arrays but not multidimensional ones. This is by design, however - the library's only goal is to provide efficient one-dimensional, Int-indexed arrays. I'm thinking about how to

Re: [Haskell-cafe] Numerical Analysis

2010-05-16 Thread Roman Leshchinskiy
On 16/05/2010, at 10:17, Pierre-Etienne Meunier wrote: I've also just noticed a lack in the vector library : multidimensional arrays seem to require indirections like in caml, whereas in C or in Data.Ix, there is a way to avoid this. This is especially important for avoiding cache misses

Re: [Haskell-cafe] Monadic style with Streams (as in Data.Array.Parallel.Stream)

2010-05-16 Thread Roman Leshchinskiy
On 16/05/2010, at 11:54, Mark Wassell wrote: Hi, This possibly might go against the spirit of what Stream programming is about but I having difficulties converting an imperative algorithm [1] into Haskell and think it would be easier if I was able to write it in a monadic style with

Re: [Haskell-cafe] Strict type system allows for a maximum number of programming errors to be caught at compile time.

2010-05-04 Thread Roman Leshchinskiy
On 04/05/2010, at 13:30, Luke Palmer wrote: On Mon, May 3, 2010 at 11:07 AM, Kyle Murphy orc...@gmail.com wrote: The fact that it doesn't is proof enough that there's a problem with it even if that problem is simply that the types you're using aren't exactly correct. Further, I'd argue that

Re: [Haskell-cafe] Haskell and the Software design process

2010-05-03 Thread Roman Leshchinskiy
On 03/05/2010, at 06:02, Jaco van Iterson wrote: I was just wondering what methods are best to design/model the software in bigger projects when you are planning to use Haskell. Is there no difference compared to other languages? Are there any Haskell tools? In addition to what Don said,

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-26 Thread Roman Leshchinskiy
On 24/04/2010, at 22:42, Roman Leshchinskiy wrote: On 24/04/2010, at 22:06, Barak A. Pearlmutter wrote: I was thinking of this: data T = T Double deriving ( Eq, Ord ) ... GHC basically produces instance Ord T where compare (T x) (T y) = compare x y t u = compare t u == LT

Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-24 Thread Roman Leshchinskiy
On 24/04/2010, at 07:29, Don Stewart wrote: Oh, the Platform has very strict standards about APIs, What is an API? The package versioning policy only seems to talk about types and function signatures. John's old-locale example shows that this is not enough. Would it perhaps make sense for at

Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-24 Thread Roman Leshchinskiy
On 24/04/2010, at 18:06, Ivan Lazar Miljenovic wrote: Roman Leshchinskiy r...@cse.unsw.edu.au writes: On 24/04/2010, at 07:29, Don Stewart wrote: Oh, the Platform has very strict standards about APIs, What is an API? The package versioning policy only seems to talk about types

Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-24 Thread Roman Leshchinskiy
On 24/04/2010, at 18:54, Ivan Lazar Miljenovic wrote: Roman Leshchinskiy r...@cse.unsw.edu.au writes: On 24/04/2010, at 18:06, Ivan Lazar Miljenovic wrote: I would think that the API is all the functions/classes/datatypes/instances/etc. exported from the library in combination

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-24 Thread Roman Leshchinskiy
On 24/04/2010, at 19:56, Barak A. Pearlmutter wrote: And yet a lot of generic code is written in terms of compare. That's can be an advantage, because often that code *should* blow up when it gets a NaN. E.g., sorting a list of Floats which includes a NaN. However, often you will know

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-24 Thread Roman Leshchinskiy
On 24/04/2010, at 22:06, Barak A. Pearlmutter wrote: Currently the standard prelude has default definition: ... compare x y | x == y= EQ | x = y= LT | otherwise = GT I'd suggest [...] compare x y | x y = LT | x

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-23 Thread Roman Leshchinskiy
On 23/04/2010, at 01:34, Barak A. Pearlmutter wrote: I'd suggest that compare involving a NaN should yield error violation of the law of the excluded middle Please think of the poor guys trying to write high-performance code in Haskell! Roman

Re: [Haskell-cafe] Proper Handling of Exceptional IEEE Floating Point Numbers

2010-04-23 Thread Roman Leshchinskiy
On 24/04/2010, at 07:15, Barak A. Pearlmutter wrote: In all seriousness, I think it is reasonable when isNaN x for x C x == C x C C x C == x C x to all be False, for all floats C, even C=x, as a sort of efficient weak Bool bottom. This is what the FP hardware does --- so it is very

Re: [Haskell-cafe] vector recycling

2010-04-18 Thread Roman Leshchinskiy
On 18/04/2010, at 08:07, Ben wrote: On Fri, Apr 16, 2010 at 11:19 PM, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: That said, it would be quite possible to provide something like the following: fold_inplace :: Vector v a = (v a - b - v a) - v a - [b] - v a as far as i understand

Re: [Haskell-cafe] vector recycling

2010-04-17 Thread Roman Leshchinskiy
On 17/04/2010, at 13:32, Ben wrote: module Main where import qualified Data.Vector.Generic as V import qualified Data.Vector.Unboxed as UV type Vec = UV.Vector Double axpy :: Double - Vec - Vec - Vec axpy a x y = V.zipWith (+) (V.map (* a) x) y sumVecs :: [(Double, Vec)] - Vec

Re: [Haskell-cafe] Strange error with type classes + associated types

2010-04-17 Thread Roman Leshchinskiy
On 17/04/2010, at 11:00, Conal Elliott wrote: I'm unsure now, but I think I tried making Basis a data type (not syn) and ran into the problem I mentioned above. The Basis *synonyms* also have HasTrie instances, which is crucially important. If we switch to (injective) data types, then we

Re: [Haskell-cafe] Floyd Warshall performance (again)

2010-04-16 Thread Roman Leshchinskiy
On 16/04/2010, at 18:06, Mathieu Boespflug wrote: shortestPath :: [(Int, Int, Int)] - UArray Int Int shortestPath g = runSTUArray $ do let mnew = newArray (0, SIZE * SIZE) 1 mread arr i j = unsafeRead arr (i * SIZE + j) mwrite arr i j x = unsafeWrite arr (i * SIZE + j) x

Re: [Haskell-cafe] Vector to Monadic Stream and back, how?

2010-04-14 Thread Roman Leshchinskiy
On 14/04/2010, at 09:05, Xiao-Yong Jin wrote: I want to use 'mapM' on Data.Vector.Vector, but it looks like the only 'mapM' defined is in Data.Vector.Fusion.Stream.Monadic. I'm able to use 'stream' and 'liftStream' to convert a 'Vector' to a monadic stream, on which I can use 'mapM'. But I

Re: [Haskell-cafe] Strange error with type classes + associated types

2010-04-14 Thread Roman Leshchinskiy
On 15/04/2010, at 00:30, Brent Yorgey wrote: On Wed, Apr 14, 2010 at 09:51:52AM +0100, Stephen Tetley wrote: On 14 April 2010 03:48, Brent Yorgey byor...@seas.upenn.edu wrote: Can someone more well-versed in the intricacies of type checking with associated types explain this? Or is this a

Re: [Haskell-cafe] what are the safety conditions for unsafeIOToST

2010-04-07 Thread Roman Leshchinskiy
On 08/04/2010, at 01:38, Henning Thielemann wrote: On Apr 6, 2010, at 5:30 PM, Roman Leshchinskiy wrote: In fact, the only safe-ish use for it I have found is to use Storable-related functions in ST, hoping that the instances don't actually use any real IO functionality. Arguably

Re: [Haskell-cafe] what are the safety conditions for unsafeIOToST

2010-04-06 Thread Roman Leshchinskiy
On 07/04/2010, at 07:33, Nicolas Frisby wrote: I haven't been able to find it via Google or Haddock. An old message suggests is was just a matter of exceptions? I don't think that's correct. You can implement unsafePerformIO in terms unsafeIOToST: unsafePerformIO :: IO a - a unsafePerformIO

Re: [Haskell-cafe] Re: replicateM over vectors

2010-04-04 Thread Roman Leshchinskiy
On 04/04/2010, at 05:33, Chad Scherrer wrote: Roman Leshchinskiy rl at cse.unsw.edu.au writes: Ah. I missed that. Then your best bet is probably replicate n action = munstream v $ Fusion.Stream.Monadic.generateM n (const action) $ new n It's uglier

Re: [Haskell-cafe] replicateM over vectors

2010-04-01 Thread Roman Leshchinskiy
On 02/04/2010, at 12:16, Don Stewart wrote: Chad.Scherrer: Hi, I'd like to be able to do replicateM, but over a vector instead of a list. Right now I'm doing this: The operation you are looking for is called newWith. It probably should be called replicate. Roman? Can we generate frozen

Re: [Haskell-cafe] replicateM over vectors

2010-04-01 Thread Roman Leshchinskiy
On 02/04/2010, at 13:01, Don Stewart wrote: rl: replicate :: Int - a - New a replicate n x = Generic.New.unstream (Fusion.Stream.replicate n x) and then either Mutable.run (replicate n x) to get a mutable vector or new (replicate n x) Hmm, but here 'a' is pure. I don't

Re: [Haskell-cafe] Re: Data Structures GSoC

2010-03-31 Thread Roman Leshchinskiy
On 31/03/2010, at 18:14, Achim Schneider wrote: We have a lot of useful interfaces (e.g. ListLike, Edison), but they don't seem to enjoy wide-spread popularity. Perhaps that's an indication that we need different interfaces? IMO, huge classes which generalise every useful function we can

Re: [Haskell-cafe] Shootout update

2010-03-31 Thread Roman Leshchinskiy
I'm wondering... Since the DPH libraries are shipped with GHC by default are we allowed to use them for the shootout? Roman On 30/03/2010, at 19:25, Simon Marlow wrote: The shootout (sorry, Computer Language Benchmarks Game) recently updated to GHC 6.12.1, and many of the results got worse.

Re: [Haskell-cafe] GHC vs GCC vs JHC

2010-03-29 Thread Roman Leshchinskiy
On 29/03/2010, at 02:27, Lennart Augustsson wrote: Does anything change if you swap the first two rhss? No, not as far as I can tell. On Sun, Mar 28, 2010 at 1:28 AM, Roman Leshchinskiy r...@cse.unsw.edu.au wrote: On 28/03/2010, at 09:47, Lennart Augustsson wrote: It's important

Re: [Haskell-cafe] GHC vs GCC

2010-03-27 Thread Roman Leshchinskiy
On 28/03/2010, at 01:36, Jan-Willem Maessen wrote: It's worth pointing out that there's a bit of bang-pattern mysticism going on in this conversation (which has not been uncommon of late!). A non-buggy strictness analyzer should expose the strictness of these functions without difficulty.

Re: [Haskell-cafe] GHC vs GCC vs JHC

2010-03-27 Thread Roman Leshchinskiy
On 27/03/2010, at 05:27, John Meacham wrote: Here are jhc's timings for the same programs on my machine. gcc and ghc both used -O3 and jhc had its full standard optimizations turned on. jhc: ./hs.out 5.12s user 0.07s system 96% cpu 5.380 total gcc: ./a.out 5.58s user 0.00s system 97%

Re: [Haskell-cafe] GHC vs GCC vs JHC

2010-03-27 Thread Roman Leshchinskiy
On 28/03/2010, at 11:07, John Meacham wrote: I have not thoroughly checked it, but I think there are a couple things going on here: It could also be worthwhile to float out (i*i + j*j) in rangeK instead of computing it in every loop iteration. Neither ghc nor gcc can do this; if jhc can then

Re: [Haskell-cafe] GHC vs GCC vs JHC

2010-03-27 Thread Roman Leshchinskiy
On 28/03/2010, at 09:47, Lennart Augustsson wrote: It's important to switch from mod to rem. This can be done by a simple abstract interpretation. Also, changing the definition of rem from a `rem` b | b == 0 = divZeroError | a == minBound b == (-1) =

Re: [Haskell-cafe] Performance question

2010-03-18 Thread Roman Leshchinskiy
On 19/03/2010, at 08:48, Daniel Fischer wrote: Am Donnerstag 18 März 2010 21:57:34 schrieb Daniel Fischer: Contrary to my expectations, however, using unboxed arrays is slower than straight arrays (in my tests). However, a few {-# SPECIALISE #-} pragmas set the record straight. This is

Re: [Haskell-cafe] vector stream fusion, inlining and compilation time

2010-03-07 Thread Roman Leshchinskiy
On 06/03/2010, at 03:10, stefan kersten wrote: i'm still curious, though, why my three versions of direct convolution perform so differently (see attached file). in particular, i somehow expected conv_3 to be the slowest and conv_2 to perform similar to conv_1. any ideas? i haven't had a

Re: [Haskell-cafe] Re: [Haskell] Recursive definition of fibonacci with Data.Vector

2010-03-07 Thread Roman Leshchinskiy
On 08/03/2010, at 12:17, Alexander Solla wrote: GHC even optimizes it to: fib = fib Sounds like an implementation bug, not an infinite dimensional vector space bug. My guess is that strictness is getting in the way, and forcing what would be a lazy call to fib in the corresponding

Re: [Haskell-cafe] vector stream fusion, inlining and compilation time

2010-03-04 Thread Roman Leshchinskiy
On 05/03/2010, at 04:34, stefan kersten wrote: i've been hunting down some performance problems in DSP code using vector and the single most important transformation seems to be throwing in INLINE pragmas for any function that uses vector combinators and is to be called from higher-level

Re: [Haskell-cafe] vector to uvector and back again

2010-02-12 Thread Roman Leshchinskiy
On 12/02/2010, at 23:28, Dan Doel wrote: On Thursday 11 February 2010 8:54:15 pm Dan Doel wrote: On Thursday 11 February 2010 12:43:10 pm stefan kersten wrote: On 10.02.10 19:03, Bryan O'Sullivan wrote: I'm thinking of switching the statistics library over to using vector. that would be

Re: [Haskell-cafe] vector to uvector and back again

2010-02-11 Thread Roman Leshchinskiy
On 12/02/2010, at 12:39, Don Stewart wrote: bos: I'm thinking of switching the statistics library over to using vector. uvector is pretty bit-rotted in comparison to vector at this point, and it's really seeing no development, while vector is The Shiny Future. Roman, would you call the

Re: [Haskell-cafe] vector to uvector and back again

2010-02-11 Thread Roman Leshchinskiy
On 12/02/2010, at 12:40, Don Stewart wrote: rl: On 11/02/2010, at 05:03, Bryan O'Sullivan wrote: I'm thinking of switching the statistics library over to using vector. uvector is pretty bit-rotted in comparison to vector at this point, and it's really seeing no development, while vector

Re: [Haskell-cafe] vector to uvector and back again

2010-02-11 Thread Roman Leshchinskiy
On 12/02/2010, at 12:54, Dan Doel wrote: I also notice that vector seems to have discarded the idea of Vec (A * B) = Vec A * Vec B Oh no, it hasn't. In contrast to uvector/DPH, which use a custom strict tuple type for rather outdated reasons, vector uses normal tuples. For instance,

Re: [Haskell-cafe] vector to uvector and back again

2010-02-11 Thread Roman Leshchinskiy
On 12/02/2010, at 13:49, Don Stewart wrote: rl: On 12/02/2010, at 12:39, Don Stewart wrote: bos: I'm thinking of switching the statistics library over to using vector. uvector is pretty bit-rotted in comparison to vector at this point, and it's really seeing no development, while vector

Re: [Haskell-cafe] vector to uvector and back again

2010-02-10 Thread Roman Leshchinskiy
On 11/02/2010, at 05:03, Bryan O'Sullivan wrote: I'm thinking of switching the statistics library over to using vector. uvector is pretty bit-rotted in comparison to vector at this point, and it's really seeing no development, while vector is The Shiny Future. Roman, would you call the

Re: [Haskell-cafe] Restrictions on associated types for classes

2009-12-17 Thread Roman Leshchinskiy
On 18/12/2009, at 00:37, Stephen Lavelle wrote: Given class MyClass k where type AssociatedType k :: * Is there a way of requiring AssociatedType be of class Eq, say? This works with -XFlexibleContexts: class Eq (AssociatedType k) = MyClass k where type AssociatedType k :: * Roman

Re: [Haskell-cafe] Boxed Mutable Arrays

2009-12-14 Thread Roman Leshchinskiy
On 15/12/2009, at 06:53, Brad Larsen wrote: On another note, does this (or perhaps better phrased, will this) bug also affect Data Parallel Haskell? Luckily, no. DPH represents arrays of user-defined types by unboxed arrays (that's essentially what the vectoriser does). It does use boxed

[Haskell-cafe] Re: [Haskell] ANN: NoSlow - Microbenchmarks for array libraries

2009-11-27 Thread Roman Leshchinskiy
On 28/11/2009, at 07:45, Henning Thielemann wrote: Is there also a darcs repository? Yes, http://www.cse.unsw.edu.au/~rl/code/darcs/NoSlow. Roman ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?

2009-11-18 Thread Roman Leshchinskiy
On 18/11/2009, at 21:10, Simon Peyton-Jones wrote: Yes I think it can, although you are right to point out that I said nothing about type inference. One minor thing is that you've misunderstood the proposal a bit. It ONLY springs into action when there's a dot. So you'd have to write

Re: [Haskell-cafe] Status of TypeDirectedNameResolution proposal?

2009-11-17 Thread Roman Leshchinskiy
Simon, have you given any thought to how this interacts with type system extensions, in particular with GADTs and type families? The proposal relies on being able to find the type of a term but it's not entirely clear to me what that means. Here is an example: foo :: F Int - Int foo :: Int -

Re: [Haskell-cafe] poor perfomance of indexU in uvector package

2009-11-16 Thread Roman Leshchinskiy
On 16/11/2009, at 22:46, Alexey Khudyakov wrote: Problems begin when you need non-contiguous block. Easiest way to so is indexing. FWIW, this operation is called backpermute and is probably exported as bpermute in uvector. Roman ___ Haskell-Cafe

Re: Re[2]: [Haskell-cafe] What's the deal with Clean?

2009-11-04 Thread Roman Leshchinskiy
On 05/11/2009, at 04:01, Bulat Ziganshin wrote: oh, can we stop saying about shootout? if you want to see speed of pure haskell code, look at papers about fast arrays/strings - their authors have measured that lazy lists are hundreds times slower than idiomatic C code. is use of lazy lists

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-03 Thread Roman Leshchinskiy
On 04/11/2009, at 13:23, Daniel Peebles wrote: In the presence of fusion (as is the case in uvector), it's hard to give meaningful time complexities for operations as they depend on what operations they are paired with. We need to think of a better way to express this behavior in the

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-03 Thread Roman Leshchinskiy
On 04/11/2009, at 13:12, brian wrote: indexU :: UA e = UArr e - Int - e O(n). indexU extracts an element out of an immutable unboxed array. This is a typo (unless Don inserted a nop loop into the original DPH code). Roman ___ Haskell-Cafe

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-03 Thread Roman Leshchinskiy
On 04/11/2009, at 13:35, wren ng thornton wrote: Roman Leshchinskiy wrote: On 04/11/2009, at 13:23, Daniel Peebles wrote: In the presence of fusion (as is the case in uvector), it's hard to give meaningful time complexities for operations as they depend on what operations they are paired

Re: [Haskell-cafe] What's the deal with Clean?

2009-11-03 Thread Roman Leshchinskiy
On 04/11/2009, at 14:07, Gregory Crosswhite wrote: Actually, it's not a typo. If you look at the source, what you'll see is indexU arr n = indexS (streamU arr) n I suspect it gets rewritten back to the O(1) version somewhere after is has had a chance to fuse. If not, then it's a bug. In

Re: [Haskell-cafe] Arrays in Clean and Haskell

2009-11-03 Thread Roman Leshchinskiy
On 04/11/2009, at 14:38, Philippos Apolinarius wrote: And here comes the reason for writing this article. In the previous version of the Gauss elimination algorithm, I have imported Data.Array.IO. I also wrote a version of the program that imports Data.Array.ST. The problem is that I

Re: [Haskell-cafe] Stream-fusion without the lists

2009-05-12 Thread Roman Leshchinskiy
On 12/05/2009, at 14:45, Reiner Pope wrote: The Stream datatype seems to be much better suited to representing loops than the list datatype is. So, instead of programming with the lists, why don't we just use the Stream datatype directly? I think the main reason is that streams don't store

Re: [Haskell-cafe] bytestring vs. uvector

2009-03-08 Thread Roman Leshchinskiy
On 09/03/2009, at 11:47, Claus Reinke wrote: Btw, have any of the Haskell array optimization researchers considered fixpoints yet? This, for instance, is a very nice paper: http://www.pllab.riec.tohoku.ac.jp/~ohori/research/OhoriSasanoPOPL07.pdf However, in the context of high-performance

  1   2   >