#1349: Generalise the ! and UNPACK mechanism for data types, to unpack function
arguments
---------------------------------+------------------------------------------
Reporter: simonpj | Owner:
Type: task | Status: new
Priority: low | Milestone: 7.2.1
Component: Compiler | Version: 6.6.1
Keywords: | Testcase:
Blockedby: | Difficulty: Unknown
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by simonpj):
At least in the '''monomorphic''' case for '''data constructors''' I think
I can see how to make this work. Let's review ordinary UNPACK pragmas as
they are today, and let's just consider single-constructor types for now.
Then when I have, say,
{{{
data T = C {-# UNPACK #-} !(Int,Int)
}}}
the UNPACK affects (a) construction of `C` and (b) pattern matching
against `C`. I'll express it like this:
{{{
data T = Cw Int Int
makeC :: (Int,Int) -> T
makeC x = case x of (a,b) -> Cw a b
matchC :: T -> ((Int,Int) -> r) -> r
matchC x k = case x of { Cw a b -> k (a,b) }
}}}
Here
* The data type `T` is ultimately represented by a data type with a data
constructor `Cw`, with two fields.
* A use of `C` to construct a value is tranformed to a call of `makeC`.
The function `makeC` constructs a value of type `T`; its signature is what
the programmer expects for his constructor `C`.
* A use of `C` in pattern matching is transformed to a call of `matchC`.
The function `matchC` matches against a value of type `T`, and applies its
continuatoin `k` to an `(Int,Int)` pair, just as the programmer expects.
So the `makeC`/`matchC` pair completely express what it means to build and
pattern match against constructor `C`. The constructor `C` is not really
a constructor at all; it's a '''view''' on the underlying data constructor
`Cw`.
Now for kolmodin's type
{{{
newtype Get a = C { runCont :: forall r.
S ->
Failure r ->
Success a r ->
Result r }
}}}
I think you would really like to say
{{{
newtype Get a = C { runCont :: forall r.
{-# UNPACK #-} !S ->
Failure r ->
Success a r ->
Result r }
}}}
And what might that mean? Presumably it means the function stored in the
data type has its arguments unpacked. So the translation is
{{{
newtype Get a = Cw { runCont :: forall r.
B.ByteString ->
B.ByteString ->
Bool ->
Failure r ->
Success a r ->
Result r }
makeC :: (forall r. S -> Failure r -> Success a r -> Result r)
-> Get a
makeC f = Get (\i ni ra -> f (S i ni ra))
matchC :: Get a -> ((forall r. S -> Failure r -> Success a r -> Result r)
-> r') -> r'
matchC (C f) = k (\(S i ni ra) -> f i ni ra)
}}}
Or something like that. The point is that the UNPACK and ! pragmas
control the generation of `makeC` and `matchC`, in a way that we can pin
down quite precisely.
Things to notice
* The UNPACK stuff might be recursive. For example, the `ByteString`
arguments of `S` are themselves given UNPACK pragmas, so probably the real
of C is more like this:
{{{
newtype Get a = Cw { runCont :: forall r.
Addr# -> Int# -> Int# ->
Addr# -> Int# -> Int# ->
Bool ->
Failure r ->
Success a r ->
Result r }
}}}
Now, whether you really want this I'm not sure, but that is the natural
thing.
* I have no idea what to do in the polymorphic case, when you can't "see"
the type of the argument to be UNPACKed. But that is just as now.
* As always with UNPACK, there's a danger that we'll do unnecessary
unboxing and reboxing. For example, with the data type `T` above, every
type we match against `C` we'll build a pair `(a,b)` (just look at
`matchC`). If the body of the pattern match uses the pair entire, rather
than deconstructing it, there's a danger that we'll build the pair lots of
times (once for each match) rather than once (when we build the C value).
And its no different for this function-UNPACK stuff.
* All of this is for constructor arguments. I'm vastly less sure of the
merits of this kind of stuff for ordinary functions.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1349#comment:34>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs