build-1.1: Build Systems à la Carte
Safe HaskellSafe-Inferred
LanguageHaskell2010

Build.Trace

Description

Build traces that are used for recording information from previuos builds.

Synopsis

Documentation

data Trace k v r Source #

A trace is parameterised by the types of keys k, hashes h, as well as the result r. For verifying traces, r = h; for constructive traces, Hash r = h.

Constructors

Trace 

Fields

Instances

Instances details
(Show k, Show v, Show r) => Show (Trace k v r) Source # 
Instance details

Defined in Build.Trace

Methods

showsPrec :: Int -> Trace k v r -> ShowS #

show :: Trace k v r -> String #

showList :: [Trace k v r] -> ShowS #

Verifying traces

data VT k v Source #

An abstract data type for a set of verifying traces equipped with recordVT, verifyVT and a Monoid instance.

Instances

Instances details
Monoid (VT k v) Source # 
Instance details

Defined in Build.Trace

Methods

mempty :: VT k v #

mappend :: VT k v -> VT k v -> VT k v #

mconcat :: [VT k v] -> VT k v #

Semigroup (VT k v) Source # 
Instance details

Defined in Build.Trace

Methods

(<>) :: VT k v -> VT k v -> VT k v #

sconcat :: NonEmpty (VT k v) -> VT k v #

stimes :: Integral b => b -> VT k v -> VT k v #

(Show k, Show v) => Show (VT k v) Source # 
Instance details

Defined in Build.Trace

Methods

showsPrec :: Int -> VT k v -> ShowS #

show :: VT k v -> String #

showList :: [VT k v] -> ShowS #

recordVT :: k -> Hash v -> [(k, Hash v)] -> VT k v -> VT k v Source #

Record a new trace for building a key with dependencies deps, obtaining the hashes of up-to-date values by using fetchHash.

verifyVT :: (Monad m, Eq k, Eq v) => k -> Hash v -> (k -> m (Hash v)) -> VT k v -> m Bool Source #

Given a function to compute the hash of a key's current value, a key, and a set of verifying traces, return True if the key is up-to-date.

Constructive traces

data CT k v Source #

An abstract data type for a set of constructive traces equipped with recordCT, isDirtyCT, constructCT and a Monoid instance.

Instances

Instances details
Monoid (CT k v) Source # 
Instance details

Defined in Build.Trace

Methods

mempty :: CT k v #

mappend :: CT k v -> CT k v -> CT k v #

mconcat :: [CT k v] -> CT k v #

Semigroup (CT k v) Source # 
Instance details

Defined in Build.Trace

Methods

(<>) :: CT k v -> CT k v -> CT k v #

sconcat :: NonEmpty (CT k v) -> CT k v #

stimes :: Integral b => b -> CT k v -> CT k v #

(Show k, Show v) => Show (CT k v) Source # 
Instance details

Defined in Build.Trace

Methods

showsPrec :: Int -> CT k v -> ShowS #

show :: CT k v -> String #

showList :: [CT k v] -> ShowS #

isDirtyCT :: (Eq k, Hashable v) => k -> Store (CT k v) k v -> Bool Source #

Check if a given key is dirty w.r.t a store.

recordCT :: k -> v -> [(k, Hash v)] -> CT k v -> CT k v Source #

Record a new trace for building a key with dependencies deps, obtaining the hashes of up-to-date values by using fetchHash.

constructCT :: (Monad m, Eq k, Eq v) => k -> (k -> m (Hash v)) -> CT k v -> m [v] Source #

Given a function to compute the hash of a key's current value, a key, and a set of constructive traces, return Just newValue if it is possible to reconstruct it from the traces. Prefer reconstructing the currenct value, if it matches one of the traces.

Constructive traces optimised for deep tasks

data DCT k v Source #

Our current model has the same representation as CT, but requires an additional invariant: if a DCT contains a trace for a key k, then it must also contain traces for each of its non-input dependencies.

Instances

Instances details
Monoid (DCT k v) Source # 
Instance details

Defined in Build.Trace

Methods

mempty :: DCT k v #

mappend :: DCT k v -> DCT k v -> DCT k v #

mconcat :: [DCT k v] -> DCT k v #

Semigroup (DCT k v) Source # 
Instance details

Defined in Build.Trace

Methods

(<>) :: DCT k v -> DCT k v -> DCT k v #

sconcat :: NonEmpty (DCT k v) -> DCT k v #

stimes :: Integral b => b -> DCT k v -> DCT k v #

(Show k, Show v) => Show (DCT k v) Source # 
Instance details

Defined in Build.Trace

Methods

showsPrec :: Int -> DCT k v -> ShowS #

show :: DCT k v -> String #

showList :: [DCT k v] -> ShowS #

recordDCT :: forall k v m. (Eq k, Hashable v, Monad m) => k -> v -> [k] -> (k -> m (Hash v)) -> DCT k v -> m (DCT k v) Source #

Record a new trace for building a key with dependencies deps, obtaining the hashes of up-to-date values from the given store.

constructDCT :: forall k v m. (Eq k, Hashable v, Monad m) => k -> (k -> m (Hash v)) -> DCT k v -> m [v] Source #

Given a function to compute the hash of a key's current value, a key, and a set of deep constructive traces, return Just newValue if it is possible to reconstruct it from the traces.

Step traces

data Step Source #

Instances

Instances details
Monoid Step Source # 
Instance details

Defined in Build.Trace

Methods

mempty :: Step #

mappend :: Step -> Step -> Step #

mconcat :: [Step] -> Step #

Semigroup Step Source # 
Instance details

Defined in Build.Trace

Methods

(<>) :: Step -> Step -> Step #

sconcat :: NonEmpty Step -> Step #

stimes :: Integral b => b -> Step -> Step #

Enum Step Source # 
Instance details

Defined in Build.Trace

Methods

succ :: Step -> Step #

pred :: Step -> Step #

toEnum :: Int -> Step #

fromEnum :: Step -> Int #

enumFrom :: Step -> [Step] #

enumFromThen :: Step -> Step -> [Step] #

enumFromTo :: Step -> Step -> [Step] #

enumFromThenTo :: Step -> Step -> Step -> [Step] #

Show Step Source # 
Instance details

Defined in Build.Trace

Methods

showsPrec :: Int -> Step -> ShowS #

show :: Step -> String #

showList :: [Step] -> ShowS #

Eq Step Source # 
Instance details

Defined in Build.Trace

Methods

(==) :: Step -> Step -> Bool #

(/=) :: Step -> Step -> Bool #

Ord Step Source # 
Instance details

Defined in Build.Trace

Methods

compare :: Step -> Step -> Ordering #

(<) :: Step -> Step -> Bool #

(<=) :: Step -> Step -> Bool #

(>) :: Step -> Step -> Bool #

(>=) :: Step -> Step -> Bool #

max :: Step -> Step -> Step #

min :: Step -> Step -> Step #

data ST k v Source #

A step trace, records the resulting value, the step it last build, the step where it changed.

Instances

Instances details
Monoid (ST k v) Source # 
Instance details

Defined in Build.Trace

Methods

mempty :: ST k v #

mappend :: ST k v -> ST k v -> ST k v #

mconcat :: [ST k v] -> ST k v #

Semigroup (ST k v) Source # 
Instance details

Defined in Build.Trace

Methods

(<>) :: ST k v -> ST k v -> ST k v #

sconcat :: NonEmpty (ST k v) -> ST k v #

stimes :: Integral b => b -> ST k v -> ST k v #

(Show k, Show v) => Show (ST k v) Source # 
Instance details

Defined in Build.Trace

Methods

showsPrec :: Int -> ST k v -> ShowS #

show :: ST k v -> String #

showList :: [ST k v] -> ShowS #

recordST :: (Hashable v, Eq k) => Step -> k -> v -> [k] -> ST k v -> ST k v Source #

Record a new trace for building a key with dependencies deps.

verifyST :: (Monad m, Eq k, Hashable v) => k -> v -> (k -> m ()) -> m (ST k v) -> m Bool Source #

Given a function to compute the hash of a key's current value, a key, and a set of verifying traces, return True if the key is up-to-date.