{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# LANGUAGE QuasiQuotes #-}
module Dhall.Docs.Store (getDocsHomeDirectory, makeHashForDirectory) where
import Dhall.Crypto (SHA256Digest (..))
import Path (Abs, Dir, Path, Rel, (</>))
import Path.IO (XdgDirectory (..))
import qualified Control.Monad as Monad
import qualified Crypto.Hash.SHA256
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Base16 as Base16
import qualified Data.ByteString.Char8 as ByteString.Char8
import qualified Data.List as List
import qualified Path
import qualified Path.IO
getDocsHomeDirectory :: IO (Path Abs Dir)
getDocsHomeDirectory :: IO (Path Abs Dir)
getDocsHomeDirectory = do
Path Abs Dir
dir <- forall (m :: * -> *).
MonadIO m =>
XdgDirectory -> Maybe (Path Rel Dir) -> m (Path Abs Dir)
Path.IO.getXdgDir XdgDirectory
Path.IO.XdgData forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ [Path.reldir|dhall-docs|]
forall (m :: * -> *) b. MonadIO m => Path b Dir -> m ()
Path.IO.ensureDir Path Abs Dir
dir
forall (m :: * -> *) a. Monad m => a -> m a
return Path Abs Dir
dir
makeHashForDirectory :: Path Abs Dir -> IO SHA256Digest
makeHashForDirectory :: Path Abs Dir -> IO SHA256Digest
makeHashForDirectory Path Abs Dir
dir = do
([Path Rel Dir]
dirs, [Path Rel File]
files) <- forall (m :: * -> *) b.
MonadIO m =>
Path b Dir -> m ([Path Rel Dir], [Path Rel File])
Path.IO.listDirRecurRel Path Abs Dir
dir
let context0 :: Ctx
context0 = Ctx
Crypto.Hash.SHA256.init
let addDir :: Ctx -> Path b t -> m Ctx
addDir Ctx
context Path b t
directory = do
let nameBytes :: ByteString
nameBytes = String -> ByteString
ByteString.Char8.pack (forall b t. Path b t -> String
Path.toFilePath Path b t
directory)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! Ctx -> ByteString -> Ctx
Crypto.Hash.SHA256.update Ctx
context ByteString
nameBytes
Ctx
context1 <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
Monad.foldM forall {m :: * -> *} {b} {t}. Monad m => Ctx -> Path b t -> m Ctx
addDir Ctx
context0 (forall a. Ord a => [a] -> [a]
List.sort [Path Rel Dir]
dirs)
let addFile :: Ctx -> Path Rel t -> IO Ctx
addFile Ctx
context Path Rel t
file = do
let nameBytes :: ByteString
nameBytes = String -> ByteString
ByteString.Char8.pack (forall b t. Path b t -> String
Path.toFilePath Path Rel t
file)
ByteString
contentBytes <- String -> IO ByteString
ByteString.readFile (forall b t. Path b t -> String
Path.toFilePath (Path Abs Dir
dir forall b t. Path b Dir -> Path Rel t -> Path b t
</> Path Rel t
file))
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! Ctx -> [ByteString] -> Ctx
Crypto.Hash.SHA256.updates Ctx
context [ ByteString
nameBytes, ByteString
contentBytes ]
Ctx
context2 <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
Monad.foldM forall {t}. Ctx -> Path Rel t -> IO Ctx
addFile Ctx
context1 (forall a. Ord a => [a] -> [a]
List.sort [Path Rel File]
files)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> SHA256Digest
SHA256Digest (Ctx -> ByteString
Crypto.Hash.SHA256.finalize Ctx
context2))