module Panda.View.Widget.Footer where
  
import Panda.Helper.Env
import Prelude hiding ((.), (/), (^), id, span)
import qualified Panda.Config.Global as G


static_footer c = toHtml
  [ toHtml $ copyright
  , toHtml $ "2008 "
  , toHtml $ G.blog_title
  , toHtml $ br
  , toHtml $ "Powered by "
  , toHtml $ hotlink G.panda_url << "Panda"
  , toHtml $ " using "
  , toHtml $ hotlink "http://www.haskell.org/" << "Haskell"
  ]
  
custom_footer _ | G.footer.isJust =  G.footer.fromJust.markup
custom_footer x = static_footer x

footer c = div_class_id c "footer" << custom_footer c