Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
Oops, not quite. "otherwise ==" should be "otherwise =". Looks like you already go this from the first one, but guard syntax looks like: defn | cond1 = ... | cond2 = ... | ... | otherwise = ... (otherwise is not actually necessary; it is just a synonym for True) Luke On Dec 6, 2007 7:

Re: [Haskell-cafe] matching

2007-12-05 Thread Luke Palmer
Just remove that if. What comes after | is already a conditional. Luke On Dec 6, 2007 7:03 AM, Ryan Bloor <[EMAIL PROTECTED]> wrote: > > hi > > I have a matching problem... I am wanting to identify whether or not a > string is an opening substring of another (ignoring leading spaces). I have >

[Haskell-cafe] matching

2007-12-05 Thread Ryan Bloor
hi I have a matching problem... I am wanting to identify whether or not a string is an opening substring of another (ignoring leading spaces). I have this: word is a single word and str is a string. match :: String -> String -> (Bool, String)match word str | if removeSpace s

Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread gwern0
On 2007.12.05 15:56:49 +0100, John van Groningen <[EMAIL PROTECTED]> scribbled 0.7K characters: > [EMAIL PROTECTED] wrote: > > >Hey everyone; recently I've been toying around with various methods of > >writing a shell and reading the academic literature on such things. The best > >prior art on t

Re: [Haskell-cafe] Re: New slogan for haskell.org

2007-12-05 Thread Albert Y. C. Lai
Combinators get my code done, tralalalala, laughing out loud! Quickcheck locates all of my bugs, tralalalala, laughing out loud! Fusion laws make my code run fast, tralala, lalala, lololol! Folks, I'm so done, Merry Christmas, tralalalala, laughing out loud! ___

Re: [Haskell-cafe] Re: type class question

2007-12-05 Thread Ryan Ingram
On 12/5/07, Ben Franksen <[EMAIL PROTECTED]> wrote: > > data Command = Skip > > class Java block command where > block_ :: [command] -> block > > compBlock :: [Command] -> block > --compBlock = block_ . map compCommand > > compCommand :: Command -> command > > This compiles ok. But when I ask ghci

Re: [Haskell-cafe] Re: type class question

2007-12-05 Thread Felipe Lessa
On Dec 5, 2007 10:38 PM, Ben Franksen <[EMAIL PROTECTED]> wrote: > data Command = Skip > > class Java block command where > block_ :: [command] -> block > > compBlock :: [Command] -> block > --compBlock = block_ . map compCommand > > compCommand :: Command -> command My guess is that nothi

[Haskell-cafe] Re: type class question

2007-12-05 Thread Ben Franksen
Brent Yorgey wrote: > Well, first of all, the definition of compCommand should use calls to > compBlock, not recursive calls to compCommand. But that's not the main > source of your problems. > > What exactly are you trying to accomplish? And why do you need a type > class? Whatever the code is

Re: [Haskell-cafe] Graph theory analysis of Haskell code

2007-12-05 Thread Ivan Miljenovic
On 06/12/2007, Tim Chevalier <[EMAIL PROTECTED]> wrote: > This is very well-trodden ground, but if you familiarize yourself with > the literature on the subject, then who knows, you may discover > something new. And you can take pleasure in knowing that you've > already independently conceived of a

Re: [Haskell-cafe] Graph theory analysis of Haskell code

2007-12-05 Thread Tim Chevalier
On 12/5/07, Ivan Miljenovic <[EMAIL PROTECTED]> wrote: > How I envisage it happening is that a parser would be used to find all > "functions" in the given code, treat these as nodes in the graph and > then use directed edges to indicate which functions call other > functions. aka a "call graph". T

[Haskell-cafe] Graph theory analysis of Haskell code

2007-12-05 Thread Ivan Miljenovic
This isn't strictly Haskell related, but anyway. Next year I will be doing my honours in mathematics. One possible topic for my thesis that I've thought of - and my supervisor is quite enthused about - is to use graph theory to analyse various textual sources, starting with source code but leavin

[Haskell-cafe] Re: [Haskell] IVar

2007-12-05 Thread Jan-Willem Maessen
On Dec 5, 2007, at 3:58 AM, Simon Marlow wrote: Jan-Willem Maessen wrote: Consider this: do x <- newIVar let y = readIVar x writeIVar x 3 print y (I wrote the let to better illustrate the problem, of course you can inline y if you want). Now suppose the compiler decided to eval

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Derek Elkins
On Wed, 2007-12-05 at 10:01 +0100, Pablo Nogueira wrote: > Hasn't Ryan raised an interesting point, though? > > Bottom is used to denote non-termination and run-time errors. Are they > the same thing? Up to observational equality, yes. > To me, they're not. A non-terminating program has > diffe

Re: [Haskell-cafe] Looking for largest power of 2 <= Integer

2007-12-05 Thread Spencer Janssen
On Tuesday 04 December 2007 15:47:19 David Benbennick wrote: > On Dec 4, 2007 11:51 AM, Don Stewart <[EMAIL PROTECTED]> wrote: > > Awesome. We can use this in Data.Bits, if you've got some QuickChecks > > for it. > > Hear hear. But is there any way to just make the compiler use > fastTestBit in pl

Re: [Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Ryan Ingram
No, that doesn't work; it's close, but not quite. liftM doesn't have the right type signature. liftM :: Monad m => (a -> r) -> (m a1 -> m r) What would work is if you could define a function liftLast :: Monad m => (a0 -> a1 -> ... -> aN -> r) -> (a0 -> a1 -> ... -> aN -> m r) then nary' f = ru

Re: [Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Dan Weston
Wouldn't any isomorphism do (like the Identity monad)? How about nary' f = runIdentity . nary (liftM f) . return Brandon S. Allbery KF8NH wrote: On Dec 5, 2007, at 16:00 , Philipp N. wrote: the odd thing is. you can get this to work, if you have a terminating type as result type (for examp

Re: [Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Brandon S. Allbery KF8NH
On Dec 5, 2007, at 16:00 , Philipp N. wrote: the odd thing is. you can get this to work, if you have a terminating type as result type (for example (IO x)). then you can work with all types (IO x), (a -> IO x), (a -> b -> IO x), ... but i don't want this delimiter IO! any ideas? Use ST i

[Haskell-cafe] distinguish functions from non-functions in a class/instances

2007-12-05 Thread Philipp N.
Hello, i'm trying to wrap functions (a -> b -> ... -> z) of any arity to functions of type ([String] -> y), where list of strings replaces the typed arguments. one attempt looks like this (here written with type families, you can replace it by functional dependencies or what ever): type family

[Haskell-cafe] Re: Why is this strict in its arguments? (Jules Bean)

2007-12-05 Thread John Lato
Wow, thanks. I had a similar function (long if/then/else chain, fromJust) that I haven't been happy with, but couldn't see how to improve it. Now I have a much better idea for how to fix that function. Thanks again, John Lato > the general pattern is : replace isNothing with a case match on Noth

Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread Sterling Clover
In an email to the HAppS listt today, alexj described that HAppS-State "provides a way to serialize function calls for replay either on-restart or on other replicated boxes." (which actually helped me to understand somewhat what's going on behind all its TemplateHaskell magic. This is somewhat more

Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Benja Fallenstein
On Dec 5, 2007 5:40 PM, Paulo J. Matos <[EMAIL PROTECTED]> wrote: > Oh, but lfpaths is not nothing so that means that isNothing rtpaths > shouldn't be evaluated, right? You're right, and I was stupid not to think about that case. Since Luke already gave an in-depth analysis I'll be quiet now :-)

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 1:51 PM, Luke Palmer <[EMAIL PROTECTED]> wrote: > > On Dec 4, 2007 9:41 PM, Paulo J. Matos <[EMAIL PROTECTED]> wrote: > > Hello all, > > > > As you might have possibly read in some previous blog posts: > > http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10 > > http://users.ecs.soton.ac

Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 1:43 PM, Benja Fallenstein <[EMAIL PROTECTED]> wrote: > Hi Paolo, > > On Dec 5, 2007 2:09 PM, Paulo J. Matos <[EMAIL PROTECTED]> wrote: > > I'm glad that my initial post generated such an interesting discussion > > but I'm still not understanding why the first version of findAllPath

Re: [Haskell-cafe] ghc overlapping instances

2007-12-05 Thread Isaac Dupree
Steffen Mazanek wrote: Hi, Stefan and Isaac, thx for providing quick advice. @Stefan: Unfortunately I have to use a list. @Isaac: I do not get it. Could you please provide a short example of your approach? The question still remains. Which arguments do I have ghc to start with to get the same

Re: [Haskell-cafe] ghc overlapping instances

2007-12-05 Thread Steffen Mazanek
Hi, Stefan and Isaac, thx for providing quick advice. @Stefan: Unfortunately I have to use a list. @Isaac: I do not get it. Could you please provide a short example of your approach? The question still remains. Which arguments do I have ghc to start with to get the same behavior than hugs with -

Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread John van Groningen
[EMAIL PROTECTED] wrote: >Hey everyone; recently I've been toying around with various methods of writing >a shell and reading the academic literature on such things. The best prior art >on the subject seems to be the ESTHER shell (see >, >

Re: [Haskell-cafe] Parsing unstructured data

2007-12-05 Thread Olivier Boudry
On Nov 29, 2007 5:31 AM, Reinier Lamers <[EMAIL PROTECTED]> wrote: > Especially in the fuzzy cases like this one, NLP often turns to machine > learning models. One could try to train a hidden Markov model or support > vector machines to label parts of the string as "name", "street", > "number", "c

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 4, 2007 9:41 PM, Paulo J. Matos <[EMAIL PROTECTED]> wrote: > Hello all, > > As you might have possibly read in some previous blog posts: > http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10 > http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=11 > > we (the FPSIG group) defined: > data BTree a = Le

Re: [Haskell-cafe] Clean Dynamics and serializing code to disk

2007-12-05 Thread Jed Brown
On 5 Dec 2007, [EMAIL PROTECTED] wrote: > Since from my Lisp days I know that code is data, it strikes me that > one could probably somehow smuggle Haskell expressions via this route > although I am not sure this is a good way to go or even how one would > do it (to turn, say, a list of the chose

Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Benja Fallenstein
Hi Paolo, On Dec 5, 2007 2:09 PM, Paulo J. Matos <[EMAIL PROTECTED]> wrote: > I'm glad that my initial post generated such an interesting discussion > but I'm still not understanding why the first version of findAllPath > seems to be computing the whole list even when I just request the > head, wh

[Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
I'm glad that my initial post generated such an interesting discussion but I'm still not understanding why the first version of findAllPath seems to be computing the whole list even when I just request the head, while the second one doesn't. I thought that this was denominated by "findAllPath is st

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 10:44 AM, Jules Bean <[EMAIL PROTECTED]> wrote: > Paulo J. Matos wrote: > > Hello all, > > Hi. > > > > findAllPath :: (a -> Bool) -> (BTree a) -> Maybe [[a]] > > findAllPath pred (Leaf l) | pred l = Just [[l]] > > | otherwise = Nothing > > findAllPath pred (

Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 5, 2007 12:16 AM, Aaron Denney <[EMAIL PROTECTED]> wrote: > On 2007-12-04, Paulo J. Matos <[EMAIL PROTECTED]> wrote: > > Hello all, > > > > As you might have possibly read in some previous blog posts: > > http://users.ecs.soton.ac.uk/pocm06r/fpsig/?p=10 > > http://users.ecs.soton.ac.uk/pocm0

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Paulo J. Matos
On Dec 4, 2007 10:00 PM, Neil Mitchell <[EMAIL PROTECTED]> wrote: > Hi > > > findAllPath :: (a -> Bool) -> (BTree a) -> [[a]] > > findAllPath pred = g where > > g (Leaf l) | pred l = [[l]] > > g (Branch lf r rt) | pred r = map (r:) $ (findAllPath pred > > lf) ++ (findAllPa

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:30 PM, Andrew Coppin <[EMAIL PROTECTED]> wrote: > > Luke Palmer wrote: > > On Dec 5, 2007 11:56 AM, Andrew Coppin <[EMAIL PROTECTED]> wrote: > > > >> I was merely noting that questions of the form "is X decidable?" are > >> usually undecidable. (It's as if God himself wants to tea

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Andrew Coppin
Luke Palmer wrote: On Dec 5, 2007 11:56 AM, Andrew Coppin <[EMAIL PROTECTED]> wrote: I was merely noting that questions of the form "is X decidable?" are usually undecidable. (It's as if God himself wants to tease us...) I take issue with your definition of "usually" then. Whenever "X

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 11:56 AM, Andrew Coppin <[EMAIL PROTECTED]> wrote: > I was merely noting that questions of the form "is X decidable?" are > usually undecidable. (It's as if God himself wants to tease us...) I take issue with your definition of "usually" then. Whenever "X is decidable" is undecidab

Re: [Haskell-cafe] type class question

2007-12-05 Thread Brent Yorgey
On Dec 3, 2007 7:43 AM, Peter Padawitz <[EMAIL PROTECTED]> wrote: > What is wrong here? ghci tries (and fails) to deduce certain types for > the comp functions that I did not expect. > > type Block = [Command] > data Command = Skip | Assign String IntE | Cond BoolE Block Block | >

Re: [Haskell-cafe] a positive challenge for the Haskell effort .....

2007-12-05 Thread Andrew Coppin
Galchin Vasili wrote: http://code.enthought.com/enthon/ .. how do Haskell libraries/packages stack up against this challenge? I suspect this question is rather nontrivial to answer. There's a library to do X. Well, yes, but is it any good? (Does it have a nice API? Is it flexible? Is it relia

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Andrew Coppin
Tillmann Rendel wrote: Andrew Coppin wrote: *thinks* Conjecture #1: All nontrivial properties of a computer program are undecidable in general. That is the well-known Rice's theorem. Wait - Rice's *theorem*? So Rice *proved* this? OMG, I was *right* about something! :-D Conjecture #2: C

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Tillmann Rendel
Andrew Coppin wrote: *thinks* Conjecture #1: All nontrivial properties of a computer program are undecidable in general. That is the well-known Rice's theorem. (A very handy one in exams about theoretical computer science, since you can smash so many questions with "follows from Rice").

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Janis Voigtlaender
See http://doi.acm.org/10.1145/301631.301637 and http://dx.doi.org/10.1016/S1571-0661(05)80288-9 Pablo Nogueira wrote: Hasn't Ryan raised an interesting point, though? Bottom is used to denote non-termination and run-time errors. Are they the same thing? To me, they're not. A non-terminatin

Re: [Haskell-cafe] Re: Why is this strict in its arguments?

2007-12-05 Thread Luke Palmer
On Dec 5, 2007 12:16 AM, Aaron Denney <[EMAIL PROTECTED]> wrote: > > we (the FPSIG group) defined: > > data BTree a = Leaf a > > | Branch (BTree a) a (BTree a) > > Totally avoiding your question, but I'm curious as to why you > deliberately exclude empty trees. > > Come to think of it,

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Andrew Coppin
Roberto Zunino wrote: Neil Mitchell wrote: is there any automated way to know when a function is strict in its arguments? Yes, strictness analysis is a very well studied subject - ...and is undecidable, in general. ;-) *thinks* Conjecture #1: All nontrivial properties of

Re: [Haskell-cafe] Array copying

2007-12-05 Thread Andrew Coppin
Jules Bean wrote: Andrew Coppin wrote: Andrew Coppin wrote: copy :: Word32 -> IOUArray Word32 Bool -> Word32 -> IO (IOUArray Word32 Bool) copy p grid size = do let size' = size * p grid' <- newArray (1,size') False mapM_ (\n -> do b <- readArray grid n if b then mapM_ (

[Haskell-cafe] SingHaskell slides

2007-12-05 Thread Martin Sulzmann
Slides (in pdf) are now available online: http://taichi.ddns.comp.nus.edu.sg/taichiwiki/SingHaskell2007 http://www.comp.nus.edu.sg/~sulzmann/singhaskell07/index.html - Tom & Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskel

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Johan Tibell
On Dec 5, 2007 11:44 AM, Jules Bean <[EMAIL PROTECTED]> wrote: > the general pattern is : replace isNothing with a case match on Nothing, > replace fromJust with a case match on Just, don't be afraid to case two > expressions at once. That's a nice little insight. I'll remember that. _

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Jules Bean
Paulo J. Matos wrote: Hello all, Hi. findAllPath :: (a -> Bool) -> (BTree a) -> Maybe [[a]] findAllPath pred (Leaf l) | pred l = Just [[l]] | otherwise = Nothing findAllPath pred (Branch lf r rt) | pred r = let lfpaths = findAllPath pred lf

Re: [Haskell-cafe] unification would give infinite type

2007-12-05 Thread Emil Axelsson
You usually don't need to worry about it. Just keep in mind that if you happen to get a strange type error concerning an (overloaded) function *without type signature*, it sometimes helps to add a signature. / Emil On 2007-12-04 15:52, Rafael wrote: I don't know about monomorphis restrictio

RE: [Haskell-cafe] building HUnit and other packages on Windows cygwin...

2007-12-05 Thread Bayley, Alistair
> From: [EMAIL PROTECTED] > [mailto:[EMAIL PROTECTED] On Behalf Of Galchin Vasili > > I believe that HUnit has absolutely not other package > dependencies. When I do a "runhaskell Setup.hs build", I get > the following error message: gcc: installation problem, cannot > exec `cc1': No such

Re: [Haskell-cafe] foild function for expressions

2007-12-05 Thread Pablo Nogueira
I believe the exercise is about understanding folds. There are two references that are related to the exercise: A tutorial on the universality and expressiveness of fold, by Graham Hutton. Dealing with large bananas, by Ralf Lammel, etc. The last paper motivates well the need to gather all t

Re: [Haskell-cafe] Why is this strict in its arguments?

2007-12-05 Thread Pablo Nogueira
Hasn't Ryan raised an interesting point, though? Bottom is used to denote non-termination and run-time errors. Are they the same thing? To me, they're not. A non-terminating program has different behaviour from a failing program. When it comes to strictness, the concept is defined in a particular

[Haskell-cafe] Re: [Haskell] Re: Haskell Digest, Vol 52, Issue 1

2007-12-05 Thread Simon Marlow
Taral wrote: On 12/4/07, Simon Marlow <[EMAIL PROTECTED]> wrote: do x <- newIVar let y = readIVar x writeIVar x 3 print y (I wrote the let to better illustrate the problem, of course you can inline y if you want). Now suppose the compiler decided to evaluate y before the

[Haskell-cafe] Re: [Haskell] IVar

2007-12-05 Thread Simon Marlow
Jan-Willem Maessen wrote: Consider this: do x <- newIVar let y = readIVar x writeIVar x 3 print y (I wrote the let to better illustrate the problem, of course you can inline y if you want). Now suppose the compiler decided to evaluate y before the writeIVar. What's to prevent i