levenshtein-0.2.1.0: Calculate the edit distance between two foldables.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Foldable.Levenshtein

Description

The Levenshtein distance is the minimal number of additions, removals, and updates one has to make to convert one list of items into another list of items. In this module we provide some functions that makes it convenient to calculate the distance and the sequence of Edits, and furthermore ways to alter the score for an addition, removal, edit that can depend on what item is modified.

Synopsis

Calculate the Levenshtein distance

genericLevenshteinDistance Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> (a -> b)

The cost of adding the given item. The return value should be positive.

-> (a -> b)

The cost of removing the given item. The return value should be positive.

-> (a -> a -> b)

The cost that it takes to replace an item of the first parameter with one of the second parameter. The return value should be positive.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> b

The edit distance between the two Foldables.

A function to determine the Levenshtein distance by specifying the cost functions of adding, removing and editing characters. This function returns the sum of the costs to transform the first Foldable (as list) into the second Foldable (as list). The (==) function is used to determine if two items are equivalent.

genericLevenshteinDistance' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> (a -> b)

The cost of adding the given item. The return value should be positive.

-> (a -> b)

The cost of removing the given item. The return value should be positive.

-> (a -> a -> b)

The cost that it takes to replace an item of the first parameter with one of the second parameter. The return value should be positive.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> b

The edit distance between the two Foldables.

A function to determine the Levenshtein distance by specifying the cost functions of adding, removing and editing characters. This function returns the sum of the costs to transform the first Foldable (as list) into the second Foldable (as list). The first parameter is an equivalence relation to determine if two items are considered equivalent.

genericLevenshteinDistanceWithScore Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> EditScore a b

The given EditScore object that determines the cost per edit.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> b

The edit distance between the two Foldables.

Calculate the Levenshtein distance with the given EditScore object that determine how costly each edit is. The function determines the minimal score with Add, Rem, Copy and Swap edits. We determine if two items are the same with the Eq instance for the item type.

genericLevenshteinDistanceWithScore' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> EditScore a b

The given EditScore object that determines the cost per edit.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> b

The edit distance between the two Foldables.

Calculate the Levenshtein distance with the given equivalence relation, and the given EditScore object that determine how costly each edit is. The function determines the minimal score with Add, Rem, Copy and Swap edits.

levenshteinDistance Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> f a

The given original sequence.

-> g a

The given target sequence.

-> b

The edit distance between the two Foldables.

Determine the edit distance where an addition, removal, and change all count as one, and where the Eq instance is used to determine whether two items are equivalent, this is for example useful for case-insensitve matching.

levenshteinDistance' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> b

The edit distance between the two Foldables.

Determine the edit distance to transform the first Foldable (as list) into a second Foldable (as list). Add, remove and swapping items all count as one edit distance. The first parameter is an equivalence relation that is used to determine if two items are considered equivalent.

Obtain the Levenshtein distance together with the path of Edits

genericLevenshtein Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> (a -> b)

The cost of adding the given item. The return value should be positive.

-> (a -> b)

The cost of removing the given item. The return value should be positive.

-> (a -> a -> b)

The cost that it takes to replace an item of the first parameter with one of the second parameter. The return value should be positive.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications in normal order as second item to transform the first sequence to the second one.

A function to determine the Levenshtein distance together with a list of Edits to apply to convert the first Foldable (as list) into the second item (as list) The cost functions of adding, removing and editing characters will be used to minimize the total edit distance. The (==) function is used to determine if two items of the Foldables are considered equivalent.

genericLevenshtein' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> (a -> b)

The cost of adding the given item. The return value should be positive.

-> (a -> b)

The cost of removing the given item. The return value should be positive.

-> (a -> a -> b)

The cost that it takes to replace an item of the first parameter with one of the second parameter. The return value should be positive.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications in normal order as second item to transform the first sequence to the second one.

A function to determine the Levenshtein distance together with a list of Edits to apply to convert the first Foldable (as list) into the second item (as list) The cost functions of adding, removing and editing characters will be used to minimize the total edit distance. The first parameter is an equivalence relation that is used to determine if two items of the Foldables are considered equivalent.

genericLevenshteinWithScore Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> EditScore a b

The given EditScore object that specifies the cost of each mutation (add, remove, replace).

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications as second item to transform the first Foldable (as list) to the second Foldable (as list).

Calculate the Levenshtein distance and the modifications with the given EditScore object that determine how costly each edit is. The function determines the minimal score with Add, Rem, Copy and Swap edits. The Eq instance of the elements is used to determine if two items are equivalent.

genericLevenshteinWithScore' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to determine if two items are the same.

-> EditScore a b

The given EditScore object that specifies the cost of each mutation (add, remove, replace).

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications as second item to transform the first Foldable (as list) to the second Foldable (as list).

Calculate the Levenshtein distance and the modifications with the given equivalence relation, and the given EditScore object that determine how costly each edit is. The function determines the minimal score with Add, Rem, Copy and Swap edits.

levenshtein Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

The edit distance between the two Foldables.

Determine the edit distance together with the steps to transform the first Foldable (as list) into a second Foldable (as list). Add, remove and swapping items all count as one edit distance.

levenshtein' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

The edit distance between the two Foldables together with a list of Edits to transform the first Foldable to the second one.

Determine the edit distance together with the steps to transform the first Foldable (as list) into a second Foldable (as list). Add, remove and swapping items all count as one edit distance. The first parameter is a function to determine if two items are of the Foldables are considered equivalent.

Obtain the Levenshtein distance together with a reversed path of Edits

genericReversedLevenshtein Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> (a -> b)

The cost of adding the given item. The return value should be positive.

-> (a -> b)

The cost of removing the given item. The return value should be positive.

-> (a -> a -> b)

The cost that it takes to replace an item of the first parameter with one of the second parameter. The return value should be positive.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications in reversed order as second item to transform the first Foldable (as list) to the second Foldable (as list).

A function to determine the Levenshtein distance together with a list of Edits to apply to convert the first Foldable (as list) into the second item (as list) in reversed order. The cost functions of adding, removing and editing characters will be used to minimize the total edit distance. The (==) function is used to determine if two items of the Foldables are considered equivalent.

genericReversedLevenshtein' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> (a -> b)

The cost of adding the given item. The return value should be positive.

-> (a -> b)

The cost of removing the given item. The return value should be positive.

-> (a -> a -> b)

The cost that it takes to replace an item of the first parameter with one of the second parameter. The return value should be positive.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications in reversed order as second item to transform the first Foldable (as list) to the second Foldable (as list).

A function to determine the Levenshtein distance together with a list of Edits to apply to convert the first Foldable (as list) into the second item (as list) in reversed order. The cost functions of adding, removing and editing characters will be used to minimize the total edit distance. The first parameter is an equivalence relation that is used to determine if two items of the Foldables are considered equivalent.

genericReversedLevenshteinWithScore Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> EditScore a b

The given EditScore object that specifies the cost of each mutation (add, remove, replace).

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications in reversed order as second item to transform the first Foldable (as list) to the second Foldable (as list).

Calculate the Levenshtein distance and the modifications with the given EditScore object that determine how costly each edit is. The function determines the minimal score with Add, Rem, Copy and Swap edits. The Eq instance of the items will determine the equivalence relation.

genericReversedLevenshteinWithScore' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to determine if two items are the same.

-> EditScore a b

The given EditScore object that specifies the cost of each mutation (add, remove, replace).

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

A 2-tuple with the edit score as first item, and a list of modifications in reversed order as second item to transform the first Foldable (as list) to the second Foldable (as list).

Calculate the Levenshtein distance and the modifications with the given equivalence relation, and the given EditScore object that determine how costly each edit is. The function determines the minimal score with Add, Rem, Copy and Swap edits.

reversedLevenshtein Source #

Arguments

:: (Foldable f, Foldable g, Eq a, Num b, Ord b) 
=> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

The edit distance between the two Foldables together with the Edits to make to convert the first sequence into the second.

Determine the edit distance together with the steps to transform the first Foldable (as list) into a second Foldable (as list). Add, remove and swapping items all count as one edit distance. The equality function (==) is used to determine if two items are equivalent.

reversedLevenshtein' Source #

Arguments

:: (Foldable f, Foldable g, Num b, Ord b) 
=> (a -> a -> Bool)

The given equivalence relation to work with.

-> f a

The given original sequence.

-> g a

The given target sequence.

-> (b, Edits a)

The edit distance between the two Foldables together with a reversed list of Edits to transform the original sequence into the target sequence.

Determine the edit distance together with the steps to transform the first Foldable (as list) into a second Foldable (as list) in reversed order. Add, remove and swapping items all count as one edit distance. The given equality function is used to determine if two items are equivalent.

Data type to present modifications from one Foldable to another.

data Edit a Source #

A data type that is used to list how to edit a sequence to form another sequence.

Constructors

Add a

We add the given element to the sequence.

Rem a

We remove the given element to the sequence.

Copy a

We copy an element from the sequence, this basically act as a no-op.

Swap a a

We modify the given first item into the second item, this thus denotes a replacement.

Instances

Instances details
Functor Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

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

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

Foldable Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

fold :: Monoid m => Edit m -> m #

foldMap :: Monoid m => (a -> m) -> Edit a -> m #

foldMap' :: Monoid m => (a -> m) -> Edit a -> m #

foldr :: (a -> b -> b) -> b -> Edit a -> b #

foldr' :: (a -> b -> b) -> b -> Edit a -> b #

foldl :: (b -> a -> b) -> b -> Edit a -> b #

foldl' :: (b -> a -> b) -> b -> Edit a -> b #

foldr1 :: (a -> a -> a) -> Edit a -> a #

foldl1 :: (a -> a -> a) -> Edit a -> a #

toList :: Edit a -> [a] #

null :: Edit a -> Bool #

length :: Edit a -> Int #

elem :: Eq a => a -> Edit a -> Bool #

maximum :: Ord a => Edit a -> a #

minimum :: Ord a => Edit a -> a #

sum :: Num a => Edit a -> a #

product :: Num a => Edit a -> a #

Traversable Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

traverse :: Applicative f => (a -> f b) -> Edit a -> f (Edit b) #

sequenceA :: Applicative f => Edit (f a) -> f (Edit a) #

mapM :: Monad m => (a -> m b) -> Edit a -> m (Edit b) #

sequence :: Monad m => Edit (m a) -> m (Edit a) #

Arbitrary1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

liftArbitrary :: Gen a -> Gen (Edit a) #

liftShrink :: (a -> [a]) -> Edit a -> [Edit a] #

Eq1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

liftEq :: (a -> b -> Bool) -> Edit a -> Edit b -> Bool #

Ord1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

liftCompare :: (a -> b -> Ordering) -> Edit a -> Edit b -> Ordering #

NFData1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

liftRnf :: (a -> ()) -> Edit a -> () #

Hashable1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Edit a -> Int #

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

Defined in Data.Foldable.Levenshtein

Methods

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

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

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

Defined in Data.Foldable.Levenshtein

Methods

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

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

toConstr :: Edit a -> Constr #

dataTypeOf :: Edit a -> DataType #

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Foldable.Levenshtein

Methods

compare :: Edit a -> Edit a -> Ordering #

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

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

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

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

max :: Edit a -> Edit a -> Edit a #

min :: Edit a -> Edit a -> Edit a #

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

Defined in Data.Foldable.Levenshtein

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

Defined in Data.Foldable.Levenshtein

Methods

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

show :: Edit a -> String #

showList :: [Edit a] -> ShowS #

Generic (Edit a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Associated Types

type Rep (Edit a) :: Type -> Type #

Methods

from :: Edit a -> Rep (Edit a) x #

to :: Rep (Edit a) x -> Edit a #

Arbitrary a => Arbitrary (Edit a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

arbitrary :: Gen (Edit a) #

shrink :: Edit a -> [Edit a] #

Binary a => Binary (Edit a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

put :: Edit a -> Put #

get :: Get (Edit a) #

putList :: [Edit a] -> Put #

NFData a => NFData (Edit a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

rnf :: Edit a -> () #

Hashable a => Hashable (Edit a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

hashWithSalt :: Int -> Edit a -> Int #

hash :: Edit a -> Int #

Generic1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Associated Types

type Rep1 Edit :: k -> Type #

Methods

from1 :: forall (a :: k). Edit a -> Rep1 Edit a #

to1 :: forall (a :: k). Rep1 Edit a -> Edit a #

type Rep (Edit a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

type Rep1 Edit Source # 
Instance details

Defined in Data.Foldable.Levenshtein

type Edits a = [Edit a] Source #

A type alias for a list of Edits.

applyEdits Source #

Arguments

:: Eq a 
=> Edits a

The given list of Edits to apply to the given list.

-> [a]

The list of items to edit with the given Edits.

-> Maybe [a]

The modified list, given the checks hold about what item to remove/replace wrapped in a Just; Nothing otherwise.

Apply the given list of Edits to the given list. If the Edits make sense, it returns the result wrapped in a Just, if a check with the item that is removed/replaced fails, the function will return Nothing.

Present the modification costs

data EditScore a b Source #

A data type that provides information about how costly a certain edit is. One can make use of this data type to change the cost functions in an effective way. The EditScore scales linear, this means that if we double all the costs, the minimal edit cost will also double.

Instances

Instances details
Functor (EditScore a) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

fmap :: (a0 -> b) -> EditScore a a0 -> EditScore a b #

(<$) :: a0 -> EditScore a b -> EditScore a a0 #

Generic1 (EditScore a :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Associated Types

type Rep1 (EditScore a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). EditScore a a0 -> Rep1 (EditScore a) a0 #

to1 :: forall (a0 :: k). Rep1 (EditScore a) a0 -> EditScore a a0 #

Generic (EditScore a b) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Associated Types

type Rep (EditScore a b) :: Type -> Type #

Methods

from :: EditScore a b -> Rep (EditScore a b) x #

to :: Rep (EditScore a b) x -> EditScore a b #

Num b => Default (EditScore a b) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

Methods

def :: EditScore a b #

type Rep1 (EditScore a :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

type Rep1 (EditScore a :: Type -> Type) = D1 ('MetaData "EditScore" "Data.Foldable.Levenshtein" "levenshtein-0.2.1.0-9OLwpElEA9W1iY6M7XxY7P" 'False) (C1 ('MetaCons "EditScore" 'PrefixI 'True) ((S1 ('MetaSel ('Just "editAdd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ((->) a :: Type -> Type)) :*: S1 ('MetaSel ('Just "editRemove") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 ((->) a :: Type -> Type))) :*: (S1 ('MetaSel ('Just "editReplace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (((->) a :: Type -> Type) :.: Rec1 ((->) a :: Type -> Type)) :*: S1 ('MetaSel ('Just "editTranspose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (((->) a :: Type -> Type) :.: Rec1 ((->) a :: Type -> Type)))))
type Rep (EditScore a b) Source # 
Instance details

Defined in Data.Foldable.Levenshtein

type Rep (EditScore a b) = D1 ('MetaData "EditScore" "Data.Foldable.Levenshtein" "levenshtein-0.2.1.0-9OLwpElEA9W1iY6M7XxY7P" 'False) (C1 ('MetaCons "EditScore" 'PrefixI 'True) ((S1 ('MetaSel ('Just "editAdd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> b)) :*: S1 ('MetaSel ('Just "editRemove") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> b))) :*: (S1 ('MetaSel ('Just "editReplace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a -> b)) :*: S1 ('MetaSel ('Just "editTranspose") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a -> b)))))

editCost Source #

Arguments

:: Num b 
=> EditScore a b

An EditScore object that determines how costly each transformation is.

-> Edit a

The given Edit for which we want to calculate the score.

-> b

The given edit distance for the given Edit with the given EditScore.

Determine the cost of a given Edit as described with the given EditScore object.

editsCost Source #

Arguments

:: (Foldable f, Num b) 
=> EditScore a b

An EditScore object that determines how costly each transformation is.

-> f (Edit a)

The given Foldable of Edits for which we want to calculate the score.

-> b

The given edit distance for all the given Edits with the given EditScore.

Determine the cost of the given sequence of Edits with the given EditScore object that determines the cost for each edit. The sum of the Edits is returned.

constantEditScore Source #

Arguments

:: b

The given cost for all the operations.

-> EditScore a b

The corresponding EditScore object.

A function to construct an EditScore object where the cost of adding, removing, replacing and transposing all have the same given cost.