{-# LANGUAGE OverloadedStrings #-}

--------------------------------------------------------------------------------
--  See end of this file for licence information.
--------------------------------------------------------------------------------
-- |
--  Module      :  Swish.RDF.Vocabulary.DublinCore
--  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 Dublin Core
--  vocabularies (<http://dublincore.org/documents/dcmi-terms/>).
--
--------------------------------------------------------------------------------

module Swish.RDF.Vocabulary.DublinCore
    ( 
      namespaceDCTERMS
    , namespaceDCELEM
    , namespaceDCAM
    , namespaceDCTYPE
        
    -- * Classes
    -- | See the \"Classes\" section at <http://dublincore.org/documents/dcmi-terms/#H6>.
    , dctAgent
    , dctAgentClass 
    , dctBibliographicResource 
    , dctFileFormat 
    , dctFrequency 
    , dctJurisdiction 
    , dctLicenseDocument 
    , dctLinguisticSystem 
    , dctLocation 
    , dctLocationPeriodOrJurisdiction 
    , dctMediaType 
    , dctMediaTypeOrExtent 
    , dctMethodOfAccrual 
    , dctMethodOfInstruction 
    , dctPeriodOfTime 
    , dctPhysicalMedium 
    , dctPhysicalResource 
    , dctPolicy 
    , dctProvenanceStatement 
    , dctRightsStatement 
    , dctSizeOrDuration 
    , dctStandard
      
    -- * Properties  
    -- | See the \"Properties\" section at <http://dublincore.org/documents/dcmi-terms/#H2>.
    , dctabstract 
    , dctaccessRights 
    , dctaccrualMethod 
    , dctaccrualPeriodicity 
    , dctaccrualPolicy 
    , dctalternative 
    , dctaudience 
    , dctavailable 
    , dctbibliographicCitation 
    , dctconformsTo 
    , dctcontributor 
    , dctcoverage 
    , dctcreated 
    , dctcreator 
    , dctdate 
    , dctdateAccepted 
    , dctdateCopyrighted 
    , dctdateSubmitted 
    , dctdescription 
    , dcteducationLevel 
    , dctextent 
    , dctformat 
    , dcthasFormat 
    , dcthasPart 
    , dcthasVersion 
    , dctidentifier 
    , dctinstructionalMethod 
    , dctisFormatOf 
    , dctisPartOf 
    , dctisReferencedBy 
    , dctisReplacedBy 
    , dctisRequiredBy 
    , dctissued 
    , dctisVersionOf 
    , dctlanguage 
    , dctlicense 
    , dctmediator 
    , dctmedium 
    , dctmodified 
    , dctprovenance 
    , dctpublisher 
    , dctreferences 
    , dctrelation 
    , dctreplaces 
    , dctrequires 
    , dctrights 
    , dctrightsHolder 
    , dctsource 
    , dctspatial 
    , dctsubject 
    , dcttableOfContents 
    , dcttemporal 
    , dcttitle 
    , dcttype 
    , dctvalid
      
    -- * Legacy Properties 
    --  
    -- | The following properties are from the legacy /elements/ vocabulary 
    -- (@http:\/\/purl.org\/dc\/elements\/1.1\/contributor\/@). See
    -- <http://dublincore.org/documents/dcmi-terms/#H3>.
      
    , dcelemcontributor
    , dcelemcoverage
    , dcelemcreator
    , dcelemdate
    , dcelemdescription
    , dcelemformat
    , dcelemidentifier
    , dcelemlanguage
    , dcelempublisher
    , dcelemrelation
    , dcelemrights
    , dcelemsource
    , dcelemsubject
    , dcelemtitle
    , dcelemtype
      
    -- * Encoding
    -- | See the \"Vocabulary Encoding Schemes\" section at <http://dublincore.org/documents/dcmi-terms/#H4>.
      
    , dctLCSH
    , dctMESH
    , dctDDC
    , dctLCC
    , dctUDC
    , dctDCMIType
    , dctIMT
    , dctTGN
    , dctNLM

    -- * Datatypes
    -- | See the \"Syntax Encoding Schemes\" section at <http://dublincore.org/documents/dcmi-terms/#H5>.

    , dctBox
    , dctISO3166
    , dctISO639_2
    , dctISO639_3
    , dctPeriod
    , dctPoint
    , dctRFC1766
    , dctRFC3066
    , dctRFC4646
    , dctRFC5646
    , dctURI
    , dctW3CDTF
      
    -- * Types
    -- | See the \"DCMI Type Vocabulary\" section at <http://dublincore.org/documents/dcmi-terms/#H7>.
    
    , dctypeCollection
    , dctypeDataset
    , dctypeEvent
    , dctypeImage
    , dctypeInteractiveResource
    , dctypeService
    , dctypeSoftware
    , dctypeSound
    , dctypeText
    , dctypePhysicalObject
    , dctypeStillImage
    , dctypeMovingImage
      
    -- * DCMI Abstract Model   
    --
    -- | Terms from the DCMI Abstract Model (<http://dublincore.org/documents/dcmi-terms/#H8>).          

    , dcammemberOf
    , dcamVocabularyEncodingScheme
      
    ) where

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

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

import qualified Data.Text as T

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

toNS :: T.Text -> String -> Namespace
toNS :: Text -> String -> Namespace
toNS Text
p = Maybe Text -> URI -> Namespace
makeNamespace (forall a. a -> Maybe a
Just Text
p) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"Internal error processing DC URI") forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Maybe URI
parseURI

-- | Maps @dcterms@ to <http://purl.org/dc/terms/>.
namespaceDCTERMS :: Namespace
namespaceDCTERMS :: Namespace
namespaceDCTERMS = Text -> String -> Namespace
toNS Text
"dcterms" String
"http://purl.org/dc/terms/"

-- | Maps @dcelem@ to the legacy namespace <http://purl.org/dc/elements/1.1/>.
namespaceDCELEM :: Namespace
namespaceDCELEM :: Namespace
namespaceDCELEM = Text -> String -> Namespace
toNS Text
"dcelem" String
"http://purl.org/dc/elements/1.1/"

-- | Maps @dcam@ to <http://purl.org/dc/dcam/>.
namespaceDCAM :: Namespace
namespaceDCAM :: Namespace
namespaceDCAM = Text -> String -> Namespace
toNS Text
"dcam" String
"http://purl.org/dc/dcam/"

-- | Maps @dctype@ to <http://purl.org/dc/dcmitype/>.
namespaceDCTYPE :: Namespace
namespaceDCTYPE :: Namespace
namespaceDCTYPE = Text -> String -> Namespace
toNS Text
"dctype" String
"http://purl.org/dc/dcmitype/"

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

toDCT, toDCE, toDCAM, toDCTYPE :: LName -> ScopedName
toDCT :: LName -> ScopedName
toDCT = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceDCTERMS
toDCE :: LName -> ScopedName
toDCE = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceDCELEM
toDCAM :: LName -> ScopedName
toDCAM = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceDCAM
toDCTYPE :: LName -> ScopedName
toDCTYPE = Namespace -> LName -> ScopedName
makeNSScopedName Namespace
namespaceDCTYPE

-- Classes

-- | @dcterms:Agent@ from <http://dublincore.org/documents/dcmi-terms/#classes-Agent>.
dctAgent :: ScopedName
dctAgent :: ScopedName
dctAgent = LName -> ScopedName
toDCT LName
"Agent"

-- | @dcterms:AgentClass@ from <http://dublincore.org/documents/dcmi-terms/#classes-AgentClass>.
dctAgentClass :: ScopedName
dctAgentClass :: ScopedName
dctAgentClass = LName -> ScopedName
toDCT LName
"AgentClass"

-- | @dcterms:BibliographicResource@ from <http://dublincore.org/documents/dcmi-terms/#classes-BibliographicResource>.
dctBibliographicResource :: ScopedName
dctBibliographicResource :: ScopedName
dctBibliographicResource = LName -> ScopedName
toDCT LName
"BibliographicResource"

-- | @dcterms:FileFormat@ from <http://dublincore.org/documents/dcmi-terms/#classes-FileFormat>.
dctFileFormat :: ScopedName
dctFileFormat :: ScopedName
dctFileFormat = LName -> ScopedName
toDCT LName
"FileFormat"

-- | @dcterms:Frequency@ from <http://dublincore.org/documents/dcmi-terms/#classes-Frequency>.
dctFrequency :: ScopedName
dctFrequency :: ScopedName
dctFrequency = LName -> ScopedName
toDCT LName
"Frequency"

-- | @dcterms:Jurisdiction@ from <http://dublincore.org/documents/dcmi-terms/#classes-Jurisdiction>.
dctJurisdiction :: ScopedName
dctJurisdiction :: ScopedName
dctJurisdiction = LName -> ScopedName
toDCT LName
"Jurisdiction"

-- | @dcterms:LicenseDocument@ from <http://dublincore.org/documents/dcmi-terms/#classes-LicenseDocument>.
dctLicenseDocument :: ScopedName
dctLicenseDocument :: ScopedName
dctLicenseDocument = LName -> ScopedName
toDCT LName
"LicenseDocument"

-- | @dcterms:LinguisticSystem@ from <http://dublincore.org/documents/dcmi-terms/#classes-LinguisticSystem>.
dctLinguisticSystem :: ScopedName
dctLinguisticSystem :: ScopedName
dctLinguisticSystem = LName -> ScopedName
toDCT LName
"LinguisticSystem"

-- | @dcterms:Location@ from <http://dublincore.org/documents/dcmi-terms/#classes-Location>.
dctLocation :: ScopedName
dctLocation :: ScopedName
dctLocation = LName -> ScopedName
toDCT LName
"Location"

-- | @dcterms:LocationPeriodOrJurisdiction@ from <http://dublincore.org/documents/dcmi-terms/#classes-LocationPeriodOrJurisdiction>.
dctLocationPeriodOrJurisdiction :: ScopedName
dctLocationPeriodOrJurisdiction :: ScopedName
dctLocationPeriodOrJurisdiction = LName -> ScopedName
toDCT LName
"LocationPeriodOrJurisdiction"

-- | @dcterms:MediaType@ from <http://dublincore.org/documents/dcmi-terms/#classes-MediaType>.
dctMediaType :: ScopedName
dctMediaType :: ScopedName
dctMediaType = LName -> ScopedName
toDCT LName
"MediaType"

-- | @dcterms:MediaTypeOrExtent@ from <http://dublincore.org/documents/dcmi-terms/#classes-MediaTypeOrExtent>.
dctMediaTypeOrExtent :: ScopedName
dctMediaTypeOrExtent :: ScopedName
dctMediaTypeOrExtent = LName -> ScopedName
toDCT LName
"MediaTypeOrExtent"

-- | @dcterms:MethodOfAccrual@ from <http://dublincore.org/documents/dcmi-terms/#classes-MethodOfAccrual>.
dctMethodOfAccrual :: ScopedName
dctMethodOfAccrual :: ScopedName
dctMethodOfAccrual = LName -> ScopedName
toDCT LName
"MethodOfAccrual"

-- | @dcterms:MethodOfInstruction@ from <http://dublincore.org/documents/dcmi-terms/#classes-MethodOfInstruction>.
dctMethodOfInstruction :: ScopedName
dctMethodOfInstruction :: ScopedName
dctMethodOfInstruction = LName -> ScopedName
toDCT LName
"MethodOfInstruction"

-- | @dcterms:PeriodOfTime@ from <http://dublincore.org/documents/dcmi-terms/#classes-PeriodOfTime>.
dctPeriodOfTime :: ScopedName
dctPeriodOfTime :: ScopedName
dctPeriodOfTime = LName -> ScopedName
toDCT LName
"PeriodOfTime"

-- | @dcterms:PhysicalMedium@ from <http://dublincore.org/documents/dcmi-terms/#classes-PhysicalMedium>.
dctPhysicalMedium :: ScopedName
dctPhysicalMedium :: ScopedName
dctPhysicalMedium = LName -> ScopedName
toDCT LName
"PhysicalMedium"

-- | @dcterms:PhysicalResource@ from <http://dublincore.org/documents/dcmi-terms/#classes-PhysicalResource>.
dctPhysicalResource :: ScopedName
dctPhysicalResource :: ScopedName
dctPhysicalResource = LName -> ScopedName
toDCT LName
"PhysicalResource"

-- | @dcterms:Policy@ from <http://dublincore.org/documents/dcmi-terms/#classes-Policy>.
dctPolicy :: ScopedName
dctPolicy :: ScopedName
dctPolicy = LName -> ScopedName
toDCT LName
"Policy"

-- | @dcterms:ProvenanceStatement@ from <http://dublincore.org/documents/dcmi-terms/#classes-ProvenanceStatement>.
dctProvenanceStatement :: ScopedName
dctProvenanceStatement :: ScopedName
dctProvenanceStatement = LName -> ScopedName
toDCT LName
"ProvenanceStatement"

-- | @dcterms:RightsStatement@ from <http://dublincore.org/documents/dcmi-terms/#classes-RightsStatement>.
dctRightsStatement :: ScopedName
dctRightsStatement :: ScopedName
dctRightsStatement = LName -> ScopedName
toDCT LName
"RightsStatement"

-- | @dcterms:SizeOrDuration@ from <http://dublincore.org/documents/dcmi-terms/#classes-SizeOrDuration>.
dctSizeOrDuration :: ScopedName
dctSizeOrDuration :: ScopedName
dctSizeOrDuration = LName -> ScopedName
toDCT LName
"SizeOrDuration"

-- | @dcterms:Standard@ from <http://dublincore.org/documents/dcmi-terms/#classes-Standard>.
dctStandard :: ScopedName
dctStandard :: ScopedName
dctStandard = LName -> ScopedName
toDCT LName
"Standard"

-- Properties

-- | @dcterms:abstract@ from <http://dublincore.org/documents/dcmi-terms/#terms-abstract>. 
dctabstract :: ScopedName
dctabstract :: ScopedName
dctabstract = LName -> ScopedName
toDCT LName
"abstract"

-- | @dcterms:accessRights@ from <http://dublincore.org/documents/dcmi-terms/#terms-accessRights>. 
dctaccessRights :: ScopedName
dctaccessRights :: ScopedName
dctaccessRights = LName -> ScopedName
toDCT LName
"accessRights"

-- | @dcterms:accrualMethod@ from <http://dublincore.org/documents/dcmi-terms/#terms-accrualMethod>. 
dctaccrualMethod :: ScopedName
dctaccrualMethod :: ScopedName
dctaccrualMethod = LName -> ScopedName
toDCT LName
"accrualMethod"

-- | @dcterms:accrualPeriodicity@ from <http://dublincore.org/documents/dcmi-terms/#terms-accrualPeriodicity>. 
dctaccrualPeriodicity :: ScopedName
dctaccrualPeriodicity :: ScopedName
dctaccrualPeriodicity = LName -> ScopedName
toDCT LName
"accrualPeriodicity"

-- | @dcterms:accrualPolicy@ from <http://dublincore.org/documents/dcmi-terms/#terms-accrualPolicy>. 
dctaccrualPolicy :: ScopedName
dctaccrualPolicy :: ScopedName
dctaccrualPolicy = LName -> ScopedName
toDCT LName
"accrualPolicy"

-- | @dcterms:alternative@ from <http://dublincore.org/documents/dcmi-terms/#terms-alternative>. 
dctalternative :: ScopedName
dctalternative :: ScopedName
dctalternative = LName -> ScopedName
toDCT LName
"alternative"

-- | @dcterms:audience@ from <http://dublincore.org/documents/dcmi-terms/#terms-audience>. 
dctaudience :: ScopedName
dctaudience :: ScopedName
dctaudience = LName -> ScopedName
toDCT LName
"audience"

-- | @dcterms:available@ from <http://dublincore.org/documents/dcmi-terms/#terms-available>. 
dctavailable :: ScopedName
dctavailable :: ScopedName
dctavailable = LName -> ScopedName
toDCT LName
"available"

-- | @dcterms:bibliographicCitation@ from <http://dublincore.org/documents/dcmi-terms/#terms-bibliographicCitation>. 
dctbibliographicCitation :: ScopedName
dctbibliographicCitation :: ScopedName
dctbibliographicCitation = LName -> ScopedName
toDCT LName
"bibliographicCitation"

-- | @dcterms:conformsTo@ from <http://dublincore.org/documents/dcmi-terms/#terms-conformsTo>. 
dctconformsTo :: ScopedName
dctconformsTo :: ScopedName
dctconformsTo = LName -> ScopedName
toDCT LName
"conformsTo"

-- | @dcterms:contributor@ from <http://dublincore.org/documents/dcmi-terms/#terms-contributor>. 
dctcontributor :: ScopedName
dctcontributor :: ScopedName
dctcontributor = LName -> ScopedName
toDCT LName
"contributor"

-- | @dcterms:coverage@ from <http://dublincore.org/documents/dcmi-terms/#terms-coverage>. 
dctcoverage :: ScopedName
dctcoverage :: ScopedName
dctcoverage = LName -> ScopedName
toDCT LName
"coverage"

-- | @dcterms:created@ from <http://dublincore.org/documents/dcmi-terms/#terms-created>. 
dctcreated :: ScopedName
dctcreated :: ScopedName
dctcreated = LName -> ScopedName
toDCT LName
"created"

-- | @dcterms:creator@ from <http://dublincore.org/documents/dcmi-terms/#terms-creator>. 
dctcreator :: ScopedName
dctcreator :: ScopedName
dctcreator = LName -> ScopedName
toDCT LName
"creator"

-- | @dcterms:date@ from <http://dublincore.org/documents/dcmi-terms/#terms-date>. 
dctdate :: ScopedName
dctdate :: ScopedName
dctdate = LName -> ScopedName
toDCT LName
"date"

-- | @dcterms:dateAccepted@ from <http://dublincore.org/documents/dcmi-terms/#terms-dateAccepted>. 
dctdateAccepted :: ScopedName
dctdateAccepted :: ScopedName
dctdateAccepted = LName -> ScopedName
toDCT LName
"dateAccepted"

-- | @dcterms:dateCopyrighted@ from <http://dublincore.org/documents/dcmi-terms/#terms-dateCopyrighted>. 
dctdateCopyrighted :: ScopedName
dctdateCopyrighted :: ScopedName
dctdateCopyrighted = LName -> ScopedName
toDCT LName
"dateCopyrighted"

-- | @dcterms:dateSubmitted@ from <http://dublincore.org/documents/dcmi-terms/#terms-dateSubmitted>. 
dctdateSubmitted :: ScopedName
dctdateSubmitted :: ScopedName
dctdateSubmitted = LName -> ScopedName
toDCT LName
"dateSubmitted"

-- | @dcterms:description@ from <http://dublincore.org/documents/dcmi-terms/#terms-description>. 
dctdescription :: ScopedName
dctdescription :: ScopedName
dctdescription = LName -> ScopedName
toDCT LName
"description"

-- | @dcterms:educationLevel@ from <http://dublincore.org/documents/dcmi-terms/#terms-educationLevel>. 
dcteducationLevel :: ScopedName
dcteducationLevel :: ScopedName
dcteducationLevel = LName -> ScopedName
toDCT LName
"educationLevel"

-- | @dcterms:extent@ from <http://dublincore.org/documents/dcmi-terms/#terms-extent>. 
dctextent :: ScopedName
dctextent :: ScopedName
dctextent = LName -> ScopedName
toDCT LName
"extent"

-- | @dcterms:format@ from <http://dublincore.org/documents/dcmi-terms/#terms-format>. 
dctformat :: ScopedName
dctformat :: ScopedName
dctformat = LName -> ScopedName
toDCT LName
"format"

-- | @dcterms:hasFormat@ from <http://dublincore.org/documents/dcmi-terms/#terms-hasFormat>. 
dcthasFormat :: ScopedName
dcthasFormat :: ScopedName
dcthasFormat = LName -> ScopedName
toDCT LName
"hasFormat"

-- | @dcterms:hasPart@ from <http://dublincore.org/documents/dcmi-terms/#terms-hasPart>. 
dcthasPart :: ScopedName
dcthasPart :: ScopedName
dcthasPart = LName -> ScopedName
toDCT LName
"hasPart"

-- | @dcterms:hasVersion@ from <http://dublincore.org/documents/dcmi-terms/#terms-hasVersion>. 
dcthasVersion :: ScopedName
dcthasVersion :: ScopedName
dcthasVersion = LName -> ScopedName
toDCT LName
"hasVersion"

-- | @dcterms:identifier@ from <http://dublincore.org/documents/dcmi-terms/#terms-identifier>. 
dctidentifier :: ScopedName
dctidentifier :: ScopedName
dctidentifier = LName -> ScopedName
toDCT LName
"identifier"

-- | @dcterms:instructionalMethod@ from <http://dublincore.org/documents/dcmi-terms/#terms-instructionalMethod>. 
dctinstructionalMethod :: ScopedName
dctinstructionalMethod :: ScopedName
dctinstructionalMethod = LName -> ScopedName
toDCT LName
"instructionalMethod"

-- | @dcterms:isFormatOf@ from <http://dublincore.org/documents/dcmi-terms/#terms-isFormatOf>. 
dctisFormatOf :: ScopedName
dctisFormatOf :: ScopedName
dctisFormatOf = LName -> ScopedName
toDCT LName
"isFormatOf"

-- | @dcterms:isPartOf@ from <http://dublincore.org/documents/dcmi-terms/#terms-isPartOf>. 
dctisPartOf :: ScopedName
dctisPartOf :: ScopedName
dctisPartOf = LName -> ScopedName
toDCT LName
"isPartOf"

-- | @dcterms:isReferencedBy@ from <http://dublincore.org/documents/dcmi-terms/#terms-isReferencedBy>. 
dctisReferencedBy :: ScopedName
dctisReferencedBy :: ScopedName
dctisReferencedBy = LName -> ScopedName
toDCT LName
"isReferencedBy"

-- | @dcterms:isReplacedBy@ from <http://dublincore.org/documents/dcmi-terms/#terms-isReplacedBy>. 
dctisReplacedBy :: ScopedName
dctisReplacedBy :: ScopedName
dctisReplacedBy = LName -> ScopedName
toDCT LName
"isReplacedBy"

-- | @dcterms:isRequiredBy@ from <http://dublincore.org/documents/dcmi-terms/#terms-isRequiredBy>. 
dctisRequiredBy :: ScopedName
dctisRequiredBy :: ScopedName
dctisRequiredBy = LName -> ScopedName
toDCT LName
"isRequiredBy"

-- | @dcterms:issued@ from <http://dublincore.org/documents/dcmi-terms/#terms-issued>. 
dctissued :: ScopedName
dctissued :: ScopedName
dctissued = LName -> ScopedName
toDCT LName
"issued"

-- | @dcterms:isVersionOf@ from <http://dublincore.org/documents/dcmi-terms/#terms-isVersionOf>. 
dctisVersionOf :: ScopedName
dctisVersionOf :: ScopedName
dctisVersionOf = LName -> ScopedName
toDCT LName
"isVersionOf"

-- | @dcterms:language@ from <http://dublincore.org/documents/dcmi-terms/#terms-language>. 
dctlanguage :: ScopedName
dctlanguage :: ScopedName
dctlanguage = LName -> ScopedName
toDCT LName
"language"

-- | @dcterms:license@ from <http://dublincore.org/documents/dcmi-terms/#terms-license>. 
dctlicense :: ScopedName
dctlicense :: ScopedName
dctlicense = LName -> ScopedName
toDCT LName
"license"

-- | @dcterms:mediator@ from <http://dublincore.org/documents/dcmi-terms/#terms-mediator>. 
dctmediator :: ScopedName
dctmediator :: ScopedName
dctmediator = LName -> ScopedName
toDCT LName
"mediator"

-- | @dcterms:medium@ from <http://dublincore.org/documents/dcmi-terms/#terms-medium>. 
dctmedium :: ScopedName
dctmedium :: ScopedName
dctmedium = LName -> ScopedName
toDCT LName
"medium"

-- | @dcterms:modified@ from <http://dublincore.org/documents/dcmi-terms/#terms-modified>. 
dctmodified :: ScopedName
dctmodified :: ScopedName
dctmodified = LName -> ScopedName
toDCT LName
"modified"

-- | @dcterms:provenance@ from <http://dublincore.org/documents/dcmi-terms/#terms-provenance>. 
dctprovenance :: ScopedName
dctprovenance :: ScopedName
dctprovenance = LName -> ScopedName
toDCT LName
"provenance"

-- | @dcterms:publisher@ from <http://dublincore.org/documents/dcmi-terms/#terms-publisher>. 
dctpublisher :: ScopedName
dctpublisher :: ScopedName
dctpublisher = LName -> ScopedName
toDCT LName
"publisher"

-- | @dcterms:references@ from <http://dublincore.org/documents/dcmi-terms/#terms-references>. 
dctreferences :: ScopedName
dctreferences :: ScopedName
dctreferences = LName -> ScopedName
toDCT LName
"references"

-- | @dcterms:relation@ from <http://dublincore.org/documents/dcmi-terms/#terms-relation>. 
dctrelation :: ScopedName
dctrelation :: ScopedName
dctrelation = LName -> ScopedName
toDCT LName
"relation"

-- | @dcterms:replaces@ from <http://dublincore.org/documents/dcmi-terms/#terms-replaces>. 
dctreplaces :: ScopedName
dctreplaces :: ScopedName
dctreplaces = LName -> ScopedName
toDCT LName
"replaces"

-- | @dcterms:requires@ from <http://dublincore.org/documents/dcmi-terms/#terms-requires>. 
dctrequires :: ScopedName
dctrequires :: ScopedName
dctrequires = LName -> ScopedName
toDCT LName
"requires"

-- | @dcterms:rights@ from <http://dublincore.org/documents/dcmi-terms/#terms-rights>. 
dctrights :: ScopedName
dctrights :: ScopedName
dctrights = LName -> ScopedName
toDCT LName
"rights"

-- | @dcterms:rightsHolder@ from <http://dublincore.org/documents/dcmi-terms/#terms-rightsHolder>. 
dctrightsHolder :: ScopedName
dctrightsHolder :: ScopedName
dctrightsHolder = LName -> ScopedName
toDCT LName
"rightsHolder"

-- | @dcterms:source@ from <http://dublincore.org/documents/dcmi-terms/#terms-source>. 
dctsource :: ScopedName
dctsource :: ScopedName
dctsource = LName -> ScopedName
toDCT LName
"source"

-- | @dcterms:spatial@ from <http://dublincore.org/documents/dcmi-terms/#terms-spatial>. 
dctspatial :: ScopedName
dctspatial :: ScopedName
dctspatial = LName -> ScopedName
toDCT LName
"spatial"

-- | @dcterms:subject@ from <http://dublincore.org/documents/dcmi-terms/#terms-subject>. 
dctsubject :: ScopedName
dctsubject :: ScopedName
dctsubject = LName -> ScopedName
toDCT LName
"subject"

-- | @dcterms:tableOfContents@ from <http://dublincore.org/documents/dcmi-terms/#terms-tableOfContents>. 
dcttableOfContents :: ScopedName
dcttableOfContents :: ScopedName
dcttableOfContents = LName -> ScopedName
toDCT LName
"tableOfContents"

-- | @dcterms:temporal@ from <http://dublincore.org/documents/dcmi-terms/#terms-temporal>. 
dcttemporal :: ScopedName
dcttemporal :: ScopedName
dcttemporal = LName -> ScopedName
toDCT LName
"temporal"

-- | @dcterms:title@ from <http://dublincore.org/documents/dcmi-terms/#terms-title>. 
dcttitle :: ScopedName
dcttitle :: ScopedName
dcttitle = LName -> ScopedName
toDCT LName
"title"

-- | @dcterms:type@ from <http://dublincore.org/documents/dcmi-terms/#terms-type>. 
dcttype :: ScopedName
dcttype :: ScopedName
dcttype = LName -> ScopedName
toDCT LName
"type"

-- | @dcterms:valid@ from <http://dublincore.org/documents/dcmi-terms/#terms-valid>. 
dctvalid :: ScopedName
dctvalid :: ScopedName
dctvalid = LName -> ScopedName
toDCT LName
"valid"

-- legacy elements vocabulary: properties

-- | @dcelem:contributor@ from <http://dublincore.org/documents/dcmi-terms/#elements-contributor>.
dcelemcontributor :: ScopedName
dcelemcontributor :: ScopedName
dcelemcontributor = LName -> ScopedName
toDCE LName
"contributor"

-- | @dcelem:coverage@ from <http://dublincore.org/documents/dcmi-terms/#elements-coverage>.
dcelemcoverage :: ScopedName
dcelemcoverage :: ScopedName
dcelemcoverage = LName -> ScopedName
toDCE LName
"coverage"

-- | @dcelem:creator@ from <http://dublincore.org/documents/dcmi-terms/#elements-creator>.
dcelemcreator :: ScopedName
dcelemcreator :: ScopedName
dcelemcreator = LName -> ScopedName
toDCE LName
"creator"

-- | @dcelem:date@ from <http://dublincore.org/documents/dcmi-terms/#elements-date>.
dcelemdate :: ScopedName
dcelemdate :: ScopedName
dcelemdate = LName -> ScopedName
toDCE LName
"date"

-- | @dcelem:description@ from <http://dublincore.org/documents/dcmi-terms/#elements-description>.
dcelemdescription :: ScopedName
dcelemdescription :: ScopedName
dcelemdescription = LName -> ScopedName
toDCE LName
"description"

-- | @dcelem:format@ from <http://dublincore.org/documents/dcmi-terms/#elements-format>.
dcelemformat :: ScopedName
dcelemformat :: ScopedName
dcelemformat = LName -> ScopedName
toDCE LName
"format"

-- | @dcelem:identifier@ from <http://dublincore.org/documents/dcmi-terms/#elements-identifier>.
dcelemidentifier :: ScopedName
dcelemidentifier :: ScopedName
dcelemidentifier = LName -> ScopedName
toDCE LName
"identifier"

-- | @dcelem:language@ from <http://dublincore.org/documents/dcmi-terms/#elements-language>.
dcelemlanguage :: ScopedName
dcelemlanguage :: ScopedName
dcelemlanguage = LName -> ScopedName
toDCE LName
"language"

-- | @dcelem:publisher@ from <http://dublincore.org/documents/dcmi-terms/#elements-publisher>.
dcelempublisher :: ScopedName
dcelempublisher :: ScopedName
dcelempublisher = LName -> ScopedName
toDCE LName
"publisher"

-- | @dcelem:relation@ from <http://dublincore.org/documents/dcmi-terms/#elements-relation>.
dcelemrelation :: ScopedName
dcelemrelation :: ScopedName
dcelemrelation = LName -> ScopedName
toDCE LName
"relation"

-- | @dcelem:rights@ from <http://dublincore.org/documents/dcmi-terms/#elements-rights>.
dcelemrights :: ScopedName
dcelemrights :: ScopedName
dcelemrights = LName -> ScopedName
toDCE LName
"rights"

-- | @dcelem:source@ from <http://dublincore.org/documents/dcmi-terms/#elements-source>.
dcelemsource :: ScopedName
dcelemsource :: ScopedName
dcelemsource = LName -> ScopedName
toDCE LName
"source"

-- | @dcelem:subject@ from <http://dublincore.org/documents/dcmi-terms/#elements-subject>.
dcelemsubject :: ScopedName
dcelemsubject :: ScopedName
dcelemsubject = LName -> ScopedName
toDCE LName
"subject"

-- | @dcelem:title@ from <http://dublincore.org/documents/dcmi-terms/#elements-title>.
dcelemtitle :: ScopedName
dcelemtitle :: ScopedName
dcelemtitle = LName -> ScopedName
toDCE LName
"title"

-- | @dcelem:type@ from <http://dublincore.org/documents/dcmi-terms/#elements-type>.
dcelemtype :: ScopedName
dcelemtype :: ScopedName
dcelemtype = LName -> ScopedName
toDCE LName
"type"

-- Datatypes

-- | @dcterms:Box@ from <http://dublincore.org/documents/dcmi-terms/#ses-Box>.
dctBox :: ScopedName
dctBox :: ScopedName
dctBox = LName -> ScopedName
toDCT LName
"Box"

-- | @dcterms:ISO3166@ from <http://dublincore.org/documents/dcmi-terms/#ses-ISO3166>.
dctISO3166 :: ScopedName
dctISO3166 :: ScopedName
dctISO3166 = LName -> ScopedName
toDCT LName
"ISO3166"

-- | @dcterms:ISO639-2@ from <http://dublincore.org/documents/dcmi-terms/#ses-ISO639-2>.
dctISO639_2 :: ScopedName
dctISO639_2 :: ScopedName
dctISO639_2 = LName -> ScopedName
toDCT LName
"ISO639-2"

-- | @dcterms:ISO639-3@ from <http://dublincore.org/documents/dcmi-terms/#ses-ISO639-3>.
dctISO639_3 :: ScopedName
dctISO639_3 :: ScopedName
dctISO639_3 = LName -> ScopedName
toDCT LName
"ISO639-3"

-- | @dcterms:Period@ from <http://dublincore.org/documents/dcmi-terms/#ses-Period>.
dctPeriod :: ScopedName
dctPeriod :: ScopedName
dctPeriod = LName -> ScopedName
toDCT LName
"Period"

-- | @dcterms:Point@ from <http://dublincore.org/documents/dcmi-terms/#ses-Point>.
dctPoint :: ScopedName
dctPoint :: ScopedName
dctPoint = LName -> ScopedName
toDCT LName
"Point"

-- | @dcterms:RFC1766@ from <http://dublincore.org/documents/dcmi-terms/#ses-RFC1766>.
dctRFC1766 :: ScopedName
dctRFC1766 :: ScopedName
dctRFC1766 = LName -> ScopedName
toDCT LName
"RFC1766"

-- | @dcterms:RFC3066@ from <http://dublincore.org/documents/dcmi-terms/#ses-RFC3066>.
dctRFC3066 :: ScopedName
dctRFC3066 :: ScopedName
dctRFC3066 = LName -> ScopedName
toDCT LName
"RFC3066"

-- | @dcterms:RFC4646@ from <http://dublincore.org/documents/dcmi-terms/#ses-RFC4646>.
dctRFC4646 :: ScopedName
dctRFC4646 :: ScopedName
dctRFC4646 = LName -> ScopedName
toDCT LName
"RFC4646"

-- | @dcterms:RFC5646@ from <http://dublincore.org/documents/dcmi-terms/#ses-RFC5646>.
dctRFC5646 :: ScopedName
dctRFC5646 :: ScopedName
dctRFC5646 = LName -> ScopedName
toDCT LName
"RFC5646"

-- | @dcterms:URI@ from <http://dublincore.org/documents/dcmi-terms/#ses-URI>.
dctURI :: ScopedName
dctURI :: ScopedName
dctURI = LName -> ScopedName
toDCT LName
"URI"

-- | @dcterms:W3CDTF@ from <http://dublincore.org/documents/dcmi-terms/#ses-W3CDTF>.
dctW3CDTF :: ScopedName
dctW3CDTF :: ScopedName
dctW3CDTF = LName -> ScopedName
toDCT LName
"W3CDTF"

-- | @dcam:memberOf@ from <http://dublincore.org/documents/dcmi-terms/#dcam-memberOf>.
dcammemberOf :: ScopedName
dcammemberOf :: ScopedName
dcammemberOf = LName -> ScopedName
toDCAM LName
"memberOf"

-- | @dcam:memberOf@ from <http://dublincore.org/documents/dcmi-terms/#dcam-memberOf>.
dcamVocabularyEncodingScheme :: ScopedName
dcamVocabularyEncodingScheme :: ScopedName
dcamVocabularyEncodingScheme = LName -> ScopedName
toDCAM LName
"VocabularyEncodingScheme"

-- | @dctype:Collection@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Collection>.
dctypeCollection :: ScopedName
dctypeCollection :: ScopedName
dctypeCollection = LName -> ScopedName
toDCTYPE LName
"Collection"

-- | @dctype:Dataset@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Dataset>.
dctypeDataset :: ScopedName
dctypeDataset :: ScopedName
dctypeDataset = LName -> ScopedName
toDCTYPE LName
"Dataset"

-- | @dctype:Event@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Event>.
dctypeEvent :: ScopedName
dctypeEvent :: ScopedName
dctypeEvent = LName -> ScopedName
toDCTYPE LName
"Event"

-- | @dctype:Image@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Image>.
dctypeImage :: ScopedName
dctypeImage :: ScopedName
dctypeImage = LName -> ScopedName
toDCTYPE LName
"Image"

-- | @dctype:InteractiveResource@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-InteractiveResource>.
dctypeInteractiveResource :: ScopedName
dctypeInteractiveResource :: ScopedName
dctypeInteractiveResource = LName -> ScopedName
toDCTYPE LName
"InteractiveResource"

-- | @dctype:Service@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Service>.
dctypeService :: ScopedName
dctypeService :: ScopedName
dctypeService = LName -> ScopedName
toDCTYPE LName
"Service"

-- | @dctype:Software@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Software>.
dctypeSoftware :: ScopedName
dctypeSoftware :: ScopedName
dctypeSoftware = LName -> ScopedName
toDCTYPE LName
"Software"

-- | @dctype:Sound@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Sound>.
dctypeSound :: ScopedName
dctypeSound :: ScopedName
dctypeSound = LName -> ScopedName
toDCTYPE LName
"Sound"

-- | @dctype:Text@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-Text>.
dctypeText :: ScopedName
dctypeText :: ScopedName
dctypeText = LName -> ScopedName
toDCTYPE LName
"Text"

-- | @dctype:PhysicalObject@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-PhysicalObject>.
dctypePhysicalObject :: ScopedName
dctypePhysicalObject :: ScopedName
dctypePhysicalObject = LName -> ScopedName
toDCTYPE LName
"PhysicalObject"

-- | @dctype:StillImage@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-StillImage>.
dctypeStillImage :: ScopedName
dctypeStillImage :: ScopedName
dctypeStillImage = LName -> ScopedName
toDCTYPE LName
"StillImage"

-- | @dctype:MovingImage@ from <http://dublincore.org/documents/dcmi-terms/#dcmitype-MovingImage>.
dctypeMovingImage :: ScopedName
dctypeMovingImage :: ScopedName
dctypeMovingImage = LName -> ScopedName
toDCTYPE LName
"MovingImage"

-- | @dcterms:LCSH@ from <http://dublincore.org/documents/dcmi-terms/#ves-LCSH>.
dctLCSH :: ScopedName
dctLCSH :: ScopedName
dctLCSH = LName -> ScopedName
toDCT LName
"LCSH"

-- | @dcterms:MESH@ from <http://dublincore.org/documents/dcmi-terms/#ves-MESH>.
dctMESH :: ScopedName
dctMESH :: ScopedName
dctMESH = LName -> ScopedName
toDCT LName
"MESH"

-- | @dcterms:DDC@ from <http://dublincore.org/documents/dcmi-terms/#ves-DDC>.
dctDDC :: ScopedName
dctDDC :: ScopedName
dctDDC = LName -> ScopedName
toDCT LName
"DDC"

-- | @dcterms:LCC@ from <http://dublincore.org/documents/dcmi-terms/#ves-LCC>.
dctLCC :: ScopedName
dctLCC :: ScopedName
dctLCC = LName -> ScopedName
toDCT LName
"LCC"

-- | @dcterms:UDC@ from <http://dublincore.org/documents/dcmi-terms/#ves-UDC>.
dctUDC :: ScopedName
dctUDC :: ScopedName
dctUDC = LName -> ScopedName
toDCT LName
"UDC"

-- | @dcterms:DCMIType@ from <http://dublincore.org/documents/dcmi-terms/#ves-DCMIType>.
dctDCMIType :: ScopedName
dctDCMIType :: ScopedName
dctDCMIType = LName -> ScopedName
toDCT LName
"DCMIType"

-- | @dcterms:IMT@ from <http://dublincore.org/documents/dcmi-terms/#ves-IMT>.
dctIMT :: ScopedName
dctIMT :: ScopedName
dctIMT = LName -> ScopedName
toDCT LName
"IMT"

-- | @dcterms:TGN@ from <http://dublincore.org/documents/dcmi-terms/#ves-TGN>.
dctTGN :: ScopedName
dctTGN :: ScopedName
dctTGN = LName -> ScopedName
toDCT LName
"TGN"

-- | @dcterms:NLM@ from <http://dublincore.org/documents/dcmi-terms/#ves-NLM>.
dctNLM :: ScopedName
dctNLM :: ScopedName
dctNLM = LName -> ScopedName
toDCT LName
"NLM"

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