Copyright | (C) 2016 mniip |
---|---|
License | MIT |
Maintainer | mniip <mniip@mniip.com> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
As of now, the GHCi interactive runtime is incapable of working on unboxed
tuples. In particular, it is unable to fully apply any function returning an
unboxed tuple, create a function that takes a non-nullary unboxed tuple as
argument, or pass a non-nullary tuple to some other function. The usual
solution is to enable object code generation with -fobject-code
. This
module serves as a workaround for the cases where -fobject-code
is
undesiable.
Due to the aforementioned restrictions on operations on unboxed tuples, we
can't simply expose operations of type (# a, b #) -> (a, b)
. We have to
provide operations for working on functions of type a -> (# b, c #)
.
More often than not, the types in unboxed tuples are themselves unboxed.
There are two major issues with this: 1) we cannot use (,)
and 2) we have to
provide different functions for different combinations of types. It is also
worth mentioning that the a
above can also be unboxed and therefore cannot
be quantified either.
This module provides a class of compose
functions of type
composeA#BC :: (a -> (# b, c, ... #)) -> a -> (b -> c -> ... -> r) -> r
Where A
is the function argument type a
, #
is number of fields in the
tuple, and BC
are the tupled types b
, c
, ...
The key for type names is as follows:
- _ =
forall (a :: *). a
(regular lifted type) - a =
Array#
- Aa =
ArrayArray#
- b =
ByteArray#
- c =
Char#
- d =
Double#
- f =
Float#
- i =
Int#
- Ma =
MutableArray#
- MAa =
MutableArrayArray#
- Mb =
MutableByteArray#
- Mv =
MVar#
- o =
BCO#
- p =
Addr#
- s =
State#
- Sa =
SmallArray#
- SMa =
SmallMutableArray#
- Sn =
StableName#
- Sp =
StablePtr#
- t =
ThreadId#
- Tv =
TVar#
- v =
MutVar#
- w =
Word#
- Wp =
Weak#
This module contains functions for all combinations of types that come up in GHC.Prim but in principle other cases could be added too.
- composea1_ :: (Addr# -> (#a#)) -> Addr# -> (a -> r) -> r
- composei1_ :: (Int# -> (#a#)) -> Int# -> (a -> r) -> r
- composeo1_ :: (BCO# -> (#a#)) -> BCO# -> (a -> r) -> r
- composed2ii :: (Double# -> (#Int#, Int##)) -> Double# -> (Int# -> Int# -> r) -> r
- composef2ii :: (Float# -> (#Int#, Int##)) -> Float# -> (Int# -> Int# -> r) -> r
- composei2i_ :: (Int# -> (#Int#, a#)) -> Int# -> (Int# -> a -> r) -> r
- composei2ii :: (Int# -> (#Int#, Int##)) -> Int# -> (Int# -> Int# -> r) -> r
- composes2s_ :: (State# s -> (#State# t, a#)) -> State# s -> (State# t -> a -> r) -> r
- composes2sa :: (State# s -> (#State# t, Array# a#)) -> State# s -> (State# t -> Array# a -> r) -> r
- composes2sAa :: (State# s -> (#State# t, ArrayArray##)) -> State# s -> (State# t -> ArrayArray# -> r) -> r
- composes2sb :: (State# s -> (#State# t, ByteArray##)) -> State# s -> (State# t -> ByteArray# -> r) -> r
- composes2sc :: (State# s -> (#State# t, Char##)) -> State# s -> (State# t -> Char# -> r) -> r
- composes2sd :: (State# s -> (#State# t, Double##)) -> State# s -> (State# t -> Double# -> r) -> r
- composes2sf :: (State# s -> (#State# t, Float##)) -> State# s -> (State# t -> Float# -> r) -> r
- composes2si :: (State# s -> (#State# t, Int##)) -> State# s -> (State# t -> Int# -> r) -> r
- composes2sSa :: (State# s -> (#State# t, SmallArray# a#)) -> State# s -> (State# t -> SmallArray# a -> r) -> r
- composes2sSMa :: (State# s -> (#State# t, SmallMutableArray# u a#)) -> State# s -> (State# t -> SmallMutableArray# u a -> r) -> r
- composes2sSn :: (State# s -> (#State# t, StableName# a#)) -> State# s -> (State# t -> StableName# a -> r) -> r
- composes2sSp :: (State# s -> (#State# t, StablePtr# a#)) -> State# s -> (State# t -> StablePtr# a -> r) -> r
- composes2sMa :: (State# s -> (#State# t, MutableArray# u a#)) -> State# s -> (State# t -> MutableArray# u a -> r) -> r
- composes2sMAa :: (State# s -> (#State# t, MutableArrayArray# u#)) -> State# s -> (State# t -> MutableArrayArray# u -> r) -> r
- composes2sMb :: (State# s -> (#State# t, MutableByteArray# u#)) -> State# s -> (State# t -> MutableByteArray# u -> r) -> r
- composes2sMv :: (State# s -> (#State# t, MVar# u a#)) -> State# s -> (State# t -> MVar# u a -> r) -> r
- composes2so :: (State# s -> (#State# t, BCO##)) -> State# s -> (State# t -> BCO# -> r) -> r
- composes2sp :: (State# s -> (#State# t, Addr##)) -> State# s -> (State# t -> Addr# -> r) -> r
- composes2st :: (State# s -> (#State# t, ThreadId##)) -> State# s -> (State# t -> ThreadId# -> r) -> r
- composes2sTv :: (State# s -> (#State# t, TVar# u a#)) -> State# s -> (State# t -> TVar# u a -> r) -> r
- composes2sv :: (State# s -> (#State# t, MutVar# u a#)) -> State# s -> (State# t -> MutVar# u a -> r) -> r
- composes2sw :: (State# s -> (#State# t, Word##)) -> State# s -> (State# t -> Word# -> r) -> r
- composes2sWp :: (State# s -> (#State# t, Weak# a#)) -> State# s -> (State# t -> Weak# a -> r) -> r
- composew2ww :: (Word# -> (#Word#, Word##)) -> Word# -> (Word# -> Word# -> r) -> r
- compose_3pab :: (a -> (#Addr#, Array# b, ByteArray##)) -> a -> (Addr# -> Array# b -> ByteArray# -> r) -> r
- composes3si_ :: (State# s -> (#State# t, Int#, a#)) -> State# s -> (State# t -> Int# -> a -> r) -> r
- composed4iwwi :: (Double# -> (#Int#, Word#, Word#, Int##)) -> Double# -> (Int# -> Word# -> Word# -> Int# -> r) -> r
- composes4siii :: (State# s -> (#State# t, Int#, Int#, Int##)) -> State# s -> (State# t -> Int# -> Int# -> Int# -> r) -> r
- decomposes2s_ :: (State# s -> (State# s -> a -> (#State# s, a#)) -> (#State# s, a#)) -> State# s -> (#State# s, a#)
Documentation
composea1_ :: (Addr# -> (#a#)) -> Addr# -> (a -> r) -> r Source #
composei1_ :: (Int# -> (#a#)) -> Int# -> (a -> r) -> r Source #
composeo1_ :: (BCO# -> (#a#)) -> BCO# -> (a -> r) -> r Source #
composes2sa :: (State# s -> (#State# t, Array# a#)) -> State# s -> (State# t -> Array# a -> r) -> r Source #
composes2sAa :: (State# s -> (#State# t, ArrayArray##)) -> State# s -> (State# t -> ArrayArray# -> r) -> r Source #
composes2sb :: (State# s -> (#State# t, ByteArray##)) -> State# s -> (State# t -> ByteArray# -> r) -> r Source #
composes2sc :: (State# s -> (#State# t, Char##)) -> State# s -> (State# t -> Char# -> r) -> r Source #
composes2sd :: (State# s -> (#State# t, Double##)) -> State# s -> (State# t -> Double# -> r) -> r Source #
composes2sf :: (State# s -> (#State# t, Float##)) -> State# s -> (State# t -> Float# -> r) -> r Source #
composes2si :: (State# s -> (#State# t, Int##)) -> State# s -> (State# t -> Int# -> r) -> r Source #
composes2sSa :: (State# s -> (#State# t, SmallArray# a#)) -> State# s -> (State# t -> SmallArray# a -> r) -> r Source #
composes2sSMa :: (State# s -> (#State# t, SmallMutableArray# u a#)) -> State# s -> (State# t -> SmallMutableArray# u a -> r) -> r Source #
composes2sSn :: (State# s -> (#State# t, StableName# a#)) -> State# s -> (State# t -> StableName# a -> r) -> r Source #
composes2sSp :: (State# s -> (#State# t, StablePtr# a#)) -> State# s -> (State# t -> StablePtr# a -> r) -> r Source #
composes2sMa :: (State# s -> (#State# t, MutableArray# u a#)) -> State# s -> (State# t -> MutableArray# u a -> r) -> r Source #
composes2sMAa :: (State# s -> (#State# t, MutableArrayArray# u#)) -> State# s -> (State# t -> MutableArrayArray# u -> r) -> r Source #
composes2sMb :: (State# s -> (#State# t, MutableByteArray# u#)) -> State# s -> (State# t -> MutableByteArray# u -> r) -> r Source #
composes2sMv :: (State# s -> (#State# t, MVar# u a#)) -> State# s -> (State# t -> MVar# u a -> r) -> r Source #
composes2so :: (State# s -> (#State# t, BCO##)) -> State# s -> (State# t -> BCO# -> r) -> r Source #
composes2sp :: (State# s -> (#State# t, Addr##)) -> State# s -> (State# t -> Addr# -> r) -> r Source #
composes2st :: (State# s -> (#State# t, ThreadId##)) -> State# s -> (State# t -> ThreadId# -> r) -> r Source #
composes2sTv :: (State# s -> (#State# t, TVar# u a#)) -> State# s -> (State# t -> TVar# u a -> r) -> r Source #
composes2sv :: (State# s -> (#State# t, MutVar# u a#)) -> State# s -> (State# t -> MutVar# u a -> r) -> r Source #
composes2sw :: (State# s -> (#State# t, Word##)) -> State# s -> (State# t -> Word# -> r) -> r Source #
composes2sWp :: (State# s -> (#State# t, Weak# a#)) -> State# s -> (State# t -> Weak# a -> r) -> r Source #
compose_3pab :: (a -> (#Addr#, Array# b, ByteArray##)) -> a -> (Addr# -> Array# b -> ByteArray# -> r) -> r Source #
composes3si_ :: (State# s -> (#State# t, Int#, a#)) -> State# s -> (State# t -> Int# -> a -> r) -> r Source #
composed4iwwi :: (Double# -> (#Int#, Word#, Word#, Int##)) -> Double# -> (Int# -> Word# -> Word# -> Int# -> r) -> r Source #
composes4siii :: (State# s -> (#State# t, Int#, Int#, Int##)) -> State# s -> (State# t -> Int# -> Int# -> Int# -> r) -> r Source #
decomposes2s_ :: (State# s -> (State# s -> a -> (#State# s, a#)) -> (#State# s, a#)) -> State# s -> (#State# s, a#) Source #
This is an "inverse" of composes2s_
because sometimes it might be
useful to produce a
of your own.
Example:State#
s a -> (# State#
s, a #)
returnIO x =IO
(decomposes2s_
(s r -> r s x))