{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -Wall #-}
module Dhall.Import.Types where
import Control.Exception (Exception)
import Control.Monad.Trans.State.Strict (StateT)
import Data.Dynamic
import Data.List.NonEmpty (NonEmpty)
import Data.Map (Map)
import Data.Semigroup ((<>))
import Data.Text.Prettyprint.Doc (Pretty(..))
import Data.Void (Void)
import Dhall.Context (Context)
import Dhall.Core
( Directory (..)
, Expr
, File (..)
, FilePrefix (..)
, Import (..)
, ImportHashed (..)
, ImportMode (..)
, ImportType (..)
, ReifiedNormalizer(..)
, URL
)
import Dhall.Parser (Src)
import Lens.Family (LensLike')
import System.FilePath (isRelative, splitDirectories)
import qualified Dhall.Context
import qualified Data.Map as Map
import qualified Data.Text
newtype Chained = Chained
{ chainedImport :: Import
}
deriving (Eq, Ord)
instance Pretty Chained where
pretty (Chained import_) = pretty import_
data ImportSemantics = ImportSemantics
{ importSemantics :: Expr Src Void
}
data Depends = Depends { parent :: Chained, child :: Chained }
data SemanticCacheMode = IgnoreSemanticCache | UseSemanticCache deriving (Eq)
data Status = Status
{ _stack :: NonEmpty Chained
, _graph :: [Depends]
, _cache :: Map Chained ImportSemantics
, _remote :: URL -> StateT Status IO Data.Text.Text
, _normalizer :: Maybe (ReifiedNormalizer Void)
, _startingContext :: Context (Expr Src Void)
, _semanticCacheMode :: SemanticCacheMode
}
emptyStatusWith :: (URL -> StateT Status IO Data.Text.Text) -> FilePath -> Status
emptyStatusWith _remote rootDirectory = Status {..}
where
_stack = pure (Chained rootImport)
_graph = []
_cache = Map.empty
_normalizer = Nothing
_startingContext = Dhall.Context.empty
_semanticCacheMode = UseSemanticCache
prefix = if isRelative rootDirectory
then Here
else Absolute
pathComponents =
fmap Data.Text.pack (reverse (splitDirectories rootDirectory))
dirAsFile = File (Directory pathComponents) "."
rootImport = Import
{ importHashed = ImportHashed
{ hash = Nothing
, importType = Local prefix dirAsFile
}
, importMode = Code
}
stack :: Functor f => LensLike' f Status (NonEmpty Chained)
stack k s = fmap (\x -> s { _stack = x }) (k (_stack s))
graph :: Functor f => LensLike' f Status [Depends]
graph k s = fmap (\x -> s { _graph = x }) (k (_graph s))
cache :: Functor f => LensLike' f Status (Map Chained ImportSemantics)
cache k s = fmap (\x -> s { _cache = x }) (k (_cache s))
remote
:: Functor f => LensLike' f Status (URL -> StateT Status IO Data.Text.Text)
remote k s = fmap (\x -> s { _remote = x }) (k (_remote s))
normalizer :: Functor f => LensLike' f Status (Maybe (ReifiedNormalizer Void))
normalizer k s = fmap (\x -> s {_normalizer = x}) (k (_normalizer s))
startingContext :: Functor f => LensLike' f Status (Context (Expr Src Void))
startingContext k s =
fmap (\x -> s { _startingContext = x }) (k (_startingContext s))
data InternalError = InternalError deriving (Typeable)
instance Show InternalError where
show InternalError = unlines
[ _ERROR <> ": Compiler bug "
, " "
, "Explanation: This error message means that there is a bug in the Dhall compiler."
, "You didn't do anything wrong, but if you would like to see this problem fixed "
, "then you should report the bug at: "
, " "
, "https://github.com/dhall-lang/dhall-haskell/issues "
, " "
, "Please include the following text in your bug report: "
, " "
, "``` "
, "Header extraction failed even though the header type-checked "
, "``` "
]
where
_ERROR :: String
_ERROR = "\ESC[1;31mError\ESC[0m"
instance Exception InternalError
data PrettyHttpException = PrettyHttpException String Dynamic
deriving (Typeable)
instance Exception PrettyHttpException
instance Show PrettyHttpException where
show (PrettyHttpException msg _) = msg