module Morte.Import (
load
, Cycle(..)
, ReferentiallyOpaque(..)
, Imported(..)
) where
import Control.Exception (Exception, IOException, catch, onException, throwIO)
import Control.Monad (join)
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.State.Strict (StateT)
import Data.Map.Strict (Map)
import Data.Monoid ((<>))
import Data.Text.Buildable (build)
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 Filesystem.Path ((</>), FilePath)
import Filesystem as Filesystem
import Lens.Micro (Lens')
import Lens.Micro.Mtl (zoom)
import Morte.Core (Expr, Path(..), X(..))
import Network.HTTP.Client (Manager)
import Prelude hiding (FilePath)
import qualified Control.Monad.Trans.State.Strict as State
import qualified Data.Foldable as Foldable
import qualified Data.List as List
import qualified Data.Map.Strict as Map
import qualified Data.Text.Lazy as Text
import qualified Data.Text.Lazy.Builder as Builder
import qualified Data.Text.Lazy.Encoding as Text
import qualified Morte.Core as Morte
import qualified Morte.Parser as Morte
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.TLS as HTTP
import qualified Filesystem.Path.CurrentOS as Filesystem
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) = "Cyclic import: " ++ builderToString (build path)
newtype ReferentiallyOpaque = ReferentiallyOpaque
{ opaqueImport :: Path
} deriving (Typeable)
instance Exception ReferentiallyOpaque
instance Show ReferentiallyOpaque where
show (ReferentiallyOpaque path) =
"Referentially 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) =
"\n"
++ unlines (map (\path -> "⤷ " ++ builderToString (build path)) paths')
++ show e
where
paths' = drop 1 (reverse (canonicalizeAll paths))
data Status = Status
{ _stack :: [Path]
, _cache :: Map Path (Expr X)
, _manager :: Maybe Manager
}
canonicalizeAll :: [Path] -> [Path]
canonicalizeAll = map canonicalize . List.tails
stack :: Lens' Status [Path]
stack k s = fmap (\x -> s { _stack = x }) (k (_stack s))
cache :: Lens' Status (Map Path (Expr X))
cache k s = fmap (\x -> s { _cache = x }) (k (_cache s))
manager :: Lens' 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
{ HTTP.managerResponseTimeout =
HTTP.responseTimeoutMicro 1000000
}
m <- liftIO (HTTP.newManager settings)
zoom manager (State.put (Just m))
return m
canonicalize :: [Path] -> Path
canonicalize [] = File "."
canonicalize (File file0:paths0) =
if Filesystem.relative file0
then go file0 paths0
else File (clean file0)
where
go currPath [] = File (clean currPath)
go currPath (URL url0:_ ) = combine prefix suffix
where
prefix = parentURL (removeAtFromURL url0)
suffix = clean currPath
combine url path = case Filesystem.stripPrefix ".." path of
Just path' -> combine url' path'
where
url' = parentURL (removeAtFromURL url)
Nothing -> case Filesystem.stripPrefix "." path of
Just path' -> combine url path'
Nothing ->
case Text.last url of
'/' -> URL (url <> path')
_ -> URL (url <> "/" <> path')
where
path' = Text.fromStrict (case Filesystem.toText path of
Left txt -> txt
Right txt -> txt )
go currPath (File file:paths) =
if Filesystem.relative file
then go file' paths
else File (clean file')
where
file' = Filesystem.parent (removeAtFromFile file) </> currPath
canonicalize (URL path:_) = URL path
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
removeAtFromFile :: FilePath -> FilePath
removeAtFromFile file =
if Filesystem.filename file == "@"
then Filesystem.parent file
else file
clean :: FilePath -> FilePath
clean = strip . Filesystem.collapse
where
strip p = case Filesystem.stripPrefix "." p of
Nothing -> p
Just p' -> p'
loadDynamic :: Path -> StateT Status IO (Expr Path)
loadDynamic p = do
paths <- zoom stack State.get
let readURL url = do
request <- liftIO (HTTP.parseUrlThrow (Text.unpack url))
m <- needManager
let httpLbs' = do
HTTP.httpLbs request m `catch` (\e -> case e of
HTTP.HttpExceptionRequest _ (HTTP.StatusCodeException _ _) -> do
let request' = request
{ HTTP.path = HTTP.path request <> "/@" }
HTTP.httpLbs request' m
`onException` throwIO (Imported paths e)
_ -> throwIO (Imported paths e) )
response <- liftIO httpLbs'
case Text.decodeUtf8' (HTTP.responseBody response) of
Left err -> liftIO (throwIO (Imported paths err))
Right txt -> return txt
let readFile' file = liftIO (do
(do txt <- Filesystem.readTextFile file
return (Text.fromStrict txt) ) `catch` (\e -> do
let _ = e :: IOException
let file' = file </> "@"
txt <- Filesystem.readTextFile file'
`onException` throwIO (Imported paths e)
return (Text.fromStrict txt) ) )
txt <- case canonicalize (p:paths) of
File file -> readFile' file
URL url -> readURL url
let abort err = liftIO (throwIO (Imported (p:paths) err))
case Morte.exprFromText txt of
Left err -> case canonicalize (p:paths) of
URL url -> do
request <- liftIO (HTTP.parseUrlThrow (Text.unpack url))
let request' = request { HTTP.path = HTTP.path request <> "/@" }
m <- needManager
response <- liftIO
(HTTP.httpLbs request' m `onException` abort err)
case Text.decodeUtf8' (HTTP.responseBody response) of
Left _ -> liftIO (abort err)
Right txt' -> case Morte.exprFromText txt' of
Left _ -> liftIO (abort err)
Right expr -> return expr
_ -> liftIO (abort err)
Right expr -> return expr
loadStatic :: Path -> StateT Status IO (Expr X)
loadStatic path = do
paths <- zoom stack State.get
let local (URL url) = case HTTP.parseUrlThrow (Text.unpack url) of
Nothing -> False
Just request -> case HTTP.host request of
"127.0.0.1" -> True
"localhost" -> True
_ -> False
local (File _) = True
let parent = canonicalize paths
let here = canonicalize (path:paths)
if local here && not (local parent)
then liftIO (throwIO (Imported paths (ReferentiallyOpaque path)))
else return ()
(expr, cached) <- if here `elem` canonicalizeAll paths
then liftIO (throwIO (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 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 loadStatic expr')
zoom stack (State.put paths)
return expr''
return (expr'', False)
if cached
then return ()
else case Morte.typeOf expr of
Left err -> liftIO (throwIO (Imported (path:paths) err))
Right _ -> return ()
return expr
load
:: Maybe Path
-> Expr Path
-> IO (Expr X)
load here expr =
State.evalStateT (fmap join (traverse loadStatic expr)) status
where
status = Status (Foldable.toList here) Map.empty Nothing