Move the caching support code into its own Nix.Cache module

This commit is contained in:
John Wiegley 2018-04-11 20:19:59 -07:00
parent 22175aa927
commit b621ffee0a
4 changed files with 48 additions and 44 deletions

View File

@ -2,7 +2,7 @@
--
-- see: https://github.com/sol/hpack
--
-- hash: 13b58b4fb9f715dd28ba6e47cb5feeb0da553ac1b16b356677c580f8b71f70e6
-- hash: 00ae617f664cd9dc67f4a6551a0e3c0eee19899f21b44c6dda24e17618a8fb5d
name: hnix
version: 0.5.0
@ -30,6 +30,7 @@ library
Nix
Nix.Atoms
Nix.Builtins
Nix.Cache
Nix.Context
Nix.Effects
Nix.Eval

View File

@ -1,19 +1,13 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiWayIf #-}
-- {-# LANGUAGE QuasiQuotes #-}
#ifdef __linux__
#define USE_COMPACT 1
#endif
module Main where
import Control.DeepSeq
import qualified Control.Exception as Exc
import Control.Monad
import Control.Monad.ST
import qualified Data.ByteString.Lazy as BS
import Data.Text (Text, pack)
import qualified Data.Text.IO as Text
import qualified Nix
@ -28,13 +22,6 @@ import System.IO
import System.FilePath
import Text.PrettyPrint.ANSI.Leijen hiding ((<$>))
#ifdef USE_COMPACT
import qualified Data.Compact as C
import qualified Data.Compact.Serialize as C
#else
import qualified Codec.Serialise as S
#endif
data Options = Options
{ verbose :: Bool
, debug :: Bool
@ -109,21 +96,8 @@ main = do
opts <- execParser optsDef
case readFrom opts of
Just path -> do
#ifdef USE_COMPACT
eres <- C.unsafeReadCompact path
case eres of
Left err -> error $ "Error reading cache file: " ++ err
Right expr -> do
let file = addExtension (dropExtension path) "nix"
process opts (Just file) (C.getCompact expr)
#else
eres <- S.deserialiseOrFail <$> BS.readFile path
case eres of
Left err -> error $ "Error reading cache file: " ++ show err
Right expr -> do
let file = addExtension (dropExtension path) "nix"
process opts (Just file) expr
#endif
let file = addExtension (dropExtension path) "nix"
process opts (Just file) =<< readCache path
Nothing -> case expression opts of
Just s -> handleResult opts Nothing (parseNixTextLoc s)
Nothing -> case fromFile opts of
@ -177,21 +151,9 @@ main = do
putStrLn . printNix =<< Nix.evalLoc mpath expr
| debug opts ->
print $ stripAnnotation expr
| cache opts ->
#ifdef USE_COMPACT
do cx <- C.compact expr
case mpath of
Nothing -> return ()
Just path -> do
let file = addExtension (dropExtension path) "nixc"
C.writeCompact file cx
#else
case mpath of
Nothing -> return ()
Just path -> do
let file = addExtension (dropExtension path) "nixc"
BS.writeFile file (S.serialise expr)
#endif
| cache opts, Just path <- mpath -> do
let file = addExtension (dropExtension path) "nixc"
writeCache file expr
| parseOnly opts ->
void $ Exc.evaluate $ force expr
| otherwise ->

39
src/Nix/Cache.hs Normal file
View File

@ -0,0 +1,39 @@
{-# LANGUAGE CPP #-}
module Nix.Cache where
import qualified Data.ByteString.Lazy as BS
import Nix.Expr.Types.Annotated
#ifdef __linux__
#define USE_COMPACT 1
#endif
#ifdef USE_COMPACT
import qualified Data.Compact as C
import qualified Data.Compact.Serialize as C
#else
import qualified Codec.Serialise as S
#endif
readCache :: FilePath -> IO NExprLoc
readCache path = do
#ifdef USE_COMPACT
eres <- C.unsafeReadCompact path
case eres of
Left err -> error $ "Error reading cache file: " ++ err
Right expr -> return $ C.getCompact expr
#else
eres <- S.deserialiseOrFail <$> BS.readFile path
case eres of
Left err -> error $ "Error reading cache file: " ++ show err
Right expr -> return expr
#endif
writeCache :: FilePath -> NExprLoc -> IO ()
writeCache path expr =
#ifdef USE_COMPACT
C.writeCompact path =<< C.compact expr
#else
BS.writeFile path (S.serialise expr)
#endif

View File

@ -111,6 +111,8 @@ instance Lift (Fix NExprF) where
-- | The monomorphic expression type is a fixed point of the polymorphic one.
type NExpr = Fix NExprF
instance Serialise NExpr
-- | A single line of the bindings section of a let expression or of a set.
data Binding r
= NamedVar !(NAttrPath r) !r