module Dhall.Import (
exprFromPath
, load
, loadWith
, loadWithContext
, hashExpression
, hashExpressionToCode
, Status(..)
, emptyStatus
, Cycle(..)
, ReferentiallyOpaque(..)
, Imported(..)
, PrettyHttpException(..)
, MissingFile(..)
, MissingEnvironmentVariable(..)
) where
import Control.Applicative (empty)
import Control.Exception
(Exception, IOException, SomeException, onException, throwIO)
import Control.Monad (join)
import Control.Monad.Catch (throwM, MonadCatch(catch))
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.State.Strict (StateT)
import Crypto.Hash (SHA256)
import Data.ByteString.Lazy (ByteString)
import Data.CaseInsensitive (CI)
import Data.Map (Map)
import Data.Monoid ((<>))
import Data.Text.Lazy (Text)
import Data.Text.Lazy.Builder (Builder)
#if MIN_VERSION_base(4,8,0)
#else
import Data.Traversable (traverse)
#endif
import Data.Typeable (Typeable)
import Formatting.Buildable (build)
import System.FilePath ((</>))
import Dhall.Core
( Expr(..)
, Chunks(..)
, HasHome(..)
, PathHashed(..)
, PathMode(..)
, PathType(..)
, Path(..)
)
import Dhall.Parser (Parser(..), ParseError(..), Src(..))
import Dhall.TypeCheck (X(..))
import Lens.Family (LensLike')
import Lens.Family.State.Strict (zoom)
#if MIN_VERSION_http_client(0,5,0)
import Network.HTTP.Client
(HttpException(..), HttpExceptionContent(..), Manager)
#else
import Network.HTTP.Client (HttpException(..), Manager)
#endif
import Text.Trifecta (Result(..))
import Text.Trifecta.Delta (Delta(..))
import qualified Control.Monad.Trans.State.Strict as State
import qualified Crypto.Hash
import qualified Data.ByteArray
import qualified Data.ByteString
import qualified Data.ByteString.Char8
import qualified Data.ByteString.Lazy
import qualified Data.CaseInsensitive
import qualified Data.Foldable
import qualified Data.List as List
import qualified Data.HashMap.Strict.InsOrd
import qualified Data.Map.Strict as Map
import qualified Data.Text.Encoding
import qualified Data.Text.IO
import qualified Data.Text.Lazy as Text
import qualified Data.Text.Lazy.Builder as Builder
import qualified Data.Text.Lazy.Encoding
import qualified Data.Text.Lazy.IO
import qualified Dhall.Core
import qualified Dhall.Parser
import qualified Dhall.Context
import qualified Dhall.TypeCheck
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.TLS as HTTP
import qualified System.Environment
import qualified System.Directory
import qualified System.FilePath as FilePath
import qualified Text.Parser.Combinators
import qualified Text.Parser.Token
import qualified Text.Trifecta
builderToString :: Builder -> String
builderToString = Text.unpack . Builder.toLazyText
newtype Cycle = Cycle
{ cyclicImport :: Path
}
deriving (Typeable)
instance Exception Cycle
instance Show Cycle where
show (Cycle path) = "\nCyclic import: " ++ builderToString (build path)
newtype ReferentiallyOpaque = ReferentiallyOpaque
{ opaqueImport :: Path
} deriving (Typeable)
instance Exception ReferentiallyOpaque
instance Show ReferentiallyOpaque where
show (ReferentiallyOpaque path) =
"\nReferentially opaque import: " ++ builderToString (build path)
data Imported e = Imported
{ importStack :: [Path]
, nested :: e
} deriving (Typeable)
instance Exception e => Exception (Imported e)
instance Show e => Show (Imported e) where
show (Imported paths e) =
(case paths of [] -> ""; _ -> "\n")
++ unlines (map indent paths')
++ show e
where
indent (n, path) =
take (2 * n) (repeat ' ') ++ "↳ " ++ builderToString (build path)
paths' = zip [0..] (drop 1 (reverse (canonicalizeAll paths)))
newtype PrettyHttpException = PrettyHttpException HttpException
deriving (Typeable)
instance Exception PrettyHttpException
#if MIN_VERSION_http_client(0,5,0)
instance Show PrettyHttpException where
show (PrettyHttpException (InvalidUrlException _ r)) =
"\n"
<> "\ESC[1;31mError\ESC[0m: Invalid URL\n"
<> "\n"
<> "↳ " <> show r
show (PrettyHttpException (HttpExceptionRequest _ e)) = case e of
ConnectionFailure e' ->
"\n"
<> "\ESC[1;31mError\ESC[0m: Wrong host\n"
<> "\n"
<> "↳ " <> show e'
InvalidDestinationHost host ->
"\n"
<> "\ESC[1;31mError\ESC[0m: Invalid host name\n"
<> "\n"
<> "↳ " <> show host
ResponseTimeout ->
"\ESC[1;31mError\ESC[0m: The host took too long to respond\n"
e' -> "\n" <> show e'
#else
instance Show PrettyHttpException where
show (PrettyHttpException e) = case e of
FailedConnectionException2 _ _ _ e' ->
"\n"
<> "\ESC[1;31mError\ESC[0m: Wrong host\n"
<> "\n"
<> "↳ " <> show e'
InvalidDestinationHost host ->
"\n"
<> "\ESC[1;31mError\ESC[0m: Invalid host name\n"
<> "\n"
<> "↳ " <> show host
ResponseTimeout ->
"\ESC[1;31mError\ESC[0m: The host took too long to respond\n"
e' -> "\n"
<> show e'
#endif
data MissingFile = MissingFile FilePath
deriving (Typeable)
instance Exception MissingFile
instance Show MissingFile where
show (MissingFile path) =
"\n"
<> "\ESC[1;31mError\ESC[0m: Missing file "
<> path
<> "\n"
newtype MissingEnvironmentVariable = MissingEnvironmentVariable { name :: Text }
deriving (Typeable)
instance Exception MissingEnvironmentVariable
instance Show MissingEnvironmentVariable where
show (MissingEnvironmentVariable {..}) =
"\n"
<> "\ESC[1;31mError\ESC[0m: Missing environment variable\n"
<> "\n"
<> "↳ " <> Text.unpack name
data Status = Status
{ _stack :: [Path]
, _cache :: Map Path (Expr Src X)
, _manager :: Maybe Manager
}
emptyStatus :: Status
emptyStatus = Status [] Map.empty Nothing
canonicalizeAll :: [Path] -> [Path]
canonicalizeAll = map canonicalizePath . List.tails
stack :: Functor f => LensLike' f Status [Path]
stack k s = fmap (\x -> s { _stack = x }) (k (_stack s))
cache :: Functor f => LensLike' f Status (Map Path (Expr Src X))
cache k s = fmap (\x -> s { _cache = x }) (k (_cache s))
manager :: Functor f => LensLike' f Status (Maybe Manager)
manager k s = fmap (\x -> s { _manager = x }) (k (_manager s))
needManager :: StateT Status IO Manager
needManager = do
x <- zoom manager State.get
case x of
Just m -> return m
Nothing -> do
let settings = HTTP.tlsManagerSettings
#if MIN_VERSION_http_client(0,5,0)
{ HTTP.managerResponseTimeout = HTTP.responseTimeoutMicro (30 * 1000 * 1000) }
#else
{ HTTP.managerResponseTimeout = Just (30 * 1000 * 1000) }
#endif
m <- liftIO (HTTP.newManager settings)
zoom manager (State.put (Just m))
return m
canonicalize :: [PathType] -> PathType
canonicalize [] = File Homeless "."
canonicalize (File hasHome0 file0:paths0) =
if FilePath.isRelative file0 && hasHome0 == Homeless
then go file0 paths0
else File hasHome0 (FilePath.normalise file0)
where
go currPath [] = File Homeless (FilePath.normalise currPath)
go currPath (Env _ :_ ) = File Homeless (FilePath.normalise currPath)
go currPath (URL url0 headers:rest ) = combine prefix suffix
where
headers' = fmap (onPathType (\h -> canonicalize (h:rest))) headers
prefix = parentURL (removeAtFromURL url0)
suffix = FilePath.normalise currPath
combine url path = case List.stripPrefix "../" path of
Just path' -> combine url' path'
where
url' = parentURL (removeAtFromURL url)
Nothing -> case List.stripPrefix "./" path of
Just path' -> combine url path'
Nothing ->
case Text.last url of
'/' -> URL (url <> path') headers'
_ -> URL (url <> "/" <> path') headers'
where
path' = Text.pack path
go currPath (File hasHome file:paths) =
if FilePath.isRelative file && hasHome == Homeless
then go file' paths
else File hasHome (FilePath.normalise file')
where
file' = FilePath.takeDirectory (removeAtFromFilename file) </> currPath
canonicalize (URL path headers:rest) = URL path headers'
where
headers' = fmap (onPathType (\h -> canonicalize (h:rest))) headers
canonicalize (Env env :_ ) = Env env
onPathType :: (PathType -> PathType) -> PathHashed -> PathHashed
onPathType f (PathHashed a b) = PathHashed a (f b)
canonicalizePath :: [Path] -> Path
canonicalizePath [] =
Path
{ pathMode = Code
, pathHashed = PathHashed
{ hash = Nothing
, pathType = canonicalize []
}
}
canonicalizePath (path:paths) =
Path
{ pathMode = pathMode path
, pathHashed = (pathHashed path)
{ hash = hash (pathHashed path)
, pathType =
canonicalize (map (pathType . pathHashed) (path:paths))
}
}
parentURL :: Text -> Text
parentURL = Text.dropWhileEnd (/= '/')
removeAtFromURL:: Text -> Text
removeAtFromURL url
| Text.isSuffixOf "/@" url = Text.dropEnd 2 url
| Text.isSuffixOf "/" url = Text.dropEnd 1 url
| otherwise = url
removeAtFromFilename :: FilePath -> FilePath
removeAtFromFilename fp =
if FilePath.takeFileName fp == "@"
then FilePath.takeDirectory fp
else fp
toHeaders
:: Expr s a
-> Maybe [(CI Data.ByteString.ByteString, Data.ByteString.ByteString)]
toHeaders (ListLit _ hs) = do
hs' <- mapM toHeader hs
return (Data.Foldable.toList hs')
toHeaders _ = do
empty
toHeader
:: Expr s a
-> Maybe (CI Data.ByteString.ByteString, Data.ByteString.ByteString)
toHeader (RecordLit m) = do
TextLit (Chunks [] keyBuilder ) <- Data.HashMap.Strict.InsOrd.lookup "header" m
TextLit (Chunks [] valueBuilder) <- Data.HashMap.Strict.InsOrd.lookup "value" m
let keyText = Text.toStrict (Builder.toLazyText keyBuilder )
let valueText = Text.toStrict (Builder.toLazyText valueBuilder)
let keyBytes = Data.Text.Encoding.encodeUtf8 keyText
let valueBytes = Data.Text.Encoding.encodeUtf8 valueText
return (Data.CaseInsensitive.mk keyBytes, valueBytes)
toHeader _ = do
empty
data InternalError = InternalError deriving (Typeable)
_ERROR :: String
_ERROR = "\ESC[1;31mError\ESC[0m"
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 "
, "``` "
]
instance Exception InternalError
data HashMismatch = HashMismatch
{ expectedHash :: Crypto.Hash.Digest SHA256
, actualHash :: Crypto.Hash.Digest SHA256
} deriving (Typeable)
instance Exception HashMismatch
instance Show HashMismatch where
show (HashMismatch {..}) =
"\n"
<> "\ESC[1;31mError\ESC[0m: Import integrity check failed\n"
<> "\n"
<> "Expected hash:\n"
<> "\n"
<> "↳ " <> show expectedHash <> "\n"
<> "\n"
<> "Actual hash:\n"
<> "\n"
<> "↳ " <> show actualHash <> "\n"
parseFromFileEx
:: Text.Trifecta.Parser a
-> FilePath
-> IO (Text.Trifecta.Result a)
parseFromFileEx parser path = do
text <- Data.Text.Lazy.IO.readFile path
let lazyBytes = Data.Text.Lazy.Encoding.encodeUtf8 text
let strictBytes = Data.ByteString.Lazy.toStrict lazyBytes
let delta = Directed bytesPath 0 0 0 0
return (Text.Trifecta.parseByteString parser delta strictBytes)
where
bytesPath = Data.ByteString.Char8.pack path
exprFromPath :: Path -> StateT Status IO (Expr Src Path)
exprFromPath (Path {..}) = case pathType of
File hasHome file -> liftIO (do
path <- case hasHome of
Home -> do
home <- System.Directory.getHomeDirectory
return (home </> file)
Homeless -> do
return file
case pathMode of
Code -> do
exists <- System.Directory.doesFileExist path
if exists
then return ()
else throwIO (MissingFile path)
let handler :: IOException -> IO (Result (Expr Src Path))
handler e = do
parseFromFileEx parser (path </> "@")
`onException` throwIO e
x <- parseFromFileEx parser path `catch` handler
case x of
Failure errInfo -> do
throwIO (ParseError (Text.Trifecta._errDoc errInfo))
Success expr -> do
return expr
RawText -> do
text <- Data.Text.IO.readFile path
return (TextLit (Chunks [] (build text))) )
URL url headerPath -> do
m <- needManager
request <- liftIO (HTTP.parseUrlThrow (Text.unpack url))
let handler :: HTTP.HttpException -> IO (HTTP.Response ByteString)
#if MIN_VERSION_http_client(0,5,0)
handler err@(HttpExceptionRequest _ (StatusCodeException _ _)) = do
#else
handler err@(StatusCodeException _ _ _) = do
#endif
let request' = request { HTTP.path = HTTP.path request <> "/@" }
HTTP.httpLbs request' m `onException` throwIO (PrettyHttpException err)
handler err = throwIO (PrettyHttpException err)
requestWithHeaders <- case headerPath of
Nothing -> return request
Just path -> do
expr <- loadStaticIO Dhall.Context.empty (Path path Code)
let expected :: Expr Src X
expected =
App List
( Record
( Data.HashMap.Strict.InsOrd.fromList
[("header", Text), ("value", Text)]
)
)
let suffix =
( Data.ByteString.Lazy.toStrict
. Data.Text.Lazy.Encoding.encodeUtf8
. Builder.toLazyText
. build
) expected
let annot = case expr of
Note (Src begin end bytes) _ ->
Note (Src begin end bytes') (Annot expr expected)
where
bytes' = bytes <> " : " <> suffix
_ ->
Annot expr expected
case Dhall.TypeCheck.typeOf annot of
Left err -> liftIO (throwIO err)
Right _ -> return ()
let expr' = Dhall.Core.normalize expr
headers <- case toHeaders expr' of
Just headers -> do
return headers
Nothing -> do
liftIO (throwIO InternalError)
let requestWithHeaders = request
{ HTTP.requestHeaders = headers
}
return requestWithHeaders
response <- liftIO (HTTP.httpLbs requestWithHeaders m `catch` handler)
let bytes = HTTP.responseBody response
text <- case Data.Text.Lazy.Encoding.decodeUtf8' bytes of
Left err -> liftIO (throwIO err)
Right text -> return text
case pathMode of
Code -> do
let urlBytes = Data.Text.Lazy.Encoding.encodeUtf8 url
let delta =
Directed (Data.ByteString.Lazy.toStrict urlBytes) 0 0 0 0
case Text.Trifecta.parseString parser delta (Text.unpack text) of
Failure err -> do
let err' = ParseError (Text.Trifecta._errDoc err)
request' <- liftIO (HTTP.parseUrlThrow (Text.unpack url))
let request'' =
request'
{ HTTP.path = HTTP.path request' <> "/@" }
response' <- liftIO (HTTP.httpLbs request'' m `onException` throwIO err' )
let bytes' = HTTP.responseBody response'
text' <- case Data.Text.Lazy.Encoding.decodeUtf8' bytes' of
Left _ -> liftIO (throwIO err')
Right text' -> return text'
case Text.Trifecta.parseString parser delta (Text.unpack text') of
Failure _ -> liftIO (throwIO err')
Success expr -> return expr
Success expr -> return expr
RawText -> do
return (TextLit (Chunks [] (build text)))
Env env -> liftIO (do
x <- System.Environment.lookupEnv (Text.unpack env)
case x of
Just str -> do
case pathMode of
Code -> do
let envBytes = Data.Text.Lazy.Encoding.encodeUtf8 env
let delta =
Directed (Data.ByteString.Lazy.toStrict envBytes) 0 0 0 0
case Text.Trifecta.parseString parser delta str of
Failure errInfo -> do
throwIO (ParseError (Text.Trifecta._errDoc errInfo))
Success expr -> do
return expr
RawText -> return (TextLit (Chunks [] (build str)))
Nothing -> throwIO (MissingEnvironmentVariable env) )
where
PathHashed {..} = pathHashed
parser = unParser (do
Text.Parser.Token.whiteSpace
r <- Dhall.Parser.expr
Text.Parser.Combinators.eof
return r )
loadDynamic
:: forall m . MonadCatch m
=> (Path -> StateT Status m (Expr Src Path))
-> Path
-> StateT Status m (Expr Src Path)
loadDynamic from_path p = do
paths <- zoom stack State.get
let handler :: SomeException -> StateT Status m (Expr Src Path)
handler e = throwM (Imported (p:paths) e)
from_path (canonicalizePath (p:paths)) `catch` handler
loadStaticIO
:: Dhall.Context.Context (Expr Src X)
-> Path
-> StateT Status IO (Expr Src X)
loadStaticIO = loadStaticWith exprFromPath
loadWith
:: MonadCatch m
=> (Path -> StateT Status m (Expr Src Path))
-> Dhall.Context.Context (Expr Src X)
-> Expr Src Path
-> m (Expr Src X)
loadWith from_path ctx = evalStatus (loadStaticWith from_path ctx)
loadWithContext
:: Dhall.Context.Context (Expr Src X)
-> Expr Src Path
-> IO (Expr Src X)
loadWithContext ctx = evalStatus (loadStaticIO ctx)
loadStaticWith
:: MonadCatch m
=> (Path -> StateT Status m (Expr Src Path))
-> Dhall.Context.Context (Expr Src X)
-> Path
-> StateT Status m (Expr Src X)
loadStaticWith from_path ctx path = do
paths <- zoom stack State.get
let local (Path (PathHashed _ (URL _ _ )) _) = False
local (Path (PathHashed _ (File _ _)) _) = True
local (Path (PathHashed _ (Env _ )) _) = True
let parent = canonicalizePath paths
let here = canonicalizePath (path:paths)
if local here && not (local parent)
then throwM (Imported paths (ReferentiallyOpaque path))
else return ()
(expr, cached) <- if here `elem` canonicalizeAll paths
then throwM (Imported paths (Cycle path))
else do
m <- zoom cache State.get
case Map.lookup here m of
Just expr -> return (expr, True)
Nothing -> do
expr' <- loadDynamic from_path path
expr'' <- case traverse (\_ -> Nothing) expr' of
Just expr -> do
zoom cache (State.put $! Map.insert here expr m)
return expr
Nothing -> do
let paths' = path:paths
zoom stack (State.put paths')
expr'' <- fmap join (traverse (loadStaticWith from_path ctx)
expr')
zoom stack (State.put paths)
return expr''
return (expr'', False)
if cached
then return ()
else case Dhall.TypeCheck.typeWith ctx expr of
Left err -> throwM (Imported (path:paths) err)
Right _ -> return ()
case hash (pathHashed path) of
Nothing -> do
return ()
Just expectedHash -> do
let actualHash = hashExpression expr
if expectedHash == actualHash
then return ()
else throwM (HashMismatch {..})
return expr
evalStatus
:: (Traversable f, Monad m, Monad f)
=> (a -> StateT Status m (f b)) -> f a -> m (f b)
evalStatus cb expr = State.evalStateT (fmap join (traverse cb expr)) emptyStatus
load :: Expr Src Path -> IO (Expr Src X)
load = loadWithContext Dhall.Context.empty
hashExpression :: Expr s X -> (Crypto.Hash.Digest SHA256)
hashExpression expr = Crypto.Hash.hashlazy actualBytes
where
text = Dhall.Core.pretty (Dhall.Core.normalize expr)
actualBytes = Data.Text.Lazy.Encoding.encodeUtf8 text
hashExpressionToCode :: Expr s X -> Text
hashExpressionToCode expr = "sha256:" <> lazyText
where
bytes = hashExpression expr
bytes16 = Data.ByteArray.convert bytes
text = Data.Text.Encoding.decodeUtf8 bytes16
lazyText = Text.fromStrict text