-- | Formats Haskell source code as HTML with CSS.
module Language.Haskell.HsColour.CSS (hscolour, hscolourFragment) where

import Language.Haskell.HsColour.Anchors
import Language.Haskell.HsColour.Classify as Classify
import Language.Haskell.HsColour.HTML (renderAnchors, renderComment, escape)

-- | Formats Haskell source code as a complete HTML document with CSS.
hscolour :: Bool   -- ^ Whether to include anchors
         -> String -- ^ Haskell source code.
         -> String -- ^ An HTML document containing the coloured 
                   --   Haskell source code.
hscolour anchor = top'n'tail . hscolourFragment anchor

-- | Formats Haskell source code as an HTML fragment with CSS.
--   No stylesheet link is included in the output.
hscolourFragment :: Bool   -- ^ Whether to include anchors
                 -> String -- ^ Haskell source code.
                 -> String -- ^ An HTML fragment containing the coloured 
                           --   Haskell source code.
hscolourFragment anchor = 
    pre . (if anchor 
           then concatMap (renderAnchors renderToken) . insertAnchors
           else concatMap renderToken) . tokenise

top'n'tail :: String -> String
top'n'tail  = (cssPrefix++) . (++cssSuffix)

pre :: String -> String
pre = ("<pre>"++) . (++"</pre>")

renderToken :: (TokenType,String) -> String
renderToken (Space,text) = text
renderToken (cls,text)   = "<span class='" ++ cssClass cls ++ "'>" ++
                           (if cls == Comment then renderComment text else escape text) ++
                           "</span>"

cssClass Keyword  = "keyword"
cssClass Keyglyph = "keyglyph"
cssClass Layout   = "layout"
cssClass Comment  = "comment"
cssClass Conid    = "conid"
cssClass Varid    = "varid"
cssClass Conop    = "conop"
cssClass Varop    = "varop"
cssClass String   = "str"
cssClass Char     = "chr"
cssClass Number   = "num"
cssClass Error    = "sel"

cssPrefix = unlines
    ["<!DOCTYPE html PUBLIC \"-//W3C//DTD XHTML 1.0 Strict//EN\" \"http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd\">"
    ,"<html>"
    ,"<head>"
    ,"<!-- Generated by HsColour, http://www.cs.york.ac.uk/fp/darcs/hscolour/ -->"
    ,"<title>Haskell Code by HsColour</title>"
    ,"<link type='text/css' rel='stylesheet' href='hscolour.css' />"
    ,"</head>"
    ,"<body>"
    ]
    
cssSuffix = unlines
    ["</body>"
    ,"</html>"
    ]