diff --git a/compiler/Bond/Parser.hs b/compiler/Bond/Parser.hs index 6f5e6736..13af405a 100644 --- a/compiler/Bond/Parser.hs +++ b/compiler/Bond/Parser.hs @@ -18,7 +18,8 @@ import Control.Monad.Reader import Text.Parsec.Pos (initialPos) import Text.Parsec hiding (many, optional, (<|>)) import Bond.Lexer -import Bond.Schema +import Bond.Schema.Types +import Bond.Schema.Util -- parser state, mutable and global data Symbols = diff --git a/compiler/Bond/Schema/Types.hs b/compiler/Bond/Schema/Types.hs new file mode 100644 index 00000000..a49018a0 --- /dev/null +++ b/compiler/Bond/Schema/Types.hs @@ -0,0 +1,148 @@ +-- Copyright (c) Microsoft. All rights reserved. +-- Licensed under the MIT license. See LICENSE file in the project root for full license information. + +{-# LANGUAGE OverloadedStrings, RecordWildCards #-} + +module Bond.Schema.Types + ( Attribute(..) + , Constant(..) + , Constraint(..) + , Declaration(..) + , Default(..) + , Field(..) + , Import(..) + , Language(..) + , Modifier(..) + , Namespace(..) + , QualifiedName + , Type(..) + , TypeParam(..) + ) where + +import Data.Word +import Bond.Util + +type QualifiedName = [String] + +data Modifier = Optional | Required | RequiredOptional deriving Eq + +data Type = + BT_Int8 | BT_Int16 | BT_Int32 | BT_Int64 | + BT_UInt8 | BT_UInt16 | BT_UInt32 | BT_UInt64 | + BT_Float | BT_Double | + BT_Bool | + BT_String | BT_WString | + BT_MetaName | BT_MetaFullName | + BT_Blob | + BT_Maybe Type | + BT_List Type | + BT_Vector Type | + BT_Nullable Type | + BT_Set Type | + BT_Map Type Type | + BT_Bonded Type | + BT_IntTypeArg Int | + BT_TypeParam TypeParam | + BT_UserDefined Declaration [Type] + deriving Eq + +data Default = + DefaultBool Bool | + DefaultInteger Integer | + DefaultFloat Double | + DefaultString String | + DefaultEnum String| + DefaultNothing + deriving Eq + +data Attribute = + Attribute + { attrName :: QualifiedName -- attribute name + , attrValue :: String -- value + } + deriving Eq + +data Field = + Field + { fieldAttributes :: [Attribute] -- zero or more attributes + , fieldOrdinal :: Word16 -- ordinal + , fieldModifier :: Modifier -- field modifier + , fieldType :: Type -- type + , fieldName :: String -- field name + , fieldDefault :: Maybe Default -- optional default value + } + deriving Eq + +data Constant = + Constant + { constantName :: String -- enum constant name + , constantValue :: Maybe Int -- optional value + } + deriving Eq + +data Constraint = Value deriving Eq + +instance Show Constraint where + show Value = ": value" + +data TypeParam = + TypeParam + { paramName :: String + , paramConstraint :: Maybe Constraint + } + deriving Eq + +instance Show TypeParam where + show TypeParam {..} = paramName ++ optional show paramConstraint + +data Declaration = + Struct + { declNamespaces :: [Namespace] -- namespace(s) in which the struct is declared + , declAttributes :: [Attribute] -- zero or more attributes + , declName :: String -- struct identifier + , declParams :: [TypeParam] -- type parameters for generics + , structBase :: Maybe Type -- optional base struct + , structFields :: [Field] -- zero or more fields + } + | + Enum + { declNamespaces :: [Namespace] -- namespace(s) in which the enum is declared + , declAttributes :: [Attribute] -- zero or more attributes + , declName :: String -- enum identifier + , enumConstants :: [Constant] -- one or more constant values + } + | + Forward + { declNamespaces :: [Namespace] -- namespace(s) in which the struct is declared + , declName :: String -- struct identifier + , declParams :: [TypeParam] -- type parameters for generics + } + | + Alias + { declNamespaces :: [Namespace] -- namespace(s) in which the alias is declared + , declName :: String -- alias identifier + , declParams :: [TypeParam] -- type parameters for generics + , aliasType :: Type -- aliased type + } + deriving Eq + +showTypeParams :: [TypeParam] -> String +showTypeParams = angles . sepBy ", " show + +instance Show Declaration where + show Struct {..} = "struct " ++ declName ++ showTypeParams declParams + show Enum {..} = "enum " ++ declName + show Forward {..} = "struct declaration " ++ declName ++ showTypeParams declParams + show Alias {..} = "alias " ++ declName ++ showTypeParams declParams + +data Import = Import FilePath + +data Language = Cpp | Cs | CSharp | Java deriving (Eq) + +data Namespace = + Namespace + { nsLanguage :: Maybe Language + , nsName :: QualifiedName + } + deriving Eq + diff --git a/compiler/Bond/Schema.hs b/compiler/Bond/Schema/Util.hs similarity index 51% rename from compiler/Bond/Schema.hs rename to compiler/Bond/Schema/Util.hs index eaa14a28..d0aa3983 100644 --- a/compiler/Bond/Schema.hs +++ b/compiler/Bond/Schema/Util.hs @@ -3,39 +3,26 @@ {-# LANGUAGE OverloadedStrings, RecordWildCards #-} -module Bond.Schema - ( Declaration(..) - , Field(..) - , makeField - , Constant(..) - , Modifier(..) - , Type(..) - , TypeParam(..) - , Constraint(..) - , Default(..) - , Import(..) - , Language(..) - , Namespace(..) - , Attribute(..) - , QualifiedName - , takeName - , takeNamespace - , showQualifiedName - , scalarType - , listType - , associativeType +module Bond.Schema.Util + ( associativeType , containerType - , stringType - , metaType - , structType - , nullableType , duplicateDeclaration - , isBaseField , foldMapFields , foldMapStructFields , foldMapType + , isBaseField + , listType + , makeField , metaField + , metaType + , nullableType , resolveAlias + , scalarType + , showQualifiedName + , stringType + , structType + , takeName + , takeNamespace ) where import Data.Maybe @@ -44,8 +31,7 @@ import Data.List import Data.Foldable (foldMap) import Data.Monoid import Bond.Util - -type QualifiedName = [String] +import Bond.Schema.Types takeName :: QualifiedName -> String takeName = last @@ -56,28 +42,6 @@ takeNamespace = subtract 1 . length >>= take showQualifiedName :: QualifiedName -> String showQualifiedName = sepBy "." id -data Modifier = Optional | Required | RequiredOptional deriving Eq - -data Type = - BT_Int8 | BT_Int16 | BT_Int32 | BT_Int64 | - BT_UInt8 | BT_UInt16 | BT_UInt32 | BT_UInt64 | - BT_Float | BT_Double | - BT_Bool | - BT_String | BT_WString | - BT_MetaName | BT_MetaFullName | - BT_Blob | - BT_Maybe Type | - BT_List Type | - BT_Vector Type | - BT_Nullable Type | - BT_Set Type | - BT_Map Type Type | - BT_Bonded Type | - BT_IntTypeArg Int | - BT_TypeParam TypeParam | - BT_UserDefined Declaration [Type] - deriving Eq - scalarType :: Type -> Bool scalarType BT_Int8 = True scalarType BT_Int16 = True @@ -129,33 +93,6 @@ nullableType _ = False metaField :: Field -> Any metaField Field {..} = Any $ metaType fieldType -data Default = - DefaultBool Bool | - DefaultInteger Integer | - DefaultFloat Double | - DefaultString String | - DefaultEnum String| - DefaultNothing - deriving Eq - -data Attribute = - Attribute - { attrName :: QualifiedName -- attribute name - , attrValue :: String -- value - } - deriving Eq - -data Field = - Field - { fieldAttributes :: [Attribute] -- zero or more attributes - , fieldOrdinal :: Word16 -- ordinal - , fieldModifier :: Modifier -- field modifier - , fieldType :: Type -- type - , fieldName :: String -- field name - , fieldDefault :: Maybe Default -- optional default value - } - deriving Eq - makeField :: [Attribute] -> Word16 -> Modifier @@ -166,68 +103,6 @@ makeField :: [Attribute] makeField a o m t n d@(Just DefaultNothing) = Field a o m (BT_Maybe t) n d makeField a o m t n d = Field a o m t n d -data Constant = - Constant - { constantName :: String -- enum constant name - , constantValue :: Maybe Int -- optional value - } - deriving Eq - -data Constraint = Value deriving Eq - -instance Show Constraint where - show Value = ": value" - -data TypeParam = - TypeParam - { paramName :: String - , paramConstraint :: Maybe Constraint - } - deriving Eq - -instance Show TypeParam where - show TypeParam {..} = paramName ++ optional show paramConstraint - -data Declaration = - Struct - { declNamespaces :: [Namespace] -- namespace(s) in which the struct is declared - , declAttributes :: [Attribute] -- zero or more attributes - , declName :: String -- struct identifier - , declParams :: [TypeParam] -- type parameters for generics - , structBase :: Maybe Type -- optional base struct - , structFields :: [Field] -- zero or more fields - } - | - Enum - { declNamespaces :: [Namespace] -- namespace(s) in which the enum is declared - , declAttributes :: [Attribute] -- zero or more attributes - , declName :: String -- enum identifier - , enumConstants :: [Constant] -- one or more constant values - } - | - Forward - { declNamespaces :: [Namespace] -- namespace(s) in which the struct is declared - , declName :: String -- struct identifier - , declParams :: [TypeParam] -- type parameters for generics - } - | - Alias - { declNamespaces :: [Namespace] -- namespace(s) in which the alias is declared - , declName :: String -- alias identifier - , declParams :: [TypeParam] -- type parameters for generics - , aliasType :: Type -- aliased type - } - deriving Eq - -showTypeParams :: [TypeParam] -> String -showTypeParams = angles . sepBy ", " show - -instance Show Declaration where - show Struct {..} = "struct " ++ declName ++ showTypeParams declParams - show Enum {..} = "enum " ++ declName - show Forward {..} = "struct declaration " ++ declName ++ showTypeParams declParams - show Alias {..} = "alias " ++ declName ++ showTypeParams declParams - mapType :: (Type -> Type) -> Type -> Type mapType f (BT_UserDefined decl args) = BT_UserDefined decl $ map f args mapType f (BT_Map key value) = BT_Map (f key) (f value) @@ -275,15 +150,3 @@ duplicateDeclaration left right = isBaseField :: String -> Maybe Type -> Bool isBaseField name = getAny . optional (foldMapFields (Any.(name==).fieldName)) -data Import = Import FilePath - -data Language = Cpp | Cs | CSharp | Java deriving (Eq) - -data Namespace = - Namespace - { nsLanguage :: Maybe Language - , nsName :: QualifiedName - } - deriving Eq - - diff --git a/compiler/Bond/Template/Cpp/Apply_cpp.hs b/compiler/Bond/Template/Cpp/Apply_cpp.hs index 92ba3d3d..07dd1b29 100644 --- a/compiler/Bond/Template/Cpp/Apply_cpp.hs +++ b/compiler/Bond/Template/Cpp/Apply_cpp.hs @@ -7,7 +7,7 @@ module Bond.Template.Cpp.Apply_cpp (apply_cpp) where import Data.Text.Lazy (Text) import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types import Bond.Template.TypeMapping import Bond.Template.Util import Bond.Template.Cpp.Apply_h diff --git a/compiler/Bond/Template/Cpp/Apply_h.hs b/compiler/Bond/Template/Cpp/Apply_h.hs index 77fe9194..61bc807e 100644 --- a/compiler/Bond/Template/Cpp/Apply_h.hs +++ b/compiler/Bond/Template/Cpp/Apply_h.hs @@ -9,7 +9,7 @@ import System.FilePath import Data.Monoid import Data.Text.Lazy (Text) import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types import Bond.Util import Bond.Template.Util import Bond.Template.TypeMapping diff --git a/compiler/Bond/Template/Cpp/Enum_h.hs b/compiler/Bond/Template/Cpp/Enum_h.hs index 96d91a24..ece5a422 100644 --- a/compiler/Bond/Template/Cpp/Enum_h.hs +++ b/compiler/Bond/Template/Cpp/Enum_h.hs @@ -8,7 +8,7 @@ module Bond.Template.Cpp.Enum_h (enum_h) where import Data.Monoid import Data.Text.Lazy (Text) import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types import Bond.Template.TypeMapping import Bond.Template.Util import qualified Bond.Template.Cpp.Util as CPP diff --git a/compiler/Bond/Template/Cpp/Reflection_h.hs b/compiler/Bond/Template/Cpp/Reflection_h.hs index 4601c877..1d804ebd 100644 --- a/compiler/Bond/Template/Cpp/Reflection_h.hs +++ b/compiler/Bond/Template/Cpp/Reflection_h.hs @@ -9,7 +9,7 @@ import System.FilePath import Data.Monoid import Data.Text.Lazy (Text) import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types import Bond.Template.TypeMapping import Bond.Template.Util import qualified Bond.Template.Cpp.Util as CPP diff --git a/compiler/Bond/Template/Cpp/Types_cpp.hs b/compiler/Bond/Template/Cpp/Types_cpp.hs index 6398aa36..29a8ca3c 100644 --- a/compiler/Bond/Template/Cpp/Types_cpp.hs +++ b/compiler/Bond/Template/Cpp/Types_cpp.hs @@ -8,7 +8,7 @@ module Bond.Template.Cpp.Types_cpp (types_cpp) where import Data.Monoid import Data.Text.Lazy (Text) import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types import Bond.Template.TypeMapping import Bond.Template.Util import qualified Bond.Template.Cpp.Util as CPP diff --git a/compiler/Bond/Template/Cpp/Types_h.hs b/compiler/Bond/Template/Cpp/Types_h.hs index c8e42b75..55ade97d 100644 --- a/compiler/Bond/Template/Cpp/Types_h.hs +++ b/compiler/Bond/Template/Cpp/Types_h.hs @@ -14,7 +14,8 @@ import qualified Data.Text.Lazy as L import Data.Foldable (foldMap) import Text.Shakespeare.Text import Bond.Version -import Bond.Schema +import Bond.Schema.Types +import Bond.Schema.Util import Bond.Util import Bond.Template.TypeMapping import Bond.Template.Util diff --git a/compiler/Bond/Template/Cpp/Util.hs b/compiler/Bond/Template/Cpp/Util.hs index 07d6d8ef..52025e4f 100644 --- a/compiler/Bond/Template/Cpp/Util.hs +++ b/compiler/Bond/Template/Cpp/Util.hs @@ -23,7 +23,7 @@ module Bond.Template.Cpp.Util import Text.Shakespeare.Text import Data.Monoid import Data.Text.Lazy (Text) -import Bond.Schema +import Bond.Schema.Types import Bond.Util import Bond.Template.Util import Bond.Template.TypeMapping diff --git a/compiler/Bond/Template/Cs/Types_cs.hs b/compiler/Bond/Template/Cs/Types_cs.hs index 2b8e4114..7b419949 100644 --- a/compiler/Bond/Template/Cs/Types_cs.hs +++ b/compiler/Bond/Template/Cs/Types_cs.hs @@ -9,7 +9,8 @@ import Data.Monoid import Data.Foldable (foldMap) import Data.Text.Lazy (Text) import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types +import Bond.Schema.Util import Bond.Util import Bond.Template.TypeMapping import Bond.Template.Util diff --git a/compiler/Bond/Template/Cs/Util.hs b/compiler/Bond/Template/Cs/Util.hs index cd9da7fa..bb41a0c3 100644 --- a/compiler/Bond/Template/Cs/Util.hs +++ b/compiler/Bond/Template/Cs/Util.hs @@ -17,7 +17,8 @@ import Data.Monoid import Data.Text.Lazy (Text) import Text.Shakespeare.Text import Bond.Version -import Bond.Schema +import Bond.Schema.Types +import Bond.Schema.Util import Bond.Template.TypeMapping import Bond.Template.Util diff --git a/compiler/Bond/Template/CustomMapping.hs b/compiler/Bond/Template/CustomMapping.hs index 24838abf..0953f657 100644 --- a/compiler/Bond/Template/CustomMapping.hs +++ b/compiler/Bond/Template/CustomMapping.hs @@ -14,7 +14,7 @@ module Bond.Template.CustomMapping import Data.Char import Control.Applicative import Text.Parsec hiding (many, optional, (<|>)) -import Bond.Schema +import Bond.Schema.Types data Fragment = Fragment String | diff --git a/compiler/Bond/Template/TypeMapping.hs b/compiler/Bond/Template/TypeMapping.hs index 2365d659..da5bcf0c 100644 --- a/compiler/Bond/Template/TypeMapping.hs +++ b/compiler/Bond/Template/TypeMapping.hs @@ -31,7 +31,8 @@ import Control.Monad.Reader import qualified Data.Text.Lazy as L import Data.Text.Lazy.Builder import Text.Shakespeare.Text -import Bond.Schema +import Bond.Schema.Types +import Bond.Schema.Util import Bond.Util import Bond.Template.Util import Bond.Template.CustomMapping diff --git a/compiler/CMakeLists.txt b/compiler/CMakeLists.txt index ded0c9fb..9c2dade2 100644 --- a/compiler/CMakeLists.txt +++ b/compiler/CMakeLists.txt @@ -13,7 +13,9 @@ set (sources Options.hs Bond/Lexer.hs Bond/Parser.hs - Bond/Schema.hs + Bond/Schema/JSON.hs + Bond/Schema/Types.hs + Bond/Schema/Util.hs Bond/Util.hs Bond/Version.hs Bond/Template/CustomMapping.hs diff --git a/compiler/Main.hs b/compiler/Main.hs index 16174bdc..309a9c02 100644 --- a/compiler/Main.hs +++ b/compiler/Main.hs @@ -18,7 +18,7 @@ import GHC.Conc (getNumProcessors, setNumCapabilities) import Data.Text.Lazy (Text) import qualified Data.Text.Lazy.IO as L import Bond.Parser -import Bond.Schema (Declaration, Import) +import Bond.Schema.Types (Declaration, Import) import Bond.Template.Util import Bond.Template.Cpp.Reflection_h import Bond.Template.Cpp.Types_h