Skip to content

Commit

Permalink
Add functions in vmchale/recursion_schemes#5
Browse files Browse the repository at this point in the history
  • Loading branch information
lotz84 committed May 7, 2020
1 parent 96d3c77 commit 56c8a35
Show file tree
Hide file tree
Showing 9 changed files with 167 additions and 8 deletions.
39 changes: 39 additions & 0 deletions docs/Algorithms/List/BasicOperations/DropWhile.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,39 @@
# dropWhile

```hs
module Algorithms.List.BasicOperations.DropWhile where

import Data.Functor.Foldable

import RecursionSchemes.Extra
```

You can implement `dropWhile` by using paramorphism and returning the list of the points where the element no longer satisfies the condition.

```hs
-- | >>> dropWhilePara odd [3, 1, 4, 1, 5]
-- [4,1,5]
dropWhilePara :: (a -> Bool) -> [a] -> [a]
dropWhilePara p = para \case
Nil -> []
Cons x (xs, ys) -> if p x then ys else x:xs
```

Monadic dropWhile also uses paramorphism, but the difference is that the object to be folded is wrapped in the monad[^1].

```hs
-- | >>> dropWhileParaM (\i -> print i >> pure (odd i)) [3, 1, 4, 1, 5]
-- 3
-- 1
-- 4
-- [4,1,5]
dropWhileParaM :: Monad m => (a -> m Bool) -> [a] -> m [a]
dropWhileParaM p = para \case
Nil -> pure []
Cons x (xs, ys) -> do
flg <- p x
if flg then ys else pure (x:xs)
```

## References
[1] [Monadic versions · Issue #5 · vmchale/recursion_schemes](https://github.com/vmchale/recursion_schemes/issues/5)
18 changes: 17 additions & 1 deletion docs/Algorithms/List/BasicOperations/Filter.md
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,8 @@ module Algorithms.List.BasicOperations.Filter where

import Data.Functor.Foldable
import GHC.Natural

import RecursionSchemes.Extra
```

This implementation can be found in Meijer (1991)[^1].
Expand All @@ -18,5 +20,19 @@ filterCata p = cata \case
(Cons a b) -> if p a then a : b else b
```

You can also implement a monadic filter, which is used to implement subsequences[^2].

```hs
-- | >>> filterCataM (pure . odd) [1, 2, 3]
-- [1,3]
filterCataM :: Monad m => (a -> m Bool) -> [a] -> m [a]
filterCataM p = cataM \case
Nil -> pure []
Cons x xs -> do
flg <- p x
pure if flg then x:xs else xs
```

## References
[1] Meijer, Erik, Maarten Fokkinga, and Ross Paterson. "Functional programming with bananas, lenses, envelopes and barbed wire." Conference on Functional Programming Languages and Computer Architecture. Springer, Berlin, Heidelberg, 1991.
[1] Meijer, Erik, Maarten Fokkinga, and Ross Paterson. "Functional programming with bananas, lenses, envelopes and barbed wire." Conference on Functional Programming Languages and Computer Architecture. Springer, Berlin, Heidelberg, 1991.
[2] [Monadic versions · Issue #5 · vmchale/recursion_schemes](https://github.com/vmchale/recursion_schemes/issues/5)
19 changes: 19 additions & 0 deletions docs/Algorithms/List/BasicOperations/Inits.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
# inits

```hs
module Algorithms.List.BasicOperations.Inits where

import Algorithms.List.BasicOperations.TakeWhile
```

`inits` is a function that returns all substrings of the list in succession from the beginning[^1].

```hs
-- | >>> inits "abc"
-- ["","a","ab","abc"]
inits :: [a] -> [[a]]
inits = takeWhileCataM (const [False, True])
```

## References
[1] [Monadic versions · Issue #5 · vmchale/recursion_schemes](https://github.com/vmchale/recursion_schemes/issues/5)
19 changes: 19 additions & 0 deletions docs/Algorithms/List/BasicOperations/Subsequences.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
# subsequences

```hs
module Algorithms.List.BasicOperations.Subsequences where

import Algorithms.List.BasicOperations.Filter
```

`subsequences` is a function that returns a partial list of all parts of a given list[^1].

```hs
-- | >>> subsequences "abc"
-- ["","a","b","ab","c","ac","bc","abc"]
subsequences :: [a] -> [[a]]
subsequences = filterCataM (const [False, True])
```

## References
[1] [Monadic versions · Issue #5 · vmchale/recursion_schemes](https://github.com/vmchale/recursion_schemes/issues/5)
19 changes: 19 additions & 0 deletions docs/Algorithms/List/BasicOperations/Tails.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
# tails

```hs
module Algorithms.List.BasicOperations.Tails where

import Algorithms.List.BasicOperations.DropWhile
```

`inits` is a function that returns all substrings of the list in succession from the beginning[^1].

```hs
-- | >>> tails "abc"
-- ["abc","bc","c",""]
tails :: [a] -> [[a]]
tails = dropWhileParaM (const [False, True])
```

## References
[1] [Monadic versions · Issue #5 · vmchale/recursion_schemes](https://github.com/vmchale/recursion_schemes/issues/5)
23 changes: 20 additions & 3 deletions docs/Algorithms/List/BasicOperations/TakeWhile.md
Original file line number Diff line number Diff line change
Expand Up @@ -9,13 +9,30 @@ import Data.Functor.Foldable
This implementation can be found in Meijer (1991)[^1].

```hs
-- | >>> takeWhileCata even [2, 4, 7]
-- [2,4]
-- | >>> takeWhileCata odd [3, 1, 4, 1, 5]
-- [3,1]
takeWhileCata :: (a -> Bool) -> [a] -> [a]
takeWhileCata p = cata \case
Nil -> []
Cons a b -> if p a then a : b else []
```

Monadic takeWhile also uses catamorphism, but the difference is that the object to be folded is wrapped in the monad[^2].

```hs
-- | >>> takeWhileCataM (\i -> print i >> pure (odd i)) [3, 1, 4, 1, 5]
-- 3
-- 1
-- 4
-- [3,1]
takeWhileCataM :: Monad m => (a -> m Bool) -> [a] -> m [a]
takeWhileCataM p = cata \case
Nil -> pure []
Cons x xs -> do
flg <- p x
if flg then (x:) <$> xs else pure []
```

## References
[1] Meijer, Erik, Maarten Fokkinga, and Ross Paterson. "Functional programming with bananas, lenses, envelopes and barbed wire." Conference on Functional Programming Languages and Computer Architecture. Springer, Berlin, Heidelberg, 1991.
[1] Meijer, Erik, Maarten Fokkinga, and Ross Paterson. "Functional programming with bananas, lenses, envelopes and barbed wire." Conference on Functional Programming Languages and Computer Architecture. Springer, Berlin, Heidelberg, 1991.
[2] [Monadic versions · Issue #5 · vmchale/recursion_schemes](https://github.com/vmchale/recursion_schemes/issues/5)
5 changes: 5 additions & 0 deletions docs/README.md
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,11 @@ This repository uses [recursion-schemes](https://hackage.haskell.org/package/rec
- [iterate](Algorithms/List/BasicOperations/Iterate.md)
- [reverse](Algorithms/List/BasicOperations/Reverse.md)
- [span](Algorithms/List/BasicOperations/Span.md)
- [subsequences](Algorithms/List/BasicOperations/Subsequences.md)
- [takeWhile](Algorithms/List/BasicOperations/TakeWhile.md)
- [dropWhile](Algorithms/List/BasicOperations/DropWhile.md)
- [inits](Algorithms/List/BasicOperations/Inits.md)
- [tails](Algorithms/List/BasicOperations/Tails.md)
- [Edit Distance](Algorithms/List/EditDistance.md)
- [Longest Common Subsequence](Algorithms/List/LongestCommonSubsequence.md)
- Sorting
Expand Down
27 changes: 24 additions & 3 deletions docs/RecursionSchemes/Extra.md
Original file line number Diff line number Diff line change
@@ -1,8 +1,11 @@
# Extra Recursion Schemes

```hs
{-# LANGUAGE FlexibleContexts #-}
module RecursionSchemes.Extra where

import Control.Monad ((>=>))

import Control.Comonad
import Control.Comonad.Cofree
import Data.Functor.Foldable
Expand All @@ -11,7 +14,6 @@ import Data.Functor.Foldable
Here is a collection of implementations of recursion schemes that are not implemented in recursion-schemes.

## Dynamorphism

Dynamorphism is the recursion schemes proposed by Kabanov and Vene to realize dynamic programming[^1]. Simply put, it is represented as a refold of Anamorphism and Histomorphism.However, here we implement Dynamorphism as an extension of Hylomorphism in order not to lose generality.

```hs
Expand All @@ -20,6 +22,25 @@ dyna phi psi = extract . hylo ap psi
where ap f = phi f :< f
```

## References
[1] Kabanov, Jevgeni, and Varmo Vene. "Recursion schemes for dynamic programming." International Conference on Mathematics of Program Construction. Springer, Berlin, Heidelberg, 2006.
## Monadic Recursion Schemes
Monadic catamorphism[^2] can be implemented as a special case of ordinary catamorphism[^3].

```hs
cataM :: (Traversable (Base t), Monad m, Recursive t)
=> (Base t c -> m c) -> t -> m c
cataM = cata . (sequence >=>)
```

You can also implement monadic paramorphism in a similar way.

```hs
paraM :: (Recursive t, Monad m, Traversable (Base t))
=> (Base t (t, c) -> m c) -> t -> m c
paraM = para . (sequence . fmap sequence >=>)
```


## References
[1] Kabanov, Jevgeni, and Varmo Vene. "Recursion schemes for dynamic programming." International Conference on Mathematics of Program Construction. Springer, Berlin, Heidelberg, 2006.
[2] Fokkinga, Maarten Maria. Monadic maps and folds for arbitrary datatypes. University of Twente, Department of Computer Science, 1994.
[3] [Suggestion: Add monadic variants of various ...morphism functions. · Issue #3 · ekmett/recursion-schemes](https://github.com/ekmett/recursion-schemes/issues/3)
6 changes: 5 additions & 1 deletion recursion-algorithms.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ cabal-version: 1.12
--
-- see: https://github.com/sol/hpack
--
-- hash: d958f4ccf65a2c93d60f047dcf2dd8ad66bd690ffb6223391f64ee83d298cf63
-- hash: dc27a89a903003ac6ce7a03966874c73789bd6e5d7d9f441347ed9425feb5db3

name: recursion-algorithms
version: 0.0.0
Expand All @@ -21,12 +21,16 @@ source-repository head

library
exposed-modules:
Algorithms.List.BasicOperations.DropWhile
Algorithms.List.BasicOperations.Filter
Algorithms.List.BasicOperations.Inits
Algorithms.List.BasicOperations.Iterate
Algorithms.List.BasicOperations.Length
Algorithms.List.BasicOperations.Map
Algorithms.List.BasicOperations.Reverse
Algorithms.List.BasicOperations.Span
Algorithms.List.BasicOperations.Subsequences
Algorithms.List.BasicOperations.Tails
Algorithms.List.BasicOperations.TakeWhile
Algorithms.List.BasicOperations.Zip
Algorithms.List.EditDistance
Expand Down

0 comments on commit 56c8a35

Please sign in to comment.