module Servant.Swagger.UI.Internal (mkRecursiveEmbedded) where
import Control.Arrow (first)
import Control.Monad (forM)
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as B8
import qualified Data.ByteString.Lazy as BL
import Language.Haskell.TH
import System.Directory
(doesDirectoryExist, getDirectoryContents)
import System.FilePath (makeRelative, (</>))
getRecursiveContents :: FilePath -> IO [(FilePath, BL.ByteString)]
getRecursiveContents topdir = do
names <- getDirectoryContents topdir
let properNames = Prelude.filter (`notElem` [".", ".."]) names
paths <- forM properNames $ \name -> do
let path = topdir </> name
isDirectory <- doesDirectoryExist path
if isDirectory
then getRecursiveContents path
else do contents <- BL.readFile path
return [(path, contents)]
return (concat paths)
makeAllRelative :: FilePath -> [(FilePath, a)] -> [(FilePath, a)]
makeAllRelative topdir = map (first (("/" ++) . makeRelative topdir))
bytestringE :: B.ByteString -> Q Exp
bytestringE b = [| B8.pack $s |]
where s = litE $ stringL $ B8.unpack b
makeEmbeddedEntry :: (FilePath, BL.ByteString) -> Q Exp
makeEmbeddedEntry (path, bs) = [| (path, $(bytestringE $ BL.toStrict bs)) |]
mkRecursiveEmbedded :: FilePath -> Q Exp
mkRecursiveEmbedded topdir = do
pairs <- runIO $ fmap (makeAllRelative topdir) $ getRecursiveContents topdir
listE $ map makeEmbeddedEntry pairs