module Ideas.Text.Latex
( Latex, ToLatex(..), (<>)
, array, commas, brackets, parens
, command
) where
import Data.List
import Data.Monoid
import Data.String
newtype Latex = L { showLatex :: String }
instance Show Latex where
show = showLatex
instance IsString Latex where
fromString = L
instance Monoid Latex where
mempty = L []
L xs `mappend` L ys = L (mappend xs ys)
class ToLatex a where
toLatex :: a -> Latex
toLatexPrec :: Int -> a -> Latex
toLatexList :: [a] -> Latex
toLatex = toLatexPrec 0
toLatexPrec = const toLatex
toLatexList = brackets . commas . map toLatex
instance ToLatex a => ToLatex [a] where
toLatex = toLatexList
toLatexPrec = const toLatexList
instance ToLatex a => ToLatex (Maybe a) where
toLatexPrec = maybe mempty . toLatexPrec
instance ToLatex Char where
toLatex = fromString . return
toLatexList = fromString
instance ToLatex Int where
toLatex = fromString . show
commas :: [Latex] -> Latex
commas = mconcat . intersperse ",\\:"
brackets, parens :: Latex -> Latex
brackets s = "[" <> s <> "]"
parens s = "(" <> s <> ")"
array :: String -> [[Latex]] -> Latex
array s rows = "\\begin{array}{" <> fromString s <> "}"
<> mconcat (intersperse "\\\\" (map (mconcat . intersperse " & ") rows))
<> "\\end{array}"
command :: String -> Latex
command s = toLatex ("\\" ++ s ++ " ")