{-# LANGUAGE OverloadedStrings #-} -------------------------------------------------------------------------------- -- See end of this file for licence information. -------------------------------------------------------------------------------- -- | -- Module : Swish.RDF.Vocabulary.SIOC -- Copyright : (c) 2011 Douglas Burke -- License : GPL V2 -- -- Maintainer : Douglas Burke -- Stability : experimental -- Portability : OverloadedStrings -- -- This module defines some commonly used vocabulary terms from the SIOC -- project (). -- -------------------------------------------------------------------------------- module Swish.RDF.Vocabulary.SIOC ( -- | The version used for this module is Revison 1.35 of the -- \"SIOC Core Ontology Specification\", dated 25 March 2010, -- . namespaceSIOC -- * Classes , siocCommunity , siocContainer , siocForum , siocItem , siocPost , siocRole , siocSite , siocSpace , siocThread , siocUserAccount , siocUsergroup -- * Properties , siocabout , siocaccount_of , siocaddressed_to , siocadministrator_of , siocattachment , siocavatar , sioccontainer_of , sioccontent , sioccreator_of , siocearlier_version , siocemail , siocemail_sha1 , siocembeds_knowledge , siocfeed , siocfollows , siocfunction_of , siochas_administrator , siochas_container , siochas_creator , siochas_discussion , siochas_function , siochas_host , siochas_member , siochas_moderator , siochas_modifier , siochas_owner , siochas_parent , siochas_reply , siochas_scope , siochas_space , siochas_subscriber , siochas_usergroup , siochost_of , siocid , siocip_address , sioclast_activity_date , sioclast_item_date , sioclast_reply_date , sioclater_version , sioclatest_version , sioclink , sioclinks_to , siocmember_of , siocmoderator_of , siocmodifier_of , siocname , siocnext_by_date , siocnext_version , siocnote , siocnum_authors , siocnum_items , siocnum_replies , siocnum_threads , siocnum_views , siocowner_of , siocparent_of , siocprevious_by_date , siocprevious_version , siocrelated_to , siocreply_of , siocscope_of , siocsibling , siocspace_of , siocsubscriber_of , sioctopic , siocusergroup_of ) where import Swish.Namespace (Namespace, makeNamespace, ScopedName, makeNSScopedName) import Swish.QName (LName) import Data.Maybe (fromMaybe) import Network.URI (URI, parseURI) ------------------------------------------------------------ -- Namespace ------------------------------------------------------------ siocURI :: URI siocURI = fromMaybe (error "Internal error processing SIOC URI") $ parseURI "http://rdfs.org/sioc/ns#" -- | Maps @sioc@ to . namespaceSIOC :: Namespace namespaceSIOC = makeNamespace (Just "sioc") siocURI ------------------------------------------------------------ -- Terms ------------------------------------------------------------ toS :: LName -> ScopedName toS = makeNSScopedName namespaceSIOC -- Classes -- | @sioc:Community@ from . siocCommunity :: ScopedName siocCommunity = toS "Community" -- | @sioc:Container@ from . siocContainer :: ScopedName siocContainer = toS "Container" -- | @sioc:Forum@ from . siocForum :: ScopedName siocForum = toS "Forum" -- | @sioc:Item@ from . siocItem :: ScopedName siocItem = toS "Item" -- | @sioc:Post@ from . siocPost :: ScopedName siocPost = toS "Post" -- | @sioc:Role@ from . siocRole :: ScopedName siocRole = toS "Role" -- | @sioc:Site@ from . siocSite :: ScopedName siocSite = toS "Site" -- | @sioc:Space@ from . siocSpace :: ScopedName siocSpace = toS "Space" -- | @sioc:Thread@ from . siocThread :: ScopedName siocThread = toS "Thread" -- | @sioc:UserAccount@ from . siocUserAccount :: ScopedName siocUserAccount = toS "UserAccount" -- | @sioc:Usergroup@ from . siocUsergroup :: ScopedName siocUsergroup = toS "Usergroup" -- Properties -- | @sioc:about@ from . siocabout :: ScopedName siocabout = toS "about" -- | @sioc:account_of@ from . siocaccount_of :: ScopedName siocaccount_of = toS "account_of" -- | @sioc:addressed_to@ from . siocaddressed_to :: ScopedName siocaddressed_to = toS "addressed_to" -- | @sioc:administrator_of@ from . siocadministrator_of :: ScopedName siocadministrator_of = toS "administrator_of" -- | @sioc:attachment@ from . siocattachment :: ScopedName siocattachment = toS "attachment" -- | @sioc:avatar@ from . siocavatar :: ScopedName siocavatar = toS "avatar" -- | @sioc:container_of@ from . sioccontainer_of :: ScopedName sioccontainer_of = toS "container_of" -- | @sioc:content@ from . sioccontent :: ScopedName sioccontent = toS "content" -- | @sioc:creator_of@ from . sioccreator_of :: ScopedName sioccreator_of = toS "creator_of" -- | @sioc:earlier_version@ from . siocearlier_version :: ScopedName siocearlier_version = toS "earlier_version" -- | @sioc:email@ from . siocemail :: ScopedName siocemail = toS "email" -- | @sioc:email_sha1@ from . siocemail_sha1 :: ScopedName siocemail_sha1 = toS "email_sha1" -- | @sioc:embeds_knowledge@ from . siocembeds_knowledge :: ScopedName siocembeds_knowledge = toS "embeds_knowledge" -- | @sioc:feed@ from . siocfeed :: ScopedName siocfeed = toS "feed" -- | @sioc:follows@ from . siocfollows :: ScopedName siocfollows = toS "follows" -- | @sioc:function_of@ from . siocfunction_of :: ScopedName siocfunction_of = toS "function_of" -- | @sioc:has_administrator@ from . siochas_administrator :: ScopedName siochas_administrator = toS "has_administrator" -- | @sioc:has_container@ from . siochas_container :: ScopedName siochas_container = toS "has_container" -- | @sioc:has_creator@ from . siochas_creator :: ScopedName siochas_creator = toS "has_creator" -- | @sioc:has_discussion@ from . siochas_discussion :: ScopedName siochas_discussion = toS "has_discussion" -- | @sioc:has_function@ from . siochas_function :: ScopedName siochas_function = toS "has_function" -- | @sioc:has_host@ from . siochas_host :: ScopedName siochas_host = toS "has_host" -- | @sioc:has_member@ from . siochas_member :: ScopedName siochas_member = toS "has_member" -- | @sioc:has_moderator@ from . siochas_moderator :: ScopedName siochas_moderator = toS "has_moderator" -- | @sioc:has_modifier@ from . siochas_modifier :: ScopedName siochas_modifier = toS "has_modifier" -- | @sioc:has_owner@ from . siochas_owner :: ScopedName siochas_owner = toS "has_owner" -- | @sioc:has_parent@ from . siochas_parent :: ScopedName siochas_parent = toS "has_parent" -- | @sioc:has_reply@ from . siochas_reply :: ScopedName siochas_reply = toS "has_reply" -- | @sioc:has_scope@ from . siochas_scope :: ScopedName siochas_scope = toS "has_scope" -- | @sioc:has_space@ from . siochas_space :: ScopedName siochas_space = toS "has_space" -- | @sioc:has_subscriber@ from . siochas_subscriber :: ScopedName siochas_subscriber = toS "has_subscriber" -- | @sioc:has_usergroup@ from . siochas_usergroup :: ScopedName siochas_usergroup = toS "has_usergroup" -- | @sioc:host_of@ from . siochost_of :: ScopedName siochost_of = toS "host_of" -- | @sioc:id@ from . siocid :: ScopedName siocid = toS "id" -- | @sioc:ip_address@ from . siocip_address :: ScopedName siocip_address = toS "ip_address" -- | @sioc:last_activity_date@ from . sioclast_activity_date :: ScopedName sioclast_activity_date = toS "last_activity_date" -- | @sioc:last_item_date@ from . sioclast_item_date :: ScopedName sioclast_item_date = toS "last_item_date" -- | @sioc:last_reply_date@ from . sioclast_reply_date :: ScopedName sioclast_reply_date = toS "last_reply_date" -- | @sioc:later_version@ from . sioclater_version :: ScopedName sioclater_version = toS "later_version" -- | @sioc:latest_version@ from . sioclatest_version :: ScopedName sioclatest_version = toS "latest_version" -- | @sioc:link@ from . sioclink :: ScopedName sioclink = toS "link" -- | @sioc:links_to@ from . sioclinks_to :: ScopedName sioclinks_to = toS "links_to" -- | @sioc:member_of@ from . siocmember_of :: ScopedName siocmember_of = toS "member_of" -- | @sioc:moderator_of@ from . siocmoderator_of :: ScopedName siocmoderator_of = toS "moderator_of" -- | @sioc:modifier_of@ from . siocmodifier_of :: ScopedName siocmodifier_of = toS "modifier_of" -- | @sioc:name@ from . siocname :: ScopedName siocname = toS "name" -- | @sioc:next_by_date@ from . siocnext_by_date :: ScopedName siocnext_by_date = toS "next_by_date" -- | @sioc:next_version@ from . siocnext_version :: ScopedName siocnext_version = toS "next_version" -- | @sioc:note@ from . siocnote :: ScopedName siocnote = toS "note" -- | @sioc:num_authors@ from . siocnum_authors :: ScopedName siocnum_authors = toS "num_authors" -- | @sioc:num_items@ from . siocnum_items :: ScopedName siocnum_items = toS "num_items" -- | @sioc:num_replies@ from . siocnum_replies :: ScopedName siocnum_replies = toS "num_replies" -- | @sioc:num_threads@ from . siocnum_threads :: ScopedName siocnum_threads = toS "num_threads" -- | @sioc:num_views@ from . siocnum_views :: ScopedName siocnum_views = toS "num_views" -- | @sioc:owner_of@ from . siocowner_of :: ScopedName siocowner_of = toS "owner_of" -- | @sioc:parent_of@ from . siocparent_of :: ScopedName siocparent_of = toS "parent_of" -- | @sioc:previous_by_date@ from . siocprevious_by_date :: ScopedName siocprevious_by_date = toS "previous_by_date" -- | @sioc:previous_version@ from . siocprevious_version :: ScopedName siocprevious_version = toS "previous_version" -- | @sioc:related_to@ from . siocrelated_to :: ScopedName siocrelated_to = toS "related_to" -- | @sioc:reply_of@ from . siocreply_of :: ScopedName siocreply_of = toS "reply_of" -- | @sioc:scope_of@ from . siocscope_of :: ScopedName siocscope_of = toS "scope_of" -- | @sioc:sibling@ from . siocsibling :: ScopedName siocsibling = toS "sibling" -- | @sioc:space_of@ from . siocspace_of :: ScopedName siocspace_of = toS "space_of" -- | @sioc:subscriber_of@ from . siocsubscriber_of :: ScopedName siocsubscriber_of = toS "subscriber_of" -- | @sioc:topic@ from . sioctopic :: ScopedName sioctopic = toS "topic" -- | @sioc:usergroup_of@ from . siocusergroup_of :: ScopedName siocusergroup_of = toS "usergroup_of" -------------------------------------------------------------------------------- -- -- 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 -- --------------------------------------------------------------------------------