{- This file is part of link-relations. - - Written in 2015 by fr33domlover . - Also includes parts generated from the IANA link relation registry. - - ♡ Copying is an act of love. Please copy, reuse and share. - - The author(s) have dedicated all copyright and related and neighboring - rights to this software to the public domain worldwide. This software is - distributed without any warranty. - - You should have received a copy of the CC0 Public Domain Dedication along - with this software. If not, see - . -} {-# LANGUAGE OverloadedStrings #-} -- | A simple web link between two web resources, e.g. a hyperlink in a webpage -- referring to another page, suggests that the resources are somehow related, -- but it doesn't say /how/ they are related. For example, a blog post may link -- to the author's main page (relation: author of the post) but also link to -- the previous post (relation: previous post by chronological order). -- -- Link relations provide a way to express the relation between resources -- linked by a web link. -- -- A link relation type may be represented by a URI, or by a registered link -- relation name. IANA maintains a -- of link -- relations. This module provides access to them through a dedicated -- 'LinkRelation' datatype. -- -- This version of the package corresponds to the ${date} -- version of the registry. module Web.LinkRelations ( -- * Types and Conversions LinkRelation , fromURI , fromURIStr , fromName , fromByteString , isURI , isName , toByteString -- * Link Relation Identifiers ${exports} ) where import Control.Applicative ((<|>)) import URI.ByteString import qualified Data.ByteString as B import qualified Data.HashMap.Strict as M -- | A web link relation type. Either a URI or a registered name. data LinkRelation = FromURI URI ${ctors} deriving (Eq, Show) -- | A mapping from name string to identifiers, for parsing a link relation -- name from a string. hashmap :: M.HashMap B.ByteString LinkRelation hashmap = M.fromList ${hashmap} ] -- | Create a link relation type from a URI. fromURI :: URI -> LinkRelation fromURI = FromURI -- | Try to parse a string into a URI, returning a link relation if successful. fromURIStr :: B.ByteString -> Maybe LinkRelation fromURIStr s = case parseURI laxURIParserOptions s of Left _ -> Nothing Right u -> Just $ fromURI u -- | Try to match a given link relation name against the registered names. -- Return the matching link relation if successful. fromName :: B.ByteString -> Maybe LinkRelation fromName s = M.lookup s hashmap -- | Try to parse the given string as a link relation, either as a registered -- name or as a URI. If both fail, return 'Nothing'. fromByteString :: B.ByteString -> Maybe LinkRelation fromByteString s = fromName s <|> fromURIStr s -- | Get the official registered name of a link relation (if it's a name) or -- its URI string (if it's a URI). toByteString :: LinkRelation -> B.ByteString toByteString lr = case lr of FromURI u -> serializeURI' u ${tostr} -- | Check whether a link relation is represented by a URI, i.e. is not a link -- relation registered name. isURI :: LinkRelation -> Bool isURI (FromURI _) = True isURI _ = False -- | Check whether a link relation is represented by a registered name, i.e. is -- not a URI. isName :: LinkRelation -> Bool isName = not . isURI ${rels}