module Data.Logic.Propositional.Tables
    ( Printer
    , colourBool
    , showBool
    , truthTable
    , truthTableP
    ) where
import Data.Logic.Propositional.Core
import Data.Map (fold)
import Text.PrettyPrint.ANSI.Leijen (green, text, red)
type Printer = (Expr -> String, Bool -> String)
truthTable :: Expr -> String
truthTable = truthTableP (show, colourBool)
truthTableP :: Printer -> Expr -> String
truthTableP (expPrinter, boolPrinter) expr = unlines [header, separator, body]
  where
    header    = unwords vs ++ " | " ++ expPrinter expr
    body      = init . unlines $ map (showAssignment boolPrinter expr) as
    separator = concat $ replicate sepLength "-"
    sepLength = length vs * 2 + length (expPrinter expr) + 2
    as        = assignments expr
    vs        = variables   expr
showAssignment :: (Bool -> String) -> Expr -> Mapping -> String
showAssignment printer expr a = showVarValues ++ " | " ++ showExprValue
  where
    showVarValues = unwords $ fold ((:) . printer) [] a
    showExprValue = printer $ interpret expr a
showBool :: Bool -> String
showBool True  = "T"
showBool False = "F"
colourBool :: Bool -> String
colourBool True  = show . green . text $ "T"
colourBool False = show . red . text $ "F"