Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Ryan Ingram
Sure, but it's easy to roll your own from those primitives: {-# LANGUAGE MagicHash, UnboxedTuples #-} import GHC.Exts addCarry :: Int -> Int -> (Int, Bool) addCarry (I# x) (I# y) = case addIntC# x y of (# s, c #) -> case c of 0# -> (I# s, False) _ -> (I# s, True) or someth

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Ryan Ingram
Actually, looking at the docs, I'm not sure if case expressions work on unboxed ints; you may need addCarry (I# x) (I# y) = case addIntC# x y of (# s, c #) -> (I# s, c /=# 0#) which is somewhat simpler anyways. -- ryan On Tue, Jul 31, 2012 at 1:56 AM, Ryan Ingram wrote: > Sure, but it's eas

[Haskell-cafe] CRIP: the Curiously Reoccuring Instance Pattern

2012-07-31 Thread oleg
Ryan Ingram wrote: > I've been seeing this pattern in a surprising number of instance > definitions lately: > > instance (a ~ ar, b ~ br) => Mcomp a ar b br [1] > instance (b ~ c, CanFilterFunc b a) => CanFilter (b -> c) a [2] And here are a few more earlier instances of the same occurrence:

[Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alexander Foremny
Hello list, I am currently thinking that a problem of mine would best be solved if there was a Map-like data structure in which the value returned is parametrized over the lookup type. I wonder is this makes sense and if such a data structure exists or if it could be created while still being wel

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Michael Snoyman
On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny wrote: > Hello list, > > I am currently thinking that a problem of mine would best be solved if > there was a Map-like data structure in which the value returned is > parametrized over the lookup type. > > I wonder is this makes sense and if such

[Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Sai Hemanth K
Hi, I am trying to use haskell for building a tool (in a commercial setting). I am trying to figure out what all licenses are involved here. Is there a single license for the entire haskell platform (and the runtime) or is it that I need to look at the individual licenses of all the libraries a

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alexander Foremny
Dear Michael, thank you very much for your quick and interesting response. This looks very much like what I want! Regards, Alexander Foremny 2012/7/31 Michael Snoyman : > On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny > wrote: >> Hello list, >> >> I am currently thinking that a problem of m

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alexander Foremny
At first glance I noticed some problems with the vault library for my particular approach. Despite from being unique, Key values don't appear to carry any information like the Label I need. However, it might be possible to work around that. The more grave problem seems to be that a Key cannot be

Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-31 Thread Richard Cobbe
On Mon, Jul 30, 2012 at 11:45:38PM +1000, Ivan Lazar Miljenovic wrote: > On 30 July 2012 04:04, Richard Cobbe wrote: > > I'm working on an application that involves processing a lot of Unicode > > data, and I'm finding the built-in Show implementation for Char to be > > really inconvenient. Speci

Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Magnus Therning
On Tue, Jul 31, 2012 at 12:29 PM, Sai Hemanth K wrote: > Hi, > > > I am trying to use haskell for building a tool (in a commercial setting). I > am trying to figure out what all licenses are involved here. > Is there a single license for the entire haskell platform (and the runtime) > or is it th

Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-31 Thread Ivan Lazar Miljenovic
On 31 July 2012 21:01, Richard Cobbe wrote: > On Mon, Jul 30, 2012 at 11:45:38PM +1000, Ivan Lazar Miljenovic wrote: >> On 30 July 2012 04:04, Richard Cobbe wrote: >> > I'm working on an application that involves processing a lot of Unicode >> > data, and I'm finding the built-in Show implementat

Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-31 Thread Henk-Jan van Tuyl
On Tue, 31 Jul 2012 00:42:40 +0200, wrote: On a side note, image based CAPACHA's can cause problems for blind people. Googles ReCaptcha can pronounce the text to type. Regards, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -

Re: [Haskell-cafe] What does unpacking an MVar really mean?

2012-07-31 Thread Bertram Felgenhauer
Leon Smith wrote: > I am familiar with the source of Control.Concurrent.MVar, and I do see {-# > UNPACK #-}'ed MVars around, for example in GHC's IO manager. What I > should have asked is, what does an MVar# look like? This cannot be > inferred from Haskell source; though I suppose I could

Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-31 Thread Henk-Jan van Tuyl
On Tue, 31 Jul 2012 00:59:28 +0200, Alexander Solla wrote: Does anybody have statistics about how often pages are edited/added? In the last seven days, there were 251 new (user)pages created; there was no spam added to existing pages. I also discovered spam added to pages at http://ha

Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Sai Hemanth K
Thanks Magnus. I guess it means that the license of individual packages is what that matters. The platform on the whole does not have any single license. In other words, I cannot just say that am using haskell platform but that I have to say, I am using x,y and z libraries which in turn are using

Re: [Haskell-cafe] specifying using type class

2012-07-31 Thread Patrick Browne
Hi,Thanks for all the very useful feed back on this thread.I would like to present my possibly incorrect summarized  view:Class signatures can contain placeholders for constructors.These place-holder-constructors cannot be used in the class to define functions (I assume other in-scope constructors

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alp Mestanogullari
Would ixset or HiggsSet be suitable? http://hackage.haskell.org/package/ixset http://hackage.haskell.org/package/HiggsSet On Tue, Jul 31, 2012 at 12:56 PM, Alexander Foremny < alexanderfore...@gmail.com> wrote: > At first glance I noticed some prob

Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread James Cook
Another option which allows you to define your own key type is the dependent-map[1] package. It requires implementing some classes for your key type that encode a proof that key equality entails equality of the type indices. If the documentation is insufficient feel free to ask me for more det

Re: [Haskell-cafe] How to define a Monad instance

2012-07-31 Thread Thiago Negri
Thanks for the reply Ryan. That's exactly the type of thing I was trying to do: use the syntactical sugar of do-notation to express some replacement rules. Why am I doing this? A long time ago, when I was learning C, I did a small project (spaghetti code) to encrypt text files in some user-defin

[Haskell-cafe] IMAGE_FILE_LARGE_ADDRESS_AWARE (4GB on Win64) ... any best practices??

2012-07-31 Thread Nick Rudnick
Dear Haskellers, did anybody of you stumble about surprisingly having a 2GB memory limit on Win64? I admit I didn't get it at once (just about to finish a complete memcheck... ;-) -- but of course there already is a discussion of this: http://stackoverflow.com/questions/10743041/making-use-of-al

Re: [Haskell-cafe] What does unpacking an MVar really mean?

2012-07-31 Thread Leon Smith
On Tue, Jul 31, 2012 at 7:37 AM, Bertram Felgenhauer < bertram.felgenha...@googlemail.com> wrote: > Note that MVar# itself cannot be unpacked -- the StgMVar record will > always be a separate heap object. One could imagine a couple of techniques to unpack the MVar# itself, and was curious if GH

[Haskell-cafe] ANN: stm-sbchan-0.1 - STM channel with maximum total size of items

2012-07-31 Thread Joey Adams
This package provides a bounded channel type for STM. TBChan (in stm-chans) and TBQueue (introduced in stm 2.4) are bounded channels that limit the number of items in the channel. SBChan, on the other hand, limits the total size of items in the channel, where "size" is defined by providing an ins

[Haskell-cafe] Explicit forall - Strange Error

2012-07-31 Thread Shayan Najd Javadipour
Hi, I wonder why the following code doesn't typecheck in GHC 7.4.1: {-# LANGUAGE GADTs,RankNTypes #-}data T a where T1 :: (forall b. b -> b) -> (forall a. Int -> T a) {- Error: Data constructor `T1' returns type `forall a. Int -> T a' instead of an instance of its parent type `T a' In t

Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Andres Löh
Hi. On Mon, Jul 30, 2012 at 8:47 AM, Евгений Пермяков wrote: > Can someone tell me if there are any primitives, that used to detect machine > type overflows, in ghc haskell ? I perfectly understand, that I can build > something based on preconditioning of variables, but this will kill any > perfo

Re: [Haskell-cafe] Explicit forall - Strange Error

2012-07-31 Thread MigMit
It really seems to me that the error message you've got explains everything quite clear. Отправлено с iPad 31.07.2012, в 22:59, Shayan Najd Javadipour написал(а): > Hi, > > I wonder why the following code doesn't typecheck in GHC 7.4.1: > > {-# LANGUAGE GADTs,RankNTypes #-} > data T a where

Re: [Haskell-cafe] Explicit forall - Strange Error

2012-07-31 Thread Shayan Najd Javadipour
If GHC handles the explicit "forall" in constructor "T1" in the same way as it does for function "f", we have: data T a where T1 :: (forall b. b -> b) -> Int -> T a Which is totally fine! The main question is then why the "forall"s are handled differently? On Tue, Jul 31, 2012 at 9:07 PM, MigMi

Re: [Haskell-cafe] Explicit forall - Strange Error

2012-07-31 Thread Brandon Allbery
On Tue, Jul 31, 2012 at 2:59 PM, Shayan Najd Javadipour wrote: > {-# LANGUAGE GADTs,RankNTypes #-}data T a where T1 :: (forall b. b -> b) -> > (forall a. Int -> T a) > {- Error: > Data constructor `T1' returns type `forall a. Int -> T a' > instead of an instance of its parent type `T a' > >

Re: [Haskell-cafe] Reddy on Referential Transparency

2012-07-31 Thread Chris Dornan
Uday Reddy has followed up with another substantial and interesting post on referential transparency here: http://stackoverflow.com/questions/210835/what-is-referential-transparency/11740176#11740176 The thrust of his argument appears to be that functional programmers have created a lot of

Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Carter Schonwald
it looks like ghc itself is under a BSD3 style license, if thats any help. So per se, I think you can assume youre dealing with a BSD3 through and through system. see here for the ghc info http://www.haskell.org/ghc/license (this is something i've been sorting out for my own projects too, and to

[Haskell-cafe] The following is supposed to be initializing a 2D array but it doesn't seem to work.

2012-07-31 Thread KC
newArr :: (Ix i) => i -> i -> e -> Array i e newArr n m x = listArray (n,m) (repeat x) - Prelude Data.Array> newArr 0 10 0 array (0,10) [(0,0),

Re: [Haskell-cafe] The following is supposed to be initializing a 2D array but it doesn't seem to work.

2012-07-31 Thread Ivan Lazar Miljenovic
On 1 August 2012 07:52, KC wrote: > newArr :: (Ix i) => i -> i -> e -> Array i e > > newArr n m x = listArray (n,m) (repeat x) > > > - > > Prelude Data.Array> newArr 0 10 0 > > array (0,10) > [(0,0),(1,0),(2,0),(3,0),(4,0),(5,0),(6,0),(7,0),(8,0),(9,0),(10,0)] > > > Prelude Data.Array> newArr

Re: [Haskell-cafe] specifying using type class

2012-07-31 Thread Ertugrul Söylemez
Patrick Browne wrote: > Thanks for all the very useful feed back on this thread. > I would like to present my possibly incorrect summarized  view: > Class signatures can contain placeholders for constructors. > These place-holder-constructors cannot be used in the class to define > functions (I a

Re: [Haskell-cafe] CRIP: the Curiously Reoccuring Instance Pattern

2012-07-31 Thread AntC
okmij.org> writes: > > [... snip] > > Of course instances above are overlapping. And when we add functional > dependencies (since we really want type-functions rather type > relations), they stop working at all. We had to employ work-arounds, > which are described in detail in the HList paper

Re: [Haskell-cafe] The following is supposed to be initializing a 2D array but it doesn't seem to work.

2012-07-31 Thread KC
That was it! On Tue, Jul 31, 2012 at 3:34 PM, Jan-Willem Maessen wrote: > > > On Tue, Jul 31, 2012 at 5:52 PM, KC wrote: > >> All I am getting is this: >> >> array ((1,5),(1,5)) [((1,5),1.0)] >> >> Maybe the behaviour of ghc was changed since the article was written. >> > > I think you've made a

Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-31 Thread Richard Cobbe
On Tue, Jul 31, 2012 at 09:17:34PM +1000, Ivan Lazar Miljenovic wrote: > On 31 July 2012 21:01, Richard Cobbe wrote: > > On Mon, Jul 30, 2012 at 11:45:38PM +1000, Ivan Lazar Miljenovic wrote: > >> Can I ask what you're doing here? Are you printing individual > >> characters or entire chunks of te

Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Thomas Schilling
You may concatenate the licenses of all the packages you are using. GHC includes the LGPL libgmp. The license file for each package is mentioned in the .cabal file. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/list