dhall-1.32.0: A configuration language guaranteed to terminate

Safe HaskellNone
LanguageHaskell2010

Dhall.TH

Contents

Description

Template Haskell utilities

Synopsis

Template Haskell

staticDhallExpression :: Text -> Q Exp Source #

This fully resolves, type checks, and normalizes the expression, so the resulting AST is self-contained.

This can be used to resolve all of an expression’s imports at compile time, allowing one to reference Dhall expressions from Haskell without having a runtime dependency on the location of Dhall files.

For example, given a file "./Some/Type.dhall" containing

< This : Natural | Other : ../Other/Type.dhall >

... rather than duplicating the AST manually in a Haskell Type, you can do:

Dhall.Type
(\case
    UnionLit "This" _ _  -> ...
    UnionLit "Other" _ _ -> ...)
$(staticDhallExpression "./Some/Type.dhall")

This would create the Dhall Expr AST from the "./Some/Type.dhall" file at compile time with all imports resolved, making it easy to keep your Dhall configs and Haskell interpreters in sync.

makeHaskellTypeFromUnion Source #

Arguments

:: Text

Name of the generated Haskell type

-> Text

Dhall code that evaluates to a union type

-> Q [Dec] 

Generate a Haskell datatype declaration from a Dhall union type where each union alternative corresponds to a Haskell constructor

For example, this Template Haskell splice:

Dhall.TH.makeHaskellTypeFromUnion "T" "< A : { x : Bool } | B >"

... generates this Haskell code:

data T = A {x :: GHC.Types.Bool} | B

This is a special case of makeHaskellTypes:

makeHaskellTypeFromUnion typeName code =
    makeHaskellTypes [ MultipleConstructors{..} ]

makeHaskellTypes :: [HaskellType Text] -> Q [Dec] Source #

Generate a Haskell datatype declaration with one constructor from a Dhall type

This comes in handy if you need to keep Dhall types and Haskell types in sync. You make the Dhall types the source of truth and use Template Haskell to generate the matching Haskell type declarations from the Dhall types.

For example, given this Dhall code:

-- ./Department.dhall
< Sales | Engineering | Marketing >
-- ./Employee.dhall
{ name : Text, department : ./Department.dhall }

... this Template Haskell splice:

{-# LANGUAGE DeriveAnyClass     #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE TemplateHaskell    #-}

Dhall.TH.makeHaskellTypes
    [ MultipleConstructors "Department" "./tests/th/Department.dhall"
    , SingleConstructor "Employee" "MakeEmployee" "./tests/th/Employee.dhall"
    ]

... generates this Haskell code:

data Department = Engineering | Marketing | Sales
  deriving stock (GHC.Generics.Generic)
  deriving anyclass (Dhall.FromDhall, Dhall.ToDhall)

data Employee
  = MakeEmployee {department :: Department,
                  name :: Data.Text.Internal.Text}
  deriving stock (GHC.Generics.Generic)
  deriving anyclass (Dhall.FromDhall, Dhall.ToDhall)

Carefully note that the conversion makes a best-effort attempt to auto-detect when a Dhall type (like ./Employee.dhall) refers to another Dhall type (like ./Department.dhall) and replaces that reference with the corresponding Haskell type.

This Template Haskell splice requires you to enable the following extensions:

  • DeriveGeneric
  • DerivingAnyClass
  • DerivingStrategies

By default, the generated types only derive Generic, FromDhall, and ToDhall. To add any desired instances (such as Eq/Ord/Show), you can use the StandaloneDeriving language extension, like this:

{-# LANGUAGE DeriveAnyClass     #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell    #-}

Dhall.TH.makeHaskellTypes
    [ MultipleConstructors "Department" "./tests/th/Department.dhall"
    , SingleConstructor "Employee" "MakeEmployee" "./tests/th/Employee.dhall"
    ]

deriving instance Eq   Department
deriving instance Ord  Department
deriving instance Show Department

deriving instance Eq   Employee
deriving instance Ord  Employee
deriving instance Show Employee

data HaskellType code Source #

Used by makeHaskellTypes to specify how to generate Haskell types

Constructors

MultipleConstructors

Generate a Haskell type with more than one constructor from a Dhall union type

Fields

  • typeName :: Text

    Name of the generated Haskell type

  • code :: code

    Dhall code that evaluates to a union type

SingleConstructor

Generate a Haskell type with one constructor from any Dhall type

To generate a constructor with multiple named fields, supply a Dhall record type. This does not support more than one anonymous field.

Fields

Instances
Functor HaskellType Source # 
Instance details

Defined in Dhall.TH

Methods

fmap :: (a -> b) -> HaskellType a -> HaskellType b #

(<$) :: a -> HaskellType b -> HaskellType a #

Foldable HaskellType Source # 
Instance details

Defined in Dhall.TH

Methods

fold :: Monoid m => HaskellType m -> m #

foldMap :: Monoid m => (a -> m) -> HaskellType a -> m #

foldr :: (a -> b -> b) -> b -> HaskellType a -> b #

foldr' :: (a -> b -> b) -> b -> HaskellType a -> b #

foldl :: (b -> a -> b) -> b -> HaskellType a -> b #

foldl' :: (b -> a -> b) -> b -> HaskellType a -> b #

foldr1 :: (a -> a -> a) -> HaskellType a -> a #

foldl1 :: (a -> a -> a) -> HaskellType a -> a #

toList :: HaskellType a -> [a] #

null :: HaskellType a -> Bool #

length :: HaskellType a -> Int #

elem :: Eq a => a -> HaskellType a -> Bool #

maximum :: Ord a => HaskellType a -> a #

minimum :: Ord a => HaskellType a -> a #

sum :: Num a => HaskellType a -> a #

product :: Num a => HaskellType a -> a #

Traversable HaskellType Source # 
Instance details

Defined in Dhall.TH

Methods

traverse :: Applicative f => (a -> f b) -> HaskellType a -> f (HaskellType b) #

sequenceA :: Applicative f => HaskellType (f a) -> f (HaskellType a) #

mapM :: Monad m => (a -> m b) -> HaskellType a -> m (HaskellType b) #

sequence :: Monad m => HaskellType (m a) -> m (HaskellType a) #