Re: [Haskell-cafe] Using Cabal during development

2010-02-10 Thread Neil Brown
Don't you simply need to do what the error message says, and add (*in the Executable section*, at the end of the file): build-depends: SFML ? Limestraël wrote: I think I must be dumb or something. I did my SFML.cabal exactly the way the packager of vty-ui did vty-ui.cabal, and I still have go

Re: [Haskell-cafe] RFC: concurrent-extra

2010-02-16 Thread Neil Brown
Hi, I had a look at the code for Event (both versions) and Lock (but not the others just yet) and it seemed fine. If you do lots of calls to waitTimeout before a set you will accumulate old locks in the list, but that won't cause any error that I can see, so it would only be a problem in pat

Re: [Haskell-cafe] RFC: concurrent-extra

2010-02-17 Thread Neil Brown
Roel van Dijk wrote: 2010/2/16 Neil Brown : I had a look at the code for Event (both versions) and Lock (but not the others just yet) and it seemed fine. If you do lots of calls to waitTimeout before a set you will accumulate old locks in the list, but that won't cause any error that

Re: [Haskell-cafe] Pointfree composition for higher arity

2010-02-17 Thread Neil Brown
Sean Leather wrote: I find myself often writing this pattern: someFun x y z = ... fun y z = runFun $ someFun someDefault y z or, alternatively: fun y = runFun . someFun someDefault y I very often write this too (wanting function composition, but with a two-argument f

Re: [Haskell-cafe] CURL and threads

2010-02-18 Thread Neil Brown
Hi, Your code forks off N threads to do HTTP response checking, then waits for the reply (invokeThreads). Each thread (runHTTPThread) calls curlGetResponse and *immediately* sends the answer back down the channel to invokeThreads (checkAuthResponse) -- then waits for half a second before ter

Re: [Haskell-cafe] Re: Proper round-trip HughesPJ/Parsec for Doubles?

2010-02-25 Thread Neil Brown
Andy Gimblett wrote: 1. break the line after "do" (to avoid a layout change when change name or arguments of float' or rename the variable "e") I'm not convinced by this; perhaps while editing the code it's useful, but those changes don't happen very often, and when they do, any half-decent

[Haskell-cafe] ANN: Progression-0.3 (supporting benchmarking in Haskell)

2010-03-02 Thread Neil Brown
Hi all, I've just uploaded the new version of my Progression benchmarking library to Hackage (http://hackage.haskell.org/package/progression). Progression is a utility built on top of Criterion that helps you record benchmark times for several different versions of your code and then draw gr

[Haskell-cafe] Benchmarking and Garbage Collection

2010-03-04 Thread Neil Brown
Hi, I'm looking at benchmarking several different concurrency libraries against each other. The benchmarks involve things like repeatedly sending values between two threads. I'm likely to use Criterion for the task. However, one thing I've found is that the libraries have noticeably diffe

Re: [Haskell-cafe] Benchmarking and Garbage Collection

2010-03-04 Thread Neil Brown
Jesper Louis Andersen wrote: On Thu, Mar 4, 2010 at 7:16 PM, Neil Brown wrote: However, one thing I've found is that the libraries have noticeably different behaviour in terms of the amount of garbage created. In fact, CML relies on the garbage collector for some implement

Re: [Haskell-cafe] Benchmarking and Garbage Collection

2010-03-04 Thread Neil Brown
Jesper Louis Andersen wrote: On Thu, Mar 4, 2010 at 8:35 PM, Neil Brown wrote: CML is indeed the library that has the most markedly different behaviour. In Haskell, the CML package manages to produce timings like this for fairly simple benchmarks: %GC time 96.3% (96.0% elapsed) I

[Haskell-cafe] Re: Benchmarking and Garbage Collection

2010-03-05 Thread Neil Brown
Simon Marlow wrote: import Control.Concurrent import Control.Concurrent.CML import Control.Monad main :: IO () main = do let numChoices = 2 cs <- replicateM numChoices channel mapM_ forkIO [replicateM_ (10 `div` numChoices) $ sync $ transmit c () | c <- cs] replicateM_ 10 $ sync $ choo

Re: [Haskell-cafe] chp-plus doesn't install

2010-03-27 Thread Neil Brown
Colin Paul Adams wrote: I'm getting these errors (ghc 6.10.4 on Linux x86_64): Building chp-plus-1.1.0... [1 of 9] Compiling Control.Concurrent.CHP.Test ( Control/Concurrent/CHP/Test.hs, dist/build/Control/Concurrent/CHP/Test.o ) [2 of 9] Compiling Control.Concurrent.CHP.Console ( Control/Conc

Re: [Haskell-cafe] chp-plus doesn't install

2010-03-28 Thread Neil Brown
Neil Brown wrote: Colin Paul Adams wrote: I'm getting these errors (ghc 6.10.4 on Linux x86_64): Building chp-plus-1.1.0... [1 of 9] Compiling Control.Concurrent.CHP.Test ( Control/Concurrent/CHP/Test.hs, dist/build/Control/Concurrent/CHP/Test.o ) [2 of 9] Comp

Re: [Haskell-cafe] Re: Haskell.org re-design

2010-04-07 Thread Neil Brown
Thomas Schilling wrote: Here's a matching Wiki style: http://i.imgur.com/XkuzH.png I like your designs (I liked the blue and orange version, but all the colour schemes seem fine). For the wiki design, it would be good to re-think and cull those links at the top of the page. For exampl

Re: [Haskell-cafe] What is the consensus about -fwarn-unused-do-bind ?

2010-04-09 Thread Neil Brown
Ivan Lazar Miljenovic wrote: As of 6.12.1, the new -fwarn-unused-do-bind warning is activated with -Wall. This is based off a bug report by Neil Mitchell: http://hackage.haskell.org/trac/ghc/ticket/3263 . However, does it make sense for this to be turned on with -Wall? For starters, why should

Re: [Haskell-cafe] GHC, odd concurrency space leak

2010-04-15 Thread Neil Brown
Jason Dagit wrote: On Wed, Apr 14, 2010 at 3:13 PM, Daniel Fischer mailto:daniel.is.fisc...@web.de>> wrote: Am Mittwoch 14 April 2010 23:49:43 schrieb Jason Dagit: > > It will be interesting to hear what fixes this! > > > > > > forever' m = do _ <- m > >

Re: [Haskell-cafe] ANN: forkable-monad 0.1

2010-04-21 Thread Neil Brown
Hi, This is quite a neat generalisation of forkIO, and something I've wanted in the past. My comment would be about the MonadIO m requirement for ForkableMonad. I understand that conceptually it's a nice thing to have. But practically, I don't think it's necessary, and could be a little r

Re: [Haskell-cafe] What do _you_ want to see in FGL?

2010-04-26 Thread Neil Brown
Hi, Primarily I want to see in FGL: documentation, documentation and more documentation. The library has lots of undocumented functions (especially the queries, e.g. http://hackage.haskell.org/packages/archive/fgl/5.4.2.2/doc/html/Data-Graph-Inductive-Query-DFS.html has no documentation at a

Re: [Haskell-cafe] and [] = True; or [] = False

2010-04-26 Thread Neil Brown
Bjorn Buckwalter wrote: Dear all, Does it make good sense that 'and []' returns 'True' and 'or []' returns 'False'? It's certainly what I would expect it to do, based on several ways of thinking. 1: If we define the function using explicit recursion: and (x:xs) = x && and xs Therefore and []

[Haskell-cafe] The Poor Man's PVP-Checking Tool

2010-04-26 Thread Neil Brown
Hi, The issue of a tool to help with checking packages against the Package Versioning Policy (PVP: http://www.haskell.org/haskellwiki/Package_versioning_policy) has come up several times on this list, and it seems to be a generally wanted tool. One of the things desired in such a tool is the

Re: [Haskell-cafe] mixing map and mapM ?

2010-05-06 Thread Neil Brown
Bill Atkins wrote: Almost - "liftM modificationTime" has type Status -> IO EpochTime. Like other IO functions (getLine, putStrLn), it returns an IO action but accepts a pure value (the modification time) Also, I like this style: import Control.Applicative ((<$>)) blah = do times <- mapM

Re: [Haskell-cafe] TDD in Haskell

2010-05-25 Thread Neil Brown
On 25/05/10 12:36, Ionut G. Stan wrote: Hi, I'm doing TDD in pretty much all of the languages that I know, and I want to introduce it early in my Haskell learning process. I wonder though, if there's some established process regarding TDD, not unit testing. I've heard of QuickCheck and HUni

Re: [Haskell-cafe] learning advanced haskell

2010-06-14 Thread Neil Brown
On 14/06/10 06:42, Aran Donohue wrote: Hi Cafe, I've been doing Haskell for a few months, and I've written some mid-sized programs and many small ones. I've read lots of documentation and many papers, but I'm having difficulty making the jump into some of the advanced concepts I've read about

Re: [Haskell-cafe] MonadCatchIO-transformers and ContT

2010-06-21 Thread Neil Brown
Hi, Here's my guess. Take a look at this version, and try running it: === {-# LANGUAGE PackageImports #-} import qualified "MonadCatchIO-transformers" Control.Monad.CatchIO as C import Control.Monad.IO.Class import Control.Monad.Trans.Cont bracket_' :: C.MonadCatchIO m => m a -- ^

Re: [Haskell-cafe] Control.Alternative --- some and many?

2010-06-23 Thread Neil Brown
On 23/06/10 06:54, Christopher Done wrote: I'm not sure how Alternative differs from MonadPlus, other than being defined for Applicative rather than Monad. They have the same laws (identity and associativity). Importantly, MonadPlus must satisfy some laws for (>>=) and (>>), whereas Alter

[Haskell-cafe] Type constraints and classes

2009-04-26 Thread Neil Brown
Hi, I have a Haskell problem that keeps cropping up and I wondered if there was any solution/work-around/dirty-hack that could help. I keep wanting to define class instances for things like Functor or Monad, but with restrictions on the inner type. I'll explain with an example, because I fi

Re: [Haskell-cafe] Question about implementing an off-side rule in Parsec 2

2009-04-28 Thread Neil Brown
Bas van Gijzel wrote: Hello everyone, I'm doing a bachelor project focused on comparing parsers. One of the parser libraries I'm using is Parsec (2) and I'm going to implement a very small subset of haskell with it, with as most important feature the off-side rule (indentation based parsing)

Re: [Haskell-cafe] instance Monad (Except err)

2009-05-04 Thread Neil Brown
Martijn van Steenbergen wrote: Hello, Mr. McBride and mr. Paterson define in their Applicative paper: data Except e a = OK a | Failed e instance Monoid e => Applicative (Except e) where ... Sometimes I'd still like to use >>= on Excepts but this "feels" wrong somehow, because it doesn't use

Re: [Haskell-cafe] Parsec - Custom Fail

2009-05-05 Thread Neil Brown
Hi, When we needed to do something similar with Parsec, we chose to pack the relevant source position into the error string (you can just use Show/Read, plus a special sequence of characters to indicate where the position ends and the real error starts). We then unpack it outside runParser b

Re: [Haskell-cafe] Trying to contact authors of "Real World Haskell"?

2009-05-07 Thread Neil Brown
Itsme (Sophie) wrote: I could not find any contact info for Brian O'Sullivan, Don Stewart, or John Goerzen on their book site. Any pointers to how I might locate any of them much appreciated. Two of the three have posted to this list in the last 24 hours, so you can take their email addresses

Re: [Haskell-cafe] Why is Bool no instance of Num and Bits?

2009-05-08 Thread Neil Brown
Neil Mitchell wrote: I didn't at first, then I remembered: 1 + True = fromInteger 1 + True And if we have Num for Bool, it type checks. Does that also mean that you could write: if 3 - 4 then ... else ... (= if (fromInteger 3 :: Bool) - (fromInteger 4 :: Bool) then ... else ...) or per

Re: [Haskell-cafe] Simulation and GHC Thread Scheduling

2009-05-09 Thread Neil Brown
properly, the slight variation is actually a good test). What I would like to know is are there any plans for GHC to incorporate user-definable scheduler? What exactly is it that you want from a user-definable scheduler? Do you want co-operative scheduling in your program, or do you want to

Re: [Haskell-cafe] Just 3 >>= (1+)?

2009-05-09 Thread Neil Brown
Hi, (1+) :: Num a => a -> a For the bind operator, you need something of type a -> Maybe b on the RHS, not simply a -> a. You want one of these instead: fmap (1+) (Just 3) liftM (1+) (Just 3) Alternatively, you may find it useful to define something like: (>>*) = flip liftM so that you ca

Re: [Haskell-cafe] Decoupling OpenAL/ALUT packages from OpenGL

2009-05-12 Thread Neil Brown
Sven Panne wrote: Regarding Functor/Applicative: The obvious instances for e.g. a 2-dimensional vertex are: data Vertex2 a = Vertex2 a a instance Functor Vertex2 where fmap f (Vertex2 x y) = Vertex2 (f x) (f y) instance Applicative Vertex2 where pure a = Vertex2 a a

Re: [Haskell-cafe] List of exports of a module - are there alternatives?

2009-05-13 Thread Neil Brown
Maurício wrote: Hi, When we want to list which declarations are exported by a module we do: module Mod ( list of exports ) where ... Are there propositions to alternatives to that (I could not find one)? Like, say, add a "do export" or "do not export" tag to declarations we want to (not) expor

Re: [Haskell-cafe] Removing mtl from the Haskell Platform

2009-05-13 Thread Neil Brown
Sittampalam, Ganesh wrote: We've discussed replacing it with transformers+monads-fd+an mtl compatiblity layer on librar...@. Ross and I plan to propose doing this for the second release of the platform - it's not fair to disrupt the first release at this stage. transformers+monads-fd is quite a

Re: [Haskell-cafe] tips on using monads

2009-05-18 Thread Neil Brown
Michael P Mossey wrote: I've got one of those algorithms which "threatens to march off the right edge" (in the words of Goerzen et al). I need something like a State or Maybe monad, but this is inside the IO monad. So I presume I need StateT or MaybeT. However, I'm still (slowly) learning about

Re: [Haskell-cafe] Introducing Instances in GHC point releases

2009-05-22 Thread Neil Brown
Duncan Coutts wrote: What we're currently missing is a PVP checker: a tool to compare APIs of package versions and check that it is following the PVP. Ideally, we will have packages opt-in to follow the PVP for those packages that do opt-in we have the PVP enforced on hackage using the checker to

Re: [Haskell-cafe] FGL Question

2009-05-24 Thread Neil Brown
Hans van Thiel wrote: Hello, I want to get the top or the bottom elements of a graph, but the following code appears to give the wrong answer in most cases, and the right answer in a few cases. Any ideas? -- get the most general or the least general elements graphMLGen :: Bool -> Gr [Rule] (

[Haskell-cafe] ANN: alloy-1.0.0 (generic programming)

2009-06-08 Thread Neil Brown
Hi all, I've just put the first release of the Alloy generic programming library on Hackage [1]. Alloy (née Polyplate) is intended to be a fairly fast blend of several other generics approaches, such as SYB (but without the dynamic typing) and Uniplate (but allowing an arbitrary number of ta

Re: [Haskell-cafe] How to improve below code?

2009-06-09 Thread Neil Brown
Andy Stewart wrote: So have a better solution to avoid write above ugly code How about: data Page a = Page {pageName :: IORef String ,pageId:: Int ,pageBuffer:: a ,pageBox :: VBox } class PageBuffer a where pageBufferClone :: a ->

Re: [Haskell-cafe] Weird and entirely random problem...

2009-06-10 Thread Neil Brown
Hi, I'm presuming the problem with your result is that the "is in the times map, and not in the store map (you weren't clear on the exact problem). I took a look at the code, here's my thoughts on why this occurs. If you start by putting something in the cache with key "foo", an entry is cr

Re: [Haskell-cafe] Software Transactional Memory and LWN

2009-06-11 Thread Neil Brown
Ketil Malde wrote: Hi, Browsing LWN, I ran across this comment: http://lwn.net/Articles/336039/ The author makes a bunch of unsubstantiated claims about STM, namely that all implementations use locking under the hood, and that STM can live- and deadlock. I've seen a lot of similar sentiments

Re: [Haskell-cafe] Software Transactional Memory and LWN

2009-06-11 Thread Neil Brown
Ketil Malde wrote: So the naïve attempt at doing this would be something like: thread = do -- grab "lock 1" t <- readTVar lock when t retry writeTVar lock True -- grab "lock 2" t2 <- readTVar lock2 when t2 retry writeTVar write

Re: [Haskell-cafe] About the Monad Transformers

2009-06-17 Thread Neil Brown
.shawn wrote: > On page 141 of "Yet another Haskell Tutorial" (9.7 Monad Transformers) > > mapTreeM action (Leaf a) = do > lift (putStrLn ("Leaf" ++ show a)) > b <- action a > return (Leaf b) > > mapTreeM :: (MonadTrans t, Monad (t IO), Show a) => (a -> t IO a1) -> > Tree a -> t IO (Tree a1) > > Wh

Re: [Haskell-cafe] how to #include files within parsec ... without unsafePerformIO?

2009-06-18 Thread Neil Brown
Leonard Siebeneicher wrote: Dear reader, I wonder whether there is a 'general' working solution to include files within a parsec parser. Without the need of unsafePerformIO. At least in parsec 2, I don't think so. Our solution was to read in the main file, tokenise it (using Alex), preproce

Re: [Haskell-cafe] Confusion on the third monad law when using lambda abstractions

2009-06-18 Thread Neil Brown
Clicking on the source code link reveals that enum2 is used in the where clause. It's not important to the transformation that Jake was performing. In essence, <=< is the monadic version of . (function composition) and as explained, it can be used to do some pointfree-like programming in the

Re: [Haskell-cafe] coding standard question

2009-06-22 Thread Neil Brown
Jules Bean wrote: I've been using GHC for years and my honest opinion is that the warnings very rarely flag an actual maintainability problem in the code I write, and very frequently annoying highlight something I knew I was doing, and did quite deliberately - most often inexhaustive patterns

Re: [Haskell-cafe] Line drawing algorithm

2009-07-17 Thread Neil Brown
CK Kashyap wrote: Hi All, I am working on a diagraming utility in Haskell. I started with line drawing. I am doing the basic stuff using the y = mx + c formula to draw a line between (x1,y1) and (x2,y2) Hi, Are you doing this to learn Haskell, learn about drawing lines, or to just get it im

Re: [Haskell-cafe] Got problems with classes

2009-08-17 Thread Neil Brown
Hi, One reason (there may be more) is as follows: Grigory Sarnitskiy wrote: class Configuration c where getParticleI :: (Particle p) => c -> Int -> p This type signature declares that for any type c that has a Configuration instance (and an Int), you can give me back something that is

[Haskell-cafe] Control.Exception base-3/base-4 woes

2009-09-11 Thread Neil Brown
Hi, In my CHP library I need to do some exception catching. I want the library to work on GHC 6.8 (with base-3 -- this is the current version in Ubuntu Hardy and Jaunty, for example) and GHC 6.10 (which comes with base-4). But base-3 and base-4 need different code for exception catching (wh

Re: [Haskell-cafe] MonadCatchIO and bracket.

2010-06-28 Thread Neil Brown
On 28/06/2010 20:02, Carl Howells wrote: While working this weekend on the Snap web framework, I ran into a problem. Snap implements MonadCatchIO, so I thought I could just use bracket to handle resource acquisition/release in a safe manner. Imagine my surprise when bracket simply failed to run

Re: [Haskell-cafe] Re: chart "broken" under 6.12 according to criterion

2010-07-01 Thread Neil Brown
On 01/07/10 10:19, Tom Doris wrote: According to the criterion.cabal file shipped with the latest (0.5.0.1) version of criterion, the Chart package is broken under GHC 6.12: flag Chart description: enable use of the Chart package -- Broken under GHC 6.12 so far Does anyone know the status

Re: [Haskell-cafe] functional dependencies question

2010-07-01 Thread Neil Brown
On 01/07/10 12:37, Patrick Browne wrote: Why do some cases such as 1) fail to run even if they are the only instantiation. -- 1) Compiles but does not run instance LocatedAt Int String where spatialLocation(1)="home" That instance is fine. I presume the problem is that you are trying

Re: [Haskell-cafe] functional dependencies question

2010-07-01 Thread Neil Brown
On 01/07/10 13:11, Patrick Browne wrote: Neil, Does the following sum up the situation? The class Num has subclasses containing various numeric types and the literal 1 is a value for one or more of those types. Hence the Haskell compiler says the instance 1) is OK. But at run time, without the qu

Re: [Haskell-cafe] Re: chart "broken" under 6.12 according to criterion

2010-07-01 Thread Neil Brown
On 02/07/2010 00:03, wren ng thornton wrote: OS= OSX 10.5.8 GHC = 6.12.1 Cabal-Install = 0.8.2 Cabal = 1.8.0.2 $> cabal install criterion -fChart --reinstall Resolving dependencies... ... Configuring cairo-0.11.0... setup: gtk2hsC2hs is required but it coul

Re: [Haskell-cafe] use of modules to save typing

2010-07-08 Thread Neil Brown
On 08/07/10 09:08, Michael Mossey wrote: data PlayState = PlayState { playState_cursor :: Int , playState_verts :: [Loc] , playState_len :: Int , playState_doc :: MusDoc } Notice how often the characters "playSt

Re: [Haskell-cafe] Actors and message-passing a la Erlang

2010-07-26 Thread Neil Brown
On 25/07/10 21:55, Yves Parès wrote: Hello ! I've been studying Erlang and Scala, and I was wondering if someone has already implemented an actors and message passing framework for concurrent and distributed programs in Haskell. Hi, Take a look at the concurrency section on Hackage: http:/

Re: [Haskell-cafe] ANNOUNCE: approximate-equality 1.0 -- Newtype wrappers for approximate equality

2010-08-03 Thread Neil Brown
On 03/08/10 05:32, Gregory Crosswhite wrote: I am pleased to announce the release of the package "approximate-equality", which provides newtype wrappers that allow one to effectively override the equality operator of a value so that it is/approximate/ rather than/exact/. The wrappers use typ

Re: [Haskell-cafe] zip-archive performance/memmory usage

2010-08-10 Thread Neil Brown
On 10/08/10 00:29, Pieter Laeremans wrote: Hello, I'm trying some haskell scripting. I'm writing a script to print some information from a zip archive. The zip-archive library does look nice but the performance of zip-archive/lazy bytestring doesn't seem to scale. Executing : eRelativeP

Re: [Haskell-cafe] Heavy lift-ing

2010-08-18 Thread Neil Brown
On 17/08/10 17:13, Tilo Wiklund wrote: On 24/07/2010, aditya siram wrote: Perhaps I'm being unclear again. All I was trying to say was that: liftM2 (-) [0,1] [2,3] /= liftM2 (-) [2,3] [0,1] -deech I'm sorry if I'm bumping an old thread, but why should "liftM2 f" be commutative when

Re: [Haskell-cafe] Having a connection between kind * and kind * -> *

2010-08-19 Thread Neil Brown
On 19/08/10 14:26, Ivan Lazar Miljenovic wrote: , | -- | Indicates what kind of value may be stored within a type. Once | -- superclass constraints are available, the @v@ parameter will | -- become an associated type. | class Stores c v | c -> v | | data family Constraints :: (* -> *)

Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-02 Thread Neil Brown
On 02/09/10 17:10, Stephen Sinclair wrote: On Thu, Sep 2, 2010 at 3:25 AM, Jan Christiansen wrote: I prefer False<= _|_ = True Sorry to go a bit off topic, but I find it funny that I never really noticed you could perform less-than or greater-than comparisons on Bool values. Wha

Re: [Haskell-cafe] Unnecessarily strict implementations

2010-09-03 Thread Neil Brown
On 03/09/10 11:11, Henning Thielemann wrote: Ivan Lazar Miljenovic schrieb: On 3 September 2010 04:57, Arie Peterson wrote: On Thu, 2 Sep 2010 19:30:17 +0200, Daniel Fischer wrote: Why would one consider using Ord for Map an abuse? A kludge, for performance reasons, but an abuse? Because i

Re: [Haskell-cafe] overloaded list literals?

2010-09-06 Thread Neil Brown
On 06/09/10 11:23, Johannes Waldmann wrote: We have overloaded numerical literals (Num.fromInteger) and we can overload string literals (IsString.fromString), so how about using list syntax ( [], : ) for anything list-like (e.g., Data.Sequence)? I would have thought you have two obvious choic

Re: [Haskell-cafe] Restricted type classes

2010-09-07 Thread Neil Brown
On 07/09/10 05:24, wren ng thornton wrote: that other class would (most likely) be a subclass of pointed functors. In any case, it does mean there's something of a mismatch between singleton vs return/pure/point/unit. Not quite sure what you mean by a "mis-match" Of course, I'd expect single

[Haskell-cafe] ANNOUNCE: game-probability-1.1

2010-09-08 Thread Neil Brown
Hi, I've just released version 1.1 of my game-probability library. It's intended to be an easy way to investigate the probability of various dice rolls and card draws (the latter is the new addition for the 1.1 release), using a Haskell library/EDSL. It has various examples in the documenta

Re: [Haskell-cafe] Question on concurrency

2010-09-14 Thread Neil Brown
On 14/09/10 07:45, Arnaud Bailly wrote: What surprised me is that I would expect the behaviour of the two functions to be different: - in doRunMvnInIO, I would expect stdout's content to be printed before stderr, ie. the 2 threads are ordered because I call takeMVar in between calls to forkIO

Re: [Haskell-cafe] Full strict functor by abusing Haskell exceptions

2010-09-14 Thread Neil Brown
On 13/09/10 17:25, Maciej Piechotka wrote: import Control.Exception import Foreign import Prelude hiding (catch) data StrictMonad a = StrictMonad a deriving Show instance Monad StrictMonad where return x = unsafePerformIO $ do (return $! x) `catch` \(SomeException _) -> return x

Re: [Haskell-cafe] try, seq, and IO

2010-09-15 Thread Neil Brown
On 15/09/10 10:13, Jeroen van Maanen wrote: The past year I have been working on a port of my machine learning project named LExAu from Java to Haskell. I'm still very glad I took the jump, because the complexity curve appears to be log shaped rather than exp shaped. In one year I almost got t

Re: [Haskell-cafe] ANNOUNCE: http-enumerator 0.0.0

2010-09-22 Thread Neil Brown
On 22/09/10 11:22, C K Kashyap wrote: Hey Michael, I'd like to announce the first release of http-enumerator[1], an HTTP client package with support for HTTPS connections. This release is very experimental; bug reports and API feedback are very welcome. This sounds nice (I'll certain

Re: [Haskell-cafe] EDSL for Makefile

2010-09-30 Thread Neil Brown
On 30/09/10 09:41, C K Kashyap wrote: Hi All, I was thinking about doing an EDSL for Makefile (as an exercise) I put down my line of thought here - http://hpaste.org/40233/haskell_makefile_edsl I'd appreciate some feedback on the approach. Also, I wanted some idea on how(in the current approach)

Re: [Haskell-cafe] Lambda-case / lambda-if

2010-10-05 Thread Neil Brown
On 05/10/10 07:52, Nicolas Wu wrote: I'd prefer to see something like \ 1 -> f | 2 -> g but I'm sure something could be worked out. While I think the "case of" is a good idea, multiple clauses in lambdas seems more canonical to me. Alternatively, we could abandon la

Re: [Haskell-cafe] Re: Lazy evaluation from "Why Functional programming matters"

2010-10-06 Thread Neil Brown
On 06/10/10 11:00, C K Kashyap wrote: My ultimate aim it to write an EDSL for x86 - as in, describe a micro-kernel in haskell, compiling and running which would generate C code ( not sure if it's even possible - but I am really hopeful). Have you seen Potential (http://intoverflow.wordpress.

Re: [Haskell-cafe] Convert Either to Tree - Occurs check

2010-10-22 Thread Neil Brown
On 22/10/10 09:23, André Batista Martins wrote: Tks for the answer, the data structure of Either is: data Either a b = Left a | Right bderiving (Eq, Ord, Read, Show) one example of what i want convert is: Left(Right(Left(Left( Hi, The problem here is that the t

Re: [Haskell-cafe] tried to use the example given in the source of network.browser

2010-10-22 Thread Neil Brown
Hi, On 22/10/10 14:58, Michael Litchard wrote: main = do rsp<- Network.Browser.browse $ do setAllowRedirects True -- handle HTTP redirects request $ getRequest "http://google.com/"; fmap (take 100) (getResponseBody rsp) but I got this errortest

Re: [Haskell-cafe] apply function arguments in a list

2009-10-05 Thread Neil Brown
Michael Mossey wrote: If I have a list containing the arguments I want to give to a function, is there a general way to supply those arguments in a compact syntax? In other words, I could have args = [1,2,3] f x y z = ... I would write t = f (args!!0) (args!!1) (args!!2) but there may be a

Re: [Haskell-cafe] ANN: text 0.5, a major revision of the Unicode text library

2009-10-11 Thread Neil Brown
Bryan O'Sullivan wrote: On Fri, Oct 9, 2009 at 8:33 AM, Jeremy Shaw > wrote: What are the chances of seeing a, instance Data Text, some day? I might as well follow up here, since I've sent Jeremy a couple of messages on this subject. I think maybe someone e

Re: [Haskell-cafe] is proof by testing possible?

2009-10-12 Thread Neil Brown
Dan Piponi wrote: On Mon, Oct 12, 2009 at 10:42 AM, muad wrote: Is it possible to prove correctness of a functions by testing it? consider a function of signature swap :: (a,b) -> (b,a) We don't need to test it at all, it can only do one thing, swap its arguments. (Assuming it termin

[Haskell-cafe] Are all arrows functors?

2009-11-03 Thread Neil Brown
Hi, I was thinking about some of my code today, and I realised that where I have an arrow in my code, A b c, the type (A b) is also a functor. The definition is (see http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Arrow.html): fmap = (^<<) -- Or, in long form: fmap f x =

[Haskell-cafe] Names for properties of operators

2009-11-07 Thread Neil Brown
Hi, We have names for properties of operators/functions. For example, if this holds: a % b = b % a for some operator %, we say that % is commutative. Similarly, if this holds: (a % b) % c = a % (b % c) we say that % is associative. Is there a name for this property, which I'm numberin

Re: [Haskell-cafe] Names for properties of operators

2009-11-08 Thread Neil Brown
Hi, Thanks for the replies so far. If it helps, after I sent my post, I spotted a couple of arithmetic examples: Neil Brown wrote: 2: (a % b) % c = (a % c) % b Division (on rationals) obeys this property (a / b) / c = (a / c) / b -- which is actually equal to a / (b * c), but that doesn&#

Re: [Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Neil Brown
Andy Gimblett wrote: Hi all, I've been doing some GUI programming recently, using wx. To help manage dependencies between state and UI elements, I looked for a Haskell version of the Observer design pattern, and I found an implementation written by Bastiaan Heeren of ou.nl [1]. Now, before

Re: [Haskell-cafe] Observer pattern in Haskell?

2009-11-09 Thread Neil Brown
Andy Gimblett wrote: was a bit surprised at first that the observers were called synchronously. Asynchronous is what I'd expect, and it's also harder to code the asynchronous handlers wrongly. One blocking call (such as putMVar) in a synchronous handler can screw up your whole program by del

Re: [Haskell-cafe] What does the `forall` mean ?

2009-11-12 Thread Neil Brown
Eugene Kirpichov wrote: 2009/11/12 Andrew Coppin : Even I am still not 100% sure how placing forall in different positions does different things. But usually it's not something I need to worry about. :-) To me it does not look like it does different things: everywhere it denotes univer

Re: [Haskell-cafe] Cabal upload issue

2009-11-12 Thread Neil Brown
Jeremy O'Donoghue wrote: Hi all, I'm in the process of trying update the revisions of wx (part of wxHaskell) on hackage. I'm getting an error I find slightly surprising: ... Library if flag(splitBase) build-depends: base >= 3, wxcore >= 0.12.1.1, stm Change this last line to base

Re: [Haskell-cafe] Strange parallel behaviour with Ubuntu Karmic / GHC 6.10.4

2009-11-15 Thread Neil Brown
Michael Lesniak wrote: Hello, I'm currently developing some applications with explicit threading using forkIO and have strange behaviour on my freshly installed Ubuntu Karmic 9.10 (Kernel 2.6.31-14 SMP). Setup: Machine A: Quadcore, Ubuntu 9.04, Kernel 2.6.28-13 SMP Machine B: AMD Opteron 875,

Re: [Haskell-cafe] Strange parallel behaviour with Ubuntu Karmic / GHC 6.10.4

2009-11-16 Thread Neil Brown
Michael Lesniak wrote: Hello, I've written a smaller example which reproduces the unusual behaviour. Should I open a GHC-Ticket, too? Hi, I get these results: $ time ./Temp +RTS -N1 -RTS 16 real0m16.010s user0m10.869s sys0m5.144s $ time ./Temp +RTS -N2 -RTS 16 real0m12.7

Re: [Haskell-cafe] Strange parallel behaviour with Ubuntu Karmic / GHC 6.10.4

2009-11-16 Thread Neil Brown
Michael Lesniak wrote: Hello, getTime? I wonder if that number might be causing the problem; can you replicate it with lower sys times? That was it! Thanks Neil! When I'm using some number crunching without getTime it works (with more or less the expected speedup and usage of two cor

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

2009-11-17 Thread Neil Brown
Simon Peyton-Jones wrote: | What's the status of the TDNR proposal [1]? It's stalled. As far as I know, there's been very little discussion about it. It's not a trivial thing to implement, and it treads on delicate territory (how "." is treated). Having skimmed the page, it seems like the re

Re: [Haskell-cafe] (possibly) a list comprehensions question

2009-11-19 Thread Neil Brown
Ozgur Akgun wrote: Anyway, just forget the fact that these funstions do not do a check on the length of the input list for a moment. My question is, how can I generalize this function to accept a list of lists of arbitrary length, and produce the required result. Hi, The concise solution is

Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread Neil Brown
It looks like a bug to me. Can you show an exact list of nodes and edges that is causing mkGraph to fail? Or is that what you have displayed, and I can't parse it properly? Thanks, Neil. Ivan Lazar Miljenovic wrote: When developing my QuickCheck-2 test-suite for graphviz, I wrote the follo

Re: [Haskell-cafe] Possible FGL bug

2009-11-25 Thread Neil Brown
David Menendez wrote: From what I can tell, insEdge inserts an edge between two nodes which are already in the graph. The code is calling insEdge on arbitrarily-labeled nodes, which may not exist in the graph. That's what I thought initially, but in fact what it is doing is exactly what you s

Re: [Haskell-cafe] Scrap your boilerplate traversals

2009-11-25 Thread Neil Brown
Hi, You want gmapT (or gmapM for the monadic version). If you look at the source to the everywhere function, you'll see that everywhere is defined in terms of gmapT: everywhere f = f . gmapT (everywhere f) Thanks, Neil. rodrigo.bonifacio wrote: Hi all, Is there a non-recursive travers

Re: [Fwd: Re: [Haskell-cafe] Implicit newtype unwrapping]

2009-12-03 Thread Neil Brown
Sjoerd Visscher wrote: In the case of Dual [1] `mappend` Dual [2] there's no need to do any unwrapping. There is if you say: l :: [Int] l = Dual [1] `mappend` Dual [2] The way I think this could work is that when the type checker detects a type error, it will first try to resolve it by newtype

Re: [Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-03 Thread Neil Brown
wren ng thornton wrote: Nicolas Pouillard wrote: Excerpts from Heinrich Apfelmus's message of Tue Dec 01 11:29:24 +0100 2009: For mnemonic value, we could call it a "train": data Train a b = Wagon a (Train a b) | Loco b I rather like it too. The mnemonic version sound

Re: [Haskell-cafe] Optimization with Strings ?

2009-12-03 Thread Neil Brown
Emmanuel CHANTREAU wrote: Le Thu, 3 Dec 2009 13:20:31 +0100, David Virebayre a écrit : It doesn't work this way : Strings are just lists of Chars. Comparison is made recursively, Char by Char. You can have a look at the source to make sure : instance (Eq a) => Eq [a] where [] == []

Re: [Haskell-cafe] GHC magic optimization ?

2009-12-04 Thread Neil Brown
Emmanuel CHANTREAU wrote: I will take an example: f x y= x+y The program ask the user to enter two numbers and print the sum. If the user enter "1 2" "f 1 2=3" is stored and a gargage collector is used to remove this dandling expression later ? If the user enter again "1 2", ghc search in dandl

Re: [Haskell-cafe] You are in a twisty maze of concurrency libraries, all different ...

2009-12-04 Thread Neil Brown
Patrick Caldon wrote: I'm looking for the "right" concurrency library/semantics for what should be a reasonably simple problem. I have a little simulator: runWorldSim :: MTGen -> SimState -> IO SimState it takes about a second to run on a PC. It's functional except it whacks the rng, which

Re: [Haskell-cafe] Does the TMVar and TChan really obey STM rules?

2009-12-24 Thread Neil Brown
Andrey Sisoyev wrote: Hi everyone, isEmptyTMVar :: TMVar a -> STM Bool Source Check whether a given TMVar is empty. Notice that the boolean value returned is just a snapshot of the state of the TMVar. By the time you get to react on its result, the TMVar may have been filled (or emptied

  1   2   >