Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution -record update

2012-02-10 Thread Steve Horne

On 10/02/2012 03:22, Donn Cave wrote:

   modifyRecord :: RecordType r =  (a -  a) -  (r -  a) -  r -  r



   data Config { tempo :: Int, ...}
   f = modifyRecord tempo (+20)


I'm hoping I missed something, and that you don't intend the (r - a) 
part of this in particular to be taken literally.


If you intend something to be used as a field identifier, you should 
give it a type that says that. A function (r - a) could be anything - 
even a use of const that ignores the value for r. Having a type class 
for field ids, parameterized by the record type and the field type, 
would make more sense. Having that, you could treat a record a bit like 
an IORef - use polymorphic read, write and modify functions. Like an 
IORef doesn't mean mutability, of course.


Personally, though, I still quite like the existing update notation, at 
least for updating multiple fields at once. Some tweaks could be nice - 
particularly for taking an (a - a) function rather than an (a) value 
for each field.


What I might do (note - spelling choices not sanity checked).

data MyRecordT = MyRec {= field01 :: Int, field02 :: Int =}
  --  New notation to avoid breaking changes where old notation is used.
  --  This notation should not provide module-level field access functions.

example_read_1 :: FieldID MyRecordT Int - MyRecordT - Int
example_read_1 fid r = readRec fid r

example_read_2 :: MyRecordT - Int
example_read_2 = readRec MyRecordT.field01
  --  This differs from my earlier typename.fieldname gives field
  --  access function idea. More clutter here, but for a reason.

example_read_3 :: MyRecordT - Int
example_read_3 r = readRec MyRec.field01 r
  --  This would only match field01 in the MyRec constructor case, even
  --  if there were other constructors for the same type. The same type as
  --  MyRecordT.field01, but a different value.

example_read_4 :: MyRecordT - Int
example_read_4 r = r.field01
  --  Direct read of a field in a known record value is a common case,
  --  and avoiding the explicit readRec avoids clutter.


example_modify_1 :: FieldID MyRecordT Int - (Int - Int) - MyRecordT 
- MyRecordT

example_modify_1 fid fun r = modifyRec fid fun r
  --  For longhand, support modifyRec and writeRec functions

example_modify_2 :: MyRecordT- (Int - Int)- MyRecordT
example_modify_2 r fun = r { field01 fun, field02 (+field01) }
  --  First item of each pair indicates field. Lack of = indicates use 
a function.
  --  Within the braces, all the functions (second item each pair) see 
an environment
  --  containing all field names, referring to the original value of 
the record.
  --  Pair doesn't mean tuple here - just two subexpressions separated 
by whitespace.

  --  Maybe - or - separator would be better instead.

example_modify_3 :: MyRecordT - FieldID MyRecordT Int - MyRecordT
example_modify_3 r fid = r { fid (+1) }
  --  First item of each pair still accepts arbitrary field IDs. Also, 
could
  --  use MyRec.field01 - to only allow matching that field in that 
constructor.
  --  Probably require parens for anything other than a single 
identifier in the

  --  field-id subexpression.

example_modify_4 :: MyRecordT - MyRecordT
example_modify_4 r = r { field01 (\_ - readRec r.field02 r) }
  --  The dot still supplies field IDs, overriding the 
names-for-initial-values
  --  environment, for record types, data constructors, and record 
values. Using
  --  the shorthand for any reads of original field values is not 
compulsory.


example_modify_5 :: MyRecordT - MyRecordT
example_modify_5 r = r { field01 = field02, field02 (+1) }
  --  The = is still available too - mixing of write and modify cases 
supported


example_modify_6 :: MyRecordT - MyRecordT
example_modify_6 = MyRecordT { field01 = field02, field02 = field01 }
  --  Allow update shorthand for the type and for the data constructor too,
  --  giving a function as normal.

On scope, the braces imply certain environment-defining rules. Also, the 
dot introduces a very short lived environment providing the field names. 
If the record type and/or data constructor is in scope, and the field 
names are made public by the module that defines them, these notations 
should just work - can't (and no need to) explicitly import the field 
names, which would import them into the wrong scope anyway. Importing 
the type name brings the field names along with it for type- and 
value-related scopes (such as typename.fieldname and 
value.fieldname) and importing the data constructor name brings the 
field names along with it for constructor-related scopes (such as 
datacons.fieldname).


Ban having type name, data constructor name or field name the same for 
the same type, except that a field name can occur within several data 
constructors for the same type - but only when using this record syntax. 
This is in part to avoid confusion within the braces notation for 
update. There is no ambiguity in principle, though, because the new 
environments hide any conflicting identifiers 

Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-02-08 Thread Steve Horne

On 07/02/2012 22:56, Richard O'Keefe wrote:

On 8/02/2012, at 2:11 AM, Steve Horne wrote:


To be fair, field OF record isn't bad in that sense. However, it would defeat 
the purpose of TDNR - the record isn't first, and therefore cannot be used (given a 
left-to-right typing direction) as a context to offer member name suggestions.

Yes, but why SHOULD there be a specific typing direction?
ML manages perfectly fine without it.
For the only reason that any language feature should exist - because it 
is useful. In any language with a rich library, it is useful to get 
hints as to which names are available in a particular context. It saves 
on the need to memorize thousands - sometimes tens or even hundreds of 
thousands - of context-sensitive names and their spellings, and saves on 
getting distracted needing to hunt through manuals.



- #1;
stdIn:1.1-1.3 Error: unresolved flex record
(can't tell what fields there are besides #1)
- #1 (true,3);
val it = true : bool
- #1 (42,stuff,false);
val it = 42 : int

If a right-to-left typing direction works well for #field record
in one language with constrained Hindley-Milner types, why would it
not work well for field¶ record in another language with constrained
Hindley-Milner types?
Parsers don't need to care much about left-to-right vs. right-to-left. 
There can be stack size issues in principle, but that hasn't stopped 
Haskell offering both left-associative and right-associative infix 
operators. The ordering has significance in certain ways in functional 
languages WRT e.g. currying, but that isn't really relevant here. In any 
case, currying is left-to-right anyway - the left-most argument is 
curried first.


The point here is for intellisense-like features to work effectively in 
text editors. The context must come to the left for that to work because...


1. Searching for all possible names within a particular context is
   easier, and generally more likely to be what is needed, than
   searching for all possible contexts that contain a particular name.
2. It's easier to type the context, then the marker, then select/type
   the name than it is to type the marker then the context, then cursor
   back to before the marker, *then* select the name, then cursor back
   to after the context.


Why sacrifice readability (field name precedes record) for the sake
of, well, for the sake of what exactly escapes me.
It doesn't sacrifice readability. The left-to-right order has been 
chosen by most programming languages, and also used in many other 
contexts, because many people find it very natural to start from the 
most general and step down to the more specific in a left-to-right 
direction. For example, chapter.section.subsection, or 
foldername/foldername/filename.


The left-to-right order isn't especially important in general - but for 
intellisense it is.



Also, even when I used COBOL (late eightees, early nineties) I'm pretty sure it supported 
record.field.

That certainly wasn't the case up to COBOL-85.  I don't have a copy of COBOL 
2002,
so I can't speak for that, but COBOL 74 and COBOL 85 are the only candidates 
for those
dates, and they definitely did NOT support record.field.  Since '.' is the 
statement
terminator in COBOL, it's intrinsically unlikely.
(You did *check* a COBOL syntax summary, easily found on the web, before 
posting?  Which?)
If I checked, I wouldn't have said pretty sure would I? Those words 
are generally acknowledged as indicating that someone is working from 
fallible memory.


That said, I did take a look in an old COBOL book. I didn't find either 
the dot or the OF. I vaguely remember that the original COBOL textbook 
I had actually considered the SORT command so intrinsically difficult 
that it was outside of the scope of the book. For various reasons, I 
find it difficult to take COBOL seriously at all, though I wish I had 
kept that original textbook that didn't cover SORT - it was a much 
better joke than the book I kept.

On the more general point of choosing an alternative operator, I agree to a point, but 
familiarity does count for something. Others will point out that Haskell dares to be 
different, but it's possible to be too daring and too different. Being different for the 
sake of being different is for those teenagers who go on about being random 
and whatever else they go on about these days. The success of languages like Java, C# and 
C++ is based on familiarity.

Using pointy brackets for generic parameters and :: for name scope were not 
familiar
when C++ introduced them.  And there was prior art in other languages for 
*both* of those.

One common prior practice, relevantly enough, was '.' for name scope.
Yes, but C++ also dares to be different, and there's a principled reason 
for having multiple selection operators in C++. There are multiple 
namespaces involved. For a smart pointer, for example, . and - access 
different namespaces. :: accesses a different namespace too - containing 
the mostly

Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-02-07 Thread Steve Horne

On 06/02/2012 23:58, Richard O'Keefe wrote:

On 4/02/2012, at 12:13 AM, Gábor Lehel wrote:

All of this said, record.field is still the most readable, intuitive,
and familiar syntax for selecting a field from a record that I know
of.

Having learned COBOL and Algol 68 before Haskell was dreamed of,
I regard

field OF record
COBOL in particular isn't a well-known exemplar of readability. It's 
widely seen as a bad joke. I have used COBOL myself, and largely agree 
with that, with the proviso that I used COBOL a long time ago and have 
repressed most of the details.


Redundancy can be important for readability, but you can have too much 
of anything, and in COBOL the level of redundancy is most kindly 
described as cluttered with excessive verbosity.


To be fair, field OF record isn't bad in that sense. However, it would 
defeat the purpose of TDNR - the record isn't first, and therefore 
cannot be used (given a left-to-right typing direction) as a context to 
offer member name suggestions.


Also, even when I used COBOL (late eightees, early nineties) I'm pretty 
sure it supported record.field. I don't remember using it, but then I 
don't remember using OF either - a side effect of loading one record 
at a time into working storage and effectively having a separate 
variable for each field. Anyway, assuming I'm not suffering from 
worse-than-usual memory, COBOL accepted this common convention.


On the more general point of choosing an alternative operator, I agree 
to a point, but familiarity does count for something. Others will point 
out that Haskell dares to be different, but it's possible to be too 
daring and too different. Being different for the sake of being 
different is for those teenagers who go on about being random and 
whatever else they go on about these days. The success of languages like 
Java, C# and C++ is based on familiarity.


I think Haskell should dare to be different when there's a point to that 
- where necessary based on a principle. We have type classes rather than 
OOP classes for a principled reason. We have the IO monad rather than 
effectful functions for a principled reason.


If we don't have traditional field-selection for a principled reason, I 
think that principle is a very weak one. If names can be scoped to 
modules, to case expressions, to let expressions etc, why not to 
records? Of course there's a difference, but IMO it's not an important one.



If we are going
to let compatibility with Pascal or C or the like be our guide to
readability and intuition, when are we going to switch from ! and
!! for indexing to _[_]?
So far as I can see, there are two likely principles behind this choice 
in Haskell - one weak and one quite strong. One is that we don't have 
expressions with syntactic forms other than prefix functions and infix 
binary operators, except for a few built-in constructs (case, let, ...) 
which aren't functions. There are no special functions with special 
parsing. I view this as a weak principle - not important to the paradigm.


OOP languages have supported built-in translations from special 
notations to functions/methods for a long time. It's a familiar and 
practical approach to, e.g., allowing programmers to define the 
semantics of indexing on a new container type.


There is, however, the issue of overloaded notation and a possible 
conflict with currying.


Python already uses [] for lists (and list comprehensions) as well as 
for indexing. However, Pythons syntax and semantics differ from Haskells 
in many ways. In particular, Python doesn't do currying. The difference 
between currying in a list parameter and indexing a collection would be 
much less clear in Haskell if it supported [] for indexing, probably 
damaging readability and possibly (I haven't checked) causing ambiguity 
that even the compiler couldn't resolve.


In this case again, perhaps Haskell is different for a principled reason 
- choosing to support currying means that either lists or indexing need 
a different syntax. IIRC, ML also dares to be different WRT indexing - 
maybe because it too supports currying.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to print out intermediate results in a recursive function?

2012-02-04 Thread Steve Horne

On 04/02/2012 08:46, MigMit wrote:

Well, if you want that in production, not for debugging purposes, you should 
change the type signature of mergesort so that it uses some monad. Printing 
requires IO monad; however, I would advise to collect all intermediate results 
using Writer monad, and print them afterwards:

mergesort [] = return []
mergesort [x] = return [x]
mergesort xs = do
   tell [xs] -- that's right, [xs], not xs
   let (as, bs) = splitAt (length xs `quot` 2) xs
   liftM2 merge (mergesort as) (mergesort bs)
Also, don't forget that IO actions are values too. IOW, your list of 
intermediate results can be a list of IO actions, effectively deferring 
their execution until later.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-02-03 Thread Steve Horne

On 03/02/2012 11:13, Gábor Lehel wrote:

The first problem is that mixing prefix and postfix function
application within the same line makes it harder to read. When you
read code to try to understand what it does, the direction you like to
go in is here's some object, first do this to it, then do that to it,
then do this other thing to it, then this fourth thing to produce the
final result. In Haskell code with prefix application, this is easy:
you read it from right to left.
I've argued before (don't think here - most likely on Programmers.SE) 
that even mathematicians think imperatively, often viewing an expression 
as if it were a right-to-left series of imperative mutations. I get 
called an idiot when I say that.


But...


This is the smaller problem. If prefix and postfix notations are
completely interchangeable, then we can at least expect people to not
make their own code hard to read, and to stick to one or the other
within an expression. (If they're *not* interchangeable, and one or
the other is required in some cases, then it's a bigger problem.)
There are already some right-associative operators and some 
left-associative operators. So the question isn't really about the 
language grammar, but how something reads.


But then, even in Haskell, where order matters, most things read from 
left to right. With the monadic bind, for example, the left argument is 
before the right argument. In let expressions, the first definition is 
the leftmost definition. In a list or a tuple, the leftmost item is 
normally considered the first item - by definition it's the head in a 
list. When currying arguments, the leftmost argument is the first to 
curry. This isn't an absolute, of course, but still - function 
composition with the dot is arguably the odd-one out.


If the point is that TDNR should use some other symbol, I have some 
sympathy with that, but Haskells freedom with operator identifiers has a 
downside - there are few if any completely safe symbols available to 
use. Unless of course we choose a completely new character that has 
never been available before...


http://www.geek.com/articles/geek-pick/unicode-6-1-released-complete-with-emoji-characters-and-a-pile-of-poo-2012022/


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-30 Thread Steve Horne

On 30/01/2012 07:09, Donn Cave wrote:

((separate . crack . .smallEnd) egg).yolk
(f egg).yolk where f = separate . crack . .smallEnd


Scary - that .smallEnd worries me. It's like a field is being 
referenced with some magical context from nowhere.


Obviously I need to read that full proposal.

Sorry for going on about it, but this wouldn't happen in my idea. If 
field access functions are just items in a module, the . separates the 
module identification from the item name, same as always. The only 
difference is how you identify the module. There's no special 
interactions with function composition, or whatever it is that's 
happening here. If you want to composite the function with some other 
function without knowing in advance which record value you're dealing 
with, just get the access function from the record-type module.


If I'm correctly guessing what your code means, that reads as...

(f egg).yolk where f = separate . crack . (eggModule.eggType.smallEnd)

OK, in a sense specifying eggModule.eggType there is a bit redundant, 
but in general that isn't true - define f separately and it needs some 
clue for the type inference to decide where to look for smallEnd, and 
eggtype provides it. I'd prefer a notation that allows me to reference 
the field without needing type inference to determine which record type 
it relates to.


But then again, I'm probably just not understanding the reason behind 
that wierdness - perhaps it wouldn't seem so wierd if I did. Or maybe 
it's just a familiarity issue.


First thought - I've not addressed access from within a polymorphic 
function with type class constraints. The situation there would (without 
extra features) be the same as it is now, with no TDNR support. Field 
access functions would have to be provided as explicit operations within 
the type class.


That said, it shouldn't be hard to handle. For example, a type class can 
explicitly state which field names it is interested in, and an instance 
can provide functions to access those fields. Alternatively, the 
instance might support using arbitrary functions (of the right type). 
This might allow some wierdness (fields that aren't really fields), but 
it may allow some useful flexibility (this particular type provides the 
field daddy, that type provides mummy, a third type has no named 
fields but has a function that works by pattern matching that can 
provide the positionally-defined field - either way, this type class 
will refer to parent) so that polymorphic functions can use the dot 
notation, but the relationship between fields in the type class and 
fields in the instance type are flexible. It's really just syntactic 
sugar for what type classes have to do now - providing a dot notation, 
but still using vtable references to field access functions to do the work.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-29 Thread Steve Horne

On 28/01/2012 13:00, Paul R wrote:

AntC  Steve, I think that proposal has been rather superseeded by
AntC  http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields, 
which
AntC  draws on TDNR. But SORF is best seen as an evolving design space, with 
precise
AntC  details yet to be clarified/agreed. I've put my own variation into the 
ring:
AntC  http://www.haskell.org/pipermail/glasgow-haskell-users/2011-
AntC  December/021298.html -- which seems to have fallen into a black hole 
:-(

AntC  One of the aspects of TDNR that wasn't so popular was that its 
type-directed
AntC  resolution was very similar to instance resolution, but subtly and 
confusingly
AntC  different.

AntC  I guess we have to be very careful about the dot. It seems to be in a
AntC  very 'crowded' syntax space, so if we implement the wrong way, we could 
end up
AntC  shutting the door with the keys left inside.

AntC  (...)

All this dot syntax magic frankly frightens me. Haskell, as a pure
functionnal language, requires (and allows !) a programming style that
just does not mix well with object oriented practices. Stretching the
syntax to have the dot feel a-bit-but-not-really like object oriented
programming, mainly to have IDE autocompletion on some cases, does not
make much sens.
That's a benefit of my idea. Modular programming used the dot long 
before OOP became popular - OOP stole the dot from modular programming! 
If a record is a module, that only means that one thing can be both a 
module and a type (or value) at the same time. It takes little from OOP 
that OOP didn't already take from the more fundamental modular 
programming - and Haskell already has modules.



If the editor matters - and it probably does -, we could rather take
a more ambitious path, and work on a real semantic editor, as opposed to
a plain left-to-right text editor, with hacked semantic goodies to
alleviate the pain.
Every programmer has their own favorite editor, usually using the same 
one to work in many different languages. For the moment, you'd have a 
hard job separating me from Notepad++.


If you really want a semantic editor, I'd argue a rich visual language 
with a file format that isn't intended to be read directly. Something 
more like writing in Word than writing in TeX. But I don't think most 
programmers are ready for this, for various reasons. Version control 
tools and readable differences get a place near the top of that list.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-29 Thread Steve Horne

On 30/01/2012 04:23, Steve Horne wrote:

On 28/01/2012 13:00, Paul R wrote:

AntC  Steve, I think that proposal has been rather superseeded by
AntC  
http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields, 
which
AntC  draws on TDNR. But SORF is best seen as an evolving design 
space, with precise
AntC  details yet to be clarified/agreed. I've put my own variation 
into the ring:

AntC  http://www.haskell.org/pipermail/glasgow-haskell-users/2011-
AntC  December/021298.html -- which seems to have fallen into a 
black hole :-(


AntC  One of the aspects of TDNR that wasn't so popular was that its 
type-directed
AntC  resolution was very similar to instance resolution, but subtly 
and confusingly

AntC  different.

AntC  I guess we have to be very careful about the dot. It seems to 
be in a
AntC  very 'crowded' syntax space, so if we implement the wrong way, 
we could end up

AntC  shutting the door with the keys left inside.

AntC  (...)

All this dot syntax magic frankly frightens me. Haskell, as a pure
functionnal language, requires (and allows !) a programming style that
just does not mix well with object oriented practices. Stretching the
syntax to have the dot feel a-bit-but-not-really like object oriented
programming, mainly to have IDE autocompletion on some cases, does not
make much sens.
That's a benefit of my idea. Modular programming used the dot long 
before OOP became popular - OOP stole the dot from modular 
programming! If a record is a module, that only means that one thing 
can be both a module and a type (or value) at the same time. It takes 
little from OOP that OOP didn't already take from the more fundamental 
modular programming - and Haskell already has modules.



Sorry for replying to myself - I just thought I could explain this better.

I'm basically asserting that a record in standard Pascal (without any of 
that OOP Turbo Pascal 5.5+/Delphi stuff) is a module. It doesn't matter 
that the only names that can be held in that module are field names - 
it's still a container of named items and therefore a special case of a 
module.


In the Pascal case (like C structs), the content of the module doesn't 
include functions or methods or whatever, it only includes fields. And 
the module is only accessible via the record instances, not via the 
record type (there's nothing like C++ member pointers).


Converting this to Haskell - well, we already use field-access 
functions, so why not move those to the record-instance module instead 
of having them pollute some existing namespace?


Since naming the same thing twice (once to identify the module, once to 
specify the instance parameter) would be annoying, why not auto-curry 
that parameter? The result is still a function living in a module.


And rather than lose the original function, why not move that to another 
scope - a module that's associated with the record type rather than the 
record instance? If you don't specify an instance, you can't curry that 
parameter - it still makes sense.


There's no inheritance here, no virtual functions, no OOP features at 
all - just Pascal-like records adapted for immutability by supplying a 
field access function rather than e.g. a field offset. The function 
placed in the record-type module would be the exact same function we get 
now, just in a different scope.


However, once you have the idea that a record is a module, maybe it 
makes sense to put some other functions in there too? As a minimal 
solution no, but it's nice to know there's room for future expansion.


There's nothing OOP about this at all - it's really just adapting and 
extending what standard Pascal does. You could extend it to include OOP 
if you really wanted to, but the minimal solution just moves the 
existing Haskell access functions to another scope, and adds a 
pre-curried version in a further scope, associating those scopes with 
the record type and record instances respectively.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wow you have to check this out Haskell

2012-01-25 Thread Steve Horne

On 25/01/2012 16:13, R J wrote:

hello Haskell the holidays are coming up soon and I think this can help 
http://www.news13open.com

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Wow you have to check this out Haskell - appols accidental resend of this scam spam

2012-01-25 Thread Steve Horne

Lesson = don't open e-mail client while borderline asleep.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-23 Thread Steve Horne
There's a proposal at the moment to add support for TDNR to Haskell - to 
leverage the power of the dot (e.g. for intellisense).


http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution

I approve of the goal, but I'd like to suggest a different approach.

My basic idea is stolen from Bertrand Meyer (Object-Oriented Software 
Construction, second edition). Basically, a class *is* both a module and 
a type. Quote...


  Classes as modules

  Object orientation is primarily an architectural technique: its major 
effect is on the

  modular structure of software systems.

  The key role here is again played by classes. A class describes not 
just a type of

  objects but also a modular unit. In a pure object-oriented approach:

   Classes should be the only modules.

By the logic of equivalence relations, we can conclude that a type *is* 
a module. Only I'd adapt that a little. In C++, the following operators 
can all be used to access the module for some type or value...


 * ::   Scope resolution
 * .Member dereference
 * -   Member dereference via a pointer
 * .*   Member-pointer dereference
 * -*  Member-pointer dereference via a pointer

In C++, a type and an instance each have their own modules. A (smart) 
pointer has its own module, separate from the module for the type it 
points to. And member-pointers exist because sometimes there's a need to 
reference a member without knowing or (yet) caring which instance.


We already have member pointers - the functions that map an instance to 
the field value. It would make some sense if these could be placed in a 
module associated with the type (not the instance).


When an instance is created of a type, that can effectively (without 
run-time overhead) create a new module associated with the new instance. 
This will contain the same field-access functions, but with the instance 
parameter already curried in.


So there's no real need for any new meaning of the . operator - it's 
just access to names within a module. And there's no need for a new 
mechanism for accessing fields - only for a way to place them in that 
module scope, and a little sugar that gives us the same field-access 
function but with the instance parameter already curried in.


Once we have these modules containing compiler-generated field-access 
functions, though, it makes some sense to allow additional functions 
(and perhaps types) to be added within that types module explicitly by 
the programmer. It may also make sense to allow functions to be 
explicitly defined which will be added to the instance-modules and 
support the prefix-instance-parameter sugar.


Finally, as with C++, when dealing with IORef and similar, it make make 
sense to have a separate - operator (spelled differently, of course). 
Or it could use the standard dot. C++ and D disagree in this (in C++, 
the smart pointer has its own module separate from the pointed-at 
instance - in D, there is no - or equivalent).


As an aside, Ada has already gone through a related transition. The 
original Ada 83 had variant records, but no true classes. In Ada 95, 
tagged types were added which were like variant records, but which 
supported inheritance and run-time dispatch. The discriminant is 
replaced by a tag which is presumably implemented as a virtual table 
pointer. However, functions and procedures weren't members. The typical 
call of a method would be...


packagename.procedure_name ( instance_arg, other_args );

Ada 2005 added some workarounds to allow conventional OOP call notation. 
See section 1.3 of the Ada 2005 rationale for details. However, it all 
feels a bit kludgy. In particular, the procedures and functions still 
aren't members - there are just some special rules for when they can be 
used as if they were. I've not actually used Ada 2005, but I'd bet some 
confusion can result from that.


Personally, I think Meyer was at least partly right - if types (and 
instances) are modules, the kludge-factor is much lower. C++ actually 
doesn't get this quite right IMO (you can access static class members 
through the instance objects, for example, not just through the 
classes), but C++ classes *do* act mostly like modules and that is a 
very useful trait - particularly within the declarative sublanguage 
(templates etc).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monads, do and strictness

2012-01-21 Thread Steve Horne

On 21/01/2012 17:29, Victor S. Miller wrote:

The do notation translates

do {x- a;f}  into

a=(\x -  f)

However when we're working in the IO monad the semantics we want requires that 
the lambda expression be strict in its argument.  So is this a special case for 
IO?  If I wanted this behavior in other monads is there a way to specify that?

IO is a special case, but strictness isn't the issue.

The value x cannot be evaluated in concrete form (I think the technical 
term is head normal form) until the IO action a has been executed. 
However, evaluating to head normal form isn't really the key issue. The 
key issue is that the effects of the action must occur at the correct time.


This is why the internals of the IO monad are a black box (you can't 
use pattern matching to sneak a look inside a cheat the evaluation 
order) and, yes, it's why the IO monad is a bit special.


But you could still in principle use a non-strict evaluation order. It's 
a bit like evaluating (a + b) * c - you don't need to specify strict, 
lazy or whatever to know that you need to evaluate (a + b) before you 
can evaluate the (? + c), that aspect of evaluation ordering is fixed 
anyway.


In this case, it's just that instead of being able to rewrite the (\x - 
f) to (\someExpression - f), there is no expression that you can insert 
there - there is e.g. no unary operator to extract out the result of an 
action and make it available as a normal value outside the IO context. 
If there were, it could defeat the whole point of the IO monad.


Even so, to see that strictness isn't the issue, imagine that (=) were 
rewritten using a unary executeActionAndExtractResult function. You 
could easily rewrite your lamba to contain this expression in place of 
x, without actually evaluating that executeActionAndExtractResult. You'd 
still be doing a form of composition of IO actions. And when you finally 
did force the evaluation of the complete composed expression, the 
ordering of side effects would still be preserved - provided you only 
used that function as an intermediate step in implementing (=) at least.


BTW - there's a fair chance I'm still not understanding this correctly 
myself (still newbie), so wait around to see everyone explain why I'm 
insane before taking this too seriously.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monads, do and strictness

2012-01-21 Thread Steve Horne

On 21/01/2012 18:08, Steve Horne wrote:
Even so, to see that strictness isn't the issue, imagine that (=) 
were rewritten using a unary executeActionAndExtractResult function. 
You could easily rewrite your lamba to contain this expression in 
place of x, without actually evaluating that 
executeActionAndExtractResult. You'd still be doing a form of 
composition of IO actions. And when you finally did force the 
evaluation of the complete composed expression, the ordering of side 
effects would still be preserved - provided you only used that 
function as an intermediate step in implementing (=) at least.


Doh!!! - that function *does* exist and is spelled unsafePerformIO. 
But AFAIK it isn't used for compilation/interpretation of (=) operators.


If it *were* used, the rewriting would also need an extra return.

So...

  a = b - f b

becomes...

  return (f (unsafePerformIO a))


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Code generation and optimisation for compiling Haskell

2012-01-12 Thread Steve Horne

On 11/01/2012 15:20, Thomas Schilling wrote:

Based on your stated background, the best start would be the (longer)
paper on the Spineless Tagless G-machine [1].
Thanks for the tips. I haven't read much yet, but considering [1], I 
guess I shouldn't have dismissed SPJs early 90's stuff so quickly.


Should be interesting.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Code generation and optimisation for compiling Haskell

2012-01-10 Thread Steve Horne


Although I'm far from being an expert Haskell programmer, I think I'm 
ready to look into some of the details of how it's compiled. I've a copy 
of Modern Compiler Design (Grune, Bal, Jacobs and Langendoen) - I first 
learned a lot of lexical and parsing stuff from it quite a few years 
ago. Today, I started looking through the functional languages section - 
I've read it before, but never absorbed much of it.


Graph reduction, lambda lifing, etc - it seems pretty simple. Far too 
simple. It's hard to believe that decent performance is possible if all 
the work is done by a run-time graph reduction engine.


Simon Peyton Jones has written a couple of books on implementing 
functional languages which are available for free download. At a glance, 
they seem to covers similar topics in much more detail. However, they're 
from 1987 and 1992. Considering SPJs period of despair when he 
couldn't get practical performance for monadic I/O, these seem very dated.


Some time ago, I made a note to look up the book Functional Programming 
and Parallel Graph Rewriting (I forget why) but again that's from the 
early 90's. I've also got a note to look up Urban Boquists thesis.


SPJ also has some papers on compilation - 
http://research.microsoft.com/en-us/um/people/simonpj/papers/papers.html#compiler 
- and the papers on optimisation by program transformation have caught 
my eye.


Are there any current text-books that describe the techniques used by 
compilers like GHC to generate efficient code from functional languages? 
It's OK to assume some knowledge of basic compiler theory - the 
important stuff is code generation and optimisation techniques for lazy 
functional languages in particular.


Also, what papers should I read? Am I on the right lines with the ones 
I've mentioned above?



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-09 Thread Steve Horne

On 08/01/2012 20:25, Brent Yorgey wrote:

On Fri, Jan 06, 2012 at 10:51:58AM +, Steve Horne wrote:

If I specify both extensions (-XMultiParamTypeClasses and
-XFlexibleInstances) it seems to work, but needing two language
extensions is a pretty strong hint that I'm doing it the wrong way.

Not necessarily.  These two extensions in particular (and especially
the second) are quite uncontroversial.

As it turns out, I don't need extensions at all, at least for 
walkableBinTree. Two answers pointed out how to handle that. I'm not yet 
entirely sure what will happen when I start adding more typeclasses 
(searchableBinTree etc) to the family - I've been distracted.


Also - after reading those answers and trying the suggestions, I'm 
pretty sure I've done tutorials that covered this after all. I must have 
just left it too long before trying them out properly.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-09 Thread Steve Horne

On 08/01/2012 21:13, Brandon Allbery wrote:


(Also, de facto I think it's already more or less been decided in 
favor of type families, just because functional dependencies are (a) a 
bit alien [being a glob of Prolog-style logic language imported into 
the middle of System Fc] and (b) [as I understand it] difficult to 
verify that the code in the compiler is handling all the potential 
corner cases right [mainly because of (a)].


Without meaning to express an opinion either way about an issue I don't 
understand...


Isn't Haskell doing some prolog-ish things anyway?

I thought the compiler must be doing unification to resolve type 
inference within expressions. It's not a simple expression evaluation 
problem (just evaluate the type rather than the value) because sometimes 
you know the return type but not (yet) the argument types - type 
information flows bottom-up and top-down through the same expression tree.


I could easily be mistaken, though. Looking at the similar 
overload-resolution problem, Ada can resolve based on return types but 
C++ cannot. Ada needs unification or something similar to resolve 
overloading, whereas C++ just evaluates expressions for type instead of 
value.


I can't now say for sure where I picked up the idea that Haskell needs 
unification to resolve type inference, but I've had some odd error 
messages which seem to confirm that belief - I assume because the 
mistake doesn't cause an immediate conflict, instead causing an indirect 
conflict somewhere else in the larger expression.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Motivation for having indexed access in Data.Map?

2012-01-07 Thread Steve Horne

On 07/01/2012 12:17, Christoph Breitkopf wrote:

Hello,

I wonder why Data.Map provides the indexed access functions:

http://hackage.haskell.org/packages/archive/containers/latest/doc/html/Data-Map.html#g:21

These functions seem rather out-of-place to me in the map api. The 
only use case I could think of so far would be to find the median, or 
in general n-th smallest key, but that does not seem sufficient reason 
(also, I think there are faster methods for that). Anything else?


I don't know the motivation in Data.Map, but here's some thoughts from a 
C++ home-rolled data structures perspective...


Somewhere around a decade ago, I started an in-memory C++ multiway tree 
library, initially an experiment seeing if I could improve sequential 
access performance. This half-worked, but I still use the data structure 
primarily because it's a bit safer in some cases than the STL 
containers, and also has some extra functionality that makes it more 
convenient.


Features include...

1.   cursor maintenance (when I insert/delete, cursors/iterators are
   not invalidated except in the special case that the cursor
   references an item that is deleted. There are two tricks for this
   case - the cursor will at least know that the item is deleted, plus
   there are special cursors that can defer deletion (mainly for
   delete-the-current-item within loops).
2. Searching based on custom comparisons - mainly searching based on
   a partial key (certain fields), so you can find the first/last item
   equal to a partial key, ignoring less significant fields.
3. Finding the first key that is *not* in the container (for unsigned
   integer keys only).
4. Subscripted access - finding a given index, determining the index to
   an item referenced by a cursor, stepping forward/backward by a given
   number of items.

The subscripted access isn't massively useful - it was implemented 
because I was curious how to handle it efficiently. However, cases do 
come up from time to time in strange places. For example, sometimes it's 
more convenient to store an index (into a container that won't change) 
than a cursor or a full key. And using an ordered container does tend to 
imply, after all, that you're interested somehow in the order (or else 
why not use a hash table?).


One case, I guess, relates to DSL-generated data structures. The point 
there is that when the generated code runs, the map instance is long 
dead. Within the generated code, ranges etc tend to be identified by 
subscript - so the DSL needs to be able to translate from key to 
subscript, and (maybe) back again. OTOH, don't forget that laziness 
thing - if the code generator was working from a sorted array it would 
know the subscripts anyway.


A particularly surprising side-effect - along with the map, multimap, 
set and multiset wrappers, I have a vector wrapper. When you have a huge 
array and do lots of inserts and deletes within that array, a multiway 
tree (with subscripted access) turns out to be a good trade-off. Some 
accesses are more awkward (because the items aren't all contiguous in 
memory), but the log-time inserts and deletes can be worth it.


The first-key-not-in-the-container stuff was mostly a side-effect of the 
data structure augmentation I did for subscripted access. That is very 
convenient, but with costs.


The no. 1 killer feature that keeps me using and maintaining this 
library is the partial-key search thing. This is so useful, I even added 
a feature to a DSL (used mainly for AST nodes and multiple dispatch - 
originally based on treecc) to make it more convenient to generate 
partial-key classes.


The cursor maintenance makes it a lot easier to write algorithms that 
update the container, but it's perhaps surprising how rare that's necessary.


The issue with all this is of course partly overhead, but also because I 
got lazy - keeping these things hanging around throughout whole program 
runs like cheap second-rate databases. They are quite convenient to work 
with, but for a long time I stopped even considering pulling all the 
data out into a flat array, processing it there, then rebuilding a new 
indexed data structure only if I really needed it, or keeping data 
mostly in an array and sorting it ready for binary searches just at the 
key point where that's needed.


Some programs I've written using them are maybe an order of magnitude 
slower than they should be, and in quite a few cases there's an 
asymptotic difference, not just a constant factor - a lot of algorithms 
are O(n log n) where without the convenience containers they could be O(n).


Very little of this would be relevant in a pure functional programming 
world, of course, but anyway - yes, subscripting can be (occasionally) 
useful. It's just hard to give specific examples, because they're buried 
in all the technicalities of quite large programs.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

[Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-06 Thread Steve Horne


I was messing around with type-classes (familiarization exercises) when 
I hit a probably newbie problem. Reducing it to the simplest case...


module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where
  --  n : node type
  --  d : data item type wrapped in each node
  class WalkableBinTree n where
wbtChildren   :: n - Maybe (n, n)
wbtData   :: n - Maybe d

  --  Simple tree type, mostly for testing
  data BT x = Branch x (BT x) (BT x)
| Empty

  instance WalkableBinTree (BT x) where
wbtChildren (Branch d l r) = Just (l, r)
wbtChildren  Empty = Nothing

wbtData (Branch d l r) = Just d
wbtData  Empty = Nothing

Loading this code into GHCi, I get...

Prelude :load BinTree
[1 of 1] Compiling BinTree  ( BinTree.hs, interpreted )

BinTree.hs:16:39:
Couldn't match type `x' with `d'
  `x' is a rigid type variable bound by
  the instance declaration at BinTree.hs:12:32
  `d' is a rigid type variable bound by
  the type signature for wbtData :: BT x - Maybe d
  at BinTree.hs:16:5
In the first argument of `Just', namely `d'
In the expression: Just d
In an equation for `wbtData': wbtData (Branch d l r) = Just d
Failed, modules loaded: none.
Prelude

I've tried varying a number of details. Adding another parameter to the 
type-class (for the item-data type) requires an extension, and even then 
the instance is rejected because (I think) the tree-node and item-data 
types aren't independent.


In any case, I can't understand why those types can't match.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple type-class experiment turns out not so simple...

2012-01-06 Thread Steve Horne

On 06/01/2012 10:29, Steffen Schuldenzucker wrote:



On 01/06/2012 11:16 AM, Steve Horne wrote:


I was messing around with type-classes (familiarization exercises) when
I hit a probably newbie problem. Reducing it to the simplest case...

module BinTree ( WalkableBinTree, BT (Branch, Empty) ) where
-- n : node type
-- d : data item type wrapped in each node
class WalkableBinTree n where
wbtChildren :: n - Maybe (n, n)
wbtData :: n - Maybe d


With 'd' not being mentioned anywhere, the signature of wbtData means 
forall d. n - Maybe d. In particular, wbtData == const Nothing.


I'm not sure what to make of that. Even if the result of wbtData is 
always Nothing, surely it still has a static type?




I've tried varying a number of details. Adding another parameter to the
type-class (for the item-data type) requires an extension, and even then
the instance is rejected because (I think) the tree-node and item-data
types aren't independent.


Did you try something like

 {-# LANGUAGE MultiParamTypeClasses #-}
 class WalkableBinTree n d where
   ... (same code as above, but 'd' is bound now)
 ...
 instance WalkableBinTree (BT x) x where
   ...



Precisely that. In that case, I get...

C:\_SVN\dev_trunk\haskell\examplesghci -XMultiParamTypeClasses
GHCi, version 7.0.4: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Loading package ffi-1.0 ... linking ... done.
Prelude :load BinTree
[1 of 1] Compiling BinTree  ( BinTree.hs, interpreted )

BinTree.hs:12:12:
Illegal instance declaration for `WalkableBinTree (BT x) x'
  (All instance types must be of the form (T a1 ... an)
   where a1 ... an are *distinct type variables*,
   and each type variable appears at most once in the instance head.
   Use -XFlexibleInstances if you want to disable this.)
In the instance declaration for `WalkableBinTree (BT x) x'
Failed, modules loaded: none.
Prelude

If I specify both extensions (-XMultiParamTypeClasses and 
-XFlexibleInstances) it seems to work, but needing two language 
extensions is a pretty strong hint that I'm doing it the wrong way.


The goal is fairly obvious - to have type-classes for binary tree 
capabilities so that different implementations can support different 
subsets of those capabilities. Being able to walk a binary tree doesn't 
need ordering of keys, whereas searching does. A red-black tree needs 
somewhere to store it's colour in the node, yet the walking and 
searching functions don't need to know about that.


As far as I remember, none of the tutorials I've read have done this 
kind of thing - but it seemed an obvious thing to do. Obviously in the 
real world I should just use library containers, but this is about 
learning Haskell better in case a similar problem arises that isn't 
about binary trees.


How should I be handling this?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-06 Thread Steve Horne

On 06/01/2012 10:39, Jon Fairbairn wrote:
groupBy is currently implemented using span. It strikes me that we 
ought to specify some properties for what we want. Start by defining: 
pairwiseInOrderBy p l = all (uncurry p) (l `zip` drop 1 l) giving all 
(pairwiseInOrderBy p) (groupCut p l) and we would want concat 
(groupCut p l) == l (all modulo nontermination side conditions). 
Anything else? 
To be honest, I've worked out what's going on in this case and I have an 
implementation or two of what I'd want in case I need it, plus I've 
posted it in case it was useful to the OP. There's nothing I really want 
to persue any further.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-05 Thread Steve Horne

On 05/01/2012 10:02, Jon Fairbairn wrote:

Steve Hornesh006d3...@blueyonder.co.uk  writes:


Personally, I think this is a tad disappointing. Given that
groupBy cannot check or enforce that it's test respects
equivalence classes, it should ideally give results that
make as much sense as possible either way. That said, even
if the test was always given adjacent elements, there's
still room for a different order of processing the list
(left-to-right or right-to-left) to give different results -
and in any case, maybe it's more efficient the way it is.

Looking back at the libraries list, I get the impression that
there was a suggestion to change the behaviour of groupBy, but
it doesn’t seem to have happened.


I've realised that the left-to-right vs. right-to-left order thing makes 
no difference - I don't know why I thought that now.


I've written an implementation, only the predicate is inverse-logic - 
True means cut-between-these rather than keep-these-together.


I keep thinking there should be a tail-recursive implementation, but the 
usual trick would either mean using ++ or difference lists or similar, 
or would deliver the results in reverse order. If anyone can think of a 
way to get the correct result in one pass through the list (assuming 
tail recursion is optimised), I'm curious.


Or... does non-strict evaluation mean I shouldn't worry about it? Maybe 
it does a good job of evaluating the head quickly anyway, as the data 
dependencies are quite localized? I've been wondering how lazy 
evaluation interacts with recursion over lists in performance terms for 
a while.


  --  groupCut - Similar to groupBy, but where groupBy assumes an 
equivalence relation,
  --  groupCut takes a function that indicates where to cut. The two 
parameters to this
  --  function are always adjacent items from the list, and if the 
function returns True,

  --  a cut is done between the two items.

  groupCut :: (x - x - Bool) - [x] - [[x]]

  groupCut f [] = []
  groupCut f xs = let (y,ys,yss) = groupCut' f xs in  (y:ys):yss

  --  arg1   - cut here test function
  --  arg2   - input list
  --  result - triple of current (head char, head group excl. head 
char, tail groups)

  --
  --  the input list must not be empty - this is handled in the 
front-end function.

  groupCut' :: (x - x - Bool) - [x] - (x, [x], [[x]])

  groupCut' f (x:[]) = (x, [], [])

  groupCut' f (x:xs) = let (y,ys,yss) = groupCut' f xs
   in  if (f x y) then (x,   [], (y:ys):yss)
  else (x, y:ys,yss)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-05 Thread Steve Horne

On 05/01/2012 11:09, Brandon Allbery wrote:
On Thu, Jan 5, 2012 at 05:57, Steve Horne sh006d3...@blueyonder.co.uk 
mailto:sh006d3...@blueyonder.co.uk wrote:


 --  groupCut - Similar to groupBy, but where groupBy assumes an
equivalence relation,
 --  groupCut takes a function that indicates where to cut. The
two parameters to this
 --  function are always adjacent items from the list, and if the
function returns True,
 --  a cut is done between the two items.


span/break?


Using those, the test function won't always be passed two *adjacent* 
elements from the list. After all, they're based on takeWhile and 
dropWhile, which take unary functions, meaning an element has already 
been curried in (the starting element of the group).


That's probably how the current groupBy is implemented - the approach 
that assumes an equivalence relation, giving unexpected results when the 
By function isn't an equivalence relation.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-05 Thread Steve Horne

On 05/01/2012 11:55, Christian Maeder wrote:

Am 05.01.2012 11:57, schrieb Steve Horne:
[...]

groupCut :: (x - x - Bool) - [x] - [[x]]

[...]

How about a break function that respects an escape character (1. arg) 
(and drops the delimiter - 2. arg) and use this function for unfolding?

Interesting.

I was going to accuse you of cheating - who says there's a spare value 
to use? - but you seem to be using Maybe, so well played.


You're also using unfoldr, which I really must play with a bit - I don't 
really have a feel for how unfolding works ATM.


Thanks.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-04 Thread Steve Horne

On 02/01/2012 11:12, Jon Fairbairn wrote:

maxm...@mtw.ru  writes:


I want to write a function whose behavior is as follows:

foo string1\nstring2\r\nstring3\nstring4 = [string1,
string2\r\nstring3, string4]

Note the sequence \r\n, which is ignored. How can I do this?

cabal install split

then do something like

import Data.List (groupBy)
import Data.List.Split (splitOn)

rn '\r' '\n' = True
rn _ _ = False

required_function = fmap concat . splitOn [\n] . groupBy rn

(though that might be an abuse of groupBy)

Sadly, it turns out that not only is this an abuse of groupBy, but it 
has (I think) a subtle bug as a result.


I was inspired by this to try some other groupBy stuff, and it didn't 
work. After scratching my head a bit, I tried the following...


Prelude import Data.List
Prelude Data.List groupBy () [1,2,3,2,1,2,3,2,1]
[[1,2,3,2],[1,2,3,2],[1]]

That wasn't exactly the result I was expecting :-(

Explanation (best guess) - the function passed to groupBy, according to 
the docs, is meant to test whether two values are 'equal'. I'm guessing 
the assumption is that the function will effectively treat values as 
belonging to equivalence classes. That implies some rules such as...


  (a == a)
  reflexivity : (a == b) = (b == a)
  transitivity : (a == b)  (b == c) = (a == c)

I'm not quite certain I got those names right, and I can't remember the 
name of the first rule at all, sorry.


The third rule is probably to blame here. By the rules, groupBy doesn't 
need to compare adjacent items. When it starts a new group, it seems to 
always use the first item in that new group until it finds a mismatch. 
In my test, that means it's always comparing with 1 - the second 2 is 
included in each group because although (3  2) is False, groupBy isn't 
testing that - it's testing (1  2).


In the context of this \r\n test function, this behaviour will I guess 
result in \r\n\n being combined into one group. The second \n will 
therefore not be seen as a valid splitting point.



Personally, I think this is a tad disappointing. Given that groupBy 
cannot check or enforce that it's test respects equivalence classes, it 
should ideally give results that make as much sense as possible either 
way. That said, even if the test was always given adjacent elements, 
there's still room for a different order of processing the list 
(left-to-right or right-to-left) to give different results - and in any 
case, maybe it's more efficient the way it is.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-04 Thread Steve Horne

On 04/01/2012 16:47, Steve Horne wrote:


  (a == a)
  reflexivity : (a == b) = (b == a)
  transitivity : (a == b)  (b == c) = (a == c)


Oops - that's...

reflexivity :  (a == a)
symmetry : (a == b) = (b == a)
transitivity : (a == b)  (b == c) = (a == c)

An equivalence relation is a relation that meets all these conditions.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Grok Monad Transformers - some help needed

2012-01-02 Thread Steve Horne

On 02/01/2012 06:12, Arseniy Alekseyev wrote:

  I don't know what to actually do with this after putting it in a *.lhs file.

You can :load *.lhs into ghci the same way you load .hs-files.

I swear I tried this before, but now it suddenly works.

Must be the chaos of stupid random assumptions making me do stupid 
things - I go through this phase with anything new. I have no idea what 
I was doing to screw things up, but I'm pretty there's no conspiracy to 
drive me nuts. Though now I think of it... hmmm... I wonder...


The errors I was getting from GHC mostly referred to the monomorphism 
restriction - at least for test1 and test2. The errors for test3 were 
much longer and scarier.


I'll try to figure out what's different going from GHC to GHCi later - 
for the moment, I'm getting back to those transformers.


BTW - interesting how the signatures of test1 and test2 are reported - I 
hadn't realised monad transformers were relevant there. Of course it 
does seem a bit silly to implement both StateT and State when StateT can 
implement State for you.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to split this string.

2012-01-02 Thread Steve Horne

On 02/01/2012 09:44, max wrote:

I want to write a function whose behavior is as follows:

foo string1\nstring2\r\nstring3\nstring4 = [string1,
string2\r\nstring3, string4]

Note the sequence \r\n, which is ignored. How can I do this?
Doing it probably the hard way (and getting it wrong) looks like the 
following...


--  Function to accept (normally) a single character. Special-cases
--  \r\n. Refuses to accept \n. Result is either an empty list, or
--  an (accepted, remaining) pair.
parseTok :: String - [(String, String)]

parseTok  = []
parseTok (c1:c2:cs) | ((c1 == '\r')  (c2 == '\n')) = [(c1:c2:[], cs)]
parseTok (c:cs) | (c /= '\n')= [(c:[], cs)]
| True   = []

--  Accept a sequence of those (mostly single) characters
parseItem :: String - [(String, String)]

parseItem  = [(,)]
parseItem cs = [(j1s ++ j2s, k2s)
 | (j1s,k1s) - parseTok  cs
 , (j2s,k2s) - parseItem k1s
   ]

--  Accept a whole list of strings
parseAll :: String - [([String], String)]

parseAll [] = [([],)]
parseAll cs = [(j1s:j2s,k2s)
| (j1s,k1s) - parseItem cs
, (j2s,k2s) - parseAll  k1s
  ]

--  Get the first valid result, which should have consumed the
--  whole string but this isn't checked. No check for existence either.
parse :: String - [String]
parse cs = fst (head (parseAll cs))

I got it wrong in that this never consumes the \n between items, so 
it'll all go horribly wrong. There's a good chance there's a typo or two 
as well. The basic idea should be clear, though - maybe I should fix it 
but I've got some other things to do at the moment. Think of the \n as a 
separator, or as a prefix to every item but the first. Alternatively, 
treat it as a prefix to *every* item, and artificially add an initial 
one to the string in the top-level parse function. The use tail etc to 
remove that from the first item.


See http://channel9.msdn.com/Tags/haskell - there's a series of 13 
videos by Dr. Erik Meijer. The eighth in the series covers this basic 
technique - it calls them monadic and uses the do notation and that 
confused me slightly at first, it's the *list* type which is monadic in 
this case and (as you can see) I prefer to use list comprehensions 
rather than do notation.


There may be a simpler way, though - there's still a fair bit of Haskell 
and its ecosystem I need to figure out. There's a tool called alex, for 
instance, but I've not used it.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2012-01-02 Thread Steve Horne

On 02/01/2012 10:03, Jerzy Karczmarczuk wrote:
But I disagree quite strongly with the idea of /World parameter as 
purely hypothetical, a trick used to gain an intuition/. I mentioned 
the language Clean (no reaction, seems that Haskellians continue to 
ignore it...)



I don't know about others, but I intend to learn one language at a time.

In any case, that's Clean, not Haskell.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2012-01-01 Thread Steve Horne

On 01/01/2012 22:57, Jerzy Karczmarczuk wrote:

Dan Doel :
...

Also, the embedded IO language does not have this property.

 do x- m ; f x x

is different from

 do x- m ; y- m ; f x y

and so on. This is why you shouldn't write your whole program with IO
functions; it lacks nice properties for working with your code.

Sorry, what are you trying to suggest?

You show two OBVIOUSLY different pieces of code, and you say that they
are different.
If, by chance, some newbie reads that and gets the impression that
(-) is something equivalent to (=), you are serving the devil.


Speaking as the devil...

The do-notation sugar may confuse the issue - the - looks like an 
operator, but translating to binds-and-lambdas form suggests otherwise. 
Quick translations (I hope no mistakes) with lots of parens...


  m = (\x - (f x x))

  m = (\x - (m = (\y - (f x y

At first sight, these two expressions can give different results for 
reasons other than evaluation order. In particular, there are two bind 
operators, not just one.


That is, x and y could get different values for reasons other than the 
two m references referring to different things. So... is that true?


Of course even the bind operator arguably isn't primitive. We could 
translate to get rid of those too, and see what lies underneath. This is 
where we start seeing functions of type...


  World - (x, World)

Problem - this level of abstraction is hypothetical. It is not part of 
the Haskell language. Haskell specifically defines the IO monad to be a 
black box.


I look at this World parameter as purely hypothetical, a trick used to 
gain an intuition. Whereas Jerzy (I think) uses it to claim Haskell is 
referentially transparent - those differing x and y values come from 
different worlds, or different world-states. I'm not entirely sure, 
though, as we got sidetracked.


If main returns a function of type World - (x, World) wrapped in a 
monad context, then there is referential transparency as defined in 
computer science. But is that a fair claim?


In this model, Haskell is an interpreted language for compositing 
functions. We can call those functions programs. The executable is a 
translation of the function returned by main, but *not* a translation of 
the source code.


But GHC is called a compiler, and compilation is usually considered a 
kind of translation - the executable is a translation of the source 
code. GHCi is an interpreter, but it doesn't stop at returning a 
function of type World - (x, World) - it does the I/O. And the reason 
we use these terms is because, as programmers, we think of the 
executable as the program - as a translation of the source code.


So what main returns - that hypothetical function World - (x, World) - 
isn't just a product of the program, it's also a representation of the 
program.


I've made similar points before, but how do they work out this time...

So...

  when   evaluate what effects  referentially 
transparent
  -    --- 
-

  compile-time   main  no   yes
  run-time   main someParticularWorld  yes  yes(?)

I've proved effects at run-time, but in this model, the intermediate and 
final world-states are products of the evaluation of that main 
someParticularWorld expression. Even the results extracted from input 
actions are referentially transparent - or if not, we're dealing with 
the philosophy of determinism.


It's probable that Jerzy told me this earlier and I wasn't ready to hear 
it then.


However - we can say basically the same things about C. The World 
parameter is implicit in C but then it's implicit in Haskell too. 
Everything inside the IO monad black box is outside the scope of the 
Haskell language except in that semantics are defined for the primitive 
IO actions - basically what happens when a result is extracted out as 
part of evaluating a bind. That (?) in the yes(?) is because this is 
all contingent on that hypothetical World - (x, World) function hidden 
inside the IO monad context, which is not specified in the Haskell language.


When I say that Haskell lacks referential transparency because the 
execution of primitive IO actions is tied to the evaluation of the bind 
operators that extract out their results, and different executions of 
the same action yield different results, I'm only appealing to the 
defined semantics of the Haskell language. I'm not appealing to a 
hypothetical model where the world is passed as a parameter.


OTOH, this World - (x, World) model is much more appealing than my 
partially-evaluated-functions-as-AST-nodes model.


So - the issue seems to be whether the IO monad is a context holding 
world-manipulating functions, or whether it's a black box with semantics 
specified at the bind level. And if referential transparency is decided 
at this level, what practical relevance does it have?


It's probably better to 

[Haskell-cafe] Grok Monad Transformers - some help needed

2012-01-01 Thread Steve Horne
I'm having another go at figuring out Monad Transformers, starting at 
the same point I've started and stopped the last couple of times. That's 
this tutorial...


http://blog.sigfpe.com/2006/05/grok-haskell-monad-transformers.html

Onion layers, lift etc - I get that. But I've never actually got 
anything to work - and therefore never built the confidence to move on.


Problem 1 - this is literate Haskell. I've tried feeding it to haddock - 
all I get is an error about it lacking a main. I don't know what to 
actually do with this after putting it in a *.lhs file.


No big deal, but...

Problem 2 - even cutting the code out, shoving it in a *.hs file, and 
:loading it into GHCi, I still get a lot of errors.


For the functions test1 and test2, the fixes were explicit type 
signatures. Easy enough to figure out...


  test1 :: State Int (Int, Int)
  test2 :: State String (String, String)

I guess the basic issue is the same with test3 (and though I haven't 
tried the others today, probably test5 and test7 too). The trouble there 
is that I don't know what those type signatures should be because I 
don't know that much about monad transformers and how they can work. I 
can see what's going on in the body of test3, but that is a very small 
amount of understanding - the type signatures are important. And I can't 
use :type because GHCi is rejecting the code.



In short... HELP!!!


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Are all monads functions?

2011-12-31 Thread Steve Horne

On 31/12/2011 13:18, Yves Parès wrote:
But still, I maintain my previous view. I could clarify that by saying 
that (e.g. for Maybe) we could separate it in two types, Maybe itself 
and its monad:


-- The plain Maybe type
data Maybe a = Just a | Nothing

-- The MaybeMonad
newtype MaybeMonad a = MM ( () - Maybe a )

You've just reminded me of a painful time - lot's a scratching my head 
and saying but these parser functions are monadic - the tutorial 
clearly says they're monadic - why does my every attempt at making the 
type an instance of Monad fail?


Answer - I only had the equivalent of the Maybe type, and I was trying 
to force it where the MaybeMonad should go.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Steve Horne

On 30/12/2011 10:41, Bardur Arantsson wrote:


This doesn't sound right to me. To me, a side effect is something 
which happens as a (intended or unintended) consequence of something 
else. An effect which you want to happen (e.g. by calling a procedure, 
or letting the GHC runtime interpreting an IO Int) is just an effect.


Trouble is, whether it sounds right doesn't really matter - that's just 
an artifact of the meaning you're most familiar with. Any specialist 
field has it's own jargon, including old words given new 
related-but-different meanings.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Steve Horne

On 30/12/2011 15:23, Gregg Reynolds wrote:

Now one way of understanding all this is to say that it implicates the 
static/dynamic (compile-time/run-time) distinction: you don't know what e.g. IO 
values are until runtime, so this distinction is critical to distinguishing 
between pure and impure.  I gather this is your view.

Yes.

I think that is reasonable, but with the caveat that it must be at the right 
level of abstraction.  I don't think ASTs etc. enter into it - those are 
implementation techniques, and the only generalization we can apply to 
compilers is that they do implement the language definition, not how they do it 
(not all C compilers use ASTs).
I would argue that AST is more an analogy than an implementation - I 
don't really care if a person dry-runs the code by reading and rewriting 
fragments of the source code in notepad - there is still something that 
represents an unevaluated function but which is itself being treated as 
a value - the fallback result in this model.


A possible way to implement a Haskell program would be...

1. Apply rewrite rules to evaluate everything possible without
   executing primitive IO actions.
2. Wait until you need to run the program.
3. Continue applying rewrite rules to evaluate everything possible, but
   this time executing primitive IO actions (and substituting run-time
   inputs into the model) as and when necessary so that the rewriting
   can eliminate them.

The model correctly describes how the program should behave. It requires 
no metaphors, only a very careful person to do the re-writing and 
(unavoidably) to execute the primitive IO actions.

   The right level of abstraction (IMHO) is the distinction between atemporality and 
temporality.  The functional stuff is atemporal, which means among other things that 
evaluation is unordered (evaluation being a temporal process).  Adding IO etc. 
capabilities to the purely functional fragment of a language infects it with temporality. 
 But we can model temporality using order, so we can dispense with the notion of run-time 
and say that IO etc. stuff adds an ordered fragment to the unordered fragment.  One goal 
of the language is then to enforce a strict correspondence between the order of events 
outside the program (e.g. keystrokes) and events inside the program (getchar).

Nice way to put it.

The beauty of the monad solution is not that it magically transforms 
non-functional stuff like IO into functional stuff, but that it exploits type 
discipline to make such operations *mimic* purely functional stuff in a sense - 
but only at the level of typing.  Impure operations then have purely functional 
type discipline while remaining essentially non-functional.  So I think of 
Haskell as a quasi-pure or hybrid language.  C on the other hand is totally 
impure (except for predefined constants like '1').  For totally pure languages 
you have to look elsewhere, e.g. logics - there are no pure programming 
languages.
Well - on C is impure, it depends how you look at that. If it's valid to 
say that your home-grown while loop is a function that accepts two 
actions as parameters, well, C has an equivalent function built into the 
compiler. Again you can separate the pure from the impure, and the 
impurity is only realized when the program is executed. The 
correspondence between orderings arises in different ways, but even C 
only demands that results are as if the standards-defined evaluation 
order were followed - partial-evaluation and other optimisations during 
compilation are done in whatever order the C compiler finds convenient, 
exploiting associativity and commutativity where those are guaranteed etc.


It doesn't make Haskell and C the same thing, of course.

It's fairly easy to grasp the point by going back to Turing's original insight. 
 The cornerstone of his ideas was not the machine but the human calculator 
working with pencil and paper, finite memory, etc.  So to see the diff all you 
have to do is think about what a human does with a problem (program) written on 
paper.  Give the human calculator a computable task - add 2+2 - and you can be 
confident you will receive a definite answer in a finite amount of time.  Lard 
this with a non-computable step - add 2 + 2 + getInt - and all bets are off.
Precisely my point with my bind example - in the expression 
getAnIntFromTheUser = \i - return (i+1) you cannot know the value 
of i at compile-time, or within the realm of the atemporal. But even if 
at one level you consider that expression still to be evaluated within 
the atemporal realm, it is still evaluated also (in 
translated/rewritten/whatever form) in the temporal realm - at run-time. 
If the user happens to enter the value 1, at some point, the expression 
i+1 is conceptually rewritten to 1+1 and then to 2.


Arguably everything that can be evaluated at compile-time - everything 
in the atemporal realm - is just optimisation. That's a narrow view, and 
not one that I (now) 

Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Steve Horne

On 30/12/2011 15:50, Gregg Reynolds wrote:

On Dec 30, 2011, at 10:34 AM, Artyom Kazak wrote:


Gregg Reynoldsd...@mobileink.com  писал(а) в своём письме Fri, 30 Dec 2011 
17:23:20 +0200:


Regarding side-effects, they can be (informally) defined pretty simply:  any 
non-computational effect caused by a computation is a side-effect.

I wonder: can writing to memory be called a “computational effect”? If yes, 
then every computation is impure. If no, then what’s the difference between 
memory and hard drive?


Great question!  It suggests that the line between computation and its side 
effects is not as clear-cut as we (well, I) thought.
It relates to that while loop thing in my last reply to you, I think - 
the computational effect dressed up as non-computational.


We can do some work in Haskell using a temporary file on disk as a 
pragmatic solution to a space issue. We can feed that composed IO action 
to unsafePerformIO without breaking referential transparency, at least 
if we choose to ignore issues like running out of disk space (we ignore 
similar memory issues all the time).


And really, it's just explicit virtual memory - it's implicitly 
happening in the background anyway.


Or - it's layers of abstraction. The implementation of a function that 
uses explicit virtual memory is impure, but the abstraction it provides 
is pure. At least in principle (hand-waving away possible disk errors 
etc), the abstraction doesn't leak impurity.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Steve Horne

On 30/12/2011 10:47, Bardur Arantsson wrote:

On 12/29/2011 11:06 PM, Steve Horne wrote:

Using similar mixed definitions to conclude that every C program is full
of bugs (basically equating intentional effects with side-effects, then
equating side-effects with unintentional bugs) is a fairly common thing
in my experience, but it's a logical fallacy. If you aren't aware of the
two definitions of side-effect, it's hard to get deal with that.

Some people don't want anyone to figure out the fallacy - they like
having this convenient way to attack C, irrespective of whether it's
valid or not. Rare I think - mostly it's more confusion and memetics.
But still, I'm convinced there's some sophistry in this. And I'm not the
only person to think so, and to have reacted against that in the past.

Extra sad - you don't need that fallacy to attack C. It's redundant. C
is quite happy to demonstrate its many failings.


That's the flimsiest straw man I've ever seen.

Calling it a straw man won't convince anyone who has the scars from 
being attacked by those straw men.


I've been in those arguments, being told that C has side-effects 
therefore all C programs are full of bugs, whereas Haskell can't have 
similar bugs because it doesn't have side-effects.


I'm really not interested in whose-side-are-you-on arguments. Trying to 
keep the two definitions separate is relevant, and that was my 
motivation for saying this - it's a fact that if you mix your 
definitions up enough you can prove anything.


I like C++. I recognise the flaws in C++, as every everyday-user of the 
language must. Pretending they don't exist doesn't solve the issues - 
it's for OTT advocates, not developers. I don't insist that every 
virtuous-sounding term must apply to C++. I don't pretend every C++ 
advocate is an angel.


I like Haskell. I can't claim to be an everyday user, but I'm learning 
more and using it more all the time. I'm still uncertain whether some 
flaws I see are real - some that I used to see weren't - but I'll 
address that over time by thinking and debating. I won't pretend every 
Haskell advocate is an angel.


I've already confessed to being in the anti-Haskell role in arguments 
where the points I, ahem, emphatically made were (I now recognise) 
fallacious. So I won't even pretend I'm an angel.


If someone who was on the other side in one of my rants makes this same 
keep-your-definitions-straight point while acting as a C advocate, is 
that also a straw-man?



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-30 Thread Steve Horne

On 30/12/2011 20:38, Scott Turner wrote:

On 2011-12-30 14:32, Steve Horne wrote:

A possible way to implement a Haskell program would be...

  1. Apply rewrite rules to evaluate everything possible without
 executing primitive IO actions.
  2. Wait until you need to run the program.
  3. Continue applying rewrite rules to evaluate everything possible, but
 this time executing primitive IO actions (and substituting run-time
 inputs into the model) as and when necessary so that the rewriting
 can eliminate them.

This is inadequate, because it is does not specify when the program's
various IO actions are executed, or even which of them are executed.
Yes it does. Specifying when all the various IO actions are executed 
relative to each other is what the IO *monad* is for.


IIRC, there is a little hand-waving that SPJ confesses to about that - 
basically that each term will only be reduced once.

  Try
 print first `seq` print second
or
 let x = print x in print value
Also, evaluate everything possible is strangely hard to match up with
the concepts involved in Haskell's non-strict evaluation.
I didn't say what order to evaluate it in. For example, in this 
expression...


  let a = (2*2) in (a+a)

One valid next evaluation (rewriting) set would give...

  (2*2)+(2*2)

Another would give...

  let a = 4 in (a+a)

I don't care which you choose. I don't demand that only concrete 
arithmetic steps count. I don't demand that evaluation must be bottom-up 
or top-down or left-to-right. Only that as many evaluation steps as 
possible are applied.


The hand-waving there - the infinity issue. For a lazy list, we need a 
very careful definition of possible. That's one reason why even lazy 
evaluation implies at least a particular preferred evaluation order - 
just not the same order as for strict evaluation.


Anyway, you cannot use rewriting to extract a result out of a primitive 
IO action without executing the IO action. Even if every IO action was 
of type IO () this still applies by the rules of the Haskell language - 
you cannot extract that () out of a (putStrLn Hello) until you execute 
that action.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 08:48, Heinrich Apfelmus wrote:

Steve Horne wrote:

Heinrich Apfelmus wrote:


Purity has nothing to do with the question of whether you can 
express IO in Haskell or not.





The beauty of the IO monad is that it doesn't change anything about 
purity. Applying the function


   bar :: Int - IO Int

to the value 2 will always give the same result:

Yes - AT COMPILE TIME by the principle of referential transparency it 
always returns the same action. However, the whole point of that 
action is that it might potentially be executed (with potentially 
side-effecting results) at run-time. Pure at compile-time, impure at 
run-time. What is only modeled at compile-time is realized at 
run-time, side-effects included.


Well, it's a matter of terminology: impure /= has side effects. 
The ability of a language to describe side effects is not tied to its 
(im)purity.


Again, purity refers to the semantics of functions (at run-time): 
given the same argument, will a function always return the same 
result? The answer to this question solely decides whether the 
language is pure or impure. Note that this depends on the meaning of 
function within that language. In C, side-effects are part of the 
semantics of functions, so it's an impure language. In Haskell, on the 
other hand, functions will always return the same result, so the 
language is pure. You could say that side effects have been moved from 
functions to some other type (namely IO) in Haskell.


WRT the IO monad, has side effects is shorthand for potentially has 
side effects, and potentially is sensitive to side-effects. Both are 
equally true - as soon as you opt to allow side-effects you also opt to 
allow sensitivity to side-effects, at least as far as the type system is 
concerned. For example an IORef - you can mutate the variable it 
references, and whenever you dereference it the result depends on 
whatever past mutations have occurred while the program was running.


In a way, it's a shame - it might be interesting to separate causing and 
reacting to side-effects in the type system (while allowing both to be 
sequenced relative to each other of course - having I action and O 
action both subtypes of IO action perhaps). It could be a useful 
distinction to make in some cases in a 
preventing-classes-of-bugs-through-typechecking kind of way. The const 
keyword in C++ might be a relevant analogy - disallowing locally-caused 
mutation of an IORef while allowing sensitivity to mutations caused 
elsewhere.


Anyway, if you're using IO actions, your code is not referentially 
transparent and is therefore impure - by your own definition of 
impure. Causing side-effects may not be pedantically the issue, but 
the mix of causing and reacting to them - ie interacting with the 
outside - clearly means that some of your function results are 
dependent on what's happening outside your program. That includes 
side-effects outside your program yet caused by program program.


Again, this is nothing new - it's clear from SPJs Tackling the Awkward 
Squad that this is what the IO monad is meant for, and if it's evil 
then at least it's controlled evil.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 18:04, Donn Cave wrote:

Quoth Steve Hornesh006d3...@blueyonder.co.uk,
...

Anyway, if you're using IO actions, your code is not referentially
transparent and is therefore impure - by your own definition of
impure. Causing side-effects may not be pedantically the issue, but
the mix of causing and reacting to them - ie interacting with the
outside - clearly means that some of your function results are
dependent on what's happening outside your program. That includes
side-effects outside your program yet caused by program program.

No, code can be referential transparent and pure and at the same time
use IO actions.  In order to understand that, you need to untangle the
notion you describe above as function result from Haskell function
value.  We can talk endlessly about what your external/execution results
might be for some IO action, but at the formulaic level of a Haskell
program it's a simple function value, e.g., IO Int.
To me, that only makes sense if you never run the compiled program - if 
the executable file is just an interesting artifact that you generated 
using a Haskell interpreter.


In reality, the behaviour of IO actions is part of Haskell. The precise 
meaning of primitive Haskell IO actions is defined. The effects of 
compositing to build larger IO actions is defined. The Haskell language 
and compiler take responsibility for meaning of IO actions. The effect 
of executing those actions, including the returned values, is absolutely 
relevant to the behaviour of the program.


You can make the argument that the world is a parameter. Well - in C, 
the world can be considered an implicit parameter. In any case, this 
only gives referential transparency by what I'd call deceptive 
definition. Only a tiny piece of the world is relevant to your 
program. You've buried the relevant in a mass of the irrelevant, very 
much like a less-than-transparent politician. Your interaction is no 
more or less likely to have bugs depending on whether you define this as 
transparent or not - arguing about the definition is besides the point.


If a program that causes and is sensitive to side-effects - that 
interacts with the outside world - is referentially transparent, then 
referential transparency has no relevant meaning.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 18:41, Chris Smith wrote:

Entering tutorial mode here...

On Thu, 2011-12-29 at 10:04 -0800, Donn Cave wrote:

We can talk endlessly about what your external/execution results
might be for some IO action, but at the formulaic level of a Haskell
program it's a simple function value, e.g., IO Int.

Not to nitpick, but I'm unsure what you might mean by function value
there.  An (IO Int) is not a function value: there is no function
involved at all.  I think the word function is causing some confusion,
so I'll avoid calling things functions when they aren't.

Except that it *is* a function value.

Basically, a data constructor is a self-referencing function. Just 1 
is a function that returns Just 1 for instance. According to WinGHCI...


   Prelude :type Just
   Just :: a - Maybe a
   Prelude

The IO monad is a black box - we can't see the data constructors - but 
in principle it's the same thing.


The value extracted out of the IO action when it is executed is a 
different thing, of course.

These are PURE values... they do NOT have side effects.  Perhaps they
describe side effects in a sense, but that's a matter of how you
interpret them; it doesn't change the fact that they play the role of
ordinary values in Haskell.  There are no special evaluation rules for
them.
The semantics of the execution of primitive IO actions are part of the 
Haskell language. The execution isn't pure functional. At compile-time 
there is no means to evaluate the key functions at all - no way to 
extract the result out of an IO action because the action cannot be 
executed and so doesn't (yet) have a result. At run-time, that 
restriction is removed, or the special evaluation rules are added in - 
either claim is fine but the effect that Haskell is doing something it 
couldn't do at compile-time.


Yes, *Haskell* is doing it - it's still a part of what the Haskell 
language defines.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 19:21, Heinrich Apfelmus wrote:


Why would  IO Int  be something special or mysterious? It's an 
ordinary value like everything else; it's on the same footing as 
[Char], Maybe Int, Int - String, Bool, and so on. I see no difference 
between the list  [1,2,3] :: [Int]  and the action  pick a random 
number between 1 and 6 :: IO Int  .


Because performing the action (as part of extracting the result out of 
it) is relevant to the semantics of the language too, whether an IO 
monadic random generator or an an interaction with the user via a GUI or 
whatever.


BTW - why use an IO action for random number generation? There's a 
perfectly good pure generator. It's probably handy to treat it 
monadically to sequence the generator state/seed/whatever but random 
number generation can be completely pure.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 10:05, Jerzy Karczmarczuk wrote:

Sorry, a long and pseudo-philosophical treatise. Trash it before reading.

Heinrich Apfelmus:
You could say that side effects have been moved from functions to 
some other type (namely IO) in Haskell. 
I have no reason to be categorical, but I believe that calling the 
interaction of a Haskell programme with the World - a side effect is 
sinful, and it is a source of semantical trouble.


People do it, SPJ (cited by S. Horne) did it as well, and this is too 
bad.
People, when you eat a sandwich: are you doing side effects??  If 
you break a tooth on it, this IS a side effect, but neither the eating 
nor digesting it, seems to be one.


By definition, an intentional effect is a side-effect. To me, it's by 
deceptive redefinition - and a lot of arguments rely on mixing 
definitions - but nonetheless the jargon meaning is correct within 
programming and has been for decades. It's not going to go away.


Basically, the jargon definition was coined by one of the pioneers of 
function programming - he recognised a problem and needed a simple way 
to describe it, but in some ways the choice of word is unfortunate.


The important thing is to make sure that the explanations you trust 
aren't based on mixing of the jargon and everyday meanings of 
side-effect. In part that's what my original e-mail is about - 
accepting the definitions of side-effect and referential transparency 
that are standard within functional programming, eliminating the common 
non-sequiturs and seeing if functional programming really does still 
make sense at the end.


What would have surprised me when I started this unintentional journey 
(each step basically being a rant at one functional programming advocate 
or another) is that actually functional programming in Haskell really 
does make sense.


This term should be used in a way compatible with its original 
meaning, that something happens implicitly, behind the curtain, 
specified most often in an informal way (not always deserving to be 
called operational). If you call all the assignments side effects, 
why not call -  let x = whatever in Something - also a local 
side-effect?
Oh, that you can often transform let in the application of lambda, 
thus purely functional?


Doesn't matter, Steve Horne will explain you that (sorry for the 
irony): let is a compile-time pure construct ; at execution this is 
impure, because x got a value.


Well, I was even more absurd than that - in C, I said there were two 
values (the reference and the value referenced) for every variable.


Sometimes, eliminating all the subtle contradictions necessarily leads 
to a much more pedantic world than intuition is happy to deal with.
S.H. admits that he reasons within his model, and has problems with 
others. Everybody has such problems, but I see here something the 
(true) Frenchies call un dialogue de sourds. For me a Haskell 
programme is ABSOLUTELY pure, including the IO. The issue is that 
`bind` within the IO monad has an implicit parameter, the World. In 
fact, a stream of Worlds, every putWhatever, getLine, etc. passes to a 
new instance.


As I said earlier, a politician who buries the relevant in a huge mass 
of the irrelevant is not considered transparent. To call this world 
parameter referentially transparent is, to me, argument by deceptive 
definitions. In any case, the world parameter is present in C - it's 
just implicit. You can translate C to Haskell and visa versa. Both the C 
and Haskell versions of a correctly translated program will have the 
same interactions with the world. Therefore there is a mathematical 
equivalence between Haskell and C.


You can argue pedantry, but the pedantry must have a point - a 
convenient word redefinition will not make your bugs go away. People 
tried that with it's not a bug it's a feature and no-one was impressed.



Simply, you are not allowed by the Holy Scripts to look under this robe.


Ah yes - well that's exactly what I'm trying to do.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 19:26, Heinrich Apfelmus wrote:

Steve Horne wrote:

Heinrich Apfelmus wrote:


Again, purity refers to the semantics of functions (at run-time): 
given the same argument, will a function always return the same 
result? The answer to this question solely decides whether the 
language is pure or impure. Note that this depends on the meaning of 
function within that language. In C, side-effects are part of the 
semantics of functions, so it's an impure language. In Haskell, on 
the other hand, functions will always return the same result, so the 
language is pure. You could say that side effects have been moved 
from functions to some other type (namely IO) in Haskell.


Anyway, if you're using IO actions, your code is not referentially 
transparent and is therefore impure - by your own definition of 
impure. Causing side-effects may not be pedantically the issue, but 
the mix of causing and reacting to them - ie interacting with the 
outside - clearly means that some of your function results are 
dependent on what's happening outside your program. That includes 
side-effects outside your program yet caused by program program.


No, that's not my definition of impure. Also, my Haskell code is 
referentially transparent even though I'm using IO actions. If this 
sounds paradoxical, then it's probably worth mulling about some more. 
Maybe it helps to try to find an example of a function  f :: A - B  
for some cleverly chosen types A,B that is not pure, i.e. does not 
return the same values for equal arguments.

That doesn't prove Haskell pure.

Of course your challenge looks like a safe one. It can't be done because 
the IO monad is a black box - you can't e.g. pattern-match on it's data 
constructors.


Of course you can extract values out of IO actions to work with them - 
the bind operator does this for you nicely, providing the value as an 
argument to the function you pass to the right-hand argument of the 
bind. But that function returns another IO action anyway - although 
you've extracted a value out and the value affects a computation, all 
you can do with it in the long run is return another IO action.


Even so, that value can only be extracted out at run-time, after the 
action is executed.


So, consider the following...

getAnIntFromTheUser :: IO Int

From a pure functional point of view, that should return the same 
action every time. Well, the partially evaluated getAnIntFromTheUser has 
the same structure each time - but the actual Int packaged inside the 
action isn't decided until runtime, when the action is executed. At 
compile-time, that action can only be partially evaluated - the final 
value OF THE ACTION depends on what Int the user chooses to give because 
that Int is a part of the action value.


For your specific challenge, place that as a left-hand argument in a bind...

f :: Int - IO Int
f = getAnIntFromTheUser = \i - return (i+1)

Well, the value of i isn't decidable until runtime. The value of i+1 is 
not decidable until runtime. The value of return (i+1) is not decidable 
until runtime and so on. It can only be partially evaluated at 
compile-time, but when it is fully evaluated, you get a different IO 
action returned by f depending on what Int you got from the user.


And so we get right back to the 
referential-transparency-by-referencing-the-world-as-an-argument thing, 
I guess.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 19:55, Bardur Arantsson wrote:

On 12/29/2011 08:47 PM, Steve Horne wrote:

On 29/12/2011 19:21, Heinrich Apfelmus wrote:



BTW - why use an IO action for random number generation? There's a
perfectly good pure generator. It's probably handy to treat it
monadically to sequence the generator state/seed/whatever but random
number generation can be completely pure.


*Pseudo* random number generation can of course be pure (though 
threading the state would be tedious and error-prone). If you want 
truly random numbers you cannot avoid IO (the monad).
On the threading the state thing - it doesn't matter whether it's the IO 
monad or the State monad (a perfect wrapper for the seed).


For where-does-the-entropy-come-from, though, yes - I guess you're right.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell /Random generators

2011-12-29 Thread Steve Horne

On 29/12/2011 20:39, Jerzy Karczmarczuk wrote:
Still, I dont understand what does S.H.  mean by a perfectly good 
pure generator.

Tell more please (unless you just mean a stream, say:

Probably bad wording, to be honest. I only meant that there's random 
number handling support in the Haskell library and, and least judging by 
type signatures, it's pure functional code with no hint of the IO monad.


AFAIK there's no hidden unsafePerformIO sneaking any entropy in behind 
the scenes. Even if there was, it might be a legitimate reason for 
unsafePerformIO - random numbers are in principle non-deterministic, not 
determined by the current state of the outside world and 
which-you-evaluate-first should be irrelevant. If you have a quantum 
genuine-random-numbers gadget, the IO monad might be considered 
redundant for functions that get values from it - though it still isn't 
referentially transparent as it returns a different value each time even 
with the same parameters.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 21:01, Chris Smith wrote:

On Thu, 2011-12-29 at 18:07 +, Steve Horne wrote:

By definition, an intentional effect is a side-effect. To me, it's by
deceptive redefinition - and a lot of arguments rely on mixing
definitions - but nonetheless the jargon meaning is correct within
programming and has been for decades. It's not going to go away.

Basically, the jargon definition was coined by one of the pioneers of
function programming - he recognised a problem and needed a simple way
to describe it, but in some ways the choice of word is unfortunate.

I don't believe this is true.  Side effect refers to having a FUNCTION
-- that is, a map from input values to output values -- such that when
it is evaluated there is some effect in addition to computing the
resulting value from that map.  The phrase side effect refers to a
very specific confusion: namely, conflating the performing of effects
with computing the values of functions.
Yes - again, by definition that is true. But that definition is not the 
everyday definition of side-effect. Repeating and explaining one 
definition doesn't make the other go away.


1. To say that the C printf function has the side-effect of printing to
   the screen - that's true.
2. To say that the C printf function has no side-effects because it
   works correctly - the only effects are intentional - that's also true.

Two definitions of side-effect. The definition used for case 2 is a lot 
older than the definition used for case 1, and remains valid. It's the 
normal usage that most people are familiar with everywhere - not just in 
programming and computer science.


I haven't failed to understand either definition - I simply accept that 
both are valid. Natural language is ambiguous - sad fact of life.


Using similar mixed definitions to conclude that every C program is full 
of bugs (basically equating intentional effects with side-effects, then 
equating side-effects with unintentional bugs) is a fairly common thing 
in my experience, but it's a logical fallacy. If you aren't aware of the 
two definitions of side-effect, it's hard to get deal with that.


Some people don't want anyone to figure out the fallacy - they like 
having this convenient way to attack C, irrespective of whether it's 
valid or not. Rare I think - mostly it's more confusion and memetics. 
But still, I'm convinced there's some sophistry in this. And I'm not the 
only person to think so, and to have reacted against that in the past.


Extra sad - you don't need that fallacy to attack C. It's redundant. C 
is quite happy to demonstrate its many failings.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell /Random generators

2011-12-29 Thread Steve Horne

On 29/12/2011 21:51, Jerzy Karczmarczuk wrote:

Steve Horne :
I only meant that there's random number handling support in the 
Haskell library and, and least judging by type signatures, it's pure 
functional code with no hint of the IO monad.

Look well at those functions, please.
Challenge accepted. Some code (intended to be loaded into GHCi and 
played with) that I once wrote when doing the ninety-nine problems thing 
(the one that doesn't have ninety-nine problems - originally based on a 
Prolog tutorial IIRC)...


   --  Randomly select the specified number of items from the list
   --
   --  Usage in GHCi...
   --
   --  import System.Random
   --  randSelect this is a list 5 (mkStdGen 9877087)
   --
   --  This will give the same results each time (for the same seed
   given to mkStdGen)
   --
   --  randSelect' does the real work, but needs to know the length of
   the remaining
   --  list and doesn't do error checks (for efficiency reasons).
   module P23 (randSelect) where
  import System.Random

  randSelect' :: RandomGen g = [x] - Int - Int - g - ([x], g)

  randSelect' [] n l g = ([], g)  --  n and l should be == 0, but
   no need for run-time check

  --  optimisation cases - no choice left
  randSelect' xs n l g | (n == l) = (xs, g)
   | (n == 0) = ([], g)

  randSelect' (x:xs) n l g = let xsLen  = (l - 1)
 (rnd, g')  = randomR (0, xsLen) g
 (keep, n') = if (rnd  n) then
   (True, (n-1)) else (False, n)
 (xs', g'') = randSelect' xs n'
   xsLen g'
 in ((if keep then (x:xs') else xs'), g'')

  randSelect :: RandomGen g = [x] - Int - g - ([x], g)

  randSelect xs n g = let len = (length xs)
  in if (n  len) then error Not enough items
   in the list!
  else randSelect' xs n len g

I see no IO monad anywhere in there. Of course I'm cheating - providing 
a constant seed at runtime. It's a bit like the classic chosen by a 
throw of a fair die joke in a way. But the functions I'm using are pure.


I don't claim to know every Haskell library function, of course. If 
there's further functions for that, all well and good - but there's 
still a perfectly adequate pure functional subset.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 30/12/2011 00:16, Sebastien Zany wrote:

Steve Horne wrote:

I haven't seen this view explicitly articulated anywhere before


See Conal Elliott's blog post The C language is purely functional 
http://conal.net/blog/posts/the-c-language-is-purely-functional.
Thanks - yes, that's basically the same point. More concise - so 
clearer, but not going into all the same issues - but still the same theme.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 29/12/2011 23:30, Chris Smith wrote:

Sorry to cut most of this out, but I'm trying to focus on the central
point here.

On Thu, 2011-12-29 at 22:01 +, Steve Horne wrote:

In pure functional terms, the result should be equivalent to a fully
evaluated value - but putStrLn isn't pure. It cannot be fully
evaluated until run-time.

And here it is, I think.  You're insisting on viewing the performing of
some effect as part of the evaluation of an expression, even though the
language is explicitly and intentionally designed not to conflate those
two ideas.  Effects do not happen as a side-effect of evaluating
expressions.  Instead they happen because you define the symbol 'main'
to be the effect that you want to perform, and then set the runtime
system to work on performing it by running your program.

So, to resurrect an example from earlier...

f :: Int - IO Int
f = getAnIntFromTheUser = \i - return (i+1)

Are you claiming that the expression (i+1) is evaluated without knowing 
the value of i?


If not, at run-time your Haskell evaluates those expressions that 
couldn't be fully evaluated at compile-time.


If you do, we're back to my original model. The value returned by main 
at compile-time is an AST-like structure wrapped in an IO monad 
instance. The AST nodes are partially evaluated functions, but since 
they can't be evaluated in a sense that knows the precise result of that 
+ operator, we say this unevaluated function can be treated as a value 
in itself - let's compose bigger ASTs out of smaller ones.


In that model, the 'i' above - the argument to the lambda - never gets 
an Int value because it's really just a placeholder for tracking the 
intended flow of data that won't actually flow until run-time.


But that AST is just a translated description of the same program. It 
isn't the end result - it's just an intermediate step along the road to 
being able to run the thing. The unevaluated function is just falling 
back on returning a representation of its unevaluated self. That model 
is still compiled to executable code. That executable code, when run, 
still interacts with it's environment. That is as much an aspect of what 
Haskell defines as the functional core.


Switching mental models doesn't change the logic any more than switching 
number bases. They are different descriptions of the same thing. The 
models are superficially different, but the logic is equivalent. It 
really doesn't matter whether you call something an AST node or an 
unevaluated function. An AST node can represent an unevaluated function. 
An unevaluated function can be implemented as a closure - which is just 
a collection of data, the same as an AST node. The two things are really 
both *still* the exact same thing. Even when it's translated to binary 
executable code, it is *still* the unevaluated function - right up until 
it gets executed (and in the same moment, evaluated).


Either way, at run-time, Haskell is impure.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell /Random generators

2011-12-29 Thread Steve Horne

On 30/12/2011 00:22, Jerzy Karczmarczuk wrote:

Steve Horne :

Some code (intended to be loaded into GHCi and played with)

--  import System.Random
--  randSelect this is a list 5 (mkStdGen 9877087)
-- ...
module P23 (randSelect) where
-- ...
  randSelect' (x:xs) n l g = let xsLen  = (l - 1)
 (rnd, g')  = randomR (0, xsLen) g
-- ...

I see no IO monad anywhere in there. Of course I'm cheating - 
providing a constant seed at runtime.


The last remark is irrelevant. Normally the seed IS constant, injected 
once, then updated by the generator iself.


I don't know what you are trying to prove.

I don't know why you think I'm trying to prove something here.

Earlier, I mentioned that Haskell provides pure functional random number 
support in the library - as part of going off on a tangent and, as it 
happens, of making a mistake. I specifically said something like with 
no mention of the IO monad with respect to type signatures.


You said Look well at those functions, please. I accepted your 
challenge. I looked well. I still say that Haskell provides pure 
functional random number support in the library.


My last remark was there basically because of the earlier mistake - 
acknowledging that I've bypassed the whole issue of where the seed comes 
from, which may for all I know be supported by a library IO action, and 
which would be relevant given how this randomness thread started. That 
was my first mistake in this randomness thread - another mistake I made 
was saying unsafePerformIO might reasonably be used to sneak in entropy.


Basically, I replied to your challenge - nothing more. I really don't 
even care much about random numbers - that's why my easiest reference 
was from back when I was doing those tutorials. There is no deep point 
here unless you're making one I haven't understood yet.


As for whether or not Haskell is pure - this randomness thread isn't 
relevant to that any more.


If you see my reference to purity as a weasel way of insinuating that 
there's also impurity in Haskell - I don't need to insinuate that, I've 
openly stated my view and explained my reasoning as well as I'm able. 
What point is there in being a cowardly weasel if you also paint a 
bullseye on your head and shout Here I am!?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Level of Win32 GUI support in the Haskell platform

2011-12-29 Thread Steve Horne
I've been for functions like GetMessage, TranslateMessage and 
DispatchMessage in the Haskell Platform Win32 library - the usual 
message loop stuff - and not finding them. Hoogle says no results found.


Is this level of Win32 GUI coding supported? (other than by dealing with 
the FFI myself)


Alternatively, should I be doing dialog-based coding and leaving Haskell 
to worry about message loops behind the scenes?


Either way, is there an example I can use for reference? I have 
something along the lines of Petzolds Hello World in mind as the ideal 
(register a window class, handle the messages, paint some text), but 
anything that shows how to get a basic Win32 GUI app running in Haskell 
is fine.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 30/12/2011 01:37, Chris Smith wrote:

On Fri, 2011-12-30 at 00:44 +, Steve Horne wrote:

So, to resurrect an example from earlier...

f :: Int -  IO Int
f = getAnIntFromTheUser= \i -  return (i+1)

Did you mean  f :: IO Int ?  If not, then I perhaps don't understand
your example, and your monad is not IO.  I'll continue assuming the
former.

Oops - I meant...

f :: Int - IO Int
f x = getAnIntFromTheUser = \i - return (i+x)

Your version should be fine, only the lack of a parameter makes a 
superficial difference.


I certainly agree that the GHC runtime system, and any other Haskell 
implementation's runtime system as well, evaluates expressions (some 
representation of them anyway), and does lots of destructive updates 
to boot. This isn't at issue. What is at issue is whether to shoehorn 
those effects into the language semantics as a side-effect of 
evaluation (or equivalently, force evaluation of expressions to be 
seen as an effect -- when you only allow for one of these concepts, 
it's a silly semantic game as to which name you call it by), or to 
treat effects as semantically first-class concepts in their own right, 
different from the simplification of expressions into values. 
Well, we're playing a semantic game anyway. Treating effects as 
first-class concepts in themselves is fine, but IMO doesn't make Haskell 
pure.



If you do, we're back to my original model. The value returned by main
at compile-time is an AST-like structure wrapped in an IO monad
instance.

Here you're introducing implementation detail here that's rather
irrelevant to the semantics of the language.
Think of it as an analogy - using the terminology of compiler design. I 
might describe arithmetic in terms of an abacus too - it doesn't mean 
I'd only get those results if I used an abacus.


The implementation details don't matter - the behaviour of the program does.


Purity isn't about the RTS implementation, which is of course plenty
effectful and involves lots of destructive updates.  It's about the
language semantics.

And the semantics of primitive IO actions *include* the run-time effects 
- those semantics are defined in the Haskell Report. For example...


   Computation hGetChar hdl reads a character from the file or channel
   managed by hdl.

If you have another meaning in mind for the word semantics, well 
that's fine. As already discussed with side effects, natural language 
is sadly ambiguous. It can be confusing, but it doesn't change the facts 
or the logic.


I don't know the first thing about denotational semantics, but I do know 
this - if you place run-time behaviour outside the scope of your model 
of program semantics, that's just a limitation of your model. It doesn't 
change anything WRT the program itself - it only limits the 
understanding you can derive using that particular model.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-29 Thread Steve Horne

On 30/12/2011 01:40, Scott Turner wrote:

On 2011-12-29 19:44, Steve Horne wrote:

[Interaction with its environment] is as much an aspect of what
Haskell defines as the functional core.

Switching mental models doesn't change the logic

But it does. Other languages do not support the distinction between pure
functions and I/O effects.
Agreed. I said basically the same thing right at the start. This doesn't 
change any logic, though.



Either way, at run-time, Haskell is impure.

No big deal. Who would want to use a language that you would call
pure? Haskell has referential transparency. In Haskell, you have
assurance that any function without IO in its type is as pure as the
lambda calculus.

Absolutely. In my original post, of course, I made my big implicit 
IORef parameter argument that says C too is referentially transparent, 
but I also pointed out another view of transparency - the politician who 
buries the relevant in a huge pile of the irrelevant is not being 
transparent - and pointed out that in Haskell you can have zero, one or 
many IORefs - you can focus in on what is relevant.


I actually thought this point would make Haskell advocates happy, but no 
sign of that yet.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Level of Win32 GUI support in the Haskell platform

2011-12-29 Thread Steve Horne

On 30/12/2011 03:43, Chris Wong wrote:

On Fri, Dec 30, 2011 at 2:53 PM, Steve Horne
sh006d3...@blueyonder.co.uk  wrote:

I've been for functions like GetMessage, TranslateMessage and
DispatchMessage in the Haskell Platform Win32 library - the usual message
loop stuff - and not finding them. Hoogle says no results found.

Is this level of Win32 GUI coding supported? (other than by dealing with the
FFI myself)

I'd recommend using Gtk2hs (http://haskell.org/gtk2hs). It's well
supported and your program will work on Mac  Linux  BSD to boot.

Trying to grapple with Win32 APIs isn't exactly my idea of fun. :)


I had dismissed GTK  - I assumed getting it set up in Windows would be a 
bit painful, and figured I'd stick with whats in the Haskell Platform 
for the moment. I'm already familiar (though very rusty) with Win32 from 
C - it seemed like an easy if limited option.


But I'll take a look at gtk2hs anyway.

Thanks.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Level of Win32 GUI support in the Haskell platform

2011-12-29 Thread Steve Horne

On 30/12/2011 04:07, Chris Smith wrote:

On Fri, 2011-12-30 at 01:53 +, Steve Horne wrote:

I've been for functions like GetMessage, TranslateMessage and
DispatchMessage in the Haskell Platform Win32 library - the usual
message loop stuff - and not finding them. Hoogle says no results found.

I see them in the Win32 package.

http://hackage.haskell.org/packages/archive/Win32/2.2.1.0/doc/html/Graphics-Win32-Window.html#v:getMessage
Ah - I didn't look in Graphics.Win32.Window because those functions 
don't relate to Windows. Clearly I gave up my search too easily - thanks.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne
This is just my view on whether Haskell is pure, being offered up for 
criticism. I haven't seen this view explicitly articulated anywhere 
before, but it does seem to be implicit in a lot of explanations - in 
particular the description of Monads in SBCs Tackling the Awkward 
Squad. I'm entirely focused on the IO monad here, but aware that it's 
just one concrete case of an abstraction.


Warning - it may look like trolling at various points. Please keep going 
to the end before making a judgement.


To make the context explicit, there are two apparently conflicting 
viewpoints on Haskell...


1. The whole point of the IO monad is to support programming with
   side-effecting actions - ie impurity.
2. The IO monad is just a monad - a generic type (IO actions), a couple
   of operators (primarily return and bind) and some rules - within a
   pure functional language. You can't create impurity by taking a
   subset of a pure language.

My view is that both of these are correct, each from a particular point 
of view. Furthermore, by essentially the same arguments, C is also both 
an impure language and a pure one.


See what I mean about the trolling thing? I'm actually quite serious 
about this, though - and by the end I think Haskell advocates will 
generally approve.


First assertion... Haskell is a pure functional language, but only from 
the compile-time point of view. The compiler manipulates and composes IO 
actions (among other things). The final resulting IO actions are finally 
swallowed by unsafePerformIO or returned from main. However, Haskell is 
an impure side-effecting language from the run-time point of view - when 
the composed actions are executed. Impurity doesn't magically spring 
from the ether - it results from the translation by the compiler of IO 
actions to executable code and the execution of that code.


In this sense, IO actions are directly equivalent to the AST nodes in a 
C compiler. A C compiler can be written in a purely functional way - in 
principle it's just a pure function that accepts a string (source code) 
and returns another string (executable code). I'm fudging issues like 
separate compilation and #include, but all of these can be resolved in 
principle in a pure functional way. Everything a C compiler does at 
compile time is therefore, in principle, purely functional.


In fact, in the implementation of Haskell compilers, IO actions almost 
certainly *are* ASTs. Obviously there's some interesting aspects to that 
such as all the partially evaluated and unevaluated functions. But even 
a partially evaluated function has a representation within a compiler 
that can be considered an AST node, and even AST nodes within a C 
compiler may represent partially evaluated functions.


Even the return and bind operators are there within the C compiler in a 
sense, similar to the do notation in Haskell. Values are converted into 
actions. Actions are sequenced. Though the more primitive form isn't 
directly available to the programmer, it could easily be explicitly 
present within the compiler.


What about variables? What about referential transparency?

Well, to a compiler writer (and equally for this argument) an identifier 
is not the same thing as the variable it references.


One way to model the situation is that for every function in a C 
program, all explicit parameters are implicitly within the IO monad. 
There is one implicit parameter too - a kind of IORef to the whole 
system memory. Identifiers have values which identify where the variable 
is within the big implicit IORef. So all the manipulation of identifiers 
and their reference-like values is purely functional. Actual handling of 
variables stored within the big implicit IORef is deferred until run-time.


So once you accept that there's an implicit big IORef parameter to every 
function, by the usual definition of referential transparency, C is as 
transparent as Haskell. The compile-time result of each function is 
completely determined by its (implicit and explicit) parameters - it's 
just that that result is typically a way to look up the run-time result 
within the big IORef later.


What's different about Haskell relative to C therefore...

1. The style of the AST is different. It still amounts to the same
   thing in this argument, but the fact that most AST nodes are simply
   partially-evaluated functions has significant practical
   consequences, especially with laziness mixed in too. There's a deep
   connection between the compile-time and run-time models (contrast
   C++ templates).
2. The IO monad is explicit in Haskell - side-effects are only
   permitted (even at run-time) where the programmer has explicitly
   opted to allow them.
3. IORefs are explicit in Haskell - instead of always having one you
   can have none, one or many. This is relevant to an alternative
   definition of referential transparency. Politicians aren't
   considered transparent when they bury the relevant in a mass 

Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne

On 28/12/2011 20:44, Heinrich Apfelmus wrote:

Steve Horne wrote:
This is just my view on whether Haskell is pure, being offered up for 
criticism. I haven't seen this view explicitly articulated anywhere 
before, but it does seem to be implicit in a lot of explanations - in 
particular the description of Monads in SBCs Tackling the Awkward 
Squad. I'm entirely focused on the IO monad here, but aware that 
it's just one concrete case of an abstraction.


Warning - it may look like trolling at various points. Please keep 
going to the end before making a judgement.


To make the context explicit, there are two apparently conflicting 
viewpoints on Haskell...


1. The whole point of the IO monad is to support programming with
   side-effecting actions - ie impurity.
2. The IO monad is just a monad - a generic type (IO actions), a couple
   of operators (primarily return and bind) and some rules - within a
   pure functional language. You can't create impurity by taking a
   subset of a pure language.

My view is that both of these are correct, each from a particular 
point of view. Furthermore, by essentially the same arguments, C is 
also both an impure language and a pure one. [...]


Purity has nothing to do with the question of whether you can express 
IO in Haskell or not.



...

The beauty of the IO monad is that it doesn't change anything about 
purity. Applying the function


   bar :: Int - IO Int

to the value 2 will always give the same result:

Yes - AT COMPILE TIME by the principle of referential transparency it 
always returns the same action. However, the whole point of that action 
is that it might potentially be executed (with potentially 
side-effecting results) at run-time. Pure at compile-time, impure at 
run-time. What is only modeled at compile-time is realized at run-time, 
side-effects included.


Consider the following...

#include stdio.h

int main (int argc, char*argv)
{
  char c;
  c = getchar ();
  putchar (c);
  return 0;
}

The identifier c is immutable. We call it a variable, but the 
compile-time value of c is really just some means to find the actual 
value in the big implicit IORef at runtime - an offset based on the 
stack pointer or whatever. Nothing mutates until compile-time, and when 
that happens, the thing that mutates (within that big implicit IORef) 
is separate from that compile-time value of c.


In C and in Haskell - the side-effects are real, and occur at run-time.

That doesn't mean Haskell is as bad as C - I get to the advantages of 
Haskell at the end of my earlier post. Mostly unoriginal, but I think 
the bit about explicit vs. implicit IORefs WRT an alternate view of 
transparency is worthwhile.


I hope If convinced you I'm not making one of the standard newbie 
mistakes. I've done all that elsewhere before, but not today, honest.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne

On 28/12/2011 22:01, Jerzy Karczmarczuk wrote:

Le 28/12/2011 22:45, Steve Horne a écrit :
Yes - AT COMPILE TIME by the principle of referential transparency it 
always returns the same action. However, the whole point of that 
action is that it might potentially be executed (with potentially 
side-effecting results) at run-time. Pure at compile-time, impure at 
run-time. What is only modeled at compile-time is realized at 
run-time, side-effects included.

(...)

I hope If convinced you I'm not making one of the standard newbie 
mistakes. I've done all that elsewhere before, but not today, honest.
Sorry, perhaps this is not a standard newbie mistake, but you - 
apparently - believe that an execution of an action on the real 
world is a side effect.


I don't think it is.
Even if a Haskell programme fires an atomic bomb, a very impure one, 
/*there are no side effects within the programme itself*/.
True. But side-effects within the program itself are not the only 
relevant side-effects.


As Simon Baron-Cohen says in Tackling the Awkward Squad...

   Yet the ultimate purpose of running a program is invariably to cause
   some side effect: a changed file, some new pixels on the screen, a
   message sent, or whatever. Indeed it's a bit cheeky to call
   input/output awkward at all. I/O is the raison d'^etre of every
   program. --- a program that had no observable effect whatsoever (no
   input, no output) would not be very useful.

Of course he then says...

   Well, if the side effect can't be in the functional program, it will
   have to be outside it.

Well, to me, that's a bit cheeky too - at least if taken overliterally. 
Even if you consider a mutation of an IORef to occur outside the 
program, it affects the later run-time behaviour of the program. The 
same with messages sent to stdout - in this case, the user is a part of 
the feedback loop, but the supposedly outside-the-program side-effect 
still potentially affects the future behaviour of the program when it 
later looks at stdin.


A key point of functional programming (including its definitions of 
side-effects and referential transparency) is about preventing bugs by 
making code easier to reason about.


Saying that the side-effects are outside the program is fine from a 
compile-time compositing-IO-actions point of view. But as far as 
understanding the run-time behaviour of the program is concerned, that 
claim really doesn't change anything. The side-effects still occur, and 
they still affect the later behaviour of the program. Declaring that 
they're outside the program doesn't make the behaviour of that program 
any easier to reason about, and doesn't prevent bugs.


A final SBC quote, still from Tackling the Awkward Squad...

   There is a clear distinction, enforced by the type system, between
   actions which may have
   side effects, and functions which may not.

SBC may consider the side-effects to be outside the program, but he 
still refers to actions which may have side-effects. The side-effects 
are still there, whether you consider them inside or outside the 
program, and as a programmer you still have to reason about them.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne

On 28/12/2011 23:56, Bernie Pope wrote:

On 29 December 2011 10:51, Steve Hornesh006d3...@blueyonder.co.uk  wrote:


As Simon Baron-Cohen says in Tackling the Awkward Squad...

I think you've mixed up your Simons; that should be Simon Peyton Jones.


Oops - sorry about that.

FWIW - I'm diagnosed Aspergers. SBC diagnosed me back in 2001, shortly 
after 9/1/1.


Yes, I *am* pedantic - which doesn't always mean right, of course.

Not relevant, but what the hell.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne
Sorry for the delay. I've written a couple of long replies already, and 
both times when I'd finished deleting all the stupid stuff there was 
nothing left - it seems I'm so focussed on my own view, I'm struggling 
with anything else today. Maybe a third try...


On 28/12/2011 19:38, AUGER Cédric wrote:

Le Wed, 28 Dec 2011 17:39:52 +,
Steve Hornesh006d3...@blueyonder.co.uk  a écrit :


This is just my view on whether Haskell is pure, being offered up for
criticism. I haven't seen this view explicitly articulated anywhere
before, but it does seem to be implicit in a lot of explanations - in
particular the description of Monads in SBCs Tackling the Awkward
Squad. I'm entirely focused on the IO monad here, but aware that
it's just one concrete case of an abstraction.



IO monad doesn't make the language impure for me, since you can give
another implementation which is perfectly pure and which has the same
behaviour (although completely unrealistic):



Now how would this work?
In a first time, you load all your system file before running the
program (a side-effect which does not modify already used structures;
it is just initialization), then you run the program in a perfectly
pure way, and at the end you commit all to the system file (so you
modify structures the running program won't access as it has
terminated).
I don't see how interactivity fits that model. If a user provides input 
in response to an on-screen prompt, you can't do all the input at the 
start (before the prompt is delayed) and you can't do all the output at 
the end.


Other than that, I'm OK with that. In fact if you're writing a compiler 
that way, it seems fine - you can certainly delay output of the 
generated object code until the end of the compilation, and the input 
done at the start of the compilation (source files) is separate from the 
run-time prompt-and-user-input thing.


See - I told you I'm having trouble seeing things in terms of someone 
elses model - I'm back to my current obsession again here.

In Haskell,
'hGetChar h= \c -  hPutChar i' always has the same value, but
'trans (hGetChar h= \c -  hPutChar i) (IO_ A)'
'trans (hGetChar h= \c -  hPutChar i) (IO_ B)'
may have different values according to A and B.

In C, you cannot express this distinction, since you only have:
'read(h,c, 1); write(i,c, 1);' and cannot pass explicitely the
environment.

Agreed. Haskell is definitely more powerful in that sense.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne

On 29/12/2011 00:57, Thiago Negri wrote:


We can do functional programming on Java. We use all the design
patterns for that.

At the very end, everything is just some noisy, hairy,
side-effectfull, gotofull machinery code.

The beauty of Haskell is that it allows you to limit the things you
need to reason about. If I see a function with the type (a, b) - a
I don't need to read a man page to see where I should use it or not. I
know what it can do by its type. In C I can not do this. What can I
say about a function int foo(char* bar)? Does it allocate memory?
Does it asks a number for the user on stdin? Or does it returns the
length of a zero-ending char sequence? In fact it can do anything, and
I can't forbid that. I can't guarantee that my function has good
behaviour. You need to trust the man page.

Well, I did say (an unoriginal point) that The IO monad is explicit in 
Haskell - side-effects are only permitted (even at run-time) where the 
programmer has explicitly opted to allow them.. So yes.


The it could do anything!!! claims are over the top and IMO 
counterproductive, though. The type system doesn't help the way it does 
in Haskell, but nevertheless, plenty of people reason about the 
side-effects in C mostly-successfully.


Mostly /= always, but bugs can occur in any language.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] On the purity of Haskell

2011-12-28 Thread Steve Horne

On 29/12/2011 01:53, Antoine Latter wrote:

The beauty of the IO monad is that it doesn't change anything about
purity. Applying the function

   bar :: Int -  IO Int

to the value 2 will always give the same result:


Yes - AT COMPILE TIME by the principle of referential transparency it always
returns the same action. However, the whole point of that action is that it
might potentially be executed (with potentially side-effecting results) at
run-time. Pure at compile-time, impure at run-time. What is only modeled at
compile-time is realized at run-time, side-effects included.


I don't think I would put it that way - the value 'bar 2' is a regular
Haskell value. I can put it in a list, return it from a function and
all other things:

myIOActions :: [IO Int]
myIOActions = [bar 2, bar (1+1), bar (5-3)]

And I can pick any of the elements of the list to execute in my main
function, and I get the same main function either way.
Yes - IO actions are first class values in Haskell. They can be derived 
using all the functional tools of the language. But if this points out a 
flaw in my logic, it's only a minor issue in my distinction between 
compile-time and run-time.


Basically, there is a phase when a model has been constructed 
representing the source code. This model is similar in principle to an 
AST, though primarily (maybe entirely?) composed of unevaluated 
functions rather than node-that-represents-whatever structs. This phase 
*must* be completed during compilation. Of course evaluation of some 
parts of the model can start before even parsing is complete, but that's 
just implementation detail.


Some reductions (if that's the right term for a single evaluation step) 
of that model cannot be applied until run-time because of the dependence 
on run-time inputs. Either the reduction implies the execution of an IO 
action, or an argument has a data dependency on an IO action.


Many reductions can occur either at compile-time or run-time.

In your list-of-actions example, the list is not an action itself, but 
it's presumably a part of the expression defining main which returns an 
IO action. The evaluation of the expression to select an action may have 
to be delayed until run-time with the decision being based on run-time 
input. The function that does the selection is still pure. Even so, this 
evaluation is part of the potentially side-effecting evaluation and 
execution of the main IO action. Overall, the run-time execution is 
impure - a single side-effect is enough.


So... compile-time pure, run-time impure.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Steve Horne


On haskell.org, the 2011.4.0.0 version is shown as the current stable 
release - but the most recent download link is for the 2011.2.0.0 version.


This is bugging me a little because the documentation in the 2011.2 
Haskell Platform download for Windows is broken - there's at least one 
bug report about this already. There's online documentation, but it's 
(1) online, where I need something I can read on an old no-internet 
laptop, and (2) I assume for the most recent version, and therefore it 
potentially misleading.


I already fixed the online side - sorry, I know slurping a whole site 
is evil but I had little choice. The fact that the docs relate to a 
version of the platform that I can't access remains. I just have to hope 
that the changes are few and won't affect me.


Extra annoying - there's no mention of why 2011.4 is missing from the 
Windows download page - no temporarily delayed or skipped due to an 
awkward technical issue or not enough Windows developers 
volunteering. For all I know, it could just be an oversight updating 
haskell.org itself, but I think that's unlikely.


So... what's the situation with the Haskell Platform on Windows? - both 
WRT my specific bit of whinging and whining, and in general?


Is Windows a low priority niche from the Haskell POV? If I intend to 
take Haskell more seriously, do I need to make Linux or some other *nix 
my primary OS?


Please say no - I've been an on-and-off Linux user for around 10 years, 
with the most recent 2 years on ending around May this year. For all the 
pros, the cons of endless graphics card driver issues, awkward 
configuration hassles and so on have defeated me yet again.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Steve Horne

On 27/12/2011 18:36, Bas van Dijk wrote:

On 27 December 2011 19:13, Steve Hornesh006d3...@blueyonder.co.uk  wrote:

On haskell.org, the 2011.4.0.0 version is shown as the current stable
release - but the most recent download link is for the 2011.2.0.0 version.

What download link are you referring to? I see that:
http://hackage.haskell.org/platform/windows.html correctly points to
the 2011.4.0.0 release.

Bas


From http://hackage.haskell.org/platform/

Click Windows to reach http://hackage.haskell.org/platform/windows.html

Seems to be the same page you're referring to, but no 2011.4 link.

Just in case, I forced a page refresh - and got a surprise when that 
fixed it.


OK - I really should have tried that before. But... why would an old 
page hang around in my Firefox cache so long and not get updated? I've 
not had this on any other sites.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell Platform and Windows - where's 2011.4?

2011-12-27 Thread Steve Horne

On 27/12/2011 18:57, Steve Horne wrote:
OK - I really should have tried that before. But... why would an old 
page hang around in my Firefox cache so long and not get updated? I've 
not had this on any other sites.

I still should be doing more checking before posting.

A look in the source for the page doesn't show any odd metadata or 
anything. Whatever the issue is, it's my end.


Sorry everyone.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe