1
+ {-# LANGUAGE BangPatterns #-}
1
2
{-# LANGUAGE DeriveTraversable #-}
2
3
{-# LANGUAGE FlexibleContexts #-}
3
4
{-# LANGUAGE OverloadedStrings #-}
@@ -19,7 +20,7 @@ module Dhall.TH
19
20
, defaultGenerateOptions
20
21
) where
21
22
22
- import Data.Bifunctor ( first )
23
+ import Data.Map ( Map )
23
24
import Data.Text (Text )
24
25
import Dhall (FromDhall , ToDhall )
25
26
import Dhall.Syntax (Expr (.. ), FunctionBinding (.. ), Var (.. ))
@@ -164,6 +165,22 @@ toNestedHaskellType typeParams haskellTypes = loop
164
165
message dhallType = Pretty. renderString (Dhall.Pretty. layout (document dhallType))
165
166
166
167
loop dhallType = case dhallType of
168
+ Var v
169
+ | Just (V param index) <- List. find (v == ) typeParams -> do
170
+ let name = Syntax. mkName $ (Text. unpack param) ++ (show index)
171
+
172
+ return (VarT name)
173
+
174
+ | otherwise -> fail $ message v
175
+
176
+ _ | Just haskellType <- List. find (predicate dhallType) haskellTypes ->
177
+ case haskellType of
178
+ Predefined {.. } -> return haskellSplice
179
+ _ -> do
180
+ let name = Syntax. mkName (Text. unpack (typeName haskellType))
181
+
182
+ return (ConT name)
183
+
167
184
Bool ->
168
185
return (ConT ''Bool)
169
186
@@ -204,19 +221,7 @@ toNestedHaskellType typeParams haskellTypes = loop
204
221
205
222
return (AppT haskellAppType haskellElementType)
206
223
207
- Var v
208
- | Just (V param index) <- List. find (v == ) typeParams -> do
209
- let name = Syntax. mkName $ (Text. unpack param) ++ (show index)
210
-
211
- return (VarT name)
212
-
213
- | otherwise -> fail $ message v
214
-
215
- _ | Just haskellType <- List. find (predicate dhallType) haskellTypes -> do
216
- let name = Syntax. mkName (Text. unpack (typeName haskellType))
217
-
218
- return (ConT name)
219
- | otherwise -> fail $ message dhallType
224
+ _ -> fail $ message dhallType
220
225
221
226
-- | A deriving clause for `Generic`.
222
227
derivingGenericClause :: DerivClause
@@ -255,12 +260,8 @@ toDeclaration globalGenerateOptions haskellTypes typ =
255
260
SingleConstructorWith {.. } -> uncurry (fromSingle options typeName constructorName) $ getTypeParams code
256
261
MultipleConstructors {.. } -> uncurry (fromMulti globalGenerateOptions typeName) $ getTypeParams code
257
262
MultipleConstructorsWith {.. } -> uncurry (fromMulti options typeName) $ getTypeParams code
263
+ Predefined {} -> return []
258
264
where
259
- getTypeParams = first numberConsecutive . getTypeParams_ []
260
-
261
- getTypeParams_ acc (Lam _ (FunctionBinding _ v _ _ _) rest) = getTypeParams_ (v: acc) rest
262
- getTypeParams_ acc rest = (acc, rest)
263
-
264
265
toTypeVar (V n i) = Syntax. PlainTV $ Syntax. mkName (Text. unpack n ++ show i)
265
266
266
267
toDataD generateOptions@ GenerateOptions {.. } typeName typeParams constructors = do
@@ -330,13 +331,21 @@ toDeclaration globalGenerateOptions haskellTypes typ =
330
331
, " ... which is not a union type."
331
332
]
332
333
333
- -- | Number each variable, starting at 0
334
- numberConsecutive :: [Text. Text ] -> [Var ]
335
- numberConsecutive = snd . List. mapAccumR go Map. empty . reverse
334
+ getTypeParams :: Expr s a -> ([Var ], Expr s a )
335
+ getTypeParams = go []
336
336
where
337
- go m k =
338
- let (i, m') = Map. updateLookupWithKey (\ _ j -> Just $ j + 1 ) k m
339
- in maybe ((Map. insert k 0 m'), (V k 0 )) (\ i' -> (m', (V k i'))) i
337
+ go :: [Text ] -> Expr s a -> ([Var ], Expr s a )
338
+ go ! acc (Lam _ (FunctionBinding _ v _ _ _) rest) = go (v: acc) rest
339
+ go ! acc rest = (numberConsecutive $ reverse acc, rest)
340
+
341
+ -- | Number each variable, starting at 0
342
+ numberConsecutive :: [Text. Text ] -> [Var ]
343
+ numberConsecutive = snd . List. mapAccumR numberVar Map. empty
344
+
345
+ numberVar :: Map Text Int -> Text -> (Map Text Int , Var )
346
+ numberVar m k =
347
+ let (i, m') = Map. updateLookupWithKey (\ _ j -> Just $ j + 1 ) k m
348
+ in maybe ((Map. insert k 0 m'), (V k 0 )) (\ i' -> (m', (V k i'))) i
340
349
341
350
-- | Convert a Dhall type to the corresponding Haskell constructor
342
351
toConstructor
@@ -432,8 +441,8 @@ data HaskellType code
432
441
, code :: code
433
442
-- ^ Dhall code that evaluates to a type
434
443
}
435
- -- | Generate a Haskell type with more than one constructor from a Dhall
436
- -- union type.
444
+ -- | Like 'MultipleConstructors', but also takes some 'GenerateOptions' to
445
+ -- use for the generation of the Haskell type.
437
446
| MultipleConstructorsWith
438
447
{ options :: GenerateOptions
439
448
-- ^ The 'GenerateOptions' to use then generating the Haskell type.
@@ -442,10 +451,8 @@ data HaskellType code
442
451
, code :: code
443
452
-- ^ Dhall code that evaluates to a union type
444
453
}
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.
454
+ -- | Like 'SingleConstructor', but also takes some 'GenerateOptions' to use
455
+ -- for the generation of the Haskell type.
449
456
| SingleConstructorWith
450
457
{ options :: GenerateOptions
451
458
-- ^ The 'GenerateOptions' to use then generating the Haskell type.
@@ -456,6 +463,14 @@ data HaskellType code
456
463
, code :: code
457
464
-- ^ Dhall code that evaluates to a type
458
465
}
466
+ -- | Declare a predefined mapping from a Dhall type to an existing Haskell
467
+ -- type.
468
+ | Predefined
469
+ { haskellSplice :: Type
470
+ -- ^ An existing Haskell type
471
+ , code :: code
472
+ -- ^ Dhall code that evaluates to a type
473
+ }
459
474
deriving (Functor , Foldable , Traversable )
460
475
461
476
-- | This data type holds various options that let you control several aspects
0 commit comments