CreateTheories.hs revision 807d5fddaa5dd8924321c73400fcf875a9ed9a9c
{-# OPTIONS -cpp #-}
{- |
Module : $Header$
Description : creating Isabelle thoeries via translations
Copyright : (c) C. Maeder, Uni Bremen 2005
License : similar to LGPL, see HetCATS/LICENSE.txt or LIZENZ.txt
Maintainer : Christian.Maeder@dfki.de
Stability : provisional
Portability : non-portable(Logic)
dumping a LibEnv to Isabelle theory files
-}
module Isabelle.CreateTheories where
import Common.Id
import Common.Result
import Common.Doc
import Logic.Coerce
import Logic.Comorphism
import Syntax.AS_Library
import Static.DevGraph
import Logic.Prover
import Common.ProofUtils
import Isabelle.IsaPrint
import Isabelle.Translate
import Isabelle.Logic_Isabelle
import CASL.Logic_CASL
import HasCASL.Logic_HasCASL
import Comorphisms.CASL2PCFOL
import Comorphisms.CASL2HasCASL
import Comorphisms.PCoClTyConsHOL2IsabelleHOL
#ifdef PROGRAMATICA
import Comorphisms.Haskell2IsabelleHOLCF
import Haskell.Logic_Haskell
#endif
printTheory :: LIB_NAME -> SIMPLE_ID -> G_theory -> Result Doc
printTheory ln sn (G_theory lid sign0 _ sens0 _) = do
let th = (sign0, toNamedList sens0)
r1 = coerceBasicTheory lid CASL "" th
r1' = do
th0 <- r1
th1 <- wrapMapTheory CASL2PCFOL th0
th2 <- wrapMapTheory CASL2HasCASL th1
wrapMapTheory PCoClTyConsHOL2IsabelleHOL th2
#ifdef PROGRAMATICA
r2 = coerceBasicTheory lid Haskell "" th
r2' = do
th0 <- r2
wrapMapTheory Haskell2IsabelleHOLCF th0
#else
r2 = r1
r2' = r1'
#endif
r4 = coerceBasicTheory lid HasCASL "" th
r4' = do
th0 <- r4
wrapMapTheory PCoClTyConsHOL2IsabelleHOL th0
r5 = coerceBasicTheory lid Isabelle "" th
r3 = case maybeResult r1 of
Nothing -> case maybeResult r2 of
Nothing -> case maybeResult r4 of
Nothing -> r5
_ -> r4'
_ -> r2'
_ -> r1'
(sign, sens) <- r3
let tn = reverse (takeWhile (/= '/')
$ reverse $ show $ getLIB_ID ln)
++ "_" ++ tokStr sn
return $ printIsaTheory tn sign
$ prepareSenNames transString
$ toNamedList $ toThSens sens