Hi!
> The list of tuples _does_ need to be strict. Beyond that, as Ketil Malde
> said, you should not use foldl -- instead, foldl' is the best version to
> use when you are recalculating the result every time a new list item is
> processed.
Thanks! I did the following:
merge [] x = [(x,1)]
merge
On 2004 November 01 Monday 16:48, Alexander N. Kogan wrote:
> Sorry, I don't understand. I thought the problem is in laziness -
You're correct. The problem is laziness rather than I/O.
> my list
> of tuples becomes ("qqq", 1+1+1+.) etc and my program reads whole file
> before it starts proces
Benjamin Franksen writes:
> On Monday 01 November 2004 23:40, Jon Fairbairn wrote:
> > Apart from matching up with the names there's not much to
> > choose between one destructor and many, except possibly when
> > one considers something like:
> >
> > Â Âcase e of
> > Â Â ÂSquare s -> ...
> > Â Â
Interesting discussion. I'm still learning Haskell and I also thought
about the difference between constructors and functions time ago. I
don't think the question about what a constructor really IS is
meaningful. It can be can be thought as a label, a special function,
... wathever is more useful i
On Monday 01 November 2004 23:48, Ben Rudiak-Gould wrote:
> Benjamin Franksen wrote:
> >Because, hmmm, isn't it rather *one* destructor with type
> >
> >destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t
> >
> >where the second and third arguments explain what to do with a Circl
On Monday 01 November 2004 23:40, Jon Fairbairn wrote:
> if Circle.destruct:: Shape -> (Double -> t) -> t -> t and
> similarly Square.destruct, we'd just have to write the case
> as
>
> Circle.destruct s f (Square.destruct s g (error "impossible"))
>
> ie the .destructs take a Shape, a function to
Benjamin Franksen wrote:
>Because, hmmm, isn't it rather *one* destructor with type
>
>destructShape :: Shape -> (Double -> t) -> (Double -> t) -> t
>
>where the second and third arguments explain what to do with a Circle
resp. a
>Square? So that
>
>case s of
>Circle r -> f r
>
Just wanted to point out you can get accessor/deconstructor functions
using record notation:
data Shape = Circle { radius :: Double } | Square { length :: Double }
Keean.
Benjamin Franksen wrote:
On Monday 01 November 2004 22:34, you wrote:
On 2004-11-01 at 23:01+0100 Benjamin Franksen wrote:
On 2004-11-02 at 00:11+0100 Benjamin Franksen wrote:
> On Monday 01 November 2004 22:34, I wrote:
> >data Shape = Circle Double | Square Double
> >
> > is a convenience that declares three new names (Shape,
> > Circle and Square), but five entities.
> >
> > There's Shape: a type, Circle, Square
On Monday 01 November 2004 22:34, you wrote:
> On 2004-11-01 at 23:01+0100 Benjamin Franksen wrote:
> > On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
> > > Put the data declaration in a module, export the type, but
> > >
> > > not the constructor you want to hide:
> > > > module Shape (Sha
Hi!
> Peter Simons wrote:
> > Read and process the file in blocks:
> >
> > http://cryp.to/blockio/docs/tutorial.html
>
> On a related note, I've found the collection of papers below to be
> helpful in understanding different methods of handling files in Haskell.
>
> http://okmij.org/ftp/
On 2004-11-01 at 23:01+0100 Benjamin Franksen wrote:
> On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
> > Put the data declaration in a module, export the type, but
> >
> > not the constructor you want to hide:
> > > module Shape (Shape(Square), circle) where
>
> Since we were talking abou
On Monday 01 November 2004 21:51, Jon Fairbairn wrote:
> On 2004-11-01 at 12:30PST "Brian Beckman" wrote:
> > Most interesting discussion -- in reading it, I realized that I had a
> > 'hidden agenda' in asking my question (hidden even from myself), and
> > that is: can I put interesting functionali
Paul Hudak wrote:
> Ben Rudiak-Gould wrote:
> > Have I succeeded in reconciling our views?
>
> Perhaps! In particular, perhaps it's just a pedagogical issue.
I'm interested in it mainly from a pedagogical perspective, yes.
> Note that instead of:
> data Shape = Circle Float
>| Square F
On 2004-11-01 at 12:30PST "Brian Beckman" wrote:
> Most interesting discussion -- in reading it, I realized that I had a
> 'hidden agenda' in asking my question (hidden even from myself), and
> that is: can I put interesting functionality, like precondition checks &
> data validation, in data const
Most interesting discussion -- in reading it, I realized that I had a
'hidden agenda' in asking my question (hidden even from myself), and
that is: can I put interesting functionality, like precondition checks &
data validation, in data constructors? I suspect not, and that's why I
tend to write s
"Alexander N. Kogan" <[EMAIL PROTECTED]> writes:
> How should I modify it to make it useful on large file?
> It eats too much memory...
> procFile =
> putStrLn .
> show .
> foldl merge [] .
^
> words
foldl is infamous for building the complete list, be
Peter Simons wrote:
>
> Read and process the file in blocks:
>
> http://cryp.to/blockio/docs/tutorial.html
>
On a related note, I've found the collection of papers below to be
helpful in understanding different methods of handling files in Haskell.
http://okmij.org/ftp/Computation
Finn Wilcox wrote:
>On Mon, 1 Nov 2004, Ben Rudiak-Gould wrote:
>
>>In particular, one cannot write an invert :: (a->b) -> Maybe
>>(b->a) which never returns a wrong answer, except for invert = const
>>Nothing
>
>How about:
>
>invert = undefined
>
>This never returns an answer at all, so it can't r
On Mon, 1 Nov 2004, Ben Rudiak-Gould wrote:
> In particular, one cannot write an invert :: (a->b) -> Maybe
> (b->a) which never returns a wrong answer, except for invert = const
> Nothing
How about:
invert = undefined
This never returns an answer at all, so it can't return a wrong one!
Finn
Ben Rudiak-Gould wrote:
> Have I succeeded in reconciling our views?
Perhaps! In particular, perhaps it's just a pedagogical issue. Note
that instead of:
data Shape = Circle Float
| Square Float
the Haskell designers might have used the following syntax:
data Shape where
Circle
Alexander N Kogan writes:
> I'm newbie and I don't understand how to process large
> files in haskell with constant memory requirements.
Read and process the file in blocks:
http://cryp.to/blockio/docs/tutorial.html
Peter
___
Haskell-Cafe mailing
On Mon, 1 Nov 2004, Ben Rudiak-Gould wrote:
> Paul Hudak wrote:
>
> > Oh, I disagree with this point of view. Circle is certainly a value,
> > i.e. a full-fledged function, as Brian Beckman correctly surmised.
>
> Interesting. I don't claim that my viewpoint is the One True Path, but I
> don
Keith Wansbrough wrote:
>Indeed, they are functions. Another way of thinking about it is as an
>"initial algebra" (technical term). What this means is this:
>
>"Shape" is a set of values that contains
> - the result of Circle x for all values x :: Float
> - the result of Square x for
Paul Hudak wrote:
Oh, I disagree with this point of view. Circle is certainly a value,
i.e. a full-fledged function, as Brian Beckman correctly surmised.
Interesting. I don't claim that my viewpoint is the One True Path, but I
don't think it's wrong, either. I know you're interested in the teach
On Mon, 1 Nov 2004, Alexander N. Kogan wrote:
> import System.Environment
>
> merge [] x = [(x,1)]
> merge (e@(a,b):xs) x | x == a = (a,b+1):xs
> | otherwise = e : merge xs x
>
> procFile =
> putStrLn .
> show .
> foldl merge [] .
> words
Hi!
I'm newbie and I don't understand how to process large files in haskell with
constant memory requirements. For example, to count numbers of different
words in text file I wrote following program:
-- start
import System.Environment
merge [] x = [(x,1)]
merge (e@(a,b):xs) x | x == a = (a,b+1
> Oh, I disagree with this point of view. Circle is certainly a value,
> i.e. a full-fledged function, as Brian Beckman correctly surmised. The
> Ben Rudiak-Gould wrote:
> > Brian Beckman wrote:
> >
> > >data Shape = Circle Float
> > > | Square Float
> > >
> > >I read this somet
Oh, I disagree with this point of view. Circle is certainly a value,
i.e. a full-fledged function, as Brian Beckman correctly surmised. The
Haskell designers did not decide "for convenience" that Circle is the
same as \x -> Circle x. Rather, that's a fundamental law (the eta law,
to be exact
Brian Beckman wrote:
>data Shape = Circle Float
> | Square Float
>
>I read this something along the lines of "'Shape' is a type constructor,
>for use in other type-defining expressions, and 'Circle' and 'Sqare' are
>its two data constructors, which should be used like functions of type
>'
John Goerzen <[EMAIL PROTECTED]> writes:
> I'm interested in this too. I see a webpage at
> http://galois.com/~sof/hugs98.net/.
>
> I was going to try building it with Mono, but all it says is that
> "Sources are available via CVS". I don't know which CVS repo, where, or
> anything. Does anybo
On 2004-11-01, David Lo <[EMAIL PROTECTED]> wrote:
> Dear all,
>
> Vincenzo, thank you for your reply and advice. I'll take a look on xmlrpc.
>
> I've heard of hugs98 for .Net. Anyone has ever tried to call haskell
> from .Net using it ? Please kindly advise, since one example provided
I'm interes
32 matches
Mail list logo