Thanks for an excellent clarification. I have been known to be rather
daft at times so I just wanted to make sure I understood everything
correctly. Thanks!
/M
On Sun, Jan 28, 2007 at 12:56:56 +0200, Yitzchak Gale wrote:
>Hi Magnus,
>
>You wrote:
>>This piece has type problems. I couldn't get
The cool thing about Excel is that it's like Function Reactive
Programming. When you update the value of a cell, all the other cells
that reference to it get updated too. That's pretty cool to have in
GUI's as well, and Haskell has that too. See [1].
-chris
[1]: http://www.haskell.org/frp/
On Wednesday 31 January 2007 22:36, Robert Dockins wrote:
> On Tuesday 30 January 2007 20:06, Bryan Donlan wrote:
> If you instead want to replace your list with one of the Edison sequence
> implementations, that should be possible. However, I'm not really sure
> that it's going to buy you a lot.
I started using Python around 1998, and I loved the elegance of it, but I
was frustrated with the performance. Around 2001 I was poking around for
something that would give me better performance but still allow some nice
capabilities for abstraction.
I started using OCaml after reading a commenta
On Tuesday 30 January 2007 19:02, Bulat Ziganshin wrote:
> Hello Tim,
>
> Saturday, January 27, 2007, 10:23:31 PM, you wrote:
> >> Humm. While I can accept that this is a valid criticism of Haskell's
> >> monadic structure for dealing with I/O, I fail to see how it could drive
> >> a decision to p
[I apologize for odd quoting, but I dislike sending html emails]
"I do like the idea of developing a table of contents first and backfilling
it, though. I would amend the process, however, to avoid the WikiBloat that
seems to inevitably follow when documentation projects get too open.
Instead of
On Tuesday 30 January 2007 20:06, Bryan Donlan wrote:
> Daniel McAllansmith wrote:
> > Hello.
> >
> > Given:
> >
> > newtype Dist a = D {unD :: [(a,Int)]}
> >
> > instance Monad Dist where
> > return x = D [(x,1)]
> > d >>= f = D [(y,q*p) | (x,p) <- unD d, (y,q) <- unD (f x)]
> > fail _ =
On Wed, 2007-31-01 at 03:25 +0300, Bulat Ziganshin wrote:
> >> I'm very serious about the need for a "Haskell for the Working
> >> Programmer" book. And by this I mean a book and not a tutorial on
> >> some part of Haskell which proves difficult.
> > Agreed. Something I can keep on my desk fo
deliverable:
> So I'm picking up Haskell bit by bit, and I found the code examples
> transpiring here most useful. Reflecting why it's harder to pick up
> Haskell than say Ruby or Python, here's what I found -- those
> languages deal with a typical domain available to any programmer --
> his own c
So I'm picking up Haskell bit by bit, and I found the code examples
transpiring here most useful. Reflecting why it's harder to pick up
Haskell than say Ruby or Python, here's what I found -- those
languages deal with a typical domain available to any programmer --
his own computer/system/shell.
Daniel McAllansmith wrote:
Hello.
Given:
newtype Dist a = D {unD :: [(a,Int)]}
instance Monad Dist where
return x = D [(x,1)]
d >>= f = D [(y,q*p) | (x,p) <- unD d, (y,q) <- unD (f x)]
fail _ = D []
How would one change Dist to wrap an instance of the (Data.Edison.Set c a)
typeclas
On Wed, Jan 31, 2007 at 02:58:20AM +0300, Bulat Ziganshin wrote:
> Hello David,
>
> Saturday, January 27, 2007, 8:48:39 PM, you wrote:
>
> > I agree that numerics and Doubles are very important, but am of the
> > opinion that we'll be better off if we (try to?) restrict ourselves to
> > code that
bulat.ziganshin:
> Hello Stefan,
>
> Monday, January 29, 2007, 1:59:22 AM, you wrote:
>
> > Note: I *have* managed to pretty thourougly understand lambdabot, but
> > it took a while, wasn't particularly easy, and anyway
> > lambdabot's dependency groups are quite small compared to eg
On Wed, Jan 31, 2007 at 01:56:32AM +0300, Bulat Ziganshin wrote:
> Hello David,
>
> Friday, January 26, 2007, 6:23:26 PM, you wrote:
>
> >> performance was not very good (the OCaml version I based it on was at
> >> least 10x faster).
>
> > I would think that what we'd want to benchmark would be
Hello Tim,
Saturday, January 27, 2007, 10:23:31 PM, you wrote:
>> Humm. While I can accept that this is a valid criticism of Haskell's monadic
>> structure for dealing with I/O, I fail to see how it could drive a decision
>> to prefer an imperative language like C#, where every statement has thi
Hello Paul,
Monday, January 29, 2007, 5:06:42 PM, you wrote:
> I'm very serious about the need for a "Haskell for the Working
> Programmer" book. And by this I mean a book and not a tutorial on
> some part of Haskell which proves difficult.
> Agreed. Something I can keep on my desk for referen
Hello David,
Saturday, January 27, 2007, 8:48:39 PM, you wrote:
> I agree that numerics and Doubles are very important, but am of the opinion
> that we'll be better off if we (try to?) restrict ourselves to code that is
> really used by someone who really cares about performance enough to
> optim
Hello Kirsten,
Saturday, January 27, 2007, 10:05:15 AM, you wrote:
> On the other hand, Meijer also has a PhD in computer science... is his
> judgment on Haskell's difficulty or lack thereof worthless, too? If
> not, then surely, judgments about whether Haskell is too hard can't
> have much to do
Hello Donald,
Saturday, January 27, 2007, 10:18:44 AM, you wrote:
>> I've never taken a graduate-level class in category theory, or any
>> course on category theory, and I'm a Haskell implementor. So perhaps
> I haven't done any graduate level category theory either, and I hack
> Haskell 24/7! L
Hello Tim,
Saturday, January 27, 2007, 6:14:01 AM, you wrote:
> He brings up a very good point. Using a monad lets you deal with
> side effects but also forces the programmer to specify an exact
> ordering.
1. it's just a *syntax* issue. at least, ML's solution can be applied:
x <- .y + .z
wh
Hello Benjamin,
Saturday, January 27, 2007, 12:00:11 AM, you wrote:
> and support operational reasoning, i.e. creating and understanding programs
> by mentally modeling their execution on a machine. This form of reasoning
> appeals to 'common sense', it is familiar to almost all (even completely
Hello Steve,
Friday, January 26, 2007, 10:03:09 PM, you wrote:
> Haskell _is_ hard, although I don't think it's _too_ hard, or I wouldn't
...
> The audience for programming languages like Haskell is always going to
> be small, because it appeals to those who want to understand how the TV
> works
Hello Neil,
Friday, January 26, 2007, 8:13:43 PM, you wrote:
> evolution of programming languages. In particular they identify
> composability, concurrency and FP as being important trends. However their
> focus is on borrowing features of FP and bringing them into mainstream
> imperative languag
Hello David,
Friday, January 26, 2007, 6:23:26 PM, you wrote:
>> performance was not very good (the OCaml version I based it on was at
>> least 10x faster).
> I would think that what we'd want to benchmark would be clean, optimized
> actually-used code. I.e. things like Data.Bytestring, so that
Hello Neil,
Monday, January 29, 2007, 2:26:03 AM, you wrote:
> Having a Hoogle database for a large
> program is also handy for figuring out where things are and what they
> do - especially when the program has introduced new custom data types.
vim+hasktags can just show definition of every iden
Hello Stefan,
Monday, January 29, 2007, 1:59:22 AM, you wrote:
> Note: I *have* managed to pretty thourougly understand lambdabot, but
> it took a while, wasn't particularly easy, and anyway
> lambdabot's dependency groups are quite small compared to eg
> lambdabot's. I'm hopin
Hello Neil,
Friday, January 26, 2007, 3:06:18 AM, you wrote:
>> One could point to O'caml or others in the ML family, or even more
>> interesting is the case of Clean, whose syntax heavily borrows from Haskell.
> ML is strict, this makes a big difference. Things that Haskell
> compilers do easil
There is a Maple plug-in for Excel. If you have Maple (on Windows),
just start Excel and you'll see extra buttons.
This allows you to have cells containing symbols, as well as access to
all of Maple's functions. This easily gets you a (very impure!)
higher-order functional language inter-ope
simonmar:
> Donald Bruce Stewart wrote:
> >Binary: high performance, pure binary serialisation for Haskell
> > --
> >The Binary Strike Team is pleased to announce the release of a new,
> >pure, efficient binary seriali
On 1/30/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
Excel is what I like to call a 0:th order functional language,
i.e., you can't even define functions, just values. :)
Every cell with an expression in Excel is a function. The problem is
that the domains and codomains of these functions
Hello.
Given:
newtype Dist a = D {unD :: [(a,Int)]}
instance Monad Dist where
return x = D [(x,1)]
d >>= f = D [(y,q*p) | (x,p) <- unD d, (y,q) <- unD (f x)]
fail _ = D []
How would one change Dist to wrap an instance of the (Data.Edison.Set c a)
typeclass so that the Monad instance
Yitzchak Gale wrote:
> Steve Downey wrote:
>> OO, at least when done well, maps well to how people think.
>
> Um, better duck. I am afraid you are about to draw
> some flames on that one. I hope people will try
> to be gentle.
No problem ;-)
I'll never get tired quoting Dijkstra; one of the thin
Excel is what I like to call a 0:th order functional language,
i.e., you can't even define functions, just values. :)
-- Lennart
On Jan 30, 2007, at 21:58 , Neil Mitchell wrote:
Hi Alexy,
Heard that statement recently -- that Excel is a functional
programming language, and the most
On 2007-01-29, Alexy Khrabrov <[EMAIL PROTECTED]> wrote:
> How do people stumble on Haskell? I've taught ML at UPenn, and many
Fascinating thread.
Awhile back, I decided that, once I got familiar and comfortable with a
programming language, I would learn a new one. I tend a learn a new
language
Hi Alexy,
Heard that statement recently -- that Excel is a functional
programming language, and the most used one -- of any programming
languages -- on Earth! Is it true? Are there good examples of
typical FP style in Excel?
You can't define functions in Excel, hence its not really a functio
Heard that statement recently -- that Excel is a functional
programming language, and the most used one -- of any programming
languages -- on Earth! Is it true? Are there good examples of
typical FP style in Excel?
Cheers,
Alexy
___
Haskell-Cafe maili
Julien Oster wrote:
Hello,
The type of the monadic bind function in the Monad class is
Monad m => m a -> (a -> m b) -> m b
Now, would it be possible to create a monad with a slightly stricter
type, like
StrictMonat m => m a -> (a -> m a) -> m a
and, accepting that all steps of the computat
Yitzchak Gale wrote:
It's short, so I'll post it here.
Any comments?
readDev :: Storable a => FilePath -> BlockingMode -> IO (Maybe a)
readDev dev mode = do
h <- openFile dev ReadMode
hSetBuffering h NoBuffering
alloca $ getMaybe h undefined
where
getMaybe :: Storable a => Handle
On Tue, Jan 30, 2007 at 10:22:58AM +, Duncan Coutts wrote:
> Ross, you need to make a monoid transformer library (at least reader and
> state) and campaign for ++ to be redefined as mappend, then everyone
> will want to use it since it'll be so neat and convenient! :-)
Reader is already there.
It's short, so I'll post it here.
Any comments?
Thanks,
-Yitz
module DevRandom where
import System.IO
import System.IO.Error
import Foreign.Marshal.Alloc
import Foreign.Storable
import Foreign.Ptr
data BlockingMode = Blocking | NonBlocking
deriving (Eq, Show)
-- Read data from the system ran
John Ky wrote:
> I can't know, but it doesn't seem unreasonable that you intend to use
>> the ArcForest as a trie, i.e. an efficient implementation of a set of
>> paths which allows to look up quickly whether a given path (here of type
>> [String]) is in the set or not. So, we have
>
> For a whil
Hello,
The type of the monadic bind function in the Monad class is
Monad m => m a -> (a -> m b) -> m b
Now, would it be possible to create a monad with a slightly stricter
type, like
StrictMonat m => m a -> (a -> m a) -> m a
and, accepting that all steps of the computation would be bound to
Alexy Khrabrov wrote:
Well, I'm thinking in terms of OOD/OOA/OOP -- Design, Architecture,
Programming. That's about the only way to model a bog system. Say I
have a stock market model -- I'll have a database of tickers, a
simulator to backtest things, a trading strategy, etc.
Do Haskell module
I think that whole "program flow" thing is something you get used to. In
true, pure functional programming (i.e. Haskell) "program flow" is a
meaningless term, basically. Haskell is a declarative language, not an
imperative one. You have to learn to give up that control and trust the
run
Have I re-invented the wheel yet again?
I have a module the following simple functions,
that I have been using for some time:
-- Read data from the system random device.
-- Return Nothing if there is currently not
-- enough entropy in the system random device.
devRandom :: Storable a => IO (Mayb
Donald Bruce Stewart wrote:
Binary: high performance, pure binary serialisation for Haskell
--
The Binary Strike Team is pleased to announce the release of a new,
pure, efficient binary serialisation library for H
Hi apfelmus,
Your code is fine, I like it. A minor hint is that mergeForest is a fold:
mergeForest = foldr merge []
Also, we have
prettyPrint = putStr . unlines . prettyPrint' $ forest
Nice help on the simple things.
I can't know, but it doesn't seem unreasonable that you intend to use
Hi Tomasz,
I actually quite like this style. I was able to understand it after
spending some time reading the docs for some of the functions you used.
My problem I guess is being able to write the code this way when the need
arises or even just recognising when and where it's an option, both of
Daniil
As you obviously know, there should be no difficulty in principle with building
GHC-Cygwin; that is, a GHC that will compile binaries that expect to run on
Cygwin (using the Cygwin dll). But this compilation route is not one we
support.
If you have managed to do it, even if the result
On Tue, Jan 30, 2007 at 10:22:58AM +, Duncan Coutts wrote:
> I was about to say that for the more complicated binary serialisation
> formats (eg GHC's .hi format) people need monads with state, like string
> pools etc, but actually now that I think about it, that can be done with
> a monoid too
On Tue, Jan 30, 2007 at 09:38:26AM +, Ross Paterson wrote:
> On Tue, Jan 30, 2007 at 09:52:01AM +1100, Donald Bruce Stewart wrote:
> > ross:
> > > why do you need a Put monad, which always seems to have
> > > the argument type ()? Monoids really are underappreciated.
> >
> > For the syntax, a
On Tue, 2007-01-30 at 09:38 +, Ross Paterson wrote:
> On Tue, Jan 30, 2007 at 09:52:01AM +1100, Donald Bruce Stewart wrote:
> > ross:
> > > why do you need a Put monad, which always seems to have
> > > the argument type ()? Monoids really are underappreciated.
> >
> > For the syntax, and So t
On Tue, Jan 30, 2007 at 09:52:01AM +1100, Donald Bruce Stewart wrote:
> ross:
> > why do you need a Put monad, which always seems to have
> > the argument type ()? Monoids really are underappreciated.
>
> For the syntax, and So that people can directly port their code from
> NewBinary. (The inst
53 matches
Mail list logo