Re: Abstracting over things that can be unpacked

2012-03-03 Thread Ryan Newton
+1 !


On Fri, Mar 2, 2012 at 7:40 PM, Johan Tibell johan.tib...@gmail.com wrote:

 Hi all,

 These ideas are still in very early stages. I present them here in hope of
 starting a discussion. (We discussed this quite a bit at last year's ICFP,
 I hope this slightly different take on the problem might lead to new ideas.)

 I think the next big step in Haskell performance is going to come from
 using better data representation in common types such as list, sets, and
 maps. Today these polymorphic data structures use both more memory and have
 more indirections than necessary, due to boxing of values. This boxing is
 due to the values being stored in fields of polymorphic type.

 First idea: instead of rejecting unpack pragmas on polymorphic fields,
 have them require a class constraint on the field types. Example:

 data UnboxPair a b = (Unbox a, Unbox b) = UP {-# UNPACK #-} !a {-#
 UNPACK #-} !b

 The Unbox type class would be similar in spirit to the class with the same
 name in the vector package, but be implemented internally by GHC. To a
 first approximation instances would only exist for fields that unpack to
 non-pointer types (e.g. Int.)

 Second idea: Introduce a new pragma, that has similar effect on
 representations as DPH's [::] vector type. This new pragma does deep
 unpacking, allowing for more types to be instances of the Unbox type e.g.
 pairs. Example:

 data T = C {-# UNWRAP #-} (a, b)

 If you squint a bit this pragma does the same as [: (a, b) :], except no
 vectors are involved. The final representation would be the
 unpacked representation of a and b, concatenated together (e.g. (Int, Int)
 would result in the field above being 128-bit wide on a 64-bit machine.

 The meta-idea tying these two ideas together is to allow for some
 abstraction over representation transforming pragmas, such as UNPACK.

 P.S. Before someone suggest using type families. Please read my email
 titled Avoiding O(n^2) instances when using associated data types to
 unpack values into constructors.

 Cheers,
   Johan


 ___
 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: Abstracting over things that can be unpacked

2012-03-03 Thread Twan van Laarhoven

On 03/03/12 01:40, Johan Tibell wrote:

Hi all,

These ideas are still in very early stages. I present them here in hope
of starting a discussion. (We discussed this quite a bit at last year's
ICFP, I hope this slightly different take on the problem might lead to
new ideas.)

I think the next big step in Haskell performance is going to come from
using better data representation in common types such as list, sets, and
maps. Today these polymorphic data structures use both more memory and
have more indirections than necessary, due to boxing of values. This
boxing is due to the values being stored in fields of polymorphic type.

First idea: instead of rejecting unpack pragmas on polymorphic fields,
have them require a class constraint on the field types. Example:

 data UnboxPair a b = (Unbox a, Unbox b) = UP {-# UNPACK #-} !a {-#
UNPACK #-} !b


I expect that this will not be easy to implement, because it requires 
interaction with things like the garbage collector. For example, 
UnboxPair will need a different info table for different a and b.


It might be possible to essentially specialize UnboxPair for each 
different a and b for which it is used, but that gets tricky with 
generic code.



The Unbox type class would be similar in spirit to the class with the
same name in the vector package, but be implemented internally by GHC.
To a first approximation instances would only exist for fields that
unpack to non-pointer types (e.g. Int.)

Second idea: Introduce a new pragma, that has similar effect on
representations as DPH's [::] vector type. This new pragma does deep
unpacking, allowing for more types to be instances of the Unbox type.


Could this be handled by just having/deriving an Unbox instance for 
(a,b)? I imagine the Unbox type class would have to contain essentially 
the same things as Storable, maybe something like


type UnboxedRepr :: Int - #
class Unbox a where
type Repr a :: # -- gives size and alignment
unbox :: a - Repr a
box   :: Repr a - a

A problem with an instance (Unboxed a, Unboxed b) = Unboxed (a,b) is 
that it allows arbitrarily large unboxed values to be created at 
runtime. That doesn't work when you use specialization to create the 
needed info tables.



Twan

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


Records in Haskell: Type-Indexed Records (another proposal)

2012-03-03 Thread Matthew Farkas-Dyck
Hello all.

I wrote a new proposal for the Haskell record system. It can be found
at http://hackage.haskell.org/trac/ghc/wiki/Records/TypeIndexedRecords

Records are indexed by arbitrary Haskell types. Scope is controlled as
scope of key types. No fieldLabel declarations needed (as in DORF).

Cheers,
strake

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


Re: Records in Haskell: Type-Indexed Records (another proposal)

2012-03-03 Thread AntC
Matthew Farkas-Dyck strake888 at gmail.com writes:

 
 Hello all.
 
 I wrote a new proposal for the Haskell record system. It can be found
 at http://hackage.haskell.org/trac/ghc/wiki/Records/TypeIndexedRecords
 
 Records are indexed by arbitrary Haskell types. Scope is controlled as
 scope of key types. No fieldLabel declarations needed (as in DORF).
 
 Cheers,
 strake
 

Thanks Matthew,

It's good to explore the design space.

Apart from the Quasifunctor bit, I think you'll find your proposal is a rather 
cut-down version of DORF, just using different syntactic sugar. (Oh, and with 
the arguments to Has in a different order, just to be confusing.)

You do have the equivalent of fieldLabel decls. Those are all your type 
indexes: data X = X, etc.

And you suggest defining
x = X

Which is equivalent to DORF mapping from field name `x` to phantom type 
Proxy_x, (but DORF keeps `x` as a field selector function, similar to H98).

To make `x` a selector function instead, you'd go:
x = (.) X   -- or probably x = get X, see below
Which is exactly the same as DORF (after adjusting for the different order of 
arguments).

And presumably instead of X you'd want a LongandMeaningfulLabel?

And if your 
data Customer_id = Customer_id
was always an Int field, wouldn't it help the reader and the compiler to say 
that? (That's the main extra part in fieldLabels.)

I think you don't want all those type vars in your record decls -- but only 
vars for the mutatable types, like this:

  type R c = { X ::. Int, Y::. String, Z ::. c, ... }

Then you don't need a Quasifunctor instance for every field, only the 
mutatable ones.

Oh, and how do you deal with multiple record constructors as in H98:
   data T a = T1 { x :: a, y :: Bool }
| T2 { x :: a }

It wouldn't work to have a different record type for each constructor, 'cos 
you'd turn functions that use them from mono to polymorphic (overloaded -- 
needing a class and instances).

You don't give full details for your Has instances, but presumably you'd do 
the same equality constraint style as SORF and DORF.

I think you still need method get and sugar to turn the dot notation into a 
call to get. Having method (.) will usurp altogether dot as function 
composition -- you'll make a lot of enemies! And we need tight binding for dot 
notation, so we might as well treat it as special syntax.

You don't show how you'd do record update. The litmus test is what is the type 
for:
r{ X = True }
That is: update record r, set its X field to True.

AntC




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