| Copyright | (c) Dong Han 2017-2018 | 
|---|---|
| License | BSD | 
| Maintainer | winterland1989@gmail.com | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Std.Data.PrimArray.QQ
Description
This module provides functions for writing PrimArray related literals QuasiQuote.
Synopsis
- arrASCII :: QuasiQuoter
 - arrW8 :: QuasiQuoter
 - arrW16 :: QuasiQuoter
 - arrW32 :: QuasiQuoter
 - arrW64 :: QuasiQuoter
 - arrWord :: QuasiQuoter
 - arrI8 :: QuasiQuoter
 - arrI16 :: QuasiQuoter
 - arrI32 :: QuasiQuoter
 - arrI64 :: QuasiQuoter
 - arrInt :: QuasiQuoter
 - asciiLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - utf8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - word8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - word16Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - word32Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - word64Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - wordLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - int8Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - int16Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - int32Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - int64Literal :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - intLiteral :: (ExpQ -> ExpQ -> ExpQ) -> String -> ExpQ
 - word8ArrayFromAddr :: Int -> Addr# -> PrimArray Word8
 - word16ArrayFromAddr :: Int -> Addr# -> PrimArray Word16
 - word32ArrayFromAddr :: Int -> Addr# -> PrimArray Word32
 - word64ArrayFromAddr :: Int -> Addr# -> PrimArray Word64
 - wordArrayFromAddr :: Int -> Addr# -> PrimArray Word
 - int8ArrayFromAddr :: Int -> Addr# -> PrimArray Int8
 - int16ArrayFromAddr :: Int -> Addr# -> PrimArray Int16
 - int32ArrayFromAddr :: Int -> Addr# -> PrimArray Int32
 - int64ArrayFromAddr :: Int -> Addr# -> PrimArray Int64
 - intArrayFromAddr :: Int -> Addr# -> PrimArray Int
 
PrimArray literal quoters
arrW8 :: QuasiQuoter Source #
arrW16 :: QuasiQuoter Source #
arrW32 :: QuasiQuoter Source #
arrW64 :: QuasiQuoter Source #
arrI8 :: QuasiQuoter Source #
arrI16 :: QuasiQuoter Source #
arrI32 :: QuasiQuoter Source #
arrI64 :: QuasiQuoter Source #
arrInt :: QuasiQuoter Source #
quoter helpers
Arguments
| :: (ExpQ -> ExpQ -> ExpQ) | Construction function which receive a byte
   length   | 
| -> String | Quoter input  | 
| -> ExpQ | Final Quoter  | 
Construct data with ASCII encoded literals.
Example usage:
arrASCII :: QuasiQuoter
arrASCII = QuasiQuoter
    (asciiLiteral $  len addr -> [| word8ArrayFromAddr $(len) $(addr) |])
    ...
word8ArrayFromAddr :: Int -> Addr# -> PrimArray Word8
{--}
word8ArrayFromAddr l addr# = runST $ do
    mba <- newPrimArray (I# l)
    copyPtrToMutablePrimArray mba 0 (Ptr addr#) l
    unsafeFreezePrimArray mba