{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
module Haskus.Memory.Embed
( embedBytes
, embedFile
, embedBuffer
, embedPinnedBuffer
, embedUnpinnedBuffer
, loadSymbol
, loadMutableSymbol
, toBufferE
, toBufferE'
, toBufferME
, toBufferME'
, makeEmbeddingFile
, EmbedEntry (..)
, SectionType (..)
)
where
import Haskus.Memory.Buffer
import Haskus.Number.Word
import Haskus.Utils.List (intersperse)
import Haskus.Utils.Maybe
import Haskus.Utils.Monad
import Foreign.Ptr
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import System.Directory (getFileSize)
import GHC.Exts
import System.IO
embedBytes :: [Word8] -> Q (TExp BufferE)
embedBytes bs = do
bufE <- fromMaybe (error "Please import Haskus.Memory.Embed") <$> lookupValueName "toBufferE'"
return $ TExp $ VarE bufE
`AppE` LitE (StringPrimL bs)
`AppE` LitE (WordPrimL (fromIntegral (length bs)))
loadSymbol :: Word -> String -> Q Exp
loadSymbol sz sym = do
nam <- newName sym
bufE <- fromMaybe (error "Please import Haskus.Memory.Embed") <$> lookupValueName "toBufferE"
ptrTy <- [t| Ptr () |]
addTopDecls
[ ForeignD $ ImportF CCall unsafe ("&"++sym) nam ptrTy
]
return $ VarE bufE
`AppE` VarE nam
`AppE` LitE (WordPrimL (fromIntegral sz))
loadMutableSymbol :: Word -> String -> Q Exp
loadMutableSymbol sz sym = do
nam <- newName sym
bufE <- fromMaybe (error "Please import Haskus.Memory.Embed") <$> lookupValueName "toBufferME"
ptrTy <- [t| Ptr () |]
addTopDecls
[ ForeignD $ ImportF CCall unsafe ("&"++sym) nam ptrTy
]
return $ VarE bufE
`AppE` VarE nam
`AppE` LitE (WordPrimL (fromIntegral sz))
toBufferE :: Ptr () -> Word# -> BufferE
{-# INLINABLE toBufferE #-}
toBufferE (Ptr x) sz = BufferE x (W# sz)
toBufferE' :: Addr# -> Word# -> BufferE
{-# INLINABLE toBufferE' #-}
toBufferE' x sz = BufferE x (W# sz)
toBufferME :: Ptr () -> Word# -> BufferME
{-# INLINABLE toBufferME #-}
toBufferME (Ptr x) sz = BufferME x (W# sz)
toBufferME' :: Addr# -> Word# -> BufferME
{-# INLINABLE toBufferME' #-}
toBufferME' x sz = BufferME x (W# sz)
data SectionType
= ReadOnlySection
| WriteableSection
| UninitializedSection
deriving (Show,Eq,Ord)
data EmbedEntry = EmbedEntry
{ embedEntryType :: SectionType
, embedEntryAlignement :: Word
, embedEntrySymbol :: String
, embedEntryFilePath :: FilePath
, embedEntryOffset :: Maybe Word
, embedEntrySize :: Maybe Word
}
deriving (Show,Eq,Ord)
makeEmbedEntry :: EmbedEntry -> String
makeEmbedEntry EmbedEntry{..} =
mconcat $ intersperse "\n" $
[ ".section " ++ case embedEntryType of
ReadOnlySection -> "\".rodata\""
WriteableSection -> "\".data\""
UninitializedSection -> "\".bss\""
, ".align " ++ show embedEntryAlignement
, ".global \"" ++ embedEntrySymbol ++ "\""
, embedEntrySymbol ++ ":"
, ".incbin \"" ++ embedEntryFilePath ++ "\""
++ (case embedEntryOffset of
Just offset -> ","++show offset
Nothing -> ",0")
++ (case embedEntrySize of
Just size -> ","++show size
Nothing -> mempty)
, "\n"
]
makeEmbeddingFile :: FilePath -> [EmbedEntry] -> IO ()
makeEmbeddingFile path entries = do
let e = concatMap makeEmbedEntry entries
let escape v = case v of
('"':xs) -> "\\\"" ++ escape xs
('\\':xs) -> "\\\\" ++ escape xs
('\n':xs) -> "\\n" ++ escape xs
x:xs -> x : escape xs
[] -> []
let e' = ("asm(\""++escape e++"\");")
writeFile path e'
embedFile
:: FilePath
-> Bool
-> Maybe Word
-> Maybe Word
-> Maybe Word
-> Q Exp
embedFile = embedFile' False
embedFile' :: Bool -> FilePath -> Bool -> Maybe Word -> Maybe Word -> Maybe Word -> Q Exp
embedFile' nodep path mutable malign moffset msize = do
nam <- newName "buffer"
let sym = show nam ++ "_data"
let entry = EmbedEntry
{ embedEntryType = if mutable
then WriteableSection
else ReadOnlySection
, embedEntryAlignement = fromMaybe 1 malign
, embedEntrySymbol = sym
, embedEntryFilePath = path
, embedEntryOffset = moffset
, embedEntrySize = msize
}
sfile <- addTempFile ".c"
liftIO (makeEmbeddingFile sfile [entry])
sz <- case msize of
Just x -> return x
Nothing -> fromIntegral <$> liftIO (getFileSize path)
when (not nodep) $
addDependentFile path
addForeignFilePath LangC sfile
if mutable
then loadMutableSymbol sz sym
else loadSymbol sz sym
embedPinnedBuffer
:: Buffer mut 'Pinned fin heap
-> Bool
-> Maybe Word
-> Maybe Word
-> Maybe Word
-> Q Exp
embedPinnedBuffer buf mut malign moffset msize = do
tmp <- qAddTempFile ".dat"
bsz <- bufferSizeIO buf
let off = fromMaybe 0 moffset
let sz = fromMaybe bsz msize
when (off+sz > bsz) $
fail "Invalid buffer offset/size combination"
liftIO $ unsafeWithBufferPtr buf $ \ptr -> do
withBinaryFile tmp WriteMode $ \hdl -> do
hPutBuf hdl (ptr `plusPtr` fromIntegral off) (fromIntegral sz)
embedFile' True tmp mut malign Nothing Nothing
embedUnpinnedBuffer
:: Buffer mut 'NotPinned fin heap
-> Bool
-> Maybe Word
-> Maybe Word
-> Maybe Word
-> Q Exp
embedUnpinnedBuffer buf mut malign moffset msize = do
bsz <- liftIO (bufferSizeIO buf)
let sz = fromMaybe bsz msize
let off = fromMaybe 0 moffset
b <- newPinnedBuffer sz
liftIO (copyBuffer buf off b 0 sz)
embedPinnedBuffer b mut malign Nothing Nothing
embedBuffer
:: Buffer mut pin fin heap
-> Bool
-> Maybe Word
-> Maybe Word
-> Maybe Word
-> Q Exp
embedBuffer b =
case bufferDynamicallyPinned b of
Left ub -> embedUnpinnedBuffer ub
Right pb -> embedPinnedBuffer pb