On Mon, 1 Sep 2003, Joost Visser wrote:
> Hi Hal and others,
>
> We would like to hear your thoughts on the viability of a conference or
> workshop dedicated to applications of Haskell for non-Haskell purposes.
>
> On Saturday 30 August 2003 01:39, Hal Daume III wrote:
> > I'm attempting to get
On Sat, 30 Aug 2003, Alastair Reid wrote:
>
> > If you use Haskell for a purpose *other than* one of those listed below,
> > I'd love to hear. I don't need a long report, anything from a simple "I
> > do" to a paragraph would be fine, and if you want to remain anonymous
> > that's fine, too.
[sn
On Thu, 16 Jan 2003, Pal-Kristian Engstad wrote:
> It struck me though, if you have a function that calculates something on a
> list 'lst', and then you calculate something on 'lst ++ [a]', then surely one
> should be able to cache the results from the previous calculation.
I'm not a Haskell expe
On Thu, 16 Jan 2003, Iavor S. Diatchki wrote:
> hi,
>
> just for fun i wrote the function in a different way. it should perform
> pretty much the same way as your function. i don't think the problem is
> (++) here, it is just the way this function is. if "f" is going to use
> all of its argumen
On 17 Sep 2002, Jan Kybic wrote:
> > > > collection. I want to try to force l to be generated on-the-fly
> > > > every time it is needed, to see if it improves performance.
> > > > What is a good way to do it? Would something like
> > > >
> > ...
> > > The easiest way is to make it a function
> >
On Fri, 30 Aug 2002, Koen Claessen wrote:
> * Every once in a while, we get messages like "your e-mail
> is under consideration for sending to the list". This
> suggests that the mailing list is moderated, and that
> there is some person deciding on what can and what cannot
> be sent to t
On 23 Jul 2002, Alastair Reid wrote:
>
> > You shouldn't _need_ to be in the IO monad to get random numbers
> > (although if you choose to that can be a good choice). Clearly
> > there's the need to initialise the generator, but if you want
> > `random' random numbers (as opposed to a known sequ
On Tue, 23 Jul 2002, Nick Name wrote:
> It's relatively simple.
>
> The random number generator is a pure function, so it cannot be
> nondeterministic. So, you have a way to build this function with a seed,
> since the author wanted you to be able to do so, I could say for
> completeness, or reu
On Fri, 31 May 2002, Manuel M. T. Chakravarty wrote:
> I think, the probelm is .NET, not Haskell. .NET just
> doesn't deliver on its promise (= marketing hype) of
> language neutrality. The problem is that .NET is language
> neutral only as long as all languages are sufficiently close
> to C#.
On Thu, 30 May 2002, Don Syme wrote:
> going to provide. Given the general complexity of GHC, the longish
> compile times and the reliance of the GHC library implementation on C
> and C libraries in so many places I decided to implement a simpler
> language from scratch. I like the idea that a
On Thu, 30 May 2002, Ashley Yakeley wrote:
> it). Certainly I find {;} more readable, and I suspect anyone else with a
> C/C++/Java background (or even a Scheme/Lisp background) does too.
Just a data point: I learned Basic, Pascal, Standard ML, C, Haskell, C++,
Perl, Python in that order and ac
On Wed, 15 May 2002, Hal Daume III wrote:
> I tend to agree. I keep meaning for experimental purposes to define a
> list type called AList or something which is syntactically identical to
> lists (i.e., you can use the familiar (:) and [] operators/sugar), but
> gets preprocessed out as actually
On Wed, 15 May 2002, Scott Finnie wrote:
> As a naive but interested newbie, I'm very keen to understand those
> things that FP does well - and just as importantly, those things it
> doesn't. (I'm coming at this from use in an industrial context).
> Based on (_very_) limited experience so far, I
On Thu, 2 May 2002, Serge D. Mechveliani wrote:
> I wrote about e :: Double for the Library.
>
> It can be obtained as exp 1,
> but I wonder whether it is good for the library to add the `e'
> denotation.
Just a comment: my programming style (and others I've seen) use single
letters param
On Sat, 16 Feb 2002, Hal Daume III wrote:
> The reason I ask is that I'm generating a FSM description file and it
> doesn't matter which order I list the transitions in. I'm curious whether
> I could get the program to run any faster if I don't care about order.
I'm a bit confused here: assumin
On Thu, 10 Jan 2002, Mark P Jones wrote:
> | If I have defined a function like this..
> | f =
> | it could be re-written..
> | f =
[snip]
> - The second will compute a value of at most
> once, then cache the result for future use. That
> could make a program run faster, but if t
> > Next Semester, I am supposed to teach a short course in Haskell.
> > Can anyone recommend interesting programming projects which can
> > be completed in about a month? Thank you very much.
This doesn't come from direct experience and you don't specify what the
students will already know, whet
As a general question (and forgive my ignorance): are the various ffi's
implemented using something like `dlopen' or are they done by actually
putting suitable stubs into the Haskell generated C-code which then gets
compiled by the C compiler as part of the overall haskell compilation?
On 14 Sep
(This response comes from the context of someone who like FP but has a day
job writing in C++.)
On Fri, 18 May 2001, Jerzy Karczmarczuk wrote:
> We know that a good part of "top-down" polymorphism (don't ask me what
> do I mean by that...) in C++ is emulated using templates.
Umm... what do you
> Tim> 6. Applying a function f:t->u to a list x::[t] translates to
> Tim> "map f x".
This can be done in mathematica via function attribute (Listable if my
memory is correct). IIRC It's defined by default only for functions that
only make sense on pure numbers/symbols (eg Sin) and it's v
On Fri, 18 Aug 2000, Doug Ransom wrote:
> I do believe FP is current 90 degrees out of phase with OO. I think the
> isue with tuples, lists, conses, etc. it the big problem. I currently see
> no way for someone to write a clever matrix library in Haskell and have it
> seamlessly integrate into
On Tue, 27 Jun 2000, Lennart Augustsson wrote:
> > Using `Left' and
> > `Right' for such cases is fundamentally confusing since it is not
> > clear what the meaning of `Left' and `Right' is.
> Well, I don't totally agree. Anyone using Right for Wrong deserves to
> have his/her head examined. :)
On 1 Jun 2000, Ketil Malde wrote:
> I could accept "mode flags" if the algorithm is extremely similar,
> e.g. passing a comparator function to a sort is a kind of mode flag
> (think ordered/reversed) which I think is perfectly acceptable.
> Having flags indicating algorithm to use (sort Merge (s:
> I knew of the namespace collision effect.
> But one has to choose between the bad and worse.
>
> And in any case, there remain too many ways to error.
> We also may paste
> True :: Bool instead of False
> (the type design does not help),
>
On Wed, 31 May 2000, S.D.Mechveliani wrote:
> And we can hardly invent the mode type better than Char,
> because any specially introduced mode types bring the long names.
>
> quotRem 'n' x (-3) looks better than the pair quotRem & divMod,
> and
> quotRem QuotRemSuchAndSuch x (-3)
>
On Wed, 29 Mar 2000, Matthias Mann wrote:
> Has anybody some experience on what's the best way to write programs that may
> interact in multiple languages?
>
> My first thought was to extract all texts from the source and put them into a
> big list or array. The program then accesses the list
On Fri, 24 Mar 2000, Marc van Dongen wrote:
> Hmm. I must have missed something. My hugs (1.4) allows it.
> I was assuming that Haskell did allow it.
> As it turns out my latest ghc doesn't. That's cool.
If you haven't loaded any modules then hugs is in `module scope' of
prelude and it's possibl
On Thu, 23 Mar 2000, D. Tweed wrote:
> such things? (The closest thing I'm aware of is David Lester's stuff on
> throw away compilation (sorry no pointer)) It just seems that functional
As Julian Seward kindly mentioned to me, I meant David Wake
This is just a curious thought:
happened to read
http://www.arstechnica.com/reviews/1q00/dynamo/dynamo-1.html which makes
the very interesting point that optimizingcompilers have a difficult job
given that they don't know the relative importances of various paths of
execution through the program
> "Ch. A. Herrmann" wrote:
> > I believe that if as much research were spent on Haskell compilation as
> > on C compilation, Haskell would outperform C.
Unless I've got a dramatically distorted view of the amount of research
that goes on for imperative vs functional languages, and C vs haskel
On Tue, 14 Mar 2000, George Russell wrote:
> In any case, in the original example
> Who the author is, and what the version is, would be better handled by
> CVS or some similar system. The "" is redundant; if it doesn't match
> the filename, we have total chaos anyway. The is a drag; I suspect
On Tue, 14 Mar 2000, George Russell wrote:
> "D. Tweed" wrote:
> > * Comments that actually contain meta-program information, eg pragmas
> The Haskell standard system for putting information for the compiler in
> things which look like comments is obnoxious, but fortun
On Tue, 14 Mar 2000, George Russell wrote:
> "D. Tweed" wrote:
> > Documentation is a vague term: certainly it'd be undesirable for a
> > specification to the libraries to just a literate copy of the code
> > itself. But if you're thinking in terms of an
On Tue, 14 Mar 2000, George Russell wrote:
> Frank Atanassow wrote:
> > What do you all think?
> Well I suppose that includes me, but I'm a bit confused. I've looked at some of
> the .lhs files containing the source of GHC, but the so-called literate nature
> of the code doesn't seem to me to ma
On Wed, 2 Feb 2000, Koen Claessen wrote:
> gen1
> /\
> gen1gen2 -- once
> / || \
> gen1 gen2 gen2 gen3 -- twice
>
> In fact, they will produce the *same* generator "gen2" on
> both sides, which will create an undesired dependency
> between the tw
[Hopefully not off-topic wrt Haskell]
On Thu, 27 Jan 2000 [EMAIL PROTECTED] wrote:
> >> Look at the popularity of PERL
> >> for example. That is one thing I will never understand.
> I'm sure I will get flamed to a crisp for this, but...
> I think PERL can be quite nice when you want a quick hac
On Tue, 25 Jan 2000, D. Tweed wrote:
Oops, fixing two thinko's
> f _ [] = []
> f a xs =res:f a' zs
> (ys,zs)=splitAt 40 xs
> (a',res)=doStuff a ys
(My haskell coding is getting worse than my C++, which I didn't
On Tue, 25 Jan 2000, Chris Okasaki wrote:
> > I'm with the option (B): negatives are just outside
> > the domain of take&drop, and should give you an error
> > message.
>
> For the people that share this sentiment, can you please
> explain why ints that are too big should not similarly
> give
On Sun, 28 Nov 1999, S.D.Mechveliani wrote:
> DoCon provides the standard functions
> cToPol "coefficient to polynomial",
> varPs "variables as polynomials".
> In other algebra systems, they are easy to program too - as soon
On Sun, 28 Nov 1999, S.D.Mechveliani wrote:
> Is there any problem?
> Introduce the program variables x,y... and bound them to the symbolic
> indeterminates.
> For example, in DoCon program, it is arranged about like this:
>
> let { s = cToPol ["x","y"] 1; [x,y] = varPs s }
> in
>
On Fri, 26 Nov 1999, Jerzy Karczmarczuk wrote:
> Do you know what makes Maple so attractive for newbies, for teachers,
> etc? One of the reasons is simply scandalous, awful, unbelievably
> silly : the lack of distinction between a symbolic indeterminate,
> and the program variable. You write ...
On Thu, 25 Nov 1999, Eduardo Costa wrote:
> course. Since I am not able to program in languages like C or
> Oberon, I would like to have a practical lazy functional compiler
> (or a practical prolog compiler). I hope to convince people to implement
> such a compiler.
I think the compiler that y
On Tue, 28 Sep 1999, Fergus Henderson wrote:
> > Personally I'd
> > always write the above, not so much for performance reasons as the fact
> > that if the objects in the vector have a shallow copy constructor
> > (generated automatically & silently) but a destructor that deallocates
> > resourc
On Mon, 27 Sep 1999, S.D.Mechveliani wrote:
> Now it shows the ratio * 6 *.
[snip]
> But this mess with platforms and versions, is not, probably, so
> important, because people can compile and run this program in their
> own environments - and correct the performance result.
>
> What do you
On Wed, 22 Sep 1999, Antti-Juhani Kaijanaho wrote:
> On Wed, Sep 22, 1999 at 02:53:03PM +0100, Claus Reinke wrote:
> > Functional programming, i.e., programming with functions, is possible in
> > languages that do not support all features that have become common in
> > many functional languages.
On 21 Sep 1999, Marcin 'Qrczak' Kowalczyk wrote:
> Sat, 18 Sep 1999 00:06:37 +0200 (MET DST), Juergen Pfitzenmaier
><[EMAIL PROTECTED]> pisze:
>
> > I dont't care very much how fast a program runs. I care about how
> > long it takes me to write it. If you take a programming task of
> > reasonab
On Thu, 9 Sep 1999, George Russell wrote:
> Here is my revised version of the documentation. Sorry I can't
> manage the pretty formatting:
>
> unzip :: [(a,b)] -> ([a],[b])
> -
> Description:
>unzip takes a list of pairs and returns a pair of lists.
Minor quibble: the verbal descriptio
On Wed, 8 Sep 1999, S. Alexander Jacobson wrote:
> Are we talking about documentation for the H98 libraries?
> Are these libraries relevant? Don't MPTC, Existential Types, Restricted
> Type Synonyms, Arrows, and an FFI substantial change the architecture,
> interface, and implementation of the l
On Thu, 26 Aug 1999, Andreas Rossberg wrote:
> Tom Pledger wrote:
> >
> > Where do units of measure fit into a type system?
>
> In Haskell this should be quite easy. Off my head I would suggest
> something like
[snip]
> instance (Unit a, Unit b) => Unit(Prod a b) where
> uni
On 25 Aug 1999, Marko Schuetz wrote:
> What I would like to know is: wouldn't it make sense to have the
> transformation
>
> f x = e where e does not mention x
>
> -->
>
> f x = f'
> f' = e
>
> in hugs? Did I miss anything?
What if e if huge (maybe an infinte list of primes) and f x is used
On Tue, 24 Aug 1999, Ronald J. Legere wrote:
> It WOULD be nice if you could match on functions and not just
> constructors. But I presume that the constructor/function dichotomy
> in Haskell is what allows it to be strongly typed? For example, in the
> untyped 'language' Mathematica employs, p
Warning: comments based on mailing list/internet obesrvations which may
be more representative of what people say than what they do.
On Thu, 19 Aug 1999, Mark P Jones wrote:
> Hi Alex,
>
> | Out of curiosity, how big is the user community? How many downloads of
> | the software? How many are
On Fri, 20 Aug 1999, Bob Howard wrote:
> data Tree a = Leaf a | Branch (Tree a) (Tree a)
> Branch :: Tree a -> Tree a -> Tree a
> Leaf :: a -> Tree a
>
> Im just learning haskell and I cant seem to figure out what is wrong with the above
>code.
> Im using Hugs98 as in interperator (sp) and I ke
On Fri, 13 Aug 1999, Rene Grognard wrote:
> My question is therefore: is Haskell at all suitable for complex numerical
> applications ?
_In my opinion_, Haskell is suitable for numerical programming if you
don't need performance close to C (because your problems are small say and
you're prototyp
On Wed, 11 Aug 1999, Rob MacAulay wrote:
> Thanks for the info. However, I think these are only useful if one
> has the original TeX source. If one only has the translated
> postscript, the fontas are embedded (so Acrobat Reader tells me..)
> as type 3 fonts.
>
> I found a link to something c
On Wed, 28 Jul 1999, Hans Aberg wrote:
> At 14:02 +0100 1999/07/28, D. Tweed wrote:
> >> As for a math description of references, one could take the view that one
> >> always constructs objects a, with references r. Then what is indicated in
> >> the language i
On Wed, 28 Jul 1999, Hans Aberg wrote:
> At 17:15 +1000 1999/07/28, Fergus Henderson wrote:
> Actually, it is just an illusion that referential transparency is broken by
>
> > ref 27 <=> ref 27
> >
> >yields False.
>
> Because the semantic runtime meaning of this is that two different objects,
On Tue, 27 Jul 1999, Simon Marlow wrote:
> > req a b = unsafePerformIO $ do
> >a' <- makeStableName a
> >b' <- makeStableName b
> >return (a' == b')
>
> That's exactly what to use in a situation like this. Pointer equality loses
> referential transparency in general (as Simon P.J. po
On Fri, 11 Jun 1999, Malcolm Wallace wrote:
> Well, compiler-independent is possible (e.g. hmake extracts
> dependencies from any Haskell sources, regardless of compiler.)
> However, language-independent is much more difficult. How could one
> tool deal with all of C, C++, Haskell, and LaTeX? S
[drifting off-topic]
On Fri, 11 Jun 1999, Malcolm Wallace wrote:
> David Tweed writes:
>
> > I think it'd probably better software engineering to split the two tasks.
> > Other than a rather nasty syntax, make does what it sets out to do quite
> > well: using specified dependencies and time-st
On Thu, 10 Jun 1999, Craig Dickson wrote:
> programming, especially lazy functional programming. If it seems desireable
> to re-implement a standard Unix utility in Haskell, I suggest 'make'. One
> could even design and implement a 'make' that would know all about Haskell
> modules, and parse the
On Wed, 19 May 1999, D. Tweed wrote:
Correcting myself slightly:
> effect of the function is to return a value. But, it's still legal &
> sensible to write things like, for f::Int -> (Double,Double), y = fst (f
> 5), or even (_,_) = f 5. So you can't rely on
On Wed, 19 May 1999, Kevin Atkinson wrote:
> I was wondering what the generally felling to allowing true ad-hoc
> overloading like it is done in C++ in Java but more powerful because
> functions can also be overloaded by the return value.
What I've always understood as the main argument for not
On Thu, 13 May 1999, Simon Peyton-Jones wrote:
> I'm not sure exactly what you are asking here.
> > For example, in {rules (map f).(map g) = map (f.g) }
> > f xs = let g = ...
> > h = ...
> > h1 = map g
> >
On Fri, 7 May 1999, S.D.Mechveliani wrote:
> Also D.Tweed <[EMAIL PROTECTED]> writes
>
> > [..] it may dramatically affect the size of expressions held
> > temporarily, eg
> >
> > tipsOfTheDay
> > = map addCopyrightLogo (map toUppercase (map addHaveANiceDay
> > [tip1,tip2,tip3,,t
I'm as excited about the possibility of a limited form of compile time
evaluation via rewrite rules but I'm a getting a bit worried that no-one
has made any examples where there's an laziness to consider: I really
wouldn't want semantic differences depending on the degree of optimization
I compile
On Wed, 5 May 1999, Kevin Atkinson wrote:
> Normally given the class.
>
> class Listable c b where
> toList :: c -> [b]
>
> to list will never be able to be resolved unless the signature is given
> when toList is called because there is no way to derive the type of b
>from the function call
On Tue, 27 Apr 1999, Hans Aberg wrote:
> Then Haskell uses this to implement sets and maps by using C++ STL style
> balanced trees. As Haskell already has generic variables, just as in the
> case of lists, it needs only be implemented once.
As just a general comment, from my usage of the STL it
On Fri, 19 Mar 1999, Fergus Henderson wrote:
> Generally programming languages themselves are always free, i.e. very
> few people have ever tried to copyright a language, and when they have,
> the courts have for the most part rejected such attempts (e.g. see [1]).
> It is of course possible to t
On Wed, 17 Feb 1999, michael abbott wrote:
> As a C++ user (with a background in categories) patiently waiting for
> something a lot better, I personally favour two principles:
> 1.let's go for undecidable type checking. I want the compiler to be able
> to do as much work as possible: ideall
On Fri, 22 Jan 1999, David Barton wrote:
> Peter M|ller Neergaard writes:
>
>1) The implementation of list concatenation ++. In the Haskell
> report it is stated that ++ in general is an operator on monads.
> In the case of lists, ++ works as list concatenation. However,
>
On Fri, 4 Dec 1998, Lennart Augustsson wrote:
>
> > There was a paper
> > published in the JFP about a better way of splitting streams which I think
> > appeared sometime between January 1996--October 1996.
> Are you perhaps referring to the paper by me, Mikael Rittri, and Dan Synek
> called "On
On Fri, 4 Dec 1998, Keith Wansbrough wrote:
> Surely it would be better to split the one stream into several infinite ones:
>
> splitStream :: [a] -> ([a],[a])
>
> splitStream xs = unzip (spl xs)
> where spl (x:y:xs) = (x,y):(spl xs)
>
> Then you don't have to know how many you are goi
On Wed, 2 Dec 1998, Keith Wansbrough wrote:
> Secondly, is it possible to specify at least some minimal conditions on the
> pseudorandom number generator? There are now some very good pseudorandom
> number generator algorithms[*], and it would be not unreasonable to require
> the generator to
On Fri, 13 Nov 1998, Fergus Henderson wrote:
> > It would
> > avoid the nastiness of a special definition for each tuple type and and
> > lead to more flexibility.
>
> I want each tuple arity to be a different type, so that I get a compile
> error rather than a run-time error if say I pass a 3-tu
On Mon, 13 Jul 1998, Eric Blough wrote:
> Alastair Reid writes:
> > [EMAIL PROTECTED] (S.D.Mechveliani) writes:
> > > Recent Haskell ignores the possibility of the automatic type
> > > conversion. Thus,
> > > 1 + 1%2
> > > is ill-typed.
> >
> > and goes on to
On Mon, 29 Jun 1998, S. Alexander Jacobson wrote:
> this:
> foldl version foldl' version
>
> = foldl (+) 0 [1..1] = foldl' (+) 0 [1..1]
> = foldl (+) (0+1) [2..1] = foldl' (+) 1 [2..1]
> = foldl (+) ((0+1)+2) [3..1] =
On Wed, 24 Jun 1998, Erik Meijer wrote:
> >and has written substantial programs. Please, no more "introduction to fp"
> >books!
>
>
> This is exactly why the summerschools on advanced functional
> programming are there. After one in Sweden and one in the USA,
> the third school will be in Br
Firstly, sorry about the double post -- my mailer seems to have the idea
that _any_ e-mail adress _anywhere_ in the header should be replied to.
On Wed, 27 Aug 1997, Hans Aberg wrote:
> At 10:35 97/08/27, D. tweed wrote:
> >.. From what I've read, the JVM is designed to be
On Tue, 26 Aug 1997, David Wilczynski wrote:
> 1) JAVA -- Are there any plans to compile Haskell into byte codes for
> execution on the Java Virtual Machine? The Java issue is very important.
This raises an interesting question (although it doesn't really directly
help David). From what I've r
Hi,
I'm writing a program for which a major part of both the code and (I
think) the execution time will be taken up by a parser( written using
parsing combinators a la Hutton & Meijer's report on monadic parser
combinators). In order to try to find silly slips through type checking I
wanted to use
DISCLAIMER: I've never written a `large' application in Haskell and
perhaps don't appreciate the problems. I _do_ use Haskell for personal
progams
because its so much quicker and easier to get right. (Work is mandated in
C++)
I like Simon Peyton Jones basic extension of guards. However, I'm a bit
82 matches
Mail list logo