{-# LANGUAGE OverloadedStrings #-}

--------------------------------------------------------------------------------
--  See end of this file for licence information.
--------------------------------------------------------------------------------
-- |
--  Module      :  Swish.RDF.Vocabulary.OWL
--  Copyright   :  (c) 2003, Graham Klyne, 2009 Vasili I Galchin, 2011 Douglas Burke
--  License     :  GPL V2
--
--  Maintainer  :  Douglas Burke
--  Stability   :  experimental
--  Portability :  OverloadedStrings
--
--  This module defines vocabulary terms from the OWL vocabulary. Note that there
--  is an unfortunate mixture of styles for property names - e.g. 'owlSameAs'
--  and 'owlequivalentClass'. At present there is no systematic attempt to
--  include terms from the vocabulary.
--
--------------------------------------------------------------------------------

module Swish.RDF.Vocabulary.OWL
    ( 
      namespaceOWL
      
    , owlOntology
    , owlimports
    , owlversionInfo
    , owldeprecated
    , owlpriorVersion
    , owlbackwardCompatibleWith
    , owlincompatibleWith
        
    , owlClass
    , owlThing
    , owlNothing
    , owlNamedIndividual
      
    , owlSameAs
    , owlequivalentClass
    , owlequivalentProperty
      
    , owlObjectProperty
    , owlDatatypeProperty
    , owlAnnotationProperty
      
    , owlrational
    , owlreal
    )
where

import Swish.Namespace (Namespace, ScopedName, makeNamespace, makeNSScopedName)
import Swish.QName (LName)

import Data.Maybe (fromMaybe)
import Network.URI (URI, parseURI)

------------------------------------------------------------
--  Namespace
------------------------------------------------------------

owlURI :: URI
owlURI :: URI
owlURI = URI -> Maybe URI -> URI
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> URI
forall a. HasCallStack => [Char] -> a
error [Char]
"Internal error processing OWL URI") (Maybe URI -> URI) -> Maybe URI -> URI
forall a b. (a -> b) -> a -> b
$ [Char] -> Maybe URI
parseURI [Char]
"http://www.w3.org/2002/07/owl#"

-- | Maps @owl@ to <http://www.w3.org/2002/07/owl#>.
namespaceOWL :: Namespace
namespaceOWL :: Namespace
namespaceOWL = Maybe Text -> URI -> Namespace
makeNamespace (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"owl") URI
owlURI

------------------------------------------------------------
--  Terms
------------------------------------------------------------

toO :: LName -> ScopedName
toO :: LName -> ScopedName
toO = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceOWL

-- | @owl:sameAs@.
owlSameAs   :: ScopedName
owlSameAs :: ScopedName
owlSameAs = LName -> ScopedName
toO LName
"sameAs"

-- | @owl:equivalentClass@.
owlequivalentClass :: ScopedName
owlequivalentClass :: ScopedName
owlequivalentClass = LName -> ScopedName
toO LName
"equivalentClass"

-- | @owl:equivalentProperty@.
owlequivalentProperty :: ScopedName
owlequivalentProperty :: ScopedName
owlequivalentProperty = LName -> ScopedName
toO LName
"equivalentPropery"

-- | @owl:Ontology@.
owlOntology :: ScopedName
owlOntology :: ScopedName
owlOntology = LName -> ScopedName
toO LName
"Ontology"

-- | @owl:imports@.
owlimports :: ScopedName
owlimports :: ScopedName
owlimports = LName -> ScopedName
toO LName
"imports"

-- | @owl:versionInfo@.
owlversionInfo :: ScopedName
owlversionInfo :: ScopedName
owlversionInfo = LName -> ScopedName
toO LName
"versionInfo"

-- | @owl:deprecated@.
owldeprecated :: ScopedName
owldeprecated :: ScopedName
owldeprecated = LName -> ScopedName
toO LName
"deprecated"

-- | @owl:priorVersion@.
owlpriorVersion :: ScopedName
owlpriorVersion :: ScopedName
owlpriorVersion = LName -> ScopedName
toO LName
"priorVersion"

-- | @owl:backwartCompatibleWith@.
owlbackwardCompatibleWith :: ScopedName
owlbackwardCompatibleWith :: ScopedName
owlbackwardCompatibleWith = LName -> ScopedName
toO LName
"backwardCompatibleWith"

-- | @owl:incompatibleWith@.
owlincompatibleWith :: ScopedName
owlincompatibleWith :: ScopedName
owlincompatibleWith = LName -> ScopedName
toO LName
"incompatibleWith"

-- | @owl:Class@.
owlClass :: ScopedName
owlClass :: ScopedName
owlClass = LName -> ScopedName
toO LName
"Class"

-- | @owl:ObjectProperty@.
owlObjectProperty :: ScopedName
owlObjectProperty :: ScopedName
owlObjectProperty = LName -> ScopedName
toO LName
"ObjectProperty"

-- | @owl:DatatypeProperty@.
owlDatatypeProperty :: ScopedName
owlDatatypeProperty :: ScopedName
owlDatatypeProperty = LName -> ScopedName
toO LName
"DatatypeProperty"

-- | @owl:AnnotationProperty@.
owlAnnotationProperty :: ScopedName
owlAnnotationProperty :: ScopedName
owlAnnotationProperty = LName -> ScopedName
toO LName
"AnnotationProperty"

-- | @owl:NamedIndividual@.
owlNamedIndividual :: ScopedName
owlNamedIndividual :: ScopedName
owlNamedIndividual = LName -> ScopedName
toO LName
"NamedIndividual"

-- | @owl:Thing@.
owlThing :: ScopedName
owlThing :: ScopedName
owlThing = LName -> ScopedName
toO LName
"Thing"

-- | @owl:Thing@.
owlNothing :: ScopedName
owlNothing :: ScopedName
owlNothing = LName -> ScopedName
toO LName
"Nothing"

-- | @owl:rational@.
owlrational :: ScopedName
owlrational :: ScopedName
owlrational = LName -> ScopedName
toO LName
"rational"

-- | @owl:real@.
owlreal :: ScopedName
owlreal :: ScopedName
owlreal = LName -> ScopedName
toO LName
"real"

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