mirror of
https://github.com/GaloisInc/cryptol.git
synced 2024-12-16 20:03:27 +03:00
Write out the typechecker prelude when necessary
Bundle the typechecker prelude (CryptolTC.z3) with the executable, so that it's able to write it out and re-use it when necessary. Fixes #404
This commit is contained in:
parent
f89c23b594
commit
7fc50a9cbb
@ -215,7 +215,7 @@ findModule n = do
|
||||
|
||||
handleNotFound =
|
||||
case n of
|
||||
m | m == preludeName -> writePreludeContents
|
||||
m | m == preludeName -> io writePreludeContents
|
||||
_ -> moduleNotFound n =<< getSearchPath
|
||||
|
||||
-- generate all possible search paths
|
||||
|
@ -8,13 +8,16 @@
|
||||
--
|
||||
-- Compile the prelude into the executable as a last resort
|
||||
|
||||
{-# LANGUAGE Trustworthy #-}
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
|
||||
module Cryptol.Prelude (writePreludeContents) where
|
||||
module Cryptol.Prelude (
|
||||
writePreludeContents,
|
||||
writeTcPreludeContents,
|
||||
) where
|
||||
|
||||
import Cryptol.ModuleSystem.Monad
|
||||
|
||||
import System.Directory (getTemporaryDirectory)
|
||||
import System.IO (hClose, hPutStr, openTempFile)
|
||||
@ -25,10 +28,24 @@ preludeContents = [there|lib/Cryptol.cry|]
|
||||
|
||||
-- | Write the contents of the Prelude to a temporary file so that
|
||||
-- Cryptol can load the module.
|
||||
writePreludeContents :: ModuleM FilePath
|
||||
writePreludeContents = io $ do
|
||||
writePreludeContents :: IO FilePath
|
||||
writePreludeContents = do
|
||||
tmpdir <- getTemporaryDirectory
|
||||
(path, h) <- openTempFile tmpdir "Cryptol.cry"
|
||||
hPutStr h preludeContents
|
||||
hClose h
|
||||
return path
|
||||
|
||||
|
||||
cryptolTcContents :: String
|
||||
cryptolTcContents = [there|lib/CryptolTC.z3|]
|
||||
|
||||
-- | Write the contents of the Prelude to a temporary file so that
|
||||
-- Cryptol can load the module.
|
||||
writeTcPreludeContents :: IO FilePath
|
||||
writeTcPreludeContents = do
|
||||
tmpdir <- getTemporaryDirectory
|
||||
(path, h) <- openTempFile tmpdir "CryptolTC.z3"
|
||||
hPutStr h cryptolTcContents
|
||||
hClose h
|
||||
return path
|
||||
|
@ -19,6 +19,7 @@ module Cryptol.TypeCheck.Monad
|
||||
import Cryptol.ModuleSystem.Name (FreshM(..),Supply)
|
||||
import Cryptol.Parser.Position
|
||||
import qualified Cryptol.Parser.AST as P
|
||||
import Cryptol.Prelude (writeTcPreludeContents)
|
||||
import Cryptol.TypeCheck.AST
|
||||
import Cryptol.TypeCheck.Subst
|
||||
import Cryptol.TypeCheck.Unify(mgu, Result(..), UnificationError(..))
|
||||
@ -34,8 +35,7 @@ import qualified Data.Map as Map
|
||||
import qualified Data.Set as Set
|
||||
import Data.Map (Map)
|
||||
import Data.Set (Set)
|
||||
import Data.List(find, minimumBy, groupBy, sortBy, foldl',
|
||||
intercalate)
|
||||
import Data.List(find, minimumBy, groupBy, sortBy, foldl')
|
||||
import Data.Maybe(mapMaybe)
|
||||
import Data.Function(on)
|
||||
import MonadLib hiding (mapM)
|
||||
@ -168,11 +168,10 @@ runInferM info (IM m) = CrySAT.withSolver (inpSolverConfig info) $ \solver ->
|
||||
-- The actual order does not matter
|
||||
cmpRange (Range x y z) (Range a b c) = compare (x,y,z) (a,b,c)
|
||||
|
||||
loadCryTCPrel _ [] =
|
||||
panic "runInferM" [ "Failed to find file: CryptolTC.z3"
|
||||
, "Searched paths: " ++
|
||||
intercalate ":" (inpSearchPath info)
|
||||
]
|
||||
loadCryTCPrel s [] =
|
||||
do file <- writeTcPreludeContents
|
||||
CrySAT.loadFile s file
|
||||
|
||||
loadCryTCPrel s (p : ps) =
|
||||
do let file = p </> "CryptolTC.z3"
|
||||
yes <- doesFileExist file
|
||||
|
Loading…
Reference in New Issue
Block a user