12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias{- |
e9458b1a7a19a63aa4c179f9ab20f4d50681c168Jens ElknerModule : ./THF/PrintTHF.hs
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasDescription : A printer for the TPTP-THF Syntax
e21e5f0fa66bf80e14cfd3f571e09b3952e46ad9Alexis TsogiasCopyright : (c) A. Tsogias, DFKI Bremen 2011
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasLicense : GPLv2 or higher, see LICENSE.txt
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
fc09e0a6af734edbd944dd8082bb51985c233b43Alexis TsogiasMaintainer : Alexis.Tsogias@dfki.de
fc09e0a6af734edbd944dd8082bb51985c233b43Alexis TsogiasStability : provisional
fc09e0a6af734edbd944dd8082bb51985c233b43Alexis TsogiasPortability : portable
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
e21e5f0fa66bf80e14cfd3f571e09b3952e46ad9Alexis TsogiasA printer for the TPTP-THF Input Syntax v5.1.0.2 taken from
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias<http://www.cs.miami.edu/~tptp/TPTP/SyntaxBNF.html>
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias-}
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogiasmodule THF.PrintTHF where
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogiasimport THF.As
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogiasimport Data.Char
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogiasimport Common.Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasimport Common.DocUtils
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroederimport Common.Id (Token)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder{- -----------------------------------------------------------------------------
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von SchroederPretty Instances for the THF and THF0 Syntax.
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von SchroederMost methods match those of As.hs
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder----------------------------------------------------------------------------- -}
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasprintTPTPTHF :: [TPTP_THF] -> Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasprintTPTPTHF [] = empty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasprintTPTPTHF (t : rt) = case t of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TPTP_THF_Annotated_Formula {} -> pretty t $++$ printTPTPTHF rt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder _ -> pretty t $+$ printTPTPTHF rt
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty TPTP_THF where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty t = case t of
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias TPTP_THF_Annotated_Formula n fr f a ->
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias text "thf" <> parens (pretty n <> comma
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <+> pretty fr <> comma
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <+> pretty f <> pretty a)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias <> text "."
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TPTP_Include i -> pretty i
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TPTP_Comment c -> pretty c
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TPTP_Defined_Comment dc -> pretty dc
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TPTP_System_Comment sc -> pretty sc
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TPTP_Header h -> prettyHeader h
748e10233de9e76b68be4f0050c7b4a7f3c415eaAlexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyHeader :: [Comment] -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyHeader = foldr (($+$) . pretty) empty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Comment where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty c = case c of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Comment_Line s -> text "%" <> (text . show) s
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Comment_Block sl -> text "/*"
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder $+$ prettyCommentBlock (lines $ show sl)
e21e5f0fa66bf80e14cfd3f571e09b3952e46ad9Alexis Tsogias $+$ text "*/"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedComment where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty dc = case dc of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Defined_Comment_Line s -> text "%$" <> (text . show) s
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Defined_Comment_Block sl -> text "/*$"
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder $+$ prettyCommentBlock (lines $ show sl)
e21e5f0fa66bf80e14cfd3f571e09b3952e46ad9Alexis Tsogias $+$ text "*/"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty SystemComment where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty sc = case sc of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder System_Comment_Line s -> text "%$$" <> (text . show) s
e21e5f0fa66bf80e14cfd3f571e09b3952e46ad9Alexis Tsogias System_Comment_Block sl -> text "/*$$"
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder $+$ prettyCommentBlock (lines $ show sl)
e21e5f0fa66bf80e14cfd3f571e09b3952e46ad9Alexis Tsogias $+$ text "*/"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyCommentBlock :: [String] -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyCommentBlock = foldr (($+$) . text) empty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Include where
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder pretty (I_Include fn nl) = text "include" <> parens (prettySingleQuoted fn
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> maybe empty (\ c -> comma <+> prettyNameList c) nl) <> text "."
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Annotations where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty a = case a of
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias Annotations s o -> comma <+> pretty s <> prettyOptionalInfo o
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Null -> empty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty FormulaRole where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty fr = text $ map toLower (show fr)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty f = case f of
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias TF_THF_Logic_Formula lf -> pretty lf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TF_THF_Sequent s -> pretty s
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0F_THF_Typed_Const tc -> pretty tc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFLogicFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty lf = case lf of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TLF_THF_Binary_Formula bf -> pretty bf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TLF_THF_Unitary_Formula uf -> pretty uf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TLF_THF_Type_Formula tf -> pretty tf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TLF_THF_Sub_Type st -> pretty st
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFBinaryFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty bf = case bf of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBF_THF_Binary_Tuple bt -> pretty bt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBF_THF_Binary_Type bt -> pretty bt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBF_THF_Binary_Pair uf1 pc uf2 ->
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty uf1 <+> pretty pc <+> pretty uf2
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFBinaryTuple where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty bt = case bt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBT_THF_Or_Formula ufl -> sepBy (map pretty ufl) orSign
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBT_THF_And_Formula ufl -> sepBy (map pretty ufl) andSign
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBT_THF_Apply_Formula ufl -> sepBy (map pretty ufl) applySign
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFUnitaryFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tuf = case tuf of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TUF_THF_Quantified_Formula qf -> pretty qf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TUF_THF_Unary_Formula uc lf -> pretty uc <+> parens (pretty lf)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TUF_THF_Atom a -> pretty a
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TUF_THF_Tuple t -> prettyTuple t
4e95ffc23b9c5f0b5980ab6f1cacbe7bd9789851Alexis Tsogias TUF_THF_Conditional lf1 lf2 lf3 ->
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias text "$itef" <> parens (pretty lf1
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> comma <+> pretty lf2
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> comma <+> pretty lf3)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TUF_THF_Logic_Formula_Par l -> parens (pretty l)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0UF_THF_Abstraction vl uf -> text "^" <+>
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias brackets (prettyVariableList vl) <+> text ":" <+> pretty uf
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFQuantifiedFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty qf = case qf of
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias TQF_THF_Quantified_Formula tq vl uf -> pretty tq <+>
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias brackets (prettyVariableList vl) <+> text ":" <+> pretty uf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0QF_THF_Quantified_Var q vl uf -> pretty q <+>
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias brackets (prettyVariableList vl) <+> text ":" <+> pretty uf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0QF_THF_Quantified_Novar tq uf ->
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tq <+> parens (pretty uf)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyVariableList :: THFVariableList -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyVariableList vl = sepByCommas (map pretty vl)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFVariable where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty v = case v of
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder TV_THF_Typed_Variable va tlt -> prettyUpperWord va
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <+> text ":" <+> pretty tlt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TV_Variable var -> prettyUpperWord var
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFTypedConst where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ttc = case ttc of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TC_Typed_Const c tlt -> prettyConstant c <+> text ":"
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <+> pretty tlt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TC_THF_TypedConst_Par tc -> parens (pretty tc)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFTypeFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ttf = case ttf of
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias TTF_THF_Type_Formula tf tlt -> pretty tf <+> text ":" <+> pretty tlt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TTF_THF_Typed_Const c tlt -> prettyConstant c <+> text ":"
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <+> pretty tlt
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFTypeableFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tbf = case tbf of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TTyF_THF_Atom a -> pretty a
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TTyF_THF_Tuple t -> prettyTuple t
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TTyF_THF_Logic_Formula lf -> parens $ pretty lf
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFSubType where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (TST_THF_Sub_Type c1 c2) =
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias prettyConstant c1 <+> text "<<" <+> prettyConstant c2
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFTopLevelType where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tlt = case tlt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TTLT_THF_Logic_Formula lf -> pretty lf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TLT_Constant c -> prettyConstant c
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TLT_Variable v -> prettyUpperWord v
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TLT_Defined_Type dt -> pretty dt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TLT_System_Type st -> prettyAtomicSystemWord st
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0TLT_THF_Binary_Type bt -> pretty bt
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFUnitaryType where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ut = case ut of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TUT_THF_Unitary_Formula uf -> pretty uf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0UT_Constant c -> prettyConstant c
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0UT_Variable v -> prettyUpperWord v
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0UT_Defined_Type dt -> pretty dt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0UT_System_Type st -> prettyAtomicSystemWord st
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias T0UT_THF_Binary_Type_Par bt -> parens (pretty bt)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFBinaryType where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tbt = case tbt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBT_THF_Mapping_Type utl -> sepBy (map pretty utl) arrowSign
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBT_THF_Xprod_Type utl -> sepBy (map pretty utl) starSign
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TBT_THF_Union_Type utl -> sepBy (map pretty utl) plusSign
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias T0BT_THF_Binary_Type_Par bt -> parens (pretty bt)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFAtom where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty a = case a of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TA_Term t -> pretty t
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TA_THF_Conn_Term ct -> pretty ct
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TA_Defined_Type dt -> pretty dt
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias TA_Defined_Plain_Formula dp -> pretty dp
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TA_System_Type st -> prettyAtomicSystemWord st
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias TA_System_Atomic_Formula st -> pretty st
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0A_Constant c -> prettyConstant c
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0A_Defined_Constant dc -> prettyAtomicDefinedWord dc
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0A_System_Constant sc -> prettyAtomicSystemWord sc
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0A_Variable v -> prettyUpperWord v
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyTuple :: THFTuple -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyTuple ufl = brackets $ sepByCommas (map pretty ufl)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFSequent where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (TS_THF_Sequent_Par s) = parens $ pretty s
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (TS_THF_Sequent t1 t2) =
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias prettyTuple t1 <+> text "-->" <+> prettyTuple t2
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFConnTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ct = case ct of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TCT_THF_Pair_Connective pc -> pretty pc
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TCT_Assoc_Connective ac -> pretty ac
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias TCT_THF_Unary_Connective uc -> pretty uc
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0CT_THF_Quantifier q -> pretty q
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFQuantifier where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty q = case q of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_ForAll -> text "!"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_Exists -> text "?"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_Lambda_Binder -> text "^"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_Dependent_Product -> text "!>"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_Dependent_Sum -> text "?*"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_Indefinite_Description -> text "@+"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder TQ_Definite_Description -> text "@-"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0Q_PiForAll -> text "!!"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0Q_SigmaExists -> text "??"
4e95ffc23b9c5f0b5980ab6f1cacbe7bd9789851Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Quantifier where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty q = case q of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0Q_ForAll -> text "!"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0Q_Exists -> text "?"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFPairConnective where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty pc = case pc of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Infix_Equality -> text "="
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Infix_Inequality -> text "!="
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Equivalent -> text "<=>"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Implication -> text "=>"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder IF -> text "<="
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder XOR -> text "<~>"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder NOR -> text "~|"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder NAND -> text "~&"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty THFUnaryConnective where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty uc = case uc of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Negation -> text "~"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder PiForAll -> text "!!"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias SigmaExists -> text "??"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty AssocConnective where
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder pretty AND = text "&"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder pretty OR = text "|"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedType where
677f88c528e9ec35e830f3eece2626dcde9895c6Jonathan von Schroeder pretty DT_oType = text "$o"
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty dt = text $ '$' : drop 3 (show dt)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedPlainFormula where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty dpf = case dpf of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DPF_Defined_Prop dp -> pretty dp
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DPF_Defined_Formula dp a -> pretty dp <> parens (prettyArguments a)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedProp where
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder pretty DP_True = text "$true"
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder pretty DP_False = text "$false"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedPred where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty dp = text $ '$' : map toLower (show dp)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Term where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty t = case t of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T_Function_Term ft -> pretty ft
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T_Variable v -> prettyUpperWord v
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty FunctionTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ft = case ft of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder FT_Plain_Term pt -> pretty pt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder FT_Defined_Term dt -> pretty dt
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder FT_System_Term st -> pretty st
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty PlainTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty pt = case pt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder PT_Constant c -> prettyConstant c
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder PT_Plain_Term f a -> pretty f <> parens (prettyArguments a)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyConstant :: Constant -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyConstant = pretty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty dt = case dt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DT_Defined_Atom da -> pretty da
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DT_Defined_Atomic_Term dpt -> pretty dpt
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedAtom where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty da = case da of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DA_Number n -> pretty n
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DA_Distinct_Object dio -> prettyDistinctObject dio
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedPlainTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty dpt = case dpt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DPT_Defined_Constant df -> pretty df
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DPT_Defined_Function df a -> pretty df <> parens (prettyArguments a)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DefinedFunctor where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty df = text $ '$' : map toLower (show df)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty SystemTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty st = case st of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder ST_System_Constant sf -> prettyAtomicSystemWord sf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder ST_System_Term sf a -> prettyAtomicSystemWord sf
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> parens (prettyArguments a)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyArguments :: Arguments -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyArguments = sepByCommas . map pretty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty PrincipalSymbol where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ps = case ps of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder PS_Functor f -> pretty f
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder PS_Variable v -> prettyUpperWord v
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Source where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty s = case s of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder S_Dag_Source ds -> pretty ds
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias S_Internal_Source it oi -> text "introduced" <> parens (
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty it <> prettyOptionalInfo oi)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder S_External_Source es -> pretty es
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder S_Sources ss -> sepByCommas (map pretty ss)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder S_Unknown -> text "unknown"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty DagSource where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ds = case ds of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DS_Name n -> pretty n
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder DS_Inference_Record aw ui pl -> text "inference"
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> parens (pretty aw <> comma <+> prettyUsefulInfo ui
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> comma <+> brackets (sepByCommas (map pretty pl)))
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty ParentInfo where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (PI_Parent_Info s mgl) =
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias let gl = maybe empty (\ c -> text ":" <> prettyGeneralList c) mgl
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias in pretty s <> gl
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty IntroType where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty it = text (drop 3 (show it))
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty ExternalSource where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty es = case es of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder ES_File_Source fs -> pretty fs
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder ES_Theory tn oi -> text "theory" <> parens (
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tn <> prettyOptionalInfo oi)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias ES_Creator_Source aw oi -> text "creator" <> parens (
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty aw <> prettyOptionalInfo oi)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty FileSource where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (FS_File fn mn) =
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias let n = maybe empty (\ c -> comma <+> pretty c) mn
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder in text "file" <> parens (prettySingleQuoted fn <> n)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty TheoryName where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty tn = text $ map toLower (show tn)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyOptionalInfo :: OptionalInfo -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyOptionalInfo = maybe empty (\ ui -> comma <+> prettyUsefulInfo ui)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyUsefulInfo :: UsefulInfo -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyUsefulInfo = brackets . sepByCommas . map pretty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty InfoItem where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ii = case ii of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder II_Formula_Item fi -> pretty fi
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder II_Inference_Item infi -> pretty infi
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder II_General_Function gf -> pretty gf
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty FormulaItem where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty fi = case fi of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder FI_Description_Item aw -> text "description" <> parens (pretty aw)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder FI_Iquote_Item aw -> text "iquote" <> parens (pretty aw)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty InferenceItem where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty ii = case ii of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder II_Inference_Status is -> pretty is
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder II_Assumptions_Record nl -> text "assumptions"
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> parens (brackets (prettyNameList nl))
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias II_New_Symbol_Record aw psl -> text "new_symbols" <> parens (pretty aw
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> comma <+> brackets (sepByCommas (map pretty psl)))
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder II_Refutation fs -> text "refutation" <> parens (pretty fs)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty InferenceStatus where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty is = case is of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder IS_Status s -> text "status" <> parens (pretty s)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder IS_Inference_Info aw1 aw2 gl -> pretty aw1 <> parens (pretty aw2
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias <> comma <+> prettyGeneralList gl)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty StatusValue where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty sv = text $ map toLower (show sv)
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyNameList :: NameList -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyNameList = sepByCommas . map pretty
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty GeneralTerm where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty gt = case gt of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GT_General_Data gd -> pretty gd
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias GT_General_Data_Term gd gt1 -> pretty gd <+> text ":" <+> pretty gt1
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GT_General_List gl -> prettyGeneralList gl
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty GeneralData where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty gd = case gd of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_Atomic_Word aw -> pretty aw
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_General_Function gf -> pretty gf
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_Variable v -> prettyUpperWord v
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_Number n -> pretty n
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_Distinct_Object dio -> prettyDistinctObject dio
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_Formula_Data fd -> pretty fd
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder GD_Bind v fd -> text "bind" <> parens (
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder prettyUpperWord v <> comma <+> pretty fd)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty GeneralFunction where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (GF_General_Function aw gts) =
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty aw <> parens (prettyGeneralTerms gts)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty FormulaData where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty (THF_Formula thff) = text "$thf" <> parens (pretty thff)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyGeneralList :: GeneralList -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyGeneralList = brackets . prettyGeneralTerms
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyGeneralTerms :: GeneralTerms -> Doc
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis TsogiasprettyGeneralTerms = sepByCommas . map pretty
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Name where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty n = case n of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder N_Atomic_Word a -> pretty a
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder N_Integer s -> text $ show s
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder T0N_Unsigned_Integer s -> text $ show s
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty AtomicWord where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty a = case a of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder A_Single_Quoted s -> prettySingleQuoted s
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder A_Lower_Word l -> prettyLowerWord l
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyAtomicSystemWord :: Token -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyAtomicSystemWord asw = text ("$$" ++ show asw)
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyAtomicDefinedWord :: Token -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyAtomicDefinedWord adw = text ('$' : show adw)
4e95ffc23b9c5f0b5980ab6f1cacbe7bd9789851Alexis Tsogias
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogiasinstance Pretty Number where
409eb8adf8c7ee0609aef256b67f5dfad2fb6386Alexis Tsogias pretty n = case n of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Num_Integer i -> text $ show i
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder Num_Rational ra -> text $ show ra
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder Num_Real re -> text $ show re
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettySingleQuoted :: Token -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettySingleQuoted s = text "\'" <> (text . show) s <> text "\'"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyDistinctObject :: Token -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyDistinctObject s = text "\"" <> (text . show) s <> text "\""
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyLowerWord :: Token -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyLowerWord uw' = let uw = show uw' in text (toLower (head uw) : tail uw)
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyUpperWord :: Token -> Doc
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von SchroederprettyUpperWord uw' = let uw = show uw' in text (toUpper (head uw) : tail uw)
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasorSign :: Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasorSign = text "|"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasandSign :: Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasandSign = text "&"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasapplySign :: Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasapplySign = text "@"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasarrowSign :: Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasarrowSign = text ">"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasstarSign :: Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasstarSign = text "*"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasplusSign :: Doc
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiasplusSign = text "+"
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis Tsogias
12f6880fc0909e8dc2bdebc5f299a6a8bfa8afa7Alexis TsogiassepBy :: [Doc] -> Doc -> Doc
1e622ddf5a057555db1924ddc88475c695c6f7f2Alexis TsogiassepBy ls s = case ls of
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder (c : []) -> c
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder (c : d) -> c <+> s <+> sepBy d s
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder [] -> empty