Safe Haskell | None |
---|---|
Language | Haskell98 |
This module uses template Haskell. Following is a simplified explanation of usage for those unfamiliar with calling Template Haskell functions.
The function embedFile
in this modules embeds a file into the executable
that you can use it at runtime. A file is represented as a ByteString
.
However, as you can see below, the type signature indicates a value of type
Q Exp
will be returned. In order to convert this into a ByteString
, you
must use Template Haskell syntax, e.g.:
$(embedFile "myfile.txt")
This expression will have type ByteString
. Be certain to enable the
TemplateHaskell language extension, usually by adding the following to the
top of your module:
{-# LANGUAGE TemplateHaskell #-}
- embedFile :: FilePath -> Q Exp
- embedOneFileOf :: [FilePath] -> Q Exp
- embedDir :: FilePath -> Q Exp
- getDir :: FilePath -> IO [(FilePath, ByteString)]
- embedStringFile :: FilePath -> Q Exp
- embedOneStringFileOf :: [FilePath] -> Q Exp
- dummySpace :: Int -> Q Exp
- dummySpaceWith :: ByteString -> Int -> Q Exp
- inject :: ByteString -> ByteString -> Maybe ByteString
- injectFile :: ByteString -> FilePath -> FilePath -> IO ()
- injectWith :: ByteString -> ByteString -> ByteString -> Maybe ByteString
- injectFileWith :: ByteString -> ByteString -> FilePath -> FilePath -> IO ()
- makeRelativeToProject :: FilePath -> Q FilePath
- stringToBs :: String -> ByteString
- bsToExp :: ByteString -> Q Exp
- strToExp :: String -> Q Exp
Embed at compile time
embedFile :: FilePath -> Q Exp Source #
Embed a single file in your source code.
import qualified Data.ByteString myFile :: Data.ByteString.ByteString myFile = $(embedFile "dirName/fileName")
embedOneFileOf :: [FilePath] -> Q Exp Source #
Embed a single existing file in your source code out of list a list of paths supplied.
import qualified Data.ByteString myFile :: Data.ByteString.ByteString myFile = $(embedFile' [ "dirName/fileName", "src/dirName/fileName" ])
embedDir :: FilePath -> Q Exp Source #
Embed a directory recursively in your source code.
import qualified Data.ByteString myDir :: [(FilePath, Data.ByteString.ByteString)] myDir = $(embedDir "dirName")
getDir :: FilePath -> IO [(FilePath, ByteString)] Source #
Get a directory tree in the IO monad.
This is the workhorse of embedDir
Embed as a IsString
embedStringFile :: FilePath -> Q Exp Source #
Embed a single file in your source code.
import Data.String myFile :: IsString a => a myFile = $(embedStringFile "dirName/fileName")
Since 0.0.9
embedOneStringFileOf :: [FilePath] -> Q Exp Source #
Embed a single existing string file in your source code out of list a list of paths supplied.
Since 0.0.9
Inject into an executable
The inject system allows arbitrary content to be embedded inside a Haskell executable, post compilation. Typically, file-embed allows you to read some contents from the file system at compile time and embed them inside your executable. Consider a case, instead, where you would want to embed these contents after compilation. Two real-world examples are:
- You would like to embed a hash of the executable itself, for sanity checking in a network protocol. (Obviously the hash will change after you embed the hash.)
- You want to create a self-contained web server that has a set of content, but will need to update the content on machines that do not have access to GHC.
The typical workflow use:
- Use
dummySpace
ordummySpaceWith
to create some empty space in your executable - Use
injectFile
orinjectFileWith
from a separate utility to modify that executable to have the updated content.
The reason for the With
-variant of the functions is for cases where you wish
to inject multiple different kinds of content, and therefore need control over
the magic key. If you know for certain that there will only be one dummy space
available, you can use the non-With
variants.
dummySpace :: Int -> Q Exp Source #
Allocate the given number of bytes in the generate executable. That space
can be filled up with the inject
and injectFile
functions.
dummySpaceWith :: ByteString -> Int -> Q Exp Source #
Like dummySpace
, but takes a postfix for the magic string. In
order for this to work, the same postfix must be used by inject
/
injectFile
. This allows an executable to have multiple
ByteString
s injected into it, without encountering collisions.
Since 0.0.8
:: ByteString | bs to inject |
-> ByteString | original BS containing dummy |
-> Maybe ByteString | new BS, or Nothing if there is insufficient dummy space |
Inject some raw data inside a ByteString
containing empty, dummy space
(allocated with dummySpace
). Typically, the original ByteString
is an
executable read from the filesystem.
:: ByteString | bs to inject |
-> FilePath | template file |
-> FilePath | output file |
-> IO () |
Same as inject
, but instead of performing the injecting in memory, read
the contents from the filesystem and write back to a different file on the
filesystem.
:: ByteString | postfix of magic string |
-> ByteString | bs to inject |
-> ByteString | original BS containing dummy |
-> Maybe ByteString | new BS, or Nothing if there is insufficient dummy space |
Like inject
, but takes a postfix for the magic string.
Since 0.0.8
:: ByteString | postfix of magic string |
-> ByteString | bs to inject |
-> FilePath | template file |
-> FilePath | output file |
-> IO () |
Like injectFile
, but takes a postfix for the magic string.
Since 0.0.8
Relative path manipulation
Internal
stringToBs :: String -> ByteString Source #