Re: GHC 7.0.4 on Lion

2011-07-25 Thread Luca Ciciriello
Yes. You have also to install Xcode 4.1.
Preinstalled Xcode 4.0.1 doesn't work on Lion

Luca.

On Jul 26, 2011, at 3:02 AM, Jack Henahan wrote:

> Does this mean I can finally switch back to Lion and expect GHC to work? 
> That's very exciting news! :D
> 
> On Jul 25, 2011, at 10:33 AM, David Peixotto wrote:
> 
>> I think the warnings are not a big concern. I silence both of them by adding 
>> -optl"-Wl,-no_compact_unwind,-no_pie" to my ghc options in /usr/bin/ghc.
>> 
>> In 10.7 they changed the default linking options to create a PIE (position 
>> independent executable). To create a PIE you have to compile all code as 
>> position independent, which is the default option of GHC on mac os x. For 
>> performance reasons some code is compiled with absolute references (like the 
>> gmp library code in your example) so it cannot be used when creating a PIE. 
>> The advantage of a PIE executable is that it is more secure because the OS 
>> can load it at a random base address.
>> 
>> I believe the "compact unwind" warning is related to the creation of unwind 
>> frames for error handling with exceptions in languages like C++. There are 
>> some more details in this trac ticket: 
>> http://hackage.haskell.org/trac/ghc/ticket/5019. I'm not sure what the 
>> advantage of the compact unwind is, but it sounds like it could make the 
>> executable smaller.
>> 
>> -David
>> 
>> On Jul 25, 2011, at 7:59 AM, Luca Ciciriello wrote:
>> 
>>> Hi All.
>>> I've installed on my Mac the new MacOS X 10.7 (Lion) with Xcode 4.1
>>> 
>>> Using ghc 7.0.4 (64-bit) on that system a get the following warnings in the 
>>> linking phase:
>>> 
>>> Linking hslint ...
>>> ld: warning: could not create compact unwind for _ffi_call_unix64: does not 
>>> use RBP or RSP based frame
>>> ld: warning: PIE disabled. Absolute addressing (perhaps -mdynamic-no-pic) 
>>> not allowed in code signed PIE, but used in ___gmpn_modexact_1c_odd from 
>>> /Library/Frameworks/GHC.framework/Versions/7.0.4-x86_64/usr/lib/ghc-7.0.4/integer-gmp-0.2.0.3/libHSinteger-gmp-0.2.0.3.a(mode1o.o).
>>>  To fix this warning, don't compile with -mdynamic-no-pic or link with 
>>> -Wl,-no_pie
>>> 
>>> Is this something to worrying about?
>>> 
>>> Thanks in advance for any answer.
>>> 
>>> Luca
>>> ___
>>> 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
> 
> Jack Henahan
> jhena...@uvm.edu
> ==
> Computer science is no more about computers than astronomy is about 
> telescopes.
> -- Edsger Dijkstra
> ==
> <398E692F.gpg>
> 


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


Re: Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-25 Thread Edward Z. Yang
Hello Brandon,

The answer is subtle, and has to do with what references are kept in code,
which make an object considered reachable.  Essentially, the main thread
itself keeps the MVar live while it still has forking to do, so that
it cannot get garbage collected and trigger these errors.

Here is a simple demonstrative program:

main = do
lock <- newMVar ()
forkIO (takeMVar lock)
forkIO (takeMVar lock)
forkIO (takeMVar lock)

Consider what the underlying code needs to do after it has performed
the first forkIO.  'lock' is a local variable that the code generator
knows it's going to need later in the function body. So what does it
do? It saves it on the stack.

// R1 is a pointer to the MVar
cqo:
Hp = Hp + 8;
if (Hp > HpLim) goto cqq;
I32[Hp - 4] = spd_info;
I32[Hp + 0] = R1;
I32[Sp + 0] = R1;
R1 = Hp - 3;
I32[Sp - 4] = spe_info;
Sp = Sp - 4;
jump stg_forkzh ();

(Ignore the Hp > HpLim; that's just the heap check.)

This lives on until we continue executing the main thread at spe_info
(at which point we may or may not deallocate the stack frame).  But what
happens instead?

cqk:
Hp = Hp + 8;
if (Hp > HpLim) goto cqm;
I32[Hp - 4] = sph_info;
I32[Hp + 0] = I32[Sp + 4];
R1 = Hp - 3;
I32[Sp + 0] = spi_info;
jump stg_forkzh ();

We keep the pointer to the MVar to the stack, because we know there
is yet /another/ forkIO (takeMVar lock) coming up. (It's located at
Sp + 4; you have to squint a little since Sp is being fiddled
with, but it's still there, we just overwrite the infotable with
a new one.)

Finally, spi_info decides we don't need the contents of Sp + 4 anymore,
and overwrites it accordingly:

cqg:
Hp = Hp + 8;
if (Hp > HpLim) goto cqi;
I32[Hp - 4] = spl_info;
I32[Hp + 0] = I32[Sp + 4];
R1 = Hp - 3;
I32[Sp + 4] = spm_info;
Sp = Sp + 4;
jump stg_forkzh ();

But in the meantime (esp. between invocation 2 and 3), the MVar cannot be
garbage collected, because it is live on the stack.

Could GHC have been more clever in this case?  Not in general, since deciding
whether or not a reference will actually be used or not boils down to the
halting problem.

loop = threadDelay 100 >> loop -- prevent blackholing from discovering this
main = do
lock <- newEmptyMVar
t1 <- newEmptyMVar
forkIO (takeMVar lock >> putMVar t1 ())
forkIO (loop `finally` putMVar lock ())
takeMVar t1

Maybe we could do something where MVar references are known to be writer ends
or read ends, and let the garbage collector know that an MVar with only read
ends left is a deadlocked one.  However, this would be a very imprecise
analysis, and would not help in your original code (since all of your remaining
threads had the possibility of writing to the MVar: it doesn't become clear
that they can't until they all hit their takeMVar statements.)

Cheers,
Edward

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


Re: GHC 7.0.4 on Lion

2011-07-25 Thread Jack Henahan
Does this mean I can finally switch back to Lion and expect GHC to work? That's 
very exciting news! :D

On Jul 25, 2011, at 10:33 AM, David Peixotto wrote:

> I think the warnings are not a big concern. I silence both of them by adding 
> -optl"-Wl,-no_compact_unwind,-no_pie" to my ghc options in /usr/bin/ghc.
> 
> In 10.7 they changed the default linking options to create a PIE (position 
> independent executable). To create a PIE you have to compile all code as 
> position independent, which is the default option of GHC on mac os x. For 
> performance reasons some code is compiled with absolute references (like the 
> gmp library code in your example) so it cannot be used when creating a PIE. 
> The advantage of a PIE executable is that it is more secure because the OS 
> can load it at a random base address.
> 
> I believe the "compact unwind" warning is related to the creation of unwind 
> frames for error handling with exceptions in languages like C++. There are 
> some more details in this trac ticket: 
> http://hackage.haskell.org/trac/ghc/ticket/5019. I'm not sure what the 
> advantage of the compact unwind is, but it sounds like it could make the 
> executable smaller.
> 
> -David
> 
> On Jul 25, 2011, at 7:59 AM, Luca Ciciriello wrote:
> 
>> Hi All.
>> I've installed on my Mac the new MacOS X 10.7 (Lion) with Xcode 4.1
>> 
>> Using ghc 7.0.4 (64-bit) on that system a get the following warnings in the 
>> linking phase:
>> 
>> Linking hslint ...
>> ld: warning: could not create compact unwind for _ffi_call_unix64: does not 
>> use RBP or RSP based frame
>> ld: warning: PIE disabled. Absolute addressing (perhaps -mdynamic-no-pic) 
>> not allowed in code signed PIE, but used in ___gmpn_modexact_1c_odd from 
>> /Library/Frameworks/GHC.framework/Versions/7.0.4-x86_64/usr/lib/ghc-7.0.4/integer-gmp-0.2.0.3/libHSinteger-gmp-0.2.0.3.a(mode1o.o).
>>  To fix this warning, don't compile with -mdynamic-no-pic or link with 
>> -Wl,-no_pie
>> 
>> Is this something to worrying about?
>> 
>> Thanks in advance for any answer.
>> 
>> Luca
>> ___
>> 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

Jack Henahan
jhena...@uvm.edu
==
Computer science is no more about computers than astronomy is about telescopes.
-- Edsger Dijkstra
==


398E692F.gpg
Description: application/apple-msg-attachment




PGP.sig
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: Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-25 Thread Brandon Simmons
On Sun, Jul 24, 2011 at 10:07 PM, Edward Z. Yang  wrote:
> Excerpts from Felipe Almeida Lessa's message of Sun Jul 24 22:02:36 -0400 
> 2011:
>> Does anything change if you somehow force a GC sometime after "good2"?
>>  Perhaps with some calculation generating garbage, perhaps with
>> performGC.  IIRC, the runtime detects BlockedIndefinitelyOnMVar on GC.
>>  But I'm probably wrong =).
>
> That's correct.
>
>   resurrectThreads is called after garbage collection on the list of
>   threads found to be garbage.  Each of these threads will be woken
>   up and sent a signal: BlockedOnDeadMVar if the thread was blocked
>   on an MVar, or NonTermination if the thread was blocked on a Black
>   Hole.
>
> Cheers,
> Edward
>

Thanks, Edward. I'm going to take a look at the GHC source and see if
I can grok any of it. Any comment on whether it is correct behavior to
have the exception raised in all the threads attempting a readMVar at
once (if that's actually what's happening), even though an exception
handler will fill the MVar for subsequent threads?

I think I'm not totally clear on what qualifies as "indefinitely"

Thanks again,
Brandon

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


Re: Understanding behavior of BlockedIndefinitelyOnMVar exception

2011-07-25 Thread Brandon Simmons
On Sun, Jul 24, 2011 at 10:02 PM, Felipe Almeida Lessa
 wrote:
> On Sun, Jul 24, 2011 at 7:56 PM, Brandon Simmons
>  wrote:
>> What I think I've learned here is that the BlockedIndefinitelyOnMVar
>> exception is raised in all the blocked threads "at once" as it were.
>> That despite the fact that the handler code in 'lockPrint' restores
>> the lock for successive threads.
>>
>> This would also seem to imply that putMVar's in an exception handler
>> don't stop the runtime from raising the BlockedIndefinitelyOnMVar. But
>> that doesn't really seem right.
>
> Does anything change if you somehow force a GC sometime after "good2"?
>  Perhaps with some calculation generating garbage, perhaps with
> performGC.  IIRC, the runtime detects BlockedIndefinitelyOnMVar on GC.
>  But I'm probably wrong =).

Here is a variation that calls 'performGC' after the first thread is
forked. It prints the exception simultaneously right before  the last
'threadDelay':

main2 = do
lock <- newMVar ()
forkIO $ lockPrint "good1" lock

threadDelay 100
forkIO $ badLockPrint "bad" lock

-- these both raise blocked indefinitely exception
threadDelay 100
forkIO $ lockPrint "good2" lock
performGC
threadDelay 100
forkIO $ lockPrint "good3" lock

threadDelay 100

Perhaps laziness is confusing the issue as well?

Thanks and sorry for the delayed response,
Brandon Simmons



>
> Cheers,
>
> --
> Felipe.
>

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


Re: Superclass Cycle via Associated Type

2011-07-25 Thread Edward Kmett
On Mon, Jul 25, 2011 at 1:40 PM, Jacques Carette wrote:

> **
> On 25/07/2011 9:55 AM, Edward Kmett wrote:
>
>   If you have an associative (+), then you can use (.*) to multiply by a
> whole number, I currently do fold a method into the Additive class to
> 'fake' a LeftModule, but you have to explicitly use it.
>
>  class Additive m => LeftModule r m
>  class LeftModule Whole m => Additive m
>
>  This says that if you have an Additive semigroup, then there exists a
> LeftModule over the whole numbers, and that every leftmodule is additive,
> but there can exist other LeftModules than just ones over the whole
> numbers!
>
>  Given LeftModule Integer m, you'd know you have Additive m and LeftModule
> Whole m.
>
>  LeftModule Integer m => LeftModule Whole m <=> Additive m.
>
>
> I believe that part of the issue here is that you are using a single
> relation (given by class-level => ) to model what are actually two different
> relations: a 'constructive' inclusion and a 'view' (to use the terminology
> from the Specifications community, which is clearly what these class
> definitions are).
>
> Just like inheritance hierarchies fail miserably when you try to model more
> than one single relation, it should not be unsurprising that the same thing
> befalls '=>', which is indeed a (multi-ary) relation.
>
> In my own hierarchy for Algebra, I use two relations.  Slightly
> over-simplifying things, one of them reflects 'syntactic' inclusion while
> the other models 'semantic' inclusion.  There are very strict rules for the
> 'syntactic' one, so that I get a nice hierarchy and lots of free theorems,
> while the semantic one is much freer, but generates proof obligations which
> must be discharged.  The syntactic one generates a nice DAG (with lots of
> harmless diamonds), while the semantic one is a fully general graph.
>
> Here is another way to look at it:  when you say
>
> class LeftModule Whole m => Additive m
> you are closer to specifying an *instance* relation than a *class
> constraint* relation.
>

This is very true.

However, as mentioned at the outset specifying such instance requires
newtype noise (on m, to avoid incoherent overlap with the other instances)
that leads to a particularly hideous programming style.

newtype NaturalModule m = NaturalModule { runNaturalModule :: m }

instance Monoidal m => LeftModule Natural (NaturalModule m) where

It isn't so bad when working with simple examples like

fiveTimes m = runNaturalModule (5 .* NaturalModule m)

but it gets progressively worse as the hierarchy gets deeper, and I have to
deal with putting on and taking off more and more of these silly wrappers.

Placing the superclass constraint enforces that such instances will always
be available to me, and admits optimized implementations, which I currently
have to shoehorn into the main class and expose by convention.

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


Re: Superclass Cycle via Associated Type

2011-07-25 Thread Jacques Carette

On 25/07/2011 9:55 AM, Edward Kmett wrote:
If you have an associative (+), then you can use (.*) to multiply by a 
whole number, I currently do fold a method into the Additive class to 
'fake' a LeftModule, but you have to explicitly use it.


class Additive m => LeftModule r m
class LeftModule Whole m => Additive m

This says that if you have an Additive semigroup, then there exists a 
LeftModule over the whole numbers, and that every leftmodule is 
additive, but there can exist other LeftModules than just ones over 
the whole numbers!


Given LeftModule Integer m, you'd know you have Additive m and 
LeftModule Whole m.


LeftModule Integer m => LeftModule Whole m <=> Additive m.


I believe that part of the issue here is that you are using a single 
relation (given by class-level => ) to model what are actually two 
different relations: a 'constructive' inclusion and a 'view' (to use the 
terminology from the Specifications community, which is clearly what 
these class definitions are).


Just like inheritance hierarchies fail miserably when you try to model 
more than one single relation, it should not be unsurprising that the 
same thing befalls '=>', which is indeed a (multi-ary) relation.


In my own hierarchy for Algebra, I use two relations.  Slightly 
over-simplifying things, one of them reflects 'syntactic' inclusion 
while the other models 'semantic' inclusion.  There are very strict 
rules for the 'syntactic' one, so that I get a nice hierarchy and lots 
of free theorems, while the semantic one is much freer, but generates 
proof obligations which must be discharged.  The syntactic one generates 
a nice DAG (with lots of harmless diamonds), while the semantic one is a 
fully general graph.


Here is another way to look at it:  when you say
class LeftModule Whole m => Additive m
you are closer to specifying an *instance* relation than a *class 
constraint* relation.


In a general categorical setting, this is not so surprising as 'classes' 
and 'instances' are the same thing.  A 'class' typically has many 
non-isomorphic models while an 'instance' typically has a unique model 
(up to isomorphism), but these are not laws [ex: real-closed Archimedian 
fields have a unique model even though a priori that is a class, and the 
Integers have multiple Monoid instances].


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


possible strictness bug in profiled version of a program

2011-07-25 Thread Peter Hercek

Here is a test program (file name prgSrc.hs):

import Data.Array.Unboxed

main = do
  let l1 = [1..10] :: [Int]
  let l2 = [ map (i+) l1 | i <- [1..500] ]
  let l3 = map (\l -> listArray (1,length l) l) l2 :: [UArray Int Int]
  print $ accumulate l3 0

accumulate [] rv = rv
accumulate (h:t) rv =
  let nextRv = (rv + sum (elems h)) in
  accumulate t $! nextRv


I used ghc 7.0.3-2 on archlinux, 64 bit version.
I created it only to check how much memory short unboxed arrays consume.
Thanks to the "$!" call at the last line of the "accumulate" function 
there should not be any stack overflow.


When I compile with these options:
--make prgSrc.hs
-O2 --make prgSrc.hs
-prof -auto-all -caf-all --make prgSrc.hs
then there is no problem.

But when I compile with these options:
-O2 -prof -auto-all -caf-all --make prgSrc.hs
then program runs out of stack.

This indicates that there is a bug while compiling "$!" in an optimized 
profiling version of this program.

Is it a bug? Should it be reported to the ghc trac database?

Peter.


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


Re: GHC 7.0.4 on Lion

2011-07-25 Thread David Peixotto
I think the warnings are not a big concern. I silence both of them by adding 
-optl"-Wl,-no_compact_unwind,-no_pie" to my ghc options in /usr/bin/ghc.

In 10.7 they changed the default linking options to create a PIE (position 
independent executable). To create a PIE you have to compile all code as 
position independent, which is the default option of GHC on mac os x. For 
performance reasons some code is compiled with absolute references (like the 
gmp library code in your example) so it cannot be used when creating a PIE. The 
advantage of a PIE executable is that it is more secure because the OS can load 
it at a random base address.

I believe the "compact unwind" warning is related to the creation of unwind 
frames for error handling with exceptions in languages like C++. There are some 
more details in this trac ticket: 
http://hackage.haskell.org/trac/ghc/ticket/5019. I'm not sure what the 
advantage of the compact unwind is, but it sounds like it could make the 
executable smaller.

-David

On Jul 25, 2011, at 7:59 AM, Luca Ciciriello wrote:

> Hi All.
> I've installed on my Mac the new MacOS X 10.7 (Lion) with Xcode 4.1
> 
> Using ghc 7.0.4 (64-bit) on that system a get the following warnings in the 
> linking phase:
> 
> Linking hslint ...
> ld: warning: could not create compact unwind for _ffi_call_unix64: does not 
> use RBP or RSP based frame
> ld: warning: PIE disabled. Absolute addressing (perhaps -mdynamic-no-pic) not 
> allowed in code signed PIE, but used in ___gmpn_modexact_1c_odd from 
> /Library/Frameworks/GHC.framework/Versions/7.0.4-x86_64/usr/lib/ghc-7.0.4/integer-gmp-0.2.0.3/libHSinteger-gmp-0.2.0.3.a(mode1o.o).
>  To fix this warning, don't compile with -mdynamic-no-pic or link with 
> -Wl,-no_pie
> 
> Is this something to worrying about?
> 
> Thanks in advance for any answer.
> 
> Luca
> ___
> 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: Superclass Cycle via Associated Type

2011-07-25 Thread Edward Kmett
2011/7/25 Gábor Lehel 

> > type family Frozen t
> > type family Thawed t
> > class Immutable (Frozen t) => Mutable t where
> >   thawedFrozen :: t -> Thawed (Frozen t)
> >   unthawedFrozen :: Thawed (Frozen t) -> t
> >
> > class Mutable (Thawed t) => Immutable t where
> >   frozenThawed :: t -> Frozen (Thawed t)
> >   unfrozenThawed :: Frozen (Thawed t) -> t
> >
> > would enable you to explicitly program with the two isomorphisms, while
> > avoiding superclass constraints.
>
> Hmm, that's an interesting thought. If I'm guesstimating correctly,
> defining instances would be more cumbersome than with the MPTC method,
> but using them would be nicer, provided I write helper functions to
> hide the use of the isomorphism witnesses. I'll give it a try. Thanks!
>
> I seem to recall that in one of your packages, you had a typeclass
> method returning a GADT wrapping the evidence for the equality of two
> types, as a workaround for the lack of superclass equality constraints
> -- what makes you prefer that workaround in one case and this one in
> another?


In a very early version of representable-tries I used my eq package to
provide equality witnesses:

http://hackage.haskell.org/packages/archive/eq/0.3.3/doc/html/Data-Eq-Type.html

But I've turned in general to using explicit isomorphisms for things like

http://hackage.haskell.org/packages/archive/representable-tries/2.0/doc/html/Data-Functor-Representable-Trie.html

because they let me define additional instances that are isomorphic to old
instances quickly, while an actual equality witness would require me to bang
out a new representation and all 20+ superclass instances. This enables me
to write instances for thin newtype wrappers like those in Data.Monoid, etc.
that I would be forced to just skip in a heavier encoding.

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


Re: Superclass Cycle via Associated Type

2011-07-25 Thread Edward Kmett
On Mon, Jul 25, 2011 at 4:46 AM, Simon Peyton-Jones
wrote:

>  On further reflection I have a question.
>
> ** **
>
> Under the limited design below, which Edward says will do all he wants:***
> *
>
> **· **The mutually recursive classes (call them A, B, C) must be
> defined all together. Like
>class B a => A a;  class C a => B a;  class A a => C a
>
> **· **If a type T is an instance of any of those classes, it must
> be a member of all of them
>
> **· **If a function f has type f :: A a => blah, then the
> signature f :: B a => blah and f :: C a => blah would work equally well
>
> In short, I see no advantage to making A,B,C separate classes compared to
> simply unioning them into a single class.
>


> **
>
> Bottom line: adding recursive superclasses with the restrictions I describe
> below would add no useful expressive power.  But it would cost effort to
> implement. So why do it?
>
> ** **
>
> Maybe I’m missing something.
>

In the univariate case this is true, but I think we've lost sight of the
original motivation.

In the MPTC case there is a real difference.

In my example (with methods),

If you have an associative (+), then you can use (.*) to multiply by a whole
number, I currently do fold a method into the Additive class to 'fake' a
LeftModule, but you have to explicitly use it.

class Additive m => LeftModule r m
class LeftModule Whole m => Additive m

This says that if you have an Additive semigroup, then there exists a
LeftModule over the whole numbers, and that every leftmodule is additive,
but there can exist other LeftModules than just ones over the whole
numbers!

Given LeftModule Integer m, you'd know you have Additive m and LeftModule
Whole m.

LeftModule Integer m => LeftModule Whole m <=> Additive m.

Balling them up together precludes the ability to use LeftModule to describe
the relationship of whole numbers to a semigroup.

But moreover it causes me to have to write code that would be parameterized
by the LeftModule in question 5 times, because I have to special case the
module structures over wholes, naturals, integers and the ring itself
relative to code for any other module.

There is a gain in expressive power, but you need multiple parameters to
exploit it.

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


GHC 7.0.4 on Lion

2011-07-25 Thread Luca Ciciriello
Hi All.
I've installed on my Mac the new MacOS X 10.7 (Lion) with Xcode 4.1

Using ghc 7.0.4 (64-bit) on that system a get the following warnings in the 
linking phase:

Linking hslint ...
ld: warning: could not create compact unwind for _ffi_call_unix64: does not use 
RBP or RSP based frame
ld: warning: PIE disabled. Absolute addressing (perhaps -mdynamic-no-pic) not 
allowed in code signed PIE, but used in ___gmpn_modexact_1c_odd from 
/Library/Frameworks/GHC.framework/Versions/7.0.4-x86_64/usr/lib/ghc-7.0.4/integer-gmp-0.2.0.3/libHSinteger-gmp-0.2.0.3.a(mode1o.o).
 To fix this warning, don't compile with -mdynamic-no-pic or link with 
-Wl,-no_pie

Is this something to worrying about?

Thanks in advance for any answer.

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


Re: Superclass Cycle via Associated Type

2011-07-25 Thread Gábor Lehel
2011/7/23 Edward Kmett :
> 2011/7/23 Gábor Lehel 
>>
>> 2011/7/22 Dan Doel :
>> > 2011/7/22 Gábor Lehel :
>> >> Yeah, this is pretty much what I ended up doing. As I said, I don't
>> >> think I lose anything in expressiveness by going the MPTC route, I
>> >> just think the two separate but linked classes way reads better. So
>> >> it's just a "would be nice" thing. Do recursive equality superclasses
>> >> make sense / would they be within the realm of the possible to
>> >> implement?
>> >
>> > Those equality superclasses are not recursive in the same way, as far
>> > as I can tell. The specifications for classes require that there is no
>> > chain:
>> >
>> >    C ... => D ... => E ... => ... => C ...
>> >
>> > However, your example just had (~) as a context for C, but C is not
>> > required by (~). And the families involved make no reference to C,
>> > either. A fully desugared version looks like:
>> >
>> >    type family Frozen a :: *
>> >    type family Thawed a :: *
>> >
>> >    class (..., Thawed (Frozen t) ~ t) => Mutable t where ...
>> >
>> > I think this will be handled if you use a version where equality
>> > superclasses are allowed.
>>
>> To be completely explicit, I had:
>>
>> class (Immutable (Frozen t), Thawed (Frozen t) ~ t) => Mutable t where
>> type Frozen t ...
>> class (Mutable (Thawed t), Frozen (Thawed t) ~ t) => Immutable t where
>> type Thawed t ...
>
>
> I had a similar issue in my representable-tries package.

I believe we actually discussed this on IRC. :-)

> In there I had
> type family Key (f :: * -> *) :: *
> class Indexable f where
>   index :: f a -> Key f -> a
> class Indexable f => Representable f where
>   tabulate :: (Key f -> a) -> f a
> such that tabulate and index witness the isomorphism from f a to (Key f ->
> a).
> So far no problem. But then to provide a Trie type that was transparent I
> wanted.
> class (Representable (BaseTrie e), Traversable (BaseTrie e), Key (BaseTrie
> e) ~ e) => HasTrie e where
>   type BaseTrie e :: * -> *
> type (:->:) e = BaseTrie e
> which I couldn't use prior to the new class constraints patch.
> The reason I mention this is that my work around was to weaken matters a bit
> class (Representable (BaseTrie e)) => HasTrie e where
>   type BaseTrie e :: * -> *
>   embedKey :: e -> Key (BaseTrie e)
>   projectKey :: Key (BaseTrie e) -> e
>
> This dodged the need for superclass equality constraints by just requiring
> me to supply the two witnesses to the isomorphism between e and Key
> (BaseTrie e).
> Moreover, in my case it helped me produce instances, because the actual
> signatures involved about 20 more superclasses, and this way I could make
> new HasTrie instances for newtype wrappers just by defining an embedding and
> projection pair for some type I'd already defined.
> But, it did require me to pay for a newtype wrapper which managed the
> embedding and projection pairs.
> newtype e :->: a = Trie (BaseTrie e a)
> In your setting, perhaps something like:
>
> type family Frozen t
> type family Thawed t
> class Immutable (Frozen t) => Mutable t where
>   thawedFrozen :: t -> Thawed (Frozen t)
>   unthawedFrozen :: Thawed (Frozen t) -> t
>
> class Mutable (Thawed t) => Immutable t where
>   frozenThawed :: t -> Frozen (Thawed t)
>   unfrozenThawed :: Frozen (Thawed t) -> t
>
> would enable you to explicitly program with the two isomorphisms, while
> avoiding superclass constraints.

Hmm, that's an interesting thought. If I'm guesstimating correctly,
defining instances would be more cumbersome than with the MPTC method,
but using them would be nicer, provided I write helper functions to
hide the use of the isomorphism witnesses. I'll give it a try. Thanks!

I seem to recall that in one of your packages, you had a typeclass
method returning a GADT wrapping the evidence for the equality of two
types, as a workaround for the lack of superclass equality constraints
-- what makes you prefer that workaround in one case and this one in
another?

-- 
Work is punishment for failing to procrastinate effectively.

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


RE: Superclass Cycle via Associated Type

2011-07-25 Thread Simon Peyton-Jones
On further reflection I have a question.

Under the limited design below, which Edward says will do all he wants:

· The mutually recursive classes (call them A, B, C) must be defined 
all together. Like
   class B a => A a;  class C a => B a;  class A a => C a

· If a type T is an instance of any of those classes, it must be a 
member of all of them

· If a function f has type f :: A a => blah, then the signature f :: B 
a => blah and f :: C a => blah would work equally well

In short, I see no advantage to making A,B,C separate classes compared to 
simply unioning them into a single class.

Bottom line: adding recursive superclasses with the restrictions I describe 
below would add no useful expressive power.  But it would cost effort to 
implement. So why do it?

Maybe I’m missing something.

Simon

From: Edward Kmett [mailto:ekm...@gmail.com]
Sent: 22 July 2011 20:07
To: Simon Peyton-Jones
Cc: Gábor Lehel; glasgow-haskell-users@haskell.org
Subject: Re: Superclass Cycle via Associated Type

2011/7/22 Simon Peyton-Jones 
mailto:simo...@microsoft.com>>
I talked to Dimitrios.  Fundamentally we think we should be able to handle 
recursive superclasses, albeit we have a bit more work to do on the type 
inference engine first.

The situation we think we can handle ok is stuff like Edward wants (I've 
removed all the methods):

class LeftModule Whole m => Additive m
class Additive m => Abelian m
class (Semiring r, Additive m) => LeftModule r m
class Multiplicative m where (*) :: m -> m -> m
class LeftModule Natural m => Monoidal m
class (Abelian m, Multiplicative m, LeftModule m m) => Semiring m
class (LeftModule Integer m, Monoidal m) => Group m
class Multiplicative m => Unital m
class (Monoidal r, Unital r, Semiring r) => Rig r
class (Rig r, Group r) => Ring r
The superclasses are recursive but
 a) They constrain only type variables
 b) The variables in the superclass context are all
mentioned in the head.  In class Q => C a b c
fv(Q) is subset of {a,b,c}

Question to all: is that enough?

This would perfectly address all of the needs that I have had!

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