Skip to content

Commit c166dcf

Browse files
committed
Added SingleConstructorWith and MultipleConstructorsWith to Dhall.TH
1 parent 48d96ea commit c166dcf

File tree

1 file changed

+47
-21
lines changed

1 file changed

+47
-21
lines changed

dhall/src/Dhall/TH.hs

Lines changed: 47 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -60,7 +60,7 @@ import qualified Numeric.Natural
6060
import qualified Prettyprinter.Render.String as Pretty
6161
import qualified System.IO
6262

63-
63+
6464
{-| This fully resolves, type checks, and normalizes the expression, so the
6565
resulting AST is self-contained.
6666
@@ -160,9 +160,9 @@ toNestedHaskellType typeParams haskellTypes = loop
160160
, " \n"
161161
, "... which did not fit any of the above criteria."
162162
]
163-
163+
164164
message dhallType = Pretty.renderString (Dhall.Pretty.layout (document dhallType))
165-
165+
166166
loop dhallType = case dhallType of
167167
Bool ->
168168
return (ConT ''Bool)
@@ -203,7 +203,7 @@ toNestedHaskellType typeParams haskellTypes = loop
203203
haskellElementType <- loop dhallElementType
204204

205205
return (AppT haskellAppType haskellElementType)
206-
206+
207207
Var v
208208
| Just (V param index) <- List.find (v ==) typeParams -> do
209209
let name = Syntax.mkName $ (Text.unpack param) ++ (show index)
@@ -249,44 +249,46 @@ toDeclaration
249249
-> [HaskellType (Expr s a)]
250250
-> HaskellType (Expr s a)
251251
-> Q [Dec]
252-
toDeclaration generateOptions@GenerateOptions{..} haskellTypes typ =
252+
toDeclaration globalGenerateOptions haskellTypes typ =
253253
case typ of
254-
SingleConstructor{..} -> uncurry (fromSingle typeName constructorName) $ getTypeParams code
255-
MultipleConstructors{..} -> uncurry (fromMulti typeName) $ getTypeParams code
254+
SingleConstructor{..} -> uncurry (fromSingle globalGenerateOptions typeName constructorName) $ getTypeParams code
255+
SingleConstructorWith{..} -> uncurry (fromSingle options typeName constructorName) $ getTypeParams code
256+
MultipleConstructors{..} -> uncurry (fromMulti globalGenerateOptions typeName) $ getTypeParams code
257+
MultipleConstructorsWith{..} -> uncurry (fromMulti options typeName) $ getTypeParams code
256258
where
257259
getTypeParams = first numberConsecutive . getTypeParams_ []
258-
260+
259261
getTypeParams_ acc (Lam _ (FunctionBinding _ v _ _ _) rest) = getTypeParams_ (v:acc) rest
260262
getTypeParams_ acc rest = (acc, rest)
261263

262-
derivingClauses = [ derivingGenericClause | generateFromDhallInstance || generateToDhallInstance ]
263-
264-
interpretOptions = generateToInterpretOptions generateOptions typ
265-
266264
toTypeVar (V n i) = Syntax.PlainTV $ Syntax.mkName (Text.unpack n ++ show i)
267265

268-
toDataD typeName typeParams constructors = do
266+
toDataD generateOptions@GenerateOptions{..} typeName typeParams constructors = do
269267
let name = Syntax.mkName (Text.unpack typeName)
270268

271269
let params = fmap toTypeVar typeParams
272270

271+
let interpretOptions = generateToInterpretOptions generateOptions typ
272+
273+
let derivingClauses = [ derivingGenericClause | generateFromDhallInstance || generateToDhallInstance ]
274+
273275
fmap concat . sequence $
274276
[pure [DataD [] name params Nothing constructors derivingClauses]] <>
275277
[ fromDhallInstance name interpretOptions | generateFromDhallInstance ] <>
276278
[ toDhallInstance name interpretOptions | generateToDhallInstance ]
277279

278-
fromSingle typeName constructorName typeParams dhallType = do
280+
fromSingle generateOptions typeName constructorName typeParams dhallType = do
279281
constructor <- toConstructor typeParams generateOptions haskellTypes typeName (constructorName, Just dhallType)
280-
281-
toDataD typeName typeParams [constructor]
282-
283-
fromMulti typeName typeParams dhallType = case dhallType of
282+
283+
toDataD generateOptions typeName typeParams [constructor]
284+
285+
fromMulti generateOptions typeName typeParams dhallType = case dhallType of
284286
Union kts -> do
285287
constructors <- traverse (toConstructor typeParams generateOptions haskellTypes typeName) (Dhall.Map.toList kts)
286288

287-
toDataD typeName typeParams constructors
288-
289-
_ -> fail $ message dhallType
289+
toDataD generateOptions typeName typeParams constructors
290+
291+
_ -> fail $ message dhallType
290292

291293
message dhallType = Pretty.renderString (Dhall.Pretty.layout $ document dhallType)
292294

@@ -430,6 +432,30 @@ data HaskellType code
430432
, code :: code
431433
-- ^ Dhall code that evaluates to a type
432434
}
435+
-- | Generate a Haskell type with more than one constructor from a Dhall
436+
-- union type.
437+
| MultipleConstructorsWith
438+
{ options :: GenerateOptions
439+
-- ^ The 'GenerateOptions' to use then generating the Haskell type.
440+
, typeName :: Text
441+
-- ^ Name of the generated Haskell type
442+
, code :: code
443+
-- ^ Dhall code that evaluates to a union type
444+
}
445+
-- | Generate a Haskell type with one constructor from any Dhall type.
446+
--
447+
-- To generate a constructor with multiple named fields, supply a Dhall
448+
-- record type. This does not support more than one anonymous field.
449+
| SingleConstructorWith
450+
{ options :: GenerateOptions
451+
-- ^ The 'GenerateOptions' to use then generating the Haskell type.
452+
, typeName :: Text
453+
-- ^ Name of the generated Haskell type
454+
, constructorName :: Text
455+
-- ^ Name of the constructor
456+
, code :: code
457+
-- ^ Dhall code that evaluates to a type
458+
}
433459
deriving (Functor, Foldable, Traversable)
434460

435461
-- | This data type holds various options that let you control several aspects

0 commit comments

Comments
 (0)