Re: [Haskell-cafe] Stupid question #374: why is MaybeT not in the standard library?

2008-12-22 Thread J. Garrett Morris
On Mon, Dec 22, 2008 at 2:31 PM, Brian Hurt bh...@spnz.org wrote: But I'm wondering why it's not in the standard library. The standards committee just hasn't gotten around to it yet? Or was there some discussion of this in the past on some (public) maillist, that my admittedly shallow

Re: [Haskell-cafe] Time for a new logo?

2008-12-14 Thread J. Garrett Morris
On Sun, Dec 14, 2008 at 2:38 PM, Don Stewart d...@galois.com wrote: ketil: Nice. For some more hubris, replace 'A' with 'The'. I had the very same thought :) It certainly wouldn't do to let, say, the existence of Concurrent Clean get in the way of our self-promotion. /g -- I am in here

Re: [Haskell-cafe] Instances that shouldn't overlap

2008-11-26 Thread J. Garrett Morris
On Wed, Nov 26, 2008 at 1:54 PM, Miguel Mitrofanov [EMAIL PROTECTED] wrote: Maybe it'd be more intuitive if written backwards: AppEq f a = (Applicative f, Eq a) or even AppEq f a = (Applicative f, Eq a) The first is good, the second isn't. The first says the right thing: if you can prove

Re: [Haskell-cafe] Re: Type question in instance of a class

2008-11-18 Thread J. Garrett Morris
On Tue, Nov 18, 2008 at 1:38 AM, Reiner Pope [EMAIL PROTECTED] wrote: ATs are Associated Types, aka Type Families. They can be found in the GHC 6.10 manual here: http://haskell.org/ghc/docs/6.10.1/html/users_guide/type-families.html As a starting point, you might want to try something like:

Re: [Haskell-cafe] Re: Type question in instance of a class

2008-11-17 Thread J. Garrett Morris
On Mon, Nov 17, 2008 at 10:38 AM, Maurí­cio [EMAIL PROTECTED] wrote: newtype ComplexWithDouble = ComplexWithDouble (ComplexNumber Double) deriving ... Perhaps you want something like: class Complex r c | c - r where makeComplex :: r - r - c realPart :: c - r imagPart

Re: [Haskell-cafe] Type question in instance of a class

2008-11-16 Thread J. Garrett Morris
On Sun, Nov 16, 2008 at 1:32 PM, Maurí­cio [EMAIL PROTECTED] wrote: Hi, Why is this wrong? class MyClass r where function :: r - s data MyData u = MyData u instance MyClass (MyData v) where function (MyData a) = a GHC says that the type of the result of 'function' is both

Re: [Haskell-cafe] getLine and ^C on Windows

2008-11-13 Thread J. Garrett Morris
I've had the same experience with runghc in GHC 6.10.1 on Vista. /g 2008/11/12 Lyle Kopnicky [EMAIL PROTECTED]: Hi folks, I'm using System.IO.getLine to read input in my program. I've compiled it on Windows Vista with ghc-6.10.1. I've noticed that if I press Ctrl+C while the program is

Re: [Haskell-cafe] [Somewhat OT] Speed

2008-10-28 Thread J. Garrett Morris
On Tue, Oct 28, 2008 at 12:31 PM, Andrew Coppin [EMAIL PROTECTED] wrote: This isn't specifically to do with Haskell, but... does anybody have any idea roughly how fast various CPU operations are? Yes: it's architecture dependent. I imagine you'll need to make your questions at least somewhat

Re: [Haskell-cafe] Crash!

2008-10-23 Thread J. Garrett Morris
On Thu, Oct 23, 2008 at 11:00 AM, Andrew Coppin [EMAIL PROTECTED] wrote: I was under the impression that this is impossible, so I'm now slightly worried. I'm not sure why you'd think that: import Foreign fail :: IO Int fail = peek nullPtr main = fail = print /g -- I am in here

Re: [Haskell-cafe] Foreign.Marshal.Error.void

2008-10-14 Thread J. Garrett Morris
mapM and mapM_ have different complexity - I don't know if the compiler would be smart enough to infer mapM_ style behavior for (void . mapM). /g On Tue, Oct 14, 2008 at 10:52 AM, Mauricio [EMAIL PROTECTED] wrote: Hi, Wouldn't it be nice if we had something like 'void' in

[Haskell-cafe] Re: Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-13 Thread J. Garrett Morris
On Mon, Oct 13, 2008 at 12:29 AM, Ryan Ingram [EMAIL PROTECTED] wrote: Of course, the point of this message isn't just to complain. The overlap implementation was abhorrent and it *is* better now than it was before. I'm curious what you find abhorrent about the overlap implementation that was

Re: [Haskell-cafe] Overlapping/Incoherent instances

2008-10-12 Thread J. Garrett Morris
On Sun, Oct 12, 2008 at 2:12 PM, Don Stewart [EMAIL PROTECTED] wrote: Though I note mtl doesn't actually list OverlappingInstances in its .cabal file, Indeed - MTL seems to have been rewritten at some point in the past to prefer exhaustive enumeration to overlap. Thank you for the other

Re: [Haskell-cafe] Haskell PNG Writer

2008-05-09 Thread J. Garrett Morris
As long as you don't mind producing two-color images, http://haskell.org/haskellwiki/Library/PNG is an option. I found it very easy to extend it to eight-bit grayscale - I didn't need fullcolor images. /g On Sat, May 3, 2008 at 11:12 PM, Nahuel Rullo [EMAIL PROTECTED] wrote: Hi list, i am new

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

2008-01-09 Thread J. Garrett Morris
I imagine you can get in touch with him through Epic (www.epicgames.com) if you can't find another way to contact him. /g On Jan 9, 2008 4:21 PM, Galchin Vasili [EMAIL PROTECTED] wrote: Hello, I have been reading with great interested Tim Sweeney's slides on the Next Generation

Re: [Haskell-cafe] A small question

2007-11-21 Thread J. Garrett Morris
On Nov 21, 2007 5:16 AM, Jeremy O'Donoghue [EMAIL PROTECTED] wrote: Not just Windows Vista. Applications and DLLs compiled with Visual Studio 2005 (Express or full version) seem to need it to run on XP as well. I believe the dependency here is version 8 of the Visual C RTL. Applications that

Re: [Haskell-cafe] A small question

2007-11-15 Thread J. Garrett Morris
http://msdn2.microsoft.com/en-us/library/1w45z383(vs.71).aspx I believe. /g On Nov 15, 2007 12:56 PM, Andrew Coppin [EMAIL PROTECTED] wrote: I notice that in GHC 6.8.1, if I compile a runnably program, as well as generating foo.exe, GHC now also generates a file foo.exe.manifest, which

[Haskell-cafe] Memory Leak Help

2007-11-11 Thread J. Garrett Morris
Hello, I have code which seems to contain a memory leak, but I'm not sure where it is or what's causing it. Any help would be greatly appreciated: The code is: data Ratings = Ratings { movieCount :: Int , movieLookup :: IOUArray Int Word32 ,

Re: [Haskell-cafe] Building production stable software in Haskell

2007-09-13 Thread J. Garrett Morris
I believe that rnf from the Control.Parallel.Strategies library shipped with GHC 6.6.1 is equivalent to deepSeq, as in: x `deepSeq` yis equivalent to rnf x `seq` y Isn't it? /g On 9/12/07, Peter Verswyvelen [EMAIL PROTECTED] wrote: Thanks for all the info. It's really good news that

Re: Re[2]: [Haskell-cafe] Is this haskelly enough?

2007-07-18 Thread J. Garrett Morris
This is probably just me, but I've always mentally separated the list monad (representing choice) from operations on ordered sets implemented by lists (which don't always have to represent choice). In this case, since the remainder of the code wasn't monadic, I find it much easier to understand

Re: [Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code cleanup request)

2007-07-18 Thread J. Garrett Morris
On 7/18/07, Dougal Stanton [EMAIL PROTECTED] wrote: I worked out that [ (a,b) | a - as, b - bs ] must be equivalent to comp = concatMap (\x - map ((,) x) ys) xs but I can't really say how conditions like a /= b get slotted in to that style. Is there a reference for that? As I understand it,

Re: [Haskell-cafe] Is this haskelly enough?

2007-07-17 Thread J. Garrett Morris
Hi James. I would be tempted to write this a little differently than you did. First, some of the pieces you've written have equivalents in the standard library; there's no harm in rewriting them, but I figured I'd point out that they're there. (Hoogle - haskell.org/hoogle, I believe - can be a

Re: [Haskell-cafe] Is this haskelly enough? -- errm but every answer is wrong(?)

2007-07-17 Thread J. Garrett Morris
On 7/17/07, Anthony Clayden [EMAIL PROTECTED] wrote: 2. The inits . tails approach adds a fault: It introduces a sprinkling of empty sub-sequences. These have sum zero. So in case the input list is all negative numbers ... At least the concatMap inits . tails code that I posted also

Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread J. Garrett Morris
morph :: ([a] - Maybe (b,[a])) - (b - [a]) - [a] - [a] Any reason not to call it 'replace'? /g On 7/6/07, Jules Bean [EMAIL PROTECTED] wrote: Hi, Yet another Function looking for a name post. Here's the type: morph :: ([a] - Maybe (b,[a])) - (b - [a]) - [a] - [a] Here, I am calling

Re: [Haskell-cafe] Tools for Haskell and COM

2007-06-27 Thread J. Garrett Morris
Microsoft's Component Object Model. http://en.wikipedia.org/wiki/Component_Object_Model /g On 6/27/07, Andrew Coppin [EMAIL PROTECTED] wrote: Simon Peyton-Jones wrote: The biggest Haskell/COM project I know of was Krasimir's implementation of Visual Haskell, which was a plug-in for Visual

Re: [Haskell-cafe] Re: Reinvention

2007-06-27 Thread J. Garrett Morris
More generally, that's unfoldr: Prelude :t Data.List.unfoldr Data.List.unfoldr :: (b - Maybe (a, b)) - b - [a] unfoldr represents the end of the unfold explicitly (using Nothing) instead of implicitly (using the empty list). /g On 27 Jun 2007 20:26:56 +0100, Jon Fairbairn [EMAIL PROTECTED]

Re: Re[2]: [Haskell-cafe] Re: Keys and Maps [Was: Re: I just don't get it (data structures and OO)]

2007-06-08 Thread J. Garrett Morris
On 6/8/07, Bulat Ziganshin [EMAIL PROTECTED] wrote: I second that. I particularly like the elimination of ]'s. We certainly need some symbol to separate the map and the key; but we do really need to also mark here be the end of the key? and how (arr ! key ++ data) should be parsed? :)

Re: [Haskell-cafe] Re: nested maybes

2007-02-06 Thread J. Garrett Morris
On 2/6/07, Yitzchak Gale [EMAIL PROTECTED] wrote: J. Garrett Morris wrote: Well, no, but it is at least no worse than apply :: Handle - Attribute a - ContT (StateT Blargh (ErrorT Fzzt IO)) a I find that in general, many functions do not need all of the capabilities. If they do, you can alias

Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread J. Garrett Morris
On 2/5/07, Yitzchak Gale [EMAIL PROTECTED] wrote: J. Garrett Morris wrote: First, we'll create a transformed version of the IO monad, Why go to the trouble of creating a new monad? The existing ones are fine. Mainly to keep the type error messages simpler. A project I was working on started

Re: [Haskell-cafe] Re: nested maybes

2007-02-05 Thread J. Garrett Morris
On 2/5/07, Yitzchak Gale [EMAIL PROTECTED] wrote: J. Garrett Morris wrote: Mainly to keep the type error messages simpler. There are two ways to get around that problem: 1. Make your functions polymorphic, using MonadState, MonadError, etc. Each function mentions only the capabilities

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris
Maybe has a Monad instance, so you can write this as follows (untested): exists str wmap = boolFromMaybe exists' where exists' = do x - Map.lookup (sort str) wmap find (== str) (snd x) boolFromMaybe (Just _) = True boolFromMaybe Nothing = False

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris
On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote: J. Garrett Morris wrote: Small improvement (Data.Maybe is underappreciated): exists str wmap = isJust exists' where exists' = do x - Map.lookup (sort str) wmap find (== str) (snd x) This is true. Some time

Re: [Haskell-cafe] nested maybes

2007-02-04 Thread J. Garrett Morris
On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote: J. Garrett Morris wrote: On 2/4/07, Udo Stenzel [EMAIL PROTECTED] wrote: Well, depends on whether we are allowed to define new combinators. I sometimes use -- Kleisli composition infixl 1 @@ (@@) :: Monad m = (a - m b) - (b - m c) - (a - m c) f

Re: [Haskell-cafe] Re: nested maybes

2007-02-04 Thread J. Garrett Morris
On 2/4/07, Martin Huschenbett [EMAIL PROTECTED] wrote: Hi, I've often got the same pattern with nested Maybes but inside the IO monad (sure this could be every other monad too). Assuming that I've got functions: This is where my favorite part of the mtl steps in: monad transformers. First,

Re: [Haskell-cafe] (a - [b]) vs. [a - b]

2007-02-02 Thread J. Garrett Morris
Uh, apologies. I got confused between reading your post and playing for a while, and answered the wrong question. /g On 2/2/07, J. Garrett Morris [EMAIL PROTECTED] wrote: On 2/2/07, Chad Scherrer [EMAIL PROTECTED] wrote: So in reality, I'm trying to construct something like f :: (a - STM b

Re: [Haskell-cafe] Levels of recursion

2007-02-02 Thread J. Garrett Morris
On 1/31/07, Andrew Wagner [EMAIL PROTECTED] wrote: So, a couple of questions to ponder about this: Is this unique to Haskell, or could the same be said about any functional language? How can we teach this better to newbies? Most of what I see in the tutorials is Higher order functions accept

Re: [Haskell-cafe] How did you stumble on Haskell?

2007-02-02 Thread J. Garrett Morris
On 1/28/07, Alexy Khrabrov [EMAIL PROTECTED] wrote: How do people stumble on Haskell? My story isn't as interesting as some of these. My first quarter in school, I took a course taught in Scheme. I expressed some dissatisfaction with the lack of types (and, in particular, the collection of

Re: [Haskell-cafe] It matters how Type Synonyms are defined?

2007-02-02 Thread J. Garrett Morris
Agreed. I've written quite a bit of code that way myself. Looking at Iavor's monadLib, though, raised a question: has there been any consider of removing the requirement that the newtype be the last argument? The classes for state monads, etc. are rather backwards as it is, since the

Re: [Haskell-cafe] A function for Maybes

2007-01-25 Thread J. Garrett Morris
fmap. e.g.: Prelude fmap ('c':) (Just a) Just ca Prelude fmap ('c':) Nothing Nothing Prelude /g On 1/25/07, John Ky [EMAIL PROTECTED] wrote: Is there a built-in function that already does this? foo :: (a - b) - Maybe a - Maybe b foo f m | isNothing m = Nothing | otherwise = Just (f

Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread J. Garrett Morris
On 1/4/07, brad clawsie [EMAIL PROTECTED] wrote: lets say i have a string s = abcdefg now i have two lists of strings, one a list of patterns to match, and a list of replacement strings: patterns = [a,b] replace = [Z,Y] from which my intent is that a be replaced by Z, b by Y etc now using

Re: [Haskell-cafe] trivial function application question

2007-01-04 Thread J. Garrett Morris
Oops, I seem not to have proofread my message. On 1/4/07, J. Garrett Morris [EMAIL PROTECTED] wrote: On 1/4/07, brad clawsie [EMAIL PROTECTED] wrote: s = abcdefg patterns = [a,b] replacements = [Z,Y] I changed the name here so as not to conflict with the replace function. snip You can

Re: [Haskell-cafe] State separation/combination pattern question

2006-12-23 Thread J. Garrett Morris
On 12/22/06, Reto Kramer [EMAIL PROTECTED] wrote: What I'm really looking for is not so much the chaining of StateT compositions, but rather the isolation of StateA from StateB while they both flow from the search loop into the respective library calls (foo, bar) transparently to the application

[Haskell-cafe] ST and Transformers

2006-12-22 Thread J. Garrett Morris
Hello everyone, I recently found myself attempting to use ST at the base of a stack of transformers, ala: type Test t r = ErrorT String (ST t) r I imagined, given the type of ST, that I would need a run function along the lines of: runTest :: (forall t. Test t r) - Either String r (which

Re: [Haskell-cafe] ST and Transformers

2006-12-22 Thread J. Garrett Morris
Hmm, that was simpler than I had imagined. Thank you both! /g On 12/22/06, Stefan O'Rear [EMAIL PROTECTED] wrote: On Fri, Dec 22, 2006 at 06:44:54PM +0100, Pepe Iborra wrote: Rank-2 types seem to interact badly with (.) and ($), but my type theory educated neuron doesn't know why. I think

Re: [Haskell-cafe] Shrinking the Prelude: The categorical approach

2006-12-20 Thread J. Garrett Morris
On 12/20/06, Diego Navarro [EMAIL PROTECTED] wrote: take map for example, and fmap, I don't think they should be named different (fmap is ugly, not suggestive, and conceptually the same). mplus could be renamed (++) (they are conceptually the same Wouldn't this raise the same problems

Re: [Haskell-cafe] Building the community

2006-12-13 Thread J. Garrett Morris
On 12/13/06, Donald Bruce Stewart [EMAIL PROTECTED] wrote: * Give tips on how to answer questions + Ok. we can put up an article here. Some suggestions: - Solutions with unsafePerformIO should be discouraged (moreso ;) I'd like to at least suggest a slight

Re: [Haskell-cafe] Writing Haskell For Dummies Or At Least For People Who Feel Like Dummies When They See The Word 'Monad'

2006-12-12 Thread J. Garrett Morris
Hello everyone, On 12/12/06, Ketil Malde [EMAIL PROTECTED] wrote: snip Some things took a bit of effort to wrap my head around, but it generally wasn't too hard to get to a level where I could write useful programs. snip * I'm already productive with what I know, so I don't have the direct

Re: [Haskell-cafe] Stratified monads

2006-12-11 Thread J. Garrett Morris
On 12/11/06, Mark T.B. Carroll [EMAIL PROTECTED] wrote: I'm not sure I actually understand them properly yet, but I'm already curious about if anybody's played with them in Haskell, or how useful it would be to do so. Any comments? Haskell implementations of the transformers in Espinosa's

Re: [Haskell-cafe] modelling problem

2006-12-08 Thread J. Garrett Morris
On 12/8/06, Kurt Schelfthout [EMAIL PROTECTED] wrote: Hi Haskell'ers, snip class Activity a c where start :: c - a - Time --start of the activity (this isn't actually dependent on c, I guess) end :: c - a - Time --end of the activity delta :: a - Time - c

Re: [Haskell-cafe] Re: How to combine Error and IO monads?

2006-12-07 Thread J. Garrett Morris
On 12/7/06, Cat Dancer [EMAIL PROTECTED] wrote: On 12/7/06, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: I'm sure from a single example I could understand what was going on and elaborate from there. Let's say I want to get a line from the user, and either return an integer or an error string

Re: [Haskell-cafe] Picking out elements of a heterogenous list

2006-12-05 Thread J. Garrett Morris
I generally use the Typeable class for this. In that example, you'd want: class Typeable a = Shape_ a instead of just class Shape_ a and then your filter predicate would look like: isSquare :: Shape - Bool isSquare (Shape s) = typeOf s == typeOf square where square :: Square ; square =

Re: [Haskell-cafe] Binary code

2006-11-27 Thread J. Garrett Morris
Hello, First, and forgive me if I'm making unwarranted assumptions, but http://haskell.org/haskellwiki/Homework_help might be useful. Second: div, mod, reverse, and the unfoldr function from Data.List will do what you want. /g On 11/25/06, escafia [EMAIL PROTECTED] wrote: Hi, i've one

Re: [Haskell-cafe] working with lists of couples

2006-11-18 Thread J. Garrett Morris
On 11/17/06, Henning Thielemann [EMAIL PROTECTED] wrote: On Fri, 17 Nov 2006, Clara Zamolo wrote: buildCouples = snd . foldl op (0,[]) where op (v,xs) x = (v+x,xs++[(x,v)]) You could make something like this that doesn't have quadratic-type appends by accumulating functions

Re: Re: [Haskell-cafe] Automatic fixity allocation for symbolic operators

2006-10-14 Thread J. Garrett Morris
On 10/14/06, Nicolas Frisby [EMAIL PROTECTED] wrote: Perhaps the editor could assume a default precedence when the user-defined precedence is not yet available. Preferably, the editor would also somehow yell at the user to indicate that it is making such an assumption. Perhaps it could even

Re: [Haskell-cafe] Mis-understanding something in Haskell interpretation

2006-10-03 Thread J. Garrett Morris
On 10/3/06, Edward Ing [EMAIL PROTECTED] wrote: The source is below. Side is types as Float. My assumption was that Haskell would know how to convert the Int to a float and all would be well. I am I mistaken somewhere? The problem is with the last line. Yes - Haskell does not automatically

Re: [Haskell-cafe] How to round off frational number?

2006-09-08 Thread J. Garrett Morris
I've always used: roundn n f = fromIntegral (round (f * 10 ^ n)) / 10 ^ n I may have missed some bugs or subtleties of floating point numbers, though. /g On 9/8/06, Sara Kenedy [EMAIL PROTECTED] wrote: Hello all, I try to find some functions in Haskell library to deal with numeric such that

Re: [Haskell-cafe] beginner's haskell question

2006-08-08 Thread J. Garrett Morris
The ghc flag -fwarn-incomplete-patterns might be what you're looking for. /g On 8/8/06, Jens Theisen [EMAIL PROTECTED] wrote: Hello, as a haskell newbie I'm wondering about the following question. Are there options to popular haskell implementations or other means (haskell lint?) to check

Re: [Haskell-cafe] A program which never crashes (even when a function calls error)

2006-08-01 Thread J. Garrett Morris
On 8/1/06, Stephane Bortzmeyer [EMAIL PROTECTED] wrote: How to do it in Haskell? How can I call functions like Prelude.head while being sure my program won't stop, even if I call head on an empty list (thus calling error)? Try looking at Control.Exception. For example: module Test where

Re: [Haskell-cafe] putStrLn

2006-06-16 Thread J. Garrett Morris
main n = putStrLn (replicate n '*') main n = putStrLn (take n (repeat '*')) main n = sequence (take n (repeat (putStr *))) (but that doesn't have a final new line. The more complicated: main n = sequence (take (n - 1) (repeat (putStr *))) putStrLn * should solve that problem.) /g On

Re: [Haskell-cafe] Separate a string into a list of strings

2006-06-12 Thread J. Garrett Morris
Off the top of my head: separate :: String - [String] separate [] = [] separate s = case break (',' ==) s of (s,[]) - [s] (s,',':s') - s : separate s' _ - error how did we get here? There is at least one cunning rewriting with foldl, I think, but I think this version is clearer. /g

Re: [Haskell-cafe] newbie type signature question

2006-06-10 Thread J. Garrett Morris
On 6/9/06, Brandon Moore [EMAIL PROTECTED] wrote: data DataType m = forall m' . (Monad m') = DataType (TyEq m m') (Char - m' ()) It appears that the more intuitive formulation: data DataType m where DataType :: Monad m = (Char - m ()) - DataType m should work in GHC 6.4 /g

Re: [Haskell-cafe] library sort

2006-02-16 Thread J. Garrett Morris
Data.List contains sort :: Ord a = [a] - [a] and sortBy :: (a - a - Ordering) - [a] - [a] I believe they're currently implemented using merge sort, at least in GHC. /g On 2/16/06, Radu Grigore [EMAIL PROTECTED] wrote: Is there a sort function in the libraries that come with GHC (6.4)? My

Re: [Haskell-cafe] round function

2006-02-12 Thread J. Garrett Morris
I think the function you're looking for is: myRound n places = round (n / fromIntegral factor) * factor where factor = 10 ^ (places - 1) In this case, 10 ^ (places - 1) has integral type (either Int or Integer). I need it to be a fractional type to divide n by it, so I use fromIntegral to

Re: [Haskell-cafe] Matching constructors

2006-02-10 Thread J. Garrett Morris
tootieIndices = findIndices isTootie where isTootie (Pa _) = False isTootie (Tootie _) = True would be my first approach. /g On 2/10/06, Creighton Hogg [EMAIL PROTECTED] wrote: Hi, If I have something like data Patootie = Pa Int | Tootie Int and I want to pull out the

Re: [Haskell-cafe] does haskell have plist's ?

2006-02-04 Thread J. Garrett Morris
On 2/4/06, raptor [EMAIL PROTECTED] wrote: does Haskell have a property lists. Like Lisp ? any pointer to examples ? Not built in to the language. It's not hard to get the same functionality though - I've attached a module that takes a (not tremendously elegant) approach to the same thing,

Re: [Haskell-cafe] Statements spanning multiple lines?

2005-12-22 Thread J. Garrett Morris
On 12/22/05, Daniel Carrera [EMAIL PROTECTED] wrote: Hi all, How do I write a statement that spans multiple lines? I have this function: pythagoras n = [(a,b,c) | a -[1..n], b -[1..n], c -[1..n], a = b, b c, a*a + b*b == c*c] This should all be in one line. I know some ways to make the

Re: [Haskell-cafe] FAQ: Why no interactive definitions?

2005-12-22 Thread J. Garrett Morris
In ghci at least, you can enter definitions like that using let binding: let mysquare x = x * x /g On 12/22/05, Greg Woodhouse [EMAIL PROTECTED] wrote: In neither GHCi nor Hugs (so far as I know) is it possible to interactively enter definitions. coming from Scheme, this was a bit of a

Re: [Haskell-cafe] Verbosity of imperative code (was: Learning Haskell)

2005-12-08 Thread J. Garrett Morris
On 12/8/05, Robin Green [EMAIL PROTECTED] wrote: Sure, I take your point. But I just jumped on my latest hobby-horse: verbosity of imperative code is not that necessary. There was a discussion along these lines some time ago, started by Frederik Eaton with the subject line Mixing monadic and

Re: [Haskell-cafe] Re: Haskell and OS X

2005-10-21 Thread J. Garrett Morris
On 10/21/05, Joel Reymont [EMAIL PROTECTED] wrote: On Oct 21, 2005, at 4:22 PM, Stefan Monnier wrote: You mean you'd like data TableInfo = TableInfo { avgPot :: Double, No, I would actually like to offset avgPot 4 spaces from TableInfo. Can I throw a vote

Re: [Haskell-cafe] map in IO

2005-09-25 Thread J. Garrett Morris
the similar function: mapM :: Monad m = (a - m b) - [a] - m [b] should do the trick for you, and is in the prelude. /g ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Basic type classing question.

2005-09-20 Thread J. Garrett Morris
On 9/20/05, Karl Grapone [EMAIL PROTECTED] wrote: What I want to be able to do is add and remove fields while the system is running, I suppose via hs-plugins, and I should be prevented from, for example, accidentally taking an employees first name and using it as a departments address. I know

Re: [Haskell-cafe] Re: OCaml list sees abysmal Language Shootoutresults

2004-10-13 Thread J. Garrett Morris
--- Ketil Malde wrote: Or, what if String were one? Could we have painless read/show with arrays of Char, as well as lists, for instance? --- end of quote --- I think with a decent set of type classes for collections, better handling of strings would come for free. If any list function could

Re: Language extension idea (was Re: [Haskell-cafe] Re: OCaml list sees...)

2004-10-10 Thread J. Garrett Morris
--- Malcolm Wallace wrote: As an example, instead of the following list-only code, f :: List a - ... f []= ... f (h:t) = ... you could write this more general version, which assumes only some class Sequence with operations null, head, tail, etc. f :: Sequence s = s a - ...

Re: Language extension idea (was Re: [Haskell-cafe] Re: OCaml list sees...)

2004-10-09 Thread J. Garrett Morris
--- Tom Pledger wrote: It could get more convenient, though, if we have data-constructors-as-class-members and move the familiar list constructors into the List class. (The following might need to be built into the compiler, because of the special [] syntax.) --- end of quote --- Changing the

Re: [Haskell-cafe] The State Monad

2004-10-07 Thread J. Garrett Morris
--- John Goerzen wrote: tick :: Int - State Int Int tick newval = do put newval return newval Or this: tick :: State Int Int tick = do n - get return n That is even more incomprehensible to me -- why would removing a line before the return cause a type error? --- end

Re: [Haskell-cafe] Parsec Problem

2004-07-27 Thread J. Garrett Morris
--- [EMAIL PROTECTED] wrote: I wish I knew what that meant. If someone could explain it and tell me what's wrong, I'd appreciate it. --- end of quote --- Lexeme is actually a selector function over the TokenParser record. In the previous section (also on lexical analysis), he included the