[Haskell-cafe] bytestring vs. uvector

Don Stewart dons at galois.com
Tue Mar 10 16:01:31 EDT 2009


bulat.ziganshin:
> Hello Don,
> 
> Tuesday, March 10, 2009, 10:40:30 PM, you wrote:
> 
> >> I think uvector only works with certain types that can be
> >> unboxed, while storablevector works with all types that
> >> instantiate Foreign.Storable.Storable.  I don't know about
> >> vector.  From the description of vector, I have the
> 
> > That's interesting. I'd expect Storable and UA to have the same set of
> > inhabitants. Is there any difference?
> 
> if uavector use ghc's built-in unboxed array operations (as
> Data.Array.Unboxed does) then it's necessarily bounded to types
> supported by those operations

And what is Storable limited to?

Ultimately they're all limited to the primops for reading and writing,
and to what types we can encode in those. So:

    primop ReadOffAddrOp_Char "readCharOffAddr#" GenPrimOp
    primop ReadOffAddrOp_WideChar "readWideCharOffAddr#" GenPrimOp

    primop ReadOffAddrOp_Int "readIntOffAddr#" GenPrimOp
    primop ReadOffAddrOp_Word "readWordOffAddr#" GenPrimOp

    primop ReadOffAddrOp_Addr "readAddrOffAddr#" GenPrimOp

    primop ReadOffAddrOp_Float "readFloatOffAddr#" GenPrimOp
    primop ReadOffAddrOp_Double "readDoubleOffAddr#" GenPrimOp

    primop ReadOffAddrOp_StablePtr "readStablePtrOffAddr#" GenPrimOp

    primop ReadOffAddrOp_Int8 "readInt8OffAddr#" GenPrimOp
    primop ReadOffAddrOp_Int16 "readInt16OffAddr#" GenPrimOp
    primop ReadOffAddrOp_Int32 "readInt32OffAddr#" GenPrimOp
    primop ReadOffAddrOp_Int64 "readInt64OffAddr#" GenPrimOp

    primop ReadOffAddrOp_Word8 "readWord8OffAddr#" GenPrimOp
    primop ReadOffAddrOp_Word16 "readWord16OffAddr#" GenPrimOp
    primop ReadOffAddrOp_Word32 "readWord32OffAddr#" GenPrimOp
    primop ReadOffAddrOp_Word64 "readWord64OffAddr#" GenPrimOp

{-
instance Storable Double
instance Storable Bool
instance Storable Char
instance Storable Int
instance Storable Float
...
-}

{-

instance UA ()
instance (UA a, UA b) => UA (a :*: b)
instance UA Bool
instance UA Char
instance UA Int
instance UA Float
instance UA Double
...
-}

So what's a type that's Storable, but not writable in UA (or UArray or ..)

-- Don


More information about the Haskell-Cafe mailing list