Skip to content

Instantly share code, notes, and snippets.

@malte-v
Created July 2, 2020 12:54
Show Gist options
  • Save malte-v/c171b6d03e2a0d194a2f4d1cb50b8be5 to your computer and use it in GitHub Desktop.
Save malte-v/c171b6d03e2a0d194a2f4d1cb50b8be5 to your computer and use it in GitHub Desktop.
{-# LANGUAGE TemplateHaskell #-}
module Common.TH
( includeFileInSource,
chooseAndIncludeFileInSource,
)
where
import Control.Monad.Extra (findM)
import Language.Haskell.TH
import RIO
import RIO.ByteString (pack, readFile, unpack)
import RIO.Directory (doesFileExist)
includeFileInSource ::
-- | Path to file
FilePath ->
-- | Haskell value name
String ->
Q [Dec]
includeFileInSource fp n = do
byteString <- runIO $ readFile fp
tWord8 <- [t|Word8|]
tByteString <- [t|ByteString|]
fnPack <- [|pack|]
pure
[ SigD (mkName n) tByteString,
FunD
(mkName n)
[ Clause
[]
( NormalB
$ AppE (SigE fnPack $ ArrowT `AppT` (ListT `AppT` tWord8) `AppT` tByteString)
$ ListE
$ fmap (LitE . IntegerL . fromIntegral) (unpack byteString)
)
[]
]
]
chooseAndIncludeFileInSource ::
-- | Paths to files
[FilePath] ->
-- | Haskell value name
String ->
Q [Dec]
chooseAndIncludeFileInSource haystack name = do
mbNeedle <- runIO $ findM doesFileExist haystack
case mbNeedle of
Just needle -> includeFileInSource needle name
Nothing -> error "None of the file choices exist."
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment