atom-basic-0.2.0: 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

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

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

data XMLGen elem node name attr Source

Constructors

XMLGen 

Fields

xmlElem :: name -> [attr] -> [node] -> elem
 
xmlName :: Maybe Text -> Text -> name
 
xmlAttr :: name -> Text -> attr
 
xmlTextNode :: Text -> node
 
xmlElemNode :: elem -> node
 

data Person Source

Constructors

Person 

Instances

data Email Source

Constructors

Email Text 

Instances

data Rel Source

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 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.

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))))))