Move gql to Language.GraphQL.TH
All checks were successful
Build / audit (push) Successful in 6s
Build / test (push) Successful in 7m6s
Build / doc (push) Successful in 7m22s

This commit is contained in:
Eugen Wissner 2024-12-03 20:41:40 +01:00
parent c95a5fcd61
commit 131576e56c
Signed by: belka
GPG Key ID: A27FDC1E8EE902C0
10 changed files with 95 additions and 19 deletions

View File

@ -6,6 +6,11 @@ The format is based on
and this project adheres to and this project adheres to
[Haskell Package Versioning Policy](https://pvp.haskell.org/). [Haskell Package Versioning Policy](https://pvp.haskell.org/).
## [Unreleased]
### Changed
- `Language.GraphQL.Class.gql` is moved to `Language.GraphQL.TH` where it was
before in `graphql`.
## [1.0.5.0] - 2024-11-21 ## [1.0.5.0] - 2024-11-21
### Added ### Added
- Add `ToGraphQL` and `FromGraphQL` instances for `Value` and `HashMap`. - Add `ToGraphQL` and `FromGraphQL` instances for `Value` and `HashMap`.
@ -41,6 +46,7 @@ and this project adheres to
- JSON serialization. - JSON serialization.
- Test helpers. - Test helpers.
[Unreleased]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.5.0...master
[1.0.5.0]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.4.0...v1.0.5.0 [1.0.5.0]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.4.0...v1.0.5.0
[1.0.4.0]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.3.0...v1.0.4.0 [1.0.4.0]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.3.0...v1.0.4.0
[1.0.3.0]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.2.0...v1.0.3.0 [1.0.3.0]: https://git.caraus.tech/OSS/graphql-spice/compare/v1.0.2.0...v1.0.3.0

View File

@ -27,6 +27,7 @@ library
Language.GraphQL.Class Language.GraphQL.Class
Language.GraphQL.JSON Language.GraphQL.JSON
Language.GraphQL.Resolver Language.GraphQL.Resolver
Language.GraphQL.TH
Test.Hspec.GraphQL Test.Hspec.GraphQL
other-modules: other-modules:
hs-source-dirs: src hs-source-dirs: src
@ -38,7 +39,7 @@ library
containers >= 0.6 && < 0.8, containers >= 0.6 && < 0.8,
exceptions ^>= 0.10.4, exceptions ^>= 0.10.4,
hspec-expectations >= 0.8.2 && < 0.9, hspec-expectations >= 0.8.2 && < 0.9,
graphql >= 1.3.0 && < 1.5.0, graphql >= 1.3.0 && < 1.6.0,
megaparsec >= 9.0 && < 10, megaparsec >= 9.0 && < 10,
scientific ^>= 0.3.7, scientific ^>= 0.3.7,
template-haskell >= 2.16 && < 3, template-haskell >= 2.16 && < 3,
@ -58,6 +59,7 @@ test-suite graphql-test
Language.GraphQL.DirectiveSpec Language.GraphQL.DirectiveSpec
Language.GraphQL.FragmentSpec Language.GraphQL.FragmentSpec
Language.GraphQL.RootOperationSpec Language.GraphQL.RootOperationSpec
Language.GraphQL.THSpec
hs-source-dirs: hs-source-dirs:
tests tests
ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall

View File

@ -485,6 +485,7 @@ stripIndentation code = reverse
-- | Removes leading and trailing newlines. Indentation of the first line is -- | Removes leading and trailing newlines. Indentation of the first line is
-- removed from each line of the string. -- removed from each line of the string.
{-# DEPRECATED gql "Use Language.GraphQL.TH.gql instead" #-}
gql :: QuasiQuoter gql :: QuasiQuoter
gql = QuasiQuoter gql = QuasiQuoter
{ quoteExp = pure . LitE . StringL . stripIndentation { quoteExp = pure . LitE . StringL . stripIndentation

View File

@ -0,0 +1,49 @@
{- This Source Code Form is subject to the terms of the Mozilla Public License,
v. 2.0. If a copy of the MPL was not distributed with this file, You can
obtain one at https://mozilla.org/MPL/2.0/. -}
module Language.GraphQL.TH
( gql
) where
import Language.Haskell.TH
( Exp(..)
, Lit(..)
)
import Language.Haskell.TH.Quote (QuasiQuoter(..))
stripIndentation :: String -> String
stripIndentation code = reverse
$ dropWhile isLineBreak
$ reverse
$ unlines
$ indent spaces <$> lines' withoutLeadingNewlines
where
indent 0 xs = xs
indent count (' ' : xs) = indent (count - 1) xs
indent _ xs = xs
withoutLeadingNewlines = dropWhile isLineBreak code
spaces = length $ takeWhile (== ' ') withoutLeadingNewlines
lines' "" = []
lines' string =
let (line, rest) = break isLineBreak string
reminder =
case rest of
[] -> []
'\r' : '\n' : strippedString -> lines' strippedString
_ : strippedString -> lines' strippedString
in line : reminder
isLineBreak = flip any ['\n', '\r'] . (==)
-- | Removes leading and trailing newlines. Indentation of the first line is
-- removed from each line of the string.
gql :: QuasiQuoter
gql = QuasiQuoter
{ quoteExp = pure . LitE . StringL . stripIndentation
, quotePat = const
$ fail "Illegal gql QuasiQuote (allowed as expression only, used as a pattern)"
, quoteType = const
$ fail "Illegal gql QuasiQuote (allowed as expression only, used as a type)"
, quoteDec = const
$ fail "Illegal gql QuasiQuote (allowed as expression only, used as a declaration)"
}

View File

@ -5,6 +5,7 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Language.GraphQL.ClassSpec module Language.GraphQL.ClassSpec
( spec ( spec
) where ) where
@ -18,7 +19,6 @@ import Language.GraphQL.Class
, ToGraphQL(..) , ToGraphQL(..)
, deriveFromGraphQL , deriveFromGraphQL
, deriveToGraphQL , deriveToGraphQL
, gql
) )
import Test.Hspec (Spec, describe, it, shouldBe) import Test.Hspec (Spec, describe, it, shouldBe)
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
@ -161,14 +161,3 @@ spec = do
let given = Type.Enum "TWO_FIELD_ENUM_2" let given = Type.Enum "TWO_FIELD_ENUM_2"
expected = TWO_FIELD_ENUM_2 expected = TWO_FIELD_ENUM_2
in fromGraphQL given `shouldBe` Just expected in fromGraphQL given `shouldBe` Just expected
describe "gql" $
it "replaces CRNL with NL" $
let expected :: Text
expected = "line1\nline2\nline3"
actual = [gql|
line1
line2
line3
|]
in actual `shouldBe` expected

View File

@ -3,6 +3,7 @@
obtain one at https://mozilla.org/MPL/2.0/. -} obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Language.GraphQL.CoerceSpec module Language.GraphQL.CoerceSpec
( spec ( spec
) where ) where

View File

@ -14,11 +14,11 @@ import Language.GraphQL.AST.Document (Name)
import Data.HashMap.Strict (HashMap) import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap import qualified Data.HashMap.Strict as HashMap
import qualified Language.GraphQL as GraphQL import qualified Language.GraphQL as GraphQL
import Language.GraphQL.TH import "graphql-spice" Language.GraphQL.TH
import Language.GraphQL.Type import Language.GraphQL.Type
import qualified Language.GraphQL.Type.Out as Out import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec (Spec, describe, it) import Test.Hspec (Spec, describe, it)
import "graphql-spice" Test.Hspec.GraphQL import Test.Hspec.GraphQL
experimentalResolver :: Schema IO experimentalResolver :: Schema IO
experimentalResolver = schema queryType Nothing Nothing mempty experimentalResolver = schema queryType Nothing Nothing mempty

View File

@ -17,10 +17,10 @@ import Data.HashMap.Strict (HashMap)
import Language.GraphQL.Type import Language.GraphQL.Type
import Language.GraphQL.Error import Language.GraphQL.Error
import qualified Language.GraphQL.Type.Out as Out import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.TH import "graphql-spice" Language.GraphQL.TH
import qualified Language.GraphQL as GraphQL import qualified Language.GraphQL as GraphQL
import Test.Hspec (Spec, describe, it) import Test.Hspec (Spec, describe, it)
import "graphql-spice" Test.Hspec.GraphQL import Test.Hspec.GraphQL
size :: (Text, Value) size :: (Text, Value)
size = ("size", String "L") size = ("size", String "L")

View File

@ -15,10 +15,10 @@ import qualified Data.HashMap.Strict as HashMap
import Language.GraphQL import Language.GraphQL
import Language.GraphQL.AST (Name) import Language.GraphQL.AST (Name)
import Test.Hspec (Spec, describe, it) import Test.Hspec (Spec, describe, it)
import Language.GraphQL.TH import "graphql-spice" Language.GraphQL.TH
import Language.GraphQL.Type import Language.GraphQL.Type
import qualified Language.GraphQL.Type.Out as Out import qualified Language.GraphQL.Type.Out as Out
import "graphql-spice" Test.Hspec.GraphQL import Test.Hspec.GraphQL
hatType :: Out.ObjectType IO hatType :: Out.ObjectType IO
hatType = Out.ObjectType "Hat" Nothing [] hatType = Out.ObjectType "Hat" Nothing []

View File

@ -0,0 +1,28 @@
{- This Source Code Form is subject to the terms of the Mozilla Public License,
v. 2.0. If a copy of the MPL was not distributed with this file, You can
obtain one at https://mozilla.org/MPL/2.0/. -}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE PackageImports #-}
module Language.GraphQL.THSpec
( spec
) where
import Data.Text (Text)
import "graphql-spice" Language.GraphQL.TH (gql)
import Test.Hspec (Spec, describe, it, shouldBe)
spec :: Spec
spec = do
describe "gql" $
it "replaces CRNL with NL" $
let expected :: Text
expected = "line1\nline2\nline3"
actual = [gql|
line1
line2
line3
|]
in actual `shouldBe` expected