Usually in monad tutorials, the >>= operator for the list monad is
defined as:
m >>= k = concat (map k m) -- or concatMap k m
but in the GHC sources it's defined as:
m >>= k = foldr ((++) . k) [] m
As far as I can tell, this definition is equivalent to the previous one
(correct me
I run haskell on Mac OS X (Snow Leopard). After upgrading my Xcode
installation to 4.0 I had a tricky time getting ghc working again; the
version bundled with the Haskell Platform no longer works and I had to
compile a recent snapshot (ghc-7.1.20110315) from source. This worked
fine, but now
to get a good conceptual
understanding of what's really going on here.
Mike
On 10/3/10 7:03 PM, Christopher Done wrote:
On 4 October 2010 03:40, Michael Vanier wrote:
newtype MyMonad a =
MyMonad ((StateT (MyData a) (Either SomeError) a))
deriving (Monad,
On 10/3/10 7:06 PM, Bryan O'Sullivan wrote:
On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier <mailto:mvanie...@gmail.com>> wrote:
{- This doesn't work: -}
newtype MyMonad a =
MyMonad ((StateT (MyData a) (Either SomeError) a))
deriving (Monad,
I'm having a problem with a simple monad transformer stack that has me
stumped. Here's the sample code:
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
import Control.Monad.Error
import Control.Monad.State
import Data.Typeable
data SomeError =
Error1
| Error2
| ErrorFail
deriving (Eq,
On 8/24/10 1:54 PM, Bartek Æwik³owski wrote:
Hello Michael,
This is because instance selection is solely based on instance heads,
it doesn't consider contexts. There's a nice explanation available
here: http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap
The fix in this case is very easy be
Hi everyone,
Here's some code that's giving me an error message I don't understand:
{-# LANGUAGE EmptyDataDecls,
MultiParamTypeClasses,
UndecidableInstances,
FlexibleInstances #-}
data Z
data S n
class Nat n where
toInt :: n -> Int
instance Nat Z wher
Hi,
Quick question about ghci: when I do this at the prompt:
ghci> :m +Control.Monad.Cont
I get
Ambiguous module name `Control.Monad.Cont':
it was found in multiple packages: mtl-1.1.0.2 monads-fd-0.0.0.1
Is there any way to fix this from within ghci (i.e. not involving
mucking wit
On 5/30/10 1:40 AM, Michael Snoyman wrote:
On Sun, May 30, 2010 at 11:35 AM, Michael Vanier <mailto:mvanie...@gmail.com>> wrote:
I stumbled across this monadic combinator:
mcombine :: Monad m => (a -> a -> a) -> m a -> m a -> m a
mcombine f mx my =
I stumbled across this monadic combinator:
mcombine :: Monad m => (a -> a -> a) -> m a -> m a -> m a
mcombine f mx my = do
x <- mx
y <- my
return (f x y)
I used it to chain the outputs of two Parsec String parsers together
using this operator:
(<++>) :: Monad m => m String -> m St
This is a great idea! IMO this is also one of the main ways that
GUI-based apps are likely to evolve into in the future. Cross-platform
GUIs are a pain in the butt in _any_ language (possibly excluding full
language platforms like Java/.NET, and I'll bet even those were a
nightmare for the or
Matthias Görgens wrote:
A shining example are Dan Piponis blog posts. Not his fault, mind. All I see
is that there is something powerful. I also notice that the big brains
construct monads in many different ways and thus giving them entirely
different capabilities. An example of this is some tech
Awesome! Thanks, Don!
Mike
Don Stewart wrote:
mvanier42:
Hi everyone,
I'm interested in collecting good references for compiler optimizations
for functional languages (lazy, strict, statically-typed or not). Any
suggestions?
There's lots for what GHC implements on SimonPJ's
Hi everyone,
I'm interested in collecting good references for compiler optimizations
for functional languages (lazy, strict, statically-typed or not). Any
suggestions?
Thanks in advance,
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.or
For a completely different approach, I've had good success running
xmonad from either Ubuntu minimal (which is a bare-bones version of
Ubuntu that few people realize exists) or Arch Linux. In either case
you have to spend more time setting up the system, but the results IMO
are worth it. I do
jean-christophe mincke wrote:
Hello,
Has there already been attempts to introduce lisp like symbols in haskell?
Thank you
Regards
J-C
J-C,
Do you mean symbols as in "interned strings with an O(1) string
comparison method"? I would love to have those, but I don't see an easy
way to get
Gregory Collins wrote:
Tom Davie writes:
On 10/31/09, Magicloud Magiclouds wrote:
After all, I never think OO as an oppsite way to all other things. The
idea is so general that if you say I cannot use it in Haskell at all,
that would make me feel weird. The only difference between la
Hi everyone,
I ran into this error when recompiling some code I hadn't worked on in a
while:
Foo.hs:19:7:
Could not find module `Control.Monad.Error':
it was found in multiple packages: monads-fd-0.0.0.1 mtl-1.1.0.2
I gather that monads-fd is supposed to be a replacement for mtl, but
Matthias-Christian Ott wrote:
Hi,
usually I'm sceptical of programming languages which are not based
on the von Neumann architecture, but recently I got interested in
functional programming languages.
The arrogance of lots of Haskell users, who made me feel that using a
programming language othe
Simon Peyton-Jones wrote:
Haskell is a great language! Check out haskell.org. I'm ccing the Haskell
Cafe which is read by many people better qualified to answer your question than
me. (Since I've been working on Haskell for many years, I am not well
qualified to say how it seems to a begi
I've been trying to build ghc head from the darcs repo using these
instructions:
http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources
Unfortunately, when I do
./darcs-all --extra get
as described under "Getting more packages" it fails because the
darcs-all script doesn't recog
haonan21 wrote:
I'm very new to haskell hugs and would appreciate it if someone could help me
out here. I've been giving 2 questions.
1.) A and B are two sets of integers. Implement a function to obtain the
integers that belong to both sets.
Test your function fully.
2.) Define and test a fun
Luke Palmer wrote:
On Tue, Apr 28, 2009 at 5:33 PM, Michael Vanier <mailto:mvanie...@gmail.com>> 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 >&g
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 sta
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?
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
he state actually used by runST is "RealWorld";
runST is just a pretty name for unsafePerformIO. So the state types
are actually the same, and the cast would succeed.
-- ryan
On Mon, Mar 16, 2009 at 5:48 PM, Michael Vanier wrote:
Hi,
I'm having a problem using Typeable with ST
Hi,
I'm having a problem using Typeable with STRefs. Basically, I want to
store STRefs (among other things) in a universal type. STRef is an
instance of Typeable2, which means that STRef s a is Typeable if s and a
are both Typeable. The problem is that the state type s is opaque and I
can
Actually, it's (+) for ints and (+.) for floats. Which kind of proves your
point.
Mike
Tim Docker wrote:
| An interesting critique of OCaml.
|
| http://enfranchisedmind.com/blog/2008/05/07/why-ocaml-sucks/
Interesting to me is that my pet ocaml peeve is not there: namely the
lack of conven
This is pure "general waffle", but I saw the following comment on reddit.com
which impressed me:
"C isn't hard; programming in C is hard. On the other hand: Haskell is hard,
but programming in Haskell is easy."
Mike
Simon Peyton-Jones wrote:
Friends
Over the next few months I'm giving two or
Bayley, Alistair wrote:
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Derek Elkins
(Not directed at gwern in particular)
I have a better idea. Let's decide to do nothing. The
benefits of this
approach are: 1) it takes zero effort to implement, 2) the number of
peo
I haven't been following this thread closely, but would it be rude to suggest that someone who
doesn't want to put the effort into learning the (admittedly difficult) concepts that Haskell
embodies shouldn't be using the language? Haskell was never intended to be The Next Big Popular
Language.
I have a copy of "COBOL for Dummies" which I bought as a joke and have never
dared read.
Mike
[EMAIL PROTECTED] wrote:
Andrew Coppin writes:
Brent Yorgey wrote:
Expressiveness certainly makes it easier, but nothing (other than
sanity...) stops you from writing a Haskell compiler in,
Bernie Pope wrote:
On 12/11/2007, at 4:32 AM, Neil Mitchell wrote:
Hi
bear no resemblence to any machine-level constructs, and it "seems"
unthinkable that you could possibly write such a compiler in anything
but Haskell itself.
Hugs is written in C.
Really? :-.
Really :-)
(Seriou
It looks as if hoogle isn't working. I get 404s whenever I try to do any
search on hoogle.
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
In ghci, why does
throw $ ArithException DivideByZero
print
*** Exception: divide by zero
while
throwDyn $ ArithException DivideByZero
print
*** Exception: (unknown)
?
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://w
I haven't been following this discussion closely, but here's an idea: use
reverse psychology.
"Haskell -- You're probably not smart enough to understand it."
Nothing like appealing to people's machismo to get them interested.
Mike
Seth Gordon wrote:
Aha! Instead of the lambda surrounded b
Hmm, I was hoping for something that didn't involve side effects.
Mike
Yitzchak Gale wrote:
Michael Vanier wrote:
I'm thinking of a symbol type that can be used
for a compiler...
Ah. Perhaps Data.HashTable is what you are looking
for th
I'm thinking of a symbol type that can be used for a compiler, so a simple algebraic data type
wouldn't work. Unfortunately the GHC datatype isn't part of the GHC haskell libraries AFAICT.
Mike
Yitzchak Gale wrote:
Michael Vanier wrote:
Is there an implementation of a symbol
Is there an implementation of a symbol type in Haskell i.e. a string which has a constant-time
comparison operation?
Mike
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
OK, you have the split function, and you have the merge function, and now you have to define the
msort function. First write down the base cases (there are two, as you mention), which should be
obvious. Then consider the remaining case. Let's say you split the list into two parts. Then what
Define a merge function that merges two sorted lists into a sorted list containing all the elements
of the two lists. Then define the msort function, which will be recursive.
Mike
PR Stanley wrote:
Hi
Taken from chapter 6, section 8 of the Hutton book on programming in
Haskell:
5. Using mer
APL is fairly obsolete now anyway. A more modern version of that language is J (www.jsoftware.com),
which does not use special characters. I've studied the language a bit, and it's quite interesting,
but it really doesn't offer much (anything?) over Haskell except a much terser notation and sim
Awesome!
I'm reminded of the IRC post that said that "Haskell is bad, it makes you hate other
languages."
Mike
Dan Weston wrote:
And here's my guide for public health officials...
WARNING: Learning Haskell is dangerous to your health!
Disguised as a fully-functional programming language, Ha
It's very nice, but I would say that anyone who needs an elevator pitch shouldn't be using or
working with Haskell. Haskell is for people who already "get it". I've had job offers from people
just because they knew I _liked_ Haskell, even though they weren't asking me to use it for the job.
O
Xavier,
First off, we don't put the () after function names in Haskell.
What's happening is this (experts please correct any mistakes here):
1) You call prime on a number (e.g. 42).
2) In order to evaluate this further, (factors 42) must be evaluated at least
partially to give input to == in p
Bill Wood wrote:
On Tue, 2007-08-14 at 16:02 -0700, Dan Piponi wrote:
. . .
On 8/14/07, Michael Vanier <[EMAIL PROTECTED]> wrote:
I'm reminded of
a physics teacher who was having a similar problem explaining the concept of
tensors, until he said
that "a tensor is something
For what it's worth, the nature of Haskell is such that you do (at least currently) have to spend a
lot of time reading research papers to understand what's going on. Maybe that will change sometime,
but probably not soon. This ties in to the open-endedness of Haskell; I sometimes think that re
As you know, an arrow tutorial is like a wrapper around a monad tutorial, sort of like a container
around it that can do extra actions with sufficient lifting. The appropriate higher-order function
to convert monad tutorials to arrow tutorials will be left as an exercise to the reader.
I'm
Hugh Perkins wrote:
I'm not trolling, despite strong appearances to the contrary ;-) My
primary objective/goal is to find a way to make threading easy. Thread
management today is like memory management in the early 90s. We kindof
had tools (new, delete in C++ for example) to do it. At som
I can't agree with your point about Haskell being (just) a prototype language (assuming that's what
you meant). If that's the case, it won't last very long. Languages need to be something you can
write real, practical applications in. Fortunately, Haskell isn't just a prototype language. I'm
Of course, you can always do this:
data Nat = Zero | Succ Nat
but it's not very much fun to work with, and not very efficient.
Mike
David Roundy wrote:
On Thu, Aug 02, 2007 at 12:29:46PM -0700, brad clawsie wrote:
On Thu, Aug 02, 2007 at 12:17:06PM -0700, brad clawsie wrote:
as far as i kno
u.au/~dons/lambdabot.html
shows it working on 6.4.1.
can it build under anything more recent?
t.
*"Stefan O'Rear" <[EMAIL PROTECTED]>*
Sent by: [EMAIL PROTECTED]
07/30/2007 11:59 PM
To
Michael Vanier <[EMAIL PROTECTED]>
cc
"has
export `minus_name'
Lib/Parser.hs:19:89:
Module `Language.Haskell.Syntax' does not export `pling_name'
I'm using the latest darcs pull of lambdabot along with ghc 6.6.1. Anyone have
any ideas?
Thanks in advance for all the help,
Mike
Michael Vanier wrote:
OK, Stefan was right.
OK, Stefan was right. The arrows package is an extension of Control.Arrow, not a from-scratch
implementation. The name confused me. Perhaps a better name would be "arrows-ext" or something
like that.
Mike
Michael Vanier wrote:
Thanks, but this doesn't answer the question.
tefan O'Rear wrote:
On Mon, Jul 30, 2007 at 06:57:25PM -0700, Michael Vanier wrote:
When I try to build lambdabot, I get this:
Configuring lambdabot-4.0...
configure: Dependency base-any: using base-2.1.1
configure: Dependency unix-any: using unix-2.1
configure: Dependency network-any: usi
When I try to build lambdabot, I get this:
Configuring lambdabot-4.0...
configure: Dependency base-any: using base-2.1.1
configure: Dependency unix-any: using unix-2.1
configure: Dependency network-any: using network-2.0.1
configure: Dependency parsec-any: using parsec-2.0
configure: Dependency m
I submit my own attempts for consideration:
http://www.cs.caltech.edu/~mvanier/hacking/rants/cars.html
Mike
Andrew Coppin wrote:
From the guy who brought you "data in Haskell is like an undead quantum
cat", I present the following:
"If programming languages were like vehicles, C would be a
We always say that Haskell is named for Haskell Curry because his work provided the
logical/computational foundations for the language. How exactly is this the case? Specifically,
does anyone claim that Curry's combinatorial logic is more relevant to the theoretical foundations
of Haskell than
Incidentally, this thread demonstrates a curious feature of Haskell programming. You write a
function which works, but somehow you're not satisfied with it. You stare at it for a while,
refactor it into a much smaller version, stare at it some more, refactor it again, and on and on
until your
On Fri, Jul 13, 2007 at 04:29:12PM -0700, Michael Vanier wrote:
Albert,
Thanks for the very detailed reply! That's the great thing about this
mailing list.
I find your description of seq somewhat disturbing. Is this behavior
documented in the API? I can't find it there. It suggest
Albert,
Thanks for the very detailed reply! That's the great thing about this mailing
list.
I find your description of seq somewhat disturbing. Is this behavior documented in the API? I
can't find it there. It suggests that perhaps there should be a
really-truly-absolutely-I-mean-right-no
That makes sense. Thanks!
Mike
Stefan O'Rear wrote:
On Thu, Jul 12, 2007 at 09:22:09PM -0700, Michael Vanier wrote:
I stumbled across a problem with IO and strictness that I could fix, but I
can't understand why the fix works. I've compressed it down into a program
which
I stumbled across a problem with IO and strictness that I could fix, but I can't understand why the
fix works. I've compressed it down into a program which simply computes the number of lines in a
file. Here is a version that doesn't work:
module Main where
import System.IO
import System.Env
That's cool -- good point. takeWhile is also trivially defined in terms of
foldr:
> takeWhile p = foldr (\x r -> if p x then x:r else []) []
Can you do dropWhile in terms of foldr? I don't see how.
Mike
Stefan O'Rear wrote:
On Wed, Jul 04, 2007 at 04:20:20PM -0700,
I'm sure this has been done a hundred times before, but a simple generalization of foldl just
occurred to me and I wonder if there's anything like it in the standard libraries (I couldn't find
anything). Basically, I was trying to define the "any" function in terms of a fold, and my first
try w
I noticed that both the Data.Array library and the Data.Map library use the (!) operator for
different purposes. How would it be possible to import both libraries usefully in a single module?
I guess what I'm really asking is: how do I qualify operator names?
Mike
___
That's pretty baa-aa-aad.
Mike
brad clawsie wrote:
On Wed, May 23, 2007 at 12:40:58PM -0700, Dan Weston wrote:
What power animal have you chosen for the cover of your O'Reilly book? Alas,
most of the good ones are gone already!
"lamb"-da?
___
Has
I'm not sure what you mean by "a lot of transcription work". It's an excellent book, aimed at
beginners.
Mike
PR Stanley wrote:
Hi
I've acquired a copy of the above title but it requires a lot of
transcription work. So, I thought I'd first ensure it's worth the time
and effort. This edition
The -> in type signatures associates to the right, so the type signatures
> fmap :: (a -> b) -> (W a -> W b)
> bind :: (a -> W b) -> (W a -> W b)
are the same as:
> fmap :: (a -> b) -> W a -> W b
> bind :: (a -> W b) -> W a -> W b
Sometimes people put in the extra parentheses because they want
momically and in terms
of its caché) - changin the mindset of the "masses" - creating the
meme - that's tricky. Especialy if they're really off the B Ark!
(http://www.bbc.co.uk/cult/hitchhikers/guide/golgafrincham.shtml)
Neil
On 18/04/07, Michael Vanier <[EMAIL PROTECTED]&g
R Hayes wrote:
On Apr 17, 2007, at 4:46 PM, David Brown wrote:
R Hayes wrote:
They *enjoy* debugging ...
I have to say this is one of the best things I've found for catching
bad programmers during interviews, no matter what kind of system it is
for. I learned this the hard way after w
P. R. Stanley wrote:
What are the pre-requisites for Lambda calculus?
Thanks
Paul
Learning lambda calculus requires no prerequisites other than the ability to
think clearly. However, don't think that you need to understand all about
lambda calculus in order to learn Haskell. It's more lik
Brandon S. Allbery KF8NH wrote:
On Feb 18, 2007, at 21:44 , Michael Vanier wrote:
I think what you're asking here is why you need the parens around
(x:y) in the second case. Function application doesn't use parentheses
Function application never applies to pattern matching
P. R. Stanley wrote:
Brandon, Chris, Don,
gentlemen,
Thank you all for your swift and well-written answers.
I should point out that I'm coming to functional programming with a
strong background in programming in C and C-type languages. I am also
very new to the whole philosophy of functional
FYI we teach and do a fair amount of functional programming here at Caltech. We
have courses using scheme, ocaml, and haskell with more on the way.
Mike
Greg Fitzgerald wrote:
Thomas,
Here's a good place to start, although I'm not sure how up to date it is:
http://haskell.org/haskellwiki/Has
Lennart,
Now you've made me curious. Which paper is this? Is it available for download
anywhere?
Mike
Lennart Augustsson wrote:
On Jan 29, 2007, at 03:01 , Alexy Khrabrov wrote:
How do people stumble on Haskell?
Well, I didn't really stumble on it. I was at the 1987 meeting
when we dec
First off, I apologize if this has come up before. As far as I can tell, the
mailing list archives don't have a search function. I'm running ghc-6.6 and
haddock-0.8, both compiled from source.
I'm working my way through the "How to Write a Haskell Program" tutorial (which
is a great idea, th
Excellent! Thanks.
Mike
Donald Bruce Stewart wrote:
Oh, like this (by Stefan Wehr):
http://www.cse.unsw.edu.au/~dons/code/icfp05/tests/unit-tests/VariableExpansion.hs
$ ghci -fth VariableExpansion.hs
*VariableExpansion> let x = 7 in $( expand "${x}" )
"7"
*VariableExpansion> let url =
Yes, just like that ;-) Thanks!
Now if somebody has a string interpolation library, I'd be a pretty
happy camper ;-)
Mike
mvanier:
Is there any support for multi-line string literals in Haskell? I've
done a web search and come up empty. I'm thinking of using Haskell to
generate web pag
Is there any support for multi-line string literals in Haskell? I've
done a web search and come up empty. I'm thinking of using Haskell to
generate web pages and having multi-line strings would be very useful.
Mike
___
Haskell-Cafe mailing list
Has
On this page:
http://www.haskell.org/tutorial/modules.html
it refers to the process of hiding imported names from a module and gives
the example:
import Prelude hiding length
whereas the correct syntax is
import Prelude hiding (length)
I spent nearly an hour beating my head against this.
The explanation given below might be a bit heavy for someone who didn't know
much
about category theory. For those individuals I'd recommend Phil Wadler's
papers:
http://homepages.inf.ed.ac.uk/wadler/topics/monads.html
I especially recommend "Monads for Functional Programming", "The Essence of
I always thought Forth was way cool, but I've never managed to get anything
significant written in it. I think that Forth has echoes of the
"point-free" style in Haskell, but Haskell is a lot friendlier.
Is the Forth environment part of the hardware? If your Forth is just a
threaded interpreter
I came up with a terrible Haskell pun that I had to share with this list:
Haskell provides special syntactic support for monads in terms of the "do
notation". There is a straightforward translation between this notation
and the core language, which constitutes its "do-notational semantics"
> Date: Wed, 11 May 2005 13:06:51 +0200
> From: Jerzy Karczmarczuk <[EMAIL PROTECTED]>
>
> Michael Vanier comments my defense of Matlab:
>
> >>I used objects, and even a lot of functional
> >>constructs. I don't see any reason to call it a creeping ho
> Date: Wed, 11 May 2005 07:49:38 +0200
> From: Jerzy Karczmarczuk <[EMAIL PROTECTED]>
>
> Michael Vanier wrote:
>
> >I have enough problems convincing people to learn Scheme. I've
> >even had people beg me to teach them Matlab as a first programming
> Date: Tue, 10 May 2005 19:02:33 -0400
> From: Daniel Carrera <[EMAIL PROTECTED]>
>
> Hello,
>
> This might be a strange question to ask on a Haskell list, but I do want
> to hear your opinions. What do you think of Python?
>
> To explain where this question is comming from:
>
> I have a lady
> From: Benjamin Franksen <[EMAIL PROTECTED]>
> Date: Wed, 4 May 2005 22:47:21 +0200
>
> On Wednesday 04 May 2005 22:22, [EMAIL PROTECTED] wrote:
> > Bryce Bockman writes:
> > > Scheme is strict, so it lacks some of the flexibility (and drawbacks)
> > > that come from Laziness, but in the book the
Translated a bit:
With lazy evaluation, the order of evaluation is irrelevant as far as the
_correctness_ of the function is concerned. However, it's much easier to
reason about the _efficiency_ of functions when the language uses strict
evaluation; you never have to scratch your head and ask "I
> Date: Tue, 03 May 2005 19:56:00 -0400
> From: Daniel Carrera <[EMAIL PROTECTED]>
>
> Hi Ben,
>
> > Take a look at this one:
> >
> > http://www.haskell.org/onlinelibrary/standard-prelude.html
>
> Thanks.
>
> What's the "Prelude" ?
It's the repository of haskell code (functions, types, type c
Marcin gives a good capsule description of the differences between ocaml
and haskell. Let me add my two cents.
I also learned ocaml before learning haskell, and the biggest single
difference I found is that haskell is a lazy, purely functional language
and ocaml is a strict, "mostly functional"
I've been trying to generate an infinite list of random coin flips in GHC
6.4, and I've come across some strange behavior:
--
import System.Random
data Coin = H | T deriving (Eq, Show)
-- Generate a random coin flip.
coinFlip :
> Date: Sun, 13 Mar 2005 00:01:17 -0800
> From: Sean Perry <[EMAIL PROTECTED]>
> Cc:
>
> Michael Vanier wrote:
> >>Date: Sat, 12 Mar 2005 23:39:21 -0800
> >>From: Sean Perry <[EMAIL PROTECTED]>
> >>Cc: Haskell-Cafe@haskell.org
> >>
&
> Date: Sat, 12 Mar 2005 23:39:21 -0800
> From: Sean Perry <[EMAIL PROTECTED]>
> Cc: Haskell-Cafe@haskell.org
>
> As an aside, I kept all of the exercises in revision control. So I can
> look back at what I first wrote and my later changes. A habit I plan to
> keep as I move on to other programm
94 matches
Mail list logo