Compare commits
No commits in common. "4e918db5cb87f79f43f75a0b5c293fbdf571b510" and "6e88780f8b40bf55e82e576f316afac73fa8f147" have entirely different histories.
4e918db5cb
...
6e88780f8b
@ -1,11 +0,0 @@
|
|||||||
state 0;
|
|
||||||
|
|
||||||
effect {
|
|
||||||
if(SOURCE == R) {
|
|
||||||
STATE = STATE + |LEFT|;
|
|
||||||
}
|
|
||||||
}
|
|
||||||
|
|
||||||
combine {
|
|
||||||
STATE = STATE + LSTATE + RSTATE;
|
|
||||||
}
|
|
@ -1,242 +0,0 @@
|
|||||||
module LanguageTwo where
|
|
||||||
import qualified PythonAst as Py
|
|
||||||
import Data.Char
|
|
||||||
import Data.Functor
|
|
||||||
import Text.Parsec
|
|
||||||
import Text.Parsec.Char
|
|
||||||
import Text.Parsec.Combinator
|
|
||||||
|
|
||||||
{- Data Types -}
|
|
||||||
data Op
|
|
||||||
= Add
|
|
||||||
| Subtract
|
|
||||||
| Multiply
|
|
||||||
| Divide
|
|
||||||
| Equal
|
|
||||||
| NotEqual
|
|
||||||
| And
|
|
||||||
| Or
|
|
||||||
|
|
||||||
data Expr
|
|
||||||
= IntLiteral Int
|
|
||||||
| BinOp Op Expr Expr
|
|
||||||
| Var String
|
|
||||||
| Length Expr
|
|
||||||
|
|
||||||
data Stmt
|
|
||||||
= IfElse Expr Stmt (Maybe Stmt)
|
|
||||||
| Assign String Expr
|
|
||||||
| Block [Stmt]
|
|
||||||
|
|
||||||
data Prog = Prog Expr [Stmt] [Stmt]
|
|
||||||
|
|
||||||
{- Parser -}
|
|
||||||
type Parser = Parsec String ()
|
|
||||||
|
|
||||||
parseKw :: String -> Parser ()
|
|
||||||
parseKw s = string s $> ()
|
|
||||||
|
|
||||||
parseKwIf :: Parser ()
|
|
||||||
parseKwIf = parseKw "if"
|
|
||||||
|
|
||||||
parseKwElse :: Parser ()
|
|
||||||
parseKwElse = parseKw "else"
|
|
||||||
|
|
||||||
parseKwState :: Parser ()
|
|
||||||
parseKwState = parseKw "state"
|
|
||||||
|
|
||||||
parseKwEffect :: Parser ()
|
|
||||||
parseKwEffect = parseKw "effect"
|
|
||||||
|
|
||||||
parseKwCombine :: Parser ()
|
|
||||||
parseKwCombine = parseKw "combine"
|
|
||||||
|
|
||||||
parseOp :: String -> Op -> Parser Op
|
|
||||||
parseOp s o = string s $> o
|
|
||||||
|
|
||||||
parseInt :: Parser Int
|
|
||||||
parseInt = read <$> (many1 digit <* spaces)
|
|
||||||
|
|
||||||
parseVar :: Parser String
|
|
||||||
parseVar =
|
|
||||||
do
|
|
||||||
c <- satisfy $ \c -> isLetter c || c == '_'
|
|
||||||
cs <- many (satisfy isLetter <|> digit) <* spaces
|
|
||||||
let name = c:cs
|
|
||||||
if name `elem` ["if", "else", "state", "effect", "combine"]
|
|
||||||
then fail "Can't use reserved keyword as identifier"
|
|
||||||
else return name
|
|
||||||
|
|
||||||
parseSurrounded :: Char -> Char -> Parser a -> Parser a
|
|
||||||
parseSurrounded c1 c2 pe =
|
|
||||||
do
|
|
||||||
char c1 >> spaces
|
|
||||||
e <- pe
|
|
||||||
spaces >> char c2 >> spaces
|
|
||||||
return e
|
|
||||||
|
|
||||||
parseLength :: Parser Expr
|
|
||||||
parseLength = Length <$> parseSurrounded '|' '|' parseExpr
|
|
||||||
|
|
||||||
parseParenthesized :: Parser Expr
|
|
||||||
parseParenthesized = parseSurrounded '(' ')' parseExpr
|
|
||||||
|
|
||||||
parseBasic :: Parser Expr
|
|
||||||
parseBasic = choice
|
|
||||||
[ IntLiteral <$> parseInt
|
|
||||||
, Var <$> parseVar
|
|
||||||
, parseLength
|
|
||||||
, parseParenthesized
|
|
||||||
]
|
|
||||||
|
|
||||||
parseLevel :: Parser Op -> Parser Expr -> Parser Expr
|
|
||||||
parseLevel po pe =
|
|
||||||
do
|
|
||||||
e <- pe <* spaces
|
|
||||||
ops <- many ((flip . BinOp <$> (po <* spaces) <*> pe) <* spaces)
|
|
||||||
return $ foldl (flip ($)) e ops
|
|
||||||
|
|
||||||
parseExpr :: Parser Expr
|
|
||||||
parseExpr = foldl (flip parseLevel) parseBasic
|
|
||||||
[ parseOp "*" Multiply <|> parseOp "/" Divide
|
|
||||||
, parseOp "+" Add <|> parseOp "-" Subtract
|
|
||||||
, parseOp "==" Equal <|> parseOp "!=" NotEqual
|
|
||||||
, parseOp "&&" And
|
|
||||||
, try $ parseOp "||" Or
|
|
||||||
]
|
|
||||||
|
|
||||||
parseIf :: Parser Stmt
|
|
||||||
parseIf = do
|
|
||||||
parseKwIf >> spaces
|
|
||||||
c <- parseParenthesized
|
|
||||||
t <- parseStmt <* spaces
|
|
||||||
e <- (Just <$> (parseKwElse >> spaces *> parseStmt)) <|> return Nothing
|
|
||||||
return $ IfElse c t e
|
|
||||||
|
|
||||||
parseBlockStmts :: Parser [Stmt]
|
|
||||||
parseBlockStmts = parseSurrounded '{' '}' (many parseStmt)
|
|
||||||
|
|
||||||
parseBlock :: Parser Stmt
|
|
||||||
parseBlock = Block <$> parseBlockStmts
|
|
||||||
|
|
||||||
parseAssign :: Parser Stmt
|
|
||||||
parseAssign = Assign <$>
|
|
||||||
(parseVar <* spaces <* char '=' <* spaces) <*>
|
|
||||||
parseExpr <* (char ';' >> spaces)
|
|
||||||
|
|
||||||
parseStmt :: Parser Stmt
|
|
||||||
parseStmt = choice
|
|
||||||
[ parseIf
|
|
||||||
, parseAssign
|
|
||||||
, parseBlock
|
|
||||||
]
|
|
||||||
|
|
||||||
parseProgram :: Parser Prog
|
|
||||||
parseProgram = do
|
|
||||||
state <- parseKwState >> spaces *> parseExpr <* char ';' <* spaces
|
|
||||||
effect <- parseKwEffect >> spaces *> parseBlockStmts <* spaces
|
|
||||||
combined <- parseKwCombine >> spaces *> parseBlockStmts <* spaces
|
|
||||||
return $ Prog state effect combined
|
|
||||||
|
|
||||||
parse :: String -> String -> Either ParseError Prog
|
|
||||||
parse = runParser parseProgram ()
|
|
||||||
|
|
||||||
{- Translation -}
|
|
||||||
baseFunction :: Py.PyExpr -> [Py.PyStmt] -> [Py.PyStmt] -> Py.PyStmt
|
|
||||||
baseFunction s e c = Py.FunctionDef "prog" ["xs"] $
|
|
||||||
[Py.IfElse
|
|
||||||
(Py.BinOp Py.LessThan
|
|
||||||
(Py.FunctionCall (Py.Var "len") [Py.Var "xs"])
|
|
||||||
(Py.IntLiteral 2))
|
|
||||||
[Py.Return $ Py.Tuple [s, Py.Var "xs"]]
|
|
||||||
[]
|
|
||||||
Nothing
|
|
||||||
, Py.Assign (Py.VarPat "leng")
|
|
||||||
(Py.BinOp Py.FloorDiv
|
|
||||||
(Py.FunctionCall (Py.Var "len") [Py.Var "xs"])
|
|
||||||
(Py.IntLiteral 2))
|
|
||||||
, Py.Assign (Py.VarPat "left")
|
|
||||||
(Py.Access
|
|
||||||
(Py.Var "xs")
|
|
||||||
[Py.Slice Nothing $ Just (Py.Var "leng")])
|
|
||||||
, Py.Assign (Py.VarPat "right")
|
|
||||||
(Py.Access
|
|
||||||
(Py.Var "xs")
|
|
||||||
[Py.Slice (Just (Py.Var "leng")) Nothing])
|
|
||||||
, Py.Assign (Py.TuplePat [Py.VarPat "ls", Py.VarPat "left"])
|
|
||||||
(Py.FunctionCall (Py.Var "prog") [Py.Var "left"])
|
|
||||||
, Py.Assign (Py.TuplePat [Py.VarPat "rs", Py.VarPat "right"])
|
|
||||||
(Py.FunctionCall (Py.Var "prog") [Py.Var "right"])
|
|
||||||
, Py.Standalone $
|
|
||||||
Py.FunctionCall (Py.Member (Py.Var "left") "reverse") []
|
|
||||||
, Py.Standalone $
|
|
||||||
Py.FunctionCall (Py.Member (Py.Var "right") "reverse") []
|
|
||||||
, Py.Assign (Py.VarPat "state") s
|
|
||||||
, Py.Assign (Py.VarPat "source") (Py.IntLiteral 0)
|
|
||||||
, Py.Assign (Py.VarPat "total") (Py.ListLiteral [])
|
|
||||||
, Py.While
|
|
||||||
(Py.BinOp Py.And
|
|
||||||
(Py.BinOp Py.NotEqual (Py.Var "left") (Py.ListLiteral []))
|
|
||||||
(Py.BinOp Py.NotEqual (Py.Var "right") (Py.ListLiteral []))) $
|
|
||||||
[ Py.IfElse
|
|
||||||
(Py.BinOp Py.LessThanEq
|
|
||||||
(Py.Access (Py.Var "left") [Py.IntLiteral $ -1])
|
|
||||||
(Py.Access (Py.Var "right") [Py.IntLiteral $ -1]))
|
|
||||||
[ Py.Standalone $
|
|
||||||
Py.FunctionCall (Py.Member (Py.Var "total") "append")
|
|
||||||
[Py.FunctionCall (Py.Member (Py.Var "left") "pop") []]
|
|
||||||
, Py.Assign (Py.VarPat "source") (Py.IntLiteral 1)
|
|
||||||
]
|
|
||||||
[] $
|
|
||||||
Just
|
|
||||||
[ Py.Standalone $
|
|
||||||
Py.FunctionCall (Py.Member (Py.Var "total") "append")
|
|
||||||
[Py.FunctionCall (Py.Member (Py.Var "right") "pop") []]
|
|
||||||
, Py.Assign (Py.VarPat "source") (Py.IntLiteral 2)
|
|
||||||
]
|
|
||||||
] ++ e
|
|
||||||
] ++ c ++
|
|
||||||
[ Py.Standalone $ Py.FunctionCall (Py.Member (Py.Var "left") "reverse") []
|
|
||||||
, Py.Standalone $ Py.FunctionCall (Py.Member (Py.Var "right") "reverse") []
|
|
||||||
, Py.Return $ Py.Tuple
|
|
||||||
[ Py.Var "state"
|
|
||||||
, foldl (Py.BinOp Py.Add) (Py.Var "total") [Py.Var "left", Py.Var "right"]
|
|
||||||
]
|
|
||||||
]
|
|
||||||
|
|
||||||
translateExpr :: Expr -> Py.PyExpr
|
|
||||||
translateExpr (IntLiteral i) = Py.IntLiteral i
|
|
||||||
translateExpr (BinOp op l r) =
|
|
||||||
Py.BinOp (translateOp op) (translateExpr l) (translateExpr r)
|
|
||||||
translateExpr (Var s)
|
|
||||||
| s == "SOURCE" = Py.Var "source"
|
|
||||||
| s == "LEFT" = Py.Var "left"
|
|
||||||
| s == "RIGHT" = Py.Var "right"
|
|
||||||
| s == "STATE" = Py.Var "state"
|
|
||||||
| s == "LSTATE" = Py.Var "ls"
|
|
||||||
| s == "RSTATE" = Py.Var "rs"
|
|
||||||
| s == "L" = Py.IntLiteral 1
|
|
||||||
| s == "R" = Py.IntLiteral 2
|
|
||||||
| otherwise = Py.Var s
|
|
||||||
translateExpr (Length e) = Py.FunctionCall (Py.Var "len") [translateExpr e]
|
|
||||||
|
|
||||||
translateOp :: Op -> Py.PyBinOp
|
|
||||||
translateOp Add = Py.Add
|
|
||||||
translateOp Subtract = Py.Subtract
|
|
||||||
translateOp Multiply = Py.Multiply
|
|
||||||
translateOp Divide = Py.Divide
|
|
||||||
translateOp Equal = Py.Equal
|
|
||||||
translateOp NotEqual = Py.NotEqual
|
|
||||||
translateOp And = Py.And
|
|
||||||
translateOp Or = Py.Or
|
|
||||||
|
|
||||||
translateStmt :: Stmt -> [Py.PyStmt]
|
|
||||||
translateStmt (IfElse c t e) =
|
|
||||||
[Py.IfElse (translateExpr c) (translateStmt t) [] (translateStmt <$> e)]
|
|
||||||
translateStmt (Assign "STATE" e) = [Py.Assign (Py.VarPat "state") (translateExpr e)]
|
|
||||||
translateStmt (Assign v e) = [Py.Assign (Py.VarPat v) (translateExpr e)]
|
|
||||||
translateStmt (Block s) = concatMap translateStmt s
|
|
||||||
|
|
||||||
translate :: Prog -> [Py.PyStmt]
|
|
||||||
translate (Prog s e c) =
|
|
||||||
[baseFunction (translateExpr s) (concatMap translateStmt e) (concatMap translateStmt c)]
|
|
@ -5,7 +5,6 @@ data PyBinOp
|
|||||||
| Subtract
|
| Subtract
|
||||||
| Multiply
|
| Multiply
|
||||||
| Divide
|
| Divide
|
||||||
| FloorDiv
|
|
||||||
| LessThan
|
| LessThan
|
||||||
| LessThanEq
|
| LessThanEq
|
||||||
| GreaterThan
|
| GreaterThan
|
||||||
@ -31,7 +30,6 @@ data PyExpr
|
|||||||
| Member PyExpr String
|
| Member PyExpr String
|
||||||
| In PyExpr PyExpr
|
| In PyExpr PyExpr
|
||||||
| NotIn PyExpr PyExpr
|
| NotIn PyExpr PyExpr
|
||||||
| Slice (Maybe PyExpr) (Maybe PyExpr)
|
|
||||||
|
|
||||||
data PyPat
|
data PyPat
|
||||||
= VarPat String
|
= VarPat String
|
||||||
|
@ -52,13 +52,11 @@ precedence Add = 3
|
|||||||
precedence Subtract = 3
|
precedence Subtract = 3
|
||||||
precedence Multiply = 4
|
precedence Multiply = 4
|
||||||
precedence Divide = 4
|
precedence Divide = 4
|
||||||
precedence FloorDiv = 4
|
|
||||||
precedence LessThan = 2
|
precedence LessThan = 2
|
||||||
precedence LessThanEq = 2
|
precedence LessThanEq = 2
|
||||||
precedence GreaterThan = 2
|
precedence GreaterThan = 2
|
||||||
precedence GreaterThanEq = 2
|
precedence GreaterThanEq = 2
|
||||||
precedence Equal = 2
|
precedence Equal = 2
|
||||||
precedence NotEqual = 2
|
|
||||||
precedence And = 1
|
precedence And = 1
|
||||||
precedence Or = 0
|
precedence Or = 0
|
||||||
|
|
||||||
@ -67,7 +65,6 @@ opString Add = "+"
|
|||||||
opString Subtract = "-"
|
opString Subtract = "-"
|
||||||
opString Multiply = "*"
|
opString Multiply = "*"
|
||||||
opString Divide = "/"
|
opString Divide = "/"
|
||||||
opString FloorDiv = "//"
|
|
||||||
opString LessThan = "<"
|
opString LessThan = "<"
|
||||||
opString LessThanEq = "<="
|
opString LessThanEq = "<="
|
||||||
opString GreaterThan = ">"
|
opString GreaterThan = ">"
|
||||||
@ -123,8 +120,6 @@ translateExpr (In m c) =
|
|||||||
"(" ++ translateExpr m ++ ") in (" ++ translateExpr c ++ ")"
|
"(" ++ translateExpr m ++ ") in (" ++ translateExpr c ++ ")"
|
||||||
translateExpr (NotIn m c) =
|
translateExpr (NotIn m c) =
|
||||||
"(" ++ translateExpr m ++ ") not in (" ++ translateExpr c ++ ")"
|
"(" ++ translateExpr m ++ ") not in (" ++ translateExpr c ++ ")"
|
||||||
translateExpr (Slice l r) =
|
|
||||||
maybe [] (parenth . translateExpr) l ++ ":" ++ maybe [] (parenth . translateExpr) r
|
|
||||||
|
|
||||||
translatePat :: PyPat -> String
|
translatePat :: PyPat -> String
|
||||||
translatePat (VarPat s) = s
|
translatePat (VarPat s) = s
|
||||||
|
@ -1,153 +0,0 @@
|
|||||||
---
|
|
||||||
title: A Language for an Assignment - Homework 2
|
|
||||||
date: 2019-12-30T20:05:10-08:00
|
|
||||||
tags: ["Haskell", "Python", "Algorithms"]
|
|
||||||
---
|
|
||||||
|
|
||||||
After the madness of the
|
|
||||||
[language for homework 1]({{< relref "00_cs325_languages_hw1.md" >}}),
|
|
||||||
the solution to the second homework offers a moment of respite.
|
|
||||||
Let's get right into the problems, shall we?
|
|
||||||
|
|
||||||
### Homework 2
|
|
||||||
Besides some free-response questions, the homework contains
|
|
||||||
two problems. The first:
|
|
||||||
|
|
||||||
{{< codelines "text" "cs325-langs/hws/hw2.txt" 29 34 >}}
|
|
||||||
|
|
||||||
And the second:
|
|
||||||
|
|
||||||
{{< codelines "text" "cs325-langs/hws/hw2.txt" 36 44 >}}
|
|
||||||
|
|
||||||
At first glance, it's not obvious why these problems are good for
|
|
||||||
us. However, there's one key observation: __`num_inversions` can be implemented
|
|
||||||
using a slightly-modified `mergesort`__. The trick is to maintain a counter
|
|
||||||
of inversions in every recursive call to `mergesort`, updating
|
|
||||||
it every time we take an element from the
|
|
||||||
{{< sidenote "right" "right-note" "right list" >}}
|
|
||||||
If this nomeclature is not clear to you, recall that
|
|
||||||
mergesort divides a list into two smaller lists. The
|
|
||||||
"right list" refers to the second of the two, because
|
|
||||||
if you visualize the original list as a rectangle, and cut
|
|
||||||
it in half (vertically, down the middle), then the second list
|
|
||||||
(from the left) is on the right.
|
|
||||||
{{< /sidenote >}} while there are still elements in the
|
|
||||||
{{< sidenote "left" "left-note" "left list" >}}
|
|
||||||
Why this is the case is left as an exercise to the reader.
|
|
||||||
{{< /sidenote >}}.
|
|
||||||
When we return from the call,
|
|
||||||
we add up the number of inversions from running `num_inversions`
|
|
||||||
on the smaller lists, and the number of inversions that we counted
|
|
||||||
as I described. We then return both the total number
|
|
||||||
of inversions and the sorted list.
|
|
||||||
|
|
||||||
So, we either perform the standard mergesort, or we perform mergesort
|
|
||||||
with additional steps added on. The additional steps can be divided into
|
|
||||||
three general categories:
|
|
||||||
|
|
||||||
1. __Initialization__: We create / set some initial state. This state
|
|
||||||
doesn't depend on the lists or anything else.
|
|
||||||
2. __Effect__: Each time that an element is moved from one of the two smaller
|
|
||||||
lists into the output list, we may change the state in some way (create
|
|
||||||
an effect).
|
|
||||||
3. __Combination__: The final state, and the results of the two
|
|
||||||
sub-problem states, are combined into the output of the function.
|
|
||||||
|
|
||||||
This is all very abstract. In the concrete case of inversions,
|
|
||||||
these steps are as follows:
|
|
||||||
|
|
||||||
1. __Initializtion__: The initial state, which is just the counter, is set to 0.
|
|
||||||
2. __Effect__: Each time an element is moved, if it comes from the right list,
|
|
||||||
the number of inversions is updated.
|
|
||||||
3. __Combination__: We update the state, simply adding the left and right
|
|
||||||
inversion counts.
|
|
||||||
|
|
||||||
We can make a language out of this!
|
|
||||||
|
|
||||||
### A Language
|
|
||||||
Again, let's start by visualizing what the solution will look like. How about this:
|
|
||||||
|
|
||||||
{{< rawblock "cs325-langs/sols/hw2.lang" >}}
|
|
||||||
|
|
||||||
We divide the code into the same three steps that we described above. The first
|
|
||||||
section is the initial state. Since it doesn't depend on anything, we expect
|
|
||||||
it to be some kind of literal, like an integer. Next, we have the effect section,
|
|
||||||
which has access to variables such as "STATE" (to access the current state)
|
|
||||||
and "LEFT" (to access the left list), or "L" to access the "name" of the left list.
|
|
||||||
We use an `if`-statement to check if the origin of the element that was popped
|
|
||||||
(held in the "SOURCE" variable) is the right list (denoted by "R"). If it is,
|
|
||||||
we increment the counter (state) by the proper amount. In the combine step, we simply increment
|
|
||||||
the state by the counters from the left and right solutions, stored in "LSTATE" and "RSTATE".
|
|
||||||
That's it!
|
|
||||||
|
|
||||||
#### Implementation
|
|
||||||
The implementation is not tricky at all. We don't need to use monads like we did last
|
|
||||||
time, and nor do we have to perform any fancy Python nested function declarations.
|
|
||||||
|
|
||||||
To keep with the Python convention of lowercase variables, we'll translate the
|
|
||||||
uppercase "global" variables to lowercase. We'll do it like so:
|
|
||||||
|
|
||||||
{{< codelines "Haskell" "cs325-langs/src/LanguageTwo.hs" 211 220 >}}
|
|
||||||
|
|
||||||
Note that we translated "L" and "R" to integer literals. We'll indicate the source of
|
|
||||||
each element with an integer, since there's no real point to representing it with
|
|
||||||
a string or a variable. We'll need to be aware of this when we implement the actual, generic
|
|
||||||
mergesort code. Let's do that now:
|
|
||||||
|
|
||||||
{{< codelines "Haskell" "cs325-langs/src/LanguageTwo.hs" 145 205 >}}
|
|
||||||
|
|
||||||
This is probably the ugliest part of this assignment: we handwrote a Python
|
|
||||||
AST in Haskell that implements mergesort with our augmentations. Note that
|
|
||||||
this is a function, which takes a `Py.PyExpr` (the initial state expression),
|
|
||||||
and two lists of `Py.PyStmt`, which are the "effect" and "combination" code,
|
|
||||||
respectively. We simply splice them into our regular mergesort function.
|
|
||||||
The translation is otherwise pretty trivial, so there's no real reason
|
|
||||||
to show it here.
|
|
||||||
|
|
||||||
### The Output
|
|
||||||
What's the output of our solution to `num_inversions`? Take a look for yourself:
|
|
||||||
|
|
||||||
```Python
|
|
||||||
def prog(xs):
|
|
||||||
if len(xs)<2:
|
|
||||||
return (0, xs)
|
|
||||||
leng = len(xs)//2
|
|
||||||
left = xs[:(leng)]
|
|
||||||
right = xs[(leng):]
|
|
||||||
(ls,left) = prog(left)
|
|
||||||
(rs,right) = prog(right)
|
|
||||||
left.reverse()
|
|
||||||
right.reverse()
|
|
||||||
state = 0
|
|
||||||
source = 0
|
|
||||||
total = []
|
|
||||||
while (left!=[])and(right!=[]):
|
|
||||||
if left[-1]<=right[-1]:
|
|
||||||
total.append(left.pop())
|
|
||||||
source = 1
|
|
||||||
else:
|
|
||||||
total.append(right.pop())
|
|
||||||
source = 2
|
|
||||||
if source==2:
|
|
||||||
state = state+len(left)
|
|
||||||
state = state+ls+rs
|
|
||||||
left.reverse()
|
|
||||||
right.reverse()
|
|
||||||
return (state, total+left+right)
|
|
||||||
```
|
|
||||||
|
|
||||||
Honestly, that's pretty clean. As clean as `left.reverse()` to allow for \\(O(1)\\) pop is.
|
|
||||||
What's really clean, however, is the implementation of mergesort in our language.
|
|
||||||
It goes as follows:
|
|
||||||
|
|
||||||
```
|
|
||||||
state 0;
|
|
||||||
effect {}
|
|
||||||
combine {}
|
|
||||||
```
|
|
||||||
|
|
||||||
To implement mergesort in our language, which describes mergesort variants, all
|
|
||||||
we have to do is not specify any additional behavior. Cool, huh?
|
|
||||||
|
|
||||||
That's the end of this post. If you liked this one (and the previous one!),
|
|
||||||
keep an eye out for more!
|
|
Loading…
Reference in New Issue
Block a user