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 #-}
Embed at compile time
embedFile :: FilePath -> Q Exp Source #
Embed a single file in your source code.
import Data.String myFile :: IsString a => a myFile = $(embedFile "dirName/fileName")
embedOneFileOf :: [FilePath] -> Q Exp Source #
Embed a single existing string file in your source code out of list a list of paths supplied.
embedDir :: FilePath -> Q Exp Source #
Embed a directory recursively in your source code.
import Data.String myDir :: IsString a => [(FilePath, a)] myDir = $(embedDir "dirName")
Relative path manipulation
makeRelativeToProject :: FilePath -> Q FilePath Source #
Take a relative file path and attach it to the root of the current project.
The idea here is that, when building with Stack, the build will always be
executed with a current working directory of the root of the project (where
your .cabal file is located). However, if you load up multiple projects with
stack ghci
, the working directory may be something else entirely.
This function looks at the source location of the Haskell file calling it, finds the first parent directory with a .cabal file, and uses that as the root directory for fixing the relative path.
$(makeRelativeToProject "data/foo.txt" >>= embedFile)
Since: 0.0.10