Re: Type operators in GHC

2012-01-19 Thread Joachim Breitner
Hello,

while I agree that operators are usually more useful als type
constructors than as type variables, I’m wondering if it is future-proof
to completely get rid of a possibility for infix type variables. With
the type class system getting stronger and stronger, would this not mean
that there will be more and more use cases for infix type variables?
Maybe the change should at keep a (small) window open. Maybe, similar to
the current situation, a special character to indicate variables, not
constructors?

(I have no good idea, but here is at least one: A dot '.' as the first
character indicates a type variable; compared to a ':' this is a
non-capitalized character).


Also, is there maybe another way of distinguishing constructors and
variables, besides capitalization, that works equally well for operators
and non-operators? That could also help if a user would like to use
unicode characters in the name of a constructor that are letters but
don’t have a upper or titlecase variant. But then, this has probably
been given thought a long time ago, without a better solution than
capitalization resp. leading ':'.

Greetings,
Joachim

-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread Malcolm Wallace
Sorry to pick on your post in particular Matthew, but I have been seeing a lot 
of this on the Haskell lists lately.

I find it completely unreasonable for a reply to a very long post to quote the 
entire text, only to add a single line at the bottom (or worse, embedded in the 
middle somewhere).  In this case, there are 7 pages of quotation before your 
one-sentence contribution.  (That is on my laptop.  I dread to think how many 
pages it represents on a smartphone screen...)  Usually, if I need to scroll 
even to the second page-worth of quotation and have still not found any new 
text, I now just delete the post without reading it.

It is a failure to communicate well, on the part of the writer who values their 
own time more highly than that of their intended readers.  Even the 
much-maligned top-posting style, as forced upon Outlook users (and as I am 
doing right here), is preferable to the failure to trim, or to get to the point 
quickly.  My inbox has 1600 unread messages in it, and life is just too short. 
 So I offer this plea as a constructive social suggestion - if you want your 
ideas to reach their intended audience, don't annoy them before they have even 
seen what you want to say.

Regards,
Malcolm


On 15 Jan 2012, at 20:33, Matthew Farkas-Dyck wrote:

 On 13/01/2012, Simon Peyton-Jones simo...@microsoft.com wrote:
 Thanks to Greg for leading the records debate.  I apologise that I
 don't have enough bandwidth to make more than an occasional
 contribution.  Greg's new wiki page, and the discussion so far has
 clarified my thinking, and this message tries to express that new
 clarity.  I put a conclusion at the end.
 
 Simon
 
 Overview
 
 It has become clear that there are two elements to pretty much all the
 proposals we have on the table.  Suppose we have two types, 'S' and 'T',
 both with a field 'f', and you want to select field 'f' from a record 'r'.
 Somehow you have to disambiguate which 'f' you mean.
 
 (Plan A) Disambiguate using qualified names.  To select field f, say
(S.f r) or (T.f r) respectively.
 
 (Plan B) Disambiguate using types. This approach usually implies
 dot-notation.
 If  (r::S), then (r.f) uses the 'f' from 'S', and similarly if
 (r::T).
 
 Note that
 
 * The Frege-derived records proposal (FDR), uses both (A) and (B)
  http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
 
 * The Simple Overloaded Record Fields (SORF) proposal uses only (B)
  http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
 
 * The Type Directed Name Resolution proposal (TDNR) uses only (B)
 
 http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution
 
 I know of no proposal that advocates only (A).  It seems that we are agreed
 that we must make use of types to disambigute common cases.
 
 Complexities of (Plan B)
 
 Proposal (Plan B) sounds innocent enough.  But I promise you, it isn't.
 There has ben some mention of the left-to-right bias of Frege type
 inference engine; indeed the wohle explanation of which programs are
 accepted and which are rejected, inherently involves an understanding
 of the type inference algorithm.  This is a Very Bad Thing when the
 type inference algorithm gets complicated, and GHC's is certainly
 complicated.
 
 Here's an example:
 
   type family F a b
   data instance F Int [a] = Mk { f :: Int }
 
   g :: F Int b  - ()
   h :: F a [Bool] - ()
 
   k x = (g x, x.f, h x)
 
 Consider type inference on k.  Initially we know nothing about the
 type of x.
 * From the application (g x) we learn that x's type has
   shape (F Int something).
 * From the application (h x) we learn that x's type has
   shape (F something else [Bool])
 * Hence x's type must be (F Int [Bool])
 * And hence, using the data family we can see which field
   f is intended.
 
 Notice that
 a) Neither left to right nor right to left would suffice
 b) There is significant interaction with type/data families
(and I can give you more examples with classes and GADTs)
 c) In passing we note that it is totally unclear how (Plan A)
would deal with data families
 
 This looks like a swamp.  In a simple Hindley-Milner typed language
 you might get away with some informal heuristics, but Haskell is far
 too complicated.
 
 Fortunately we know exactly what to do; it is described in some detail
 in our paper Modular type inference with local assumptions
 http://www.haskell.org/haskellwiki/Simonpj/Talk:OutsideIn
 
 The trick is to *defer* all these decisions by generating *type constraints*
 and solving them later.  We express it like this:
 
   G, r:t1  |-  r.f : t2,  (Has t1 f t2)
 
 This says that if r is in scope with type t1, then (r.f) has type t2,
 plus the constraint (Has t1 f t2), which we read as saying
 
   Type t1 must have a field f of type t2
 
 We gather up all the constraints and solve them.  In solving them
 we may figure out t1 from some *other* constraint (to the left or
 right, 

Re: Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread José Pedro Magalhães
Hi,

One could also argue that a good email client should automatically hide
long quotes. In fact, I guess many people are not even aware of the problem
because their client does this.


Cheers,
Pedro

On Thu, Jan 19, 2012 at 11:14, Malcolm Wallace malcolm.wall...@me.comwrote:

 Sorry to pick on your post in particular Matthew, but I have been seeing a
 lot of this on the Haskell lists lately.

 I find it completely unreasonable for a reply to a very long post to quote
 the entire text, only to add a single line at the bottom (or worse,
 embedded in the middle somewhere).  In this case, there are 7 pages of
 quotation before your one-sentence contribution.  (That is on my laptop.  I
 dread to think how many pages it represents on a smartphone screen...)
  Usually, if I need to scroll even to the second page-worth of quotation
 and have still not found any new text, I now just delete the post without
 reading it.

 It is a failure to communicate well, on the part of the writer who values
 their own time more highly than that of their intended readers.  Even the
 much-maligned top-posting style, as forced upon Outlook users (and as I am
 doing right here), is preferable to the failure to trim, or to get to the
 point quickly.  My inbox has 1600 unread messages in it, and life is just
 too short.  So I offer this plea as a constructive social suggestion - if
 you want your ideas to reach their intended audience, don't annoy them
 before they have even seen what you want to say.

 Regards,
Malcolm


 On 15 Jan 2012, at 20:33, Matthew Farkas-Dyck wrote:

  On 13/01/2012, Simon Peyton-Jones simo...@microsoft.com wrote:
  Thanks to Greg for leading the records debate.  I apologise that I
  don't have enough bandwidth to make more than an occasional
  contribution.  Greg's new wiki page, and the discussion so far has
  clarified my thinking, and this message tries to express that new
  clarity.  I put a conclusion at the end.
 
  Simon
 
  Overview
  
  It has become clear that there are two elements to pretty much all the
  proposals we have on the table.  Suppose we have two types, 'S' and 'T',
  both with a field 'f', and you want to select field 'f' from a record
 'r'.
  Somehow you have to disambiguate which 'f' you mean.
 
  (Plan A) Disambiguate using qualified names.  To select field f, say
 (S.f r) or (T.f r) respectively.
 
  (Plan B) Disambiguate using types. This approach usually implies
  dot-notation.
  If  (r::S), then (r.f) uses the 'f' from 'S', and similarly if
  (r::T).
 
  Note that
 
  * The Frege-derived records proposal (FDR), uses both (A) and (B)
   http://hackage.haskell.org/trac/ghc/wiki/Records/NameSpacing
 
  * The Simple Overloaded Record Fields (SORF) proposal uses only (B)
 
 http://hackage.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
 
  * The Type Directed Name Resolution proposal (TDNR) uses only (B)
 
 
 http://hackage.haskell.org/trac/haskell-prime/wiki/TypeDirectedNameResolution
 
  I know of no proposal that advocates only (A).  It seems that we are
 agreed
  that we must make use of types to disambigute common cases.
 
  Complexities of (Plan B)
  
  Proposal (Plan B) sounds innocent enough.  But I promise you, it isn't.
  There has ben some mention of the left-to-right bias of Frege type
  inference engine; indeed the wohle explanation of which programs are
  accepted and which are rejected, inherently involves an understanding
  of the type inference algorithm.  This is a Very Bad Thing when the
  type inference algorithm gets complicated, and GHC's is certainly
  complicated.
 
  Here's an example:
 
type family F a b
data instance F Int [a] = Mk { f :: Int }
 
g :: F Int b  - ()
h :: F a [Bool] - ()
 
k x = (g x, x.f, h x)
 
  Consider type inference on k.  Initially we know nothing about the
  type of x.
  * From the application (g x) we learn that x's type has
shape (F Int something).
  * From the application (h x) we learn that x's type has
shape (F something else [Bool])
  * Hence x's type must be (F Int [Bool])
  * And hence, using the data family we can see which field
f is intended.
 
  Notice that
  a) Neither left to right nor right to left would suffice
  b) There is significant interaction with type/data families
 (and I can give you more examples with classes and GADTs)
  c) In passing we note that it is totally unclear how (Plan A)
 would deal with data families
 
  This looks like a swamp.  In a simple Hindley-Milner typed language
  you might get away with some informal heuristics, but Haskell is far
  too complicated.
 
  Fortunately we know exactly what to do; it is described in some detail
  in our paper Modular type inference with local assumptions
  http://www.haskell.org/haskellwiki/Simonpj/Talk:OutsideIn
 
  The trick is to *defer* all these decisions by generating *type
 constraints*
  and solving them later.  We express it like this:
 
G, 

Re: Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread Henrik Nilsson

Hi,

On 01/19/2012 10:22 AM, Jos Pedro Magalhes wrote:

One could also argue that a good email client should automatically hide
long quotes. In fact, I guess many people are not even aware of the
problem because their client does this.


But then what is the point of including the text in the first place if
it is understood it is only there to be hidden?

Besides, personally, I don't want my e-mail client to attempt (and,
short of it truly having an understanding of what is being said,
inevitably fail) to understand which parts of an e-mail are of
interest to me and which parts are not.

No, I agree completely with Malcolm: not taking the time to
quote ONLY what is of relevance to provide the immediately
relevant context for a point one wishes to make is a failure
of communication and, indeed, an abuse of other's time.

Thanks, Malcolm, well said!

/Henrik

--
Henrik Nilsson
School of Computer Science
The University of Nottingham
n...@cs.nott.ac.uk

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread Matthew Farkas-Dyck
On 19/01/2012, Malcolm Wallace malcolm.wall...@me.com wrote:
 I find it completely unreasonable for a reply to a very long post to quote
 the entire text, only to add a single line at the bottom (or worse, embedded
 in the middle somewhere).  In this case, there are 7 pages of quotation
 before your one-sentence contribution.  (That is on my laptop.  I dread to
 think how many pages it represents on a smartphone screen...)  Usually, if I
 need to scroll even to the second page-worth of quotation and have still not
 found any new text, I now just delete the post without reading it.

 Regards,
 Malcolm


Sorry.

The reason that I have done so is that my primary mail client (GMail
web) automatically folds quoted text (marked by  at start of line).
(I'm not sure whether my secondary client (mutt) can do so.)

When I first saw this message, I thought I would be slammed for
top-posts (I have been guilty a few times).

Anyhow, I shall keep this in mind.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type operators in GHC

2012-01-19 Thread Matthew Farkas-Dyck
On 19/01/2012, Joachim Breitner m...@joachim-breitner.de wrote:
 (I have no good idea, but here is at least one: A dot '.' as the first
 character indicates a type variable; compared to a ':' this is a
 non-capitalized character).

So that all symbols that start in dot are variables, and all others
are types/constructors?

 Also, is there maybe another way of distinguishing constructors and
 variables, besides capitalization, that works equally well for operators
 and non-operators? That could also help if a user would like to use
 unicode characters in the name of a constructor that are letters but
 don’t have a upper or titlecase variant. But then, this has probably
 been given thought a long time ago, without a better solution than
 capitalization resp. leading ':'.

Sometimes I thought to use ∀ to quantify over type variables, as
over term variables, at least as an option.

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type operators in GHC

2012-01-19 Thread Joachim Breitner
Hi,

Am Donnerstag, den 19.01.2012, 07:11 -0500 schrieb Matthew Farkas-Dyck:
 On 19/01/2012, Joachim Breitner m...@joachim-breitner.de wrote:
  (I have no good idea, but here is at least one: A dot '.' as the first
  character indicates a type variable; compared to a ':' this is a
  non-capitalized character).
 
 So that all symbols that start in dot are variables, and all others
 are types/constructors?

exactly, that would be an option to get the benefit of the proposal
(nicer type constructor operator names) without giving up completely on
type variable operators names.

Greetings,
Joachim
-- 
Joachim nomeata Breitner
  m...@joachim-breitner.de  |  nome...@debian.org  |  GPG: 0x4743206C
  xmpp: nome...@joachim-breitner.de | http://www.joachim-breitner.de/



signature.asc
Description: This is a digitally signed message part
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type operators in GHC

2012-01-19 Thread Ian Lynagh
On Thu, Jan 19, 2012 at 07:11:19AM -0500, Matthew Farkas-Dyck wrote:
 
 Sometimes I thought to use ∀ to quantify over type variables, as
 over term variables, at least as an option.

Do you mean that in

f :: (x, X, (+), (:+))

only x would be a type variable and X, (+), (:+) would be type
constructors, but that in

g :: forall y, Y, (*), (:*) .
 (x, X, (+), (:+), y, Y, (*), (:*))

y, Y, (*), (:*) would be type variables and x, X, (+), (:+) would be
whatever is in scope (constructors, unless there is an enclosing forall
that binds them)?

Perhaps we should be heading towards a case-insensitive syntax for type
names.


Thanks
Ian


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Posting etiquette, was Re: Records in Haskell

2012-01-19 Thread Tyson Whitehead
On January 19, 2012 05:14:30 Malcolm Wallace wrote:
 I find it completely unreasonable for a reply to a very long post to quote
 the entire text, only to add a single line at the bottom (or worse,
 embedded in the middle somewhere).

+1

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: named pipes

2012-01-19 Thread Serge D. Mechveliani
To my 
 Dear GHC team,
 I am testing the IO operations of GHC with the Unix  named pipes
 [..]

Albert Y. C. Lai  writes on 19 Jan 2012

 Main.hs  does not open fromA at all. (fromA_IO is dead code.) This causes
 fifo2.c to be hung whenever it opens fromA. From the man page of mkfifo(3)
 on Linux:
 Opening a FIFO for reading normally blocks until some other process opens
 the same FIFO for writing, and vice versa. See fifo(7) for nonblocking
 handling of FIFO special files.

I see now. Thank you.
The intitial example was with a real usage of toA and fromA, and it did 
not work as expected. Then, I simplified it, but just missed the point 
that ./Main does not really open  fromA. 
Now, I provide below the initial example.

Can people explain, please, why it performs so? 

 In the sister thread in haskell-cafe, the addition of unsafePerformIO
 throws further disorder into these highly order-sensitive operations.

By the way, can you respond (if not to `glasgow' then to mech...@botik.ru)
to my last simple and concrete question to  cafe  on the subject of   
unsafePerformIO ?

Anyway, the below example is free of  unsafePerformIO.
And I need to delay the remaining questions on  unsafePerformIO
(for myself and maybe, for `cafe') until the current example is fixed.

Regards, 

--
Sergei
mech...@botik.ru




I am testing the IO operations of GHC with the Unix named pipes --
(in  ghc-7.01  under Debian Linux).

In the below example, 
the pipe pair are created bymkfifo toA
mkfifo fromA,

`main'  in  Main.hs  opens  toAfor writing,
 opens  fromA  for reading,
 outputs  A1  to  toA,
 inputs the respond string  str'  from  fromA,
 prints  str'  to the screen.
The C program  fifo2  
  opens  toAfor reading,
  opens  fromA  for writing,
  inputs a string  str  from  toA,
  converts  str  to the lower case, obtaining  str'
  outputs  str'  to  fromA.

Main.hs   is built by   ghc --make Main,
The C program is built by   gcc -o fifo2 fifo2.c

First,  ./fifo2   is run on  terminal-2,
then./Mainis run on  terminal-1.

The effect is that   fifo2(on terminal-2)  hangs silent, and
 Main.hs  (on terminal-1)  reports only 
  str1  --  hFlush done, and then hangs.

This contradicts to that  ./Main   must print  str'  to the screen.

The modules are as follows.


-- Main.hs -
import System.IO (IOMode(..), IO(..), Handle, openFile, hPutStr, 
   hFlush, hGetLine)
dir = showString /home/mechvel/ghc/notes/npipe/

toA_IO   = openFile (dir toA)   WriteMode   :: IO Handle
fromA_IO = openFile (dir fromA) ReadMode  

axiomIO :: Handle - Handle - String - IO String
axiomIOh1h2str = 
   do
   hPutStr h1 str 
   hFlush h1
   putStr hFlush done\n
   str' - hGetLine h2
   putStr (concat [hGetLine -  , str', \n])
   return str'
main = do
   h1 - toA_IO
   h2 - fromA_IO
   putStr str1  --   
   str1' - axiomIO h1 h2 A1
   putStr (str1' ++ \n)


--- fifo2.c -
#include stdio.h
#include string.h  
#define BOUND 64
static  char  str[BOUND];

main() 
{
  int l, i;   FILE *toA, *fromA;

  toA = fopen(/home/mechvel/ghc/notes/npipe/toA, r);
  if (toA == NULL) {perror(fopen(toA, r)  failed:  );  return;};   
  fromA = fopen(/home/mechvel/ghc/notes/npipe/fromA, w);
  if (fromA == NULL) {perror(fopen(fromA, w)  failed:  );  return;};   

  if (fgets(str, BOUND, toA) == NULL) { 
 perror(fgets(str, bound, toA)  failed:  ); return;
  };
  printf(input = %s\n, str);
 
  l = strlen(str) - 1; 
  i = 0;   // convert the string to the lower case
  while (i  l) {str[i] = tolower(str[i]);  i++;}

  printf(output = %s\n, str);
  fputs(str, fromA);
  fflush(fromA);
  printf(output to fromA done\n);
  return;
} 
-


Comparison with C - C
-
If both programs are in C, then the whole loop of the string exchange 
(with  fifo2.c  rewritten into a loop) works as needed, both for the 
variants with fgets and with `read'.


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type operators in GHC

2012-01-19 Thread Matthew Farkas-Dyck
On 19/01/2012, Ian Lynagh ig...@earth.li wrote:
 Do you mean that in

 f :: (x, X, (+), (:+))

 only x would be a type variable and X, (+), (:+) would be type
 constructors, but that in

 g :: forall y, Y, (*), (:*) .
  (x, X, (+), (:+), y, Y, (*), (:*))

 y, Y, (*), (:*) would be type variables and x, X, (+), (:+) would be
 whatever is in scope (constructors, unless there is an enclosing forall
 that binds them)?

Just so.

 Perhaps we should be heading towards a case-insensitive syntax for type
 names.

I've often had that thought myself, for types and terms both. It would
make it much nicer to do general numeric computations in Haskell (e.g.
fluid mechanics) since one could use upper-case term names, which are
often customary. I actually designed a compiled-to-Haskell language
for just this reason (for fluid mechanics lab), but it's very crude.

That said, for word-names, the case-sensitive system we have is nice and brief.


 Thanks
 Ian


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


strange behavior of let in ghci

2012-01-19 Thread 山本和彦
Hello,

I met strange behavior of let in ghci 7.0.4. The following works well.

 :m Data.List
 let compFst (n1,s1) (n2,s2) = compare n1 n2
 maximumBy compFst [(1, boo), (3, foo), (2, woo)]
(3,foo)

But if I bind maximumBy compFst to chooseMax with let, it causes
error:

 let chooseMax = maximumBy compFst
 chooseMax [(1,boo),(3,foo),(2,woo)]
interactive:1:33:
No instance for (Num ())
  arising from the literal `2'
Possible fix: add an instance declaration for (Num ())
In the expression: 2
In the expression: (2, woo)
In the first argument of `chooseMax', namely
  `[(1, boo), (3, foo), (2, woo)]'

It's very strange to me. Why does this happen? 

:t says:

 :t maximumBy compFst
maximumBy compFst :: Ord a = [(a, t)] - (a, t)
 :t chooseMax 
chooseMax :: [((), t)] - ((), t)

I'm writing a tutorial of Haskell and I would like to define chooseMax
in ghci with let without specifying its signature.

--Kazu

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: strange behavior of let in ghci

2012-01-19 Thread Antoine Latter
On Thu, Jan 19, 2012 at 10:55 PM, Kazu Yamamoto k...@iij.ad.jp wrote:
 Hello,

 I met strange behavior of let in ghci 7.0.4. The following works well.


You're running into the monomorphism restriction:
http://www.haskell.org/haskellwiki/Monomorphism_restriction


 let chooseMax = maximumBy compFst

If you re-define this to be:

 let chooseMax x = maximumBy compFst x

you'll get around it in the easiest way.

You can also turn off the restriction at the command-line with the
argument '-XNoMonomorphismRestriction', I think.

Antoine

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: strange behavior of let in ghci

2012-01-19 Thread 山本和彦
Antoine, 

 You're running into the monomorphism restriction:
 http://www.haskell.org/haskellwiki/Monomorphism_restriction

Oh. Thanks.

 You can also turn off the restriction at the command-line with the
 argument '-XNoMonomorphismRestriction', I think.

I will use ghci -XNoMonomorphismRestriction in my tutorial. Thank
you again.

--Kazu

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users