Skip to content

Commit 87027f7

Browse files
committed
Rename Type to GType
We have two things called `Type`: the AST-level type and the Schema-level type. Here, we rename both. `GType` is chosen for consistency with `GInt`, `GBool`, etc. Motivation is allowing us to work on GHC 8.0 and 8.2. See protolude/protolude#79 for details.
1 parent ccc7d54 commit 87027f7

File tree

8 files changed

+24
-24
lines changed

8 files changed

+24
-24
lines changed

src/GraphQL/API.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -191,7 +191,7 @@ class HasAnnotatedType a where
191191
-- forget this. Maybe we can flip the internal encoding to be
192192
-- non-null by default and needing explicit null-encoding (via
193193
-- Maybe).
194-
getAnnotatedType :: Either NameError (Schema.AnnotatedType Schema.Type)
194+
getAnnotatedType :: Either NameError (Schema.AnnotatedType Schema.GType)
195195

196196
-- | Turn a non-null type into the optional version of its own type.
197197
dropNonNull :: Schema.AnnotatedType t -> Schema.AnnotatedType t
@@ -204,7 +204,7 @@ instance forall a. HasAnnotatedType a => HasAnnotatedType (Maybe a) where
204204
-- see TODO in HasAnnotatedType class
205205
getAnnotatedType = dropNonNull <$> getAnnotatedType @a
206206

207-
builtinType :: Schema.Builtin -> Either NameError (Schema.AnnotatedType Schema.Type)
207+
builtinType :: Schema.Builtin -> Either NameError (Schema.AnnotatedType Schema.GType)
208208
builtinType = pure . Schema.TypeNonNull . Schema.NonNullTypeNamed . Schema.BuiltinType
209209

210210
-- TODO(jml): Given that AnnotatedType is parametrised, we can probably reduce

src/GraphQL/Internal/Execution.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ import GraphQL.Internal.Validation
3232
, VariableDefinition(..)
3333
, VariableValue
3434
, Variable
35-
, Type(..)
35+
, GType(..)
3636
)
3737

3838
-- | Get an operation from a GraphQL document

src/GraphQL/Internal/Schema.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@
88
--
99
-- Equivalent representation of GraphQL /values/ is in "GraphQL.Value".
1010
module GraphQL.Internal.Schema
11-
( Type(..)
11+
( GType(..)
1212
-- * Builtin types
1313
, Builtin(..)
1414
-- * Defining new types
@@ -40,7 +40,7 @@ module GraphQL.Internal.Schema
4040
, lookupType
4141
) where
4242

43-
import Protolude hiding (Type)
43+
import Protolude
4444

4545
import qualified Data.Map as Map
4646
import GraphQL.Value (Value)
@@ -100,13 +100,13 @@ data NonNullType t = NonNullTypeNamed t
100100
| NonNullTypeList (ListType t)
101101
deriving (Eq, Ord, Show)
102102

103-
data Type = DefinedType TypeDefinition | BuiltinType Builtin deriving (Eq, Ord, Show)
103+
data GType = DefinedType TypeDefinition | BuiltinType Builtin deriving (Eq, Ord, Show)
104104

105-
instance DefinesTypes Type where
105+
instance DefinesTypes GType where
106106
getDefinedTypes (BuiltinType _) = mempty
107107
getDefinedTypes (DefinedType t) = getDefinedTypes t
108108

109-
instance HasName Type where
109+
instance HasName GType where
110110
getName (DefinedType x) = getName x
111111
getName (BuiltinType x) = getName x
112112

@@ -154,7 +154,7 @@ instance DefinesTypes ObjectTypeDefinition where
154154

155155
type Interfaces = [InterfaceTypeDefinition]
156156

157-
data FieldDefinition = FieldDefinition Name [ArgumentDefinition] (AnnotatedType Type)
157+
data FieldDefinition = FieldDefinition Name [ArgumentDefinition] (AnnotatedType GType)
158158
deriving (Eq, Ord, Show)
159159

160160
instance HasName FieldDefinition where

src/GraphQL/Internal/Syntax/AST.hs

Lines changed: 10 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ module GraphQL.Internal.Syntax.AST
2727
, ObjectField(..)
2828
, DefaultValue
2929
, Directive(..)
30-
, Type(..)
30+
, GType(..)
3131
, NamedType(..)
3232
, ListType(..)
3333
, NonNullType(..)
@@ -46,7 +46,7 @@ module GraphQL.Internal.Syntax.AST
4646
, TypeExtensionDefinition(..)
4747
) where
4848

49-
import Protolude hiding (Type)
49+
import Protolude
5050

5151
import Test.QuickCheck (Arbitrary(..), listOf, oneof)
5252

@@ -78,7 +78,7 @@ data OperationDefinition
7878
data Node = Node (Maybe Name) [VariableDefinition] [Directive] SelectionSet
7979
deriving (Eq,Show)
8080

81-
data VariableDefinition = VariableDefinition Variable Type (Maybe DefaultValue)
81+
data VariableDefinition = VariableDefinition Variable GType (Maybe DefaultValue)
8282
deriving (Eq,Show)
8383

8484
newtype Variable = Variable Name deriving (Eq, Ord, Show)
@@ -169,14 +169,14 @@ data Directive = Directive Name [Argument] deriving (Eq,Show)
169169

170170
-- * Type Reference
171171

172-
data Type = TypeNamed NamedType
173-
| TypeList ListType
174-
| TypeNonNull NonNullType
175-
deriving (Eq, Ord, Show)
172+
data GType = TypeNamed NamedType
173+
| TypeList ListType
174+
| TypeNonNull NonNullType
175+
deriving (Eq, Ord, Show)
176176

177177
newtype NamedType = NamedType Name deriving (Eq, Ord, Show)
178178

179-
newtype ListType = ListType Type deriving (Eq, Ord, Show)
179+
newtype ListType = ListType GType deriving (Eq, Ord, Show)
180180

181181
data NonNullType = NonNullTypeNamed NamedType
182182
| NonNullTypeList ListType
@@ -198,12 +198,12 @@ data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces [FieldDefinitio
198198

199199
type Interfaces = [NamedType]
200200

201-
data FieldDefinition = FieldDefinition Name ArgumentsDefinition Type
201+
data FieldDefinition = FieldDefinition Name ArgumentsDefinition GType
202202
deriving (Eq,Show)
203203

204204
type ArgumentsDefinition = [InputValueDefinition]
205205

206-
data InputValueDefinition = InputValueDefinition Name Type (Maybe DefaultValue)
206+
data InputValueDefinition = InputValueDefinition Name GType (Maybe DefaultValue)
207207
deriving (Eq,Show)
208208

209209
data InterfaceTypeDefinition = InterfaceTypeDefinition Name [FieldDefinition]

src/GraphQL/Internal/Syntax/Encoder.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -138,7 +138,7 @@ directive (AST.Directive name args) = "@" <> unName name <> optempty arguments a
138138

139139
-- * Type Reference
140140

141-
type_ :: AST.Type -> Text
141+
type_ :: AST.GType -> Text
142142
type_ (AST.TypeNamed (AST.NamedType x)) = unName x
143143
type_ (AST.TypeList x) = listType x
144144
type_ (AST.TypeNonNull x) = nonNullType x

src/GraphQL/Internal/Syntax/Parser.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -208,7 +208,7 @@ directive = AST.Directive
208208

209209
-- * Type Reference
210210

211-
type_ :: Parser AST.Type
211+
type_ :: Parser AST.GType
212212
type_ = AST.TypeList <$> listType
213213
<|> AST.TypeNonNull <$> nonNullType
214214
<|> AST.TypeNamed <$> namedType

src/GraphQL/Internal/Validation.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ module GraphQL.Internal.Validation
4444
, VariableDefinition(..)
4545
, VariableValue
4646
, Variable
47-
, AST.Type(..)
47+
, AST.GType(..)
4848
-- * Resolving queries
4949
, SelectionSetByType
5050
, SelectionSet(..)
@@ -624,7 +624,7 @@ validateArguments args = Arguments <$> mapErrors DuplicateArgument (makeMap [(na
624624
data VariableDefinition
625625
= VariableDefinition
626626
{ variable :: Variable -- ^ The name of the variable
627-
, variableType :: AST.Type -- ^ The type of the variable
627+
, variableType :: AST.GType -- ^ The type of the variable
628628
, defaultValue :: Maybe Value -- ^ An optional default value for the variable
629629
} deriving (Eq, Ord, Show)
630630

tests/SchemaTests.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ import GraphQL.Internal.Schema
2727
, AnnotatedType(..)
2828
, ListType(..)
2929
, UnionTypeDefinition(..)
30-
, Type(..)
30+
, GType(..)
3131
, TypeDefinition(..)
3232
, NonNullType(..)
3333
, Builtin(..)

0 commit comments

Comments
 (0)