module Data.GraphViz.Printing
( module Text.PrettyPrint.Leijen.Text.Monadic
, DotCode
, renderDot
, PrintDot(..)
, unqtText
, dotText
, printIt
, addQuotes
, unqtEscaped
, printEscaped
, wrap
, commaDel
, printField
, angled
, fslash
, printColorScheme
) where
import Data.GraphViz.Util
import Data.GraphViz.State
import Data.GraphViz.Attributes.ColorScheme
import Text.PrettyPrint.Leijen.Text.Monadic hiding ( SimpleDoc(..)
, renderPretty
, renderCompact
, displayT
, displayIO
, putDoc
, hPutDoc
, Pretty(..)
, bool
, string
, width
, (<$>))
import qualified Text.PrettyPrint.Leijen.Text.Monadic as PP
import qualified Data.Text.Lazy as T
import Data.Text.Lazy(Text)
import Data.Char(toLower)
import qualified Data.Set as Set
import Data.Word(Word8, Word16)
import Control.Monad(ap, when)
import Control.Monad.Trans.State
type DotCode = State GraphvizState Doc
instance Show DotCode where
showsPrec d = showsPrec d . renderDot
renderDot :: DotCode -> Text
renderDot = PP.displayT . PP.renderPretty 0.4 80
. (`evalState` initialState)
class PrintDot a where
unqtDot :: a -> DotCode
toDot :: a -> DotCode
toDot = unqtDot
unqtListToDot :: [a] -> DotCode
unqtListToDot = list . mapM unqtDot
listToDot :: [a] -> DotCode
listToDot = dquotes . unqtListToDot
printIt :: (PrintDot a) => a -> Text
printIt = renderDot . toDot
instance PrintDot Int where
unqtDot = int
instance PrintDot Integer where
unqtDot = text . T.pack . show
instance PrintDot Word8 where
unqtDot = int . fromIntegral
instance PrintDot Word16 where
unqtDot = int . fromIntegral
instance PrintDot Double where
unqtDot d = if d == fromIntegral di
then int di
else double d
where
di = round d
toDot d = if any ((==) 'e' . toLower) $ show d
then dquotes ud
else ud
where
ud = unqtDot d
unqtListToDot = hcat . punctuate colon . mapM unqtDot
listToDot [d] = toDot d
listToDot ds = dquotes $ unqtListToDot ds
instance PrintDot Bool where
unqtDot True = text "true"
unqtDot False = text "false"
instance PrintDot Char where
unqtDot = char
toDot = qtChar
unqtListToDot = unqtDot . T.pack
listToDot = toDot . T.pack
instance PrintDot Text where
unqtDot = unqtString
toDot = qtString
unqtText :: Text -> DotCode
unqtText = unqtDot
dotText :: Text -> DotCode
dotText = toDot
qtChar :: Char -> DotCode
qtChar c
| restIDString c = char c
| otherwise = dquotes $ char c
needsQuotes :: Text -> Bool
needsQuotes str
| T.null str = True
| isKeyword str = True
| isIDString str = False
| isNumString str = False
| otherwise = True
addQuotes :: Text -> DotCode -> DotCode
addQuotes = bool id dquotes . needsQuotes
unqtString :: Text -> DotCode
unqtString "" = empty
unqtString str = unqtEscaped [] str
qtString :: Text -> DotCode
qtString = printEscaped []
instance (PrintDot a) => PrintDot [a] where
unqtDot = unqtListToDot
toDot = listToDot
wrap :: DotCode -> DotCode -> DotCode -> DotCode
wrap b a d = b <> d <> a
commaDel :: (PrintDot a, PrintDot b) => a -> b -> DotCode
commaDel a b = unqtDot a <> comma <> unqtDot b
printField :: (PrintDot a) => Text -> a -> DotCode
printField f v = text f <> equals <> toDot v
unqtEscaped :: [Char] -> Text -> DotCode
unqtEscaped cs = text . addEscapes cs
printEscaped :: [Char] -> Text -> DotCode
printEscaped cs str = addQuotes str' $ text str'
where
str' = addEscapes cs str
addEscapes :: [Char] -> Text -> Text
addEscapes cs = foldr escape T.empty . withNext
where
cs' = Set.fromList $ quote : slash : cs
slash = '\\'
quote = '"'
escape (c,c') str
| c == slash && c' `Set.member` escLetters = c `T.cons` str
| c `Set.member` cs' = slash `T.cons` (c `T.cons` str)
| c == '\n' = slash `T.cons` ('n' `T.cons` str)
| otherwise = c `T.cons` str
escLetters = Set.fromList ['N', 'G', 'E', 'T', 'H', 'L', 'n', 'l', 'r']
withNext "" = []
withNext str = T.zip `ap` ((`T.snoc` ' ') . T.tail) $ str
angled :: DotCode -> DotCode
angled = wrap langle rangle
fslash :: DotCode
fslash = char '/'
instance PrintDot ColorScheme where
unqtDot = printColorScheme True
printColorScheme :: Bool -> ColorScheme -> DotCode
printColorScheme scs cs = do when scs $ setColorScheme cs
case cs of
X11 -> unqtText "X11"
SVG -> unqtText "svg"
Brewer bs -> unqtDot bs
instance PrintDot BrewerScheme where
unqtDot (BScheme n l) = unqtDot n <> unqtDot l
instance PrintDot BrewerName where
unqtDot Accent = unqtText "accent"
unqtDot Blues = unqtText "blues"
unqtDot Brbg = unqtText "brbg"
unqtDot Bugn = unqtText "bugn"
unqtDot Bupu = unqtText "bupu"
unqtDot Dark2 = unqtText "dark2"
unqtDot Gnbu = unqtText "gnbu"
unqtDot Greens = unqtText "greens"
unqtDot Greys = unqtText "greys"
unqtDot Oranges = unqtText "oranges"
unqtDot Orrd = unqtText "orrd"
unqtDot Paired = unqtText "paired"
unqtDot Pastel1 = unqtText "pastel1"
unqtDot Pastel2 = unqtText "pastel2"
unqtDot Piyg = unqtText "piyg"
unqtDot Prgn = unqtText "prgn"
unqtDot Pubu = unqtText "pubu"
unqtDot Pubugn = unqtText "pubugn"
unqtDot Puor = unqtText "puor"
unqtDot Purd = unqtText "purd"
unqtDot Purples = unqtText "purples"
unqtDot Rdbu = unqtText "rdbu"
unqtDot Rdgy = unqtText "rdgy"
unqtDot Rdpu = unqtText "rdpu"
unqtDot Rdylbu = unqtText "rdylbu"
unqtDot Rdylgn = unqtText "rdylgn"
unqtDot Reds = unqtText "reds"
unqtDot Set1 = unqtText "set1"
unqtDot Set2 = unqtText "set2"
unqtDot Set3 = unqtText "set3"
unqtDot Spectral = unqtText "spectral"
unqtDot Ylgn = unqtText "ylgn"
unqtDot Ylgnbu = unqtText "ylgnbu"
unqtDot Ylorbr = unqtText "ylorbr"
unqtDot Ylorrd = unqtText "ylorrd"