33{-# LANGUAGE DeriveAnyClass #-}
44{-# LANGUAGE DeriveDataTypeable #-}
55{-# LANGUAGE DeriveGeneric #-}
6+ {-# LANGUAGE DeriveLift #-}
67{-# LANGUAGE DeriveTraversable #-}
78{-# LANGUAGE LambdaCase #-}
89{-# LANGUAGE OverloadedLists #-}
@@ -101,7 +102,6 @@ import qualified Data.Text
101102import qualified Data.Text.Prettyprint.Doc as Pretty
102103import qualified Dhall.Crypto
103104import qualified Dhall.Optics as Optics
104- import qualified Language.Haskell.TH.Syntax as Syntax
105105import qualified Network.URI as URI
106106
107107{-| Constants for a pure type system
@@ -124,10 +124,7 @@ import qualified Network.URI as URI
124124 Dhall is not a dependently typed language
125125-}
126126data Const = Type | Kind | Sort
127- deriving (Show , Eq , Ord , Data , Bounded , Enum , Generic , NFData )
128-
129- instance Lift Const where
130- lift = Syntax. liftData
127+ deriving (Show , Eq , Ord , Data , Bounded , Enum , Generic , Lift , NFData )
131128
132129instance Pretty Const where
133130 pretty = Pretty. unAnnotate . prettyConst
@@ -165,10 +162,7 @@ instance Pretty Const where
165162 appear as a numeric suffix.
166163-}
167164data Var = V Text ! Int
168- deriving (Data , Generic , Eq , Ord , Show , NFData )
169-
170- instance Lift Var where
171- lift = Syntax. liftData
165+ deriving (Data , Generic , Eq , Ord , Show , Lift , NFData )
172166
173167instance IsString Var where
174168 fromString str = V (fromString str) 0
@@ -196,7 +190,7 @@ data Binding s a = Binding
196190 , annotation :: Maybe (Maybe s , Expr s a )
197191 , bindingSrc2 :: Maybe s
198192 , value :: Expr s a
199- } deriving (Data , Eq , Foldable , Functor , Generic , NFData , Ord , Show , Traversable )
193+ } deriving (Data , Eq , Foldable , Functor , Generic , Lift , NFData , Ord , Show , Traversable )
200194
201195instance Bifunctor Binding where
202196 first k (Binding src0 a src1 b src2 c) =
@@ -214,7 +208,7 @@ makeBinding name = Binding Nothing name Nothing Nothing Nothing
214208-- | This wrapper around 'Prelude.Double' exists for its 'Eq' instance which is
215209-- defined via the binary encoding of Dhall @Double@s.
216210newtype DhallDouble = DhallDouble { getDhallDouble :: Double }
217- deriving (Show , Data , NFData , Generic )
211+ deriving (Show , Data , Lift , NFData , Generic )
218212
219213-- | This instance satisfies all the customary 'Eq' laws except substitutivity.
220214--
@@ -245,10 +239,7 @@ instance Ord DhallDouble where
245239
246240-- | The body of an interpolated @Text@ literal
247241data Chunks s a = Chunks [(Text , Expr s a )] Text
248- deriving (Functor , Foldable , Generic , Traversable , Show , Eq , Ord , Data , NFData )
249-
250- instance (Lift s , Lift a , Data s , Data a ) => Lift (Chunks s a ) where
251- lift = Syntax. liftData
242+ deriving (Functor , Foldable , Generic , Traversable , Show , Eq , Ord , Data , Lift , NFData )
252243
253244instance Data.Semigroup. Semigroup (Chunks s a ) where
254245 Chunks xysL zL <> Chunks [] zR =
@@ -273,7 +264,7 @@ data PreferAnnotation s a
273264 | PreferFromWith (Expr s a )
274265 -- ^ Stores the original @with@ expression
275266 | PreferFromCompletion
276- deriving (Data , Eq , Foldable , Functor , Generic , NFData , Ord , Show , Traversable )
267+ deriving (Data , Eq , Foldable , Functor , Generic , Lift , NFData , Ord , Show , Traversable )
277268
278269instance Bifunctor PreferAnnotation where
279270 first _ PreferFromSource = PreferFromSource
@@ -480,7 +471,7 @@ data Expr s a
480471 | ImportAlt (Expr s a ) (Expr s a )
481472 -- | > Embed import ~ import
482473 | Embed a
483- deriving (Foldable , Generic , Traversable , Show , Data , NFData )
474+ deriving (Foldable , Generic , Traversable , Show , Data , Lift , NFData )
484475-- NB: If you add a constructor to Expr, please also update the Arbitrary
485476-- instance in Dhall.Test.QuickCheck.
486477
@@ -497,9 +488,6 @@ deriving instance (Eq s, Eq a) => Eq (Expr s a)
497488-- | Note that this 'Ord' instance inherits `DhallDouble`'s defects.
498489deriving instance (Ord s , Ord a ) => Ord (Expr s a )
499490
500- instance (Lift s , Lift a , Data s , Data a ) => Lift (Expr s a ) where
501- lift = Syntax. liftData
502-
503491-- This instance is hand-written due to the fact that deriving
504492-- it does not give us an INLINABLE pragma. We annotate this fmap
505493-- implementation with this pragma below to allow GHC to, possibly,
0 commit comments