{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}
module Hakyll.Web.Dhall (
DExpr(..)
, dExprCompiler, dExprCompilerWith
, loadDhall, loadDhallSnapshot
, dhallCompiler, dhallCompilerWith
, parseDhall, parseDhallWith
, parseDhallExpr, parseDhallExprWith
, dhallPrettyCompiler
, dhallRawPrettyCompiler, dhallFullPrettyCompiler
, dhallPrettyCompilerWith
, renderDhallExprWith
, DhallCompilerOptions(..), DhallCompilerTrust(..)
, defaultDhallCompilerOptions, dcoResolver, dcoMinimize, dcoNormalize
, DhallResolver(..), DefaultDhallResolver(..), drRemap, drFull
, interpretDhallCompiler
, parseRawDhallExprWith
, resolveDhallImports
) where
import Control.Monad
import Control.Monad.Error.Class
import Data.Either.Validation
import Control.Monad.Trans.State.Strict
import Data.Default.Class
import Data.Kind
import Data.Maybe as M
import Data.Typeable (Typeable)
import Data.Void
import Dhall hiding (map)
import Dhall.Binary
import Dhall.Core
import Dhall.Diff
import Dhall.Import
import Dhall.Parser
import Dhall.Pretty
import Dhall.TypeCheck
import Hakyll.Core.Compiler
import Hakyll.Core.Compiler.Internal
import Hakyll.Core.Dependencies
import Hakyll.Core.Identifier
import Hakyll.Core.Item
import Hakyll.Core.Writable
import Lens.Micro
import Lens.Micro.TH
import System.FilePath
import System.IO
import qualified Data.Binary as Bi
import qualified Data.Binary.Get as Bi
import qualified Data.Binary.Put as Bi
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Prettyprinter as PP
import qualified Prettyprinter.Render.Text as PP
import qualified Dhall.Map as DM
newtype DExpr a = DExpr { forall a. DExpr a -> Expr Src a
getDExpr :: Expr Src a }
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (DExpr a) x -> DExpr a
forall a x. DExpr a -> Rep (DExpr a) x
$cto :: forall a x. Rep (DExpr a) x -> DExpr a
$cfrom :: forall a x. DExpr a -> Rep (DExpr a) x
Generic, Typeable)
instance Bi.Binary (DExpr Void) where
put :: DExpr Void -> Put
put = ByteString -> Put
Bi.putLazyByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Serialise (Expr Void a) => Expr Void a -> ByteString
encodeExpression
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a t. Expr s a -> Expr t a
denote
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. DExpr a -> Expr Src a
getDExpr
get :: Get (DExpr Void)
get = do
ByteString
bs <- Get ByteString
Bi.getRemainingLazyByteString
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> FilePath
show) (forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr Src a -> DExpr a
DExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a t. Expr s a -> Expr t a
denote @Void) forall a b. (a -> b) -> a -> b
$ forall s a.
Serialise (Expr s a) =>
ByteString -> Either DecodingFailure (Expr s a)
decodeExpression ByteString
bs
instance PP.Pretty a => Writable (DExpr a) where
write :: FilePath -> Item (DExpr a) -> IO ()
write FilePath
fp Item (DExpr a)
e = forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withFile FilePath
fp IOMode
WriteMode forall a b. (a -> b) -> a -> b
$ \Handle
h ->
forall ann. Handle -> SimpleDocStream ann -> IO ()
PP.renderIO Handle
h
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
PP.layoutSmart LayoutOptions
layoutOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ann xxx. Doc ann -> Doc xxx
PP.unAnnotate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a s. Pretty a => Expr s a -> Doc Ann
prettyExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. DExpr a -> Expr Src a
getDExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Item a -> a
itemBody
forall a b. (a -> b) -> a -> b
$ Item (DExpr a)
e
data DhallCompilerTrust = DCTLocal
| DCTRemote
| DCTEnv
deriving (forall x. Rep DhallCompilerTrust x -> DhallCompilerTrust
forall x. DhallCompilerTrust -> Rep DhallCompilerTrust x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DhallCompilerTrust x -> DhallCompilerTrust
$cfrom :: forall x. DhallCompilerTrust -> Rep DhallCompilerTrust x
Generic, Typeable, Int -> DhallCompilerTrust -> ShowS
[DhallCompilerTrust] -> ShowS
DhallCompilerTrust -> FilePath
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [DhallCompilerTrust] -> ShowS
$cshowList :: [DhallCompilerTrust] -> ShowS
show :: DhallCompilerTrust -> FilePath
$cshow :: DhallCompilerTrust -> FilePath
showsPrec :: Int -> DhallCompilerTrust -> ShowS
$cshowsPrec :: Int -> DhallCompilerTrust -> ShowS
Show, DhallCompilerTrust -> DhallCompilerTrust -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
$c/= :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
== :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
$c== :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
Eq, Eq DhallCompilerTrust
DhallCompilerTrust -> DhallCompilerTrust -> Bool
DhallCompilerTrust -> DhallCompilerTrust -> Ordering
DhallCompilerTrust -> DhallCompilerTrust -> DhallCompilerTrust
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DhallCompilerTrust -> DhallCompilerTrust -> DhallCompilerTrust
$cmin :: DhallCompilerTrust -> DhallCompilerTrust -> DhallCompilerTrust
max :: DhallCompilerTrust -> DhallCompilerTrust -> DhallCompilerTrust
$cmax :: DhallCompilerTrust -> DhallCompilerTrust -> DhallCompilerTrust
>= :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
$c>= :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
> :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
$c> :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
<= :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
$c<= :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
< :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
$c< :: DhallCompilerTrust -> DhallCompilerTrust -> Bool
compare :: DhallCompilerTrust -> DhallCompilerTrust -> Ordering
$ccompare :: DhallCompilerTrust -> DhallCompilerTrust -> Ordering
Ord)
data DhallCompilerOptions a = DCO
{ forall a. DhallCompilerOptions a -> DhallResolver a
_dcoResolver :: DhallResolver a
, forall a. DhallCompilerOptions a -> Bool
_dcoMinimize :: Bool
, forall a. DhallCompilerOptions a -> Bool
_dcoNormalize :: Bool
}
deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (DhallCompilerOptions a) x -> DhallCompilerOptions a
forall a x.
DhallCompilerOptions a -> Rep (DhallCompilerOptions a) x
$cto :: forall a x.
Rep (DhallCompilerOptions a) x -> DhallCompilerOptions a
$cfrom :: forall a x.
DhallCompilerOptions a -> Rep (DhallCompilerOptions a) x
Generic, Typeable)
data DhallResolver :: Type -> Type where
DRRaw :: { DhallResolver Import -> Import -> Compiler (Expr Src Import)
_drRemap :: Import -> Compiler (Expr Src Import)
} -> DhallResolver Import
DRFull :: { DhallResolver Void -> Set DhallCompilerTrust
_drTrust :: S.Set DhallCompilerTrust
} -> DhallResolver Void
drRemap
:: Lens' (DhallResolver Import) (Import -> Compiler (Expr Src Import))
drRemap :: Lens' (DhallResolver Import) (Import -> Compiler (Expr Src Import))
drRemap (Import -> Compiler (Expr Src Import))
-> f (Import -> Compiler (Expr Src Import))
f (DRRaw Import -> Compiler (Expr Src Import)
r) = (Import -> Compiler (Expr Src Import)) -> DhallResolver Import
DRRaw forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Import -> Compiler (Expr Src Import))
-> f (Import -> Compiler (Expr Src Import))
f Import -> Compiler (Expr Src Import)
r
drFull
:: Lens' (DhallResolver Void) (S.Set DhallCompilerTrust)
drFull :: Lens' (DhallResolver Void) (Set DhallCompilerTrust)
drFull Set DhallCompilerTrust -> f (Set DhallCompilerTrust)
f (DRFull Set DhallCompilerTrust
t) = Set DhallCompilerTrust -> DhallResolver Void
DRFull forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set DhallCompilerTrust -> f (Set DhallCompilerTrust)
f Set DhallCompilerTrust
t
makeLenses ''DhallCompilerOptions
defaultDhallCompilerOptions
:: DefaultDhallResolver a
=> DhallCompilerOptions a
defaultDhallCompilerOptions :: forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions = DCO
{ _dcoResolver :: DhallResolver a
_dcoResolver = forall a. DefaultDhallResolver a => DhallResolver a
defaultDhallResolver
, _dcoMinimize :: Bool
_dcoMinimize = Bool
False
, _dcoNormalize :: Bool
_dcoNormalize = Bool
True
}
class DefaultDhallResolver a where
defaultDhallResolver :: DhallResolver a
instance DefaultDhallResolver Import where
defaultDhallResolver :: DhallResolver Import
defaultDhallResolver = (Import -> Compiler (Expr Src Import)) -> DhallResolver Import
DRRaw forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s a. a -> Expr s a
Embed
instance DefaultDhallResolver Void where
defaultDhallResolver :: DhallResolver Void
defaultDhallResolver = Set DhallCompilerTrust -> DhallResolver Void
DRFull forall a b. (a -> b) -> a -> b
$ forall a. a -> Set a
S.singleton DhallCompilerTrust
DCTRemote
instance DefaultDhallResolver a => Default (DhallCompilerOptions a) where
def :: DhallCompilerOptions a
def = forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
dhallPrettyCompiler
:: forall a. DefaultDhallResolver a
=> Compiler (Item String)
dhallPrettyCompiler :: forall a. DefaultDhallResolver a => Compiler (Item FilePath)
dhallPrettyCompiler = forall a. DhallCompilerOptions a -> Compiler (Item FilePath)
dhallPrettyCompilerWith @a forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
dhallRawPrettyCompiler :: Compiler (Item String)
dhallRawPrettyCompiler :: Compiler (Item FilePath)
dhallRawPrettyCompiler = forall a. DhallCompilerOptions a -> Compiler (Item FilePath)
dhallPrettyCompilerWith @Import forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
dhallFullPrettyCompiler :: Compiler (Item String)
dhallFullPrettyCompiler :: Compiler (Item FilePath)
dhallFullPrettyCompiler = forall a. DhallCompilerOptions a -> Compiler (Item FilePath)
dhallPrettyCompilerWith @Void forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
dhallPrettyCompilerWith
:: DhallCompilerOptions a
-> Compiler (Item String)
dhallPrettyCompilerWith :: forall a. DhallCompilerOptions a -> Compiler (Item FilePath)
dhallPrettyCompilerWith DhallCompilerOptions a
dco = do
DExpr Expr Src a
e <- forall a. Item a -> a
itemBody forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DhallCompilerOptions a -> Compiler (Item (DExpr a))
dExprCompilerWith DhallCompilerOptions a
dco
forall a. a -> Compiler (Item a)
makeItem forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
T.unpack forall a b. (a -> b) -> a -> b
$ forall a. DhallCompilerOptions a -> Expr Src a -> Text
renderDhallExprWith DhallCompilerOptions a
dco Expr Src a
e
renderDhallExprWith
:: DhallCompilerOptions a
-> Expr Src a
-> T.Text
renderDhallExprWith :: forall a. DhallCompilerOptions a -> Expr Src a -> Text
renderDhallExprWith DCO{Bool
DhallResolver a
_dcoNormalize :: Bool
_dcoMinimize :: Bool
_dcoResolver :: DhallResolver a
_dcoNormalize :: forall a. DhallCompilerOptions a -> Bool
_dcoMinimize :: forall a. DhallCompilerOptions a -> Bool
_dcoResolver :: forall a. DhallCompilerOptions a -> DhallResolver a
..} = case DhallResolver a
_dcoResolver of
DRRaw Import -> Compiler (Expr Src Import)
_ -> forall a. (Pretty a, Eq a) => Expr Src a -> Text
go
DRFull Set DhallCompilerTrust
_ -> forall a. (Pretty a, Eq a) => Expr Src a -> Text
go
where
go :: (PP.Pretty a, Eq a) => Expr Src a -> T.Text
go :: forall a. (Pretty a, Eq a) => Expr Src a -> Text
go | Bool
_dcoMinimize = forall a. Pretty a => a -> Text
pretty forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr Src a -> Expr Src a
norm
| Bool
otherwise = forall ann. SimpleDocStream ann -> Text
PP.renderStrict
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
PP.layoutSmart LayoutOptions
layoutOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ann xxx. Doc ann -> Doc xxx
PP.unAnnotate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a s. Pretty a => Expr s a -> Doc Ann
prettyExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Expr Src a -> Expr Src a
norm
where
norm :: Expr Src a -> Expr Src a
norm
| Bool
_dcoNormalize = forall a s t. Eq a => Expr s a -> Expr t a
normalize
| Bool
otherwise = forall a. a -> a
id
dExprCompiler :: DefaultDhallResolver a => Compiler (Item (DExpr a))
dExprCompiler :: forall a. DefaultDhallResolver a => Compiler (Item (DExpr a))
dExprCompiler = forall a. DhallCompilerOptions a -> Compiler (Item (DExpr a))
dExprCompilerWith forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
dExprCompilerWith
:: DhallCompilerOptions a
-> Compiler (Item (DExpr a))
dExprCompilerWith :: forall a. DhallCompilerOptions a -> Compiler (Item (DExpr a))
dExprCompilerWith DhallCompilerOptions a
dco = do
FilePath
b <- forall a. Item a -> a
itemBody forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler (Item FilePath)
getResourceBody
FilePath
d <- ShowS
takeDirectory forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identifier -> FilePath
toFilePath forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Compiler Identifier
getUnderlying
forall a. a -> Compiler (Item a)
makeItem forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr Src a -> DExpr a
DExpr forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a.
DhallCompilerOptions a
-> Maybe FilePath -> Text -> Compiler (Expr Src a)
parseDhallExprWith DhallCompilerOptions a
dco (forall a. a -> Maybe a
Just FilePath
d) (FilePath -> Text
T.pack FilePath
b)
dhallCompiler
:: Decoder a
-> Compiler (Item a)
dhallCompiler :: forall a. Decoder a -> Compiler (Item a)
dhallCompiler = forall a.
DhallCompilerOptions Void -> Decoder a -> Compiler (Item a)
dhallCompilerWith forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
dhallCompilerWith
:: DhallCompilerOptions Void
-> Decoder a
-> Compiler (Item a)
dhallCompilerWith :: forall a.
DhallCompilerOptions Void -> Decoder a -> Compiler (Item a)
dhallCompilerWith DhallCompilerOptions Void
dco Decoder a
t = do
DExpr Expr Src Void
e <- forall a. Item a -> a
itemBody forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DhallCompilerOptions a -> Compiler (Item (DExpr a))
dExprCompilerWith DhallCompilerOptions Void
dco
forall a. a -> Compiler (Item a)
makeItem forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Decoder a -> Expr Src Void -> Compiler a
interpretDhallCompiler Decoder a
t Expr Src Void
e
loadDhall
:: Decoder a
-> Identifier
-> Compiler (Item a)
loadDhall :: forall a. Decoder a -> Identifier -> Compiler (Item a)
loadDhall Decoder a
t Identifier
i = do
DExpr Expr Src Void
e <- forall a. (Binary a, Typeable a) => Identifier -> Compiler a
loadBody Identifier
i
forall a. a -> Compiler (Item a)
makeItem forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Decoder a -> Expr Src Void -> Compiler a
interpretDhallCompiler Decoder a
t Expr Src Void
e
loadDhallSnapshot
:: Decoder a
-> Identifier
-> Snapshot
-> Compiler (Item a)
loadDhallSnapshot :: forall a. Decoder a -> Identifier -> FilePath -> Compiler (Item a)
loadDhallSnapshot Decoder a
t Identifier
i FilePath
s = do
DExpr Expr Src Void
e <- forall a.
(Binary a, Typeable a) =>
Identifier -> FilePath -> Compiler a
loadSnapshotBody Identifier
i FilePath
s
forall a. a -> Compiler (Item a)
makeItem forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Decoder a -> Expr Src Void -> Compiler a
interpretDhallCompiler Decoder a
t Expr Src Void
e
parseDhall
:: Maybe FilePath
-> Decoder a
-> T.Text
-> Compiler (Item a)
parseDhall :: forall a. Maybe FilePath -> Decoder a -> Text -> Compiler (Item a)
parseDhall = forall a.
DhallCompilerOptions Void
-> Maybe FilePath -> Decoder a -> Text -> Compiler (Item a)
parseDhallWith forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
parseDhallWith
:: DhallCompilerOptions Void
-> Maybe FilePath
-> Decoder a
-> T.Text
-> Compiler (Item a)
parseDhallWith :: forall a.
DhallCompilerOptions Void
-> Maybe FilePath -> Decoder a -> Text -> Compiler (Item a)
parseDhallWith DhallCompilerOptions Void
dco Maybe FilePath
fp Decoder a
t Text
b = do
Expr Src Void
e <- forall a.
DhallCompilerOptions a
-> Maybe FilePath -> Text -> Compiler (Expr Src a)
parseDhallExprWith DhallCompilerOptions Void
dco Maybe FilePath
fp Text
b
forall a. a -> Compiler (Item a)
makeItem forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. Decoder a -> Expr Src Void -> Compiler a
interpretDhallCompiler Decoder a
t Expr Src Void
e
interpretDhallCompiler
:: Decoder a
-> Expr Src Void
-> Compiler a
interpretDhallCompiler :: forall a. Decoder a -> Expr Src Void -> Compiler a
interpretDhallCompiler Decoder a
t Expr Src Void
e = case forall (f :: * -> *) a s.
Alternative f =>
Decoder a -> Expr s Void -> f a
rawInput Decoder a
t Expr Src Void
e of
Maybe a
Nothing -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath
terrforall a. a -> [a] -> [a]
:) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. a -> [a] -> [a]
:[]) forall a b. (a -> b) -> a -> b
$ case forall s. Expr s Void -> Either (TypeError s Void) (Expr s Void)
typeOf Expr Src Void
e of
Left TypeError Src Void
err -> forall a. Show a => a -> FilePath
show TypeError Src Void
err
Right Expr Src Void
t0 -> case forall a. Decoder a -> Expector (Expr Src Void)
expected Decoder a
t of
Success Expr Src Void
tExpect -> Text -> FilePath
T.unpack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ann. SimpleDocStream ann -> Text
PP.renderStrict
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
PP.layoutSmart LayoutOptions
layoutOpts
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Diff -> Doc Ann
doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a s. (Eq a, Pretty a) => Expr s a -> Expr s a -> Diff
diffNormalized Expr Src Void
tExpect
forall a b. (a -> b) -> a -> b
$ Expr Src Void
t0
Failure ExpectedTypeErrors
q -> forall e. Show e => FilePath -> DhallErrors e -> FilePath
showDhallErrors FilePath
"" ExpectedTypeErrors
q
Just a
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
x
where
terr :: FilePath
terr = FilePath
"Error interpreting Dhall expression as desired type."
parseDhallExpr
:: DefaultDhallResolver a
=> Maybe FilePath
-> T.Text
-> Compiler (Expr Src a)
parseDhallExpr :: forall a.
DefaultDhallResolver a =>
Maybe FilePath -> Text -> Compiler (Expr Src a)
parseDhallExpr = forall a.
DhallCompilerOptions a
-> Maybe FilePath -> Text -> Compiler (Expr Src a)
parseDhallExprWith forall a. DefaultDhallResolver a => DhallCompilerOptions a
defaultDhallCompilerOptions
parseDhallExprWith
:: DhallCompilerOptions a
-> Maybe FilePath
-> T.Text
-> Compiler (Expr Src a)
parseDhallExprWith :: forall a.
DhallCompilerOptions a
-> Maybe FilePath -> Text -> Compiler (Expr Src a)
parseDhallExprWith DhallCompilerOptions a
dco Maybe FilePath
d Text
b = case forall a. DhallCompilerOptions a -> DhallResolver a
_dcoResolver DhallCompilerOptions a
dco of
DRRaw Import -> Compiler (Expr Src Import)
_ -> forall b s. Eq b => Expr s b -> Expr s b
norm forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> DhallCompilerOptions Import -> Text -> Compiler (Expr Src Import)
parseRawDhallExprWith DhallCompilerOptions a
dco Text
b
DRFull Set DhallCompilerTrust
_ -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b s. Eq b => Expr s b -> Expr s b
norm
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DhallCompilerOptions Void
-> Maybe FilePath -> Expr Src Import -> Compiler (Expr Src Void)
resolveDhallImports DhallCompilerOptions a
dco Maybe FilePath
d
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< DhallCompilerOptions Import -> Text -> Compiler (Expr Src Import)
parseRawDhallExprWith (DhallCompilerOptions a
dco { _dcoResolver :: DhallResolver Import
_dcoResolver = forall a. DefaultDhallResolver a => DhallResolver a
defaultDhallResolver })
Text
b
where
norm :: Eq b => Expr s b -> Expr s b
norm :: forall b s. Eq b => Expr s b -> Expr s b
norm
| forall a. DhallCompilerOptions a -> Bool
_dcoNormalize DhallCompilerOptions a
dco = forall a s t. Eq a => Expr s a -> Expr t a
normalize
| Bool
otherwise = forall a. a -> a
id
parseRawDhallExprWith
:: DhallCompilerOptions Import
-> T.Text
-> Compiler (Expr Src Import)
parseRawDhallExprWith :: DhallCompilerOptions Import -> Text -> Compiler (Expr Src Import)
parseRawDhallExprWith DCO{Bool
DhallResolver Import
_dcoNormalize :: Bool
_dcoMinimize :: Bool
_dcoResolver :: DhallResolver Import
_dcoNormalize :: forall a. DhallCompilerOptions a -> Bool
_dcoMinimize :: forall a. DhallCompilerOptions a -> Bool
_dcoResolver :: forall a. DhallCompilerOptions a -> DhallResolver a
..} Text
b =
case FilePath -> Text -> Either ParseError (Expr Src Import)
exprFromText FilePath
"Hakyll.Web.Dhall.parseRawDhallExprWith" Text
b of
Left ParseError
e -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError
[ FilePath
"Error parsing raw dhall file"
, FilePath
"<<" forall a. [a] -> [a] -> [a]
++ Text -> FilePath
T.unpack Text
b forall a. [a] -> [a] -> [a]
++ FilePath
">>"
, forall a. Show a => a -> FilePath
show ParseError
e
]
Right Expr Src Import
e -> forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (DhallResolver Import -> Import -> Compiler (Expr Src Import)
_drRemap DhallResolver Import
_dcoResolver) Expr Src Import
e
resolveDhallImports
:: DhallCompilerOptions Void
-> Maybe FilePath
-> Expr Src Import
-> Compiler (Expr Src Void)
resolveDhallImports :: DhallCompilerOptions Void
-> Maybe FilePath -> Expr Src Import -> Compiler (Expr Src Void)
resolveDhallImports DCO{Bool
DhallResolver Void
_dcoNormalize :: Bool
_dcoMinimize :: Bool
_dcoResolver :: DhallResolver Void
_dcoNormalize :: forall a. DhallCompilerOptions a -> Bool
_dcoMinimize :: forall a. DhallCompilerOptions a -> Bool
_dcoResolver :: forall a. DhallCompilerOptions a -> DhallResolver a
..} Maybe FilePath
d Expr Src Import
e = do
(Expr Src Void
res, Status{Map Chained ImportSemantics
_cache :: Status -> Map Chained ImportSemantics
_cache :: Map Chained ImportSemantics
_cache}) <- forall a. IO a -> Compiler a
unsafeCompiler forall a b. (a -> b) -> a -> b
$
forall s (m :: * -> *) a. StateT s m a -> s -> m (a, s)
runStateT (Expr Src Import -> StateT Status IO (Expr Src Void)
loadWith Expr Src Import
e) (FilePath -> Status
emptyStatus (forall a. a -> Maybe a -> a
fromMaybe FilePath
"./" Maybe FilePath
d))
let imps :: [Dependency]
imps = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Import -> Maybe Dependency
mkDep forall b c a. (b -> c) -> (a -> b) -> a -> c
. Chained -> Import
chainedImport) (forall k v. Map k v -> [k]
DM.keys Map Chained ImportSemantics
_cache)
[Dependency] -> Compiler ()
compilerTellDependencies [Dependency]
imps
forall (f :: * -> *) a. Applicative f => a -> f a
pure Expr Src Void
res
where
DRFull{Set DhallCompilerTrust
_drTrust :: Set DhallCompilerTrust
_drTrust :: DhallResolver Void -> Set DhallCompilerTrust
..} = DhallResolver Void
_dcoResolver
mkDep :: Import -> Maybe Dependency
mkDep :: Import -> Maybe Dependency
mkDep Import
i = case ImportHashed -> ImportType
importType (Import -> ImportHashed
importHashed Import
i) of
Local FilePrefix
Here (File (Directory [Text]
xs) Text
x) -> forall a. a -> Maybe a
Just
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Identifier -> Dependency
IdentifierDependency
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Identifier
fromFilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> FilePath
joinPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Text -> FilePath
T.unpack
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse
forall a b. (a -> b) -> a -> b
$ Text
x forall a. a -> [a] -> [a]
: [Text]
xs
Local FilePrefix
_ File
_
| DhallCompilerTrust
DCTLocal forall a. Ord a => a -> Set a -> Bool
`S.member` Set DhallCompilerTrust
_drTrust -> forall a. Maybe a
Nothing
| Bool
otherwise -> forall a. a -> Maybe a
Just Dependency
neverTrust
Remote URL
_
| DhallCompilerTrust
DCTRemote forall a. Ord a => a -> Set a -> Bool
`S.member` Set DhallCompilerTrust
_drTrust -> forall a. Maybe a
Nothing
| Bool
otherwise -> forall a. a -> Maybe a
Just Dependency
neverTrust
Env Text
_
| DhallCompilerTrust
DCTEnv forall a. Ord a => a -> Set a -> Bool
`S.member` Set DhallCompilerTrust
_drTrust -> forall a. Maybe a
Nothing
| Bool
otherwise -> forall a. a -> Maybe a
Just Dependency
neverTrust
ImportType
Missing -> forall a. a -> Maybe a
Just Dependency
neverTrust
neverTrust :: Dependency
neverTrust = Pattern -> Set Identifier -> Dependency
PatternDependency forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty