{-# LANGUAGE OverloadedStrings #-} -------------------------------------------------------------------------------- -- See end of this file for licence information. -------------------------------------------------------------------------------- -- | -- Module : Swish.RDF.Vocabulary.XSD -- Copyright : (c) 2011 Douglas Burke -- License : GPL V2 -- -- Maintainer : Douglas Burke -- Stability : experimental -- Portability : OverloadedStrings -- -- This module defines vocabulary terms from the XSD document. -- -------------------------------------------------------------------------------- module Swish.RDF.Vocabulary.XSD ( namespaceXSD -- * XSD data types -- -- | See the XSD Schema Part 2 documentation at <http://www.w3.org/TR/xmlschema-2/>; -- the version used is \"W3C Recommendation 28 October 2004\", -- <http://www.w3.org/TR/2004/REC-xmlschema-2-20041028/>. , xsdType -- ** Primitive datatypes -- -- | See the section \"Primitive datatypes\" at -- <http://www.w3.org/TR/xmlschema-2/#built-in-primitive-datatypes>. , xsdString , xsdBoolean , xsdDecimal , xsdFloat , xsdDouble , xsdDateTime , xsdTime , xsdDate , xsdAnyURI -- ** Derived datatypes -- -- | See the section \"Derived datatypes\" at -- <http://www.w3.org/TR/xmlschema-2/#built-in-derived>. , xsdInteger , xsdNonPosInteger , xsdNegInteger , xsdLong , xsdInt , xsdShort , xsdByte , xsdNonNegInteger , xsdUnsignedLong , xsdUnsignedInt , xsdUnsignedShort , xsdUnsignedByte , xsdPosInteger ) where import Swish.Namespace (Namespace, ScopedName, makeNamespace, makeNSScopedName) import Swish.QName (LName) import Data.Maybe (fromMaybe) import Network.URI (URI, parseURI) ------------------------------------------------------------ -- Namespace ------------------------------------------------------------ xsdURI :: URI xsdURI :: URI xsdURI = URI -> Maybe URI -> URI forall a. a -> Maybe a -> a fromMaybe ([Char] -> URI forall a. HasCallStack => [Char] -> a error [Char] "Internal error processing XSD URI") (Maybe URI -> URI) -> Maybe URI -> URI forall a b. (a -> b) -> a -> b $ [Char] -> Maybe URI parseURI [Char] "http://www.w3.org/2001/XMLSchema#" -- | Maps @xsd@ to <http://www.w3.org/2001/XMLSchema#>. namespaceXSD :: Namespace namespaceXSD :: Namespace namespaceXSD = Maybe Text -> URI -> Namespace makeNamespace (Text -> Maybe Text forall a. a -> Maybe a Just Text "xsd") URI xsdURI ------------------------------------------------------------ -- Terms ------------------------------------------------------------ -- | Create a scoped name for an XSD datatype with the given name. xsdType :: LName -> ScopedName xsdType :: LName -> ScopedName xsdType = Namespace -> LName -> ScopedName makeNSScopedName Namespace namespaceXSD -- | @xsd:string@ from <http://www.w3.org/TR/xmlschema-2/#string>. xsdString :: ScopedName xsdString :: ScopedName xsdString = LName -> ScopedName xsdType LName "string" -- | @xsd:boolean@ from <http://www.w3.org/TR/xmlschema-2/#boolean>. xsdBoolean :: ScopedName xsdBoolean :: ScopedName xsdBoolean = LName -> ScopedName xsdType LName "boolean" -- | @xsd:decimal@ from <http://www.w3.org/TR/xmlschema-2/#decimal>. xsdDecimal :: ScopedName xsdDecimal :: ScopedName xsdDecimal = LName -> ScopedName xsdType LName "decimal" -- | @xsd:integer@ from <http://www.w3.org/TR/xmlschema-2/#integer>. xsdInteger :: ScopedName xsdInteger :: ScopedName xsdInteger = LName -> ScopedName xsdType LName "integer" -- | @xsd:nonNegativeInteger@ from <http://www.w3.org/TR/xmlschema-2/#nonNegativeInteger>. xsdNonNegInteger :: ScopedName xsdNonNegInteger :: ScopedName xsdNonNegInteger = LName -> ScopedName xsdType LName "nonNegativeInteger" -- | @xsd:nonPositiveInteger@ from <http://www.w3.org/TR/xmlschema-2/#nonPositiveInteger>. xsdNonPosInteger :: ScopedName xsdNonPosInteger :: ScopedName xsdNonPosInteger = LName -> ScopedName xsdType LName "nonPositiveInteger" -- | @xsd:positiveInteger@ from <http://www.w3.org/TR/xmlschema-2/#positiveInteger>. xsdPosInteger :: ScopedName xsdPosInteger :: ScopedName xsdPosInteger = LName -> ScopedName xsdType LName "positiveInteger" -- | @xsd:negativeInteger@ from <http://www.w3.org/TR/xmlschema-2/#negativeInteger>. xsdNegInteger :: ScopedName xsdNegInteger :: ScopedName xsdNegInteger = LName -> ScopedName xsdType LName "negativeInteger" -- | @xsd:float@ from <http://www.w3.org/TR/xmlschema-2/#float>. xsdFloat :: ScopedName xsdFloat :: ScopedName xsdFloat = LName -> ScopedName xsdType LName "float" -- | @xsd:double@ from <http://www.w3.org/TR/xmlschema-2/#double>. xsdDouble :: ScopedName xsdDouble :: ScopedName xsdDouble = LName -> ScopedName xsdType LName "double" -- | @xsd:long@ from <http://www.w3.org/TR/xmlschema-2/#long>. xsdLong :: ScopedName xsdLong :: ScopedName xsdLong = LName -> ScopedName xsdType LName "long" -- | @xsd:int@ from <http://www.w3.org/TR/xmlschema-2/#int>. xsdInt :: ScopedName xsdInt :: ScopedName xsdInt = LName -> ScopedName xsdType LName "int" -- | @xsd:short@ from <http://www.w3.org/TR/xmlschema-2/#short>. xsdShort :: ScopedName xsdShort :: ScopedName xsdShort = LName -> ScopedName xsdType LName "short" -- | @xsd:byte@ from <http://www.w3.org/TR/xmlschema-2/#byte>. xsdByte :: ScopedName xsdByte :: ScopedName xsdByte = LName -> ScopedName xsdType LName "byte" -- | @xsd:unsignedLong@ from <http://www.w3.org/TR/xmlschema-2/#unsignedLong>. xsdUnsignedLong :: ScopedName xsdUnsignedLong :: ScopedName xsdUnsignedLong = LName -> ScopedName xsdType LName "unsignedLong" -- | @xsd:unsignedInt@ from <http://www.w3.org/TR/xmlschema-2/#unsignedInt>. xsdUnsignedInt :: ScopedName xsdUnsignedInt :: ScopedName xsdUnsignedInt = LName -> ScopedName xsdType LName "unsignedInt" -- | @xsd:unsignedShort@ from <http://www.w3.org/TR/xmlschema-2/#unsignedShort>. xsdUnsignedShort :: ScopedName xsdUnsignedShort :: ScopedName xsdUnsignedShort = LName -> ScopedName xsdType LName "unsignedShort" -- | @xsd:unsignedByte@ from <http://www.w3.org/TR/xmlschema-2/#unsignedByte>. xsdUnsignedByte :: ScopedName xsdUnsignedByte :: ScopedName xsdUnsignedByte = LName -> ScopedName xsdType LName "unsignedByte" -- | @xsd:date@ from <http://www.w3.org/TR/xmlschema-2/#date>. xsdDate :: ScopedName xsdDate :: ScopedName xsdDate = LName -> ScopedName xsdType LName "date" -- | @xsd:dateTime@ from <http://www.w3.org/TR/xmlschema-2/#dateTime>. xsdDateTime :: ScopedName xsdDateTime :: ScopedName xsdDateTime = LName -> ScopedName xsdType LName "dateTime" -- | @xsd:time@ from <http://www.w3.org/TR/xmlschema-2/#time>. xsdTime :: ScopedName xsdTime :: ScopedName xsdTime = LName -> ScopedName xsdType LName "time" -- | @xsd:anyURI@ from <http://www.w3.org/TR/xmlschema-2/#anyURI>. xsdAnyURI :: ScopedName xsdAnyURI :: ScopedName xsdAnyURI = LName -> ScopedName xsdType LName "anyURI" -------------------------------------------------------------------------------- -- -- Copyright (c) 2011 Douglas Burke -- All rights reserved. -- -- This file is part of Swish. -- -- Swish is free software; you can redistribute it and/or modify -- it under the terms of the GNU General Public License as published by -- the Free Software Foundation; either version 2 of the License, or -- (at your option) any later version. -- -- Swish is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU General Public License for more details. -- -- You should have received a copy of the GNU General Public License -- along with Swish; if not, write to: -- The Free Software Foundation, Inc., -- 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -- --------------------------------------------------------------------------------