Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Colin Paul Adams
Judah == Judah Jacobson judah.jacob...@gmail.com writes: Judah On Wed, Aug 19, 2009 at 10:31 AM, Iain Barnettiainsp...@gmail.com wrote: Quick question: I've tested this in a couple of different terminals (roxterm and xterm), so I'm fairly sure it's GHC that's the problem.

Re[2]: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Bulat Ziganshin
Hello Colin, Thursday, August 20, 2009, 10:13:28 AM, you wrote: I don't understand where latin-1 comes into this. String is supposed to be a list of Unicode characters. but ghc 6.10 i/o used String as list of bytes -- Best regards, Bulat

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Colin Paul Adams
Bulat == Bulat Ziganshin bulat.zigans...@gmail.com writes: Bulat Hello Colin, Bulat Thursday, August 20, 2009, 10:13:28 AM, you wrote: I don't understand where latin-1 comes into this. String is supposed to be a list of Unicode characters. Bulat but ghc 6.10 i/o used String

[Haskell-cafe] Right way to implement setPixel function

2009-08-20 Thread CK Kashyap
Hi, I had posted a note on line drawing algo with Haskell some time back. Now, I am trying to write a PNM image. import qualified Data.ByteString as B width = 256 height = 256 bytesInImage = width * height * 3 blankImage = B.pack $ take bytesInImage (repeat 0) type Color = (Int,Int,Int)

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Stuart Cook
On Thu, Aug 20, 2009 at 4:28 PM, Colin Paul Adamsco...@colina.demon.co.uk wrote: But how do you get Latin-1 bytes from a Unicode string? This would need a transcoding process. The first 256 code-points of Unicode coincide with Latin-1. Therefore, if you truncate Unicode characters down to 8

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Colin Paul Adams
Stuart == Stuart Cook sco...@gmail.com writes: Stuart On Thu, Aug 20, 2009 at 4:28 PM, Colin Paul Stuart Adamsco...@colina.demon.co.uk wrote: But how do you get Latin-1 bytes from a Unicode string? This would need a transcoding process. Stuart The first 256 code-points of

Re[2]: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Bulat Ziganshin
Hello Colin, Thursday, August 20, 2009, 11:12:53 AM, you wrote: Yes, but surely this will work both ways. The same bytes on input should come back on output, shouldn't they? only ascii subset that have fixed encoding. the rest may migrate in some way -- Best regards, Bulat

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Stuart Cook
On Thu, Aug 20, 2009 at 5:12 PM, Colin Paul Adamsco...@colina.demon.co.uk wrote: Yes, but surely this will work both ways. The same bytes on input should come back on output, shouldn't they? I would have thought so, but apparently this isn't actually what happens. GHCi, version 6.8.2:

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ryan Ingram
On Wed, Aug 19, 2009 at 1:20 PM, Peter Verswyvelenbugf...@gmail.com wrote: Well I really wrote this code as an exercise, and it was a good one. Now I (or someone) needs to explain why it works. There's a bit of trickiness, but it's not that hard when you break it down. Lets look at a

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
This is very very informative, thanks. One thing I still struggle with (because I haven't practiced much I guess) is writing down the desugaring/evaluation/expansion/reduction (how do you call it?). I know how to do it more or less (tried it for a fix fac, since fix feels like magic for an

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Ketil Malde
Stuart Cook sco...@gmail.com writes: GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. Prelude map Data.Char.ord 饁 [39233]== 0x9941 Prelude putStrLn 饁 A == 0x41 It seems that GHCi is clever enough to

[Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Max Desyatov
Hi, all. I've come into trouble defining function `gmap` which will work on these data types: data Row = Row (E Name) (E Salary) (E Department) type E a = Either (Maybe RowIndex) (Maybe a) type RowIndex = Int `RowIndex`, `Name`, `Salary`, `Department` have kind *

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Jules Bean
Peter Verswyvelen wrote: Not at all, use it for whatever you want to :-) I'm writing this code because I'm preparing to write a bunch of tutorials on FRP, and I first wanted to start with simple console based FRP, e.g. making a little text adventure game, where the input/choices of the user

[Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Max Desyatov
Sorry for a type and probably confusing you, it must be: readRow l = gmap (\(Left (Just ri)) - Right $ l `atMay` ri = readMay) instead of l `atMay` c ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Re: Keeping an indexed collection of values?

2009-08-20 Thread Heinrich Apfelmus
Job Vranish wrote: I've been in a situation a lot lately where I need to keep a collection of values, and keep track of them by a persistent index. data IndexedCollection a = IndexedCollection { nextKey :: Int, availableKeys :: [Int], items :: IntMap a } deriving

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
I don't fully understand. interact gives you a stream of input characters that the user types, and produces a stream of output characters that are displayed back (with buffering set to NoBuffering). it should behave predictable no? and since the input that the user gives depends on the output on

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Iain Barnett
2009/8/20 Ketil Malde ke...@malde.org Stuart Cook sco...@gmail.com writes: GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. Prelude map Data.Char.ord 饁 [39233]== 0x9941 Prelude putStrLn 饁 A ==

Re: [Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Sean Leather
Hi Max, I've come into trouble defining function `gmap` which will work on these data types: data Row = Row (E Name) (E Salary) (E Department) type E a = Either (Maybe RowIndex) (Maybe a) type RowIndex = Int `RowIndex`, `Name`, `Salary`, `Department` have kind *

[Haskell-cafe] Parsec lookahead and |

2009-08-20 Thread Martijn van Steenbergen
Goedemiddag café, Consider the following function, using parsec-3.0.0: la :: Parsec String () (Maybe Char) la = lookAhead (optionMaybe anyChar) *Lookahead parseTest (char 'a' | char 'b') a 'a' *Lookahead parseTest (char 'a' | char 'b') b 'b' *Lookahead parseTest (la * char 'a' | char 'b') a

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Brandon S. Allbery KF8NH
On Aug 20, 2009, at 05:07 , Ketil Malde wrote: % ghci -e 'map Data.Char.ord 饁' interactive:1:21: lexical error in string/character literal at character '\129' but again: % ghci -e 'map Data.Char.ord £' [194,163] So GHCi used interactively translates input from the

[Haskell-cafe] ANNOUNCE: ministg-0.2, an interpreter for STG operational semantics

2009-08-20 Thread Bernie Pope
I'm pleased to announce the first public release of Ministg. Ministg is an interpreter for a high-level, small-step, operational semantics for the STG machine. The STG machine is the abstract machine at the core of GHC. The operational semantics used in Ministg is taken from the paper Making a

[Haskell-cafe] Tips for deployment?

2009-08-20 Thread Günther Schmidt
Hi all, my haskell app is getting closer to shipping and what I need to do now is to give product protection some thought. The product is for hospitals and therefore a very limited set of clients. I do not expect anyone to try to hack my application but I need a basic protection mechanism

Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Wed, Aug 19, 2009 at 8:32 AM, Jules Beanju...@jellybean.co.uk wrote: Do not blame haskell, blame emacs, if emacs is so stupid. How can you blame emacs? Do you expect emacs to read programmer's minds? John ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread Jules Bean
John D. Ramsdell wrote: On Wed, Aug 19, 2009 at 8:32 AM, Jules Beanju...@jellybean.co.uk wrote: Do not blame haskell, blame emacs, if emacs is so stupid. How can you blame emacs? Do you expect emacs to read programmer's minds? No, I expect emacs to select a suitable first indentation

Re: [Haskell-cafe] Re: Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Wed, Aug 19, 2009 at 11:38 PM, Chung-chieh Shanccs...@post.harvard.edu wrote: Thanks!  Another small change that might shorten the code is to use Data.Map for linear combinations: I chose to use association lists because I did not want to explain the adjust function one would use to

Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk wrote: I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant. Let's put this issue in perspective. For those few Haskell programmers that do find layout

Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread John D. Ramsdell
On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk wrote: I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant. Let's put this issue in perspective. For those few Haskell programmers that do find layout

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
It seems that with Ryan's approach, DList is not needed, simple concat works fine. It also seems to run in constant space. Now I must do the exercise of rewriting it to see why concat works, since = is infixl and ++ is infixr, this seems odd :) But again, my mind might be thinking too strict (bad

Re: [Haskell-cafe] gbp sign showing as unknown character by GHC

2009-08-20 Thread Iain Barnett
Got this back from the bug tracker 6.12.1 will have Unicode support in the IO library which mostly fixes this problem. The rest is fixed by #3398. Iain ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Where does documentation get installed with cabal?

2009-08-20 Thread Colin Paul Adams
Hello, I'm trying to find the API documentation for happstack 0.3 (online is for 0.2). So I did: cabal install happstack --reinstall --enable-documentation but I can't find it anywhere within ~/.cabal - where should I look? -- Colin Adams Preston Lancashire

Re: [Haskell-cafe] Unifcation and matching in Abelian groups

2009-08-20 Thread Jules Bean
John D. Ramsdell wrote: On Thu, Aug 20, 2009 at 9:08 AM, Jules Beanju...@jellybean.co.uk wrote: I don't find layout a problem, with good editor support. I agree it's a problem, with poor editor support. That's all I meant. Let's put this issue in perspective. For those few Haskell

RE: [Haskell-cafe] generalize RecordPuns and RecordWildCards to work with qualified names?

2009-08-20 Thread Simon Peyton-Jones
Evan, Lennart Thanks for the provocation. I've committed a patch that fixes all these issues. Try now! Simon Thu Aug 20 13:34:43 BST 2009 simo...@microsoft.com * Improvements to record puns, wildcards * Make C { A.a } work with punning, expanding to C { A.a = a } * Make it so

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Leimbach
On Thu, Aug 20, 2009 at 2:52 AM, Jules Bean ju...@jellybean.co.uk wrote: Peter Verswyvelen wrote: Not at all, use it for whatever you want to :-) I'm writing this code because I'm preparing to write a bunch of tutorials on FRP, and I first wanted to start with simple console based FRP, e.g.

Re: [Haskell-cafe] Where does documentation get installed with cabal?

2009-08-20 Thread Max Desyatov
Colin Paul Adams co...@colina.demon.co.uk writes: I'm trying to find the API documentation for happstack 0.3 (online is for 0.2). So I did: cabal install happstack --reinstall --enable-documentation but I can't find it anywhere within ~/.cabal - where should I look? In most cases it is

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Leimbach
and since the input that the user gives depends on the output on the screen (it represents the user - machine dialog loop), we must make sure that laziness does not go wild and strictness is needed to respect this dependency. But as Ryan showed, seq is not really needed (but pattern

Re: [Haskell-cafe] Where does documentation get installed with cabal?

2009-08-20 Thread Colin Paul Adams
Max == Max Desyatov explicitc...@googlemail.com writes: Max Colin Paul Adams co...@colina.demon.co.uk writes: I'm trying to find the API documentation for happstack 0.3 (online is for 0.2). So I did: cabal install happstack --reinstall --enable-documentation

Re: [Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Max Desyatov
Sean Leather leat...@cs.uu.nl writes: I'm not sure the problem you're running into is strictly a generic programming (GP) one. Typically, GP takes code that is often written and generalizes it, so that it doesn't have to be written for multiple datatypes. That seems to be GP problem, as your

[Haskell-cafe] Can't derive Binary for StdGen

2009-08-20 Thread Grigory Sarnitskiy
Hello! I'm trying to derive Binary for StdGen with DrIFT: module Main where import System.Random import Data.Binary {-!for StdGen derive : Binary !-} data Foo = Foo StdGen StdGen deriving (Show) {-! derive : Binary !-} but I got error DrIFT: can't find module System/Random What shall I do?

Re: [Haskell-cafe] Parsec lookahead and |

2009-08-20 Thread Job Vranish
Yeah, that's weird. I played around with la and it seems to only cause problems when the parser passed into lookAhead succeeds, which seem to go directly against it's stated purpose. lookAhead isn't consuming, (hence the unexpected b) but still prevents | from doing it's thing. Seems like a

Re: [Haskell-cafe] Parsec lookahead and |

2009-08-20 Thread Daniel Fischer
Am Donnerstag 20 August 2009 13:44:15 schrieb Martijn van Steenbergen: Goedemiddag café, Consider the following function, using parsec-3.0.0: la :: Parsec String () (Maybe Char) la = lookAhead (optionMaybe anyChar) *Lookahead parseTest (char 'a' | char 'b') a 'a' *Lookahead parseTest

Re: [Haskell-cafe] Can't derive Binary for StdGen

2009-08-20 Thread Max Desyatov
Grigory Sarnitskiy sargrig...@ya.ru writes: Hello! I'm trying to derive Binary for StdGen with DrIFT: [...] but I got error DrIFT: can't find module System/Random What shall I do? I'd use http://hackage.haskell.org/packages/archive/derive/2.0.1/doc/html/Data-Derive-Binary.html instead.

[Haskell-cafe] Re: Haddock: Failed to create dependency graph (when adding sections with * or a module heading)

2009-08-20 Thread Jared Updike
Simple fix (terrible error message): Move the ( up to the line with the module name. Previous bad code: module Data.DualMap -- * The @DualMap@ abstract type ( DualMap () -- * (?) internal? -- exposed for testing purposes, for now... , dmFlip -- * converting

Re: [Haskell-cafe] Generics for constructing Rows

2009-08-20 Thread Sean Leather
That seems to be GP problem, as your solution doesn't scale well when I wan't to add/remove/change fields in the `Row` record. Ah yes, this is a good use case. I wasn't paying close enough attention before, and I didn't see an immediate implementation of your function at the time. The

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ryan Ingram
On Thu, Aug 20, 2009 at 7:37 AM, David Leimbachleim...@gmail.com wrote: I'm pretty certain that forcing a pattern match via case is what disallows the laziness to get out of hand.  The case statement, when evaluated, must choose a matched pattern branch, even if it's the only possibility, which

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ryan Ingram
On Thu, Aug 20, 2009 at 9:56 AM, Ryan Ingramryani.s...@gmail.com wrote: Compare these identical code fragments: Er, strike identical. Oops! Comparing identical fragments would be boring. -- ryan ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Right way to implement setPixel function

2009-08-20 Thread Job Vranish
Your setPixel function is almost ready to work in a State monad If you modify your setPixel function slightly like so: setPixel' :: Int - Int - Color - B.ByteString - ((), B.ByteString) setPixel' x y (r,g,b) image = ((), B.concat [beforePixel, pixel, afterPixel]) and then wrap it in the State

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Lennart Augustsson
Using seq to control a program's semantics (as in, input-output behaviour) is a horrible hack. The seq operation there to control space and time aspects of your program. (The specification of seq doesn't even say that the first argument is evaluated before the second one.) You should use data

Re: [Haskell-cafe] Right way to implement setPixel function

2009-08-20 Thread Job Vranish
Opps: setPixel = State setPixel' should be: setPixel x y rgb = State $ setPixel' x y rgb - Job On Thu, Aug 20, 2009 at 1:05 PM, Job Vranish jvran...@gmail.com wrote: Your setPixel function is almost ready to work in a State monad If you modify your setPixel function slightly like so:

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Ketil Malde
David Leimbach leim...@gmail.com writes: I'm pretty certain that forcing a pattern match via case is what disallows the laziness to get out of hand. The case statement, when evaluated, must choose a matched pattern branch, even if it's the only possibility, which ends up boiling down to seq

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Antoine Latter
On Thu, Aug 20, 2009 at 1:02 PM, Ketil Maldeke...@malde.org wrote: David Leimbach leim...@gmail.com writes: I'm pretty certain that forcing a pattern match via case is what disallows the laziness to get out of hand.  The case statement, when evaluated, must choose a matched pattern branch,

Re: [Haskell-cafe] Where does documentation get installed with cabal?

2009-08-20 Thread John Dorsey
I'm trying to find the API documentation for happstack 0.3 (online is for 0.2). [...] Max In most cases it is installed in Max ~/.cabal/share/doc/happstack*/html. Is there any files at Max that directory? There are now, but only a very few. And very little contents

[Haskell-cafe] Re: Parsec lookahead and |

2009-08-20 Thread Christian Maeder
Daniel Fischer wrote: Am Donnerstag 20 August 2009 13:44:15 schrieb Martijn van Steenbergen: Goedemiddag café, Consider the following function, using parsec-3.0.0: la :: Parsec String () (Maybe Char) la = lookAhead (optionMaybe anyChar) *Lookahead parseTest (char 'a' | char 'b') a 'a'

Re: [Haskell-cafe] Where does documentation get installed with cabal?

2009-08-20 Thread Antoine Latter
On Thu, Aug 20, 2009 at 8:58 AM, Colin Paul Adamsco...@colina.demon.co.uk wrote: Hello, I'm trying to find the API documentation for happstack 0.3 (online is for 0.2). So I did: cabal install happstack --reinstall --enable-documentation but I can't find it anywhere within ~/.cabal -

Re: [Haskell-cafe] Re: Parsec lookahead and |

2009-08-20 Thread Job Vranish
try works in this case, but it won't if we are using a parser which can consume and then fail (instead of char 'a'). In which case we may want it to fail without exploring the second option. Hmmm though you might be right. Having lookAhead return Consumed is only a problem if the parser passed to

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
I totally agree that data dependencies are the best way to do that. And I'm beginning to see why interact might not be suitable for demonstrating FRP. On the other hand, when you say data dependencies, you mean that the value of expression A depends on the value of expression B, but what if that

[Haskell-cafe] Re: Parsec lookahead and |

2009-08-20 Thread Daniel Fischer
Apologies to Christian for the double post, didn't look at the To-field. Am Thursday 20 August 2009 20:21:30 schrieben Sie: Daniel Fischer wrote: Am Donnerstag 20 August 2009 13:44:15 schrieb Martijn van Steenbergen: Goedemiddag café, Consider the following function, using parsec-3.0.0:

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Dan Weston
Peter, I think you are right that there is no way in general to prevent a valid graph rewrite to remove a vacuous dependency. That is why seq is there. The funny business is visible right in the type signature of seq: seq :: forall a t. a - t - t If seq had nonstrict semantics, this would

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 3:43 PM, Peter Verswyvelenbugf...@gmail.com wrote: Also doesn't Haskell's IO system uses a hidden RealWorld type that has no value but which is passed from between monadics binds in a strict way to make the ordering work? Haskell only describes how the IO monad

Re: [Haskell-cafe] Tips for deployment?

2009-08-20 Thread Don Stewart
gue.schmidt: Hi all, my haskell app is getting closer to shipping and what I need to do now is to give product protection some thought. The product is for hospitals and therefore a very limited set of clients. I do not expect anyone to try to hack my application but I need a basic

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
But how does GHC implement the RealWorld internally? I guess this can't be done using standard Haskell stuff? It feels to me that if I would implement it, I would need seq again, or a strict field, or some incrementing time value that is a strict argument of each of the IO primitives. In any case,

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 4:41 PM, Peter Verswyvelenbugf...@gmail.com wrote: But how does GHC implement the RealWorld internally? I guess this can't be done using standard Haskell stuff? It feels to me that if I would implement it, I would need seq again, or a strict field, or some incrementing

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Peter Verswyvelen
On Thu, Aug 20, 2009 at 11:23 PM, David Menendez d...@zednenem.com wrote: The important things to note are (1) getChar# depends on the token returned by putChar#, thus guaranteeing that putChar# gets executed first, and (2) putChar# and getChar# are impure and cannot normally be defined in

Re: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread David Menendez
On Thu, Aug 20, 2009 at 6:57 PM, Peter Verswyvelenbugf...@gmail.com wrote: On Thu, Aug 20, 2009 at 11:23 PM, David Menendez d...@zednenem.com wrote: The important things to note are (1) getChar# depends on the token returned by putChar#, thus guaranteeing that putChar# gets executed first,

Re[2]: [Haskell-cafe] Re: Where do I put the seq?

2009-08-20 Thread Bulat Ziganshin
Hello Peter, Friday, August 21, 2009, 12:41:35 AM, you wrote: But how does GHC implement the RealWorld internally? I guess look the base library sources for RealWorld -- Best regards, Bulatmailto:bulat.zigans...@gmail.com