{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
module Dhall.Core (
Const(..)
, Directory(..)
, File(..)
, FilePrefix(..)
, Import(..)
, ImportHashed(..)
, ImportMode(..)
, ImportType(..)
, URL(..)
, Scheme(..)
, DhallDouble(..)
, Var(..)
, Binding(..)
, makeBinding
, Chunks(..)
, PreferAnnotation(..)
, Expr(..)
, alphaNormalize
, normalize
, normalizeWith
, normalizeWithM
, Normalizer
, NormalizerM
, ReifiedNormalizer (..)
, judgmentallyEqual
, subst
, shift
, isNormalized
, isNormalizedWith
, denote
, renote
, shallowDenote
, freeIn
, pretty
, subExpressions
, chunkExprs
, bindingExprs
, multiLet
, wrapInLets
, MultiLet(..)
, internalError
, reservedIdentifiers
, escapeText
, pathCharacter
, throws
, Eval.textShow
, censorExpression
, censorText
, Syntax.desugarWith
) where
import Control.Exception (Exception)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Text (Text)
import Data.Text.Prettyprint.Doc (Pretty)
import Dhall.Normalize
import Dhall.Src (Src(..))
import Dhall.Syntax
import Dhall.Pretty.Internal
import Instances.TH.Lift ()
import Lens.Family (over)
import Prelude hiding (succ)
import qualified Control.Exception
import qualified Data.Text
import qualified Dhall.Eval as Eval
import qualified Dhall.Syntax as Syntax
pretty :: Pretty a => a -> Text
pretty = pretty_
{-# INLINE pretty #-}
escapeText :: Text -> Text
escapeText = escapeText_
{-# INLINE escapeText #-}
censorExpression :: Expr Src a -> Expr Src a
censorExpression (TextLit chunks) = TextLit (censorChunks chunks)
censorExpression (Note src e) = Note (censorSrc src) (censorExpression e)
censorExpression e = over subExpressions censorExpression e
censorChunks :: Chunks Src a -> Chunks Src a
censorChunks (Chunks xys z) = Chunks xys' z'
where
z' = censorText z
xys' = [ (censorText x, censorExpression y) | (x, y) <- xys ]
censorText :: Text -> Text
censorText = Data.Text.map (\_ -> ' ')
censorSrc :: Src -> Src
censorSrc (Src { srcText = oldText, .. }) = Src { srcText = newText, .. }
where
newText = censorText oldText
throws :: (Exception e, MonadIO io) => Either e a -> io a
throws (Left e) = liftIO (Control.Exception.throwIO e)
throws (Right r) = return r