Separate schema data definitions and helper functions

This commit is contained in:
Adam Sapek 2015-03-10 01:41:11 -07:00
Родитель f710ceb39f
Коммит c2adfae6ee
16 изменённых файлов: 183 добавлений и 165 удалений

Просмотреть файл

@ -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 =

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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 |

Просмотреть файл

@ -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

Просмотреть файл

@ -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

Просмотреть файл

@ -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