Add 'yesod-newsfeed/' from commit 'e68851b9db97519e0cade5dc10bb964c270b4a9a'

git-subtree-dir: yesod-newsfeed
git-subtree-mainline: 83813b1df4
git-subtree-split: e68851b9db
This commit is contained in:
Michael Snoyman 2011-07-22 08:59:57 +03:00
commit 894336a482
7 changed files with 299 additions and 0 deletions

25
yesod-newsfeed/LICENSE Normal file
View File

@ -0,0 +1,25 @@
The following license covers this documentation, and the source code, except
where otherwise indicated.
Copyright 2010, Michael Snoyman. All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions are met:
* Redistributions of source code must retain the above copyright notice, this
list of conditions and the following disclaimer.
* Redistributions in binary form must reproduce the above copyright notice,
this list of conditions and the following disclaimer in the documentation
and/or other materials provided with the distribution.
THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS "AS IS" AND ANY EXPRESS OR
IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO
EVENT SHALL THE COPYRIGHT HOLDERS BE LIABLE FOR ANY DIRECT, INDIRECT,
INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA,
OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF
LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE
OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF
ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.

0
yesod-newsfeed/README Normal file
View File

View File

@ -0,0 +1,87 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE CPP #-}
---------------------------------------------------------
--
-- Module : Yesod.AtomFeed
-- Copyright : Michael Snoyman
-- License : BSD3
--
-- Maintainer : Michael Snoyman <michael@snoyman.com>
-- Stability : Stable
-- Portability : portable
--
-- Generating atom news feeds.
--
---------------------------------------------------------
-- | Generation of Atom newsfeeds.
module Yesod.AtomFeed
( atomFeed
, atomLink
, RepAtom (..)
, module Yesod.FeedTypes
) where
import Yesod.Content
import Yesod.Handler
import Yesod.Widget
import Yesod.FeedTypes
import Text.Hamlet (Hamlet, xhamlet, hamlet)
import qualified Data.ByteString.Char8 as S8
import Control.Monad (liftM)
newtype RepAtom = RepAtom Content
instance HasReps RepAtom where
chooseRep (RepAtom c) _ = return (typeAtom, c)
atomFeed :: Monad mo => Feed (Route master) -> GGHandler sub master mo RepAtom
atomFeed = liftM RepAtom . hamletToContent . template
template :: Feed url -> Hamlet url
template arg =
#if __GLASGOW_HASKELL__ >= 700
[xhamlet|
#else
[$xhamlet|
#endif
\<?xml version="1.0" encoding="utf-8"?>
<feed xmlns="http://www.w3.org/2005/Atom"
<title>#{feedTitle arg}
<link rel=self href=@{feedLinkSelf arg}
<link href=@{feedLinkHome arg}
<updated>#{formatW3 $ feedUpdated arg}
<id>@{feedLinkHome arg}
$forall entry <- feedEntries arg
^{entryTemplate entry}
|]
entryTemplate :: FeedEntry url -> Hamlet url
entryTemplate arg =
#if __GLASGOW_HASKELL__ >= 700
[xhamlet|
#else
[$xhamlet|
#endif
<entry
<id>@{feedEntryLink arg}
<link href=@{feedEntryLink arg}
<updated>#{formatW3 $ feedEntryUpdated arg}
<title>#{feedEntryTitle arg}
<content type=html>
\<![CDATA[
\#{feedEntryContent arg}
]]>
|]
-- | Generates a link tag in the head of a widget.
atomLink :: Route m
-> String -- ^ title
-> GWidget s m ()
atomLink u title = addHamletHead
#if __GLASGOW_HASKELL__ >= 700
[hamlet|
#else
[$hamlet|
#endif
<link href=@{u} type=#{S8.unpack typeAtom} rel="alternate" title=#{title}
|]

View File

@ -0,0 +1,40 @@
-------------------------------------------------------------------------------
--
-- Module : Yesod.Feed
-- Copyright : Patrick Brisbin
-- License : as-is
--
-- Maintainer : Patrick Brisbin <me@pbrisbin.com>
-- Stability : Stable
-- Portability : Portable
--
-- Generic Feed and Feed Entry data types that can be used as either an
-- Rss feed or an Atom feed (or both, or other).
--
-- Atom spec: <http://en.wikipedia.org/wiki/Atom_(standard)>
-- Rss spec: <http://www.rssboard.org/rss-specification>
--
-------------------------------------------------------------------------------
module Yesod.Feed
( newsFeed
, RepAtomRss (..)
, module Yesod.FeedTypes
) where
import Yesod.FeedTypes
import Yesod.AtomFeed
import Yesod.RssFeed
import Yesod.Content (HasReps (chooseRep), typeAtom, typeRss)
import Yesod.Handler (Route, GGHandler)
data RepAtomRss = RepAtomRss RepAtom RepRss
instance HasReps RepAtomRss where
chooseRep (RepAtomRss (RepAtom a) (RepRss r)) = chooseRep
[ (typeAtom, a)
, (typeRss, r)
]
newsFeed :: Monad mo => Feed (Route master) -> GGHandler sub master mo RepAtomRss
newsFeed f = do
a <- atomFeed f
r <- rssFeed f
return $ RepAtomRss a r

View File

@ -0,0 +1,34 @@
module Yesod.FeedTypes
( Feed (..)
, FeedEntry (..)
) where
import Text.Hamlet (Html)
import Data.Time.Clock (UTCTime)
import Data.Text (Text)
-- | The overal feed
data Feed url = Feed
{ feedTitle :: Text
, feedLinkSelf :: url
, feedLinkHome :: url
-- | note: currently only used for Rss
, feedDescription :: Html
-- | note: currently only used for Rss, possible values:
-- <http://www.rssboard.org/rss-language-codes>
, feedLanguage :: Text
, feedUpdated :: UTCTime
, feedEntries :: [FeedEntry url]
}
-- | Each feed entry
data FeedEntry url = FeedEntry
{ feedEntryLink :: url
, feedEntryUpdated :: UTCTime
, feedEntryTitle :: Text
, feedEntryContent :: Html
}

View File

@ -0,0 +1,84 @@
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE CPP #-}
-------------------------------------------------------------------------------
--
-- Module : Yesod.RssFeed
-- Copyright : Patrick Brisbin
-- License : as-is
--
-- Maintainer : Patrick Brisbin <me@pbrisbin.com>
-- Stability : Stable
-- Portability : Portable
--
-------------------------------------------------------------------------------
module Yesod.RssFeed
( rssFeed
, rssLink
, RepRss (..)
, module Yesod.FeedTypes
) where
import Yesod.Handler
import Yesod.Content
import Yesod.Widget
import Yesod.FeedTypes
import Text.Hamlet (Hamlet, xhamlet, hamlet)
import qualified Data.ByteString.Char8 as S8
import Control.Monad (liftM)
newtype RepRss = RepRss Content
instance HasReps RepRss where
chooseRep (RepRss c) _ = return (typeRss, c)
-- | Generate the feed
rssFeed :: Monad mo => Feed (Route master) -> GGHandler sub master mo RepRss
rssFeed = liftM RepRss . hamletToContent . template
template :: Feed url -> Hamlet url
template arg =
#if __GLASGOW_HASKELL__ >= 700
[xhamlet|
#else
[$xhamlet|
#endif
\<?xml version="1.0" encoding="utf-8"?>
<rss version="2.0" xmlns:atom="http://www.w3.org/2005/Atom"
<channel
<atom:link href=@{feedLinkSelf arg} rel="self" type=#{S8.unpack typeRss}
<title> #{feedTitle arg}
<link> @{feedLinkHome arg}
<description> #{feedDescription arg}
<lastBuildDate>#{formatRFC822 $ feedUpdated arg}
<language> #{feedLanguage arg}
$forall entry <- feedEntries arg
^{entryTemplate entry}
|]
entryTemplate :: FeedEntry url -> Hamlet url
entryTemplate arg =
#if __GLASGOW_HASKELL__ >= 700
[xhamlet|
#else
[$xhamlet|
#endif
<item
<title> #{feedEntryTitle arg}
<link> @{feedEntryLink arg}
<guid> @{feedEntryLink arg}
<pubDate> #{formatRFC822 $ feedEntryUpdated arg}
<description>#{feedEntryContent arg}
|]
-- | Generates a link tag in the head of a widget.
rssLink :: Route m
-> String -- ^ title
-> GWidget s m ()
rssLink u title = addHamletHead
#if __GLASGOW_HASKELL__ >= 700
[hamlet|
#else
[$hamlet|
#endif
<link href=@{u} type=#{S8.unpack typeRss} rel="alternate" title=#{title}
|]

View File

@ -0,0 +1,29 @@
name: yesod-newsfeed
version: 0.3.0
license: BSD3
license-file: LICENSE
author: Michael Snoyman, Patrick Brisbin
maintainer: Michael Snoyman <michael@snoyman.com>
synopsis: Helper functions and data types for producing News feeds.
category: Web, Yesod
stability: Stable
cabal-version: >= 1.6
build-type: Simple
homepage: http://docs.yesodweb.com/
library
build-depends: base >= 4 && < 5
, yesod-core >= 0.9 && < 0.10
, time >= 1.1.4 && < 1.3
, hamlet >= 0.9 && < 0.10
, bytestring >= 0.9 && < 0.10
, text >= 0.9 && < 1.0
exposed-modules: Yesod.AtomFeed
, Yesod.RssFeed
, Yesod.Feed
other-modules: Yesod.FeedTypes
ghc-options: -Wall
source-repository head
type: git
location: git://github.com/snoyberg/yesod-newsfeed.git