658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias{- |
e9458b1a7a19a63aa4c179f9ab20f4d50681c168Jens ElknerModule : ./THF/HasCASL2THF0Buildins.hs
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasDescription : create legal THF mixfix identifier
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasCopyright : (c) A. Tsogias, DFKI Bremen 2011
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasLicense : GPLv2 or higher, see LICENSE.txt
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasMaintainer : Alexis.Tsogias@dfki.de
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasStability : provisional
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasPortability : portable
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiastranslations for the buildins of HasCasl
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias-}
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasmodule THF.HasCASL2THF0Buildins where
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport Common.AS_Annotation
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport Common.DocUtils
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport Common.Result
c95de7451b35950f21196b610dab702730221a98Alexis Tsogiasimport Common.Id
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport HasCASL.Builtin
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport THF.As
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport THF.Cons
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport THF.Sign
990d9f14e81ad0ffb0fbec4224725b631f5fae27Jonathan von Schroederimport THF.ParseTHF
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport THF.Translate
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport THF.PrintTHF ()
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport Text.ParserCombinators.Parsec
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport Data.Maybe
c95de7451b35950f21196b610dab702730221a98Alexis Tsogiasimport qualified Data.Set as Set
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasimport qualified Data.Map as Map
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder{- -----------------------------------------------------------------------------
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von SchroederAssumps
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder----------------------------------------------------------------------------- -}
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
c95de7451b35950f21196b610dab702730221a98Alexis TsogiaspreDefHCAssumps :: Set.Set Id -> ConstMap
c95de7451b35950f21196b610dab702730221a98Alexis TsogiaspreDefHCAssumps ids =
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder let asl = [ (botId, botci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (defId, defci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (notId, o2ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (negId, o2ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder-- , (whenElse, "hcc" ++ show whenElse)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (trueId, o1ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (falseId, o1ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (eqId, a2o1ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (exEq, a2o1ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (resId, resci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (andId, o3ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (orId, o3ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (eqvId, o3ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (implId, o3ci)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (infixIf, o3ci) ]
c95de7451b35950f21196b610dab702730221a98Alexis Tsogias in Map.fromList $ map
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder (\ (i, tf) -> let c = (fromJust . maybeResult . transAssumpId) i
c95de7451b35950f21196b610dab702730221a98Alexis Tsogias in (c , tf c))
c95de7451b35950f21196b610dab702730221a98Alexis Tsogias (filter (\ (i, _) -> Set.member i ids) asl)
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiaso1ci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiaso1ci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constType = OType
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiaso2ci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiaso2ci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constType = MapType OType OType
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiaso3ci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiaso3ci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constType = MapType OType (MapType OType OType)
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasa2o1ci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasa2o1ci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder , constType = MapType (VType $ mkSimpleId "A")
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder (MapType (VType $ mkSimpleId "A") OType)
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasresci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasresci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder , constType = MapType (VType $ mkSimpleId "A")
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder (MapType (VType $ mkSimpleId "B")
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder (VType $ mkSimpleId "A"))
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasbotci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasbotci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constType = OType
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasdefci :: Constant -> ConstInfo
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogiasdefci c = ConstInfo
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder { constId = c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constName = mkConstsName c
8fb127028cb7dd361e348a3252e33487f73428bcJonathan von Schroeder , constType = MapType (VType $ mkSimpleId "A") OType
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias , constAnno = Null }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder{- -----------------------------------------------------------------------------
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von SchroederAxioms
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder----------------------------------------------------------------------------- -}
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
8394b397aadaf0c2bfc19c0628f17f83f031a759Jonathan von SchroederpreDefAxioms :: Set.Set Id -> [Named THFFormula]
c95de7451b35950f21196b610dab702730221a98Alexis TsogiaspreDefAxioms ids =
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder let axl = [ (notId, notFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (negId, notFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (trueId, trueFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (falseId, falseFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (andId, andFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (orId, orFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (eqvId, eqvFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (implId, implFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (infixIf, ifFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (resId, resFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (botId, botFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder , (defId, defFS)
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder{- , (whenElse, "hcc" ++ show whenElse) -} ]
c95de7451b35950f21196b610dab702730221a98Alexis Tsogias in map (\ (i, fs) -> mkNSD
c95de7451b35950f21196b610dab702730221a98Alexis Tsogias (fromJust $ maybeResult $ transAssumpId i) fs)
c95de7451b35950f21196b610dab702730221a98Alexis Tsogias (filter (\ (i, _) -> Set.member i ids) axl)
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
8394b397aadaf0c2bfc19c0628f17f83f031a759Jonathan von SchroedermkNSD :: Constant -> (Constant -> String) -> Named THFFormula
80b1e7cd6565f9eceb8c8b4fa15defe610250a99Christian MaedermkNSD c f = (makeNamed (show . pretty . mkDefName $ c) $ genTHFFormula c f)
80b1e7cd6565f9eceb8c8b4fa15defe610250a99Christian Maeder { isDef = True }
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasgenTHFFormula :: Constant -> (Constant -> String) -> THFFormula
990d9f14e81ad0ffb0fbec4224725b631f5fae27Jonathan von SchroedergenTHFFormula c f = case parse parseTHF "" (f c) of
f5427040f85fbd2621ffbd86e6b4ce605d15b4b9Jonathan von Schroeder Left msg -> error (unlines
f5427040f85fbd2621ffbd86e6b4ce605d15b4b9Jonathan von Schroeder ["Fatal error while generating the predefined Sentence"
f5427040f85fbd2621ffbd86e6b4ce605d15b4b9Jonathan von Schroeder ++ " for: " ++ show (pretty c),
f5427040f85fbd2621ffbd86e6b4ce605d15b4b9Jonathan von Schroeder "Parsing " ++ show (f c) ++ " failed with message",
f5427040f85fbd2621ffbd86e6b4ce605d15b4b9Jonathan von Schroeder show msg])
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias Right x -> thfFormulaAF $ head x
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder{- -----------------------------------------------------------------------------
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroederformulas as Strings
87d946b3c13ffd7f6391aa796e786c2b31b122b1Jonathan von Schroeder----------------------------------------------------------------------------- -}
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasnotFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasnotFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [A : $o] : ~(A))")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasfalseFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasfalseFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = $false")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiastrueFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiastrueFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = $true")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasandFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasandFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : $o, Y : $o] : (X & Y))")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasorFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasorFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : $o, Y : $o] : (X | Y))")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiaseqvFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiaseqvFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : $o, Y : $o] : (X <=> Y))")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasimplFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasimplFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : $o, Y : $o] : (X => Y))")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasifFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasifFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : $o, Y : $o] : (Y => X))")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasresFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasresFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : A, Y : B] : X)")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasbotFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasbotFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = $false")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasdefFS :: Constant -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasdefFS c =
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias let ns = (show . pretty . mkDefName) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias cs = (show . pretty) c
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias in encTHF (ns ++ defnS ++ cs ++ " = (^ [X : A] : $true)")
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasdefnS :: String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasdefnS = ", definition, "
658187feb755694eb5ff29561bda7109c22c743cAlexis Tsogias
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasencTHF :: String -> String
658187feb755694eb5ff29561bda7109c22c743cAlexis TsogiasencTHF s = "thf(" ++ s ++ ")."