Skip to content

Commit f5ba617

Browse files
committed
Added Predefined to Dhall.TH
1 parent f87eac8 commit f5ba617

File tree

1 file changed

+46
-31
lines changed

1 file changed

+46
-31
lines changed

dhall/src/Dhall/TH.hs

Lines changed: 46 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE BangPatterns #-}
12
{-# LANGUAGE DeriveTraversable #-}
23
{-# LANGUAGE FlexibleContexts #-}
34
{-# LANGUAGE OverloadedStrings #-}
@@ -19,7 +20,7 @@ module Dhall.TH
1920
, defaultGenerateOptions
2021
) where
2122

22-
import Data.Bifunctor (first)
23+
import Data.Map (Map)
2324
import Data.Text (Text)
2425
import Dhall (FromDhall, ToDhall)
2526
import Dhall.Syntax (Expr (..), FunctionBinding (..), Var (..))
@@ -164,6 +165,22 @@ toNestedHaskellType typeParams haskellTypes = loop
164165
message dhallType = Pretty.renderString (Dhall.Pretty.layout (document dhallType))
165166

166167
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+
167184
Bool ->
168185
return (ConT ''Bool)
169186

@@ -204,19 +221,7 @@ toNestedHaskellType typeParams haskellTypes = loop
204221

205222
return (AppT haskellAppType haskellElementType)
206223

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
220225

221226
-- | A deriving clause for `Generic`.
222227
derivingGenericClause :: DerivClause
@@ -255,12 +260,8 @@ toDeclaration globalGenerateOptions haskellTypes typ =
255260
SingleConstructorWith{..} -> uncurry (fromSingle options typeName constructorName) $ getTypeParams code
256261
MultipleConstructors{..} -> uncurry (fromMulti globalGenerateOptions typeName) $ getTypeParams code
257262
MultipleConstructorsWith{..} -> uncurry (fromMulti options typeName) $ getTypeParams code
263+
Predefined{} -> return []
258264
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-
264265
toTypeVar (V n i) = Syntax.PlainTV $ Syntax.mkName (Text.unpack n ++ show i)
265266

266267
toDataD generateOptions@GenerateOptions{..} typeName typeParams constructors = do
@@ -330,13 +331,21 @@ toDeclaration globalGenerateOptions haskellTypes typ =
330331
, "... which is not a union type."
331332
]
332333

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 []
336336
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
340349

341350
-- | Convert a Dhall type to the corresponding Haskell constructor
342351
toConstructor
@@ -432,8 +441,8 @@ data HaskellType code
432441
, code :: code
433442
-- ^ Dhall code that evaluates to a type
434443
}
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.
437446
| MultipleConstructorsWith
438447
{ options :: GenerateOptions
439448
-- ^ The 'GenerateOptions' to use then generating the Haskell type.
@@ -442,10 +451,8 @@ data HaskellType code
442451
, code :: code
443452
-- ^ Dhall code that evaluates to a union type
444453
}
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.
449456
| SingleConstructorWith
450457
{ options :: GenerateOptions
451458
-- ^ The 'GenerateOptions' to use then generating the Haskell type.
@@ -456,6 +463,14 @@ data HaskellType code
456463
, code :: code
457464
-- ^ Dhall code that evaluates to a type
458465
}
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+
}
459474
deriving (Functor, Foldable, Traversable)
460475

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

0 commit comments

Comments
 (0)