Re: [Haskell-cafe] Type arithmetic with ATs/TFs

2010-02-12 Thread Luke Palmer
On Fri, Feb 12, 2010 at 2:10 PM, Edward Kmett wrote: > On Fri, Feb 12, 2010 at 2:11 PM, Andrew Coppin > wrote: >> >> OK, well in that case, I'm utterly puzzled as to why both forms exist in >> the first place. If TFs don't allow you to do anything that can't be done >> with ATs, why have them? >>

Re: [Haskell-cafe] Computing sums

2010-02-20 Thread Luke Palmer
On Sat, Feb 20, 2010 at 3:30 AM, Andrew Coppin wrote: > Have I just invented arrows? No... you have a data type which is *an* Arrow (probably/almost). The pure implementation bugs me because of its use of undefined. Might still be okay though. I would be more comfortable if it could not output

[Haskell-cafe] Real-time garbage collection for Haskell

2010-02-27 Thread Luke Palmer
I have seen some proposals around here for SoC projects and other things to try to improve the latency of GHC's garbage collector. I'm currently developing a game in Haskell, and even 100ms pauses are unacceptable for a real-time game. I'm calling out to people who have seen or made such proposal

Re: [Haskell-cafe] Real-time garbage collection for Haskell

2010-02-28 Thread Luke Palmer
On Sun, Feb 28, 2010 at 2:06 AM, Pavel Perikov wrote: > Did you really seen 100ms pauses?! I never did extensive research on this but > my numbers are rather in microseconds range (below 1ms). What causes such a > long garbage collection? Lots of allocated and long-living objects? This is all h

[Haskell-cafe] Re: Real-time garbage collection for Haskell

2010-03-02 Thread Luke Palmer
On Tue, Mar 2, 2010 at 7:17 AM, Simon Marlow wrote: >> For games, >> though, we have a very good point that occurs regularly where we know >> that all/most short-lived objects will no longer be referenced - at the >> start of a fresh frame. > > System.Mem.performGC is your friend, but if you're un

Re: [Haskell-cafe] Monad laws

2010-03-02 Thread Luke Palmer
On Tue, Mar 2, 2010 at 1:17 PM, David Sabel wrote: > Hi, > when checking the first monad law (left unit) for the IO-monad (and also for > the ST monad): > > return a >>= f ≡ f a > > I figured out that there is the "distinguishing" context (seq [] True) which > falsifies the law > for a and f defin

Re: [Haskell-cafe] Monad laws

2010-03-02 Thread Luke Palmer
On Tue, Mar 2, 2010 at 4:37 PM, Yitzchak Gale wrote: > For this reason, I consider it a bug in GHC that return :: IO a > is lazy. Wait a minute... return undefined >>= const (return 42) = const (return 42) undefined = return 42 But if return undefined = undefined, then that equals; undefi

Re: [Haskell-cafe] GPL answers from the SFLC (WAS: Re: ANN: hakyll-0.1)

2010-03-05 Thread Luke Palmer
On Fri, Mar 5, 2010 at 12:53 AM, Kevin Jardine wrote: > I'm a Haskell newbie but long time open source developer and I've been > following this thread with some interest. > > The GPL is not just a license - it is a form of social engineering and social > contract. The idea if I use the GPL is th

Re: [Haskell-cafe] How to put data from a string to a tuple

2010-03-05 Thread Luke Palmer
Consider taking this to the haskell-beginners list. On Fri, Mar 5, 2010 at 4:32 AM, Pradeep Wickramanayake wrote: > Hi, > > Im self learner in Haskell. And im stuck in a  small place which I tried > searching in google but couldn't find > Proper answer > > I have some values in a string, Im remov

Re: [Haskell-cafe] Parsec monad transformer with IO?

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 10:37 AM, Stefan Klinger wrote: > Hello! > > Nice, Parsec 3 comes with a monad transformer [1]. So I thought I could > use IO as inner monad, and perform IO operations during parsing. > > But I failed. Monad transformers still bend my mind. My problem: I > don't see a funct

Re: [Haskell-cafe] Abstraction in data types

2010-03-18 Thread Luke Palmer
On Thu, Mar 18, 2010 at 12:17 PM, John Meacham wrote: > On Wed, Mar 17, 2010 at 09:20:49PM -0700, Darrin Chandler wrote: >> data Point    = Cartesian (Cartesian_coord, Cartesian_coord) >>               | Spherical (Latitude, Longitude) > > Just a quick unrelated note, though you are probably aware

Re: [Haskell-cafe] Are there any female Haskellers?

2010-03-27 Thread Luke Palmer
On Sat, Mar 27, 2010 at 2:22 PM, Peter Verswyvelen wrote: > So the first computer nerd was a women??!!! ;-) ;-) ;-) Yeah, and she was so attractive that the entire male gender spent the next 50 years trying to impress her. Luke > On Sat, Mar 27, 2010 at 9:06 PM, John Van Enk wrote: >> http

Re: [Haskell-cafe] Re: Are there any female Haskellers?

2010-03-28 Thread Luke Palmer
2010/3/28 Pekka Enberg : > 2010/3/28 Günther Schmidt : >> This is definately a point where we will continue to disagree. I found >> myself assuming that there are no female haskellers and wanted to verify it >> by asking for data. > > So what exactly is off-topic for this list?  Is unsubscribing fr

[Haskell-cafe] Announce: hothasktags

2010-04-01 Thread Luke Palmer
Hi, I'd like to draw attention to a little script I wrote. I tend to use qualified imports and short names like "new" and "filter". This makes hasktags pretty much useless, since it basically just guesses which one to go to. hothasktags is a reimplementation of hasktags that uses haskell-src-ex

Re: [Haskell-cafe] Re: Hackage accounts and real names

2010-04-05 Thread Luke Palmer
On Mon, Apr 5, 2010 at 9:18 PM, Ertugrul Soeylemez wrote: > David House wrote: > >> * "Reputation. Using a RealName is the most credible way to build a >> combined online and RealLife identity." (Some people don't want this, >> for whatever reasons.) > > I agree that the restriction should be lif

Re: [Haskell-cafe] Announce: hothasktags

2010-04-07 Thread Luke Palmer
On Wed, Apr 7, 2010 at 1:23 AM, Evan Laforge wrote: > On Thu, Apr 1, 2010 at 1:46 PM, Luke Palmer wrote: >> Hi, >> >> I'd like to draw attention to a little script I wrote.  I tend to use >> qualified imports and short names like "new" and "filte

Re: [Haskell-cafe] Re: instance Eq (a -> b)

2010-04-14 Thread Luke Palmer
On Wed, Apr 14, 2010 at 4:41 AM, wrote: > As ski noted on #haskell we probably want to extend this to work on Compact > types and not just Finite types > > instance (Compact a, Eq b) => Eq (a -> b) where ... > > For example (Int -> Bool) is a perfectly fine Compact set that isn't finite > and (In

Re: [Haskell-cafe] Re: instance Eq (a -> b)

2010-04-14 Thread Luke Palmer
On Wed, Apr 14, 2010 at 5:13 AM, Luke Palmer wrote: > On Wed, Apr 14, 2010 at 4:41 AM,   wrote: >> As ski noted on #haskell we probably want to extend this to work on Compact >> types and not just Finite types >> >> instance (Compact a, Eq b) => Eq (a -> b)

Re: [Haskell-cafe] FRP for game programming / artifical life simulation

2010-04-21 Thread Luke Palmer
On Wed, Apr 21, 2010 at 4:47 PM, Ben Christy wrote: > I have an interest in both game programming and artificial life. I have > recently stumbled on Haskell and would like to take a stab at programming a > simple game using FRP such as YAMPA or Reactive but I am stuck. I am not > certain which one

Re: [Haskell-cafe] I need help getting started

2010-04-24 Thread Luke Palmer
On Sat, Apr 24, 2010 at 10:34 PM, wrote: > Hi, > > > > I’m just starting to learn, or trying to learn Haskell.  I want to write a > function to tell me if a number’s prime.  This is what I’ve got: > > > > f x n y = if n>=y > >   then True > >   else > >   if gcd x n == 1 >

Re: [Haskell-cafe] singleton types

2010-04-25 Thread Luke Palmer
2010/4/25 Günther Schmidt : > Hello, > > HaskellDB makes extensive use of Singleton Types, both in its original > version and the more recent one where it's using HList instead of the legacy > implementation. > > I wonder if it is possible, not considering feasibility for the moment, to > implement

Re: [Haskell-cafe] Re: Learning about Programming Languages (specifically Haskell)

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 9:17 AM, Kyle Murphy wrote: > Reasons to learn Haskell include: > Lazy evaluation can make some kinds of algorithms possible to implement that > aren't possible to implement in other languages (without modification to the > algorithm). One could say the reverse as well. I

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

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 9:34 AM, Casey Hawthorne wrote: >>Strict type system allows for a maximum number of programming errors to be >>caught at compile time. > > I keep hearing this statement but others would argue that programming > errors caught at compile time only form a minor subset of all e

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

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 11:07 AM, Kyle Murphy wrote: > The problem with dynamic typing is that it has a much higher chance of > having a subtle error creep into your code that can go undetected for a long > period of time. A strong type system forces the code to fail early where > it's easier to tr

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

2010-05-03 Thread Luke Palmer
On Mon, May 3, 2010 at 10:13 PM, Ivan Miljenovic wrote: > On 4 May 2010 13:30, Luke Palmer wrote: >> Here is a contrived example of what I am referring to: >> >> prefac f 0 = 1 >> prefac f n = n * f (n-1) >> >> fac = (\x -> x x) (\x -> prefac (x x)) &

Re: [Haskell-cafe] ANN: has-0.4 Entity based records

2010-05-04 Thread Luke Palmer
On Tue, May 4, 2010 at 10:18 AM, HASHIMOTO, Yusaku wrote: > Hello, > > I'm pleased to announce the release of my new library, named "has", > written to aim to ease pain at inconvinience of Haskell's build-in > records. Hmm, nice work, looks interesting. > With the has, You can reuse accessors ov

Re: [Haskell-cafe] Proof question -- (==) over Bool

2010-05-21 Thread Luke Palmer
2010/5/21 R J : > I'm trying to prove that (==) is reflexive, symmetric, and transitive over > the Bools, given this definition: > (==)                       :: Bool -> Bool -> Bool > x == y                     =  (x && y) || (not x && not y) > My question is:  are the proofs below for reflexivity

Re: [Haskell-cafe] How to "Show" an Operation?

2010-06-09 Thread Luke Palmer
On Wed, Jun 9, 2010 at 12:33 PM, Martin Drautzburg wrote: > So far so good. However my "Named" things are all functions and I don't see I > ever want to map over any of them. But what I'd like to do is use them like > ordinary functions as in: > > f::Named (Int->Int) > f x > > Is there a way to do

Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin wrote: > Control.Concurrent provides the threadDelay function, which allows you to > make the current thread sleep until T=now+X. However, I can't find any way > of making the current thread sleep until T=X. In other words, I want to > specify an abs

Re: [Haskell-cafe] Thread scheduling

2010-06-10 Thread Luke Palmer
Say, using System.Time.getClockTime. Luke On Thu, Jun 10, 2010 at 11:31 PM, Luke Palmer wrote: > On Thu, Jun 10, 2010 at 11:50 AM, Andrew Coppin > wrote: >> Control.Concurrent provides the threadDelay function, which allows you to >> make the current thread sleep until T

Re: [Haskell-cafe] Re: How to "Show" an Operation?

2010-06-10 Thread Luke Palmer
On Thu, Jun 10, 2010 at 10:43 PM, Brandon S. Allbery KF8NH wrote: > On Jun 10, 2010, at 17:38 , Martin Drautzburg wrote: >>> >>> instance Applicative Named where >>>   pure x = Named "" x >>>   (Named s f) <*> (Named t v) = Named (s ++ "(" ++ t ++ ")") (f v) >> >> Applicative. Need to study that >

Re: [Haskell-cafe] Re: How to "Show" an Operation?

2010-06-11 Thread Luke Palmer
On Thu, Jun 10, 2010 at 2:10 PM, Maciej Piechotka wrote: > data Named a = Named String a > > instance Functor Named where >    f `fmap` (Named s v) = Named s (f v) > > instance Applicative Named where >    pure x = Named "" x >    (Named s f) <*> (Named t v) = Named (s ++ "(" ++ t ++ ")") (f v) T

Re: [Haskell-cafe] How to browse code written by others

2010-06-14 Thread Luke Palmer
On Mon, Jun 14, 2010 at 2:02 AM, Jean-Marie Gaillourdet wrote: > Hello, > > On 13.06.2010, at 22:32, Martin Drautzburg wrote: > >> I need your advice about how to browse code which was written by someone else >> (Paul Hudak's Euterpea, to be precise, apx. 1 LOC). I had set some hopes >> on lek

Re: [Haskell-cafe] Vague: Assembly line process

2010-06-14 Thread Luke Palmer
So hang on, what is the problem? You have described something like a vague model, but what information are you trying to get? Say, perhaps, a set of possible output lists from a given input list? Luke On Mon, Jun 14, 2010 at 11:16 AM, Martin Drautzburg wrote: > Hello all, > > this is a problem

Re: [Haskell-cafe] The Arrow class (was: Vague: Assembly line process)

2010-06-19 Thread Luke Palmer
On Fri, Jun 18, 2010 at 5:57 PM, Ryan Ingram wrote: > Related to this, I really would like to be able to use arrow notation > without "arr"; I was looking into writing a "circuit optimizer" that > modified my arrow-like circuit structure, but since it's impossible to > "look inside" arr, I ran int

Re: [Haskell-cafe] General function to count list elements?

2009-04-18 Thread Luke Palmer
On Sat, Apr 18, 2009 at 11:11 AM, michael rice wrote: > > To compare two functions in C, I would compare their machine addresses. > > > > Why would you need that at all? > > How would *you* do it? Do what? What is the problem? No, I don't mean "comparing two functions". I rather mean, why ar

Re: [Haskell-cafe] Converting IO [XmlTree] to [XmlTree]

2009-04-19 Thread Luke Palmer
On Sun, Apr 19, 2009 at 9:48 AM, Manlio Perillo wrote: > Henning Thielemann ha scritto: > > > > On Tue, 14 Apr 2009, rodrigo.bonifacio wrote: > > > >> I guess this is a very simple question. How can I convert IO [XmlTree] > >> to just a list of > >> XmlTree? > > > > The old Wiki had: > > http://

Re: [Haskell-cafe] Re: General function to count list elements?

2009-04-20 Thread Luke Palmer
On Mon, Apr 20, 2009 at 7:57 AM, Achim Schneider wrote: > Lennart Augustsson wrote: > > > On Sun, Apr 19, 2009 at 10:43 PM, Peter Verswyvelen > > wrote: > > > For example, suppose you have a predicate a -> Bool, and a list of > > > these predicates [a -> Bool], but you want to remove all functi

Re: [Haskell-cafe] breaking too long lines

2009-04-22 Thread Luke Palmer
On Mon, Apr 20, 2009 at 8:44 AM, Tillmann Rendel wrote: > However, I would prefer the following Coq-like syntax: > > data Maybe a = >| Just a >| Nothing Of course, Coq's inductive syntax is just GADT form: Inductive Maybe a := | Just : a -> Maybe a | Nothing : Maybe a. data Maybe a w

Re: [Haskell-cafe] Overriding a Prelude function?

2009-04-22 Thread Luke Palmer
On Wed, Apr 22, 2009 at 1:47 PM, michael rice wrote: > Here's what I get: > > [mich...@localhost ~]$ ghci > GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer ... linking ... done. > Loading package base ... li

Re: [Haskell-cafe] Optimizing unamb by determining the "state" of a thunk?

2009-04-22 Thread Luke Palmer
On Mon, Apr 20, 2009 at 2:54 PM, Peter Verswyvelen wrote: > I find this very confusing. Is the documentation of seq wrong (should be > weak head normal form)? > Yes. Weak head normal form is really the only *essential* one. The popular runtimes do not know how to reduce under a lambda, so they

Re: [Haskell-cafe] GADT on the wiki: I'm lost

2009-04-22 Thread Luke Palmer
On Wed, Apr 22, 2009 at 3:30 PM, Peter Verswyvelen wrote: > I was reading the explanation of GADTs on the > wiki , > and but can't make any sense of the examples. > Sure I understand what a GADT is, but I'm looking for practical examples, > and the ones

[Haskell-cafe] a question about *** Exception: stack overflow ..

2009-04-23 Thread Luke Palmer
On Thu, Apr 23, 2009 at 7:02 AM, Mozhgan Kabiri wrote: > Hi Luck , > > I got you email from the Haskell Cafe list. Hope you don't mind. > Recently I was running a simple program in Haskell and keep getting *** > Exception: stack overflow error ! > > I don't know how to solve it or handle it !

Re: [Haskell-cafe] Overriding a Prelude function?

2009-04-23 Thread Luke Palmer
On Thu, Apr 23, 2009 at 1:34 PM, Miguel Mitrofanov wrote: > > Well, than, what would you expect from this: > > let {f x = g x; > g 0 = 0; > g n = f (n-1)} > in show f Well, not show, because any show instance for functions breaks r.t. But the interactive interpreter, if it is not subj

Re: [Haskell-cafe] default values in a record structure

2009-04-28 Thread Luke Palmer
On Tue, Apr 28, 2009 at 4:09 PM, Vasili I. Galchin wrote: > Hello, > > Is there anyway when defining a dat type record struct to indicate > default values for some of the fields? The usual pattern is to use a default record, and specialize it: data Foo = Foo { bar :: Int, baz :: Int, quux

Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Luke Palmer
On Tue, Apr 28, 2009 at 4:54 PM, Michael Vanier wrote: > I've stumbled upon a structure that is like a weaker version of a monad, > one that supports return and >> but not >>=. Has anyone seen this before, > and if so, does it have a standard name? That is a strange structure. The type parame

Re: [Haskell-cafe] name for monad-like structure?

2009-04-28 Thread Luke Palmer
On Tue, Apr 28, 2009 at 5:33 PM, Michael Vanier wrote: > Tony Morris wrote: > > Michael Vanier wrote: > > > I've stumbled upon a structure that is like a weaker version of a > monad, one that supports return and >> but not >>=. Has anyone seen > this before, and if so, does it have a standard

Re: [Haskell-cafe] Arrow preprocessor and *** combinator

2009-04-30 Thread Luke Palmer
On Thu, Apr 30, 2009 at 11:42 AM, Peter Verswyvelen wrote: > Thanks Ross. > Does anyone know how to tackle this? Combining GHC's builtin arrow > processor and rewrite rules? > Another possibility is to make an "optimizer" arrow transformer that encodes the rules. Eg. data Optimize a b c where

Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-01 Thread Luke Palmer
On Fri, May 1, 2009 at 8:47 PM, Anatoly Yakovenko wrote: > So I am trying to traverse a tree in a specific order, but i have no > idea where the things that i am looking for are located, and i want to > avoid explicit backtracking. Though I don't fully understand what you are doing (specifically

Re: [Haskell-cafe] traversing a tree using monad.cont

2009-05-02 Thread Luke Palmer
On Sat, May 2, 2009 at 3:13 AM, Anatoly Yakovenko wrote: > > Though I don't fully understand what you are doing (specifically what you > > mean by "specific order"), but in a lazy language, traversals are usually > > simply encoded as lists. Just write a function which returns all the > leaves >

Re: [Haskell-cafe] Re: gcd

2009-05-03 Thread Luke Palmer
On Sat, May 2, 2009 at 4:17 PM, Achim Schneider wrote: > Steve wrote: > > > "It is useful to define gcd(0, 0) = 0 and lcm(0, 0) = 0 because then > > the natural numbers become a complete distributive lattice with gcd > > as meet and lcm as join operation. This extension of the definition > > is

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Luke Palmer
mplus requires both arguments to be in the same monad (the same type, even). Fortunately, the empty list behaves like Nothing, and a singleton list behaves like Just. So convert the Maybe before composing, using: maybeToList Nothing = [] maybeToList (Just x) = [x] (The maybeToList function can

Re: [Haskell-cafe] Combining computations

2009-05-03 Thread Luke Palmer
On Sun, May 3, 2009 at 4:41 AM, Luke Palmer wrote: > mplus requires both arguments to be in the same monad (the same type, > even). Fortunately, the empty list behaves like Nothing, and a singleton > list behaves like Just. So convert the Maybe before composing, using: > > mayb

Re: [Haskell-cafe] Interesting Thread on OO Usefulness (scala mailing list)

2009-05-04 Thread Luke Palmer
ML functors seem the ideal tool for this task. People have shown how you can emulate them with typeclasses, but it won't necessarily be pretty... On Mon, May 4, 2009 at 4:05 AM, Paolo Losi wrote: > Hi all, > > I'm following an interesting thread on the scala mailing list: > > http://www.nabble.

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-05 Thread Luke Palmer
On Sun, May 3, 2009 at 11:27 AM, Tobias Olausson wrote: > Hello! > I have a program that is using ST.Strict, which works fine. > However, the program needs to be extended, and to do that, > lazy evaluation is needed. As a result of that, I have switched > to ST.Lazy to be able to do stuff like

Re: [Haskell-cafe] ST.Lazy vs ST.Strict

2009-05-05 Thread Luke Palmer
On Tue, May 5, 2009 at 3:27 PM, Luke Palmer wrote: > On Sun, May 3, 2009 at 11:27 AM, Tobias Olausson wrote: > >> Hello! >> I have a program that is using ST.Strict, which works fine. >> However, the program needs to be extended, and to do that, >> lazy evaluation

Re: [Haskell-cafe] Writing a compiler in Hakell

2009-05-05 Thread Luke Palmer
On Wed, May 6, 2009 at 12:07 AM, Rouan van Dalen wrote: > > Hi everyone. > > I am designing my own programming language. > > I would like to know what is the best way to go about writing my compiler > in haskell. > What are the tools available in haskell that can help with compiler > construction?

Re: [Haskell-cafe] Writing a compiler in Hakell (continued 1)

2009-05-06 Thread Luke Palmer
On Wed, May 6, 2009 at 4:17 AM, Rouan van Dalen wrote: > > As for the target language, im not quite sure yet. I am doing a lot of > work in > .NET/C# at the moment, but I would eventually like to use my own > programming language, > instead of C#. I would also like to use my language for linux

Re: [Haskell-cafe] beginners question about fromMaybe

2009-06-02 Thread Luke Palmer
On Tue, Jun 2, 2009 at 4:59 PM, Nico Rolle wrote: > hi there > > heres a code snipped, don't care about the parameters. > the thing is i make a lookup on my map "m" and then branch on that return > value > > probePhase is sc [] m = [] > probePhase is sc (x:xs) m >| val == Nothing = probePhas

Re: [Haskell-cafe] Re: Non Empty List?

2009-06-05 Thread Luke Palmer
On Fri, Jun 5, 2009 at 4:13 PM, Jason Dagit wrote: > > > On Fri, Jun 5, 2009 at 2:58 PM, MH wrote: > >> I actually meant >> >> data Container a = Many a(Container a) >> >> but here is what I don't understand (fyi, I am a beginner) how can you >> construct this container? I can do > > > I think

Re: [Haskell-cafe] Why are these record accesses ambiguous

2009-06-06 Thread Luke Palmer
On Sat, Jun 6, 2009 at 1:48 AM, John Ky wrote: > Hi Haskell Cafe, > > In the following code, I get an error saying Ambiguous occurrence `x'. Why > can't Haskell work out which x to call based on the type of getA? > > Thanks > > -John > > #!/usr/bin/env runhaskell > > > {-# LANGUAGE DisambiguateR

Re: [Haskell-cafe] Convert IO Int to Int

2009-06-09 Thread Luke Palmer
2009/6/9 Krzysztof Skrzętnicki > On Tue, Jun 9, 2009 at 16:14, Daniel Fischer > wrote: > > If you're doing much with random generators, wrap it in a State monad. > > To avoid reinventing the wheel one can use excellent package available > on Hackage: > http://hackage.haskell.org/cgi-bin/hackage-s

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

2009-06-11 Thread Luke Palmer
On Thu, Jun 11, 2009 at 2:30 AM, 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

Re: [Haskell-cafe] Logo fun

2009-06-12 Thread Luke Palmer
Nice work, I love this one. :-) On Fri, Jun 12, 2009 at 3:25 AM, Thomas Davie wrote: > > On 12 Jun 2009, at 11:15, Deniz Dogan wrote: > > 2009/6/12 Deniz Dogan : >> >>> 2009/6/12 Tom Lokhorst : >>> There's a SVG version of the logo on the wiki: http://haskell.org/haskellwiki/Thompson

Re: [Haskell-cafe] Performance of functional priority queues

2009-06-15 Thread Luke Palmer
On Sun, Jun 14, 2009 at 9:18 PM, Richard O'Keefe wrote: > There's a current thread in the Erlang mailing list about > priority queues. I'm aware of, for example, the Brodal/Okasaki > paper and the David King paper. I'm also aware of James Cook's > priority queue package in Hackage, have my own c

Re: [Haskell-cafe] Runtime strictness analysis for polymorphic HOFs?

2009-06-15 Thread Luke Palmer
On Sun, Jun 14, 2009 at 5:42 PM, Paul Chiusano wrote: > > Note that I'm not suggesting Haskell should do anything like this. I'm > playing around with the ideas because I'm interesting in creating a lazy > language and I was hoping to have strictness analysis be very predictable > and uniform, som

Re: [Haskell-cafe] I need a hint in list processing

2009-06-15 Thread Luke Palmer
On Sun, Jun 14, 2009 at 2:06 AM, Fernan Bolando wrote: > Hi all > > If I have a number of list > example > list1 = [2,3] > list2 = [1,2] > list3 = [2,3,4] > list4 = [1,2,3] > > I want to create a list from the list above with n elements, > non-repeating and each elements index represents 1 of the

Re: [Haskell-cafe] Haskell - string to list isusses, and more

2009-06-15 Thread Luke Palmer
On Sun, Jun 14, 2009 at 11:14 AM, Gjuro Chensen wrote: > > Gjuro Chensen wrote: > > > > > > /cut > > > > > > I dont know everyone will see this, but I would like thank everyone who > found time to help, and not spam too much doing it:D. > Well, I did it! Its not great (especially comparing to tho

Re: [Haskell-cafe] Haskell - string to list isusses, and more

2009-06-15 Thread Luke Palmer
On Mon, Jun 15, 2009 at 3:03 AM, Luke Palmer wrote: > > The last thing: we made startsWithUpper less general in the process; it is > undefined for empty strings. We need to verify that words never returns any > empty strings. I did this using SmallCheck: > > ghci> import T

Re: [Haskell-cafe] IORef memory leak

2009-06-18 Thread Luke Palmer
On Thu, Jun 18, 2009 at 9:55 PM, Ross Mellgren wrote: > It looks offhand like you're not being strict enough when you put things > back in the IORef, and so it's building up thunks of (+1)... > > With two slight mods: > > go 0 = return () > go n = do modifyIORef ior (+1) > go (n-1

Forward compatibility (was Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature)

2009-06-23 Thread Luke Palmer
On Tue, Jun 23, 2009 at 2:20 AM, wrote: > > Simple: the definition of MonadState uses those extensions. > > Thanks, yes it helps and explains all. :^) > > I suppose then that if -XFlexibleContexts is indeed required by the > standard libraries, it is a "safe" extension, meaning supported by all >

Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-23 Thread Luke Palmer
On Tue, Jun 23, 2009 at 2:20 AM, wrote: > > Simple: the definition of MonadState uses those extensions. > > Thanks, yes it helps and explains all. :^) > > I suppose then that if -XFlexibleContexts is indeed required by the > standard libraries, it is a "safe" extension, meaning supported by all >

Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-23 Thread Luke Palmer
On Tue, Jun 23, 2009 at 6:05 PM, Eric Dedieu wrote: > So > > 1) How can I use transformers instead of the mtl? This is in no > tutorial, and searchinf for "mtl" on the haskell wiki yields no > result at all. > cabal install transformers (you need cabal-install to do this... consult #haskell i

Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature

2009-06-23 Thread Luke Palmer
On Tue, Jun 23, 2009 at 6:05 PM, Eric Dedieu wrote: > Now, trying to avoid duplicate code at this very level of simplicity > seems to require compiler extensions! Here it is: On a higher level, in case you are interested, here's a description of how I would model your problem. Take this with a

Re: Forward compatibility (was Re: [Haskell-cafe] GHCi infers a type but refuses it as type signature)

2009-06-24 Thread Luke Palmer
On Tue, Jun 23, 2009 at 8:28 PM, Brandon S. Allbery KF8NH < allb...@ece.cmu.edu> wrote: > On Jun 23, 2009, at 05:20 , Luke Palmer wrote: > > obsolete now, will your code still work when they are gone? Will it still > work when the typeclass resolution algorithm is obsol

Re: [Haskell-cafe] lazy data structure for best-first search

2009-06-24 Thread Luke Palmer
On Wed, Jun 24, 2009 at 7:53 PM, Martin Hofmann < martin.hofm...@uni-bamberg.de> wrote: > I am looking for a good (preferably lazy) way to implement some kind of > best-first search. Here's what I came up with. bestFirst :: (Ord o) => (a -> o) -> (a -> [a]) -> [a] -> [a] bestFirst rate edges =

Re: [Haskell-cafe] Using unsafePerformIO safely

2009-06-24 Thread Luke Palmer
On Wed, Jun 24, 2009 at 7:56 PM, Hector Guilarte wrote: > Thanks for answering so fast. > > Yes, GCL == Guarded Command Language... It is for an assigment I have in my > Languages and Machines Course. > > About the nicer/Haskellier solution you proposed: If there is a way of > printing right in th

Re: [Haskell-cafe] Using unsafePerformIO safely

2009-06-24 Thread Luke Palmer
On Wed, Jun 24, 2009 at 11:13 PM, Hector Guilarte wrote: > > Thanks! Actually, if I understood well what you proposed, that's how I > first tought of doing it, but with a [Maybe String] and only append whenever > I actually had a (Just string), but as I said before, I don't think my > teacher is

Re: [Haskell-cafe] Network.CGI -- practical web programming example.

2009-06-27 Thread Luke Palmer
Your code examples are: On Sat, Jun 27, 2009 at 6:07 PM, Edward Ing wrote: > saveFile n = >do cont <- (liftM fromJust) $ getInputFPS "file" > let f = uploadDir ++ "/" ++ basename n > liftIO $ BS.writeFile f cont > return $ paragraph << ("Saved as " +++ anchor

Re: [Haskell-cafe] Monad Input/Output and Monad Transformers

2009-07-02 Thread Luke Palmer
On Thu, Jul 2, 2009 at 5:31 AM, Maciej Piechotka wrote: > 2. I find writing monad transformers annoying. > Additionally if package defines transformer A and another transformer B > they need to be connected 'by hand'. You have not given any concrete problems or examples, so it's hard for me to c

Re: [Haskell-cafe] How to present the commonness of some objects?

2009-07-03 Thread Luke Palmer
On Thu, Jul 2, 2009 at 8:32 PM, Magicloud Magiclouds < magicloud.magiclo...@gmail.com> wrote: > Wow, this complex Thank you. I will try that. No, don't! There is an easier way. Don't use a class, just use a record. I would translate your class as: data Widget = Widget { widgetRun ::

Re: [Haskell-cafe] How to present the commonness of some objects?

2009-07-03 Thread Luke Palmer
2009/7/3 Ross Mellgren > Wordy (and yet technically accurate) names aside, isn't this basically the > same thing, except that you must pass the dictionary around by hand? > A SomeWidget is defined as "any object which has a Widget dictionary". It's still an object; the link from it to its dicti

Re: [Haskell-cafe] Implementing Las Vegas algorithms in Haskell

2009-07-06 Thread Luke Palmer
2009/7/6 Matthias Görgens > A Las Vegas algorithm, like randomized quicksort, uses a source of > randomness to make certain decisions. However its output is > unaffected by the randomness. So a function > > > f :: RandomGen g => g -> a -> b > > implementing a Las-Vegas-Algorithm 'looks' like a

Re: [Haskell-cafe] Implementing Las Vegas algorithms in Haskell

2009-07-07 Thread Luke Palmer
2009/7/7 Matthias Görgens > >> What I wondered was, if one could hid the random plumbing in some data > >> structure, like the state monad, but less linear. > > > > This problem cries for a State monad solution - but you don't need to > > do it yourself, there's already a Random monad defined for

Re: [Haskell-cafe] Are GADTs what I need?

2009-07-13 Thread Luke Palmer
On Mon, Jul 13, 2009 at 6:09 AM, Chris Eidhof wrote: > Hey Kev, > > The types are "thrown away" during compile time. Therefore, if you have a > constructor "VWrapper :: a -> Value" nothing is known about that "a" when > you scrutinize it. > > What you could do, however, is something like this: >

Re: [Haskell-cafe] Re: Are GADTs what I need?

2009-07-13 Thread Luke Palmer
On Mon, Jul 13, 2009 at 10:33 PM, Ashley Yakeley wrote: > On Mon, 2009-07-13 at 23:20 -0700, Jason Dagit wrote: > > data EqualType a b where > >MkEqualType :: EqualType t t > > > > Is there any reason to prefer this over: > > data EqualType a b where > > MkEqualType :: Equal

Re: [Haskell-cafe] Pattern matching does not work like this?

2009-07-15 Thread Luke Palmer
On Wed, Jul 15, 2009 at 3:08 AM, Hans Aberg wrote: > On 15 Jul 2009, at 12:25, Eugene Kirpichov wrote: > > If ++ could be pattern matched, what should have been the result of >> "let (x++y)=[1,2,3] in (x,y)"? >> > > It will branch. In terms of unification, you get a list of substitutions. f ::

Re: [Haskell-cafe] powerSet = filterM (const [True, False]) ... is this obfuscated haskell?

2009-07-17 Thread Luke Palmer
On Fri, Jul 17, 2009 at 1:35 AM, Thomas Hartman wrote: > on haskell reddit today > > powerSet = filterM (const [True, False]) The M is the list, i.e. *nondeterminism* monad. For each element in the list, there is one return value where it appears (True), and one where it does not (False). Ba

Re: [Haskell-cafe] Testing nested implication properties with QuickCheck?

2009-07-27 Thread Luke Palmer
2009/7/27 Ahn, Ki Yung : > How should I you use QuickCheck for testing a property that is a nested > implecation such as (A ==> B) ==> C ? You could use the classical equivalence (A ==> B) <=> (~A \/ B). I'm not sure you would get very much out of the implication strategy for the nested one, anyw

Re: [Haskell-cafe] Importing Control.Arrow changes inferred type of (m >>= f) x in ghci

2009-07-27 Thread Luke Palmer
On Mon, Jul 27, 2009 at 7:58 PM, Dan Weston wrote: > The following inferred type has a constraint that can be trivially > satisfied, but isn't: > > Control.Monad> :t \ (m,f,x) -> (m >>= f) x > \ (m,f,x) -> (m >>= f) x >  :: forall t a b. (Monad ((->) t)) => (t -> a, a -> t -> b, t) -> b > > -- In C

Re: [Haskell-cafe] [Haskell Cafe] Data construction: how to avoid boilerplate code?

2009-07-29 Thread Luke Palmer
On Wed, Jul 29, 2009 at 6:27 AM, Paul Sujkov wrote: > Hi haskellers, > > I have a datatype of this sort: > > data Type = Status >   | Message >   | Warning >   | Error >   | StepIn >   | StepOut deriving (Eq, Show) > > and (at this moment) two fabric-like fun

Re: [Haskell-cafe] [Haskell Cafe] Data construction: how to avoid boilerplate code?

2009-07-29 Thread Luke Palmer
ot;, Integer 240) >   | Message <-- (String "-M-", Integer 64) >   | Warning <-- (String "-W-", Integer 32) > > however, I'm not sure this one is really needed. Something for the (*) is > much more interesting > > 2009/7/2

Re: [Haskell-cafe] [Haskell Cafe] Troubles with StateT and Parsec

2009-08-03 Thread Luke Palmer
On Mon, Aug 3, 2009 at 11:46 AM, Paul Sujkov wrote: > 2) too many lifts in the code. I have only one function that really affects > state, but code is filled with lifts from StateT to underlying Parser You do know you can do this, right? do x <- get put (x + 1) lift $ do etc e

Re: [Haskell-cafe] Library function for map+append

2009-08-18 Thread Luke Palmer
2009/8/18 Dusan Kolar : > Dlists maybe good it all the app is written using them. Probably not good > idea to switch to them in the middle of project... I have a different criterion for DLists. I think they are best to use in small scopes (I think the same of monads), as opposed to interfacing be

Re: [Haskell-cafe] (no subject)

2009-08-21 Thread Luke Palmer
On Fri, Aug 21, 2009 at 7:03 PM, Sebastian Sylvan wrote: >> I think that there must be standard function that can do this. What do >> experienced Haskellers use? > > I usually just whip up a quick parser using Text.ParserCombinators.Parsec I usually prefer ReadP for quick stuff, for an unknown rea

Re: [Haskell-cafe] STM problems

2009-08-23 Thread Luke Palmer
On Sun, Aug 23, 2009 at 1:33 AM, Michael Speer wrote: > data HashTable a b = HashTable (a -> Int) (STM (Array Int (TVar (Maybe b So wait... a HashTable is a hash function together with an *action returning an array of TVars?*I don't think that's right. It looks like that action is recreat

Re: Re[Haskell-cafe] duction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread Luke Palmer
On Fri, Aug 28, 2009 at 3:54 AM, staafmeister wrote: > Thanks for the memo trick! Now I understand that the haskell compiler > cannot memoize functions of integers, because it could change the space > behaviour. However I think it could memoize everything else. Because all > types that are data obj

Re: Re[2]: Re[Haskell-cafe] [2]: Re[2]: Re[2]: Reduction Sequence of simple Fibonacci sequence implementation

2009-08-28 Thread Luke Palmer
On Fri, Aug 28, 2009 at 6:04 AM, Bulat Ziganshin wrote: > Hello staafmeister, > > Friday, August 28, 2009, 3:31:13 PM, you wrote: > >> All the values that are computed but are also GCed (and they will be, 10^9 >> bytes >> is the mem limit). If the GC removes a value then all references in cache to

Re: [Haskell-cafe] How to fix such a TYPE problem ?

2009-08-31 Thread Luke Palmer
On Mon, Aug 31, 2009 at 9:47 PM, zaxis wrote: > >>let [y,m,d] = map (\x -> read x::Int) $ splitRegex (mkRegex "-") > "2009-08-31" >>fromGregorian y m d > > Couldn't match expected type `Integer' against inferred type `Int' >    In the first argument of `fromGregorian', namely `y' >    In the expres

Re: [Haskell-cafe] Question about Lazy.IO

2009-09-01 Thread Luke Palmer
On Tue, Sep 1, 2009 at 3:05 AM, staafmeister wrote: > Hi, > > I've been wondering about Lazy IO for a while. Suppose we have a program > like > > main = interact (unlines . somefunction . lines) > > then somefunction is a pure function. With the semantic interpretation of: > given a input list > re

  1   2   3   4   5   6   7   >