Skip to content

Commit

Permalink
fix double bang
Browse files Browse the repository at this point in the history
  • Loading branch information
roryc89 committed Dec 8, 2023
1 parent 5e17f33 commit 105be21
Showing 1 changed file with 38 additions and 4 deletions.
42 changes: 38 additions & 4 deletions src/GraphQL/Client/Variables.purs
Original file line number Diff line number Diff line change
@@ -1,13 +1,37 @@
module GraphQL.Client.Variables where
module GraphQL.Client.Variables
( CombineVarsProp
, GetVarRec(..)
, GqlQueryVars
, GqlQueryVarsN(..)
, PropGetGqlVars
, WithVars(..)
, class GetGqlQueryVars
, class GetGqlQueryVarsRecord
, class GetVar
, class GqlArrayAndMaybeType
, class VarsTypeChecked
, combineVars
, getQuery
, getQueryVars
, getVar
, gqlArrayAndMaybeType
, getVarsJson
, getVarsTypeNames
, propGetGqlVars
, withVars
, withVarsEncode
) where

import Prelude

import Control.Apply (lift2)
import Data.Argonaut.Core (Json, jsonEmptyObject)
import Data.Argonaut.Encode (class EncodeJson, encodeJson)
import Data.List (List(..), intercalate)
import Data.Maybe (Maybe)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype, unwrap)
import Data.String as String
import Data.String.CodeUnits (charAt)
import Data.Symbol (class IsSymbol, reflectSymbol)
import GraphQL.Client.Alias (Alias)
import GraphQL.Client.Alias.Dynamic (Spread)
Expand Down Expand Up @@ -360,8 +384,18 @@ else instance GqlArrayAndMaybeType a => GqlArrayAndMaybeType (Array a) where
gqlArrayAndMaybeType _ str = "[" <> gqlArrayAndMaybeType (Proxy :: _ a) str <> "]!"

else instance GqlArrayAndMaybeType a => GqlArrayAndMaybeType (Maybe a) where
gqlArrayAndMaybeType _ str = str
gqlArrayAndMaybeType _ str = removeSuffix '!' str

else instance GqlArrayAndMaybeType a where
gqlArrayAndMaybeType _ str = str <> "!"
gqlArrayAndMaybeType _ str = if endsWith '!' str then str else str <> "!"

endsWith :: Char -> String -> Boolean
endsWith c str =
let
len = String.length str
in
charAt (len - 1) str == Just c

removeSuffix :: Char -> String -> String
removeSuffix c str = if endsWith c str then String.take (String.length str - 1) str else str

0 comments on commit 105be21

Please sign in to comment.