Re: optimizing StgPtr allocate (Capability *cap, W_ n)

2014-10-16 Thread Edward Z. Yang
Hi Bulat,

This seems quite reasonable to me. Have you eyeballed the assembly
GCC produces to see that the hotpath is improved? If you can submit
a patch that would be great!

Cheers,
Edward

Excerpts from Bulat Ziganshin's message of 2014-10-14 10:08:59 -0700:
 Hello Glasgow-haskell-users,
 
 i'm looking a the 
 https://github.com/ghc/ghc/blob/23bb90460d7c963ee617d250fa0a33c6ac7bbc53/rts/sm/Storage.c#L680
 
 if i correctly understand, it's speed-critical routine?
 
 i think that it may be improved in this way:
 
 StgPtr allocate (Capability *cap, W_ n)
 {
 bdescr *bd;
 StgPtr p;
 
 TICK_ALLOC_HEAP_NOCTR(WDS(n));
 CCS_ALLOC(cap-r.rCCCS,n);
 
 /// here starts new improved code:
 
 bd = cap-r.rCurrentAlloc;
 if (bd == NULL || bd-free + n  bd-end) {
 if (n = LARGE_OBJECT_THRESHOLD/sizeof(W_)) {
 
 }
 if (bd-free + n = bd-start + BLOCK_SIZE_W)
 bd-end = min (bd-start + BLOCK_SIZE_W, bd-free + 
 LARGE_OBJECT_THRESHOLD)
 goto usual_alloc;
 }
 
 }
 
 /// and here it stops
 
 usual_alloc:
 p = bd-free;
 bd-free += n;
 
 IF_DEBUG(sanity, ASSERT(*((StgWord8*)p) == 0xaa));
 return p;
 }
 
 
 i  think  it's  obvious - we consolidate two if's on the crirical path
 into the single one plus avoid one ADD by keeping highly-useful bd-end 
 pointer
 
 further   improvements   may   include   removing  bd==NULL  check  by
 initializing bd-free=bd-end=NULL   and   moving   entire   if body
 into   separate   slow_allocate()  procedure  marked  noinline  with
 allocate() probably marked as forceinline:
 
 StgPtr allocate (Capability *cap, W_ n)
 {
 bdescr *bd;
 StgPtr p;
 
 TICK_ALLOC_HEAP_NOCTR(WDS(n));
 CCS_ALLOC(cap-r.rCCCS,n);
 
 bd = cap-r.rCurrentAlloc;
 if (bd-free + n  bd-end)
 return slow_allocate(cap,n);
 
 p = bd-free;
 bd-free += n;
 
 IF_DEBUG(sanity, ASSERT(*((StgWord8*)p) == 0xaa));
 return p;
 }
 
 this  change  will  greatly simplify optimizer's work. according to my
 experience   current  C++  compilers  are  weak  on  optimizing  large
 functions with complex execution paths and such transformations really
 improve the generated code
 
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type checker plugins

2014-10-16 Thread Adam Gundry
Hi Iavor,


On 13/10/14 21:34, Iavor Diatchki wrote:
 Hello,
 
 We now have an implementation of type-checker with plugin support.   If
 you are interested in trying it out:
 
   - Checkout and build the `wip/tc-plugins` branch of GHC


Thanks, this is great! I'd been working on a similar implementation, but
yours is much better integrated. I am trying to adapt my units of
measure plugin to work with this interface, and work out what else I
need in TcPluginM.

One problem I've run into is transforming the flattened CFunEqCans into
unflattened form (so the flatten-skolems don't get in the way of
AG-unification). Do you know if there is an easy way to do this, or do I
need to rebuild the tree manually in the plugin?

Also, I notice that you are providing only equality constraints to the
plugin. Is there any reason we can't make other types of constraint
available as well? For example, one might want to introduce a typeclass
with a special solution strategy (cf. Coercible, or the Has class in
OverloadedRecordFields).


Cheers,

Adam


   - As an example, I've extracted my work on using an SMT solver at the
 type level as a separate plugin:
   
   https://github.com/yav/type-nat-solver
 
- To see how to invoke a module that uses a plugin, have a look in
 `examples/A.hs`.
  (Currently, the plugin assumes that you have `cvc4` installed and
 available in the path).
 
 - Besides this, we don't have much documentation yet.  For hackers:
 we tried to use `tcPlugin` on
 `TcPlugin` in the names of all things plugin related, so you could
 grep for this.  The basic API
  types and functions are defined in `TcRnTypes` and `TcRnMonad`.
 
 Happy hacking,
 -Iavor


-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Type checker plugins

2014-10-16 Thread Simon Peyton Jones
This will become easier, I think. look on wip/new-flatten-skoelms-Aug14.  I'm 
now unflattening after solving the flat constraints. 

Simon

|  -Original Message-
|  From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
|  boun...@haskell.org] On Behalf Of Adam Gundry
|  Sent: 16 October 2014 11:59
|  To: Iavor Diatchki
|  Cc: glasgow-haskell-users@haskell.org
|  Subject: Re: Type checker plugins
|  
|  Hi Iavor,
|  
|  
|  On 13/10/14 21:34, Iavor Diatchki wrote:
|   Hello,
|  
|   We now have an implementation of type-checker with plugin support.
|  If
|   you are interested in trying it out:
|  
| - Checkout and build the `wip/tc-plugins` branch of GHC
|  
|  
|  Thanks, this is great! I'd been working on a similar implementation,
|  but yours is much better integrated. I am trying to adapt my units of
|  measure plugin to work with this interface, and work out what else I
|  need in TcPluginM.
|  
|  One problem I've run into is transforming the flattened CFunEqCans
|  into unflattened form (so the flatten-skolems don't get in the way of
|  AG-unification). Do you know if there is an easy way to do this, or do
|  I need to rebuild the tree manually in the plugin?
|  
|  Also, I notice that you are providing only equality constraints to the
|  plugin. Is there any reason we can't make other types of constraint
|  available as well? For example, one might want to introduce a
|  typeclass with a special solution strategy (cf. Coercible, or the Has
|  class in OverloadedRecordFields).
|  
|  
|  Cheers,
|  
|  Adam
|  
|  
| - As an example, I've extracted my work on using an SMT solver at
|   the type level as a separate plugin:
|  
| https://github.com/yav/type-nat-solver
|  
|  - To see how to invoke a module that uses a plugin, have a look
|  in
|   `examples/A.hs`.
|(Currently, the plugin assumes that you have `cvc4` installed
|  and
|   available in the path).
|  
|   - Besides this, we don't have much documentation yet.  For
|  hackers:
|   we tried to use `tcPlugin` on
|   `TcPlugin` in the names of all things plugin related, so you
|  could
|   grep for this.  The basic API
|types and functions are defined in `TcRnTypes` and `TcRnMonad`.
|  
|   Happy hacking,
|   -Iavor
|  
|  
|  --
|  Adam Gundry, Haskell Consultant
|  Well-Typed LLP, http://www.well-typed.com/
|  ___
|  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: Type checker plugins

2014-10-16 Thread Adam Gundry
Thanks Simon, your branch does make it a lot more feasible to unflatten,
so I'll just go ahead and implement that in my plugin for now.

Eric, that's fair enough, and I don't have any concrete use cases for
non-equality constraints at the moment. I'm just keen to minimize the
restrictions placed on plugins, because it is much easier to recompile a
plugin than make changes in GHC itself!

On that note, I still wonder if it would be better to define TcPluginM
as a wrapper around TcS rather than TcM. While in principle TcM should
suffice, in practice GHC sometimes uses TcS for things that a plugin
might want (I've run into TcSMonad.matchFam, which could easily be
implemented in TcM instead). Is there any downside to defining a nice
API in TcPluginM but providing an escape hatch to TcS, not just TcM?

Thanks,

Adam


On 16/10/14 16:21, Eric Seidel wrote:
 Our branch is actually based on yours Simon, are there any changes in the 
 past week that we should pull in for people who want to experiment?
 
 Adam, we talked about passing other constraints to the plugins, but didn't 
 have a concrete use-case at the time, so we just kept it as simple as 
 possible. I don't see a reason to hide constraints if, as you say, there are 
 plugins that may want to solve them. 
 
 Eric
 
 Sent from my iPhone
 
 On Oct 16, 2014, at 07:08, Simon Peyton Jones simo...@microsoft.com wrote:

 This will become easier, I think. look on wip/new-flatten-skoelms-Aug14.  
 I'm now unflattening after solving the flat constraints. 

 Simon

 |  -Original Message-
 |  From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
 |  boun...@haskell.org] On Behalf Of Adam Gundry
 |  Sent: 16 October 2014 11:59
 |  To: Iavor Diatchki
 |  Cc: glasgow-haskell-users@haskell.org
 |  Subject: Re: Type checker plugins
 |  
 |  Hi Iavor,
 |  
 |  
 |  On 13/10/14 21:34, Iavor Diatchki wrote:
 |   Hello,
 |  
 |   We now have an implementation of type-checker with plugin support.
 |  If
 |   you are interested in trying it out:
 |  
 | - Checkout and build the `wip/tc-plugins` branch of GHC
 |  
 |  
 |  Thanks, this is great! I'd been working on a similar implementation,
 |  but yours is much better integrated. I am trying to adapt my units of
 |  measure plugin to work with this interface, and work out what else I
 |  need in TcPluginM.
 |  
 |  One problem I've run into is transforming the flattened CFunEqCans
 |  into unflattened form (so the flatten-skolems don't get in the way of
 |  AG-unification). Do you know if there is an easy way to do this, or do
 |  I need to rebuild the tree manually in the plugin?
 |  
 |  Also, I notice that you are providing only equality constraints to the
 |  plugin. Is there any reason we can't make other types of constraint
 |  available as well? For example, one might want to introduce a
 |  typeclass with a special solution strategy (cf. Coercible, or the Has
 |  class in OverloadedRecordFields).
 |  
 |  
 |  Cheers,
 |  
 |  Adam
 |  
 |  
 | - As an example, I've extracted my work on using an SMT solver at
 |   the type level as a separate plugin:
 |  
 | https://github.com/yav/type-nat-solver
 |  
 |  - To see how to invoke a module that uses a plugin, have a look
 |  in
 |   `examples/A.hs`.
 |(Currently, the plugin assumes that you have `cvc4` installed
 |  and
 |   available in the path).
 |  
 |   - Besides this, we don't have much documentation yet.  For
 |  hackers:
 |   we tried to use `tcPlugin` on
 |   `TcPlugin` in the names of all things plugin related, so you
 |  could
 |   grep for this.  The basic API
 |types and functions are defined in `TcRnTypes` and `TcRnMonad`.
 |  
 |   Happy hacking,
 |   -Iavor

-- 
Adam Gundry, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Hiding import behaviour

2014-10-16 Thread Malcolm Gooding
With the prelude changes that people have been discussing recently
I've been wondering is there any reason why importing an identifier
explicitly and unqualified doesn't automatically hide any implicit
imports of the same identifier? Specifically I'm wondering about cases
where you've imported an identifier explicitly from only one module,
like this:

module Foo (x, ...) where { ... }
module Bar (x, ...) where { ... }

import Bar
import Foo (x)

Even if you needed a pragma to enable it I can't think of any sensible
reason why that shouldn't be equivalent to:

import Bar hiding (x)
import Foo (x)

I don't know much of GHC's internals, but it seems like a pretty
minimal change. Typing rules remain the same; explicit imports just
shadow implicits. So importing multiple identifiers both implicitly or
both explicitly would remain ambiguous.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Hiding import behaviour

2014-10-16 Thread David Feuer
I think this is a great idea. I also think it should apply to the name
shadowing warning—identifiers imported implicitly should never trigger that.

On Thu, Oct 16, 2014 at 6:19 PM, Malcolm Gooding goodi...@gmail.com wrote:

 With the prelude changes that people have been discussing recently
 I've been wondering is there any reason why importing an identifier
 explicitly and unqualified doesn't automatically hide any implicit
 imports of the same identifier? Specifically I'm wondering about cases
 where you've imported an identifier explicitly from only one module,
 like this:

 module Foo (x, ...) where { ... }
 module Bar (x, ...) where { ... }

 import Bar
 import Foo (x)

 Even if you needed a pragma to enable it I can't think of any sensible
 reason why that shouldn't be equivalent to:

 import Bar hiding (x)
 import Foo (x)

 I don't know much of GHC's internals, but it seems like a pretty
 minimal change. Typing rules remain the same; explicit imports just
 shadow implicits. So importing multiple identifiers both implicitly or
 both explicitly would remain ambiguous.
 ___
 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: Hiding import behaviour

2014-10-16 Thread Austin Seipp
My first thought is: Wouldn't this make it impossible to reorder or
sort imports lexicographically (or otherwise), without fully parsing,
renaming and typechecking the code?

For example, I often use ghc-mod plus stylish-haskell to order and
format my imports. If there is no syntactic indication that one import
should be hidden (and another preferred) as there is now, then
reordering the imports of a working program willy-nilly could result
in a program that no longer typechecks (or worse, one that does, but
is now wrong).

Maybe there are some cases today where something like this could
happen, but this seems awfully, awfully implicit and hard-to-follow as
a language feature.

In general I think a program that has imports like this that may clash
can be automated to make it easier to manage - but ultimately such
imports tend to represent a complex relationship between a module and
its dependencies - I'd prefer it if these were as clear as possible.

On Thu, Oct 16, 2014 at 5:19 PM, Malcolm Gooding goodi...@gmail.com wrote:
 With the prelude changes that people have been discussing recently
 I've been wondering is there any reason why importing an identifier
 explicitly and unqualified doesn't automatically hide any implicit
 imports of the same identifier? Specifically I'm wondering about cases
 where you've imported an identifier explicitly from only one module,
 like this:

 module Foo (x, ...) where { ... }
 module Bar (x, ...) where { ... }

 import Bar
 import Foo (x)

 Even if you needed a pragma to enable it I can't think of any sensible
 reason why that shouldn't be equivalent to:

 import Bar hiding (x)
 import Foo (x)

 I don't know much of GHC's internals, but it seems like a pretty
 minimal change. Typing rules remain the same; explicit imports just
 shadow implicits. So importing multiple identifiers both implicitly or
 both explicitly would remain ambiguous.
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




-- 
Regards,

Austin Seipp, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: Type checker plugins

2014-10-16 Thread Simon Peyton Jones
| Thanks Simon, your branch does make it a lot more feasible to unflatten,
| so I'll just go ahead and implement that in my plugin for now.

Actually it would be worth pausing.  If you get the latest Unflattening is now 
done by getInertUnsolved, which itself is called by solveFlatWanteds, 
immediately after calling solveFlats.  And solveFlats (which used to be called 
solveInteract) is where Iavor has the plugin interface.

In short, if you'd like to see unflattened constraints, rather than flattened 
ones, that would be easy.

Unflattening yourself is inadvisable.  The unflattening code in 
getInertUnsolved is quite remarkably tricky and it took me some time get it 
right.  (I have to write a long Note before committing it to head.)

All this is in the just-committed wip/new-flatten-skolems-Aug14 branch

Simon

| -Original Message-
| From: Adam Gundry [mailto:a...@well-typed.com]
| Sent: 16 October 2014 21:50
| To: Eric Seidel; Simon Peyton Jones
| Cc: Iavor Diatchki; glasgow-haskell-users@haskell.org
| Subject: Re: Type checker plugins
| 
| Thanks Simon, your branch does make it a lot more feasible to unflatten,
| so I'll just go ahead and implement that in my plugin for now.
| 
| Eric, that's fair enough, and I don't have any concrete use cases for
| non-equality constraints at the moment. I'm just keen to minimize the
| restrictions placed on plugins, because it is much easier to recompile a
| plugin than make changes in GHC itself!
| 
| On that note, I still wonder if it would be better to define TcPluginM
| as a wrapper around TcS rather than TcM. While in principle TcM should
| suffice, in practice GHC sometimes uses TcS for things that a plugin
| might want (I've run into TcSMonad.matchFam, which could easily be
| implemented in TcM instead). Is there any downside to defining a nice
| API in TcPluginM but providing an escape hatch to TcS, not just TcM?
| 
| Thanks,
| 
| Adam
| 
| 
| On 16/10/14 16:21, Eric Seidel wrote:
|  Our branch is actually based on yours Simon, are there any changes in
| the past week that we should pull in for people who want to experiment?
| 
|  Adam, we talked about passing other constraints to the plugins, but
| didn't have a concrete use-case at the time, so we just kept it as simple
| as possible. I don't see a reason to hide constraints if, as you say,
| there are plugins that may want to solve them.
| 
|  Eric
| 
|  Sent from my iPhone
| 
|  On Oct 16, 2014, at 07:08, Simon Peyton Jones simo...@microsoft.com
| wrote:
| 
|  This will become easier, I think. look on wip/new-flatten-skoelms-
| Aug14.  I'm now unflattening after solving the flat constraints.
| 
|  Simon
| 
|  |  -Original Message-
|  |  From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
|  |  boun...@haskell.org] On Behalf Of Adam Gundry
|  |  Sent: 16 October 2014 11:59
|  |  To: Iavor Diatchki
|  |  Cc: glasgow-haskell-users@haskell.org
|  |  Subject: Re: Type checker plugins
|  |
|  |  Hi Iavor,
|  |
|  |
|  |  On 13/10/14 21:34, Iavor Diatchki wrote:
|  |   Hello,
|  |  
|  |   We now have an implementation of type-checker with plugin
| support.
|  |  If
|  |   you are interested in trying it out:
|  |  
|  | - Checkout and build the `wip/tc-plugins` branch of GHC
|  |
|  |
|  |  Thanks, this is great! I'd been working on a similar
| implementation,
|  |  but yours is much better integrated. I am trying to adapt my units
| of
|  |  measure plugin to work with this interface, and work out what else
| I
|  |  need in TcPluginM.
|  |
|  |  One problem I've run into is transforming the flattened CFunEqCans
|  |  into unflattened form (so the flatten-skolems don't get in the way
| of
|  |  AG-unification). Do you know if there is an easy way to do this, or
| do
|  |  I need to rebuild the tree manually in the plugin?
|  |
|  |  Also, I notice that you are providing only equality constraints to
| the
|  |  plugin. Is there any reason we can't make other types of constraint
|  |  available as well? For example, one might want to introduce a
|  |  typeclass with a special solution strategy (cf. Coercible, or the
| Has
|  |  class in OverloadedRecordFields).
|  |
|  |
|  |  Cheers,
|  |
|  |  Adam
|  |
|  |
|  | - As an example, I've extracted my work on using an SMT solver
| at
|  |   the type level as a separate plugin:
|  |  
|  | https://github.com/yav/type-nat-solver
|  |  
|  |  - To see how to invoke a module that uses a plugin, have a
| look
|  |  in
|  |   `examples/A.hs`.
|  |(Currently, the plugin assumes that you have `cvc4`
| installed
|  |  and
|  |   available in the path).
|  |  
|  |   - Besides this, we don't have much documentation yet.  For
|  |  hackers:
|  |   we tried to use `tcPlugin` on
|  |   `TcPlugin` in the names of all things plugin related, so you
|  |  could
|  |   grep for this.  The basic API
|  |types and functions are defined in `TcRnTypes` and
| `TcRnMonad`.
|  |  
|  |   Happy hacking,
|  |   -Iavor
| 
| 

Re: Type checker plugins

2014-10-16 Thread Barney Hilken
I can think of a use for a non-equality constraint: an alphabetical ordering on 
Symbol. This would allow experimental implementations of extensible records 
(without shadowing) which keep the labels sorted.

An order constraint on Nat might be useful, too.

Barney.

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


Re: Type checker plugins

2014-10-16 Thread Carter Schonwald
the alphabetical ordering on Symbol is already exposed via TypeLits... this
would be some machinery to help maintain that ordering with less user
intervention?

On Thu, Oct 16, 2014 at 6:59 PM, Barney Hilken b.hil...@ntlworld.com
wrote:

 I can think of a use for a non-equality constraint: an alphabetical
 ordering on Symbol. This would allow experimental implementations of
 extensible records (without shadowing) which keep the labels sorted.

 An order constraint on Nat might be useful, too.

 Barney.

 ___
 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: Type checker plugins

2014-10-16 Thread Barney Hilken
Ok, I hadn't realised that. Looking in the user's guide, I see = and =? for 
Nat, but I couldn't find anything about Symbol. I must try them out!


 From: Carter Schonwald carter.schonw...@gmail.com
 
 the alphabetical ordering on Symbol is already exposed via TypeLits... this 
 would be some machinery to help maintain that ordering with less user 
 intervention?
 
 On Thu, Oct 16, 2014 at 6:59 PM, Barney Hilken b.hil...@ntlworld.com wrote:
 I can think of a use for a non-equality constraint: an alphabetical ordering 
 on Symbol. This would allow experimental implementations of extensible 
 records (without shadowing) which keep the labels sorted.
 
 An order constraint on Nat might be useful, too.
 
 Barney.
 
 ___
 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: Hiding import behaviour

2014-10-16 Thread David Feuer
It should be good enough (for what you're talking about) to hide them all.
Turn

import A (foo)
import B (bar)
import C hiding (baz)
import D

into

import A (foo)
import B (bar)
import C hiding (foo,bar,baz)
import D hiding (foo,bar)

There's no reason to worry about hiding nonexistent identifiers, I don't
think.

On Thu, Oct 16, 2014 at 7:10 PM, htebalaka goodi...@gmail.com wrote:

 Well I suppose tooling might need to be aware of the feature depending on
 what it does, but I don't see why the code actually typechecking would need
 to be dependent on ordering. When I say shadowing I don't mean explicitly
 having any explicit import create a new scope, since in that case it would
 be sensitive to re-ordering, which I agree would be bad. My thought would
 be
 first you would need to parse all the imports to see which identifiers they
 import, then do another pass to change the imports to hide any identifiers
 that should be shadowed.

 So in the example I gave you would need to be aware that Foo exports x,
 because otherwise there would be no way to know that x needs to be hidden
 from Bar. I assume GHC already would have access to that information
 though.



 --
 View this message in context:
 http://haskell.1045720.n5.nabble.com/Hiding-import-behaviour-tp5758155p5758161.html
 Sent from the Haskell - Glasgow-haskell-users mailing list archive at
 Nabble.com.
 ___
 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: Hiding import behaviour

2014-10-16 Thread htebalaka
Yeah, I just realized that would work too. You would still need to do two
passes over the imports, so foo and bar are hidden from anything imported
above A. Though while we're reasoning syntactically, you would also need to
hide them from the Prelude if it was being implicitly imported.



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/Hiding-import-behaviour-tp5758155p5758166.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Type checker plugins

2014-10-16 Thread Carter Schonwald
http://hackage.haskell.org/package/base-4.7.0.1/docs/GHC-TypeLits.html

type family CmpSymbol m n :: Ordering
http://hackage.haskell.org/package/base-4.7.0.1/docs/Data-Ord.html#t:Ordering

On Thu, Oct 16, 2014 at 7:14 PM, Barney Hilken b.hil...@ntlworld.com
wrote:

 Ok, I hadn't realised that. Looking in the user's guide, I see = and =?
 for Nat, but I couldn't find anything about Symbol. I must try them out!


  From: Carter Schonwald carter.schonw...@gmail.com
 
  the alphabetical ordering on Symbol is already exposed via TypeLits...
 this would be some machinery to help maintain that ordering with less user
 intervention?
 
  On Thu, Oct 16, 2014 at 6:59 PM, Barney Hilken b.hil...@ntlworld.com
 wrote:
  I can think of a use for a non-equality constraint: an alphabetical
 ordering on Symbol. This would allow experimental implementations of
 extensible records (without shadowing) which keep the labels sorted.
 
  An order constraint on Nat might be useful, too.
 
  Barney.
 
  ___
  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: Type checker plugins

2014-10-16 Thread Carter Schonwald
mind you, i'm not sure what the ordering is specified to be :)

On Thu, Oct 16, 2014 at 9:24 PM, Carter Schonwald 
carter.schonw...@gmail.com wrote:

 http://hackage.haskell.org/package/base-4.7.0.1/docs/GHC-TypeLits.html

 type family CmpSymbol m n :: Ordering
 http://hackage.haskell.org/package/base-4.7.0.1/docs/Data-Ord.html#t:Ordering

 On Thu, Oct 16, 2014 at 7:14 PM, Barney Hilken b.hil...@ntlworld.com
 wrote:

 Ok, I hadn't realised that. Looking in the user's guide, I see = and =?
 for Nat, but I couldn't find anything about Symbol. I must try them out!


  From: Carter Schonwald carter.schonw...@gmail.com
 
  the alphabetical ordering on Symbol is already exposed via TypeLits...
 this would be some machinery to help maintain that ordering with less user
 intervention?
 
  On Thu, Oct 16, 2014 at 6:59 PM, Barney Hilken b.hil...@ntlworld.com
 wrote:
  I can think of a use for a non-equality constraint: an alphabetical
 ordering on Symbol. This would allow experimental implementations of
 extensible records (without shadowing) which keep the labels sorted.
 
  An order constraint on Nat might be useful, too.
 
  Barney.
 
  ___
  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: Windows build broken in Linker.c

2014-10-16 Thread John Wiegley
 Simon Marlow marlo...@gmail.com writes:

 I was working on a fix yesterday but ran out of time. Frankly this code is a
 nightmare, every time I touch it it breaks on some platform - this time I
 validated on 64 bit Windows but not 32. Aargh indeed.

Before I start breaking this code up into pieces, do we have tests that solely
target the linking sub-components, and how would I run them?  Perhaps I can
setup a fleet of virtual machines to try it out in every combination where we
expect the code to compile.

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