module Data.Rewriting.Rule.Pretty (
prettyRule
) where
import Data.Rewriting.Rule.Type
import Data.Rewriting.Term (prettyTerm)
import Text.PrettyPrint.ANSI.Leijen
prettyRule :: Doc -> (f -> Doc) -> (v -> Doc) -> Rule f v -> Doc
prettyRule :: forall f v. Doc -> (f -> Doc) -> (v -> Doc) -> Rule f v -> Doc
prettyRule Doc
arr f -> Doc
fun v -> Doc
var (Rule Term f v
l Term f v
r) = Int -> Doc -> Doc
hang Int
2 (Doc -> Doc) -> Doc -> Doc
forall a b. (a -> b) -> a -> b
$ Term f v -> Doc
term Term f v
l Doc -> Doc -> Doc
<+> Doc
arr Doc -> Doc -> Doc
</> Term f v -> Doc
term Term f v
r where
term :: Term f v -> Doc
term = (f -> Doc) -> (v -> Doc) -> Term f v -> Doc
forall f v. (f -> Doc) -> (v -> Doc) -> Term f v -> Doc
prettyTerm f -> Doc
fun v -> Doc
var
instance (Pretty f, Pretty v) => Pretty (Rule f v) where
pretty :: Rule f v -> Doc
pretty = Doc -> (f -> Doc) -> (v -> Doc) -> Rule f v -> Doc
forall f v. Doc -> (f -> Doc) -> (v -> Doc) -> Rule f v -> Doc
prettyRule (String -> Doc
text String
"->") f -> Doc
forall a. Pretty a => a -> Doc
pretty v -> Doc
forall a. Pretty a => a -> Doc
pretty