GTALib-0.0.4: A library for GTA programming

Safe HaskellNone

GTA.Data.ConsList

Documentation

data ConsList a Source

Constructors

Cons a (ConsList a) 
Nil 

Instances

Eq a => Eq (ConsList a) 
Ord a => Ord (ConsList a) 
Read a => Read (ConsList a) 
Show a => Show (ConsList a) 
GenericSemiringStructure (ConsListAlgebra a0) (ConsList a0) (ConsListMapFs a0) 

data ConsListAlgebra a gta Source

Constructors

ConsListAlgebra 

Fields

cons :: a -> gta -> gta
 
nil :: gta
 

Instances

GenericSemiringStructure (ConsListAlgebra a0) (ConsList a0) (ConsListMapFs a0) 

consize :: forall a. [a] -> ConsList aSource

deconsize :: forall a. ConsList a -> [a]Source

segs :: [a] -> ConsSemiring a s -> sSource

inits :: [a] -> ConsSemiring a s -> sSource

tails :: [a] -> ConsSemiring a s -> sSource

subs :: [a] -> ConsSemiring a s -> sSource

assigns :: [m] -> [a] -> ConsSemiring (m, a) s -> sSource

assignsBy :: (a -> [m]) -> [a] -> ConsSemiring (m, a) s -> sSource

paths :: BinTree a a -> ConsSemiring a s -> sSource

mapC :: forall b a. (b -> a) -> ConsListMapFs b aSource

maxsumWith :: (Ord a, Num a) => (b -> a) -> ConsSemiring b (AddIdentity a)Source

maxsumKWith :: (Ord a, Num a) => Int -> (b -> a) -> ConsSemiring b [AddIdentity a]Source

maxsumsolutionXKWith :: (Ord a, Num a) => ConsSemiring c b -> Int -> (c -> a) -> ConsSemiring c [(AddIdentity a, b)]Source

maxsumsolutionXWith :: (Ord a, Num a) => ConsSemiring c b -> (c -> a) -> ConsSemiring c (AddIdentity a, b)Source

maxsumsolutionKWith :: (Ord a, Num a) => Int -> (b -> a) -> ConsSemiring b [(AddIdentity a, Bag (ConsList b))]Source

maxprodWith :: (Ord a, Num a) => (b -> a) -> ConsSemiring b (AddIdentity a)Source

maxprodKWith :: (Ord a, Num a) => Int -> (b -> a) -> ConsSemiring b [AddIdentity a]Source

maxprodsolutionXKWith :: (Ord a, Num a) => ConsSemiring c b -> Int -> (c -> a) -> ConsSemiring c [(AddIdentity a, b)]Source

maxprodsolutionXWith :: (Ord a, Num a) => ConsSemiring c b -> (c -> a) -> ConsSemiring c (AddIdentity a, b)Source

maxprodsolutionKWith :: (Ord a, Num a) => Int -> (b -> a) -> ConsSemiring b [(AddIdentity a, Bag (ConsList b))]Source

foldr' :: forall a s. (a -> s -> s) -> s -> ConsListAlgebra a sSource