Copyright | (c) Justus Sagemüller 2017 |
---|---|
License | GPL v3 |
Maintainer | (@) jsagemue $ uni-koeln.de |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
- cached :: (Hash h, Binary a, Typeable a, Binary h) => Prehashed h a -> IO a
- cached' :: (Hash h, Binary a, Typeable a, Binary h) => CacheAccessConf -> Prehashed h a -> IO a
- fundamental :: QuasiQuoter
- (<#>) :: Hash h => Prehashed h (a -> b) -> Prehashed h a -> Prehashed h b
- liftPH2 :: Hash h => Prehashed h (a -> b -> c) -> Prehashed h a -> Prehashed h b -> Prehashed h c
- data CacheAccessConf
- cachingLocation :: Lens' CacheAccessConf (Maybe FilePath)
- usePrecalculated :: Lens' CacheAccessConf Bool
- calculateIfNecessary :: Lens' CacheAccessConf Bool
- writeUsedVersion :: Lens' CacheAccessConf Bool
- burnAfterReading :: Lens' CacheAccessConf Bool
- cachedValueInFile :: Binary a => CacheAccessConf -> FilePath -> a -> IO a
The caching actions
cached :: (Hash h, Binary a, Typeable a, Binary h) => Prehashed h a -> IO a Source #
Look up a value in the project-global cache store. If it has already been computed during an earlier program run, simply re-use that result, else calculate it and store for future runs to use.
This is a shortcut for
, which corresponds to the optionscached'
def
cachingLocation
.~ (Just ".hscache/lazy-hashed")usePrecalculated
.~ TruecalculateIfNecessary
.~ TruewriteUsedVersion
.~ TrueburnAfterReading
.~ False
This function is polymorphic in the type of hash it uses, but this can require boilerplate signature and you'll probably want to choose one such type and stick to it for your entire project. We offer specialised versions for this purpose; see Data.LazyHash.Cache.Int.
:: (Hash h, Binary a, Typeable a, Binary h) | |
=> CacheAccessConf | |
-> Prehashed h a | Value to cache |
-> IO a |
Write, re-use or modify the cache, depending on the configuration.
Prehashing tools
fundamental :: QuasiQuoter #
Transform an ordinary value into a pre-hashed one. This hashes the source code contained in the quasi quote, making the assumption that the behaviour of anything invoked therein will never change.
Applying this to anything but named, fixed-predefined values (standard library functions etc.) is probably a bad idea.
(<#>) :: Hash h => Prehashed h (a -> b) -> Prehashed h a -> Prehashed h b infixl 4 #
Analogous to <$>
: apply a hash-supported function to a
hash-supported value.
Configuration
cachingLocation :: Lens' CacheAccessConf (Maybe FilePath) Source #
Where the cache-files should be stored. If Nothing
, the system temporary
folder will be used.
usePrecalculated :: Lens' CacheAccessConf Bool Source #
Whether to actually make use of a cached value, in case one is found. Usually,
doing that is the entire point of this library, but sometimes you may want
to disable it (e.g. after debbuging some function that was assumed fundamental
).
calculateIfNecessary :: Lens' CacheAccessConf Bool Source #
Whether you want the processor to bite the bullet and compute the value itself, in case it can't be found in the cache. Again, you will need to have this on at some point (the cached values have to come from somewhere, after all).
writeUsedVersion :: Lens' CacheAccessConf Bool Source #
Whether to store the computed value in cache. This too should usually be enabled.
burnAfterReading :: Lens' CacheAccessConf Bool Source #
Enable this to have the cached value deleted after use. May be useful to save disk space.
(For the record: this does not perform any kind of special secure-memore-erasing, it only removes the cache file.)
Internals
:: Binary a | |
=> CacheAccessConf | |
-> FilePath | File to store this value in. |
-> a | Value to cache |
-> IO a |