atom-basic-0.2.1: Basic Atom feed construction

Safe HaskellSafe-Inferred
LanguageHaskell2010

Web.Atom

Description

You use this package by specifying XMLGen generator functions, constructing a Feed, and then using the feedXML function to generate the XML.

For example, using the xml package to generate our XML could look like this:

{-# LANGUAGE OverloadedStrings #-}

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

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
    }

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

main = putStrLn $ showTopElement $ Atom.feedXML xmlgen feed

Or you might want to use the xml-conduit package:

{-# LANGUAGE OverloadedStrings #-}

import           Data.Map.Lazy     (fromList)
import qualified Data.Text         as T
import qualified Data.Text.Lazy.IO as TL
import           Data.Time         (UTCTime (..), fromGregorian)
import           Text.XML
import qualified Web.Atom          as Atom

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
    }

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

main = TL.putStrLn $ renderText def (Document (Prologue [] Nothing []) xml [])
  where xml = Atom.feedXML xmlgen feed

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) 
Show e => Show (Feed e) 

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) 
Show e => Show (Entry e) 

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) 
Show e => Show (Source e) 

data Category Source

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

Instances

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

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

data Text e Source

Instances

Eq e => Eq (Text e) 
Show e => Show (Text e) 
IsString (Text e) 

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.

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

uriScheme :: String
foo:
uriAuthority :: Maybe URIAuth
//anonymous@www.haskell.org:42
uriPath :: String
/ghc
uriQuery :: String
?query
uriFragment :: String
#frag

Instances

Eq URI 
Data URI 
Ord URI 
Show URI 
Generic URI 
NFData URI 
Typeable * URI 
type Rep URI = D1 D1URI (C1 C1_0URI ((:*:) ((:*:) (S1 S1_0_0URI (Rec0 String)) (S1 S1_0_1URI (Rec0 (Maybe URIAuth)))) ((:*:) (S1 S1_0_2URI (Rec0 String)) ((:*:) (S1 S1_0_3URI (Rec0 String)) (S1 S1_0_4URI (Rec0 String))))))