patience-0.2.1.0: Patience diff and longest increasing subsequence

Safe HaskellSafe
LanguageHaskell2010

Patience

Contents

Description

Implements "patience diff" and the patience algorithm for the longest increasing subsequence problem.

Synopsis

Patience diff

diff :: Ord a => [a] -> [a] -> [Item a] Source #

The difference between two lists, according to the "patience diff" algorithm.

data Item a Source #

An element of a computed difference.

Constructors

Old a

Value taken from the "old" list, i.e. left argument to diff

New a

Value taken from the "new" list, i.e. right argument to diff

Both a a

Value taken from both lists. Both values are provided, in case your type has a non-structural definition of equality.

Instances
Functor Item Source # 
Instance details

Defined in Patience

Methods

fmap :: (a -> b) -> Item a -> Item b #

(<$) :: a -> Item b -> Item a #

Eq a => Eq (Item a) Source # 
Instance details

Defined in Patience

Methods

(==) :: Item a -> Item a -> Bool #

(/=) :: Item a -> Item a -> Bool #

Data a => Data (Item a) Source # 
Instance details

Defined in Patience

Methods

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

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

toConstr :: Item a -> Constr #

dataTypeOf :: Item a -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord (Item a) Source # 
Instance details

Defined in Patience

Methods

compare :: Item a -> Item a -> Ordering #

(<) :: Item a -> Item a -> Bool #

(<=) :: Item a -> Item a -> Bool #

(>) :: Item a -> Item a -> Bool #

(>=) :: Item a -> Item a -> Bool #

max :: Item a -> Item a -> Item a #

min :: Item a -> Item a -> Item a #

Read a => Read (Item a) Source # 
Instance details

Defined in Patience

Show a => Show (Item a) Source # 
Instance details

Defined in Patience

Methods

showsPrec :: Int -> Item a -> ShowS #

show :: Item a -> String #

showList :: [Item a] -> ShowS #

itemChar :: Item a -> Char Source #

Deprecated: Don't use this. It will be removed in a later version.

The character '-' or '+' or ' ' for Old or New or Both respectively.

itemValue :: Item a -> a Source #

Deprecated: Don't use this. It will be removed in a later version.

The value from an Item. For Both, returns the "old" value.

Longest increasing subsequence

longestIncreasing :: [(Int, a)] -> [(Int, a)] Source #

Given: a list of distinct integers. Picks a subset of the integers in the same order, i.e. a subsequence, with the property that

  • it is monotonically increasing, and
  • it is at least as long as any other such subsequence.

This function uses patience sort: http://en.wikipedia.org/wiki/Patience_sorting. For implementation reasons, the actual list returned is the reverse of the subsequence.

You can pair each integer with an arbitrary annotation, which will be carried through the algorithm.