{-# LANGUAGE OverloadedStrings #-}
module Swish.RDF.Vocabulary.DublinCore
(
namespaceDCTERMS
, namespaceDCELEM
, namespaceDCAM
, namespaceDCTYPE
, dctAgent
, dctAgentClass
, dctBibliographicResource
, dctFileFormat
, dctFrequency
, dctJurisdiction
, dctLicenseDocument
, dctLinguisticSystem
, dctLocation
, dctLocationPeriodOrJurisdiction
, dctMediaType
, dctMediaTypeOrExtent
, dctMethodOfAccrual
, dctMethodOfInstruction
, dctPeriodOfTime
, dctPhysicalMedium
, dctPhysicalResource
, dctPolicy
, dctProvenanceStatement
, dctRightsStatement
, dctSizeOrDuration
, dctStandard
, 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
, dcelemcontributor
, dcelemcoverage
, dcelemcreator
, dcelemdate
, dcelemdescription
, dcelemformat
, dcelemidentifier
, dcelemlanguage
, dcelempublisher
, dcelemrelation
, dcelemrights
, dcelemsource
, dcelemsubject
, dcelemtitle
, dcelemtype
, dctLCSH
, dctMESH
, dctDDC
, dctLCC
, dctUDC
, dctDCMIType
, dctIMT
, dctTGN
, dctNLM
, dctBox
, dctISO3166
, dctISO639_2
, dctISO639_3
, dctPeriod
, dctPoint
, dctRFC1766
, dctRFC3066
, dctRFC4646
, dctRFC5646
, dctURI
, dctW3CDTF
, dctypeCollection
, dctypeDataset
, dctypeEvent
, dctypeImage
, dctypeInteractiveResource
, dctypeService
, dctypeSoftware
, dctypeSound
, dctypeText
, dctypePhysicalObject
, dctypeStillImage
, dctypeMovingImage
, 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
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
namespaceDCTERMS :: Namespace
namespaceDCTERMS :: Namespace
namespaceDCTERMS = Text -> String -> Namespace
toNS Text
"dcterms" String
"http://purl.org/dc/terms/"
namespaceDCELEM :: Namespace
namespaceDCELEM :: Namespace
namespaceDCELEM = Text -> String -> Namespace
toNS Text
"dcelem" String
"http://purl.org/dc/elements/1.1/"
namespaceDCAM :: Namespace
namespaceDCAM :: Namespace
namespaceDCAM = Text -> String -> Namespace
toNS Text
"dcam" String
"http://purl.org/dc/dcam/"
namespaceDCTYPE :: Namespace
namespaceDCTYPE :: Namespace
namespaceDCTYPE = Text -> String -> Namespace
toNS Text
"dctype" String
"http://purl.org/dc/dcmitype/"
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
dctAgent :: ScopedName
dctAgent :: ScopedName
dctAgent = LName -> ScopedName
toDCT LName
"Agent"
dctAgentClass :: ScopedName
dctAgentClass :: ScopedName
dctAgentClass = LName -> ScopedName
toDCT LName
"AgentClass"
dctBibliographicResource :: ScopedName
dctBibliographicResource :: ScopedName
dctBibliographicResource = LName -> ScopedName
toDCT LName
"BibliographicResource"
dctFileFormat :: ScopedName
dctFileFormat :: ScopedName
dctFileFormat = LName -> ScopedName
toDCT LName
"FileFormat"
dctFrequency :: ScopedName
dctFrequency :: ScopedName
dctFrequency = LName -> ScopedName
toDCT LName
"Frequency"
dctJurisdiction :: ScopedName
dctJurisdiction :: ScopedName
dctJurisdiction = LName -> ScopedName
toDCT LName
"Jurisdiction"
dctLicenseDocument :: ScopedName
dctLicenseDocument :: ScopedName
dctLicenseDocument = LName -> ScopedName
toDCT LName
"LicenseDocument"
dctLinguisticSystem :: ScopedName
dctLinguisticSystem :: ScopedName
dctLinguisticSystem = LName -> ScopedName
toDCT LName
"LinguisticSystem"
dctLocation :: ScopedName
dctLocation :: ScopedName
dctLocation = LName -> ScopedName
toDCT LName
"Location"
dctLocationPeriodOrJurisdiction :: ScopedName
dctLocationPeriodOrJurisdiction :: ScopedName
dctLocationPeriodOrJurisdiction = LName -> ScopedName
toDCT LName
"LocationPeriodOrJurisdiction"
dctMediaType :: ScopedName
dctMediaType :: ScopedName
dctMediaType = LName -> ScopedName
toDCT LName
"MediaType"
dctMediaTypeOrExtent :: ScopedName
dctMediaTypeOrExtent :: ScopedName
dctMediaTypeOrExtent = LName -> ScopedName
toDCT LName
"MediaTypeOrExtent"
dctMethodOfAccrual :: ScopedName
dctMethodOfAccrual :: ScopedName
dctMethodOfAccrual = LName -> ScopedName
toDCT LName
"MethodOfAccrual"
dctMethodOfInstruction :: ScopedName
dctMethodOfInstruction :: ScopedName
dctMethodOfInstruction = LName -> ScopedName
toDCT LName
"MethodOfInstruction"
dctPeriodOfTime :: ScopedName
dctPeriodOfTime :: ScopedName
dctPeriodOfTime = LName -> ScopedName
toDCT LName
"PeriodOfTime"
dctPhysicalMedium :: ScopedName
dctPhysicalMedium :: ScopedName
dctPhysicalMedium = LName -> ScopedName
toDCT LName
"PhysicalMedium"
dctPhysicalResource :: ScopedName
dctPhysicalResource :: ScopedName
dctPhysicalResource = LName -> ScopedName
toDCT LName
"PhysicalResource"
dctPolicy :: ScopedName
dctPolicy :: ScopedName
dctPolicy = LName -> ScopedName
toDCT LName
"Policy"
dctProvenanceStatement :: ScopedName
dctProvenanceStatement :: ScopedName
dctProvenanceStatement = LName -> ScopedName
toDCT LName
"ProvenanceStatement"
dctRightsStatement :: ScopedName
dctRightsStatement :: ScopedName
dctRightsStatement = LName -> ScopedName
toDCT LName
"RightsStatement"
dctSizeOrDuration :: ScopedName
dctSizeOrDuration :: ScopedName
dctSizeOrDuration = LName -> ScopedName
toDCT LName
"SizeOrDuration"
dctStandard :: ScopedName
dctStandard :: ScopedName
dctStandard = LName -> ScopedName
toDCT LName
"Standard"
dctabstract :: ScopedName
dctabstract :: ScopedName
dctabstract = LName -> ScopedName
toDCT LName
"abstract"
dctaccessRights :: ScopedName
dctaccessRights :: ScopedName
dctaccessRights = LName -> ScopedName
toDCT LName
"accessRights"
dctaccrualMethod :: ScopedName
dctaccrualMethod :: ScopedName
dctaccrualMethod = LName -> ScopedName
toDCT LName
"accrualMethod"
dctaccrualPeriodicity :: ScopedName
dctaccrualPeriodicity :: ScopedName
dctaccrualPeriodicity = LName -> ScopedName
toDCT LName
"accrualPeriodicity"
dctaccrualPolicy :: ScopedName
dctaccrualPolicy :: ScopedName
dctaccrualPolicy = LName -> ScopedName
toDCT LName
"accrualPolicy"
dctalternative :: ScopedName
dctalternative :: ScopedName
dctalternative = LName -> ScopedName
toDCT LName
"alternative"
dctaudience :: ScopedName
dctaudience :: ScopedName
dctaudience = LName -> ScopedName
toDCT LName
"audience"
dctavailable :: ScopedName
dctavailable :: ScopedName
dctavailable = LName -> ScopedName
toDCT LName
"available"
dctbibliographicCitation :: ScopedName
dctbibliographicCitation :: ScopedName
dctbibliographicCitation = LName -> ScopedName
toDCT LName
"bibliographicCitation"
dctconformsTo :: ScopedName
dctconformsTo :: ScopedName
dctconformsTo = LName -> ScopedName
toDCT LName
"conformsTo"
dctcontributor :: ScopedName
dctcontributor :: ScopedName
dctcontributor = LName -> ScopedName
toDCT LName
"contributor"
dctcoverage :: ScopedName
dctcoverage :: ScopedName
dctcoverage = LName -> ScopedName
toDCT LName
"coverage"
dctcreated :: ScopedName
dctcreated :: ScopedName
dctcreated = LName -> ScopedName
toDCT LName
"created"
dctcreator :: ScopedName
dctcreator :: ScopedName
dctcreator = LName -> ScopedName
toDCT LName
"creator"
dctdate :: ScopedName
dctdate :: ScopedName
dctdate = LName -> ScopedName
toDCT LName
"date"
dctdateAccepted :: ScopedName
dctdateAccepted :: ScopedName
dctdateAccepted = LName -> ScopedName
toDCT LName
"dateAccepted"
dctdateCopyrighted :: ScopedName
dctdateCopyrighted :: ScopedName
dctdateCopyrighted = LName -> ScopedName
toDCT LName
"dateCopyrighted"
dctdateSubmitted :: ScopedName
dctdateSubmitted :: ScopedName
dctdateSubmitted = LName -> ScopedName
toDCT LName
"dateSubmitted"
dctdescription :: ScopedName
dctdescription :: ScopedName
dctdescription = LName -> ScopedName
toDCT LName
"description"
dcteducationLevel :: ScopedName
dcteducationLevel :: ScopedName
dcteducationLevel = LName -> ScopedName
toDCT LName
"educationLevel"
dctextent :: ScopedName
dctextent :: ScopedName
dctextent = LName -> ScopedName
toDCT LName
"extent"
dctformat :: ScopedName
dctformat :: ScopedName
dctformat = LName -> ScopedName
toDCT LName
"format"
dcthasFormat :: ScopedName
dcthasFormat :: ScopedName
dcthasFormat = LName -> ScopedName
toDCT LName
"hasFormat"
dcthasPart :: ScopedName
dcthasPart :: ScopedName
dcthasPart = LName -> ScopedName
toDCT LName
"hasPart"
dcthasVersion :: ScopedName
dcthasVersion :: ScopedName
dcthasVersion = LName -> ScopedName
toDCT LName
"hasVersion"
dctidentifier :: ScopedName
dctidentifier :: ScopedName
dctidentifier = LName -> ScopedName
toDCT LName
"identifier"
dctinstructionalMethod :: ScopedName
dctinstructionalMethod :: ScopedName
dctinstructionalMethod = LName -> ScopedName
toDCT LName
"instructionalMethod"
dctisFormatOf :: ScopedName
dctisFormatOf :: ScopedName
dctisFormatOf = LName -> ScopedName
toDCT LName
"isFormatOf"
dctisPartOf :: ScopedName
dctisPartOf :: ScopedName
dctisPartOf = LName -> ScopedName
toDCT LName
"isPartOf"
dctisReferencedBy :: ScopedName
dctisReferencedBy :: ScopedName
dctisReferencedBy = LName -> ScopedName
toDCT LName
"isReferencedBy"
dctisReplacedBy :: ScopedName
dctisReplacedBy :: ScopedName
dctisReplacedBy = LName -> ScopedName
toDCT LName
"isReplacedBy"
dctisRequiredBy :: ScopedName
dctisRequiredBy :: ScopedName
dctisRequiredBy = LName -> ScopedName
toDCT LName
"isRequiredBy"
dctissued :: ScopedName
dctissued :: ScopedName
dctissued = LName -> ScopedName
toDCT LName
"issued"
dctisVersionOf :: ScopedName
dctisVersionOf :: ScopedName
dctisVersionOf = LName -> ScopedName
toDCT LName
"isVersionOf"
dctlanguage :: ScopedName
dctlanguage :: ScopedName
dctlanguage = LName -> ScopedName
toDCT LName
"language"
dctlicense :: ScopedName
dctlicense :: ScopedName
dctlicense = LName -> ScopedName
toDCT LName
"license"
dctmediator :: ScopedName
dctmediator :: ScopedName
dctmediator = LName -> ScopedName
toDCT LName
"mediator"
dctmedium :: ScopedName
dctmedium :: ScopedName
dctmedium = LName -> ScopedName
toDCT LName
"medium"
dctmodified :: ScopedName
dctmodified :: ScopedName
dctmodified = LName -> ScopedName
toDCT LName
"modified"
dctprovenance :: ScopedName
dctprovenance :: ScopedName
dctprovenance = LName -> ScopedName
toDCT LName
"provenance"
dctpublisher :: ScopedName
dctpublisher :: ScopedName
dctpublisher = LName -> ScopedName
toDCT LName
"publisher"
dctreferences :: ScopedName
dctreferences :: ScopedName
dctreferences = LName -> ScopedName
toDCT LName
"references"
dctrelation :: ScopedName
dctrelation :: ScopedName
dctrelation = LName -> ScopedName
toDCT LName
"relation"
dctreplaces :: ScopedName
dctreplaces :: ScopedName
dctreplaces = LName -> ScopedName
toDCT LName
"replaces"
dctrequires :: ScopedName
dctrequires :: ScopedName
dctrequires = LName -> ScopedName
toDCT LName
"requires"
dctrights :: ScopedName
dctrights :: ScopedName
dctrights = LName -> ScopedName
toDCT LName
"rights"
dctrightsHolder :: ScopedName
dctrightsHolder :: ScopedName
dctrightsHolder = LName -> ScopedName
toDCT LName
"rightsHolder"
dctsource :: ScopedName
dctsource :: ScopedName
dctsource = LName -> ScopedName
toDCT LName
"source"
dctspatial :: ScopedName
dctspatial :: ScopedName
dctspatial = LName -> ScopedName
toDCT LName
"spatial"
dctsubject :: ScopedName
dctsubject :: ScopedName
dctsubject = LName -> ScopedName
toDCT LName
"subject"
dcttableOfContents :: ScopedName
dcttableOfContents :: ScopedName
dcttableOfContents = LName -> ScopedName
toDCT LName
"tableOfContents"
dcttemporal :: ScopedName
dcttemporal :: ScopedName
dcttemporal = LName -> ScopedName
toDCT LName
"temporal"
dcttitle :: ScopedName
dcttitle :: ScopedName
dcttitle = LName -> ScopedName
toDCT LName
"title"
dcttype :: ScopedName
dcttype :: ScopedName
dcttype = LName -> ScopedName
toDCT LName
"type"
dctvalid :: ScopedName
dctvalid :: ScopedName
dctvalid = LName -> ScopedName
toDCT LName
"valid"
dcelemcontributor :: ScopedName
dcelemcontributor :: ScopedName
dcelemcontributor = LName -> ScopedName
toDCE LName
"contributor"
dcelemcoverage :: ScopedName
dcelemcoverage :: ScopedName
dcelemcoverage = LName -> ScopedName
toDCE LName
"coverage"
dcelemcreator :: ScopedName
dcelemcreator :: ScopedName
dcelemcreator = LName -> ScopedName
toDCE LName
"creator"
dcelemdate :: ScopedName
dcelemdate :: ScopedName
dcelemdate = LName -> ScopedName
toDCE LName
"date"
dcelemdescription :: ScopedName
dcelemdescription :: ScopedName
dcelemdescription = LName -> ScopedName
toDCE LName
"description"
dcelemformat :: ScopedName
dcelemformat :: ScopedName
dcelemformat = LName -> ScopedName
toDCE LName
"format"
dcelemidentifier :: ScopedName
dcelemidentifier :: ScopedName
dcelemidentifier = LName -> ScopedName
toDCE LName
"identifier"
dcelemlanguage :: ScopedName
dcelemlanguage :: ScopedName
dcelemlanguage = LName -> ScopedName
toDCE LName
"language"
dcelempublisher :: ScopedName
dcelempublisher :: ScopedName
dcelempublisher = LName -> ScopedName
toDCE LName
"publisher"
dcelemrelation :: ScopedName
dcelemrelation :: ScopedName
dcelemrelation = LName -> ScopedName
toDCE LName
"relation"
dcelemrights :: ScopedName
dcelemrights :: ScopedName
dcelemrights = LName -> ScopedName
toDCE LName
"rights"
dcelemsource :: ScopedName
dcelemsource :: ScopedName
dcelemsource = LName -> ScopedName
toDCE LName
"source"
dcelemsubject :: ScopedName
dcelemsubject :: ScopedName
dcelemsubject = LName -> ScopedName
toDCE LName
"subject"
dcelemtitle :: ScopedName
dcelemtitle :: ScopedName
dcelemtitle = LName -> ScopedName
toDCE LName
"title"
dcelemtype :: ScopedName
dcelemtype :: ScopedName
dcelemtype = LName -> ScopedName
toDCE LName
"type"
dctBox :: ScopedName
dctBox :: ScopedName
dctBox = LName -> ScopedName
toDCT LName
"Box"
dctISO3166 :: ScopedName
dctISO3166 :: ScopedName
dctISO3166 = LName -> ScopedName
toDCT LName
"ISO3166"
dctISO639_2 :: ScopedName
dctISO639_2 :: ScopedName
dctISO639_2 = LName -> ScopedName
toDCT LName
"ISO639-2"
dctISO639_3 :: ScopedName
dctISO639_3 :: ScopedName
dctISO639_3 = LName -> ScopedName
toDCT LName
"ISO639-3"
dctPeriod :: ScopedName
dctPeriod :: ScopedName
dctPeriod = LName -> ScopedName
toDCT LName
"Period"
dctPoint :: ScopedName
dctPoint :: ScopedName
dctPoint = LName -> ScopedName
toDCT LName
"Point"
dctRFC1766 :: ScopedName
dctRFC1766 :: ScopedName
dctRFC1766 = LName -> ScopedName
toDCT LName
"RFC1766"
dctRFC3066 :: ScopedName
dctRFC3066 :: ScopedName
dctRFC3066 = LName -> ScopedName
toDCT LName
"RFC3066"
dctRFC4646 :: ScopedName
dctRFC4646 :: ScopedName
dctRFC4646 = LName -> ScopedName
toDCT LName
"RFC4646"
dctRFC5646 :: ScopedName
dctRFC5646 :: ScopedName
dctRFC5646 = LName -> ScopedName
toDCT LName
"RFC5646"
dctURI :: ScopedName
dctURI :: ScopedName
dctURI = LName -> ScopedName
toDCT LName
"URI"
dctW3CDTF :: ScopedName
dctW3CDTF :: ScopedName
dctW3CDTF = LName -> ScopedName
toDCT LName
"W3CDTF"
dcammemberOf :: ScopedName
dcammemberOf :: ScopedName
dcammemberOf = LName -> ScopedName
toDCAM LName
"memberOf"
dcamVocabularyEncodingScheme :: ScopedName
dcamVocabularyEncodingScheme :: ScopedName
dcamVocabularyEncodingScheme = LName -> ScopedName
toDCAM LName
"VocabularyEncodingScheme"
dctypeCollection :: ScopedName
dctypeCollection :: ScopedName
dctypeCollection = LName -> ScopedName
toDCTYPE LName
"Collection"
dctypeDataset :: ScopedName
dctypeDataset :: ScopedName
dctypeDataset = LName -> ScopedName
toDCTYPE LName
"Dataset"
dctypeEvent :: ScopedName
dctypeEvent :: ScopedName
dctypeEvent = LName -> ScopedName
toDCTYPE LName
"Event"
dctypeImage :: ScopedName
dctypeImage :: ScopedName
dctypeImage = LName -> ScopedName
toDCTYPE LName
"Image"
dctypeInteractiveResource :: ScopedName
dctypeInteractiveResource :: ScopedName
dctypeInteractiveResource = LName -> ScopedName
toDCTYPE LName
"InteractiveResource"
dctypeService :: ScopedName
dctypeService :: ScopedName
dctypeService = LName -> ScopedName
toDCTYPE LName
"Service"
dctypeSoftware :: ScopedName
dctypeSoftware :: ScopedName
dctypeSoftware = LName -> ScopedName
toDCTYPE LName
"Software"
dctypeSound :: ScopedName
dctypeSound :: ScopedName
dctypeSound = LName -> ScopedName
toDCTYPE LName
"Sound"
dctypeText :: ScopedName
dctypeText :: ScopedName
dctypeText = LName -> ScopedName
toDCTYPE LName
"Text"
dctypePhysicalObject :: ScopedName
dctypePhysicalObject :: ScopedName
dctypePhysicalObject = LName -> ScopedName
toDCTYPE LName
"PhysicalObject"
dctypeStillImage :: ScopedName
dctypeStillImage :: ScopedName
dctypeStillImage = LName -> ScopedName
toDCTYPE LName
"StillImage"
dctypeMovingImage :: ScopedName
dctypeMovingImage :: ScopedName
dctypeMovingImage = LName -> ScopedName
toDCTYPE LName
"MovingImage"
dctLCSH :: ScopedName
dctLCSH :: ScopedName
dctLCSH = LName -> ScopedName
toDCT LName
"LCSH"
dctMESH :: ScopedName
dctMESH :: ScopedName
dctMESH = LName -> ScopedName
toDCT LName
"MESH"
dctDDC :: ScopedName
dctDDC :: ScopedName
dctDDC = LName -> ScopedName
toDCT LName
"DDC"
dctLCC :: ScopedName
dctLCC :: ScopedName
dctLCC = LName -> ScopedName
toDCT LName
"LCC"
dctUDC :: ScopedName
dctUDC :: ScopedName
dctUDC = LName -> ScopedName
toDCT LName
"UDC"
dctDCMIType :: ScopedName
dctDCMIType :: ScopedName
dctDCMIType = LName -> ScopedName
toDCT LName
"DCMIType"
dctIMT :: ScopedName
dctIMT :: ScopedName
dctIMT = LName -> ScopedName
toDCT LName
"IMT"
dctTGN :: ScopedName
dctTGN :: ScopedName
dctTGN = LName -> ScopedName
toDCT LName
"TGN"
dctNLM :: ScopedName
dctNLM :: ScopedName
dctNLM = LName -> ScopedName
toDCT LName
"NLM"