{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards   #-}
module Dhall.DirectoryTree
    ( 
      toDirectoryTree
    , FilesystemError(..)
    ) where
import Control.Exception (Exception)
import Data.Monoid ((<>))
import Data.Void (Void)
import Dhall.Syntax (Chunks(..), Expr(..))
import System.FilePath ((</>))
import qualified Control.Exception                       as Exception
import qualified Data.Text.Prettyprint.Doc.Render.String as Pretty
import qualified Dhall.Util                              as Util
import qualified Dhall.Map                               as Map
import qualified Dhall.Pretty
import qualified System.Directory                        as Directory
import qualified Data.Text                               as Text
import qualified Data.Text.IO                            as Text.IO
toDirectoryTree :: FilePath -> Expr Void Void -> IO ()
toDirectoryTree path expression = case expression of
    RecordLit keyValues -> do
        let process key value = do
                Directory.createDirectoryIfMissing False path
                toDirectoryTree (path </> Text.unpack key) value
        Map.unorderedTraverseWithKey_ process keyValues
    TextLit (Chunks [] text) -> do
        Text.IO.writeFile path text
    Some value -> do
        toDirectoryTree path value
    App None _ -> do
        return ()
    _ -> do
        let unexpectedExpression = expression
        Exception.throwIO FilesystemError{..}
newtype FilesystemError =
    FilesystemError { unexpectedExpression :: Expr Void Void }
instance Show FilesystemError where
    show FilesystemError{..} =
        Pretty.renderString (Dhall.Pretty.layout message)
      where
        message =
          Util._ERROR <> ": Not a valid directory tree expression\n\
          \                                                                                \n\
          \Explanation: Only a subset of Dhall expressions can be converted to a directory \n\
          \tree.  Specifically, record literals can be converted to directories, ❰Text❱    \n\
          \literals can be converted to files, and ❰Optional❱ values are included if ❰Some❱\n\
          \and omitted if ❰None❱.  No other type of value can be translated to a directory \n\
          \tree.                                                                           \n\
          \                                                                                \n\
          \For example, this is a valid expression that can be translated to a directory   \n\
          \tree:                                                                           \n\
          \                                                                                \n\
          \                                                                                \n\
          \    ┌──────────────────────────────────┐                                        \n\
          \    │ { `example.json` = \"[1, true]\" } │                                      \n\
          \    └──────────────────────────────────┘                                        \n\
          \                                                                                \n\
          \                                                                                \n\
          \In contrast, the following expression is not allowed due to containing a        \n\
          \❰Natural❱ field, which cannot be translated in this way:                        \n\
          \                                                                                \n\
          \                                                                                \n\
          \    ┌───────────────────────┐                                                   \n\
          \    │ { `example.txt` = 1 } │                                                   \n\
          \    └───────────────────────┘                                                   \n\
          \                                                                                \n\
          \                                                                                \n\
          \You tried to translate the following expression to a directory tree:            \n\
          \                                                                                \n\
          \" <> Util.insert unexpectedExpression <> "\n\
          \                                                                                \n\
          \... which is neither a ❰Text❱ literal, a record literal, nor an ❰Optional❱      \n\
          \value.                                                                          \n"
instance Exception FilesystemError