-- | Formats Haskell source code as HTML with inline CSS.
module Language.Haskell.HsColour.InlineCSS (hscolour,top'n'tail) where

import Language.Haskell.HsColour.Anchors
import Language.Haskell.HsColour.Classify as Classify
import Language.Haskell.HsColour.Colourise
import Language.Haskell.HsColour.HTML (renderAnchors, renderComment,
                                       renderNewLinesAnchors, escape)
import Text.Printf

-- | Formats Haskell source code as a complete HTML document with inline styling
hscolour :: ColourPrefs	-- ^ Preferences for styling.
         -> Bool   -- ^ Whether to include anchors.
         -> String -- ^ Haskell source code.
         -> String -- ^ An HTML document containing the coloured 
                   --   Haskell source code.
hscolour :: ColourPrefs -> Bool -> String -> Stringhscolour prefs :: ColourPrefsprefs anchor :: Boolanchor =
  pre :: String -> Stringpre
  (.) :: (b -> c) -> (a -> b) -> a -> c. (if anchor :: Boolanchor 
        then renderNewLinesAnchors :: String -> StringrenderNewLinesAnchors
             (.) :: (b -> c) -> (a -> b) -> a -> c. concatMap :: (a -> [b]) -> [a] -> [b]concatMap (renderAnchors :: (a -> String) -> Either String a -> StringrenderAnchors (renderToken :: ColourPrefs -> (TokenType, String) -> StringrenderToken prefs :: ColourPrefsprefs))
             (.) :: (b -> c) -> (a -> b) -> a -> c. insertAnchors ::
  [(TokenType, String)] -> [Either Anchor (TokenType, String)]insertAnchors
        else concatMap :: (a -> [b]) -> [a] -> [b]concatMap (renderToken :: ColourPrefs -> (TokenType, String) -> StringrenderToken prefs :: ColourPrefsprefs))
  (.) :: (b -> c) -> (a -> b) -> a -> c. tokenise :: String -> [(TokenType, String)]tokenise

top'n'tail :: String -> String -> String
top'n'tail :: String -> String -> Stringtop'n'tail title :: Stringtitle  = (cssPrefix :: [Char] -> StringcssPrefix title :: Stringtitle (++) :: [a] -> [a] -> [a]++) (.) :: (b -> c) -> (a -> b) -> a -> c. ((++) :: [a] -> [a] -> [a]++cssSuffix :: StringcssSuffix)

pre :: String -> String
pre :: String -> Stringpre =   ("<pre style=\"font-family:Consolas, Monaco, Monospace;\">"(++) :: [a] -> [a] -> [a]++)
      (.) :: (b -> c) -> (a -> b) -> a -> c. ((++) :: [a] -> [a] -> [a]++"</pre>")

renderToken :: ColourPrefs -> (TokenType,String) -> String
renderToken :: ColourPrefs -> (TokenType, String) -> StringrenderToken prefs :: ColourPrefsprefs (cls :: TokenTypecls,text :: Stringtext) =
  stylise :: [Highlight] -> String -> Stringstylise (colourise :: ColourPrefs -> TokenType -> [Highlight]colourise prefs :: ColourPrefsprefs cls :: TokenTypecls) ($) :: (a -> b) -> a -> b$
  if cls :: TokenTypecls (==) :: Eq a => a -> a -> Bool== Comment :: TokenTypeComment then renderComment :: String -> StringrenderComment text :: Stringtext else escape :: String -> Stringescape text :: Stringtext

stylise :: [Highlight] -> String -> String
stylise :: [Highlight] -> String -> Stringstylise hs :: [Highlight]hs s :: Strings = "<span style=\"" (++) :: [a] -> [a] -> [a]++ concatMap :: (a -> [b]) -> [a] -> [b]concatMap style :: Highlight -> Stringstyle hs :: [Highlight]hs (++) :: [a] -> [a] -> [a]++ "\">" (++) :: [a] -> [a] -> [a]++s :: Strings(++) :: [a] -> [a] -> [a]++ "</span>"

cssPrefix :: [Char] -> StringcssPrefix title :: [Char]title = unlines :: [String] -> Stringunlines
    ["<?xml version=\"1.0\" encoding=\"UTF-8\">"
    ,"<!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://code.haskell.org/~malcolm/hscolour/ -->"
    ,"<title>"(++) :: [a] -> [a] -> [a]++title :: Stringtitle(++) :: [a] -> [a] -> [a]++"</title>"
    ,"</head>"
    ,"<body style=\"background-color: #131313; color: #ffffff;\">"
    ]
    
cssSuffix :: StringcssSuffix = unlines :: [String] -> Stringunlines
    ["</body>"
    ,"</html>"
    ]

style :: Highlight -> String
style :: Highlight -> Stringstyle Normal         = ""
style Bold           = "font-weight: bold;"
style Dim            = "font-weight: lighter;"
style Underscore     = "text-decoration: underline;"
style Blink          = "text-decoration:  blink;"
style ReverseVideo   = ""
style Concealed      = "text-decoration:  line-through;"
style (Foreground c :: Colourc) = "color: "(++) :: [a] -> [a] -> [a]++csscolour :: Colour -> Stringcsscolour c :: Colourc(++) :: [a] -> [a] -> [a]++";"
style (Background c :: Colourc) = "background-color: "(++) :: [a] -> [a] -> [a]++csscolour :: Colour -> Stringcsscolour c :: Colourc(++) :: [a] -> [a] -> [a]++";"
style Italic         = "font-style: italic;"

csscolour :: Colour -> String
csscolour :: Colour -> Stringcsscolour Black   = "#000000"
csscolour Red     = "#ff0000"
csscolour Green   = "#00ff00"
csscolour Yellow  = "#ffff00"
csscolour Blue    = "#0000ff"
csscolour Magenta = "#ff00ff"
csscolour Cyan    = "#00ffff"
csscolour White   = "#ffffff"
csscolour (Rgb r :: Word8r g :: Word8g b :: Word8b) = printf :: PrintfType r => String -> rprintf "#%02x%02x%02x" r :: Word8r g :: Word8g b :: Word8b