Skip to content
Snippets Groups Projects
Commit 248b76b4 authored by Mark Lentczner's avatar Mark Lentczner
Browse files

move CSS Theme functions into Themes.hs

parent 87b91ac8
No related branches found
No related tags found
No related merge requests found
......@@ -26,6 +26,7 @@ import Haddock.Backends.Xhtml.Decl
import Haddock.Backends.Xhtml.DocMarkup
import Haddock.Backends.Xhtml.Layout
import Haddock.Backends.Xhtml.Names
import Haddock.Backends.Xhtml.Themes
import Haddock.Backends.Xhtml.Types
import Haddock.Backends.Xhtml.Utils
import Haddock.ModuleTree
......@@ -154,7 +155,7 @@ copyHtmlBits odir libdir _maybe_css = do
copyFile (joinPath [libhtmldir, f]) (joinPath [odir, f])
--copyFile css_file css_destination
mapM_ copyLibFile cssFiles
mapM_ copyLibFile [ iconFile, plusFile, minusFile, jsFile, framesFile ]
mapM_ copyLibFile [ plusFile, minusFile, jsFile, framesFile ]
headHtml :: String -> Maybe String -> Html
......
-----------------------------------------------------------------------------
-- |
-- Module : Haddock.Backends.Html.Themes
-- Copyright : (c) Mark Lentczner 2010
-- License : BSD-like
--
-- Maintainer : haddock@projects.haskell.org
-- Stability : experimental
-- Portability : portable
-----------------------------------------------------------------------------
module Haddock.Backends.Xhtml.Themes (
CssTheme(..),
cssFiles, styleSheet, stylePickers, styleMenu
)
where
import Haddock.Backends.Xhtml.Utils (onclick)
import Haddock.Utils (iconFile)
import Data.List (nub)
import Text.XHtml hiding ( name, title, p, quote )
import qualified Text.XHtml as XHtml
-- Standard set of style sheets, first is the preferred
data CssTheme = CssTheme {
themeName :: String,
themeHref :: String,
themeFiles :: [FilePath]
}
themes :: [CssTheme]
themes = [
CssTheme "Classic" "xhaddock.css" ["xhaddock.css", iconFile],
CssTheme "Tibbe" "thaddock.css" ["thaddock.css", iconFile],
CssTheme "Snappy" "shaddock.css" ["shaddock.css", iconFile]
]
cssFiles :: [String]
cssFiles = nub (concatMap themeFiles themes)
styleSheet :: Html
styleSheet = toHtml $ zipWith mkLink themes rels
where
rels = ("stylesheet" : repeat "alternate stylesheet")
mkLink (CssTheme aTitle aRef _) aRel =
(thelink ! [href aRef, rel aRel, thetype "text/css", XHtml.title aTitle]) noHtml
stylePickers :: [Html]
stylePickers = map mkPicker themes
where
mkPicker (CssTheme aTitle aRef _) =
let js = "setActiveStyleSheet('" ++ aRef ++ "'); return false;" in
anchor ! [href "#", onclick js] << aTitle
styleMenu :: Html
styleMenu = thediv ! [identifier "style-menu-holder"] << [
anchor ! [ href "#", onclick js ] << "Style\9662",
unordList stylePickers ! [ identifier "style-menu", theclass "hide" ]
]
where
js = "styleMenu(); return false;"
......@@ -23,9 +23,9 @@ module Haddock.Backends.Xhtml.Utils (
arrow, comma, dcolon, dot, darrow, equals, forallSymbol, quote,
hsep,
collapsebutton, collapseId,
cssFiles, styleSheet, stylePickers, styleMenu
) where
......@@ -202,11 +202,9 @@ cssThemes = [
("Snappy", "shaddock.css")
]
cssFiles :: [String]
cssFiles = map snd cssThemes
styleSheet :: Html
styleSheet = toHtml $ zipWith mkLink cssThemes rels
where
......@@ -214,15 +212,13 @@ styleSheet = toHtml $ zipWith mkLink cssThemes rels
mkLink (aTitle, aFile) aRel =
(thelink ! [href aFile, rel aRel, thetype "text/css", XHtml.title aTitle]) noHtml
stylePickers :: [Html]
stylePickers = map mkPicker cssThemes
where
mkPicker (aTitle, aFile) =
mkPicker (aTitle, aFile) =
let js = "setActiveStyleSheet('" ++ aFile ++ "'); return false;" in
anchor ! [href "#", onclick js] << aTitle
styleMenu :: Html
styleMenu = thediv ! [identifier "style-menu-holder"] << [
anchor ! [ href "#", onclick js ] << "Style\9662",
......@@ -230,4 +226,4 @@ styleMenu = thediv ! [identifier "style-menu-holder"] << [
]
where
js = "styleMenu(); return false;"
\ No newline at end of file
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment