master-plan-0.3.1: The project management tool for hackers

Copyright(c) Rodrigo Setti 2017
LicenseMIT
Maintainerrodrigosetti@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

MasterPlan.Data

Description

 

Synopsis

Documentation

type ProjectKey = String Source #

When using to reference projects by name

data Project e Source #

Structure of a project expression

Instances

Eq e => Eq (Project e) Source # 

Methods

(==) :: Project e -> Project e -> Bool #

(/=) :: Project e -> Project e -> Bool #

Data e => Data (Project e) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Project e -> c (Project e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Project e) #

toConstr :: Project e -> Constr #

dataTypeOf :: Project e -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Project e)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d a. (Data d, Data a) => c (t d a)) -> Maybe (c (Project e)) #

gmapT :: (forall b. Data b => b -> b) -> Project e -> Project e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Project e -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Project e -> r #

gmapQ :: (forall d. Data d => d -> u) -> Project e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Project e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Project e -> m (Project e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Project e -> m (Project e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Project e -> m (Project e) #

Show e => Show (Project e) Source # 

Methods

showsPrec :: Int -> Project e -> ShowS #

show :: Project e -> String #

showList :: [Project e] -> ShowS #

data ProjectProperties Source #

Any binding (with a name) may have associated properties

Instances

Eq ProjectProperties Source # 
Data ProjectProperties Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProjectProperties -> c ProjectProperties #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProjectProperties #

toConstr :: ProjectProperties -> Constr #

dataTypeOf :: ProjectProperties -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ProjectProperties) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProjectProperties) #

gmapT :: (forall b. Data b => b -> b) -> ProjectProperties -> ProjectProperties #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProjectProperties -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProjectProperties -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProjectProperties -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProjectProperties -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProjectProperties -> m ProjectProperties #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectProperties -> m ProjectProperties #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProjectProperties -> m ProjectProperties #

Show ProjectProperties Source # 

newtype Trust Source #

Constructors

Trust 

Fields

Instances

Eq Trust Source # 

Methods

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

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

Fractional Trust Source # 
Data Trust Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Trust -> c Trust #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Trust #

toConstr :: Trust -> Constr #

dataTypeOf :: Trust -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Trust) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Trust) #

gmapT :: (forall b. Data b => b -> b) -> Trust -> Trust #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Trust -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Trust -> r #

gmapQ :: (forall d. Data d => d -> u) -> Trust -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Trust -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Trust -> m Trust #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Trust -> m Trust #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Trust -> m Trust #

Num Trust Source # 
Ord Trust Source # 

Methods

compare :: Trust -> Trust -> Ordering #

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

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

(>) :: Trust -> Trust -> Bool #

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

max :: Trust -> Trust -> Trust #

min :: Trust -> Trust -> Trust #

Real Trust Source # 

Methods

toRational :: Trust -> Rational #

RealFrac Trust Source # 

Methods

properFraction :: Integral b => Trust -> (b, Trust) #

truncate :: Integral b => Trust -> b #

round :: Integral b => Trust -> b #

ceiling :: Integral b => Trust -> b #

floor :: Integral b => Trust -> b #

Show Trust Source # 

Methods

showsPrec :: Int -> Trust -> ShowS #

show :: Trust -> String #

showList :: [Trust] -> ShowS #

newtype Cost Source #

Constructors

Cost 

Fields

Instances

Eq Cost Source # 

Methods

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

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

Fractional Cost Source # 

Methods

(/) :: Cost -> Cost -> Cost #

recip :: Cost -> Cost #

fromRational :: Rational -> Cost #

Data Cost Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cost -> c Cost #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cost #

toConstr :: Cost -> Constr #

dataTypeOf :: Cost -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Cost) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cost) #

gmapT :: (forall b. Data b => b -> b) -> Cost -> Cost #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cost -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cost -> r #

gmapQ :: (forall d. Data d => d -> u) -> Cost -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Cost -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cost -> m Cost #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cost -> m Cost #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cost -> m Cost #

Num Cost Source # 

Methods

(+) :: Cost -> Cost -> Cost #

(-) :: Cost -> Cost -> Cost #

(*) :: Cost -> Cost -> Cost #

negate :: Cost -> Cost #

abs :: Cost -> Cost #

signum :: Cost -> Cost #

fromInteger :: Integer -> Cost #

Ord Cost Source # 

Methods

compare :: Cost -> Cost -> Ordering #

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

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

(>) :: Cost -> Cost -> Bool #

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

max :: Cost -> Cost -> Cost #

min :: Cost -> Cost -> Cost #

Real Cost Source # 

Methods

toRational :: Cost -> Rational #

RealFrac Cost Source # 

Methods

properFraction :: Integral b => Cost -> (b, Cost) #

truncate :: Integral b => Cost -> b #

round :: Integral b => Cost -> b #

ceiling :: Integral b => Cost -> b #

floor :: Integral b => Cost -> b #

Show Cost Source # 

Methods

showsPrec :: Int -> Cost -> ShowS #

show :: Cost -> String #

showList :: [Cost] -> ShowS #

newtype Progress Source #

Constructors

Progress 

Fields

Instances

Eq Progress Source # 
Fractional Progress Source # 
Data Progress Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Progress -> c Progress #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Progress #

toConstr :: Progress -> Constr #

dataTypeOf :: Progress -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Progress) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Progress) #

gmapT :: (forall b. Data b => b -> b) -> Progress -> Progress #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Progress -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Progress -> r #

gmapQ :: (forall d. Data d => d -> u) -> Progress -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Progress -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Progress -> m Progress #

Num Progress Source # 
Ord Progress Source # 
Real Progress Source # 
RealFrac Progress Source # 

Methods

properFraction :: Integral b => Progress -> (b, Progress) #

truncate :: Integral b => Progress -> b #

round :: Integral b => Progress -> b #

ceiling :: Integral b => Progress -> b #

floor :: Integral b => Progress -> b #

Show Progress Source # 

cost :: ProjectExpr -> Cost Source #

Expected cost

trust :: ProjectExpr -> Trust Source #

Expected probability of succeeding

simplify :: Project a -> Project a Source #

Simplify a project expression structure 1) transform singleton collections into it's only child 2) flatten same constructor of the collection

prioritize :: ProjectExpr -> ProjectExpr Source #

Sort project in order that minimizes cost