|
1 | 1 | {-# LANGUAGE LambdaCase #-}
|
2 |
| -{-# LANGUAGE TemplateHaskell #-} |
| 2 | +{-# LANGUAGE TemplateHaskellQuotes #-} |
3 | 3 | {-# LANGUAGE TypeFamilies, ScopedTypeVariables #-}
|
4 | 4 | {-# LANGUAGE UndecidableInstances, MultiParamTypeClasses #-}
|
5 | 5 | {-# LANGUAGE UndecidableSuperClasses #-}
|
@@ -45,7 +45,7 @@ import qualified Data.HashMap.Strict as KM
|
45 | 45 | import Data.Functor.Compose
|
46 | 46 | import qualified Data.HashMap.Strict as HM
|
47 | 47 | import Data.Incremental
|
48 |
| -import Data.Maybe (isJust) |
| 48 | +import Data.Maybe (isJust, fromMaybe) |
49 | 49 | import Data.Monoid (Any(..))
|
50 | 50 | import Prettyprinter
|
51 | 51 | import qualified Data.Vector.Generic as G
|
@@ -123,7 +123,7 @@ instance WrapForall Bounded h xs => Bounded (xs :& h) where
|
123 | 123 | instance WrapForall TH.Lift h xs => TH.Lift (xs :& h) where
|
124 | 124 | lift = hfoldrWithIndexFor (Proxy :: Proxy (Instance1 TH.Lift h))
|
125 | 125 | (\_ x xs -> infixE (Just $ TH.lift x) (varE '(<:)) (Just xs)) (varE 'nil)
|
126 |
| -#if MIN_VERSION_template_haskell(2,17,0) |
| 126 | +#if MIN_VERSION_template_haskell(2,17,0) |
127 | 127 | liftTyped e = TH.Code $ TH.TExp <$> TH.lift e
|
128 | 128 | #elif MIN_VERSION_template_haskell(2,16,0)
|
129 | 129 | liftTyped e = TH.TExp <$> TH.lift e
|
@@ -225,7 +225,7 @@ instance Forall (KeyTargetAre KnownSymbol (Instance1 J.FromJSON h)) xs => J.From
|
225 | 225 | parseJSON = J.withObject "Object" $ \v -> hgenerateFor
|
226 | 226 | (Proxy :: Proxy (KeyTargetAre KnownSymbol (Instance1 J.FromJSON h)))
|
227 | 227 | $ \m -> let k = stringKeyOf m
|
228 |
| - in fmap Field $ J.prependFailure ("parsing " ++ show k ++ ": ") $ J.parseJSON $ maybe J.Null id $ KM.lookup k v |
| 228 | + in fmap Field $ J.prependFailure ("parsing " ++ show k ++ ": ") $ J.parseJSON $ fromMaybe J.Null $ KM.lookup k v |
229 | 229 |
|
230 | 230 | instance Forall (KeyTargetAre KnownSymbol (Instance1 J.ToJSON h)) xs => J.ToJSON (xs :& Field h) where
|
231 | 231 | toJSON = J.Object . hfoldlWithIndexFor
|
|
0 commit comments