source/build separation

2011-11-15 Thread Rustom Mody
I am building ghc from source.

The building page
http://hackage.haskell.org/trac/ghc/wiki/Building/Using#Sourcetreesandbuildtrees
mentions lndir for separating source trees from build trees.

Given how much detail is generally given for individual commands eg
http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources

maybe it would be nice to have a (typical?) lndir command also given?

Also there is a mention about using a local git clone here
 http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources
Arent these two alternative ways with similar intent - viz. keeping source
pristine and separating build 'messiness'?
Or do people use both git (local) clone + lndir?  If so why?


Rusi

[ghc noob here: Please tell me if this is the wrong list to ask this kind
of question :-) ]
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Why not allow empty record updates?

2011-11-15 Thread Yitzchak Gale
Simon Peyton-Jones wrote:
 Trouble is, what type does this have?
       f x = x {}

Malcolm Wallace wrote:
 Empty record patterns {} are permitted, even for types
 that are not declared with named fields.
 So I don't see why an empty record update should
 require the type to be declared with named fields either.

Yes. The translation of record updates given in the Report
makes perfect sense for {}. It is only forbidden by
n = 1, but no reason is given for that restriction.

According to that translation, the type of x {} is
the type of the case expression it translates to.

Thanks,
Yitz

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


Re: Why not allow empty record updates?

2011-11-15 Thread Ian Lynagh
On Tue, Nov 15, 2011 at 08:34:01AM +, Malcolm Wallace wrote:
 
 On 14 Nov 2011, at 22:09, Simon Peyton-Jones wrote:
 
  Trouble is, what type does this have?
  
  f x = x {}
 
 f :: a - a

That wouldn't help the original poster, as it is incompatible with
f :: Foo Clean - Foo Dirty


Thanks
Ian


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


RE: Why not allow empty record updates?

2011-11-15 Thread Simon Peyton-Jones
Hmm yes. Fair enough.  Does anyone care enough?  I can see (now) that it 
wouldn't really be hard.

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Yitzchak Gale
| Sent: 15 November 2011 11:16
| To: Malcolm Wallace
| Cc: GHC-users List
| Subject: Re: Why not allow empty record updates?
| 
| Simon Peyton-Jones wrote:
|  Trouble is, what type does this have?
|        f x = x {}
| 
| Malcolm Wallace wrote:
|  Empty record patterns {} are permitted, even for types
|  that are not declared with named fields.
|  So I don't see why an empty record update should
|  require the type to be declared with named fields either.
| 
| Yes. The translation of record updates given in the Report
| makes perfect sense for {}. It is only forbidden by
| n = 1, but no reason is given for that restriction.
| 
| According to that translation, the type of x {} is
| the type of the case expression it translates to.
| 
| Thanks,
| Yitz
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


RE: Why not allow empty record updates?

2011-11-15 Thread Simon Peyton-Jones
|   Trouble is, what type does this have?
|  
| f x = x {}
| 
|  f :: a - a
| 
| That wouldn't help the original poster, as it is incompatible with
| f :: Foo Clean - Foo Dirty

Ah!  *That* is why I said it was awkward.  Thanks Ian. 

Simon

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


Re: source/build separation

2011-11-15 Thread Simon Marlow

On 15/11/2011 10:21, Rustom Mody wrote:

I am building ghc from source.

The building page
http://hackage.haskell.org/trac/ghc/wiki/Building/Using#Sourcetreesandbuildtrees
mentions lndir for separating source trees from build trees.

Given how much detail is generally given for individual commands eg
http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources

maybe it would be nice to have a (typical?) lndir command also given?


Sure.  It's just

  $ mkdir build
  $ cd build
  $ lndir source

but lndir is not a standard tool (any more), so you might have to build 
it yourself.  There are sources in the GHC source tree in utils/lndir.


Note the GHC build works perfectly well without a separate build tree, 
and I think that's the way most people do it.



Also there is a mention about using a local git clone here
http://hackage.haskell.org/trac/ghc/wiki/Building/GettingTheSources
Arent these two alternative ways with similar intent - viz. keeping
source pristine and separating build 'messiness'?
Or do people use both git (local) clone + lndir?  If so why?


Right - arguably you can just clone a new source tree for each build 
that you want.  I use separate build trees for two reasons:


 - my source trees are on a backed-up network file system, but the
   build trees are on fast local disk.

 - I can have several builds on different machines all using the same
   source tree.

On my laptop the situation is similar, but my source trees are in my 
home dir which is an ecryptfs and the build trees are outside on the 
unencrypted partition.  Not only is ecryptfs too slow for building on, 
it also doesn't work properly (there's some bug related to time stamps 
that I never managed to narrow down, it results in unnecessary rebuilding).


You could do all this with git clones, but it would mean extra shuffling 
of patches around.  If you're happy with that, then that's fine - use 
whatever scheme you're more comfortable with.


Cheers,
Simon

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


Re: source/build separation

2011-11-15 Thread David Brown

On Tue, Nov 15, 2011 at 04:47:18PM +, Simon Marlow wrote:

You could do all this with git clones, but it would mean extra 
shuffling of patches around.  If you're happy with that, then that's 
fine - use whatever scheme you're more comfortable with.


There's a script in git's contrib directory called 'git-new-workdir'.
You can use it to have multiple working directories that share the
same git back end.  I'll typically do something like:

  git clone ... mainsrc
  git new-workdir mainsrc worksrc
  cd worksrc
  git checkout -b work
.. hack ..
  git add; git commit
  cd ../mainsrc
  git merge work  # or cherry-pick or whatever
  test away

I find it helps when making multiple patches to be able to test that
the intermediate versions work, without having to mess up my main
working tree.

To install the script, just copy it somewhere into your path, and make
it executable.  Or make an executable script in your path like this:

  #!/bin/sh
  exec sh /usr/share/doc/git/contrib/workdir/git-new-workdir $@

David

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


Re: Why not allow empty record updates?

2011-11-15 Thread Yitzchak Gale
Simon Peyton-Jones wrote:
 Trouble is, what type does this have?
   f x = x {}

Malcolm Wallace wrote:
 f :: a - a

Ian Lynagh wrote:
 That wouldn't help the original poster, as it is incompatible with
 f :: Foo Clean - Foo Dirty

Only because in that expression the type of x is not known.

 ...the whole feature of type-changing update is (as you know)
 a bit obscure and not widely used, so it'd be adding
 complexity to an already-dark corner.

To me, at least, that is surprising. The report implies that
record updates are just sugar for the given case expression.
Whether or not it changes a type parameter seems
unimportant.

In fact, I would even advocate adding a line of explanation
in the Report that this is a convenient way of copying
a value from an ADT to itself with a different type
as its parameter. I agree with Malcolm that this is
analogous to using empty record syntax in a pattern
to avoid hard-coding the number of parameter to
a constructor.

I usually avoid using the combination of type parameters and
record syntax altogether, mainly because this obvious syntax
doesn't work. Perhaps that's the reason why type-changing
update is not widely used.

(Admittedly, I didn't think of Herbert's trick. But doesn't
that seem like somewhat of an ugly hack?)

Are you hesitant because of implementation difficulty,
or only because you are worried about the semantics
being confusing? In my opinion, it's more confusing
the way it is now.

Thanks,
Yitz

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


Re: Why not allow empty record updates?

2011-11-15 Thread wagnerdm

Quoting Yitzchak Gale g...@sefer.org:


Yes. The translation of record updates given in the Report
makes perfect sense for {}. It is only forbidden by
n = 1, but no reason is given for that restriction.


It doesn't make sense to me. The translation explodes a value into a  
case statement over its constructors; what constructors do you use  
when you don't know the type of the value?


When n = 1, you know the type of the value by looking where the field  
came from, and hence which constructors to use in the case statement.


~d

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


RE: instance union proposal

2011-11-15 Thread Simon Peyton-Jones
Serge

I'm afraid I don't really follow your proposal in detail, but I think it may be 
a version of the proposal described here
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
Perhaps you could see if the design there would meet your goals.

Simon

|  -Original Message-
|  From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Serge D. Mechveliani
|  Sent: 12 November 2011 10:51
|  To: glasgow-haskell-users@haskell.org
|  Subject: instance union proposal
|  
|  Dear Haskell implementors,
|  
|  I suggest the following small extension to the instance declaration in
|  the language. So far -- for  Haskell + glasgow-ext.
|  I think that they are easy to implement.
|  This is the  instance union  proposal.
|  It is needed to write shorter several `old' instance declarations.
|  This will make programs easier to read.
|  It suggests the so-called
| inherited decl  and, more general,  union decl.
|  
|  Inherited instance decl proposal
|  
|  
|  Union several instance declarations with the same condition part and such
|  that among the conclusion  classes there exists some which inherits all
|  others.
|  Example 1.  My program uses the class tower
|  
| Field a Picture 1.
| |
| ERing
| |
| CRing a
| |
| Ring a
|/\
|  AddGroup a  MulSemigroup a
|   |  |
|  AddSemigroup a  |
|   \ /
|Set a
|  
|  -- | means that the upper inherits from the lower.
|  Now, by the application meaning, I need to write
|  
|instance (Show a, CRing a) = CRing (Pol a)
|  where
|  implement operations of Set
|  implement operations of AddGroup
|  ...
|  implement operations of CRing
|  
|  From the class decls it is clear to the compiler that  CRing  inherits
|  all that is lower on the picture. Therefore, the conditional
|  `instance (Show a, CRing a) =' and 'where'
|  is written only once.
|  In the existing language, I need to write this conditional 6 times.
|  
|  
|  Union instance decl proposal
|  
|  
|  It is a generalization for  inhereted decl.
|  
|  instances (cond_1, ..., cond_n) -- of the type parameters a_1 ... a_m
|=
|typeTuple (params)  has  {conclInstList}
|where
|implement operations for each member of conclInstList.
|  
|  It differs from the old instance declaration in that
|  1) it unions several old declarations having the same conditional part,
|  2) each member of conclInstList can be conditional,
|  3) in conclInstList it can be skipped any instance which is inherited
| by some other member in this list.
|  
|  params is a subset of {a_1 ... a_m},
|  typeTuple (params)
|  is a tuple of type expressions, as in old declaration,
|  for example,  `(a, b)', `Vector a', `[(a,b), Vector a]'.
|  It is the argument for the conclusion instance declarations.
|  
|  conclInstList is a list of inst-members separated by comma.
|  Each member of  conclInstList  is either an
|  old  conclusion instance declaration
|  or a conditional declaration.
|  
|  Example.
|  In the situtation of  Picture 1,  I need to declare
|  
|instance (Show a, CRing a) =
| (Pol a) has { CRing,  if (has a Field) then ERing }
|  where
|  define operations for  Set (Pol a)
|  define operations for  AddSemigroup (Pol a)
|  ...
|  define operations for  CRing (Polynomial a)
|  
|  define operations for  ERing (Pol a)  -- this part has the
|-- additional condition  (Field a)
|  
|  Its meaning is that the complier extends this into several `old'
|  instance declarations:
|instance (Show a, CRing a) = Set (Pol a) where
|  define operations for  Set (Pol a)
|...
|instance (Show a, CRing a) = CRing (Pol a) where
|  define operations for  Set (Pol a)
|  
|instance (Show a, Field a) = ERing (Pol a) where
|define operations for  ERing (Pol a)
|  
|  (in the last decl `Field a' has been moved to LHS).
|  
|  In this example  typeTuple === (Pol a).
|  For bi-parametric instances, the concusion part may be, for example
|=
|[a, Pol a] has {Foo1, Foo2} ...
|  
|  This means the two instance assertions  Foo1 a (Pol a),  Foo a (Pol a),
|  and `[a, Pol a]' is the agrument tuple for the instance conclusions.
|  
|  
|  This is a draft proposal. If the idea is accepted, some generalizations
|  and 

Re: Why not allow empty record updates?

2011-11-15 Thread wren ng thornton

On 11/15/11 12:33 PM, Yitzchak Gale wrote:

Simon Peyton-Jones wrote:

Trouble is, what type does this have?
   f x = x {}


Malcolm Wallace wrote:

f :: a -  a


Ian Lynagh wrote:

That wouldn't help the original poster, as it is incompatible with
f :: Foo Clean -  Foo Dirty


Only because in that expression the type of x is not known.


...the whole feature of type-changing update is (as you know)
a bit obscure and not widely used, so it'd be adding
complexity to an already-dark corner.


To me, at least, that is surprising. The report implies that
record updates are just sugar for the given case expression.
Whether or not it changes a type parameter seems
unimportant.

In fact, I would even advocate adding a line of explanation
in the Report that this is a convenient way of copying
a value from an ADT to itself with a different type
as its parameter. I agree with Malcolm that this is
analogous to using empty record syntax in a pattern
to avoid hard-coding the number of parameter to
a constructor.

I usually avoid using the combination of type parameters and
record syntax altogether, mainly because this obvious syntax
doesn't work. Perhaps that's the reason why type-changing
update is not widely used.

(Admittedly, I didn't think of Herbert's trick. But doesn't
that seem like somewhat of an ugly hack?)

Are you hesitant because of implementation difficulty,
or only because you are worried about the semantics
being confusing? In my opinion, it's more confusing
the way it is now.


For what it's worth, I do the exact same thing in the project I've been 
working on. The phantom type is a clean/dirty bit even :)


It's an incredibly helpful thing to have for records. Especially for the 
context I'm in: I'm generating summary data over gobs of input, but the 
input can come incrementally. So long as the core of the summary is 
correct, then I don't care about maintaining the cache fields while I'm 
just shoveling data in; but I do want to make sure the caches are valid 
before I try to get any information out. This is exactly the sort of 
type-level hackery which makes Haskell a joy to work in and other 
languages such a pain.


So far I've just defined helper functions to adjust the phantom type[1], 
each of which is implemented by (\x - x { foo = foo x }). It's a 
horrible hack, but at least it's hidden away in library functions 
instead of something I have to look at. The annoying part is that when I 
adjust the members of the records, if I remove or rename foo then I have 
to fix all those coercion functions too.



[1] set bit to Clean, set bit to Dirty, and unsafe set bit to 'a'.

--
Live well,
~wren

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


Re: Why not allow empty record updates?

2011-11-15 Thread Edward Kmett


Sent from my iPad

On Nov 15, 2011, at 7:18 PM, wren ng thornton w...@freegeek.org wrote:

 On 11/15/11 12:33 PM, Yitzchak Gale wrote:
 Simon Peyton-Jones wrote:
 Trouble is, what type does this have?
   f x = x {}
 
 Malcolm Wallace wrote:
 f :: a -  a
 
 Ian Lynagh wrote:
 That wouldn't help the original poster, as it is incompatible with
 f :: Foo Clean -  Foo Dirty
 
 Only because in that expression the type of x is not known.
 
 ...the whole feature of type-changing update is (as you know)
 a bit obscure and not widely used, so it'd be adding
 complexity to an already-dark corner.
 
 To me, at least, that is surprising. The report implies that
 record updates are just sugar for the given case expression.
 Whether or not it changes a type parameter seems
 unimportant.
 
 In fact, I would even advocate adding a line of explanation
 in the Report that this is a convenient way of copying
 a value from an ADT to itself with a different type
 as its parameter. I agree with Malcolm that this is
 analogous to using empty record syntax in a pattern
 to avoid hard-coding the number of parameter to
 a constructor.
 
 I usually avoid using the combination of type parameters and
 record syntax altogether, mainly because this obvious syntax
 doesn't work. Perhaps that's the reason why type-changing
 update is not widely used.
 
 (Admittedly, I didn't think of Herbert's trick. But doesn't
 that seem like somewhat of an ugly hack?)
 
 Are you hesitant because of implementation difficulty,
 or only because you are worried about the semantics
 being confusing? In my opinion, it's more confusing
 the way it is now.
 
 For what it's worth, I do the exact same thing in the project I've been 
 working on. The phantom type is a clean/dirty bit even :)
 
 It's an incredibly helpful thing to have for records. Especially for the 
 context I'm in: I'm generating summary data over gobs of input, but the input 
 can come incrementally. So long as the core of the summary is correct, then I 
 don't care about maintaining the cache fields while I'm just shoveling data 
 in; but I do want to make sure the caches are valid before I try to get any 
 information out. This is exactly the sort of type-level hackery which makes 
 Haskell a joy to work in and other languages such a pain.
 
 So far I've just defined helper functions to adjust the phantom type[1], each 
 of which is implemented by (\x - x { foo = foo x }). It's a horrible hack, 
 but at least it's hidden away in library functions instead of something I 
 have to look at. The annoying part is that when I adjust the members of the 
 records, if I remove or rename foo then I have to fix all those coercion 
 functions too.
 


My biggest issue is loss of sharing, but you could always use

castFoo = asTypeOf unsafeCoerce $ \x - x { foo = foo x }

to maximize sharing, but that doesn't help with the code rewriting,

Or less horrifically just carry the phantom in a newtype wrapper wrapped around 
your record, and cast by putting it on and taking it off, which also maximizes 
sharing in exchange for newtype noise on access.


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