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