mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-14 17:02:49 +03:00
Remove some TemplateHaskell from Hasura.SQL
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/9699 GitOrigin-RevId: 63d6a229f1feadcb07fac86181d4361d9229ef67
This commit is contained in:
parent
cb02a9a034
commit
5d027f9861
@ -1,5 +1,3 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Hasura.SQL.GeoJSON
|
||||
( Position (..),
|
||||
Point (..),
|
||||
@ -18,7 +16,6 @@ where
|
||||
import Control.Monad
|
||||
import Data.Aeson qualified as J
|
||||
import Data.Aeson.Casing qualified as J
|
||||
import Data.Aeson.TH qualified as J
|
||||
import Data.Aeson.Types qualified as J
|
||||
import Data.Vector qualified as V
|
||||
import Hasura.Prelude
|
||||
@ -129,28 +126,54 @@ newtype MultiPolygon = MultiPolygon {unMultiPolygon :: [Polygon]}
|
||||
data CRSNameProps = CRSNameProps
|
||||
{ _cnpName :: !Text
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
deriving (Show, Eq, Generic)
|
||||
|
||||
data CRSLinkProps = CRSLinkProps
|
||||
{ _clpHref :: !Text,
|
||||
_clpType :: !(Maybe Text)
|
||||
}
|
||||
deriving (Show, Eq)
|
||||
deriving (Show, Eq, Generic)
|
||||
|
||||
data CRS
|
||||
= CRSName !CRSNameProps
|
||||
| CRSLink !CRSLinkProps
|
||||
deriving (Show, Eq)
|
||||
deriving (Show, Eq, Generic)
|
||||
|
||||
$(J.deriveJSON (J.aesonPrefix J.camelCase) ''CRSNameProps)
|
||||
$(J.deriveJSON (J.aesonPrefix J.camelCase) ''CRSLinkProps)
|
||||
$( J.deriveJSON
|
||||
J.defaultOptions
|
||||
{ J.constructorTagModifier = J.camelCase . drop 3,
|
||||
J.sumEncoding = J.TaggedObject "type" "properties"
|
||||
}
|
||||
''CRS
|
||||
)
|
||||
instance J.FromJSON CRSNameProps where
|
||||
parseJSON = J.genericParseJSON (J.aesonPrefix J.camelCase)
|
||||
|
||||
instance J.ToJSON CRSNameProps where
|
||||
toJSON = J.genericToJSON (J.aesonPrefix J.camelCase)
|
||||
toEncoding = J.genericToEncoding (J.aesonPrefix J.camelCase)
|
||||
|
||||
instance J.FromJSON CRSLinkProps where
|
||||
parseJSON = J.genericParseJSON (J.aesonPrefix J.camelCase)
|
||||
|
||||
instance J.ToJSON CRSLinkProps where
|
||||
toJSON = J.genericToJSON (J.aesonPrefix J.camelCase)
|
||||
toEncoding = J.genericToEncoding (J.aesonPrefix J.camelCase)
|
||||
|
||||
instance J.FromJSON CRS where
|
||||
parseJSON =
|
||||
J.genericParseJSON
|
||||
J.defaultOptions
|
||||
{ J.constructorTagModifier = J.camelCase . drop 3,
|
||||
J.sumEncoding = J.TaggedObject "type" "properties"
|
||||
}
|
||||
|
||||
instance J.ToJSON CRS where
|
||||
toJSON =
|
||||
J.genericToJSON
|
||||
J.defaultOptions
|
||||
{ J.constructorTagModifier = J.camelCase . drop 3,
|
||||
J.sumEncoding = J.TaggedObject "type" "properties"
|
||||
}
|
||||
toEncoding =
|
||||
J.genericToEncoding
|
||||
J.defaultOptions
|
||||
{ J.constructorTagModifier = J.camelCase . drop 3,
|
||||
J.sumEncoding = J.TaggedObject "type" "properties"
|
||||
}
|
||||
|
||||
data GeometryWithCRS = GeometryWithCRS
|
||||
{ _gwcGeom :: !Geometry,
|
||||
|
@ -1,5 +1,3 @@
|
||||
{-# LANGUAGE TemplateHaskell #-}
|
||||
|
||||
module Hasura.SQL.Types
|
||||
( ToSQL (..),
|
||||
toSQLTxt,
|
||||
@ -10,7 +8,6 @@ where
|
||||
|
||||
import Autodocodec (Autodocodec (..), HasCodec (codec), dimapCodec, named, textCodec)
|
||||
import Data.Aeson
|
||||
import Data.Aeson.TH
|
||||
import Hasura.Prelude
|
||||
import Text.Builder qualified as TB
|
||||
|
||||
@ -44,7 +41,12 @@ instance (NFData a) => NFData (CollectableType a)
|
||||
|
||||
instance (Hashable a) => Hashable (CollectableType a)
|
||||
|
||||
$(deriveJSON defaultOptions {constructorTagModifier = drop 6} ''CollectableType)
|
||||
instance (FromJSON a) => FromJSON (CollectableType a) where
|
||||
parseJSON = genericParseJSON defaultOptions {constructorTagModifier = drop 6}
|
||||
|
||||
instance (ToJSON a) => ToJSON (CollectableType a) where
|
||||
toJSON = genericToJSON defaultOptions {constructorTagModifier = drop 6}
|
||||
toEncoding = genericToEncoding defaultOptions {constructorTagModifier = drop 6}
|
||||
|
||||
instance (ToSQL a) => ToSQL (CollectableType a) where
|
||||
toSQL = \case
|
||||
|
Loading…
Reference in New Issue
Block a user