{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
module Dhall.TH
(
staticDhallExpression
, makeHaskellTypeFromUnion
, makeHaskellTypes
, HaskellType(..)
) where
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Text.Prettyprint.Doc (Pretty)
import Dhall.Syntax (Expr(..))
import Dhall (FromDhall, ToDhall)
import GHC.Generics (Generic)
import Language.Haskell.TH.Quote (dataToExpQ)
import Language.Haskell.TH.Syntax
( Con(..)
, Dec(..)
, Exp(..)
, Q
, Type(..)
, Bang(..)
, SourceStrictness(..)
, SourceUnpackedness(..)
#if MIN_VERSION_template_haskell(2,12,0)
, DerivClause(..)
, DerivStrategy(..)
#else
, Pred
#endif
)
import qualified Data.List as List
import qualified Data.Text as Text
import qualified Data.Text.Prettyprint.Doc.Render.String as Pretty
import qualified Data.Typeable as Typeable
import qualified Dhall
import qualified Dhall.Core as Core
import qualified Dhall.Map
import qualified Dhall.Pretty
import qualified Dhall.Util
import qualified GHC.IO.Encoding
import qualified Numeric.Natural
import qualified System.IO
import qualified Language.Haskell.TH.Syntax as Syntax
staticDhallExpression :: Text -> Q Exp
staticDhallExpression text = do
Syntax.runIO (GHC.IO.Encoding.setLocaleEncoding System.IO.utf8)
expression <- Syntax.runIO (Dhall.inputExpr text)
dataToExpQ (\a -> liftText <$> Typeable.cast a) expression
where
liftText = fmap (AppE (VarE 'Text.pack)) . Syntax.lift . Text.unpack
toNestedHaskellType
:: (Eq a, Pretty a)
=> [HaskellType (Expr s a)]
-> Expr s a
-> Q Type
toNestedHaskellType haskellTypes = loop
where
loop dhallType = case dhallType of
Bool -> do
return (ConT ''Bool)
Double -> do
return (ConT ''Double)
Integer -> do
return (ConT ''Integer)
Natural -> do
return (ConT ''Numeric.Natural.Natural)
Text -> do
return (ConT ''Text)
App List dhallElementType -> do
haskellElementType <- loop dhallElementType
return (AppT (ConT ''[]) haskellElementType)
App Optional dhallElementType -> do
haskellElementType <- loop dhallElementType
return (AppT (ConT ''Maybe) haskellElementType)
_ | Just haskellType <- List.find predicate haskellTypes -> do
let name = Syntax.mkName (Text.unpack (typeName haskellType))
return (ConT name)
| otherwise -> do
let document =
mconcat
[ "Unsupported nested type\n"
, " \n"
, "Explanation: Not all Dhall types can be nested within Haskell datatype \n"
, "declarations. Specifically, only the following simple Dhall types are supported\n"
, "as a nested type inside of a data declaration: \n"
, " \n"
, "• ❰Bool❱ \n"
, "• ❰Double❱ \n"
, "• ❰Integer❱ \n"
, "• ❰Natural❱ \n"
, "• ❰Text❱ \n"
, "• ❰List a❱ (where ❰a❱ is also a valid nested type) \n"
, "• ❰Optional a❱ (where ❰a❱ is also a valid nested type) \n"
, "• Another matching datatype declaration \n"
, " \n"
, "The Haskell datatype generation logic encountered the following Dhall type: \n"
, " \n"
, " " <> Dhall.Util.insert dhallType <> "\n"
, " \n"
, "... which did not fit any of the above criteria."
]
let message = Pretty.renderString (Dhall.Pretty.layout document)
fail message
where
predicate haskellType =
Core.judgmentallyEqual (code haskellType) dhallType
#if MIN_VERSION_template_haskell(2,12,0)
derivingClauses :: [DerivClause]
derivingClauses =
[ DerivClause (Just StockStrategy) [ ConT ''Generic ]
, DerivClause (Just AnyclassStrategy) [ ConT ''FromDhall, ConT ''ToDhall ]
]
#else
derivingClauses :: [Pred]
derivingClauses = [ ConT ''Generic, ConT ''FromDhall, ConT ''ToDhall ]
#endif
toDeclaration
:: (Eq a, Pretty a)
=> [HaskellType (Expr s a)]
-> HaskellType (Expr s a)
-> Q Dec
toDeclaration haskellTypes MultipleConstructors{..} = do
case code of
Union kts -> do
let name = Syntax.mkName (Text.unpack typeName)
constructors <- traverse (toConstructor haskellTypes) (Dhall.Map.toList kts )
return (DataD [] name [] Nothing constructors derivingClauses)
_ -> do
let document =
mconcat
[ "Dhall.TH.makeHaskellTypes: Not a union type\n"
, " \n"
, "Explanation: This function expects the ❰code❱ field of ❰MultipleConstructors❱ to\n"
, "evaluate to a union type. \n"
, " \n"
, "For example, this is a valid Dhall union type that this function would accept: \n"
, " \n"
, " \n"
, " ┌──────────────────────────────────────────────────────────────────┐ \n"
, " │ Dhall.TH.makeHaskellTypes (MultipleConstructors \"T\" \"< A | B >\") │ \n"
, " └──────────────────────────────────────────────────────────────────┘ \n"
, " \n"
, " \n"
, "... which corresponds to this Haskell type declaration: \n"
, " \n"
, " \n"
, " ┌────────────────┐ \n"
, " │ data T = A | B │ \n"
, " └────────────────┘ \n"
, " \n"
, " \n"
, "... but the following Dhall type is rejected due to being a bare record type: \n"
, " \n"
, " \n"
, " ┌──────────────────────────────────────────────┐ \n"
, " │ Dhall.TH.makeHaskellTypes \"T\" \"{ x : Bool }\" │ Not valid \n"
, " └──────────────────────────────────────────────┘ \n"
, " \n"
, " \n"
, "The Haskell datatype generation logic encountered the following Dhall type: \n"
, " \n"
, " " <> Dhall.Util.insert code <> "\n"
, " \n"
, "... which is not a union type."
]
let message = Pretty.renderString (Dhall.Pretty.layout document)
fail message
toDeclaration haskellTypes SingleConstructor{..} = do
let name = Syntax.mkName (Text.unpack typeName)
constructor <- toConstructor haskellTypes (constructorName, Just code)
return (DataD [] name [] Nothing [constructor] derivingClauses)
toConstructor
:: (Eq a, Pretty a)
=> [HaskellType (Expr s a)]
-> (Text, Maybe (Expr s a))
-> Q Con
toConstructor haskellTypes (constructorName, maybeAlternativeType) = do
let name = Syntax.mkName (Text.unpack constructorName)
let bang = Bang NoSourceUnpackedness NoSourceStrictness
case maybeAlternativeType of
Just (Record kts) -> do
let process (key, dhallFieldType) = do
haskellFieldType <- toNestedHaskellType haskellTypes dhallFieldType
return (Syntax.mkName (Text.unpack key), bang, haskellFieldType)
varBangTypes <- traverse process (Dhall.Map.toList kts)
return (RecC name varBangTypes)
Just dhallAlternativeType -> do
haskellAlternativeType <- toNestedHaskellType haskellTypes dhallAlternativeType
return (NormalC name [ (bang, haskellAlternativeType) ])
Nothing -> do
return (NormalC name [])
makeHaskellTypeFromUnion
:: Text
-> Text
-> Q [Dec]
makeHaskellTypeFromUnion typeName code =
makeHaskellTypes [ MultipleConstructors{..} ]
data HaskellType code
= MultipleConstructors
{ typeName :: Text
, code :: code
}
| SingleConstructor
{ typeName :: Text
, constructorName :: Text
, code :: code
}
deriving (Functor, Foldable, Traversable)
makeHaskellTypes :: [HaskellType Text] -> Q [Dec]
makeHaskellTypes haskellTypes = do
Syntax.runIO (GHC.IO.Encoding.setLocaleEncoding System.IO.utf8)
haskellTypes' <- traverse (traverse (Syntax.runIO . Dhall.inputExpr)) haskellTypes
traverse (toDeclaration haskellTypes') haskellTypes'