Re: proposal for trailing comma and semicolon

2013-05-18 Thread Heinrich Apfelmus

Tillmann Rendel wrote:


I like to put commas at the beginning of lines, because there, I can 
make them line up and it is visually clear that they are all at the same 
nesting level. I like how the commas look a bit like bullet points. For 
example, I would write:


items =
  [ "red"
  , "blue"
  , "green"
  ]

Could we extend Garett's proposal to also allow prefixing the first 
element of a list with a comma, to support this style:


items = [
  , "red"
  , "blue"
  , "green"
  ]

Allowing an optional extra comma both at the beginning and at the end 
would allow programmers the choice where they want to put their commas.


This is the style I am using for records and lists as well. Here an 
example from actual code


data EventNetwork = EventNetwork
{ actuate :: IO ()
, pause   :: IO ()
}

These days, all my record definitions look like that.

Allowing a superfluous leading comma would be great, because that makes 
it easier to move around the first line.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: Proposal: Scoping rule change

2012-07-25 Thread Heinrich Apfelmus

Heinrich Apfelmus wrote:

Lennart Augustsson wrote:

It's not often that one gets the chance to change something as
fundamental as the scoping rules of a language.  Nevertheless, I would
like to propose a change to Haskell's scoping rules.

The change is quite simple.  As it is, top level entities in a module
are in the same scope as all imported entities.  I suggest that this
is changed to that the entities from the module are in an inner scope
and do not clash with imported identifiers.

Why?  Consider the following snippet

module M where
import I
foo = True


I like it.

That said, how does the the fact that the scope is nested affect the 
export list? If the module scope is inside the scope of the imports, 
then this means the name  I.foo  should appear in the export list, not 
foo , because the latter is in the outermost scope.


I think the solution to these problems is to rearrange the  import 
declarations so that the syntax mirrors the scoping rules. In other 
words, I boldly propose to move the  import  declaration *before* the 
module  declaration, i.e.


   import I
   module M where
   foo = True

or even

   import I where
   module M where
   foo = True

This way, it is clear that the module M opens an inner scope and that 
the export list of M uses the names from the inner scope.


Actually, the latter syntax should be

   import I in ...
   let import I in ...

The idea is that this mirrors a  let  expression. (The "where" keyword 
would be misleading.)



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: Proposal: Scoping rule change

2012-07-25 Thread Heinrich Apfelmus

Lennart Augustsson wrote:

It's not often that one gets the chance to change something as
fundamental as the scoping rules of a language.  Nevertheless, I would
like to propose a change to Haskell's scoping rules.

The change is quite simple.  As it is, top level entities in a module
are in the same scope as all imported entities.  I suggest that this
is changed to that the entities from the module are in an inner scope
and do not clash with imported identifiers.

Why?  Consider the following snippet

module M where
import I
foo = True


I like it.

That said, how does the the fact that the scope is nested affect the 
export list? If the module scope is inside the scope of the imports, 
then this means the name  I.foo  should appear in the export list, not 
foo , because the latter is in the outermost scope.


I think the solution to these problems is to rearrange the  import 
declarations so that the syntax mirrors the scoping rules. In other 
words, I boldly propose to move the  import  declaration *before* the 
module  declaration, i.e.


   import I
   module M where
   foo = True

or even

   import I where
   module M where
   foo = True

This way, it is clear that the module M opens an inner scope and that 
the export list of M uses the names from the inner scope.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: String != [Char]

2012-03-24 Thread Heinrich Apfelmus

Edward Kmett wrote:

Like I said, my objection to including Text is a lot less strong than
my feelings on any notion of deprecating String.

[..]

The pedagogical concern is quite real, remember many introductory
lanuage classes have time to present Haskell and the list data type
and not much else. Showing parsing through pattern matching on
strings makes a very powerful tool, its harder to show that with
Text.

[..]

The major benefits of Text come from FFI opportunities, but even
there if you dig into its internals it has to copy out of the array
to talk to foreign functions because it lives in unpinned memory
unlike ByteString.


I agree with Edward Kmett on the virtues of  String = [Char]  for 
learning Haskell. I'm teaching beginners regularly and it is simply 
eye-opening for them that they can use the familiar list operations to 
solve real world problems which usually involve textual data.


Which brings me to the fundamental question behind this proposal: Why do 
we need Text at all? What are its virtues and how do they compare? What 
is the trade-off? (I'm not familiar enough with the Text library to 
answer these.)


To put it very pointedly: is a %20 performance increase on the current 
generation of computers worth the cost in terms of ease-of-use, when the 
performance can equally be gained by buying a faster computer or more 
RAM? I'm not sure whether I even agree with this statement, but this is 
the trade-off we are deciding on.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: PROPOSAL: Include record puns in Haskell 2011

2010-02-26 Thread Heinrich Apfelmus
Simon Marlow wrote:
> While I agree with these points, I was converted to record punning
> (actually record wildcards) when I rewrote the GHC IO library.  Handle
> is a record with 12 or so fields, and there are literally dozens of
> functions that start like this:
> 
>   flushWriteBuffer :: Handle -> IO ()
>   flushWriteBuffer Handle{..} = do
> 
> if I had to write out the field names I use each time, and even worse,
> think up names to bind to each of them, it would be hideous.

What about using field names as functions?

flushWriteBuffer h@(Handle {}) = do
... buffer h ...

Of course, you always have to drag  h  around.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: Proposal: Hexadecimal floating point constants

2010-02-20 Thread Heinrich Apfelmus
Nick Bowler wrote:
> I'd like to propose what I believe is a simple but valuable extension to
> Haskell that I haven't seen proposed elsewhere.
> 
> C has something it calls hexadecimal floating constants, and it would be
> very nice if Haskell had it too.  For floating point systems where the
> radix is a power of two (very common), they offer a means of clearly and
> exactly specifying any finite floating point value.
>
> [..]
> 
> Similarly, the greatest finite double value can be written as
> 0x1.fp+1023.
> 
> These constants have the form
> 
>   0x[HH][.H]p[+/-]DDD

If you don't want to wait on an (uncertain) inclusion into the Haskell
standard, you can implement a small helper function to that effect
yourself; essentially using  encodeFloat .


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


Re: Unsafe hGetContents

2009-10-11 Thread Heinrich Apfelmus
Iavor Diatchki wrote:
> Hello,
> 
> well, I think that the fact that we seem to have a program context
> that can distinguish "f1" from "f2" is worth discussing because I
> would have thought that in a pure language they are interchangable.
> The question is, does the context in Oleg's example really distinguish
> between "f1" and "f2"?  You seem to be saying that this is not the
> case:  in both cases you end up with the same non-deterministic
> program that reads two numbers from the standard input and subtracts
> them but you can't assume anything about the order in which the
> numbers are extracted from the input---it is merely an artifact of the
> GHC implementation that with "f1" the subtraction always happens the
> one way, and with "f2" it happens the other way.
>
> I can (sort of) buy this argument, after all, it is quite similar to
> what happens with asynchronous exceptions (f1 (error "1") (error "2")
> vs f2 (error "1") (error "2")).  Still, the whole thing does not
> "smell right":  there is some impurity going on here, and trying to
> offload the problem onto the IO monad only makes reasoning about IO
> computations even harder (and it is petty hard to start with).  So,
> discussion and alternative solutions should be strongly encouraged, I
> think.

To put it in different words, here an elaboration on what exactly the
non-determinism argument is:


Consider programs  foo1  and  foo2  defined as

foo :: (a -> b -> c) -> IO String
foo f = Control.Exception.catch
(evaluate (f (error "1") (error "2")) >> return "3")
(\(ErrorCall s) -> return s)

foo1  = foo f1  where  f1 x y = x `seq` y `seq` ()
foo2  = foo f2  where  f2 x y = y `seq` x `seq` ()

Knowing how exceptions and  seq  behave in GHC, it is straightforward to
prove that

foo1  = return "1"
foo2  = return "2"

which clearly violates referential transparency. This is bad, so the
idea is to disallow the proof.


In particular, the idea is that referential transparency can be restored
if we only allow proofs that work for all evaluation orders, which is
equivalent to introducing non-determinism. In other words, we are only
allowed to prove

foo1  = return "1"  or  return "2"
foo2  = return "1"  or  return "2"

Moreover, we can push the non-determinism into the IO type and pretend
that pure functions  A -> B  are semantically lifted to  Nondet A ->
Nondet B  with some kind of  fmap .


The same goes for  hGetContents : if you use it twice on the same
handle, you're only allowed to prove non-deterministic behavior, which
is not very useful if you want a deterministic program. But you are
allowed to prove deterministic results if you use it with appropriate
caution.


In other words, the language semantics guarantees less than GHC actually
does. In particular, the semantics only allows reasoning that is
independent of the evaluation order and this means to treat IO as
non-deterministic in certain cases.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: Haskell 2010: libraries

2009-07-16 Thread Heinrich Apfelmus
Simon Marlow wrote:
> Ian Lynagh wrote:
>> Simon Marlow wrote:
>>> But there's a solution: we could remove the "standard" modules from
>>> base, and have them only provided by haskell-std (since base will just
>>> be a re-exporting layer on top of base-internals, this will be easy to
>>> do).  Most packages will then have dependencies that look like
>>>
>>>build-depends: base-4.*, haskell-std-2010
>>
>> We'll probably end up with situations where one dependency of a package
>> needs haskell-std-2010, and another needs haskell-std-2011. I don't know
>> which impls support that at the moment.
> 
> That's the case with base-3/base-4 at the moment.  Is it a problem?

I think the issue raised is the diamond import problem, for instance
that say the list type from  haskell-std-2010  is spuriously different
from the one in  haskell-std-2011 .

This would affect new programs based on the 2011 standard that want to
use older libraries based on the 2010 standard; the point being that the
latter are "intentionally" not updated to the newer standard.

Of course, that's just the base-3 / base-4  issue which can be solved;
it's just that it's not automatic but needs explicit work by
implementors every time there is a new library standard.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: Haskell 2010: libraries

2009-07-10 Thread Heinrich Apfelmus
Simon Marlow wrote:
> Heinrich Apfelmus wrote:
>>
>> If I understand that correctly, this would mean to simply include the
>> particular version of a library that happens to be the current one at
>> the report deadline. In other words, the report specifies that say
>> version 4.1.0.0 of the base library is the standard one for 2010.
>>
>> Since old library versions are archived on hackage, this looks like a
>> cheap and easy solution to me. It's more an embellishment of alternative
>> 1. than a genuine 3.
> 
> So, just to be clear, you're suggesting that we
> 
>   - remove the whole of the Library Report,
> 
>   - declare a list of packages and versions that we consider
> to be the standard libraries for Haskell 2010.

Yes.

> This would be a bold step, in that we would be effectively standardising
> a lot more libraries than the current language standard.  The base
> package is a fairly random bag of library modules, for instance.  It
> contains a lot of modules that are only implemented by GHC.  It contains
> backwards compatibility stuff (Control.OldException), and stuff that
> doesn't really belong (Data.HashTable).  Perhaps we could explicitly
> list the modules that the standard requires.

Oh, that sounds more bold than I expected it to be. Yes, I agree that we
should exclude modules that don't really belong; this should be cheap to
implement.

> On the other hand, this would be a useful step, in that it gives users a
> wide base of libraries to rely on.  And it's cheap to implement in the
> report.
> 
> Any other thoughts?

The way I imagine it is that the libraries thus standardized will *not*
be the libraries that most people are going to use; the latest versions
of the  base  library or the Haskell Platform will define a current set
of "standard" libraries.

Rather, I imagine the libraries standardized in the report to be a
reference for writing code that does not need to be updated when  base
or the HP change. Put differently, if I put the

  {-# LANGUAGE Haskell'2010 #-}

flag into my source code, then I'm assured that it will compile for all
eternity because my favorite compiler is going to use the  base  library
specified in the report instead of the newest  base  library available
on hackage. This requires compiler support.

In other words, this is option 1. embellished with the cheapest way of
blessing a bunch libraries for the purpose of backward compatibility.


This may not be the best solution to the  backward compatibility VS
libraries change  dilemma, but I think it reflects current practice. I
can write strict H98 if I want to, but most of the time I'm just going
to use the latest  base  anyway.



On a side note, if Haskell 2010 gets a library report, then I think this
should be in the form of a simple package on hackage, named something
like "haskell2010-libraries".


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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


Re: Haskell 2010: libraries

2009-07-08 Thread Heinrich Apfelmus
Bulat Ziganshin wrote:
> Simon Marlow wrote:
> 
>>   3. Update the libraries to match what we have at the moment.
>>  e.g. rename List to Data.List, and add the handful of
>>  functions that have since been added to Data.List.  One
>>  problem with this is that these modules are then tied to
>>  the language definition, and can't be changed through
>>  the usual library proposal process.
> 
> not necessarily. we already apply versioning to these libs, it may be
> made official in Report too. i.e. Report defines libraries standard
> for year 2010 (like it defines language standard for only one year),
> while we continue to improve libraries that will eventually become
> version standard for year 2011 (or higher)

If I understand that correctly, this would mean to simply include the
particular version of a library that happens to be the current one at
the report deadline. In other words, the report specifies that say
version 4.1.0.0 of the base library is the standard one for 2010.

Since old library versions are archived on hackage, this looks like a
cheap and easy solution to me. It's more an embellishment of alternative
1. than a genuine 3.


Regards,
apfelmus

--
http://apfelmus.nfshost.com

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