Hets - the Heterogeneous Tool Set
Copyright(c) DFKI GmbH 2012
LicenseGPLv2 or higher, see LICENSE.txt
MaintainerEugen Kuksa <eugenk@informatik.uni-bremen.de>
Stabilityprovisional
Portabilityportable
Safe HaskellSafe

Common.IRI

Description

This module defines functions for handling IRIs. It was adopted from the Network.URI module by Graham Klyne, but is extended to IRI support [2] and CURIE [3].

Four methods are provided for parsing different kinds of IRI string (as noted in [1], [2]): parseIRI parseIRIReference

An additional method is provided for parsing an abbreviated IRI according to [3]: parseIRICurie

Additionally, classification of full, abbreviated and simple IRI is provided.

The abbreviated syntaxes [3] provide three different kinds of IRI.

References

  1. http://www.ietf.org/rfc/rfc3986.txt
  2. http://www.ietf.org/rfc/rfc3987.txt
  3. http://www.w3.org/TR/rdfa-core/#s_curies
Synopsis

Documentation

data IRI Source #

Represents a general universal resource identifier using its component parts.

For example, for the (full) IRI

  foo://anonymous@www.haskell.org:42/ghc?query#frag

or the abbreviated IRI

  prefix:iFragement

or the simple IRI

 iFragement

The isAbbrev flag is set, if an iri i is abbreviated. With a prefix map pm or pm' it can be expanded using expandIRI pm i, expandIRI' pm' i, expandCurie pm i, and expandCurie' pm ' i yielding a new IRI which stores both, the abbreviated and absolute IRI.

Constructors

IRI 

Fields

Instances

Instances details
Eq IRI Source # 
Instance details

Defined in Common.IRI

Methods

(==) :: IRI -> IRI -> Bool

(/=) :: IRI -> IRI -> Bool

Data IRI Source # 
Instance details

Defined in Common.IRI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IRI -> c IRI

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IRI

toConstr :: IRI -> Constr

dataTypeOf :: IRI -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IRI)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IRI)

gmapT :: (forall b. Data b => b -> b) -> IRI -> IRI

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IRI -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IRI -> r

gmapQ :: (forall d. Data d => d -> u) -> IRI -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IRI -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IRI -> m IRI

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IRI -> m IRI

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IRI -> m IRI

Ord IRI Source #

compares two IRIs

If both IRIs are absolute or are expanded, only the absolute IRIs are compared. If both IRIs abbreviated *and* not expanded their abbreviated forms are compared.

Comparision is done componentwise for all components in any other case: If both IRIs, i and j, abbreviated forms are equal but only one IRI i is expanded they don't have to be equal and cannot be compared based on their abbreviated forms as the prefix of j might not point to the same as the prefix of i. This cannot be resolved at the time of comparison.

Instance details

Defined in Common.IRI

Methods

compare :: IRI -> IRI -> Ordering

(<) :: IRI -> IRI -> Bool

(<=) :: IRI -> IRI -> Bool

(>) :: IRI -> IRI -> Bool

(>=) :: IRI -> IRI -> Bool

max :: IRI -> IRI -> IRI

min :: IRI -> IRI -> IRI

Show IRI Source # 
Instance details

Defined in Common.IRI

Methods

showsPrec :: Int -> IRI -> ShowS

show :: IRI -> String

showList :: [IRI] -> ShowS

Generic IRI 
Instance details

Defined in ATC.IRI

Associated Types

type Rep IRI :: Type -> Type

Methods

from :: IRI -> Rep IRI x

to :: Rep IRI x -> IRI

GetRange IRI Source # 
Instance details

Defined in Common.IRI

FromJSON IRI 
Instance details

Defined in ATC.IRI

Methods

parseJSON :: Value -> Parser IRI

parseJSONList :: Value -> Parser [IRI]

ToJSON IRI 
Instance details

Defined in ATC.IRI

Methods

toJSON :: IRI -> Value

toEncoding :: IRI -> Encoding

toJSONList :: [IRI] -> Value

toEncodingList :: [IRI] -> Encoding

ShATermConvertible IRI 
Instance details

Defined in ATC.IRI

Methods

toShATermAux :: ATermTable -> IRI -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [IRI] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, IRI)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [IRI])

SymbolName IRI Source # 
Instance details

Defined in Common.SetColimit

Methods

addString :: (IRI, String) -> IRI Source #

Pretty IRI Source # 
Instance details

Defined in Common.DocUtils

Methods

pretty :: IRI -> Doc Source #

pretties :: [IRI] -> Doc Source #

Function IRI Source # 
Instance details

Defined in OWL2.Function

Methods

function :: Action -> AMap -> IRI -> IRI Source #

Function PrefixMap Source # 
Instance details

Defined in OWL2.Function

type Rep IRI 
Instance details

Defined in ATC.IRI

type Rep IRI = D1 ('MetaData "IRI" "Common.IRI" "main" 'False) (C1 ('MetaCons "IRI" 'PrefixI 'True) (((S1 ('MetaSel ('Just "iriPos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Range) :*: S1 ('MetaSel ('Just "iriScheme") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :*: (S1 ('MetaSel ('Just "iriAuthority") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe IRIAuth)) :*: (S1 ('MetaSel ('Just "iriPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Id) :*: S1 ('MetaSel ('Just "iriQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)))) :*: ((S1 ('MetaSel ('Just "iriFragment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "prefixName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "iFragment") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) :*: (S1 ('MetaSel ('Just "isAbbrev") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "isBlankNode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "hasAngles") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))))

data IRIAuth Source #

Type for authority value within a IRI

Constructors

IRIAuth String String String 

Instances

Instances details
Eq IRIAuth Source # 
Instance details

Defined in Common.IRI

Methods

(==) :: IRIAuth -> IRIAuth -> Bool

(/=) :: IRIAuth -> IRIAuth -> Bool

Data IRIAuth Source # 
Instance details

Defined in Common.IRI

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IRIAuth -> c IRIAuth

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IRIAuth

toConstr :: IRIAuth -> Constr

dataTypeOf :: IRIAuth -> DataType

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IRIAuth)

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IRIAuth)

gmapT :: (forall b. Data b => b -> b) -> IRIAuth -> IRIAuth

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IRIAuth -> r

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IRIAuth -> r

gmapQ :: (forall d. Data d => d -> u) -> IRIAuth -> [u]

gmapQi :: Int -> (forall d. Data d => d -> u) -> IRIAuth -> u

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IRIAuth -> m IRIAuth

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IRIAuth -> m IRIAuth

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IRIAuth -> m IRIAuth

Ord IRIAuth Source # 
Instance details

Defined in Common.IRI

Methods

compare :: IRIAuth -> IRIAuth -> Ordering

(<) :: IRIAuth -> IRIAuth -> Bool

(<=) :: IRIAuth -> IRIAuth -> Bool

(>) :: IRIAuth -> IRIAuth -> Bool

(>=) :: IRIAuth -> IRIAuth -> Bool

max :: IRIAuth -> IRIAuth -> IRIAuth

min :: IRIAuth -> IRIAuth -> IRIAuth

Show IRIAuth Source # 
Instance details

Defined in Common.IRI

Methods

showsPrec :: Int -> IRIAuth -> ShowS

show :: IRIAuth -> String

showList :: [IRIAuth] -> ShowS

Generic IRIAuth 
Instance details

Defined in ATC.IRI

Associated Types

type Rep IRIAuth :: Type -> Type

Methods

from :: IRIAuth -> Rep IRIAuth x

to :: Rep IRIAuth x -> IRIAuth

FromJSON IRIAuth 
Instance details

Defined in ATC.IRI

Methods

parseJSON :: Value -> Parser IRIAuth

parseJSONList :: Value -> Parser [IRIAuth]

ToJSON IRIAuth 
Instance details

Defined in ATC.IRI

Methods

toJSON :: IRIAuth -> Value

toEncoding :: IRIAuth -> Encoding

toJSONList :: [IRIAuth] -> Value

toEncodingList :: [IRIAuth] -> Encoding

ShATermConvertible IRIAuth 
Instance details

Defined in ATC.IRI

Methods

toShATermAux :: ATermTable -> IRIAuth -> IO (ATermTable, Int)

toShATermList' :: ATermTable -> [IRIAuth] -> IO (ATermTable, Int)

fromShATermAux :: Int -> ATermTable -> (ATermTable, IRIAuth)

fromShATermList' :: Int -> ATermTable -> (ATermTable, [IRIAuth])

type Rep IRIAuth 
Instance details

Defined in ATC.IRI

type Rep IRIAuth = D1 ('MetaData "IRIAuth" "Common.IRI" "main" 'False) (C1 ('MetaCons "IRIAuth" 'PrefixI 'True) (S1 ('MetaSel ('Just "iriUserInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: (S1 ('MetaSel ('Just "iriRegName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "iriPort") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

nullIRI :: IRI Source #

Blank IRI

iriToStringUnsecure :: IRI -> String Source #

converts IRI to String of expanded form. if available. Also showing Auth

iriToStringShortUnsecure :: IRI -> String Source #

converts IRI to String of abbreviated form. if available. Also showing Auth info.

hasFullIRI :: IRI -> Bool Source #

check that we have a full (possibly expanded) IRI (i.e. for comparisons)

isSimple :: IRI -> Bool Source #

check that we have a simple IRI that is a (possibly expanded) abbreviated IRI without prefix

isURN :: IRI -> Bool Source #

check whether the IRI is a URN (uniform resource name)

addSuffixToIRI :: String -> IRI -> IRI Source #

addSuffixToIRI s iri adds a suffix s to iri.

s is added to the iFragement if iri is abbreviated. s is added to the query or the path of iri if iri contains an absolute IRI (either being an absolute IRI or being an expanded abbreviated IRI)

showTrace :: IRI -> String Source #

Parsing

iriParser :: IRIParser st IRI Source #

angles :: IRIParser st IRI -> IRIParser st IRI Source #

iriCurie :: IRIParser st IRI Source #

Parses an IRI reference enclosed in <, > or a CURIE

urnParser :: IRIParser st IRI Source #

compoundIriCurie :: IRIParser st IRI Source #

parseCurie :: String -> Maybe IRI Source #

Turn a string containing a CURIE into an IRI

parseIRICurie :: String -> Maybe IRI Source #

Turn a string containing an IRI or a CURIE into an IRI. Returns Nothing if the string is not a valid IRI; (an absolute IRI enclosed in < and > with optional fragment identifier or a CURIE).

parseIRIReference :: String -> Maybe IRI Source #

Parse a IRI reference to an IRI value. Returns Nothing if the string is not a valid IRI reference. (an absolute or relative IRI with optional fragment identifier).

parseIRICompoundCurie :: String -> Maybe IRI Source #

parseIRI :: String -> Maybe IRI Source #

Turn a string containing an RFC3987 IRI into an IRI. Returns Nothing if the string is not a valid IRI; (an absolute IRI with optional fragment identifier).

ncname :: GenParser Char st String Source #

Prefix part of CURIE in prefix_part:reference http://www.w3.org/TR/2009/REC-xml-names-20091208/#NT-NCName

mergeCurie :: IRI -> IRI -> Maybe IRI Source #

mergeCurie merges the CURIE c into IRI i, appending their string representations

expandCurie :: Map String IRI -> IRI -> Maybe IRI Source #

Expands a CURIE to an IRI. Nothing iff there is no IRI i assigned to the prefix of c or the concatenation of i and iriPath c is not a valid IRI.

expandIRI :: Map String IRI -> IRI -> IRI Source #

expandIRI pm iri returns the expanded iri with a declaration from pm. If no declaration is found, return iri unchanged.

expandIRI' :: Map String String -> IRI -> IRI Source #

Same as expandIRI but with a Map String String as prefix map. See expandCurie' for more details.

relativeTo :: IRI -> IRI -> Maybe IRI Source #

Returns a new IRI which represents the value of the first IRI interpreted as relative to the second IRI. For example:

"foo" `relativeTo` "http://bar.org/" = "http://bar.org/foo"

relativeFrom :: IRI -> IRI -> IRI Source #

Returns a new IRI which represents the relative location of the first IRI with respect to the second IRI. Thus, the values supplied are expected to be absolute IRIs, and the result returned may be a relative IRI.

Example:

"http://example.com/Root/sub1/name2#frag"
  `relativeFrom` "http://example.com/Root/sub2/name2#frag"
  == "../sub1/name2#frag"

There is no single correct implementation of this function, but any acceptable implementation must satisfy the following:

(uabs `relativeFrom` ubase) `relativeTo` ubase == uabs

For any valid absolute IRI. (cf. http://lists.w3.org/Archives/Public/iri/2003Jan/0008.html http://lists.w3.org/Archives/Public/iri/2003Jan/0005.html)

Conversion

simpleIdToIRI :: SIMPLE_ID -> IRI Source #

Converts a Simple_ID to an IRI

setAngles :: Bool -> IRI -> IRI Source #

methods from OWL2.AS

isNullIRI :: IRI -> Bool Source #

check that we have a nullIRI

iRIRange :: IRI -> [Pos] Source #

set the Range attribute of IRIs setIRIRange :: Range -> IRI -> IRI setIRIRange r i = i { iriPos = r }

checks if a string (bound to be localPart of an IRI) contains "://" cssIRI :: String -> String cssIRI i | isInfixOf "://" i = Full | otherwise = Abbreviated

showIRI :: IRI -> String Source #

showIRICompact :: IRI -> String Source #

show IRI as abbreviated, when possible

showIRIFull :: IRI -> String Source #

show IRI in angle brackets as full IRI

showURN :: IRI -> String Source #

dummyIRI :: IRI Source #

a default ontology name

mkIRI :: String -> IRI Source #

mkAbbrevIRI :: String -> String -> IRI Source #

setPrefix :: String -> IRI -> IRI Source #

uriToCaslId :: IRI -> Id Source #

Extracts Id from URI