1+ {-# LANGUAGE CPP #-}
12{-# LANGUAGE DeriveTraversable #-}
23{-# LANGUAGE FlexibleContexts #-}
34{-# LANGUAGE OverloadedStrings #-}
@@ -60,7 +61,7 @@ import qualified Numeric.Natural
6061import qualified Prettyprinter.Render.String as Pretty
6162import qualified System.IO
6263
63-
64+
6465{-| This fully resolves, type checks, and normalizes the expression, so the
6566 resulting AST is self-contained.
6667
@@ -160,9 +161,9 @@ toNestedHaskellType typeParams haskellTypes = loop
160161 , " \n "
161162 , " ... which did not fit any of the above criteria."
162163 ]
163-
164+
164165 message dhallType = Pretty. renderString (Dhall.Pretty. layout (document dhallType))
165-
166+
166167 loop dhallType = case dhallType of
167168 Bool ->
168169 return (ConT ''Bool)
@@ -203,7 +204,7 @@ toNestedHaskellType typeParams haskellTypes = loop
203204 haskellElementType <- loop dhallElementType
204205
205206 return (AppT haskellAppType haskellElementType)
206-
207+
207208 Var v
208209 | Just (V param index) <- List. find (v == ) typeParams -> do
209210 let name = Syntax. mkName $ (Text. unpack param) ++ (show index)
@@ -255,15 +256,21 @@ toDeclaration generateOptions@GenerateOptions{..} haskellTypes typ =
255256 MultipleConstructors {.. } -> uncurry (fromMulti typeName) $ getTypeParams code
256257 where
257258 getTypeParams = first numberConsecutive . getTypeParams_ []
258-
259+
259260 getTypeParams_ acc (Lam _ (FunctionBinding _ v _ _ _) rest) = getTypeParams_ (v: acc) rest
260261 getTypeParams_ acc rest = (acc, rest)
261262
262263 derivingClauses = [ derivingGenericClause | generateFromDhallInstance || generateToDhallInstance ]
263264
264265 interpretOptions = generateToInterpretOptions generateOptions typ
265266
266- toTypeVar (V n i) = Syntax. PlainTV $ Syntax. mkName (Text. unpack n ++ show i)
267+ #if MIN_VERSION_template_haskell(2,17,0)
268+ toTypeVar :: Var -> Syntax. TyVarBndr ()
269+ toTypeVar (V n i) = Syntax. PlainTV (Syntax. mkName (Text. unpack n ++ show i)) ()
270+ #else
271+ toTypeVar :: Var -> Syntax. TyVarBndr
272+ toTypeVar (V n i) = Syntax. PlainTV (Syntax. mkName (Text. unpack n ++ show i))
273+ #endif
267274
268275 toDataD typeName typeParams constructors = do
269276 let name = Syntax. mkName (Text. unpack typeName)
@@ -277,16 +284,16 @@ toDeclaration generateOptions@GenerateOptions{..} haskellTypes typ =
277284
278285 fromSingle typeName constructorName typeParams dhallType = do
279286 constructor <- toConstructor typeParams generateOptions haskellTypes typeName (constructorName, Just dhallType)
280-
287+
281288 toDataD typeName typeParams [constructor]
282-
289+
283290 fromMulti typeName typeParams dhallType = case dhallType of
284291 Union kts -> do
285292 constructors <- traverse (toConstructor typeParams generateOptions haskellTypes typeName) (Dhall.Map. toList kts)
286293
287294 toDataD typeName typeParams constructors
288-
289- _ -> fail $ message dhallType
295+
296+ _ -> fail $ message dhallType
290297
291298 message dhallType = Pretty. renderString (Dhall.Pretty. layout $ document dhallType)
292299
0 commit comments