Pesto is a text-based, human-editable, and machine-transformable cooking recipe interchange format.
module Codec.Pesto where
This section contains various information about this document. The second section motivates why inventing another file format is necessary, followed by the goals of Pesto. After a short Pesto primer for the casual user, the language’s syntax and semantics are presented. The linting section limits the language to useful cooking recipes. Examples for user presentation of recipes and serialization follow.
Being a literate program, this document is specification and reference implementation simultaneously. The code is written in Haskell and uses the parsec parser combinator library, as well as HUnit for unit tests. Even without knowing Haskell’s syntax, you should be able to understand this specification. There’s a description above every code snippet explaining what is going on.
The key words “MUST”, “MUST NOT”, “REQUIRED”, “SHALL”, “SHALL NOT”, “SHOULD”, “SHOULD NOT”, “RECOMMENDED”, “MAY”, and “OPTIONAL” in this document are to be interpreted as described in RFC 2119.
1
The landscape of recipe interchange formats is quite fragmented. First, there’s HTML microdata: Google rich snippets, equivalent to the schema.org microdata vocabulary, are widely used by commercial recipe sites. Although the main objective of microdata is to make content machine-readable most sites will probably use it because it is considered a search-engine optimization (SEO) and not a method for sharing recipes. h-recipe provides a second vocabulary that has not been adopted widely yet.
Most cooking-related software comes with custom recipe file formats. Some of them can be imported by other programs. Meal-Master is one of these widely supported formats. A vast trove of recipe files is available in this format. There does not seem to be any official documentation for the format, but inofficial ABNF grammar and format description exist. A Meal-Master recipe template might look like this:
---------- Recipe via Meal-Master (tm)
Title: <Title>
Categories: <Categories>
Yield: <N servings>
<N> <unit> <ingredient>
…
-------------------------------<Section name>-----------------------------
<More ingredients>
<Instructions>
-----
Rezkonv aims to improve the Mealmaster format by lifting some of its character limits, adding new syntax, and translating it to german. However, the specification is available on request only.
A second format some programs can import is MasterCook’s MXP file format and its XML-based successor, MX2. Beyond that there exist numerous application-specific, proprietary formats:
Uses a XML-based format called fdx version 1.1. There’s no specification to be found, but a few examples are available, and those are dated 2006.
Uses the file extension .mcb. A specification is available.
Uses its own export format. However, there is no documentation whatsoever.
The program’s export format suffers from the same problem. The only document available is the DTD.
Last updated in 2006 (version 1.0.4) for the german-language shareware program Kalorio has a custom and restrictive license that requires attribution and forbids derivate works.
Cross-platform application which supports its own “emailed recipe format” and a simple YAML-based format.
Between 2002 and 2005, a bunch of XML-based exchange formats were created. They are not tied to specific software, so none of them seems to be actively used nowadays:
Formerly known as DESSERT and released in 2002 (version 0.5). The license requires attribution and – at the same time – forbids using the name RecipeML for promotion without written permission.
Version 1.1 was released in 2002 as well, but the site is not online anymore. The DTD is licensed under the CC by-sa license.
Released in 2005 (version 0.5), aims to improve support for commercial uses (restaurant menus and cookbooks). The XSD’s license allows free use and redistribution, but the reference implementation has no licensing information.
Released 2005 as well and shared under the terms of CC by-sa is not available on the web anymore.
Finally, a few non-XML or obscure exchange formats have been created in the past: YumML is an approach similar to those listed above but based on YAML instead of XML. The specification has been removed from the web and is available through the Web Archive only.
Cordon Bleu (1999) encodes recipes as programs for a cooking machine and defines a Pascal-like language. Being so close to real programming languages, Cordon Bleu is barely usable by anyone except programmers. Additionally, the language is poorly-designed since its syntax is inconsistent, and the user is limited to a set of predefined functions.
Finally, there is RxOL, created in 1985. It constructs a graph from recipes written down with a few operators and postfix notation, and does not separate ingredients and cooking instructions like every other syntax introduced before. Although Pesto is not a direct descendant of RxOL both share many ideas.
microformats.org has a similar list of recipe interchange formats.
First of all, recipes are written by humans for humans. Thus a human-readable recipe interchange format is not enough. The recipes need to be human-editable without guidance like a GUI or assistant. That’s why, for instance, XML is unsuitable, and the interchange formats listed above have largely failed to gain traction. Even though simple, XML is still too complicated for the ordinary user. Instead, a format needs to be as simple as possible, with as little markup as possible. A human editor must be able to remember the entire syntax. This works best if the file contents “make sense.” An excellent example of this is Markdown.
We also must acknowledge that machines play an important role in our daily lives. They can help us, the users, accomplish our goals if they can also understand the recipes. Thus they, too, need to be able to read and write recipes. Again, designing a machine-readable format is not enough. Recipes must be machine-transformable. A computer program should be able to create a new recipe from two existing ones, look up the ingredients and tell us how many joules one piece of that cake will have. And so on.
That being said, Pesto does not aim to carry additional information about ingredients or recipes themselves. Nutrition data for each ingredient should be maintained in a separate database. Due to its minimal syntax, Pesto is also not suitable for extensive guides on cooking or the usual chitchat found in cooking books.
So let’s start by introducing Pesto by example. This text does not belong
to the recipe and is ignored by any software. The following line starts the
recipe:
%pesto
&pot
+1 l water
+salt
[boil]
+100 g penne
&10 min
[cook]
>1 serving pasta
(language: en)
And that’s how you make pasta: Boil one liter of water in a pot with a little bit of salt. Then add 100 g penne, cook them for ten minutes, and you get one serving pasta. That’s all.
There’s more syntax available to express alternatives (either penne or tagliatelle), ranges (1–2 l water or approximately 1 liter water), and metadata. But now you can have a first peek at my recipe collection.
module Codec.Pesto.Parse (
parse
, testInstruction(..)
, Quantity(..)
, Unit
, Object
, Approximately(..)
, Amount(..)
,
, isResult
, isReference
, isAlternative
, isAnnotation
, isAction
, isDirective
, isUnknown
, spaces1
, notspacewhere
) import Data.Char (isSpace)
import Data.Ratio ((%))
import Text.Parsec hiding (parse)
import Text.ParserCombinators.Parsec.Pos (newPos)
import Text.ParserCombinators.Parsec.Error (newErrorUnknown)
import Test.HUnit hiding (test)
import Codec.Pesto.Serialize (serialize)
Pesto parses UTF-8 encoded input data consisting of space-delimited token. Every character within the Unicode whitespace class is considered a space.
= ((,) <$> getPosition <*> instruction) `sepEndBy` spaces1
stream <?> "stream"
= many1 space spaces1
The following instructions are supported:
data Instruction =
Annotation String
| Ingredient Quantity
| Tool Quantity
| Action String
| Reference Quantity
| Result Quantity
| Alternative Quantity
| Directive String
| Unknown String
deriving (Show, Eq)
=
instruction
try annotation<|> try ingredient
<|> try tool
<|> try action
<|> try result
<|> try alternative
<|> try reference
<|> try directive
<|> try unknown
<?> "instruction"
The pesto grammar has two instruction types: The first one begins
with a start symbol (start
) and consumes any character up
to and including a terminating symbol (end
), which can be
escaped with a backslash (\
).
betweenEscaped :: Char -> Char -> Parsec String () String
=
betweenEscaped start end
char start*> many (try (char '\\' *> char end) <|> satisfy (/= end))
<* char end
Annotations and actions both are of this kind:
= Annotation <$> betweenEscaped '(' ')'
annotation = Action <$> betweenEscaped '[' ']' action
Here are examples for both:
= [cmpInstruction "(skinless\nboneless)" (Right (Annotation "skinless\nboneless"))
testOpterm "[stir together]" (Right (Action "stir together"))
, cmpInstruction "[stir\\]together]" (Right (Action "stir]together"))
, cmpInstruction "[stir [together]" (Right (Action "stir [together"))] , cmpInstruction
The second one starts with one identifying character, ignores the
following whitespace characters, and then consumes a
Quantity
.
oparg :: Char -> Parsec String () Instruction -> Parsec String () Instruction
= char ident *> spaces *> cont
oparg ident cont
= oparg '+' (Ingredient <$> quantity)
ingredient = oparg '&' (Tool <$> quantity)
tool = oparg '>' (Result <$> quantity)
result = oparg '|' (Alternative <$> quantity)
alternative = oparg '*' (Reference <$> quantity) reference
Additionally, there are two special instructions. Directives are
similar to the previous instructions but consume a quoted string
(qstr
).
= oparg '%' (Directive <$> qstr) directive
Unknown instructions are the fallthrough-case and accept anything. They must not be discarded at this point. The point of accepting anything is to fail as late as possible while processing input. This gives the parser a chance to print helpful messages that provide additional aid to the user, who can then fix the problem.
= Unknown <$> many1 notspace unknown
Below are examples for these instructions:
= [
testOparg "+100 g flour"
cmpInstruction Right (Ingredient (Quantity (Exact (AmountRatio (100%1))) "g" "flour")))
("&oven"
, cmpInstruction Right (Tool (strQuantity "oven")))
(">dough" (Right (Result (strQuantity "dough")))
, cmpInstruction "|trimmings" (Right (Alternative (strQuantity "trimmings")))
, cmpInstruction "*fish"
, cmpInstruction Right (Reference (strQuantity "fish")))
("% invalid" (Right (Directive "invalid")) "%invalid"
, cmpInstruction3 "* \t\n 1 _ cheese"
, cmpInstruction3 Right (Reference (Quantity (Exact (AmountRatio (1%1))) "" "cheese")))
("*1 _ cheese"
"!invalid" (Right (Unknown "!invalid")) "!invalid"
, cmpInstruction3 ]
Before introducing quantities we need to have a look at qstr, which is used by them. A qstr, short for quoted string, can be a string enclosed in double quotes, a single word or the underscore character that represents the empty string.
= try (betweenEscaped '"' '"')
qstr <|> word
<|> char '_' *> return ""
A word always starts with a letter, followed by any number of non-space characters.
= (:) <$> letter <*> many notspace
word = satisfy (not . isSpace) notspace
The empty string can be represented by two double quotes or the underscore, but not the empty string itself.
= [
testQstr "\"\"" (Right "") "_"
cmpQstr3 "_" (Right "")
, cmpQstr "" parseError , cmpQstr
Any Unicode character with a General_Category major class L (i.e., a letter, see Unicode standard section 4.5 for example) is accepted as first character of a word. That includes german umlauts as well as greek or arabic script. Numbers, separators, punctuation, and others are not permitted.
"water" (Right "water")
, cmpQstr "Äpfel" (Right "Äpfel")
, cmpQstr "τυρί" (Right "τυρί")
, cmpQstr "جبن" (Right "جبن")
, cmpQstr "1sugar" parseError
, cmpQstr "+milk" parseError
, cmpQstr "∀onion" parseError , cmpQstr
The remaining letters of a word can be any character, including symbols, numbers, …
"rump-roast" (Right "rump-roast")
, cmpQstr "v1negar" (Right "v1negar")
, cmpQstr "mush\"rooms" (Right "mush\"rooms") , cmpQstr
…but not spaces.
" tomatoes" parseError
, cmpQstr "tomatoes " parseError
, cmpQstr "lemon juice" parseError
, cmpQstr "sour\tcream" parseError
, cmpQstr "white\nwine" parseError , cmpQstr
If a string contains spaces or starts with a special character, it must be enclosed in double quotes.
"\"salt\"" (Right "salt") "salt"
, cmpQstr3 "\"+milk\"" (Right "+milk")
, cmpQstr "\"soy sauce\"" (Right "soy sauce")
, cmpQstr "\"1sugar\"" (Right "1sugar")
, cmpQstr "\"chicken\tbreast\nmeat\"" (Right "chicken\tbreast\nmeat") , cmpQstr
Doublequotes within a string can be quoted by prepending a backslash. However, the usual escape codes like \n, \t, … will not be expanded.
"\"vine\"gar\"" parseError
, cmpQstr "\"vine\\\"gar\"" (Right "vine\"gar") "vine\"gar"
, cmpQstr3 "\"oli\\ve oil\"" (Right "oli\\ve oil")
, cmpQstr "\"oli\\\\\"ve oil\"" (Right "oli\\\"ve oil")
, cmpQstr "\"sal\\tmon\"" (Right "sal\\tmon") "sal\\tmon"
, cmpQstr3 ]
A Quantity
is a triple of Approximately
,
Unit
and Object
as parameter.
data Quantity = Quantity Approximately Unit Object deriving (Show, Eq)
The syntactic construct is overloaded and accepts one to three
arguments. If just one is given, it is assumed to be the
Object
and Approximately
and Unit
are empty. Two arguments set Approximately
and
Unit
, which is convenient when the unit implies the object
(minutes usually refer to the object time, for example).
= try quantityA <|> quantityB quantity
= Quantity
quantityA <$> approximately
<* spaces1
<*> unit
<*> (try (spaces1 *> object) <|> return "")
= Quantity
quantityB <$> return (Exact (AmountStr ""))
<*> return ""
<*> object
= [
testQuantityOverloaded "oven" (exactQuantity (AmountStr "") "" "oven")
cmpQuantity "10 min" (exactQuantity (AmountRatio (10%1)) "min" "")
, cmpQuantity "100 g flour" (exactQuantity (AmountRatio (100%1)) "g" "flour") , cmpQuantity
The first two are equivalent to
"_ _ oven" (exactQuantity (AmountStr "") "" "oven") "oven"
, cmpQuantity3 "10 min _" (exactQuantity (AmountRatio (10%1)) "min" "") "10 min" , cmpQuantity3
Missing units must not be omitted. The version with underscore should be preferred.
"1 \"\" meal" (exactQuantity (AmountRatio (1%1)) "" "meal") "1 _ meal"
, cmpQuantity3 "1 _ meal" (exactQuantity (AmountRatio (1%1)) "" "meal")
, cmpQuantity ]
Units and objects are just strings. However, units should be limited to well-known metric units.
type Unit = String
= qstr
unit
type Object = String
= qstr object
Approximately
is a wrapper for ranges, that is, two
amounts separated by a dash, approximate amounts, prepended with a
tilde, and exact amounts without a modifier.
data Approximately =
Range Amount Amount
| Approx Amount
| Exact Amount
deriving (Show, Eq)
= try range <|> try approx <|> exact
approximately range = Range <$> amount <*> (char '-' *> amount)
= Approx <$> (char '~' *> amount)
approx = Exact <$> amount exact
= [
testQuantityApprox "1-2 _ bananas" (Right (Quantity (Range (AmountRatio (1%1)) (AmountRatio (2%1))) "" "bananas"))
cmpQuantity "1 - 2 _ bananas" parseError
, cmpQuantity "1- 2 _ bananas" parseError
, cmpQuantity "1 -2 _ bananas" parseError
, cmpQuantity "~2 _ bananas" (Right (Quantity (Approx (AmountRatio (2%1))) "" "bananas"))
, cmpQuantity "~ 2 _ bananas" parseError
, cmpQuantity ]
Amounts are limited to rational numbers and strings. There are no real numbers by design, and implementations should avoid representing rational numbers as floating point numbers. They are not required and introduce ugly corner cases when rounding while converting units, for example.
data Amount =
AmountRatio Rational
| AmountStr String
deriving (Show, Eq)
= try ratio <|> AmountStr <$> qstr amount
= [
testQuantityAmount "some _ pepper" (exactQuantity (AmountStr "some") "" "pepper")
cmpQuantity "\"some\"-\"a few\" _ bananas" (Right (Quantity (Range (AmountStr "some") (AmountStr "a few")) "" "bananas")) "some-\"a few\" _ bananas"
, cmpQuantity3 "~\"the stars in your eyes\" _ bananas" (Right (Quantity (Approx (AmountStr "the stars in your eyes")) "" "bananas"))
, cmpQuantity ]
Rational numbers can be an integral, numerator, and denominator, each separated by a forward slash, just the numerator and denominator, again separated by a forward slash, or just a numerator with the default denominator 1 (i.e., ordinary integral number).
= let toRatio i num denom = AmountRatio ((i*denom+num)%denom) in
ratio <$> int <*> (char '/' *> int) <*> (char '/' *> int))
try (toRatio <|> try (toRatio <$> return 0 <*> int <*> (char '/' *> int))
<|> try (toRatio <$> return 0 <*> int <*> return 1)
The following representations are all equal with the first one being the preferred one:
= [
testQuantityRatio "3 _ bananas" (exactQuantity (AmountRatio (3%1)) "" "bananas")
cmpQuantity "3/1 _ bananas" (exactQuantity (AmountRatio (3%1)) "" "bananas")
, cmpQuantity3 "3 _ bananas"
"3/0/1 _ bananas" (exactQuantity (AmountRatio (3%1)) "" "bananas")
, cmpQuantity3 "3 _ bananas"
Two numbers are numerator and denominator:
"3/5 _ bananas" (exactQuantity (AmountRatio (3%5)) "" "bananas") , cmpQuantity
Three numbers add an integral part:
"3/5/7 _ bananas" (exactQuantity (AmountRatio ((3*7+5)%7)) "" "bananas")
, cmpQuantity "10/3 _ bananas" (exactQuantity (AmountRatio (10%3)) "" "bananas")
, cmpQuantity3 "3/1/3 _ bananas"
Rational numbers can be used in ranges and mixed with strings too.
"1-\"a few\" _ bananas" (Right (Quantity
, cmpQuantity Range (AmountRatio (1%1)) (AmountStr "a few")) "" "bananas"))
("1/1/2-2 _ bananas" (Right (Quantity
, cmpQuantity Range (AmountRatio (3%2)) (AmountRatio (4%2))) "" "bananas"))
("~1/1/2 _ bananas" (Right (Quantity
, cmpQuantity Approx (AmountRatio (3%2))) "" "bananas"))
( ]
Parser main entry point.
= runParser stream () ""
parse = read <$> many1 digit int
Test helpers:
Left _) = True
isLeft (= False isLeft _
A generic parser error:
= Left (newErrorUnknown (newPos "" 0 0)) parseError
Compare output of parser f
for string str
with expected
. The expected result can be a parser error,
which matches any actual parse error (first case).
Left _) = TestCase $ assertBool str $ isLeft $ runParser (f <* eof) () "" str
cmpParser f str (= str ~: runParser (f <* eof) () "" str ~?= expected cmpParser f str expected
@(Left _) _ = [cmpParser f str expectp]
cmpParseSerialize f str expectp@(Right expectpval) expects = [
cmpParseSerialize f str expectp
cmpParser f str expectp~?= expects] , serialize expectpval
Wrap qstr test in AmountStr to aid serialization test
= cmpQstr3 input expectp input
cmpQstr input expectp Left expect) _ = [cmpParser (AmountStr <$> qstr) input (Left expect)]
cmpQstr3 input (Right expect) expects = cmpParseSerialize (AmountStr <$> qstr) input (Right (AmountStr expect)) expects cmpQstr3 input (
= cmpQuantity3 a b a
cmpQuantity a b = cmpParseSerialize quantity cmpQuantity3
= cmpInstruction3 a b a
cmpInstruction a b = cmpParseSerialize instruction cmpInstruction3
= Right (Quantity (Exact a) b c)
exactQuantity a b c = Quantity (Exact (AmountStr "")) "" strQuantity
= [
test "quantity" ~: testQuantityOverloaded
++ testQuantityApprox
++ testQuantityAmount
++ testQuantityRatio
"qstr" ~: testQstr
, "oparg" ~: testOparg
, "opterm" ~: testOpterm
, ]
Result _) = True
isResult (= False
isResult _ Reference _) = True
isReference (= False
isReference _ Alternative _) = True
isAlternative (= False
isAlternative _ Annotation _) = True
isAnnotation (= False
isAnnotation _ Action _) = True
isAction (= False
isAction _ Directive _) = True
isDirective (= False
isDirective _ Unknown _) = True
isUnknown (= False isUnknown _
module Codec.Pesto.Graph (
toGraph
, walkRoot
, outgoingEdges
, outgoingNodes
, incomingEdges
, incomingNodes
, firstNodeId
, resolveReferences
, test
, extractNodeId
, Node
, Nodes
, Edge
, Edges
, where
) import Data.Char (toLower)
import Data.List (sort, nub)
import Test.HUnit hiding (test, Node)
import Codec.Pesto.Parse hiding (test)
The parser’s output, a stream of instructions, may contain multiple recipes. A recipe must start with the directive “pesto” and may end with “buonappetito”, which allows embedding recipes into other (plain-text) documents. This function extracts all recipes from the stream and removes both directives.
= Directive "pesto"
startDirective = Directive "buonappetito" endDirective
= []
extract [] :stream) | s == startDirective = between:extract next
extract (swhere
| x `elem` [startDirective, endDirective] = True
isEnd x = False
isEnd _ = break isEnd stream
(between, next) :xs) = extract xs extract (_
Start and end directives are removed from the extracted instructions. The directive “buonappetito” is optional at the end of a stream.
= [
testExtract ~?= [[]]
extract [startDirective, endDirective] Action "foobar", endDirective] ~?= [[Action "foobar"]]
, extract [startDirective, ~?= [[]]
, extract [startDirective] Directive "foobar"] ~?= [[Directive "foobar"]] , extract [startDirective,
Instructions surrounding the start and end directive are removed.
Unknown "Something", startDirective] ~?= [[]]
, extract [Unknown "Something", Action "pour", startDirective] ~?= [[]]
, extract [Annotation "something"] ~?= [[]] , extract [startDirective, endDirective,
The stream may contain multiple recipes. The start directive also ends the previous recipe and starts a new one.
, extract [
startDirectiveAction "pour"
,
, endDirectiveAction "foobar"
,
, startDirectiveAnnotation "something"]
, ~?= [[Action "pour"], [Annotation "something"]]
, extract [
startDirectiveAction "heat"
,
, startDirectiveAnnotation "something"]
, ~?= [[Action "heat"], [Annotation "something"]]
, extract [
startDirectiveAnnotation "foobar"
,
, startDirective
, endDirective]~?= [[Annotation "foobar"], []]
]
Each recipe’s stream of instructions drives a stack-based machine that transforms it into a directed graph. Think of the stack as your kitchen’s workspace that is used to prepare the food’s components. You can add new ingredients, perform actions on them, put them aside, and add them again.
This function processes a list of nodes, that is, instructions uniquely identified by an integer, and returns the edges of the directed graph as a list of tuples.
toGraph :: Nodes Instruction -> Edges
= third $ foldl f (Nothing, [[]], []) nodes
toGraph nodes where
Ingredients are simply added to the current workspace. They should, for example, appear on the shopping list.
Ingredient _) = addToStack ctx i f ctx (i,
The same happens for tools. However, they are not part of the final product but are used in the process of making it. Thus, they do not appear on the shopping list. Time is considered a tool.
Tool _) = addToStack ctx i f ctx (i,
Actions take all ingredients and tools currently on the workspace, perform some action with them, and put the product back onto the workspace.
:sx, edges) (i, Action _) = (Just i, [i]:stack:sx, edgesTo i stack ++ edges)
f (_, stackAction _) = undefined -- never reached f (_, [], _) (_,
Results add a label to the current workspace’s contents and move them out of the way. It should be a meaningful name, not just A and B. Consecutive results add different labels to the same workspace. That’s useful when an action yields multiple results at once that are processed in different ways.
Result _) = consumeStack ctx i f ctx (i,
Alternatives, too, add a label to the current workspace’s content, but they pick one of the things on the workspace and throw everything else away. This allows adding optional or equivalent ingredients to a recipe (i.e., margarine or butter).
Alternative _) = consumeStack ctx i f ctx (i,
References are similar to ingredients. They are used to add items
from a workspace labeled with Result
or
Alternative
. More on that in the next
section.
Reference _) = addToStack ctx i f ctx (i,
Annotations add a description to any of the previous instructions.
They can be used to provide more information about ingredients (so “hot
water” becomes +water (hot)
, tools
(&oven (200 °C)
), or actions
([cook] (until brown)
).
@(Nothing, _, _) (_, Annotation _) = ctx
f ctxJust prev, s, edges) (i, Annotation _) = (Just prev, s, (i, prev):edges) f (
Unused directives or unknown instructions are danging nodes with no connection to other nodes.
Directive _) = ctx
f ctx (_, Unknown _) = ctx f ctx (_,
These are helper functions:
:sx, edges) i = (Just i, (i:stack):sx, edges)
addToStack (_, stack= undefined -- never reached
addToStack (_, [], _) _ =
consumeStack (_, s, edges) i let
= dropWhile null s
stack :sx) = if null stack then [[]] else stack
(topin (Just i, []:top:sx, edgesTo i top ++ edges)
= map (\x -> (x, i)) edgesTo i
Here are a few examples of how this stack-machine works. Each edge is
a tuple of two integer numbers. These are the nodes it connects,
starting with zero. Ingredient
, Tool
, and
Reference
itself do not create any edges:
= [
testGraph "+ketchup &spoon *foobar" [] cmpGraph
But Action
, Alternative
and
Result
do in combination with them:
"+foobar [barbaz]" [(0, 1)]
, cmpGraph "+foobar |barbaz" [(0, 1)]
, cmpGraph "+foobar >barbaz" [(0, 1)]
, cmpGraph "+foobar +B >barbaz" [(0, 2), (1, 2)]
, cmpGraph "+foobar >barbaz +foobar >barbaz" [(0, 1), (2, 3)]
, cmpGraph "+foobar [barbaz] +foobar >barbaz" [(0, 1), (1, 3), (2, 3)]
, cmpGraph "&foobar [barbaz] [C] >D" [(0, 1), (1, 2), (2, 3)] , cmpGraph
If the stack is empty, i.e. it was cleared by a Result
or Alternative
instruction, consecutive results or
alternatives operate on the previous, non-empty stack.
"+foobar >barbaz >C" [(0, 1), (0, 2)]
, cmpGraph "+foobar >barbaz >C >D" [(0, 1), (0, 2), (0, 3)]
, cmpGraph "+foobar |barbaz |C" [(0, 1), (0, 2)]
, cmpGraph "+foobar >barbaz |C" [(0, 1), (0, 2)] , cmpGraph
Unless that stack too is empty. Then they do nothing:
">foobar >foobar" []
, cmpGraph "|foobar |foobar" []
, cmpGraph "(foobar) (foobar)" []
, cmpGraph "[foobar]" [] , cmpGraph
The Annotation
instruction always creates an edge to the
most-recently processed node that was not an annotation. Thus two
consecutive annotations create edges to the same node.
"+foobar (barbaz)" [(1, 0)]
, cmpGraph "+foobar (barbaz) (C)" [(1, 0), (2, 0)]
, cmpGraph "+foobar (barbaz) >barbaz" [(1, 0), (0, 2)]
, cmpGraph "+foobar >barbaz (C)" [(0, 1), (2, 1)]
, cmpGraph "+foobar |barbaz (C)" [(0, 1), (2, 1)]
, cmpGraph "*foobar (C)" [(1, 0)] , cmpGraph
Unknown directives or instructions are never connected to other nodes.
"%invalid" []
, cmpGraph "invalid" []
, cmpGraph ]
Results and alternatives can be referenced with the
Reference
instruction. Resolving these references does not
happen while building the graph but afterward. This allows referencing a
result or alternative before its definition with regard to their
processing order.
Resolving references is fairly simple: For every reference’s object name, a case-insensitive lookup is performed in a table containing all results and alternatives. If it succeeds, an edge from every result and alternative returned to the reference in question is created.
resolveReferences :: Nodes Instruction -> Edges
= foldl f [] nodes
resolveReferences nodes where
@(Reference _)) = map (\x -> (x, i)) (findTargets nodes ref) ++ edges
f edges (i, ref= edges f edges _
findTargets :: Nodes Instruction -> Instruction -> [NodeId]
Reference (Quantity _ _ a)) = map fst $ filter (isTarget a) nodes
findTargets nodes (where
= map toLower
lc Result (Quantity _ _ x)) = lc x == lc dest
isTarget dest (_, Alternative (Quantity _ _ x)) = lc x == lc dest
isTarget dest (_, = False
isTarget _ _ = [] findTargets _ _
References are position-independent and can be used before or after the result instruction they are referencing.
= [
testRef ">foobar *foobar" [(0, 1)]
cmpGraphRef ">foobar |foobar *foobar" [(0, 2), (1, 2)]
, cmpGraphRef "+A >foobar +B >barbaz *foobar *barbaz" [(1, 4), (3, 5)]
, cmpGraphRef "*foobar >foobar" [(1, 0)] , cmpGraphRef
Nonexistent references do not create an edge.
">foobar *barbaz" [] , cmpGraphRef
References can use amounts and units.
">foobar *1 _ foobar *2 _ foobar" [(0, 1), (0, 2)] , cmpGraphRef
There are a few cases that do not make sense here (like loops or multiple results with the same name). They are permitted at this stage, but rejected later.
"*foobar |foobar >foobar" [(1, 0), (2, 0)]
, cmpGraphRef "|foobar *foobar >foobar *foobar" [(0, 1), (0, 3), (2, 1), (2, 3)]
, cmpGraphRef ]
= sort edges ~?= sort expect
runGraphWith f doc expect where
Right op) = (head . extract . snd . unzip) <$> parse ("%pesto " ++ doc)
(= zip [firstNodeId..] op
nodes = f nodes
edges = runGraphWith toGraph
cmpGraph = runGraphWith resolveReferences cmpGraphRef
type NodeId = Int
type Node a = (NodeId, a)
type Nodes a = [Node a]
type Edge = (NodeId, NodeId)
type Edges = [Edge]
= 0 :: NodeId firstNodeId
Find graph’s root node(s), that is a node without outgoing edges:
= let out = nub $ map fst edges
walkRoot nodes edges in filter (\(x, _) -> notElem x out) nodes
Get all nodes with edges pointing towards nodeid
= filter ((==) nodeid . snd) edges
incomingEdges edges nodeid = map ((!!) nodes . fst) $ incomingEdges edges nodeid incomingNodes nodes edges nodeid
= filter ((==) nodeid . fst) edges
outgoingEdges edges nodeid = map ((!!) nodes . snd) $ outgoingEdges edges nodeid outgoingNodes nodes edges nodeid
= ["graph" ~: testGraph, "ref" ~: testRef, "extract" ~: testExtract] test
= x third (_, _, x)
module Codec.Pesto.Lint (lint
, test
, parseMetadata
, extractMetadataMetadata(..)
, LintResult(..)) where
, import Test.HUnit hiding (test, Node)
import Data.List (sort, isPrefixOf, insert, intersect)
import Text.Parsec hiding (parse)
import Data.Char (isSpace, toLower)
import Data.Ratio ((%))
import Data.Maybe (fromMaybe)
import qualified Data.Map.Strict as M
import Codec.Pesto.Graph hiding (test)
import Codec.Pesto.Parse hiding (test)
Not every graph generated in the previous section is a useful recipe. Some instruction sequences just do not make sense. The tests in this section can detect those. Failing any of them does not render a stream of instructions or graph invalid. They just do not describe a useful recipe. Thus implementations must not generate or export such documents. However, they should accept input that fails any of the tests and warn the user about the failure.
Additionally, this section provides guidance on how to use the instructions provided by the Pesto language properly.
The graph must have exactly one root node (i.e., a node with incoming edges only). This also requires all results and alternatives to be referenced somewhere. Directives are either consumed when parsing, generating a graph, and linting. Otherwise they are dangling as well. Unknown instructions are always dangling.
= case walkRoot nodes edges of
rootIsResult nodes edges -> [LintResult NoRootNode []]
[] Result _):[] -> []
(_, :[] -> [LintResult NonResultRootNode [i]]
(i, _)-> [LintResult MoreThanOneRootNode (map fst xs)] xs
Empty recipes or circular references have no root node:
= [
testConnectivity "" [LintResult NoRootNode [], LintResult NoMetadata []]
cmpLint "*foobar >foobar"
, cmpLint LintResult NoRootNode [], LintResult CircularLoop [0, 1], LintResult NoMetadata []]
["+foobar"
, cmpLint LintResult NonResultRootNode [0], LintResult NoMetadata []] [
Directives and unknown instructions are dangling and thus root nodes.
"invalid %invalid +foo >bar"
, cmpLint LintResult MoreThanOneRootNode [0,1,3], LintResult NoMetadata []]
[ ]
The graph’s root node must be a result. It contains yield (amount and unit) and title (object) of the recipe.
= case walkRoot nodes edges of
extractMetadata nodes edges Result q@(Quantity _ _ title))] ->
[(i, Just $ (i, ("title", MetaStr title))
:(i, ("yield", MetaQty q))
:foldl f [] (incomingNodes nodes edges i)
-> Nothing
_ where
Additional key-value metadata for the whole recipe can be added as annotations to the root node. If multiple annotations with the same key exist, the key maps to a list of those values. Annotations that are unparseable key-value pairs are added as recipe description instead.
Annotation s) = case parseMetadata s of
f xs (i, Left _ -> (i, ("description", MetaStr s)):xs
Right (k, v) -> (i, (k, MetaStr v)):xs
= xs f xs _
Key and value are separated by a colon. Keys must not contain whitespace or the colon char. A value may be empty.
= runParser metadata () ""
parseMetadata = let keychars = satisfy (\x -> not (isSpace x) && x /= ':') in (,)
metadata <$> many1 keychars
<*> (char ':' *> spaces *> many anyChar)
= case extractMetadata nodes edges of
lintMetadata nodes edges Just result -> foldl checkKey [] result
Nothing -> [LintResult NoMetadata []]
where
| isKeyKnown k = xs
checkKey xs (_, (k, _)) = LintResult UnknownMetadataKey [i]:xs checkKey xs (i, _)
Valid metadata keys are listed below. Additionally, applications may add keys by prefixing them with “x-myapp-”. Thus an application called “basil” adding “some-key” would use the full key “x-basil-some-key”.
= k `elem` knownKeys || "x-" `isPrefixOf` k isKeyKnown k
The following metadata keys are permitted:
= [ knownKeys
The title, description and yield are implicit.
"title"
"description"
, "yield" ,
The recipe’s language, as 2 character code (ISO 639-1).
"language" ,
Time both must be a time-unit quantity.
"time" ,
An image can be a relative file reference or URI
"image"
, "author"
, ]
For instance a german language recipe for one person would look like this:
= [
testMetadata "+foo >1 _ foobar (language: de) (x-app-key: value)"
cmpLintMeta
[]Just [(1, ("title", MetaStr "foobar"))
(1, ("yield", MetaQty (Quantity (Exact (AmountRatio (1%1))) "" "foobar")))
, (2, ("language", MetaStr "de"))
, (3, ("x-app-key", MetaStr "value"))]) , (
Unparseable annotations or unknown keys are linting errors:
"+foo >foobar (unknown-key: value)"
, cmpLintMeta LintResult UnknownMetadataKey [2]]
[Just [(1, ("title", MetaStr "foobar"))
(1, ("yield", MetaQty (strQuantity "foobar")))
, (2, ("unknown-key", MetaStr "value"))]) , (
Root node annotations not containing a parseable key-value pair are assigned the key “description”.
"+foo >foobar ( some description ) (another one: with colon) (another: valid key-value)"
, cmpLintMeta LintResult UnknownMetadataKey [4]]
[Just [(1, ("title", MetaStr "foobar"))
(1, ("yield", MetaQty (strQuantity "foobar")))
, (2, ("description", MetaStr " some description "))
, (3, ("description", MetaStr "another one: with colon"))
, (4, ("another", MetaStr "valid key-value"))])
, ( ]
By definition, time is a tool and not an ingredient.
= ["s", "min", "h", "d"]
timeUnits
Quantity _ unit "") | unit `elem` timeUnits = True
isTime (= False isTime _
= foldl f [] nodes
timeIsATool nodes _ where
Ingredient q) | isTime q = LintResult TimeIsATool [nodeid]:xs
f xs (nodeid, = xs f xs _
= [
testLintQuantity "+10 min >foo" [LintResult TimeIsATool [0]]
cmpLint "+10-12 h >foo" [LintResult TimeIsATool [0]]
, cmpLint "+90/120 s >foo" [LintResult TimeIsATool [0]]
, cmpLint "+~12 s >foo" [LintResult TimeIsATool [0]]
, cmpLint "&10 min [bar] >foo" []
, cmpLint ]
Only actions can be annotated like this. It can be used to indicate how long a particular action is expected to take (i.e., peeling potatoes takes two minutes) or how long the action is supposed to be executed (i.e. cook for five minutes). More time annotations improve the software’s scheduling capabilities.
= foldl f [] nodes
timeAnnotatesAction nodes edges where
Tool q) | isTime q && (not . allActions) (outgoingEdges edges nodeid) = LintResult TimeAnnotatesAction [nodeid]:xs
f xs (nodeid, = xs
f xs _ = (!!) nodes . snd
toNodelist = all (isAction . snd . toNodelist) allActions
For example, “cook 10 minutes” can be expressed with:
= [
testTimeAnnotatesAction "&10 min [cook] >soup" []
cmpLint "&10 min [cook] &5-6 h [cook again] >soup" []
, cmpLint "&10 min >soup" [LintResult TimeAnnotatesAction [0]]
, cmpLint "&10 min &15 min |time *time [cook] >soup"
, cmpLint LintResult TimeAnnotatesAction [0], LintResult TimeAnnotatesAction [1]]
[ ]
Units can be arbitrary strings, but implementations should recognize the standard metric units g (gram), l (liter), and m (meter). One of these prefixes may be used with each of them: m (milli-), c (centi-), d (dezi-), and k (kilo-). Additionally, time in s (second), min (minute), h (hour), and d (day) should be accepted.
= foldl f [] nodes
wellKnownUnit nodes _ where
Ingredient q) = Just q
extractQty (Tool q) = Just q
extractQty (Result q) = Just q
extractQty (Alternative q) = Just q
extractQty (Reference q) = Just q
extractQty (= Nothing
extractQty _ | fromMaybe False (extractQty instr >>= (return . not . known)) =
f xs (nodeid, instr) LintResult UnitNotWellKnown [nodeid]:xs
= xs
f xs _ Quantity _ unit _) = unit `elem` knownUnits
known (= [
knownUnits ""
"mg", "g", "kg"
, "ml", "cl", "dl", "l"
, "cm", "dm", "m"
, ++ timeUnits ]
Usage of imperial units (inch, pound, …), non-standard units like “teaspoon,” “cup,” or similar is discouraged because the former is used by just three countries in the world right now, and the latter is language- and country-dependent. The implementation may provide the user with a conversion utility.
= [
testLintWellKnownUnit "+1 in foobar >bar" [LintResult UnitNotWellKnown [0]]
cmpLint "+2 teaspoons foobar >bar" [LintResult UnitNotWellKnown [0]]
, cmpLint "+3 cups foobar >bar" [LintResult UnitNotWellKnown [0]]
, cmpLint "+1 ml foobar >bar" []
, cmpLint "+1 cl foobar >bar" []
, cmpLint "+1 dl foobar >bar" []
, cmpLint "+1 l foobar >bar" []
, cmpLint "+2 _ something >bar" []
, cmpLint "&1 min [foo] >bar" [] , cmpLint
The unit is case-sensitive, thus
"+1 Mg foobar >bar" [LintResult UnitNotWellKnown [0]]
, cmpLint "+1 kG foobar >bar" [LintResult UnitNotWellKnown [0]]
, cmpLint "&1 MIN [foo] >bar" [LintResult UnitNotWellKnown [0]]
, cmpLint ]
All references must be resolved. An earlier check ensures all results and alternatives are referenced at some point.
= foldl f [] nodes
referencesResolved nodes edges where
Reference _) | null (incomingEdges edges nodeid) =
f xs (nodeid, LintResult UndefinedReference [nodeid]:xs
= xs f xs _
= [
testLintRefs "*foobar >foobar >barbaz" [LintResult CircularLoop [0, 1]]
cmpLint "*foobar >foo" [LintResult UndefinedReference [0]]
, cmpLint ]
Results and alternatives must not have duplicate names, so collect
their lower-case object names into a Map
and flag those
which reference multiple nodes.
= M.foldl f [] nameMap
uniqueNames nodes _ where
| length fnodes > 1 = LintResult DuplicateReferenceName fnodes:xs
f xs fnodes = xs
f xs _ = foldl buildMap M.empty nodes
nameMap Result qty) = M.insertWith append (getObject qty) [nodeid] m
buildMap m (nodeid, Alternative qty) = M.insertWith append (getObject qty) [nodeid] m
buildMap m (nodeid, = m
buildMap m _ Quantity _ _ object) = map toLower object
getObject (= insert (head a) b append a b
= [
testUniqueNames "+a >x +b >y *x *y >foo" []
cmpLint "+a >x +b >x *x >y" [LintResult DuplicateReferenceName [1, 3]]
, cmpLint "+a >x +b +c |x *x >y" [LintResult DuplicateReferenceName [1, 4]]
, cmpLint "+a >1 _ foo +a >2 _ FOO +a >3 _ foO *Foo >y"
, cmpLint LintResult DuplicateReferenceName [1, 3, 5]]
[ ]
A result must have at least one incoming edge. This is a special case and can only occur at the beginning of a recipe.
= foldl f [] nodes
resultNonempty nodes edges where
Result _) | null (incomingEdges edges nodeid) =
f xs (nodeid, LintResult TooFewChildren [nodeid]:xs
= xs f xs _
= [
testLintResultNonempty ">bar *bar >baz" [LintResult TooFewChildren [0]]
cmpLint "+A >bar *bar >baz" []
, cmpLint "+A >bar >foo *bar *foo >baz" []
, cmpLint ]
Alternatives must have at least two incoming edges since a smaller amount would make the alternative pointless.
= foldl f [] nodes
twoAlternatives nodes edges where
Alternative _) | length (incomingEdges edges nodeid) < 2 =
f xs (nodeid, LintResult TooFewChildren [nodeid]:xs
= xs f xs _
= [
testLintTwoAlternatives "+A |foo *foo >bar" [LintResult TooFewChildren [1]]
cmpLint "+A +B |foo *foo >bar" []
, cmpLint "+A &B |foo *foo >bar" []
, cmpLint ]
References cannot loop because, well, you cannot cook something and use an ingredient you have not made yet. It is possible to branch out and merge again if an ingredient is split into multiple parts and added to different outputs.
= map (LintResult CircularLoop) circles
circularLoops nodes edges where
= foldl referenceNodes [] nodes
allReferences Reference _) = nodeid:xs
referenceNodes xs (nodeid, = xs
referenceNodes xs _ = filter (not . null) $ map (visitIncoming [] . singleton) allReferences
circles = [x]
singleton x = []
visitIncoming _ [] = case length (intersect visited nextNext) of
visitIncoming visited next 0 -> visitIncoming nextVisited nextNext
-> nextVisited
_ where
= visited ++ next
nextVisited = map fst $ concat $ map (incomingNodes nodes edges) next nextNext
= [
testLintCircularLoops "*y >x *x >y >foobar"
cmpLint LintResult CircularLoop [0, 3, 2, 1] , LintResult CircularLoop [2, 1, 0, 3]]
["*z >x *x >y *y >z *z >foobar" [
, cmpLint LintResult CircularLoop [0, 5, 4, 3, 2, 1]
LintResult CircularLoop [2, 1, 0, 5, 4, 3]
, LintResult CircularLoop [4, 3, 2, 1, 0, 5]
, LintResult CircularLoop [6, 5, 4, 3, 2, 1, 0]
,
]"+a >foobar *1/2 _ foobar >x *1/2 _ foobar >y *x *y >final" []
, cmpLint "+a >foobar *1/2 _ foobar >x *x *1/2 _ foobar >final" []
, cmpLint ]
The first amount of a range ratio must be strictly smaller than the second. This limitation is not enforced for ranges containing strings.
= foldl f [] nodes
rangeFromLargerThanTo nodes _ where
Ingredient q) | not $ rangeOk q =
f xs (nodeid, LintResult RangeFromLargerThanTo [nodeid]:xs
Reference q) | not $ rangeOk q =
f xs (nodeid, LintResult RangeFromLargerThanTo [nodeid]:xs
= xs
f xs _ Quantity (Range (AmountRatio a) (AmountRatio b)) _ _) = a < b
rangeOk (= True rangeOk _
= [
testRangeFromLargerThanTo "+2-3 l water >bar" []
cmpLint "+3-2 l water >bar" [LintResult RangeFromLargerThanTo [0]]
, cmpLint "+2/3-1/3 l water >bar" [LintResult RangeFromLargerThanTo [0]]
, cmpLint "+some-many _ eggs >bar" []
, cmpLint "+1-\"a few\" _ eggs >bar" []
, cmpLint ]
data LintResult = LintResult LintStatus [NodeId] deriving (Show, Eq, Ord)
data LintStatus =
NoRootNode
| NonResultRootNode
| MoreThanOneRootNode
| UndefinedReference
| DuplicateReferenceName
| CircularLoop
| TooFewChildren
| TimeIsATool
| TimeAnnotatesAction
| UnitNotWellKnown
| InvalidNode
| RangeFromLargerThanTo
| NoMetadata
| UnknownMetadataKey
deriving (Show, Eq, Ord)
Every lint test checks a single aspect of the graph.
= concatMap (\f -> f nodes edges) lintTests lint nodes edges
= [
lintTests
rootIsResult
, referencesResolved
, uniqueNames
, circularLoops
, resultNonempty
, twoAlternatives
, timeIsATool
, timeAnnotatesAction
, wellKnownUnit
, lintMetadata
, rangeFromLargerThanTo ]
= f nodes edges
withGraph doc f where
Right op) = (head . extract . snd . unzip) <$> parse ("%pesto " ++ doc)
(= zip [firstNodeId..] op
nodes = toGraph nodes ++ resolveReferences nodes edges
= withGraph doc (\nodes edges -> doc ~: sort (lint nodes edges) ~?= sort expect) cmpLint doc expect
data Metadata = MetaQty Quantity | MetaStr String deriving (Show, Eq)
= withGraph doc (\nodes edges -> doc ~: [
cmpLintMeta doc expectLint expectMeta sort (lint nodes edges) ~?= sort expectLint
~?= expectMeta
, extractMetadata nodes edges
])= Quantity (Exact (AmountStr "")) "" strQuantity
= [
test
testConnectivity
, testMetadata
, testLintRefs
, testUniqueNames
, testLintCircularLoops
, testLintQuantity
, testLintWellKnownUnit
, testTimeAnnotatesAction
, testLintTwoAlternatives
, testLintResultNonempty
, testRangeFromLargerThanTo ]
module Codec.Pesto.Serialize (serialize) where
import Data.Char (isSpace, isLetter)
import Data.Ratio (numerator, denominator)
import {-# SOURCE #-} Codec.Pesto.Parse
Serialization turns a linear list of instructions back into a human representation.
class Serializeable a where
serialize :: a -> String
instance Serializeable a => Serializeable [a] where
= unlines $ map serialize ops serialize ops
instance Serializeable Instruction where
Annotation s) = quote '(' ')' s
serialize (Ingredient q) = '+':serialize q
serialize (Tool q) = '&':serialize q
serialize (Action s) = quote '[' ']' s
serialize (Reference q) = '*':serialize q
serialize (Result q) = '>':serialize q
serialize (Alternative q) = '|':serialize q
serialize (Directive s) = '%':serializeQstr s
serialize (Unknown s) = s serialize (
instance Serializeable Quantity where
Quantity a b "") = serialize a ++ " " ++ serializeQstr b
serialize (Quantity (Exact (AmountStr "")) "" c) = serializeQstr c
serialize (Quantity a "" c) = serialize a ++ " _ " ++ serializeQstr c
serialize (Quantity a b c) = serialize a ++ " " ++ serializeQstr b ++ " " ++ serializeQstr c serialize (
instance Serializeable Approximately where
Range a b) = serialize a ++ "-" ++ serialize b
serialize (Approx a) = '~':serialize a
serialize (Exact a) = serialize a serialize (
There are two special cases here, both for aesthetic reasons:
instance Serializeable Amount where
AmountRatio a) | denominator a == 1 = show (numerator a)
serialize (AmountRatio a) | numerator a > denominator a =
serialize (show full ++ "/" ++ show num ++ "/" ++ show denom
where
= numerator a `div` denom
full = numerator a - full * denom
num = denominator a
denom AmountRatio a) = show (numerator a) ++ "/" ++ show (denominator a)
serialize (AmountStr s) = serializeQstr s serialize (
"" = "_"
serializeQstr | (not . isLetter . head) s || hasSpaces s = quote '"' '"' s
serializeQstr s = s
serializeQstr s = any isSpace
hasSpaces = [start] ++ concatMap (\c -> if c == end then ['\\', end] else [c]) s ++ [end] quote start end s
This project uses cabal. It provides the Codec.Pesto
library that implements the Pesto language as described in the previous
sections. It also comes with three binaries.
module Main (main) where
import System.Environment (getArgs)
import Data.List (intercalate)
import Codec.Pesto.Parse (parse, Instruction (Ingredient), Quantity (..))
import Codec.Pesto.Graph (extract, toGraph, firstNodeId, resolveReferences)
import Codec.Pesto.Lint (lint, extractMetadata, Metadata(..), LintResult (LintResult))
import Codec.Pesto.Serialize (serialize)
The user-interface reads a single recipe from the standard input.
= do
main :_) <- getArgs
(op<- getContents
s either malformedRecipe (run op) (parse s)
It has three modes of operation, described in the next sections.
"dot" = runDot
run "metadata" = runMeta
run "ingredients" = runIngredients
run = const (putStrLn "unknown operation") run _
Since each recipe is just a directed graph (digraph), GraphViz’ dot language can represent recipes as well. Example:
cabal run --verbose=0 pesto dot < spaghetti.pesto | dot -Tpng > spaghetti.png
= putStrLn $ toDot dotNodes dotEdges
runDot stream where
= streamToGraph stream
(nodes, edges) = (maximum $ map fst nodes) + 1
maxId = unzip $ map (uncurry lintToNodesEdges)
(lintNodes, lintEdges) $ zip [maxId..] (lint nodes edges)
= concat [
dotNodes "node", [("fontname", "Roboto Semi-Light")])]
[(map (\(a, label) -> (show a, [("label", serialize label)])) nodes
,
, lintNodes
]= concat [
dotEdges map (both show) edges
concat lintEdges
, ]
LintResult t nodes) = let
lintToNodesEdges nodeid (= (show nodeid, [("label", show t), ("color", "red")])
n = map (\i -> both show (nodeid, i)) nodes
e in (n, e)
= (f a, f b) both f (a, b)
= "digraph a {"
toDot nodes edges <> mconcat (map nodeToDot nodes)
<> mconcat (map edgeToDot edges)
<> "}"
where
= a <> " -> " <> b <> ";"
edgeToDot (a, b) = a <> " [" <> mconcat (mapToDot b) <> "];" nodeToDot (a, b)
= map kvToDot
mapToDot = k <> "=\"" <> quoteString v <> "\""
kvToDot (k, v) = mconcat $ map quoteChar s
quoteString s '\n' = "\\n"
quoteChar '"' = "\\\""
quoteChar = [x] quoteChar x
Print metadata as key-value pairs, separated by =
.
= maybe (return ()) (mapM_ printMeta) $ uncurry extractMetadata $ streamToGraph stream runMeta stream
Extract ingredients and print them in CSV format. This does not take alternatives into account yet.
= mapM_ (putStrLn . csvQty) $ reverse $ foldl getIngredient [] stream
runIngredients stream where
Ingredient q) = q:xs
getIngredient xs (_, = xs getIngredient xs _
MetaStr value)) = putStrLn $ key ++ "=" ++ value
printMeta (_, (key, MetaQty q)) = putStrLn $ key ++ "=" ++ csvQty q printMeta (_, (key,
Quantity a b c) = intercalate "," [serialize a, b, c] csvQty (
= print malformedRecipe
= (nodes, edges)
streamToGraph stream where
= (head . extract . snd . unzip) stream
doc = zip [firstNodeId..] doc
nodes = toGraph nodes ++ resolveReferences nodes edges
import Test.HUnit
import System.Exit (exitFailure, exitSuccess)
import Codec.Pesto.Parse (test)
import Codec.Pesto.Lint (test)
import Codec.Pesto.Graph (test)
The testcases can be run with cabal test
. This runs
all testcases from all modules and prints a summary.
= runTestTT tests >>= \c -> if errors c + failures c > 0 then exitFailure else exitSuccess main
= TestList [
tests "parse" ~: Codec.Pesto.Parse.test
"graph" ~: Codec.Pesto.Graph.test
, "lint" ~: Codec.Pesto.Lint.test
, ]
{-# LANGUAGE OverloadedStrings #-}
import Text.Pandoc
import Text.Pandoc.Highlighting (tango)
import qualified Data.Text.IO as TIO
import System.Directory (setCurrentDirectory)
import Data.Map as M
import Text.DocTemplates (ToContext(toVal), Context(..))
import Data.Text (pack)
import Data.Either.Combinators (rightToMaybe)
The documentation can be generated by running
cabal run pesto-doc
. It is exclusively based on the
restructuredText inside this package’s literal Haskell source code.
= readRST def {
readDoc = extensionsFromList [
readerExtensions Ext_literate_haskell
Ext_implicit_header_references
,
]= True } , readerStandalone
Pandoc outputs a single HTML5 page with syntax highlighting and MathJax for formulas.
= writeHtml5String def {
writeDoc tpl = tpl
writerTemplate = Just tango
, writerHighlightStyle = True
, writerNumberSections = True
, writerSectionDivs = 4
, writerTabStop = MathJax "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML"
, writerHTMLMathMethod = Context $ M.fromList [
, writerVariables "css", toVal $ pack "pesto.css")
("lang", toVal $ pack "en")
, ("include-before", toVal $ pack "<div class=\"wrapper\">")
, ("include-after", toVal $ pack "</div>")
, (
]
}
= do main
The module Codec.Pesto
serves as starting point and it
includes every other module in a sensible order. For the relative
includes to work, we need to change our current working directory.
<- runIO $ compileDefaultTemplate "html5"
tpl "src/lib/Codec"
setCurrentDirectory <- TIO.readFile "Pesto.lhs"
doc <- runIO $ readDoc doc >>= writeDoc (rightToMaybe tpl)
result "../../../"
setCurrentDirectory <- handleError result html
Output is written to the directory _build
, which
contains the corresponding stylesheet.
"_build/index.html" html TIO.writeFile