{-# LANGUAGE OverloadedStrings #-}

--------------------------------------------------------------------------------
--  See end of this file for licence information.
--------------------------------------------------------------------------------
-- |
--  Module      :  Swish.RDF.Vocabulary.FOAF
--  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 FOAF
--  vocabulary (<http://xmlns.com/foaf/spec/>).
--
--  Note that unlike some of the existing vocabularies in Swish, the FOAF
--  one matches the case and spelling of the RDF terms; so we
--  use 'foafbased_near'
--  rather than @foafBasedNear@. This is partly because some terms would
--  end up with the same Haskell label if a conversion to camel-case wer
--  used.
--
--------------------------------------------------------------------------------

module Swish.RDF.Vocabulary.FOAF
    ( 
      -- | The version used for this module is 
      -- \"FOAF Vocabulary Specification 0.98 Namespace Document 9 August 2010 - /Marco Polo Edition/\",
      -- <http://xmlns.com/foaf/spec/20100809.html>.
      namespaceFOAF
      
      -- * Classes
      , foafAgent
      , foafDocument
      , foafGroup
      , foafImage
      , foafLabelProperty
      , foafOnlineAccount
      , foafOnlineChatAccount
      , foafOnlineEcommerceAccount
      , foafOnlineGamingAccount
      , foafOrganization
      , foafPerson
      , foafPersonalProfileDocument
      , foafProject
        
      -- * Properties
      , foafaccount
      , foafaccountName
      , foafaccountServiceHomepage
      , foafage
      , foafaimChatID
      , foafbased_near
      , foafbirthday
      , foafcurrentProject
      , foafdepiction
      , foafdepicts
      , foafdnaChecksum
      , foaffamilyName
      , foaffamily_name
      , foaffirstName
      , foaffocus
      , foaffundedBy
      , foafgeekcode
      , foafgender
      , foafgivenName
      , foafgivenname
      , foafholdsAccount
      , foafhomepage
      , foaficqChatID
      , foafimg
      , foafinterest
      , foafisPrimaryTopicOf
      , foafjabberID
      , foafknows
      , foaflastName
      , foaflogo
      , foafmade
      , foafmaker
      , foafmbox
      , foafmbox_sha1sum
      , foafmember
      , foafmembershipClass
      , foafmsnChatID
      , foafmyersBriggs
      , foafname
      , foafnick
      , foafopenid
      , foafpage
      , foafpastProject
      , foafphone
      , foafplan
      , foafprimaryTopic
      , foafpublications
      , foafschoolHomepage
      , foafsha1
      , foafskypeID
      , foafstatus
      , foafsurname
      , foaftheme
      , foafthumbnail
      , foaftipjar
      , foaftitle
      , foaftopic
      , foaftopic_interest
      , foafweblog
      , foafworkInfoHomepage
      , foafworkplaceHomepage
      , foafyahooChatID
    )
where

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

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

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

foafURI :: URI
foafURI :: URI
foafURI = URI -> Maybe URI -> URI
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> URI
forall a. HasCallStack => [Char] -> a
error [Char]
"Internal error processing FOAF URI") (Maybe URI -> URI) -> Maybe URI -> URI
forall a b. (a -> b) -> a -> b
$ [Char] -> Maybe URI
parseURI [Char]
"http://xmlns.com/foaf/0.1/"

-- | Maps @foaf@ to <http://xmlns.com/foaf/0.1/>.
namespaceFOAF :: Namespace
namespaceFOAF :: Namespace
namespaceFOAF = Maybe Text -> URI -> Namespace
makeNamespace (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"foaf") URI
foafURI

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

toF :: LName -> ScopedName
toF :: LName -> ScopedName
toF  = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceFOAF

-- Classes

-- | @foaf:Agent@ from <http://xmlns.com/foaf/spec/#term_Agent>.
foafAgent :: ScopedName
foafAgent :: ScopedName
foafAgent = LName -> ScopedName
toF LName
"Agent"

-- | @foaf:Document@ from <http://xmlns.com/foaf/spec/#term_Document>.
foafDocument :: ScopedName
foafDocument :: ScopedName
foafDocument = LName -> ScopedName
toF LName
"Document"

-- | @foaf:Group@ from <http://xmlns.com/foaf/spec/#term_Group>.
foafGroup :: ScopedName
foafGroup :: ScopedName
foafGroup = LName -> ScopedName
toF LName
"Group"

-- | @foaf:Image@ from <http://xmlns.com/foaf/spec/#term_Image>.
foafImage :: ScopedName
foafImage :: ScopedName
foafImage = LName -> ScopedName
toF LName
"Image"

-- | @foaf:LabelProperty@ from <http://xmlns.com/foaf/spec/#term_LabelProperty>.
foafLabelProperty :: ScopedName
foafLabelProperty :: ScopedName
foafLabelProperty = LName -> ScopedName
toF LName
"LabelProperty"

-- | @foaf:OnlineAccount@ from <http://xmlns.com/foaf/spec/#term_OnlineAccount>.
foafOnlineAccount :: ScopedName
foafOnlineAccount :: ScopedName
foafOnlineAccount = LName -> ScopedName
toF LName
"OnlineAccount"

-- | @foaf:OnlineChatAccount@ from <http://xmlns.com/foaf/spec/#term_OnlineChatAccount>.
foafOnlineChatAccount :: ScopedName
foafOnlineChatAccount :: ScopedName
foafOnlineChatAccount = LName -> ScopedName
toF LName
"OnlineChatAccount"

-- | @foaf:OnlineEcommerceAccount@ from <http://xmlns.com/foaf/spec/#term_OnlineEcommerceAccount>.
foafOnlineEcommerceAccount :: ScopedName
foafOnlineEcommerceAccount :: ScopedName
foafOnlineEcommerceAccount = LName -> ScopedName
toF LName
"OnlineEcommerceAccount"

-- | @foaf:OnlineGamingAccount@ from <http://xmlns.com/foaf/spec/#term_OnlineGamingAccount>.
foafOnlineGamingAccount :: ScopedName
foafOnlineGamingAccount :: ScopedName
foafOnlineGamingAccount = LName -> ScopedName
toF LName
"OnlineGamingAccount"

-- | @foaf:Organization@ from <http://xmlns.com/foaf/spec/#term_Organization>.
foafOrganization :: ScopedName
foafOrganization :: ScopedName
foafOrganization = LName -> ScopedName
toF LName
"Organization"

-- | @foaf:Person@ from <http://xmlns.com/foaf/spec/#term_Person>.
foafPerson :: ScopedName
foafPerson :: ScopedName
foafPerson = LName -> ScopedName
toF LName
"Person"

-- | @foaf:PersonalProfileDocument@ from <http://xmlns.com/foaf/spec/#term_PersonalProfileDocument>.
foafPersonalProfileDocument :: ScopedName
foafPersonalProfileDocument :: ScopedName
foafPersonalProfileDocument = LName -> ScopedName
toF LName
"PersonalProfileDocument"

-- | @foaf:Project@ from <http://xmlns.com/foaf/spec/#term_Project>.
foafProject :: ScopedName
foafProject :: ScopedName
foafProject = LName -> ScopedName
toF LName
"Project"

-- Properties

-- | @foaf:account@ from <http://xmlns.com/foaf/spec/#term_account>. 
foafaccount :: ScopedName
foafaccount :: ScopedName
foafaccount = LName -> ScopedName
toF LName
"account"
  
-- | @foaf:accountName@ from <http://xmlns.com/foaf/spec/#term_accountName>. 
foafaccountName :: ScopedName
foafaccountName :: ScopedName
foafaccountName = LName -> ScopedName
toF LName
"accountName"
  
-- | @foaf:accountServiceHomepage@ from <http://xmlns.com/foaf/spec/#term_accountServiceHomepage>. 
foafaccountServiceHomepage :: ScopedName
foafaccountServiceHomepage :: ScopedName
foafaccountServiceHomepage = LName -> ScopedName
toF LName
"accountServiceHomepage"
  
-- | @foaf:age@ from <http://xmlns.com/foaf/spec/#term_age>. 
foafage :: ScopedName
foafage :: ScopedName
foafage = LName -> ScopedName
toF LName
"age"
  
-- | @foaf:aimChatID@ from <http://xmlns.com/foaf/spec/#term_aimChatID>. 
foafaimChatID :: ScopedName
foafaimChatID :: ScopedName
foafaimChatID = LName -> ScopedName
toF LName
"aimChatID"
  
-- | @foaf:based_near@ from <http://xmlns.com/foaf/spec/#term_based_near>. 
foafbased_near :: ScopedName
foafbased_near :: ScopedName
foafbased_near = LName -> ScopedName
toF LName
"based_near"
  
-- | @foaf:birthday@ from <http://xmlns.com/foaf/spec/#term_birthday>. 
foafbirthday :: ScopedName
foafbirthday :: ScopedName
foafbirthday = LName -> ScopedName
toF LName
"birthday"
  
-- | @foaf:currentProject@ from <http://xmlns.com/foaf/spec/#term_currentProject>. 
foafcurrentProject :: ScopedName
foafcurrentProject :: ScopedName
foafcurrentProject = LName -> ScopedName
toF LName
"currentProject"
  
-- | @foaf:depiction@ from <http://xmlns.com/foaf/spec/#term_depiction>. 
foafdepiction :: ScopedName
foafdepiction :: ScopedName
foafdepiction = LName -> ScopedName
toF LName
"depiction"
  
-- | @foaf:depicts@ from <http://xmlns.com/foaf/spec/#term_depicts>. 
foafdepicts :: ScopedName
foafdepicts :: ScopedName
foafdepicts = LName -> ScopedName
toF LName
"depicts"
  
-- | @foaf:dnaChecksum@ from <http://xmlns.com/foaf/spec/#term_dnaChecksum>. 
foafdnaChecksum :: ScopedName
foafdnaChecksum :: ScopedName
foafdnaChecksum = LName -> ScopedName
toF LName
"dnaChecksum"
  
-- | @foaf:familyName@ from <http://xmlns.com/foaf/spec/#term_familyName>. 
foaffamilyName :: ScopedName
foaffamilyName :: ScopedName
foaffamilyName = LName -> ScopedName
toF LName
"familyName"
  
-- | @foaf:family_name@ from <http://xmlns.com/foaf/spec/#term_family_name>. 
foaffamily_name :: ScopedName
foaffamily_name :: ScopedName
foaffamily_name = LName -> ScopedName
toF LName
"family_name"
  
-- | @foaf:firstName@ from <http://xmlns.com/foaf/spec/#term_firstName>. 
foaffirstName :: ScopedName
foaffirstName :: ScopedName
foaffirstName = LName -> ScopedName
toF LName
"firstName"
  
-- | @foaf:focus@ from <http://xmlns.com/foaf/spec/#term_focus>. 
foaffocus :: ScopedName
foaffocus :: ScopedName
foaffocus = LName -> ScopedName
toF LName
"focus"
  
-- | @foaf:fundedBy@ from <http://xmlns.com/foaf/spec/#term_fundedBy>. 
foaffundedBy :: ScopedName
foaffundedBy :: ScopedName
foaffundedBy = LName -> ScopedName
toF LName
"fundedBy"
  
-- | @foaf:geekcode@ from <http://xmlns.com/foaf/spec/#term_geekcode>. 
foafgeekcode :: ScopedName
foafgeekcode :: ScopedName
foafgeekcode = LName -> ScopedName
toF LName
"geekcode"
  
-- | @foaf:gender@ from <http://xmlns.com/foaf/spec/#term_gender>. 
foafgender :: ScopedName
foafgender :: ScopedName
foafgender = LName -> ScopedName
toF LName
"gender"
  
-- | @foaf:givenName@ from <http://xmlns.com/foaf/spec/#term_givenName>. 
foafgivenName :: ScopedName
foafgivenName :: ScopedName
foafgivenName = LName -> ScopedName
toF LName
"givenName"
  
-- | @foaf:givenname@ from <http://xmlns.com/foaf/spec/#term_givenname>. 
foafgivenname :: ScopedName
foafgivenname :: ScopedName
foafgivenname = LName -> ScopedName
toF LName
"givenname"
  
-- | @foaf:holdsAccount@ from <http://xmlns.com/foaf/spec/#term_holdsAccount>. 
foafholdsAccount :: ScopedName
foafholdsAccount :: ScopedName
foafholdsAccount = LName -> ScopedName
toF LName
"holdsAccount"
  
-- | @foaf:homepage@ from <http://xmlns.com/foaf/spec/#term_homepage>. 
foafhomepage :: ScopedName
foafhomepage :: ScopedName
foafhomepage = LName -> ScopedName
toF LName
"homepage"
  
-- | @foaf:icqChatID@ from <http://xmlns.com/foaf/spec/#term_icqChatID>. 
foaficqChatID :: ScopedName
foaficqChatID :: ScopedName
foaficqChatID = LName -> ScopedName
toF LName
"icqChatID"
  
-- | @foaf:img@ from <http://xmlns.com/foaf/spec/#term_img>. 
foafimg :: ScopedName
foafimg :: ScopedName
foafimg = LName -> ScopedName
toF LName
"img"
  
-- | @foaf:interest@ from <http://xmlns.com/foaf/spec/#term_interest>. 
foafinterest :: ScopedName
foafinterest :: ScopedName
foafinterest = LName -> ScopedName
toF LName
"interest"
  
-- | @foaf:isPrimaryTopicOf@ from <http://xmlns.com/foaf/spec/#term_isPrimaryTopicOf>. 
foafisPrimaryTopicOf :: ScopedName
foafisPrimaryTopicOf :: ScopedName
foafisPrimaryTopicOf = LName -> ScopedName
toF LName
"isPrimaryTopicOf"
  
-- | @foaf:jabberID@ from <http://xmlns.com/foaf/spec/#term_jabberID>. 
foafjabberID :: ScopedName
foafjabberID :: ScopedName
foafjabberID = LName -> ScopedName
toF LName
"jabberID"
  
-- | @foaf:knows@ from <http://xmlns.com/foaf/spec/#term_knows>. 
foafknows :: ScopedName
foafknows :: ScopedName
foafknows = LName -> ScopedName
toF LName
"knows"
  
-- | @foaf:lastName@ from <http://xmlns.com/foaf/spec/#term_lastName>. 
foaflastName :: ScopedName
foaflastName :: ScopedName
foaflastName = LName -> ScopedName
toF LName
"lastName"
  
-- | @foaf:logo@ from <http://xmlns.com/foaf/spec/#term_logo>. 
foaflogo :: ScopedName
 = LName -> ScopedName
toF LName
"logo"
  
-- | @foaf:made@ from <http://xmlns.com/foaf/spec/#term_made>. 
foafmade :: ScopedName
foafmade :: ScopedName
foafmade = LName -> ScopedName
toF LName
"made"
  
-- | @foaf:maker@ from <http://xmlns.com/foaf/spec/#term_maker>. 
foafmaker :: ScopedName
foafmaker :: ScopedName
foafmaker = LName -> ScopedName
toF LName
"maker"
  
-- | @foaf:mbox@ from <http://xmlns.com/foaf/spec/#term_mbox>. 
foafmbox :: ScopedName
foafmbox :: ScopedName
foafmbox = LName -> ScopedName
toF LName
"mbox"
  
-- | @foaf:mbox_sha1sum@ from <http://xmlns.com/foaf/spec/#term_mbox_sha1sum>. 
foafmbox_sha1sum :: ScopedName
foafmbox_sha1sum :: ScopedName
foafmbox_sha1sum = LName -> ScopedName
toF LName
"mbox_sha1sum"
  
-- | @foaf:member@ from <http://xmlns.com/foaf/spec/#term_member>. 
foafmember :: ScopedName
foafmember :: ScopedName
foafmember = LName -> ScopedName
toF LName
"member"
  
-- | @foaf:membershipClass@ from <http://xmlns.com/foaf/spec/#term_membershipClass>. 
foafmembershipClass :: ScopedName
foafmembershipClass :: ScopedName
foafmembershipClass = LName -> ScopedName
toF LName
"membershipClass"

-- | @foaf:msnChatID@ from <http://xmlns.com/foaf/spec/#term_msnChatID>.  
foafmsnChatID :: ScopedName
foafmsnChatID :: ScopedName
foafmsnChatID = LName -> ScopedName
toF LName
"msnChatID"

-- | @foaf:myersBriggs@ from <http://xmlns.com/foaf/spec/#term_myersBriggs>. 
foafmyersBriggs :: ScopedName
foafmyersBriggs :: ScopedName
foafmyersBriggs = LName -> ScopedName
toF LName
"myersBriggs"

-- | @foaf:name@ from <http://xmlns.com/foaf/spec/#term_name>. 
foafname :: ScopedName
foafname :: ScopedName
foafname = LName -> ScopedName
toF LName
"name"

-- | @foaf:nick@ from <http://xmlns.com/foaf/spec/#term_nick>. 
foafnick :: ScopedName
foafnick :: ScopedName
foafnick = LName -> ScopedName
toF LName
"nick"

-- | @foaf:openid@ from <http://xmlns.com/foaf/spec/#term_openid>. 
foafopenid :: ScopedName
foafopenid :: ScopedName
foafopenid = LName -> ScopedName
toF LName
"openid"
 
-- | @foaf:page@ from <http://xmlns.com/foaf/spec/#term_page>. 
foafpage :: ScopedName
foafpage :: ScopedName
foafpage = LName -> ScopedName
toF LName
"page"
  
-- | @foaf:pastProject@ from <http://xmlns.com/foaf/spec/#term_pastProject>. 
foafpastProject :: ScopedName
foafpastProject :: ScopedName
foafpastProject = LName -> ScopedName
toF LName
"pastProject"
  
-- | @foaf:phone@ from <http://xmlns.com/foaf/spec/#term_phone>. 
foafphone :: ScopedName
foafphone :: ScopedName
foafphone = LName -> ScopedName
toF LName
"phone"
  
-- | @foaf:plan@ from <http://xmlns.com/foaf/spec/#term_plan>. 
foafplan :: ScopedName
foafplan :: ScopedName
foafplan = LName -> ScopedName
toF LName
"plan"

-- | @foaf:primaryTopic@ from <http://xmlns.com/foaf/spec/#term_primaryTopic>.  
foafprimaryTopic :: ScopedName
foafprimaryTopic :: ScopedName
foafprimaryTopic = LName -> ScopedName
toF LName
"primaryTopic"

-- | @foaf:publications@ from <http://xmlns.com/foaf/spec/#term_publications>. 
foafpublications :: ScopedName
foafpublications :: ScopedName
foafpublications = LName -> ScopedName
toF LName
"publications"

-- | @foaf:schoolHomepage@ from <http://xmlns.com/foaf/spec/#term_schoolHomepage>. 
foafschoolHomepage :: ScopedName
foafschoolHomepage :: ScopedName
foafschoolHomepage = LName -> ScopedName
toF LName
"schoolHomepage"

-- | @foaf:sha1@ from <http://xmlns.com/foaf/spec/#term_sha1>. 
foafsha1 :: ScopedName
foafsha1 :: ScopedName
foafsha1 = LName -> ScopedName
toF LName
"sha1"

-- | @foaf:skypeID@ from <http://xmlns.com/foaf/spec/#term_skypeID>. 
foafskypeID :: ScopedName
foafskypeID :: ScopedName
foafskypeID = LName -> ScopedName
toF LName
"skypeID"
 
-- | @foaf:status@ from <http://xmlns.com/foaf/spec/#term_status>. 
foafstatus :: ScopedName
foafstatus :: ScopedName
foafstatus = LName -> ScopedName
toF LName
"status"
  
-- | @foaf:surname@ from <http://xmlns.com/foaf/spec/#term_surname>. 
foafsurname :: ScopedName
foafsurname :: ScopedName
foafsurname = LName -> ScopedName
toF LName
"surname"
  
-- | @foaf:theme@ from <http://xmlns.com/foaf/spec/#term_theme>. 
foaftheme :: ScopedName
foaftheme :: ScopedName
foaftheme = LName -> ScopedName
toF LName
"theme"
  
-- | @foaf:thumbnail@ from <http://xmlns.com/foaf/spec/#term_thumbnail>. 
foafthumbnail :: ScopedName
foafthumbnail :: ScopedName
foafthumbnail = LName -> ScopedName
toF LName
"thumbnail"

-- | @foaf:tipjar@ from <http://xmlns.com/foaf/spec/#term_tipjar>.  
foaftipjar :: ScopedName
foaftipjar :: ScopedName
foaftipjar = LName -> ScopedName
toF LName
"tipjar"

-- | @foaf:title@ from <http://xmlns.com/foaf/spec/#term_title>. 
foaftitle :: ScopedName
foaftitle :: ScopedName
foaftitle = LName -> ScopedName
toF LName
"title"

-- | @foaf:topic@ from <http://xmlns.com/foaf/spec/#term_topic>. 
foaftopic :: ScopedName
foaftopic :: ScopedName
foaftopic = LName -> ScopedName
toF LName
"topic"
 
-- | @foaf:topic_interest@ from <http://xmlns.com/foaf/spec/#term_topic_interest>. 
foaftopic_interest :: ScopedName
foaftopic_interest :: ScopedName
foaftopic_interest = LName -> ScopedName
toF LName
"topic_interest"
  
-- | @foaf:weblog@ from <http://xmlns.com/foaf/spec/#term_weblog>. 
foafweblog :: ScopedName
foafweblog :: ScopedName
foafweblog = LName -> ScopedName
toF LName
"weblog"
  
-- | @foaf:workInfoHomepage@ from <http://xmlns.com/foaf/spec/#term_workInfoHomepage>. 
foafworkInfoHomepage :: ScopedName
foafworkInfoHomepage :: ScopedName
foafworkInfoHomepage = LName -> ScopedName
toF LName
"workInfoHomepage"
  
-- | @foaf:workplaceHomepage@ from <http://xmlns.com/foaf/spec/#term_workplaceHomepage>. 
foafworkplaceHomepage :: ScopedName
foafworkplaceHomepage :: ScopedName
foafworkplaceHomepage = LName -> ScopedName
toF LName
"workplaceHomepage"
  
-- | @foaf:yahooChatID@ from <http://xmlns.com/foaf/spec/#term_yahooChatID>. 
foafyahooChatID :: ScopedName
foafyahooChatID :: ScopedName
foafyahooChatID = LName -> ScopedName
toF LName
"yahooChatID"
  
--------------------------------------------------------------------------------
--
--  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
--
--------------------------------------------------------------------------------