On 20/09/2013, at 11:47 PM, damodar kulkarni wrote:
>
> There is an Eq instance defined for these types!
>
> So I tried this:
> *Main> sqrt (10.0) ==3.1622776601683795
> True
> *Main> sqrt (10.0) ==3.16227766016837956
> True
> *Main> sqrt (10.0) ==3.1622776601683795643
> True
> *Main> sqrt (10.
The original poster wants to
- read a file
- get the contents as a String
- break the string into lines
- do something with the lines
- and presumably print the result
Easy. Put the following lines in a file called 'rf.hs':
file_name = "rf.hs"
main =
readFile file_name >>= \string -> p
On 3/09/2013, at 10:44 PM, Rustom Mody wrote:
> Whoops! my bad -- I was *thinking* 'pipes' but ended up *writing* 'IPC' :-)
>
> So let me restate more explicitly what I intended -- pipes, FIFOs, sockets,
> etc.
> IOW read/write/send/recv calls and the mathematical model represented by the
> (
allPairs2 can be simplified using a trick I wouldn't dare use in
any language but Haskell:
triangle4 xs = fused undefined [] xs
where fused x (y:ys) zs = (x,y) : fused x ys zs
fused _ [] (z:zs) = fused z zs zs
fused _ [] [] = []
I submit this just for grins; it h
On 3/09/2013, at 5:17 PM, damodar kulkarni wrote:
> I didn't want to clutter that thread so I am asking a question here.
> Where do I find foundational and/or other good references on the topic of
> "stream interface vs string interface to convert objects to text"? I tried
> google but failed.
On 2/09/2013, at 3:55 PM, Rustom Mody wrote:
> On Mon, Sep 2, 2013 at 5:43 AM, Richard A. O'Keefe wrote:
>
> A slogan I have programmed by since I first met C and recognised
> how vastly superior to PL/I it was for text manipulation _because_
> it didn't have a prope
On 1/09/2013, at 6:02 PM, yi lu wrote:
> I want to know if it is possible that I use strings without "".
>
> If I type
> Prelude>foo bar
> which actually I mean
> Prelude>foo "bar"
> However I don't want to type ""s.
>
> I have noticed if bar is predefined or it is a number, it can be used as
On 1/09/2013, at 7:06 PM, Christopher Howard wrote:
> It seemed to be suggesting that a Num instance for functions would imply the
> need for constant number functions, which leads to difficulties. But I don't
> see why one would have to take it that far.
You *cannot* make a type an instance of
On 20/08/2013, at 6:44 PM, Kyle Miller wrote:
> By "working as expected" I actually just meant that they distribute (as in
> a(b+c)=ab+ac) and commute (ab=ba and a+b=b+a),
That is a tiny fraction of "working as expected".
The whole "modular arithmetic" argument would come close to
having some vi
On 20/08/2013, at 3:43 AM, Kyle Miller wrote:
> On Sun, Aug 18, 2013 at 8:04 PM, Richard A. O'Keefe
> wrote:
> The argument for twos-complement, which always puzzled me, is that the other
> systems have two ways to represent zero. I never found this to be a problem,
>
On 19/08/2013, at 3:38 AM, Nicolas Frisby wrote:
> The docs at
>
>
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:gcd
>
> give a NB mentioning that (abs minBound == minBound) is possible for
> fixed-width types.
At least three ways to represent negative integer
On 8/08/2013, at 2:56 AM, Donn Cave wrote:
> The RFC822 headers of your email suggest that you use a Macintosh computer,
> so apart from the apparently disputable question of whether you're familiar
> with English, you have the same online dictionary as mine.
My department has an electronic subsc
On 8/08/2013, at 2:09 AM, damodar kulkarni wrote:
> Thanks for pointing this out, I was not able to point my thoughts in this
> direction.
>
> But I still have a doubt: if my familiarity doesn't come in the form of some
> "analogy", then my acquired intuition about "it" would be of little use.
On 7/08/2013, at 9:17 PM, Jerzy Karczmarczuk wrote:
> I am the last here who would quarrel with Richard O'K., but I firmly believe
> that such reasoning is a Pandora box.
>
> The King, the government, the Pope, etc. have no power, only the
> interpretation of their decrees by "outer agents" _d
On 7/08/2013, at 2:10 PM, damodar kulkarni wrote:
> I bet you can find an abundance of C programmers who think that
> "strcmp" is an intuitive name for string comparison (rather than compression,
> say).
>
> But at least, 'strcmp' is not a common English language term, to have
> acquired some
On 6/08/2013, at 9:28 PM, J. Stutterheim wrote:
> That argument makes sense, although I find it a bit counter-intuitive still.
In discussions like this, I have never been able to discover any meaning for
"intuitive" other than "familiar". Applying "pure" to an IO operation doesn't
go against *m
On 31/07/2013, at 8:16 PM, Simon Hengel wrote:
>
> * There is no such thing as a parse error in Markdown, and I think we
> should try to make this true for Haddock markup, too
It is very far from clear that this is a virtue in Markdown.
In trying to learn Markdown, I found it an excessively ti
On 25/07/2013, at 7:09 PM, wrote:
> Here is a snippet from a real code that could benefit from
> non-recursive let.
[[A big blob of extremely dense code.]]
_Nothing_ is going to make that easy to read.
And I say that as someone who loves Haskell and is in *awe* of
Oleg. I mean, if the functi
On 22/07/2013, at 8:14 PM, Andreas Abel wrote:
> Just today, my student asked me why the following program does nothing:
Did you ask your student why their code should not be torn into pieces,
burned to ashes, and incorporated into a pot for radioactive waste?
All those occurrences of unsafePer
On 21/07/2013, at 7:36 AM, Evan Laforge wrote:
> Just by coincidence, I recently wrote this:
This is a BEAUTIFUL example.
I think we may disagree about what it's an example OF,
however. I found the code a little difficult to
follow, but when that's fixed up, there's no longer
any reason to want
Brian Marick sent me a couple of his stickers.
The one I have on my door reads "to be less wrong than yesterday".
The other one I keep free to bring out and wave around:
"An example would be handy about now."
All of the arguing to and fro -- including mine! -- about
non-recursive let has
On 16/07/2013, at 3:21 PM, Clark Gaebel wrote:
>
> I'm still against having an Ord version, since my intuition tells me
> that hash-based data structures are faster than ordered ones.
There are at least four different things that "an Ord version" might
mean:
- first sort a list, then eliminate
On 15/07/2013, at 8:23 PM, J. Stutterheim wrote:
> The OS dependency for dynamics stems from the fact that the Clean dynamics
> are quite a bit more powerful than Haskell's. For example, using dynamics, it
> is possible to send arbitrary functions to another Clean application, which
> can then
On 13/07/2013, at 11:27 PM, J. Stutterheim wrote:
>> - they then abandoned the Macintosh world for
>> Windows. The Mac IDE was killed off; there is
>> now an IDE for Windows but not MacOS or Linux.
>
> The good news is that the latest version of Clean[2] and its code
> generator[3] now works
On 12/07/2013, at 6:12 PM, Andreas Abel wrote:
[I can't try your F# example but ocaml does something different.]
Yes. They are different languages.
By the way, I used the F# that comes with Mono.
> On 12.07.2013 02:22, Richard A. O'Keefe wrote:
>> For what it's wor
On 11/07/2013, at 6:16 PM, wrote:
>
> I'd like to emphasize that there is a precedent to non-recursive let
> in the world of (relatively pure) lazy functional programming.
So what? You can find precedents for almost anything.
I could even point you to a lazy mostly-functional language
with as
On 11/07/2013, at 11:09 AM, Donn Cave wrote:
> let x = t + 1 in
> let y = x in
> let x = y + 1 in x
>
Still no cigar.
nhc98 v1.16
Program:
main = print $ (let t = 0 in let x = t + 1 in let y = x in let x = y + 1 in x)
Output:
2
___
Ha
On 11/07/2013, at 4:00 AM, Donn Cave wrote:
> I've gone to some trouble to dig up an nhc98 install (but can't seem to
> find one among my computers and GHC 7 won't build the source thanks to
> library re-orgs etc.) Because, I vaguely recall that nhc98's rules
> were different here? Anyone in a p
On 10/07/2013, at 8:42 PM, Andreas Abel wrote:
>>
>>> Hear, hear! In OCaml, I can (and often do) write
>>>
>>> let (x,s) = foo 1 [] in
>>> let (y,s) = bar x s in
>>> let (z,s) = baz x y s in ...
I really wish you wouldn't do that.
After reading Dijkstra's paper on the f
On 2/07/2013, at 12:00 AM, Richard Cobbe wrote:
> Sure. So my first question boils down to which of the two alternatives
> below does the community prefer? (To be clear about the intended
> semantics: this is the application of the function f to the arguments x, y,
> and z.)
>
>f x
>y
On 1/07/2013, at 1:04 PM, Richard Cobbe wrote:
>
> I should have been clearer in my original question: I'm curious about what
> to do when a multi-argument function application gets split across lines.
> That wiki page dicsusses how the layout rule interacts with various special
> forms (let, whe
An important question here is whether you want to notice
when a Roman numeral is invalid, e.g., iix, or not.
From a parsing point of view context-free grammars are not
ideal. We have the patterns
i{1,3} | iv | vi{1,3} | ix units
x{1,3} | xl | lx{1,3} | xc
My original problem was that I wanted to load a particular set of
packages using 'cabal install'. It didn't work (cabal install issues)
and while the maintainer reacted promptly and helpfully, cabal
kept on trying to install the wrong version.
Part of the problem was that blasting away ~/.cabal a
Today I cleared out everything, using uninstall-hs and
rm -rf ~/.cabal ~/Library/Haskell
I downloaded Haskell Platform 2013.2.0.0 64bit.pkg
and installed it.
I was unsuccessful in installing the packages I wanted
using cabal install, which suggested running ghc-pkg check.
So I cleared out everyt
On 11/06/2013, at 1:58 AM, Alberto G. Corona wrote:
> I have ever wondered how a committee could have made Haskell.
A committee made Algol 60, described as "an improvement on most
of its successors". A committee maintains Scheme.
On the other hand, an individual gave us Perl.
And an individual
On 4/06/2013, at 4:22 PM, Rustom Mody wrote:
>
>
> On Tue, Jun 4, 2013 at 7:35 AM, Richard A. O'Keefe
> wrote:
>
> On 3/06/2013, at 6:58 PM, Carter Schonwald wrote:
> > If the Int type had either of these semantics by default, many many
> > performance
On 3/06/2013, at 6:58 PM, Carter Schonwald wrote:
> If the Int type had either of these semantics by default, many many
> performance sensitive libraries would suddenly have substantially less
> compelling performance. Every single operation that was branchless before
> would have a branch *ev
On 15/05/2013, at 2:57 AM, John wrote:
> Hi,
>
> I have to write a function which returns a list of all pairs (x,y) where x,
> y ∈ N AND:
> – x is the product of two natural numbers (x = a · b, where a, b ∈ N) AND
> – x is really bigger than 5 but really smaller than 500, AND
> – y is a squer
On 29/04/2013, at 10:04 PM, kudah wrote:
> On Mon, 29 Apr 2013 18:04:47 +1200 "Richard A. O'Keefe"
> wrote:
>
>> so that there is no possibility of catching errors early;
>> by definition in that processor there are no errors.
>
> Haddock's
I should add that as a consumer of Haddock documentation
I can testify that fancier styling (in whatever format)
would be of little benefit to _me_. What I need is more
plain text and more examples.
To be perfectly honest, most of the time when looking at
a Haddock page, I end up clicking on the
On 29/04/2013, at 4:18 PM, Chris Smith wrote:
>
> My point was not anything at all to do with programming. It was about
> writing comments, which is fundamentally a communication activity. That
> makes a difference. It's important to keep in mind that the worst possible
> consequence of get
On 29/04/2013, at 3:26 AM, Chris Smith wrote:
> I think it's worth backing up here, and remembering the original point
> of the proposal, by thinking about what is and isn't a goal. I think
> I'd classify things like this:
>
> Goals:
> - Use a lightweight, common, and familiar core syntax for s
The basic problem is that the University has a strict policy
that academic staff must not have root access on any machine
that is connected to the University network. I was given an
administrator account so that I could resume the printer and
install (some) stuff, but /Developer is owned by root,
On 11/04/2013, at 12:56 PM, Brandon Allbery wrote:
>
> Xcode 4.2 and on do not use /Developer at all. You have an older Xcode on
> your system somehow, which does not understand newer object files; you should
> remove the entire /Developer tree. (Xcode, in order to be distributable via
> the A
On 10/04/2013, at 2:45 PM, wrote:
... unsafeInterleaveST is really unsafe ...
> import Control.Monad.ST.Lazy (runST)
> import Control.Monad.ST.Lazy.Unsafe (unsafeInterleaveST)
> import Data.STRef.Lazy
>
> bad_ctx :: ((Bool,Bool) -> Bool) -> Bool
> bad_ctx body = body $ runST (do
> r <- newSTR
Machine:an Intel Core 2 Duo desktop Mac.
OS: Mac OS X 10.7.4
Xcode: 4.6.1 (including command line tools)
Haskell:"Haskell Platform 2012.4.0.0 64bit.pkg"
downloaded today (GHC 7.4.2)
cabal update advised me to install a new cabal-install.
m% cab
There is no fundamental problem with non-linear patterns
using ==. (The functional logic programming world long
ago generalised the idea of unification to 'narrowing'.)
There _is_ a technical problem in Haskell about whether
the == here is necessarily the one from the Prelude or
whether it might
On 8/04/2013, at 11:21 AM, Levent Erkok wrote:
> It appears that the consensus is that this is a historical definition dating
> back to the times when IEEE754 itself wasn't quite clear on the topic itself,
> and "so nobody thought that hard about negative zeroes." (The quote is from a
> comment
On 5/04/2013, at 2:00 PM, Johan Tibell wrote:
>> Would it be too much to ask that a notation be used which has
>> a formal syntax and a formal semantics?
>
> We will document our superset, sure. That's what others did as well.
> The point is using Markdown as the shared base.
Nononono.
Sure, th
On 5/04/2013, at 12:34 PM, Johan Tibell wrote:
>
> Markdown has won. Look at all the big programming sites out there,
> from GitHub to StackOverflow, they all use a superset of Markdown.
Yes, but they tend to use _different_ supersets of Markdown.
Would it be too much to ask that a notation be
On 5/04/2013, at 1:22 AM, Tillmann Rendel wrote:
> Hi,
>
> Richard A. O'Keefe wrote:
>>> As I understand it, in ML, it seemed to be a clever idea to not have type
>>> signatures at all.
>>
>> Wrong. In ML, it seemed to be a clever idea not
On 4/04/2013, at 5:59 AM, Tillmann Rendel wrote:
> As I understand it, in ML, it seemed to be a clever idea to not have type
> signatures at all.
Wrong. In ML, it seemed to be a clever idea not to *NEED* type signatures,
and for local definitions they are very commonly omitted.
But you can cert
I should mention that both functional programming in general
and Backus's FP _have_ been influenced by APL, which, while
imperative, strongly encourages "algebraic" combination of
small functions and had (a fixed set of) higher-order "operators".
As for Brute Force Learning by reading imperative c
It's "Backus", people. He was never the god of wine.
I cannot detect any trace of Backus's FP in Haskell at all.
FP is strict. Haskell is not.
FP is typeless. Haskell is highly typeful.
FP does not name formal parameters. Haskell often does.
FP has roots in APL. Haskell doesn't.
I don't see a
On 19/03/2013, at 9:31 AM, OWP wrote:
> If I may ask, I'm not quite sure what O(2^n) and O(1) are?
Check any data structures and algorithms textbook.
Reverting to the original topic, THIS is the age of specialised
machines. A lot of the chips out there are not just a CPU but
a SoC (System on a
Carlos Camarao wrote:
> Sorry, I think my sentence:
>"To define (+) as an overloaded operator in Haskell,
> you have to define and use a type class."
>is not quite correct. I meant that to define any operator in Haskell you have
>to
> have a type class defined with that operator as m
On 12/03/2013, at 10:00 AM, MigMit wrote:
>
> On Mar 12, 2013, at 12:44 AM, "Richard A. O'Keefe"
> wrote:
>>
>> Prelude> :type (+)
>> (+) :: Num a => a -> a -> a
>>
>> The predefined (+) in Haskell requires its arguments a
On 12/03/2013, at 3:15 AM, Carlos Camarao wrote:
> On Sat, Mar 9, 2013 at 5:33 PM, Peter Caspers wrote:
>
> Hi,
>
> I just started playing around a bit with Haskell, so sorry in
> advance for very basic (and maybe stupid) questions. Coming from
> the C++ world one thing I would
On 11/03/2013, at 12:10 AM, Peter Caspers wrote:
> thanks, this was the core of my question. So by example, if I define a Date
> type as
>
> data Date = Date Int deriving Show
>
> representing a date by its serial number and want two constructors
> (conditions are only examples here)
>
> --
Just to play devil's advocate:
100% agreed that there are better things to do in Haskell _source code_ than
regexps.
The thing about regexps is that they can be accepted at run time as _data_.
This means, for example, that they can be put in whatever you use for
localisation.
See for exam
On 22 Sep 2008, at 9:19 am, Albert Y. C. Lai wrote:
Everyone should use exclusively ancient Egyptian iconography. It is
the only universally readable language.
I know this was full of (:-) (:-),
but it seems like the perfect chance to mention Blissymbols.
http://unicode.org/roadmaps/smp/smp-4
Erlang's equivalent of [m..n] is lists:seq(M, N),
which is currently defined to raise an exception when N < M.
In particular, lists:seq(1, N) returns a list of length N
when N > 0, but not when N = 0.
I'm currently arguing that lists:seq(1, 0) should be [],
not an exception. Oddly enough, I'm bei
It may be of interest that although Erlang has been doing
lightweight concurrency for >20 years,
- you can choose whether you want to use an SMP version that
has as many schedulers as there are cores (plus internal
locking as needed) or a non-SMP version with one scheduler
(and no intern
On 18 Sep 2008, at 3:20 am, Mauricio wrote:
Agree about the answer, not about the question. The
correct one would be "is it possible to change haskell
syntax to support the international notation (not any
locally sensitive one) for decimal real numbers? Would
a change in 'read' be a good first s
On 15 Sep 2008, at 12:51 pm, Daniel Fischer wrote:
Am Montag, 15. September 2008 02:24 schrieb Cetin Sert:
Hi why do I get?
Buffering. For compiled programmes, stdin and stdout are line-
buffered by
default, so the output doesn't appear until the program finishes.
Either put
hSetBuffering
On 14 Sep 2008, at 10:59 pm, Rafael Almeida wrote:
One thing have always bugged me: how do you prove that you have
correctly proven something?
This really misses the point of trying to formally verify something.
That point is that you almost certainly have NOT. By the time you
get a theorem p
On 11 Sep 2008, at 3:54 am, Brandon S. Allbery KF8NH wrote:
I think that only counts as the origin of the idea; isn't :-prefixed
infix constructors a ghc-ism?
Haskell 98 report, page 10:
"An operator symbol starting with a colon is a constructor".
(I seem to have four copies of the report on
On 9 Sep 2008, at 8:15 am, Kyle Consalus wrote:
Anyway, for the time being I believe there are operations that can be
done with shared memory
that can't be done with message passing if we make "good performance"
a requirement.
One of our people here has been working on Distributed Shared Memo
I think the demonstration is in Hoare's book on co-operating
sequential processes, but if you have pure processes and
message passing, you can simulate conventional variables.
Here's an Erlang version:
variable_loop(State) ->
receive
{ask,Sender} -> Sender!{self(),State},
On 28 Aug 2008, at 9:07 pm, Jules Bean wrote:
Insert for Data.Sequence is log(i) where i is the position of the
insertion; clearly bounded by log(n). toList is O(n) and index is
(at worst) log(i).
I think the corresponding operations with tries are log(n),
Let the key you want to insert h
On 28 Aug 2008, at 8:34 am, Aaron Tomb wrote:
What type safety buys you, in my mind, is that Nothing is only a
valid value for explicit Maybe types. In cases where you don't use
Maybe, the "null" situation just can't occur. In languages with null
pointers, any pointer could possibly be null
Someone wrote:
trie: O(len)*O(width)
hashed trie: O(len)
hash: O(len)
If "width" here refers to the branching factor of the trie,
it's actually O(len.lg(width)), and the width that matters
is not the *possible* number of choices but the *actual*
number.
The great problem with hash tables is d
On 26 Aug 2008, at 3:42 pm, Deborah Goldsmith wrote:
All characters with general category Lu have the property Uppercase,
but the converse is not true.
It depends on what the OP wants to do with the information.
For example, Unicode Standard Annex 31,
http://www.unicode.org/reports/tr31/tr31
On 26 Aug 2008, at 1:31 pm, Deborah Goldsmith wrote:
You can't determine Unicode character properties by analyzing the
names of the characters.
However, the OP *does* have a copy of the UnicodeData...txt file,
and you *can* determine the relevant Unicode character properties from
that.
F
Speaking of GdH, the web page
http://www.macs.hw.ac.uk/~dsg/gdh/
was last updated in June 2007, it says,
but the binary snapshot (Linux only) is February 2002,
and the "installing GdH" part says it's built using
the GHC 5.00 sources.
Is GdH dead, or is there a more up to date version
lurking some
Just an idiot-level question: so these "constants" are subject
to revision, but *how often*? What is the actual cost of
recompiling and using them *as* constants, compared with the
cost of rereading the stuff every time you run the program and
passing it around?
--
If stupidity were a crime, who
On 15 Aug 2008, at 12:17 pm, Brandon S. Allbery KF8NH wrote:
Actually, while I'm not sure how Linux does it, on the *BSDs pipes
are actually socketpairs.
This raises the question, which the documentation did not make clear
to me,
whether a "named pipe" is a pipe. One would hope it was, bu
On 14 Aug 2008, at 6:28 pm, Ketil Malde wrote:
Isn't [sendfile()] superseeded by splice(2) nowadays?
Solaris 10:
f% man splice
No manual entry for splice
Mac OS X 10.5.4
m% man splice
No manual entry for splice
Linux 2.6.23...
o% man splice
..
one of the descriptors MUST refer to
On 14 Aug 2008, at 10:47 am, John Meacham wrote:
There isn't a standard unix sendfile, while a few different ones have
functions called 'sendfile', they have different meanings/prototypes
in
general.
For example, I'm typing this on an Intel Mac running Mac OS 10.5.4,
and 'man sendfile' show
On 25 Jul 2008, at 10:55 am, Duncan Coutts wrote:
The problem of course is recursion and deeply nested call stacks which
don't make good use of register windows because they keep having to
interrupt to spill them to the save area.
A fair bit of thought was put into SPARC V9 to making saving an
On 24 Jul 2008, at 3:52 am, Duncan Coutts wrote:
[Sun have donated a T5120 server + USD10k to develop
support for Haskell on the SPARC.]
This is wonderful news.
I have a 500MHz UltraSPARC II on my desktop running Solaris 2.10.
Some time ago I tried to install GHC 6.6.1 on it, but ended up
with
I think it may be time for a little clarity about aoicb's.
From the Single Unix Specification:
"The header shall define the aiocb structure
which shall include AT LEAST the following members:
int aio_fildes File descriptor.
off_t aio_offset File offset.
On Fri, 18 Jul 2008, stefan kersten wrote:
On 17.07.2008, at 21:46, Lennart Augustsson wrote:
If scaleFloat and exponent are implemented with bit twiddling
they can
be quite fast.
is there a way in ghc to 'cast' between float/int32 and double/
int64 (without going through memory)?
I read
On 27 Jun 2008, at 11:36 am, Adam Langley wrote:
Specialised for 2d only, but:
http://www.imperialviolet.org/binary/NearestNeighbour2D.hs
In my C code for this, specialised to 3D,
- dimension numbers were never stored
- no arrays were used
- the "search in x" function called
the "search
On 27 Jun 2008, at 3:11 am, Andrew Wagner wrote:
For what it's worth, a 3-dimensional kd tree really flew on this
problem.
I did some reading up on this, and it seems interesting. It would be
need to implement something like this in Haskell, but I can't seem to
find any detailed specs on the
On 26 Jun 2008, at 8:14 am, Andrew Wagner wrote:
6.) You have a [(WeatherStationId, Latitude, Longitude)]. Similar to
#3, write a function which will, off-line, turn this into a data
structure from which you can easily determine the nearest Weather
Station, given an arbitrary Latitude and Longit
On 23 Jun 2008, at 6:30 pm, leledumbo wrote:
I've successfully create a function to return lists of N-ple that
satisfy the
following function:
x1 + x2 + x3 + ... + xN = C
But unfortunately, it's not generic.
Why do you want it to be a tuple? All the elements are the same type,
so it
migh
This is increasingly less relevant to Haskell, except
of course to demonstrate what a nice language Haskell is.
On 20 Jun 2008, at 11:34 pm, Jules Bean wrote:
I think where I differ on you is how to map the semantics of a C-
like language to explicit references.
I would argue that the glyph "c"
On 19 Jun 2008, at 5:53 pm, Jules Bean wrote:
Richard A. O'Keefe wrote:
- what you get is a reference to a variable (as you do in Scheme)
but loop variables really are variables, not names for values,
so lambdas created in different iterations of the same loop point
so the same
On 19 Jun 2008, at 4:16 am, Anatoly Yakovenko wrote:
C doesn't work like that :). functions always get called.
Not true. A C compiler must produce the same *effect* as if
the function had been called, but if by some means the compiler
knows that the function has no effect, it is entitled to
On 18 Jun 2008, at 4:36 pm, Karoly Negyesi wrote:
(a) I would *never* want to use an implementation of closures like
that.
Could you elaborate on a) ?
It wasn't me who wrote it, but consider
- non-local variables are *not* captured unless you explicitly
hoist them into the lambda expressio
I believe C# already has lambdas, and Java is supposed to be getting
them. PHP is playing catchup, is all. (Oh, and Eiffel has 'agents',
and I think I saw something about C++ Next Degeneration, and ...)
Heck, the idea has only been around in computing since the 1950s...
___
Since Haskell-Café often strays into mathematics,
this may not be too far off topic.
On 17 Jun 2008, at 2:29 pm, Evan Laforge wrote:
Yeah, on reflection, I think my "intuition" derives from me asking a
math teacher back in high school "isn't n/0 infinity?" after looking
at a graph, to which he s
On 17 Jun 2008, at 11:07 am, Evan Laforge wrote:
So, I know this has been discussed before, but:
1/0
Infinity
0/0
NaN
... so I see from the archives that Infinity is mandated by ieee754
even though my intuition says both should be NaN.
Other people have other intuitions. It may be that
On 28 May 2008, at 1:04 pm, Dan Piponi wrote:
In particular, which syllable gets the stress, and what are the
lengths of the two vowels? Couldn't find anything in the FAQ
(http://www.haskell.org/haskellwiki/Cabal/FAQ).
I've always pronounced it k'BAHL, but was surprised to find that
the OED (
On 21 May 2008, at 9:25 am, Conal Elliott wrote:
I think the practice of constraint in type definitions is generally
discouraged,
Is this true? If so, why?
If I have a data type that simply doesn't make sense unless some of the
type variables belong to certain classes, _shouldn't_ that be st
On 15 May 2008, at 8:33 pm, Yitzchak Gale wrote:
The point is that it is always best to keep language syntax
as simple as possible, for many reasons. In the case of Unicode,
that means staying as close as possible to the spirit of Unicode and
minimizing our own ad hoc rules.
In particular, Unic
On 15 May 2008, at 2:34 pm, Brandon S. Allbery KF8NH wrote:
Hm. Newer Unicode standard than the version supported by OSX and
GNOME, I take it? That's not so helpful if nobody actually supports
the characters in question. (My Mac claims 166CC is in an
unassigned area, and no supplied font
On 15 May 2008, at 7:19 am, Brandon S. Allbery KF8NH wrote:
Unfortunately, while I thought there was a distinct lambda sign that
wasn't the lowercase Greek letter, there isn't. (That said, I don't
see why it couldn't be a keyword. You'd need a space after it.)
There are three lambda letter
On 14 May 2008, at 8:58 am, Andrew Coppin wrote:
What I'm trying to say [and saying very badly] is that Haskell is an
almost terrifyingly subtle language.
Name me a useful programming language that isn't.
Simply interchanging two for-loops, from
for (i = 0; i < N; i++) for (j = 0; j <
1 - 100 of 128 matches
Mail list logo