{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Dhall.TH
(
staticDhallExpression
, makeHaskellTypeFromUnion
) where
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.Text.Prettyprint.Doc (Pretty)
import Dhall.Syntax (Expr(..))
import Language.Haskell.TH.Quote (dataToExpQ)
import Language.Haskell.TH.Syntax
( Con(..)
, Dec(..)
, Exp(..)
, Q
, Type(..)
#if MIN_VERSION_template_haskell(2,11,0)
, Bang(..)
, SourceStrictness(..)
, SourceUnpackedness(..)
#else
, Strict(..)
#endif
)
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.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
toSimpleHaskellType :: Pretty a => Expr s a -> Q Type
toSimpleHaskellType 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 <- toSimpleHaskellType dhallElementType
return (AppT (ConT ''[]) haskellElementType)
App Optional dhallElementType -> do
haskellElementType <- toSimpleHaskellType dhallElementType
return (AppT (ConT ''Maybe) haskellElementType)
_ -> do
let document =
mconcat
[ "Unsupported simple type\n"
, " \n"
, "Explanation: Not all Dhall alternative types can be converted to Haskell \n"
, "constructor types. Specifically, only the following simple Dhall types are \n"
, "supported as an alternative type or a field of an alternative type: \n"
, " \n"
, "• ❰Bool❱ \n"
, "• ❰Double❱ \n"
, "• ❰Integer❱ \n"
, "• ❰Natural❱ \n"
, "• ❰Text❱ \n"
, "• ❰List a❱ (where ❰a❱ is also a simple type) \n"
, "• ❰Optional a❱ (where ❰a❱ is also a simple type) \n"
, " \n"
, "The Haskell datatype generation logic encountered the following complex \n"
, "Dhall type: \n"
, " \n"
, " " <> Dhall.Util.insert dhallType <> "\n"
, " \n"
, "... where a simpler type was expected."
]
let message = Pretty.renderString (Dhall.Pretty.layout document)
fail message
toConstructor :: Pretty a => (Text, Maybe (Expr s a)) -> Q Con
toConstructor (constructorName, maybeAlternativeType) = do
let name = Syntax.mkName (Text.unpack constructorName)
#if MIN_VERSION_template_haskell(2,11,0)
let bang = Bang NoSourceUnpackedness NoSourceStrictness
#else
let bang = NotStrict
#endif
case maybeAlternativeType of
Just (Record kts) -> do
let process (key, dhallFieldType) = do
haskellFieldType <- toSimpleHaskellType dhallFieldType
return (Syntax.mkName (Text.unpack key), bang, haskellFieldType)
varBangTypes <- traverse process (Dhall.Map.toList kts)
return (RecC name varBangTypes)
Just dhallAlternativeType -> do
haskellAlternativeType <- toSimpleHaskellType dhallAlternativeType
return (NormalC name [ (bang, haskellAlternativeType) ])
Nothing -> do
return (NormalC name [])
makeHaskellTypeFromUnion
:: Text
-> Text
-> Q [Dec]
makeHaskellTypeFromUnion typeName text = do
Syntax.runIO (GHC.IO.Encoding.setLocaleEncoding System.IO.utf8)
expression <- Syntax.runIO (Dhall.inputExpr text)
case expression of
Union kts -> do
let name = Syntax.mkName (Text.unpack typeName)
constructors <- traverse toConstructor (Dhall.Map.toList kts )
let declaration = DataD [] name []
#if MIN_VERSION_template_haskell(2,11,0)
Nothing
#else
#endif
constructors []
return [ declaration ]
_ -> do
let document =
mconcat
[ "Dhall.TH.makeHaskellTypeFromUnion: Unsupported Dhall type\n"
, " \n"
, "Explanation: This function only coverts Dhall union types to Haskell datatype \n"
, "declarations. \n"
, " \n"
, "For example, this is a valid Dhall union type that this function would accept: \n"
, " \n"
, " \n"
, " ┌──────────────────────────────────────────────────────────────────┐ \n"
, " │ Dhall.TH.makeHaskellTypeFromUnion \"T\" \"< A : { x : Bool } | B >\" │ \n"
, " └──────────────────────────────────────────────────────────────────┘ \n"
, " \n"
, " \n"
, "... which corresponds to this Haskell type declaration: \n"
, " \n"
, " \n"
, " ┌──────────────────────────────────────┐ \n"
, " │ data T = A {x :: GHC.Types.Bool} | 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.makeHaskellTypeFromUnion \"T\" \"{ x : Bool }\" │ Not valid \n"
, " └──────────────────────────────────────────────────────┘ \n"
, " \n"
, " \n"
, "If you are starting from a file containing only a record type and you want to \n"
, "generate a Haskell type from that, then wrap the record type in a union with one\n"
, "alternative, like this: \n"
, " \n"
, " \n"
, " ┌──────────────────────────────────────────────────────────────────┐ \n"
, " │ Dhall.TH.makeHaskellTypeFromUnion \"T\" \"< A : ./recordType.dhall >\" │ \n"
, " └──────────────────────────────────────────────────────────────────┘ \n"
, " \n"
, " \n"
, "The Haskell datatype generation logic encountered the following Dhall type: \n"
, " \n"
, " " <> Dhall.Util.insert expression <> "\n"
, " \n"
, "... which is not a union type."
]
let message = Pretty.renderString (Dhall.Pretty.layout document)
fail message