Re: Revert a CAF?

2011-12-07 Thread Simon Marlow

On 06/12/2011 17:48, wren ng thornton wrote:

So, I have an optimization/internals question. Does the GHC API have any
hooks for being able to revert a CAF to the original expression, thus
discarding the previously computed result?

The reason I'm wanting this is that I have a particular CAF which is an
infinite list. Unfolding that list takes a fair deal of work, so we want
to share it whenever possible; however it doesn't take an overwhelming
amount of work, so if we know we've evaluated more of the list than
necessary (for a long while), it'd be nice to be able to revert the
evaluation in order to save on memory overhead (e.g., by calling relax
:: IO()).

I could hack something together based on unsafePerformIO and top-level
IORefs, and it's clear that this is in fact a safe thing to do, but I'm
worried about the semantic issues inherent in unsafePerformIOed
top-level IORefs (e.g., the fact that their scope isn't particularly
well defined: is it per library instance? per runtime?...).
Unfortunately, for what I'm doing, it isn't really feasible to just
leave the IO type in there nor to pass around the infinite list so we
can use scoping rules to decide when to free it.

(Feel free to offer alternative suggestions to handling this situation
too.)


It would be possible, but it's not quite as straightforward as you might 
think.  Suppose you have a program like this:


xs = [1..10]
evens = filter ((==0) . (`mod` 2)) xs

and you fully evaluate "evens".  Now, GHC will garbage collect "xs", 
because it isn't required any more.  However, if you revert "evens" to a 
CAF, now we require "xs" again, so we have to either revert that to a 
CAF or arrange to retain it in the first place on the grounds that we 
might need it again if some other CAF is reverted.


Reverting xs to a CAF is not hard - we could have the GC revert CAFs as 
soon as they become unreachable.  Arranging to retain it is harder.


GHCi gets around this by reverting *all* CAFs at the same time when you 
say :load.


There's one other thing: GHC doesn't support reverting CAFs in 
interpreted code at the moment, you have to reload the module.


So you need the following things:

 - modify the GC to revert CAFs when they become garbage

 - add a primop to revert a single CAF

not too hard, I would think...

Cheers,
Simon

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


Re: Revert a CAF?

2011-12-07 Thread Twan van Laarhoven

On 06/12/11 18:48, wren ng thornton wrote:

So, I have an optimization/internals question. Does the GHC API have any
hooks for being able to revert a CAF to the original expression, thus
discarding the previously computed result?

...

I could hack something together based on unsafePerformIO and top-level
IORefs, and it's clear that this is in fact a safe thing to do, but I'm
worried about the semantic issues inherent in unsafePerformIOed
top-level IORefs (e.g., the fact that their scope isn't particularly
well defined: is it per library instance? per runtime?...).
Unfortunately, for what I'm doing, it isn't really feasible to just
leave the IO type in there nor to pass around the infinite list so we
can use scoping rules to decide when to free it.


How bad is the IORef solution really? I.e. can someone more well versed 
in ghc internals tell me why this wouldn't work?


type CAF a = IORef (() -> a, a)
mkCAF :: (() -> a) -> a
mkCAF f = unsafePerformIO $ newIORef (f, f ())
getCAF :: CAF a -> a
getCAF = snd . unsafeDupablePerformIO . readIORef
resetCAF :: CAF a -> IO ()
resetCAF = modifyIORef $ \(f,_) -> (f, f ())

myCAF :: CAF [Int]
myCAF = mkCAF $ \_ -> [1..100]
{-# NOINLINE myCAF #-}


Twan

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


GHC HEAD build error

2011-12-07 Thread Bas van Dijk
Hello,

I'm trying to build GHC HEAD but get the following error:

"inplace/bin/ghc-stage1"   -H64m -O0 -fasm -Iincludes -Irts
-Irts/dist/build -DCOMPILING_RTS -package-name rts  -dcmm-lint  -i
-irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build
-Irts/dist/build/autogen-optc-O2   -c
rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o

rts/HeapStackCheck.cmm:159:305: parse error on input `('

The bug is in the GC_GENERIC macro on line 99:

Capability_interrupt(MyCapability())  != 0 :: CInt

However, I can't spot the problem.

Bas

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


Re: GHC HEAD build error

2011-12-07 Thread Ian Lynagh
On Wed, Dec 07, 2011 at 04:45:31PM +0100, Bas van Dijk wrote:
> 
> "inplace/bin/ghc-stage1"   -H64m -O0 -fasm -Iincludes -Irts
> -Irts/dist/build -DCOMPILING_RTS -package-name rts  -dcmm-lint  -i
> -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build
> -Irts/dist/build/autogen-optc-O2   -c
> rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o
> 
> rts/HeapStackCheck.cmm:159:305: parse error on input `('

This is probably caused by old header files in includes/. Updating to
the latest HEAD and making clean should fix it.


Thanks
Ian


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


Re: GHC HEAD build error

2011-12-07 Thread Daniel Fischer
On Wednesday 07 December 2011, 16:45:31, Bas van Dijk wrote:
> Hello,
> 
> I'm trying to build GHC HEAD but get the following error:
> 
> "inplace/bin/ghc-stage1"   -H64m -O0 -fasm -Iincludes -Irts
> -Irts/dist/build -DCOMPILING_RTS -package-name rts  -dcmm-lint  -i
> -irts -irts/dist/build -irts/dist/build/autogen -Irts/dist/build
> -Irts/dist/build/autogen-optc-O2   -c
> rts/HeapStackCheck.cmm -o rts/dist/build/HeapStackCheck.o
> 
> rts/HeapStackCheck.cmm:159:305: parse error on input `('
> 
> The bug is in the GC_GENERIC macro on line 99:
> 
> Capability_interrupt(MyCapability())  != 0 :: CInt
> 
> However, I can't spot the problem.

I had the same recently, it's probably because GHCConstants.h and 
DerivedConstants.h have been moved but you still have them in include/ from 
a previous build.
Deleting them should fix it.

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


Re: [Haskell-cafe] More liberal than liberal type synonyms

2011-12-07 Thread Dan Doel
On Wed, Dec 7, 2011 at 5:48 AM, Dmitry Kulagin  wrote:
> I am still pretty new in Haskell, but this problem annoys me already.
>
> If I define certain monad as a type synonym:
>
>    type StateA a = StateT SomeState SomeMonad a
>
> Then I can't declare new monad based on the synonym:
>
>    type StateB a = StateT SomeOtherState StateA a
>
> The only way I know to overcome is to declare StateA without `a':
>
>    type StateA = StateT SomeState SomeMonad
>
> But it is not always possible with existing code base.

I'm afraid my proposal doesn't make this work. You could perhaps
define StateB, but when you expand in a type you get:

StateB a = StateT SomeOtherState StateA a

which has a partially applied StateA, and is rejected. The only way to
make this work is to eta reduce StateA manually, or make GHC recognize
when a synonym can be eta reduced in this way (which might be both
possible and useful as a separate proposal).

My extension fell within the liberal type synonym space, which says
that if you have:

F G

where F and G are both synonyms, and G is partially applied, then it
is okay as long as expansion of F (and any subsequent expansions)
cause G to become fully applied. My extension of this is just to allow
partial application inside aliases as long as it meets these same
criteria.

The reason to disallow partially applied type aliases is that they
make inference pretty much impossible, unless you only infer them in
very limited circumstances perhaps. And if you can't get inference of
them, you probably need to start having explicit annotations to tell
the type checker what you want to happen, which has some of its own
complications with the way quantifiers work in GHC and such. It'd
cascade into some thorny issues.

Hopefully that covers all the other subsequent stuff folks have been
talking about.

-- Dan

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


Re: GHC HEAD build error

2011-12-07 Thread Bas van Dijk
On 7 December 2011 16:54, Ian Lynagh  wrote:
> This is probably caused by old header files in includes/. Updating to
> the latest HEAD and making clean should fix it.

I already performed a make clean so that doesn't fix it. Fortunately a
make maintainer-clean does.

Thanks,

Bas

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


Superclass Cycle via Associated Type

2011-12-07 Thread Nicolas Frisby
(Sorry I'm so late to this dialogue.)

In http://www.haskell.org/pipermail/glasgow-haskell-users/2011-July/020593.html,
SPJ asks

> 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?

I just recently came upon my own desire for this capability, but I'm
pretty sure my reply to SPJ's question is "No." I'd like to extend
Sat's modeling capabilities to also cover superclass constraints.

> type family Super a
> class Sat (Super a) => Sat a where dict :: a

This seems to necessitate recursive dictionaries — I'm not familiar
enough with the dictionary-implementation details to understand how
much of an understatement that might be. All I can say is that my own
intuitions about those things don't yet deem this technique
infeasible.

Let's take a reification of Ord as an example.

> data EmptyD a = EmptyD
> type instance Super (EmptyD a) = EmptyD a
> instance Sat (EmptyD a) where dict = EmptyD
>
> data EqD a where EqD :: Eq a => EqD a
> type instance Super (EqD a) = EmptyD a
> instance Eq a => Sat (EqD a) where dict = EqD
>
> data OrdD a where OrdD :: Ord a => OrdD a
> type instance Super (OrdD a) = EqD a
> instance Ord a => Sat (OrdD a) where dict = OrdD

Now GHC can derive Sat (EqD a) from Sat (OrdD a). I'd bet this could
be cleaned via Constraint Kinds [1] — if not totally subsumed by them:

> type family Super a :: Constraint
> class Super a => Sat a where dict :: a
>
> data OrdD a where OrdD :: Ord a => OrdD a
> type instance Super (OrdD a) = Ord a
> instance Ord a => Sat (OrdD a) where dict = OrdD

With these definitions, there'd be an isomorphism between Sat (OrdD a)
and Ord a. I don't know how difficult it would be for GHC to wield
that isomorphism.

At this point, though, perhaps Constraint Kinds simply deprecate Sat?
[1] does, after all, define "one reified dictionary to rule them all".

-

[1] - http://blog.omega-prime.co.uk/?p=127

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