Created
July 2, 2017 22:55
-
-
Save dgendill/041bd8e5e838e1fc87bb6afaeaf3b3a8 to your computer and use it in GitHub Desktop.
Factorial Recursion Schemes
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module RecursionSchemesExample where | |
import Prelude | |
import Control.Monad.Free (Free, liftF) | |
import Data.Foldable (foldMap) | |
import Data.Functor.Nu (Nu) | |
import Data.List (List, catMaybes, null) | |
import Data.Tuple (Tuple(..)) | |
import Matryoshka as M | |
import Matryoshka.Algebra (GAlgebra, Algebra) | |
import Matryoshka.Class.Recursive (class Recursive, project) | |
import Matryoshka.Coalgebra (GCoalgebra, Coalgebra) | |
import Data.Either(Either(..)) | |
-- | AST represeting a factorial | |
data FactF a = Next Int a | Done | |
type Fact = Nu FactF | |
derive instance functorFactF :: Functor FactF | |
-- | Tear a factorial down to a number | |
factTearDown :: GAlgebra (Tuple Fact) FactF Int | |
factTearDown Done = 1 | |
factTearDown (Next n (Tuple nu m)) = n * m | |
-- | Build a factorial from a number | |
factBuildUp :: Coalgebra FactF Int | |
factBuildUp 0 = Done | |
factBuildUp a = Next a (a - 1) | |
-- | Build a factorial from a number, and stop when a certain | |
-- | number is reached | |
factLimitBuildUp :: Int -> GCoalgebra (Either Fact) FactF Int | |
factLimitBuildUp l a | |
| a == 0 = Done | |
| l == a = Next a (Left $ M.embed Done) -- (a - 1)) | |
| otherwise = Next a (Right (a - 1)) | |
-- | Interpret a factorial as numbers | |
factAlg :: Algebra FactF Int | |
factAlg Done = 1 | |
factAlg (Next i a) = i * a | |
-- | Get the factorial of a number | |
factPara :: Int -> Int | |
factPara i = runFact (val i) | |
where | |
val :: Int -> Fact | |
val n = M.ana factBuildUp n | |
-- | Get the factorial of a number | |
factHylo :: Int -> Int | |
factHylo = M.hylo factAlg factBuildUp | |
-- | Interpret a factorial as a number | |
runFact :: Fact -> Int | |
runFact = M.para factTearDown | |
-- | A factorial-like function that short circuits | |
-- | at a certain number | |
-- | ``` | |
-- | factUntil 4 5 = 20 = 5*4 | |
-- | factUntil 3 5 = 60 = 5*4*3 | |
-- | factUntil 2 5 = 160 = 5*4*3*2 | |
-- | factUntil 5 10 = 151200 = 10*9*8*7*6*5 | |
-- | ``` | |
factUntil :: Int -> Int -> Int | |
factUntil l i = runFact $ M.apo (factLimitBuildUp l) i |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment