Re: [Haskell-cafe] Small optimisation question

2007-11-17 Thread Jake McArthur
On Nov 17, 2007, at 11:26 AM, Stefan O'Rear wrote: The STG-machine was brilliant when it was designed, but times have changed. In particular, indirect jumps are no longer cheap. Pointer tagging has allowed STG to hobble into the 21st century, but really the air is ripe for a new abstract

Re: [Haskell-cafe] New to Haskell

2007-12-19 Thread Jake McArthur
On Dec 19, 2007, at 6:25 PM, John Meacham wrote: On Tue, Dec 18, 2007 at 01:58:00PM +0300, Miguel Mitrofanov wrote: I just want the sistem to be able to print one of these expressions ! Its this too much to ask ? Yes, 'cause it means you want to embed almost all source code into the

Re: [Haskell-cafe] Specializing classes with classes

2007-12-29 Thread Jake McArthur
On Dec 28, 2007, at 10:18 PM, [EMAIL PROTECTED] wrote: Quoting alex [EMAIL PROTECTED]: I would like to do this: class Foo t where hi :: t - Bool class Foo t = Bar t where hi x = True This is arguably one of the most requested features in Haskell. The only reason why

Re: [Haskell-cafe] Basic question concerning data constructors

2007-12-30 Thread Jake McArthur
On Dec 30, 2007, at 8:24 AM, Joost Behrends wrote: For adapting hws (one of the reasons for me to be here, not many languages have a native web server) to Windows i must work on time. In System.Time i found data ClockTime = TOD Integer Integer 2 questions arise here: Does this define TOD

Re: [Haskell-cafe] ReRe: Basic question concerning data constructors

2007-12-30 Thread Jake McArthur
On Dec 30, 2007, at 12:32 PM, Joost Behrends wrote: Thanks to both fast answers. there remain problems with Jakes mail for me. This: When you define datatypes, you are essentially defining a type-level constructors on the left hand side and (value-level) constructors on the right hand side.

Re: [Haskell-cafe] Re: Web server continued

2007-12-31 Thread Jake McArthur
On Dec 31, 2007, at 6:50 AM, Cristian Baboi wrote: On Mon, 31 Dec 2007 14:36:02 +0200, Joost Behrends [EMAIL PROTECTED] wrote: I forgot 2 things: The distinction between '=' and '==' is much like in C, although mixing them up is not so dangerous like in C. ':=' and '=' like in Wirth

Re: [Haskell-cafe] Trying to fix space leak

2007-12-31 Thread Jake McArthur
On Dec 31, 2007, at 9:53 AM, Paul Johnson wrote: I'd advise against trying to make your program stricter because you might suddenly find yourself building an entire 6GB structure in memory before traversing it, which would not be a Good Thing. I disagree. It might be the case that the

Re: [Haskell-cafe] Re: Trying to fix space leak

2007-12-31 Thread Jake McArthur
On Dec 31, 2007, at 11:21 AM, Achim Schneider wrote: Jake McArthur [EMAIL PROTECTED] wrote: I disagree. It might be the case that the _contents_ of the data structure are lazy, in which case I would say the relevant constructor parameters should be made strict. As long as the structural parts

Re: [Haskell-cafe] Re: Tim Sweeney (the gamer)

2008-01-10 Thread Jake McArthur
On Jan 10, 2008, at 1:57 PM, Achim Schneider wrote: Now don't make me think of using par on a beowolf cluster of ps3's. Never in my life have I _literally_ drooled over using a programming abstraction. - Jake___ Haskell-Cafe mailing list

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

2010-03-10 Thread Jake McArthur
Here's a transcript from a conversation I had with Conal on IRC. tl;dr: conal cross-module inlining is only possible because ghc stashes a definition in a .hi, iuuc. i'm suggesting that the stashed definition either (a) never include further inlinings, or (b) be augmented by such a definition.

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

2010-04-04 Thread Jake McArthur
On 04/04/2010 06:35 PM, Ivan Miljenovic wrote: I would wonder _why_ anyone would refuse to do so. Are they that ashamed of their own software that they wouldn't want to be associated with it, or is there some legal reason that they don't want to be associated with it? This seems to be

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

2010-04-05 Thread Jake McArthur
On 04/05/2010 11:32 PM, Ivan Miljenovic wrote: 4) The people who support the policy don't see why anyone has a problem with it. I have seen no logical explanation of *why* anybody supports this policy. I've only seen vague hand-wavy statements like people who use real names are more

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

2010-04-06 Thread Jake McArthur
On Tue, Apr 6, 2010 at 6:08 AM, Serguey Zefirov sergu...@gmail.com wrote: http://lambda-the-ultimate.org is one lovely community that has that restriction: http://lambda-the-ultimate.org/policies#Policies I quote the policy in full here: Many of us here post with our real, full names.

Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-23 Thread Jake McArthur
On 05/23/2010 02:17 PM, Peter Verswyvelen wrote: IMO: For AAA game programming? Definitely not. Why not? I suppose it may depend on your definition of AAA, since there doesn't seem to be any consensus on it. I have seen it mean various combinations of the following, but rarely, if ever, all

Re: [Haskell-cafe] Proposal: Sum type branches as extended types (as Type!Constructor)

2010-06-03 Thread Jake McArthur
On 06/03/2010 10:14 AM, Gabriel Riba wrote: No need for runtime errors or exception control hd :: List!Cons a - a hd (Cons x _) = x This is already doable using GADTs: data Z data S n data List a n where Nil :: List a Z Cons :: a - List a n - List a (S n)

Fwd: [Haskell-cafe] Rewriting a famous library and using the same name: pros and cons

2010-06-08 Thread Jake McArthur
Sorry, I hit Reply instead of Reply To All. -- Forwarded message -- From: Jake McArthur jake.mcart...@gmail.com Date: Tue, Jun 8, 2010 at 6:16 PM Subject: Re: [Haskell-cafe] Rewriting a famous library and using the same name: pros and cons To: Don Stewart d...@galois.com Making

Re: [Haskell-cafe] Construction of short vectors

2010-06-28 Thread Jake McArthur
On Sun, Jun 27, 2010 at 4:44 PM, Alexey Khudyakov alexey.sklad...@gmail.com wrote: Dependent types would be nice but there isn't anything usable out there. Newtype wrapper parametrized by type level number works fine so far. If you interested sources are available here:

Re: [Haskell-cafe] [C Binding] Turning the mutable to immutable?

2010-07-05 Thread Jake McArthur
On 07/05/2010 04:48 PM, Yves Parès wrote: 3) Is there another library on hackage that handles images in a functional way? (I mean not /all in IO/) Check out graphics-drawingcombinators. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] trees and pointers

2010-07-14 Thread Jake McArthur
On 07/14/2010 05:01 PM, Victor Gorokhov wrote: You can implement pure pointers on top of Data.Map with O(log n) time Or on top of Data.IntMap with O(1) time. ;) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread Jake McArthur
On 07/15/2010 02:30 AM, Stephen Tetley wrote: 2010/7/15 Jake McArthurjake.mcart...@gmail.com: On 07/14/2010 05:01 PM, Victor Gorokhov wrote: You can implement pure pointers on top of Data.Map with O(log n) time Or on top of Data.IntMap with O(1) time. ;) Unlikely... From the docs,

Re: [Haskell-cafe] trees and pointers

2010-07-15 Thread Jake McArthur
On 07/15/2010 05:33 PM, Victor Gorokhov wrote: Thanks for an example! Probably, one can think about using Arrays instead of Map or IntMap in order to achieve 'true' O(1) in pure. But I suppose that there are some trouble with array expanding. Or somebody would already make it. Pure arrays

Re: [Haskell-cafe] MonadLib usage

2010-07-18 Thread Jake McArthur
On 07/18/2010 08:27 AM, Ivan Lazar Miljenovic wrote: When discussing a similar issue with Manuel Chakravarty, he convinced me that cunning newtype deriving is actually rather bad in practice and shouldn't be used as there's a lack of proofs or some such (I can't remember the arguments, but I

Re: [Haskell-cafe] Hangman game

2008-01-21 Thread Jake McArthur
On Jan 20, 2008, at 1:03 PM, Yitzchak Gale wrote: Generating an infinite list from a random generator burns up the generator, making it unusable for any further calculations. That's what the split function is for. ^_^ - Jake ___ Haskell-Cafe

Re: [Haskell-cafe] Problem with HGL

2008-01-26 Thread Jake McArthur
On Jan 26, 2008, at 12:20 PM, jia wang wrote: Graphics/HGL/Key.hs:57:7: Could not find module `Graphics.Win32': it is a member of package Win32-2.1.1.0, which is hidden You need to install the Win32 package. http://hackage.haskell.org/cgi-bin/hackage-scripts/package/Win32-2.1.0.0 -

Re: [Haskell-cafe] existential types

2008-02-13 Thread Jake McArthur
Oops, I was hasty in typing those data definitions. They will not work because they have no constructors. Sorry about that. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] existential types

2008-02-13 Thread Jake McArthur
From: Jake McArthur [EMAIL PROTECTED] Date: February 13, 2008 7:04:49 PM CST To: Felipe Lessa [EMAIL PROTECTED] Subject: Re: [Haskell-cafe] existential types On Feb 13, 2008, at 11:15 AM, Felipe Lessa wrote: On Feb 13, 2008 2:41 PM, Jake McArthur [EMAIL PROTECTED] wrote: Now we can have

Re: [Haskell-cafe] Re: Shouldn't this loop indefinitely = take (last [0..]) [0..]

2008-04-04 Thread Jake Mcarthur
On Apr 4, 2008, at 11:31 AM, Loup Vaillant wrote: I mean, could we calculate this equality without reducing length ys to weak head normal form (and then to plain normal form)? Yes. Suppose equality over Nat is defined something like: Z == Z = True S x == S y = x == y x == y

Re: [Haskell-cafe] ghc

2008-04-11 Thread Jake Mcarthur
On Apr 10, 2008, at 1:20 PM, Brent Yorgey wrote: This is true for any compiler that produces native binaries (as opposed to certain languages which require a virtual machine...) Unless, of course, it results in a dynamically linked binary, which I'm pretty sure GHC doesn't support at all

Re: [Haskell-cafe] install trouble with SDL on win32+cygwin

2008-04-11 Thread Jake Mcarthur
On Apr 11, 2008, at 8:37 PM, Conal Elliott wrote: I'm trying to install the SDL package (on win32+cygwin), and configure isn't able to find my SDL.dll, though it's on my PATH. Any ideas? - Conal I think this has been a known (neglected?) issue for quite some time. That's why I am not

Re: [Haskell-cafe] install trouble with SDL on win32+cygwin

2008-04-12 Thread Jake Mcarthur
On Apr 12, 2008, at 9:48 PM, Conal Elliott wrote: If not, is GLFW the recommended cross-platform GL toolkit? Don't forget there is GLUT as well. – Jake___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Parallel weirdness

2008-04-19 Thread Jake Mcarthur
On Apr 19, 2008, at 9:56 AM, Andrew Coppin wrote: Weird thing #3: Adding the -threaded compiler option makes *everything* run a few percent faster. Even with only 1 OS thread. I had a similar thing happen to me once.

Re: [Haskell-cafe] Parallel weirdness

2008-04-19 Thread Jake Mcarthur
Okay, here are my thoughts: On Apr 19, 2008, at 9:56 AM, Andrew Coppin wrote: Weird thing #1: The first time you sort the data, it takes a few seconds. The other 7 times, it takes a split second - roughly 100x faster. Wuh? This looks like standard memoization to me. I know, I know, GHC

Re: [Haskell-cafe] n00b circular dep question

2008-04-25 Thread Jake Mcarthur
On Apr 25, 2008, at 11:54 AM, Jennifer Miller wrote: I have a circular dependency in my modules that I don't know how to resolve in Haskell. I'm pretty sure that GHC will sort out those dependencies for you as long as you are exporting the correct things from each module. - Jake

[Haskell-cafe] Caching the Result of a Transaction?

2008-04-26 Thread Jake Mcarthur
this would be to change the STM implementation slightly and create a new primitive function. If there is a way to do something like this with the current STM API, I would love to hear suggestions. Any ideas? - Jake McArthur ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Trouble compiling collections-0.3 (from Hackage)

2008-04-26 Thread Jake Mcarthur
On Apr 26, 2008, at 4:25 PM, David F. Place wrote: Data/Collections.hs:154:17: Could not find module `Data.ByteString.Lazy': it is a member of package bytestring-0.9.0.4, which is hidden In the .cabal file, add bytestring to the dependencies property. - Jake

Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-26 Thread Jake Mcarthur
On Apr 26, 2008, at 7:18 PM, Conal Elliott wrote: Here's another angle on part of Jake's question: Can we implement a type 'TIVal a' (preferably without unsafePerformIO) with the following interface: newIVal :: STM (TIVal a, a - STM ()) -- or IO (...) force :: TIVal a - STM a

Re: [Haskell-cafe] Caching the Result of a Transaction?

2008-04-27 Thread Jake Mcarthur
On Apr 27, 2008, at 10:05 AM, Jake Mcarthur wrote: On Apr 27, 2008, at 9:36 AM, Conal Elliott wrote: I think we *do* want unsafeNewEmptyTMVar inlined. Here's a convenient caching wrapper: cached :: STM a - TIVal a cached m = TIVal m (unsafePerformIO newEmptyTMVarIO) Yes

Re: [Haskell-cafe] Something like optimistic evaluation

2008-04-28 Thread Jake Mcarthur
On Apr 28, 2008, at 5:09 PM, Daniil Elovkov wrote: Somewhat on the topic of optimistic evaluation, I've just thought of another way to evaluate thunks. When the program is about to block on some IO, what if we start a thread to evaluate (any) unevaluated thunks. We'll have additional

Re: [Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-28 Thread Jake Mcarthur
On Apr 28, 2008, at 10:01 PM, Ryan Ingram wrote: [...] if you have a :: TIVal a, and f :: a - TIVal b, and you execute force (a = f) and the action returned by f executes retry for whatever reason, then the caching done in a gets undone. Dangit, you're right. You just rained on the parade!

Re: [Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-29 Thread Jake Mcarthur
On Apr 28, 2008, at 10:01 PM, Ryan Ingram wrote: The problem I have with all of these STM-based solutions to this problem is that they don't actually cache until the action fully executes successfully. I just hacked together a new monad that I think might solve this, at least with a little

Re: [Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-29 Thread Jake Mcarthur
*sigh* As is usual with my untested code, the code I just sent was wrong. I will be able to actually test, correct, and refine it tonight. If nobody else has picked it up by then I will do so. - Jake ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Re: Caching the Result of a Transaction?

2008-04-29 Thread Jake Mcarthur
Alright, I have tested it now. I still feel funny about most of the names I chose for the types and functions, and it's still very ugly, but the code appears to work correctly. In this version I have also added retry and orElse functions so that it can feel more like the STM monad. I think

Re: [Haskell-cafe] Help me speed up my program... or back to the issue of memoization

2008-05-05 Thread Jake Mcarthur
/2006/MemoMixins.pdf for an example. - Jake McArthur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] I/O without monads, using an event loop

2008-05-30 Thread Jake Mcarthur
On May 30, 2008, at 9:09 AM, Robin Green wrote: eventMain :: (Event, SystemState AppState) - (Command, SystemState AppState) The first thing I would do with this type is probably wrap it up in a State monad so I don't have to keep track of the SystemState AppState stuff myself, which

Re: [Haskell-cafe] const is question

2008-06-14 Thread Jake Mcarthur
that help? - Jake McArthur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Designing a DSL?

2009-10-02 Thread Jake McArthur
Günther Schmidt wrote: And that I find to be the really tricky part, how do I *design* a DSL? My favorite approach is something like as described in these: http://lukepalmer.wordpress.com/2008/07/18/semantic-design/ http://conal.net/papers/type-class-morphisms/ It takes a little bit of

Re: [Haskell-cafe] dsl and gui toolkit

2009-10-05 Thread Jake McArthur
If you could throw it on Hackage or a public repo you will get more exposure. :) - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] GPipe example and screenshot

2009-10-08 Thread Jake McArthur
Tobias Bexelius wrote: I've put a simple GPipe example (including a screenshot) on the haskellwiki now, showing off an animated spinning box. Nice to see Data.Vec.LinAlg.Transform3D! That will be a big help. I'm having fun with GPipe. Thanks for the library! - Jake

Re: [Haskell-cafe] newtype deriving Alternative

2009-10-14 Thread Jake McArthur
Martijn van Steenbergen wrote: It doesn't work for this one: newtype Split a = Split { runSplit :: [Either a (Char, Split a) ]} But my handwritten instance remains identical. The instance has the form [], not the form [Either _ (Char, Split _)]. Since they don't match exactly, it won't

Re: [Haskell-cafe] What does :*: mean again?

2009-10-23 Thread Jake McArthur
Nothing by itself. It's just a definable constructor of some sort. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Calling all Haskellers in Huntsville, Alabama, or surrounding areas!

2009-11-10 Thread Jake McArthur
Shae Errisson, myself, Greg Bacon, and some other locals who I think might not have as big a presence online are starting a user's group in Huntsville, AL. Please join the Google group / mailing list [1] if you are interested! [1] http://groups.google.com/group/alabamahaskell - Jake McArthur

Re: [Haskell-cafe] ANN: bindings-SDL 1.0.2, the domain specific language for FFI description

2009-11-19 Thread Jake McArthur
I did not notice when this was released, but I saw it on Hackage yesterday and, with it, wrote some of the easiest bindings to a fairly complex C API I've written in a while. This package is excellent! Thank you for sharing it. My only complaint is that the macros get confused if you use a

Re: [Haskell-cafe] Re: ANN: bindings-SDL 1.0.2, the domain specific language for FFI description

2009-11-19 Thread Jake McArthur
Maurí­cio CA wrote: My only complaint is that the macros get confused if you use a Haskell type that has a single quote in it. Can you give me an example? It turns out that I read the documentation incorrectly, but here is what I was trying to do. I had two structs, one of which used

Re: [Haskell-cafe] Re: ANN: bindings-SDL 1.0.2, the domain specific language for FFI description

2009-11-20 Thread Jake McArthur
Maurí­cio CA wrote: I believe I forgot to write a section with that information, as well as others one would like to know from start. I wrote a new section trying to fix that in 'how to use it' topic. http://bitbucket.org/mauricio/bindings-dsl/wiki/HowToUseIt Very nice. I think that is clear

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

2010-03-07 Thread Jake McArthur
I've run into an issue with inlining that I'm not sure how to work around. I am instantiating some pre-existing type classes with Vector-based types. There already exist generic functions in modules I do not control that use this type class, and they are not tagged with the INLINE pragma. I am

[Haskell-cafe] Google AI Challenge: Planet Wars - Accepting Haskell Submissions

2010-09-10 Thread Jake McArthur
Just wanted to let everybody know that there is an AI contest [1] that started today. Everybody has about two months to create bots that compete against each other 1-on-1 in a game based on Galcon [2]. A couple issues to mention for full disclosure: There is some sponsorship by Google, but

Re: [Haskell-cafe] Ultra-newbie Question

2010-09-18 Thread Jake McArthur
On 09/18/2010 02:51 AM, Christopher Tauss wrote: I am trying to write a function that takes a list and returns the last n elements. This may just be for the sake of learning, in which case this is fine, but usually, needing to do this would be a sign that you are using lists improperly

Re: [Haskell-cafe] Layered maps

2010-10-08 Thread Jake McArthur
On 10/08/2010 04:23 PM, Alex Rozenshteyn wrote: Does there exist a library which allows me to have maps whose elements are maps whose elements ... with a convenient syntax. It sounds like you might be looking for a trie of some sort. Would something like the TrieMap package suit your needs?

Re: [Haskell-cafe] Layered maps

2010-10-09 Thread Jake McArthur
What you describe sounds like a perfect job for a trie, so that's what I think you should look into. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Haskell Weekly News: Issue 159 - November 17, 2010

2010-11-17 Thread Jake McArthur
On 11/17/2010 09:56 PM, Daniel Santa Cruz wrote: Curious about the most active members of the #haskell IRC channel? Out of around 28K utterances in the channel this week, 24% of them where spoken by the top 5 most active members. Not suprisingly, the dear lambdabot is at the top

Re: [Haskell-cafe] DPH and GHC 7.0.1

2010-11-19 Thread Jake McArthur
On 11/19/2010 05:24 PM, Gregory Propf wrote: I was hoping to play around with Data.Parallel.Haskell (dph) but noticed that it seems to have been exiled from ghc 7.0.1 which I just installed. It also doesn't seem to be in cabal. Anybody know how to use dph with 7.0.1 or has it been abandoned or

Re: [Haskell-cafe] Offer to mirror Hackage

2010-12-04 Thread Jake McArthur
I am no decision maker regarding Hackage, but I would like to echo my support for this offer. Hackage is a vital part of my workflow, and I'm sure I'm not the only one. Its importance to the Haskell community has grown quickly and is continuing to do so. Each time it goes down, the impact is

Re: [Haskell-cafe] Polymorphic function over pairs of maybes.

2010-12-28 Thread Jake McArthur
FromMaybe String where type Maybe' String = Maybe String fromMaybe = Data.Maybe.fromMaybe instance (FromMaybe a, FromMaybe b) = FromMaybe (a, b) where type Maybe' (a, b) = (Maybe' a, Maybe' b) fromMaybe (x, y) (a, b) = (fromMaybe x a, fromMaybe y b) - Jake McArthur

Re: [Haskell-cafe] Type System vs Test Driven Development

2011-01-05 Thread Jake McArthur
On 01/05/2011 03:44 AM, Jonathan Geddes wrote: When I write Haskell code, I write functions (and monadic actions) that are either a) so trivial that writing any kind of unit/property test seems silly, or are b) composed of other trivial functions using equally-trivial combinators. There are

Re: [Haskell-cafe] Guy Steele's Praise For Haskell @ Strange Loop Keynote

2011-01-15 Thread Jake McArthur
So everybody doesn't have to go watch it, here is a shortened version of what Steele said in the video: Although Fortress is originally designed as an object-oriented framework in which to build an array-style scientific programming language, [...] as we've experimented with it and tried to

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

2009-04-20 Thread Jake McArthur
Sure, so hnf would give us a non-determined result, but I don't think that makes unamb any less referentially transparent – the same value is always returned, and always reduced at least to hnf. I think it is hnf that Peter was talking about needing to be in IO, not unamb. - Jake

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

2009-04-20 Thread Jake McArthur
Christopher Lane Hinson wrote: What we'd like to avoid is duplicate verification that a thunk is hnf. Do we have evidence that this verification ever actually consumes a lot of resources? I think the OP is trying to avoid spawning unnecessary threads at the cost of duplicate checks for HNF.

Re: [Haskell-cafe] Getting the x out

2009-04-22 Thread Jake McArthur
michael rice wrote: Got it! I figured there must be some way to unpack it. If you peek at the thread about getting a value out of IO [1], you will see some similarities. If you look at my response [2], you will see that the functions I suggested for IO are exactly the same as the functions

Re: [Haskell-cafe] Haskell and symbolic references

2009-05-29 Thread Jake McArthur
Patrick LeBoutillier wrote: Hi all, Is it possible with Haskell to call a function whose name is contained in a String? Something like: five = call_func add [2, 3] You could use Data.Map: call_func = (funcMap !) where funcMap = fromList [ (add, add)

Re: [Haskell-cafe] Non Empty List?

2009-06-04 Thread Jake McArthur
GüŸnther Schmidt wrote: data Container a = Single a | Many a [a] but the problem above is that the data structure would allow to construct a Many 5 [] :: Container Int. I think you meant to do either data Container a = Single a | Many a (Container a) or data Container a =

Re: [Haskell-cafe] curious about sum

2009-06-13 Thread Jake McArthur
Keith Sheppard wrote: Is there any reason that sum isn't strict? I can't think of any case where that is a good thing. Prelude sum [0 .. 100] *** Exception: stack overflow As others have said, there are cases where non-strictness is what you want. And if you are using a type that is

Re: [Haskell-cafe] Tree Semantics and efficiency

2009-06-17 Thread Jake McArthur
Rouan van Dalen wrote: It is important to store only a reference to the parent and not a copy of the entire parent for efficiency. Others have already recommended the rosezipper package, which gives you what you want, but I want to address one thing. foo = stuff bar = foo In most

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

2009-06-17 Thread Jake McArthur
Jon Strait wrote: I'm reading the third (bind associativity) law for monads in this form: m = (\x - k x = h) = (m = k) = h Arguably, that law would be better stated as: (h = k) = m = h = (k = m) This wouldn't be so unintuitive. - Jake ___

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

2009-06-18 Thread Jake McArthur
Hans van Thiel wrote: The only place I've ever seen Kleisli composition, or its flip, used is in demonstrating the monad laws. Yet it is so elegant and, even having its own name, it must have some practical use. Do you, or anybody else, have some pointers? I only just started finding places to

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

2009-06-18 Thread Jake McArthur
Jake McArthur wrote: Generally, you can transform anything of the form: baz x1 = a = b = ... = z x1 into: baz = a = b = ... = z I was just looking through the source for the recently announced Hyena library and decided to give a more concrete example from a real-world project

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

2009-06-18 Thread Jake McArthur
Hans van Thiel wrote: Just to show I'm paying attention, there's an arrow missing, right? (.) ::(b - c) - (a - b) - (a - c) Correct. I noticed that after I sent it but I figured that it would be noticed. I also used () where I meant (=) at the bottom. They are

Re: [Haskell-cafe] Installing agda through cabal

2009-06-19 Thread Jake McArthur
Paulo J. Matos wrote: As you can see, I had just finished installing alex 2.3.1, so why does cabal still request alex =2.0.1 3? Probably you don't have alex in your PATH. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] Which one is right?

2009-06-24 Thread Jake McArthur
Linker wrote: Hugs [0,0.1..1] [0.0,0.1,0.2,0.3,0.4,0.5,0.6,0.7,0.8,0.9,1.0] Prelude [0,0.1..1] [0.0,0.1,0.2,0.30004,0.4,0.5,0.6,0.7,0.7999,0.8999,0.] Just floating point errors. In this case, you may be able to get away with something

Re: [Haskell-cafe] RE: Haskell as a first language?

2009-07-14 Thread Jake McArthur
Michael Vanier wrote: Haskell is a wonderful language (my favorite language by far) but it is pretty difficult for a beginner. In fact, it is pretty difficult for anyone to learn in my experience, because it has so many advanced concepts that simply don't exist in other languages, and trying

Re: [Haskell-cafe] Why is there no Zippable class? Would this work?

2009-07-16 Thread Jake McArthur
I think there are some basic equivalents in the TypeCompose and category-extras packages, for the record, but a standalone version wouldn't hurt either! - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] n00b question: defining datatype

2009-07-23 Thread Jake McArthur
Iain Barnett wrote: data Task = Task { title :: String, completed :: Bool, subtasks :: [Task] } This one looks the best to me. Remember, you can just use an empty list if the task has no subtasks. - Jake ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] n00b question: defining datatype

2009-07-23 Thread Jake McArthur
Actually, how about this? import Data.Tree newtype Task = Task (Tree (String, Bool)) Now you already have that tree structure you wanted. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] A mistake in haskellwiki

2009-08-06 Thread Jake McArthur
Don Stewart wrote: leaveye.guo: Hi haskellers: There is a mistake in http://www.haskell.org/haskellwiki/State_Monad It post two functions like this : evalState :: State s a - s - a evalState act = fst $ runState act execState :: State s a - s - s execState act = snd $ runState act

Re: [Haskell-cafe] unsafeDestructiveAssign?

2009-08-11 Thread Jake McArthur
Job Vranish wrote: What I am trying to do is hyper unusual and I really do need an unsafeHorribleThings to do it. Normally when I really, honestly think this, I'm wrong anyway. - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] containers and maps

2009-08-12 Thread Jake McArthur
The monoids package offers something similar to this: mapReduce :: (Generator c, Reducer e m) = (Elem c - e) - c - m If we take (Elem c) to be (item), (e) to be (item'), (c) to be (full), and (m) to be (full'), it's basically the same thing, and offers the same advantages as the ones you

Re: [Haskell-cafe] containers and maps

2009-08-12 Thread Jake McArthur
Jake McArthur wrote: The monoids package offers something similar to this: mapReduce :: (Generator c, Reducer e m) = (Elem c - e) - c - m If we take (Elem c) to be (item), (e) to be (item'), (c) to be (full), and (m) to be (full'), it's basically the same thing, and offers the same

Re: [Haskell-cafe] containers and maps

2009-08-13 Thread Jake McArthur
John Lato wrote: This looks to be essentially the same as the 'map' function in ListLike, and suffers from the same problem. It won't have the performance characteristics of the native map functions. Using e.g. ByteStrings, you're recreating a ByteString by snoc'ing elements. Oh, I see now

Re: [Haskell-cafe] Planning for a website

2009-08-18 Thread Jake McArthur
Colin Paul Adams wrote: One problem will be to get GHC ported to DragonFly BSD, but that can wait until I have a test version of the site working on Linux. I would love to see this. It's the biggest thing blocking me from trying Dragonfly more seriously. WASH attracts me, with it's

Re: [Haskell-cafe] Planning for a website

2009-08-18 Thread Jake McArthur
I forgot to also mention this somewhat recent announcement for a pedantically type safe HTML library: http://www.haskell.org/pipermail/haskell-cafe/2009-August/064907.html - Jake ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] (no subject)

2009-08-22 Thread Jake McArthur
staafmeister wrote: Yes I know but there are a lot of problems requiring O(1) array updates so then you are stuck with IO again Or use ST. Or use IntMap (which is O(log n), but n is going to max out on the integer size for your architecture, so it's really just O(32) or O(64), which is

Re: [haskell-cafe] Monad and kinds

2008-09-02 Thread Jake Mcarthur
you the solution because it sounds like you want to solve this for yourself and learn from it. - Jake McArthur ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [haskell-cafe] Monad and kinds

2008-09-04 Thread Jake Mcarthur
On Sep 4, 2008, at 10:19 AM, Tim Chevalier wrote: The master programmer does not add strictness annotations, for she has not yet run the profiler. My guess would be that a master usually adds strictness annotations as documentation rather than as optimizations. - Jake McArthur

Re: [haskell-cafe] Monad and kinds

2008-09-04 Thread Jake Mcarthur
On Sep 4, 2008, at 9:52 PM, Tim Chevalier wrote: I'm no master, but I've never encountered a situation where strictness annotations would be useful as documentation, nor can I imagine one. I'm no master either, but how about these simple examples? data Stream a = Cons !a (Stream

Re: [haskell-cafe] Monad and kinds

2008-09-04 Thread Jake Mcarthur
On Sep 4, 2008, at 11:23 PM, Jake Mcarthur wrote: To quote a blog article[1] I wrote in June, And of course I would forget to link the article. My bad. [1] http://geekrant.wordpress.com/2008/06/23/misconceptions/ - Jake McArthur ___ Haskell-Cafe

Re: [Haskell-cafe] Is it usual to read a Maybe (IORef a) ?

2008-09-04 Thread Jake Mcarthur
On Sep 4, 2008, at 12:50 PM, minh thu wrote: I'd have thought you wanted IORef (Maybe Thing), which says that the pointer always exists, but may not point to anything. On the other hand Maybe (IORef Thing) says that the pointer may or may not exist. Yes, someone else said it too. But

Re: [haskell-cafe] Monad and kinds

2008-09-04 Thread Jake Mcarthur
languages, as well. What if, as a thought experiment, you tried substituting laziness for strictness in that paragraph of your essay? I think the same points would apply, honestly. Do you believe they would change in some way? - Jake McArthur ___ Haskell

Re: [haskell-cafe] Monad and kinds

2008-09-04 Thread Jake Mcarthur
On Sep 5, 2008, at 12:45 AM, Tim Chevalier wrote: On 9/4/08, Jake Mcarthur [EMAIL PROTECTED] wrote: Two lazy algorithms tend to compose well and result in a lazy algorithm. A lazy algorithm can compose with a strict algorithm in two different ways. One way is for the lazy algorithm

Re: [Haskell-cafe] Line noise

2008-09-22 Thread Jake Mcarthur
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Most people seem far more confused by what a fold might be. A fold by any other name would smell as sweet. ;) -BEGIN PGP SIGNATURE- Version: GnuPG v1.4.8 (Darwin) iEYEARECAAYFAkjYE7kACgkQTkPEVFd3yxh7HwCfVzopoOCgg49YI0Y88g9rjXqI

Re: [Haskell-cafe] Is there already an abstraction for this?

2008-09-23 Thread Jake Mcarthur
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 The first thing I thought of was to try to apply one of the recursion schemes in the category-extras package. Here is what I managed using catamorphism. - - Jake -

Re: [Haskell-cafe] Shooting your self in the foot with Haskell

2008-10-01 Thread Jake McArthur
John Van Enk wrote: I had a co-worker ask me how you'd shoot your self in the foot with Haskell. [...] Some one please give me something more worth of the original list. Couldn't match expected type 'Deer' against inferred type 'Foot' - Jake ___

  1   2   3   >