atom-basic-0.2.5: Basic Atom feed construction

Safe HaskellSafe
LanguageHaskell2010

Web.Atom

Description

atom-basic lets you generate Atom Feeds and Atom Entries. It provides the Feed and Entry types for the respective Atom document. This module is intended to be imported qualified to avoid name clashes:

import qualified Web.Atom as Atom

XML generation is not built in because there are several Haskell XML libraries that you might want to use depending on your circumstances. To allow for this, you need to provide an XMLGen record to the feedXML or entryXML functions. An XMLGen record contains functions that generate XML of the type you prefer. Thanks to Ollie Charles for this suggestion.

A minimal example using the xml package looks like this (GitHub):

{-# LANGUAGE OverloadedStrings #-}

import qualified Data.Text      as T
import           Data.Time      (UTCTime (..), fromGregorian)
import           Text.XML.Light
import qualified Web.Atom       as Atom

feed :: Atom.Feed Element
feed = Atom.makeFeed
    (Atom.unsafeURI "https://haskell.org/")
    (Atom.TextHTML "The <em>Title</em>")
    (UTCTime (fromGregorian 2015 7 8) 0)

xmlgen :: Atom.XMLGen Element Content QName Attr
xmlgen = Atom.XMLGen
    { Atom.xmlElem     = \n as ns    -> Element n as ns Nothing
    , Atom.xmlName     = \nsMay name -> QName (T.unpack name)
                                          (fmap T.unpack nsMay) Nothing
    , Atom.xmlAttr     = \k v        -> Attr k (T.unpack v)
    , Atom.xmlTextNode = \t          -> Text $ CData CDataText (T.unpack t) Nothing
    , Atom.xmlElemNode = Elem
    }

main = putStr $ ppTopElement $ Atom.feedXML xmlgen feed

Another example that uses the xml-conduit package instead is also available in the GitHub repository.

Synopsis

Documentation

makeFeed Source #

Arguments

:: URI

Feed ID

-> Text e

Feed Title

-> UTCTime

Updated timestamp

-> Feed e 

Convenience constructor with defaults for all non-required fields.

makeEntry Source #

Arguments

:: URI

Entry ID

-> Text e

Entry Title

-> UTCTime

Updated timestamp

-> Entry e 

Convenience constructor with defaults for all non-required fields.

feedXML :: XMLGen e node name attr -> Feed e -> e Source #

Generate an XML value from a Feed.

entryXML :: XMLGen e node name attr -> Entry e -> e Source #

Generate an XML value from an Entry.

data XMLGen elem node name attr Source #

This record defines what kind of XML we should construct. A valid definition of this record must be provided to the feedXML and entryXML functions. This lets users use the XML library of their choice for the Atom feed XML. A couple of concrete examples are provided at the top of this page. Here's an example that uses the xml-conduit package:

xmlgen :: Atom.XMLGen Element Node Name (Name, T.Text)
xmlgen = Atom.XMLGen
    { Atom.xmlElem     = \n as ns    -> Element n (fromList as) ns
    , Atom.xmlName     = \nsMay name -> Name name nsMay Nothing
    , Atom.xmlAttr     = \k v        -> (k, v)
    , Atom.xmlTextNode = NodeContent
    , Atom.xmlElemNode = NodeElement
    }

Constructors

XMLGen 

Fields

  • xmlElem :: name -> [attr] -> [node] -> elem

    Create element from name, attributes, and nodes/contents.

  • xmlName :: Maybe Text -> Text -> name

    Create qualified name from optional namespace and name.

  • xmlAttr :: name -> Text -> attr

    Create attribute from qualified name and text value.

  • xmlTextNode :: Text -> node

    Create text node/content from text value.

  • xmlElemNode :: elem -> node

    Create element node/content from element.

data Feed e Source #

Top-level element for an Atom Feed Document as per https://tools.ietf.org/html/rfc4287#section-4.1.1.

Instances

Eq e => Eq (Feed e) Source # 

Methods

(==) :: Feed e -> Feed e -> Bool #

(/=) :: Feed e -> Feed e -> Bool #

Show e => Show (Feed e) Source # 

Methods

showsPrec :: Int -> Feed e -> ShowS #

show :: Feed e -> String #

showList :: [Feed e] -> ShowS #

data Entry e Source #

An individual Atom entry that can be used either as a child of Feed or as the top-level element of a stand-alone Atom Entry Document as per https://tools.ietf.org/html/rfc4287#section-4.1.2.

Instances

Eq e => Eq (Entry e) Source # 

Methods

(==) :: Entry e -> Entry e -> Bool #

(/=) :: Entry e -> Entry e -> Bool #

Show e => Show (Entry e) Source # 

Methods

showsPrec :: Int -> Entry e -> ShowS #

show :: Entry e -> String #

showList :: [Entry e] -> ShowS #

data Source e Source #

If an Atom entry is copied into a different feed, Source can be used to preserve the metadata of the original feed as per https://tools.ietf.org/html/rfc4287#section-4.2.11.

Instances

Eq e => Eq (Source e) Source # 

Methods

(==) :: Source e -> Source e -> Bool #

(/=) :: Source e -> Source e -> Bool #

Show e => Show (Source e) Source # 

Methods

showsPrec :: Int -> Source e -> ShowS #

show :: Source e -> String #

showList :: [Source e] -> ShowS #

data Category Source #

Information about a feed or entry category as per https://tools.ietf.org/html/rfc4287#section-4.2.2.

data Generator Source #

Identifies the agent used to generate the feed, for debugging and other purposes as per https://tools.ietf.org/html/rfc4287#section-4.2.4.

data Email Source #

An email address. xsd:string { pattern = ".+.+" }@

Constructors

Email Text 

Instances

Eq Email Source # 

Methods

(==) :: Email -> Email -> Bool #

(/=) :: Email -> Email -> Bool #

Show Email Source # 

Methods

showsPrec :: Int -> Email -> ShowS #

show :: Email -> String #

showList :: [Email] -> ShowS #

data Rel Source #

rel attribute for link elements as per https://tools.ietf.org/html/rfc4287#section-4.2.7.2.

Constructors

RelText Text 
RelURI URI 

Instances

Eq Rel Source # 

Methods

(==) :: Rel -> Rel -> Bool #

(/=) :: Rel -> Rel -> Bool #

Show Rel Source # 

Methods

showsPrec :: Int -> Rel -> ShowS #

show :: Rel -> String #

showList :: [Rel] -> ShowS #

data Text e Source #

Instances

Eq e => Eq (Text e) Source # 

Methods

(==) :: Text e -> Text e -> Bool #

(/=) :: Text e -> Text e -> Bool #

Show e => Show (Text e) Source # 

Methods

showsPrec :: Int -> Text e -> ShowS #

show :: Text e -> String #

showList :: [Text e] -> ShowS #

IsString (Text e) Source # 

Methods

fromString :: String -> Text e #

data Link Source #

Defines a reference to a web resource as per https://tools.ietf.org/html/rfc4287#section-4.2.7.

data MediaType Source #

A media type. xsd:string { pattern = ".+/.+" }

Constructors

MediaType ByteString 

data UTCTime :: * #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Eq UTCTime 

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) #

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

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

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

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

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

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

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

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

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

Ord UTCTime 
NFData UTCTime 

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
ParseTime UTCTime 

unsafeURI :: String -> URI Source #

Convenience function to create a URIs from hardcoded strings. /This function is partial so only use this if you're hardcoding the URI string and you're sure that it's valid./

data URI :: * #

Represents a general universal resource identifier using its component parts.

For example, for the URI

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

the components are:

Constructors

URI 

Fields

Instances

Eq URI 

Methods

(==) :: URI -> URI -> Bool #

(/=) :: URI -> URI -> Bool #

Data URI 

Methods

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

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

toConstr :: URI -> Constr #

dataTypeOf :: URI -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c URI) #

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

gmapT :: (forall b. Data b => b -> b) -> URI -> URI #

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

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

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

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

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

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

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

Ord URI 

Methods

compare :: URI -> URI -> Ordering #

(<) :: URI -> URI -> Bool #

(<=) :: URI -> URI -> Bool #

(>) :: URI -> URI -> Bool #

(>=) :: URI -> URI -> Bool #

max :: URI -> URI -> URI #

min :: URI -> URI -> URI #

Show URI 

Methods

showsPrec :: Int -> URI -> ShowS #

show :: URI -> String #

showList :: [URI] -> ShowS #

Generic URI 

Associated Types

type Rep URI :: * -> * #

Methods

from :: URI -> Rep URI x #

to :: Rep URI x -> URI #

NFData URI 

Methods

rnf :: URI -> () #

type Rep URI