{-# LANGUAGE DataKinds #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Swarm.Doc.Wiki.Cheatsheet (
PageAddress (..),
SheetType (..),
makeWikiPage,
) where
import Control.Effect.Lift
import Control.Lens (view, (^.))
import Control.Lens.Combinators (to)
import Data.Foldable (find, toList)
import Data.List (transpose)
import Data.List.Extra (enumerate)
import Data.Map.Lazy qualified as Map
import Data.Maybe (isJust)
import Data.Set qualified as S
import Data.Text (Text)
import Data.Text qualified as T
import Data.Text.IO qualified as T
import Swarm.Doc.Schema.Render
import Swarm.Doc.Util
import Swarm.Doc.Wiki.Matrix
import Swarm.Doc.Wiki.Util
import Swarm.Failure (simpleErrorHandle)
import Swarm.Game.Device qualified as D
import Swarm.Game.Display (displayChar)
import Swarm.Game.Entity (Entity, EntityMap (entitiesByName), entityDisplay, entityName, loadEntities)
import Swarm.Game.Entity qualified as E
import Swarm.Game.Recipe (Recipe, loadRecipes, recipeCatalysts, recipeInputs, recipeOutputs, recipeTime, recipeWeight)
import Swarm.Game.Terrain (loadTerrain, terrainByName)
import Swarm.Language.Capability (Capability)
import Swarm.Language.Capability qualified as Capability
import Swarm.Language.Syntax (Const (..))
import Swarm.Language.Syntax qualified as Syntax
import Swarm.Language.Text.Markdown as Markdown (docToMark)
import Swarm.Language.Typecheck (inferConst)
import Swarm.Pretty (prettyText, prettyTextLine)
import Swarm.Util (applyWhen, maximum0, showT)
data PageAddress = PageAddress
{ PageAddress -> Text
entityAddress :: Text
, PageAddress -> Text
commandsAddress :: Text
, PageAddress -> Text
capabilityAddress :: Text
, PageAddress -> Text
recipesAddress :: Text
}
deriving (PageAddress -> PageAddress -> Bool
(PageAddress -> PageAddress -> Bool)
-> (PageAddress -> PageAddress -> Bool) -> Eq PageAddress
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PageAddress -> PageAddress -> Bool
== :: PageAddress -> PageAddress -> Bool
$c/= :: PageAddress -> PageAddress -> Bool
/= :: PageAddress -> PageAddress -> Bool
Eq, Int -> PageAddress -> ShowS
[PageAddress] -> ShowS
PageAddress -> String
(Int -> PageAddress -> ShowS)
-> (PageAddress -> String)
-> ([PageAddress] -> ShowS)
-> Show PageAddress
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PageAddress -> ShowS
showsPrec :: Int -> PageAddress -> ShowS
$cshow :: PageAddress -> String
show :: PageAddress -> String
$cshowList :: [PageAddress] -> ShowS
showList :: [PageAddress] -> ShowS
Show)
data SheetType = Entities | Terrain | Commands | CommandMatrix | Capabilities | Recipes | Scenario
deriving (SheetType -> SheetType -> Bool
(SheetType -> SheetType -> Bool)
-> (SheetType -> SheetType -> Bool) -> Eq SheetType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SheetType -> SheetType -> Bool
== :: SheetType -> SheetType -> Bool
$c/= :: SheetType -> SheetType -> Bool
/= :: SheetType -> SheetType -> Bool
Eq, Int -> SheetType -> ShowS
[SheetType] -> ShowS
SheetType -> String
(Int -> SheetType -> ShowS)
-> (SheetType -> String)
-> ([SheetType] -> ShowS)
-> Show SheetType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SheetType -> ShowS
showsPrec :: Int -> SheetType -> ShowS
$cshow :: SheetType -> String
show :: SheetType -> String
$cshowList :: [SheetType] -> ShowS
showList :: [SheetType] -> ShowS
Show, Int -> SheetType
SheetType -> Int
SheetType -> [SheetType]
SheetType -> SheetType
SheetType -> SheetType -> [SheetType]
SheetType -> SheetType -> SheetType -> [SheetType]
(SheetType -> SheetType)
-> (SheetType -> SheetType)
-> (Int -> SheetType)
-> (SheetType -> Int)
-> (SheetType -> [SheetType])
-> (SheetType -> SheetType -> [SheetType])
-> (SheetType -> SheetType -> [SheetType])
-> (SheetType -> SheetType -> SheetType -> [SheetType])
-> Enum SheetType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SheetType -> SheetType
succ :: SheetType -> SheetType
$cpred :: SheetType -> SheetType
pred :: SheetType -> SheetType
$ctoEnum :: Int -> SheetType
toEnum :: Int -> SheetType
$cfromEnum :: SheetType -> Int
fromEnum :: SheetType -> Int
$cenumFrom :: SheetType -> [SheetType]
enumFrom :: SheetType -> [SheetType]
$cenumFromThen :: SheetType -> SheetType -> [SheetType]
enumFromThen :: SheetType -> SheetType -> [SheetType]
$cenumFromTo :: SheetType -> SheetType -> [SheetType]
enumFromTo :: SheetType -> SheetType -> [SheetType]
$cenumFromThenTo :: SheetType -> SheetType -> SheetType -> [SheetType]
enumFromThenTo :: SheetType -> SheetType -> SheetType -> [SheetType]
Enum, SheetType
SheetType -> SheetType -> Bounded SheetType
forall a. a -> a -> Bounded a
$cminBound :: SheetType
minBound :: SheetType
$cmaxBound :: SheetType
maxBound :: SheetType
Bounded)
makeWikiPage :: PageAddress -> SheetType -> IO ()
makeWikiPage :: PageAddress -> SheetType -> IO ()
makeWikiPage PageAddress
address SheetType
s = case SheetType
s of
SheetType
Commands -> Text -> IO ()
T.putStrLn Text
commandsPage
SheetType
CommandMatrix -> case Pandoc -> Either Text Text
pandocToText Pandoc
commandsMatrix of
Right Text
x -> Text -> IO ()
T.putStrLn Text
x
Left Text
x -> Text -> IO ()
T.putStrLn Text
x
SheetType
Capabilities -> ThrowC SystemFailure IO () -> IO ()
forall a. ThrowC SystemFailure IO a -> IO a
simpleErrorHandle (ThrowC SystemFailure IO () -> IO ())
-> ThrowC SystemFailure IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
EntityMap
entities <- ThrowC SystemFailure IO EntityMap
forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
(Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) =>
m EntityMap
loadEntities
IO () -> ThrowC SystemFailure IO ()
forall (sig :: (* -> *) -> * -> *) (m :: * -> *) a.
Has (Lift IO) sig m =>
IO a -> m a
sendIO (IO () -> ThrowC SystemFailure IO ())
-> IO () -> ThrowC SystemFailure IO ()
forall a b. (a -> b) -> a -> b
$ Text -> IO ()
T.putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ PageAddress -> EntityMap -> Text
capabilityPage PageAddress
address EntityMap
entities
SheetType
Entities -> ThrowC SystemFailure IO () -> IO ()
forall a. ThrowC SystemFailure IO a -> IO a
simpleErrorHandle (ThrowC SystemFailure IO () -> IO ())
-> ThrowC SystemFailure IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
EntityMap
entities <- ThrowC SystemFailure IO EntityMap
forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
(Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) =>
m EntityMap
loadEntities
IO () -> ThrowC SystemFailure IO ()
forall (sig :: (* -> *) -> * -> *) (m :: * -> *) a.
Has (Lift IO) sig m =>
IO a -> m a
sendIO (IO () -> ThrowC SystemFailure IO ())
-> IO () -> ThrowC SystemFailure IO ()
forall a b. (a -> b) -> a -> b
$ Text -> IO ()
T.putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ PageAddress -> [Entity] -> Text
entitiesPage PageAddress
address (Map Text Entity -> [Entity]
forall k a. Map k a -> [a]
Map.elems (Map Text Entity -> [Entity]) -> Map Text Entity -> [Entity]
forall a b. (a -> b) -> a -> b
$ EntityMap -> Map Text Entity
entitiesByName EntityMap
entities)
SheetType
Terrain -> ThrowC SystemFailure IO () -> IO ()
forall a. ThrowC SystemFailure IO a -> IO a
simpleErrorHandle (ThrowC SystemFailure IO () -> IO ())
-> ThrowC SystemFailure IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
TerrainMap
terrains <- ThrowC SystemFailure IO TerrainMap
forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
(Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) =>
m TerrainMap
loadTerrain
IO () -> ThrowC SystemFailure IO ()
forall (sig :: (* -> *) -> * -> *) (m :: * -> *) a.
Has (Lift IO) sig m =>
IO a -> m a
sendIO (IO () -> ThrowC SystemFailure IO ())
-> (Map TerrainType TerrainObj -> IO ())
-> Map TerrainType TerrainObj
-> ThrowC SystemFailure IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> IO ()
T.putStrLn (Text -> IO ())
-> (Map TerrainType TerrainObj -> Text)
-> Map TerrainType TerrainObj
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.unlines ([Text] -> Text)
-> (Map TerrainType TerrainObj -> [Text])
-> Map TerrainType TerrainObj
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TerrainObj -> Text) -> [TerrainObj] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map TerrainObj -> Text
forall a. Show a => a -> Text
showT ([TerrainObj] -> [Text])
-> (Map TerrainType TerrainObj -> [TerrainObj])
-> Map TerrainType TerrainObj
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Map TerrainType TerrainObj -> [TerrainObj]
forall k a. Map k a -> [a]
Map.elems (Map TerrainType TerrainObj -> ThrowC SystemFailure IO ())
-> Map TerrainType TerrainObj -> ThrowC SystemFailure IO ()
forall a b. (a -> b) -> a -> b
$ TerrainMap -> Map TerrainType TerrainObj
terrainByName TerrainMap
terrains
SheetType
Recipes -> ThrowC SystemFailure IO () -> IO ()
forall a. ThrowC SystemFailure IO a -> IO a
simpleErrorHandle (ThrowC SystemFailure IO () -> IO ())
-> ThrowC SystemFailure IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
EntityMap
entities <- ThrowC SystemFailure IO EntityMap
forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
(Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) =>
m EntityMap
loadEntities
[Recipe Entity]
recipes <- EntityMap -> ThrowC SystemFailure IO [Recipe Entity]
forall (sig :: (* -> *) -> * -> *) (m :: * -> *).
(Has (Throw SystemFailure) sig m, Has (Lift IO) sig m) =>
EntityMap -> m [Recipe Entity]
loadRecipes EntityMap
entities
IO () -> ThrowC SystemFailure IO ()
forall (sig :: (* -> *) -> * -> *) (m :: * -> *) a.
Has (Lift IO) sig m =>
IO a -> m a
sendIO (IO () -> ThrowC SystemFailure IO ())
-> IO () -> ThrowC SystemFailure IO ()
forall a b. (a -> b) -> a -> b
$ Text -> IO ()
T.putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ PageAddress -> [Recipe Entity] -> Text
recipePage PageAddress
address [Recipe Entity]
recipes
SheetType
Scenario -> IO ()
genScenarioSchemaDocs
escapeTable :: Text -> Text
escapeTable :: Text -> Text
escapeTable = (Char -> Text) -> Text -> Text
T.concatMap (\Char
c -> if Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'|' then Text -> Char -> Text
T.snoc Text
"\\" Char
c else Char -> Text
T.singleton Char
c)
separatingLine :: [Int] -> Text
separatingLine :: [Int] -> Text
separatingLine [Int]
ws = Char -> Text -> Text
T.cons Char
'|' (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Int -> Text) -> [Int] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ((Text -> Char -> Text) -> Char -> Text -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Char -> Text
T.snoc Char
'|' (Text -> Text) -> (Int -> Text) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Text -> Text) -> Text -> Int -> Text
forall a b c. (a -> b -> c) -> b -> a -> c
flip Int -> Text -> Text
T.replicate Text
"-" (Int -> Text) -> (Int -> Int) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
+)) [Int]
ws
listToRow :: [Int] -> [Text] -> Text
listToRow :: [Int] -> [Text] -> Text
listToRow [Int]
mw [Text]
xs = Char -> Text -> Text
wrap Char
'|' (Text -> Text) -> ([Text] -> Text) -> [Text] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
"|" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Int -> Text -> Text) -> [Int] -> [Text] -> [Text]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Text -> Text
format [Int]
mw [Text]
xs
where
format :: Int -> Text -> Text
format Int
w Text
x = Char -> Text -> Text
wrap Char
' ' Text
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.replicate (Int
w Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
x) Text
" "
maxWidths :: [[Text]] -> [Int]
maxWidths :: [[Text]] -> [Int]
maxWidths = ([Text] -> Int) -> [[Text]] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> Int
forall a. (Num a, Ord a) => [a] -> a
maximum0 ([Int] -> Int) -> ([Text] -> [Int]) -> [Text] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Int) -> [Text] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Text -> Int
T.length) ([[Text]] -> [Int]) -> ([[Text]] -> [[Text]]) -> [[Text]] -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Text]] -> [[Text]]
forall a. [[a]] -> [[a]]
transpose
commandHeader :: [Text]
commandHeader :: [Text]
commandHeader = [Text
"Syntax", Text
"Type", Text
"Capability", Text
"Description"]
commandToList :: Const -> [Text]
commandToList :: Const -> [Text]
commandToList Const
c =
(Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map
Text -> Text
escapeTable
[ Text -> Text -> Text
addLink (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Const -> Text
forall a. Show a => a -> Text
showT Const
c) (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
codeQuote (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Const -> Text
constSyntax Const
c
, Text -> Text
codeQuote (Text -> Text) -> (Polytype -> Text) -> Polytype -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Polytype -> Text
forall a. PrettyPrec a => a -> Text
prettyTextLine (Polytype -> Text) -> Polytype -> Text
forall a b. (a -> b) -> a -> b
$ Const -> Polytype
inferConst Const
c
, Text -> (Capability -> Text) -> Maybe Capability -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" Capability -> Text
Capability.capabilityName (Maybe Capability -> Text) -> Maybe Capability -> Text
forall a b. (a -> b) -> a -> b
$ Const -> Maybe Capability
Capability.constCaps Const
c
, ConstDoc -> Text
Syntax.briefDoc (ConstDoc -> Text) -> (ConstInfo -> ConstDoc) -> ConstInfo -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstInfo -> ConstDoc
Syntax.constDoc (ConstInfo -> Text) -> ConstInfo -> Text
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
Syntax.constInfo Const
c
]
constTable :: [Const] -> Text
constTable :: [Const] -> Text
constTable [Const]
cs = [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
header [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> ([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> [Text] -> Text
listToRow [Int]
mw) [[Text]]
commandRows
where
mw :: [Int]
mw = [[Text]] -> [Int]
maxWidths ([Text]
commandHeader [Text] -> [[Text]] -> [[Text]]
forall a. a -> [a] -> [a]
: [[Text]]
commandRows)
commandRows :: [[Text]]
commandRows = (Const -> [Text]) -> [Const] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map Const -> [Text]
commandToList [Const]
cs
header :: [Text]
header = [[Int] -> [Text] -> Text
listToRow [Int]
mw [Text]
commandHeader, [Int] -> Text
separatingLine [Int]
mw]
commandToSection :: Const -> Text
commandToSection :: Const -> Text
commandToSection Const
c =
[Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
[ Text
"## " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (Const -> String
forall a. Show a => a -> String
show Const
c)
, Text
""
, Text
"- syntax: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text
codeQuote (Const -> Text
constSyntax Const
c)
, Text
"- type: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Text -> Text
codeQuote (Text -> Text) -> (Polytype -> Text) -> Polytype -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Polytype -> Text
forall a. PrettyPrec a => a -> Text
prettyText (Polytype -> Text) -> Polytype -> Text
forall a b. (a -> b) -> a -> b
$ Const -> Polytype
inferConst Const
c)
, Text -> (Capability -> Text) -> Maybe Capability -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"" ((Text
"- required capabilities: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> (Capability -> Text) -> Capability -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Capability -> Text
Capability.capabilityName) (Maybe Capability -> Text) -> Maybe Capability -> Text
forall a b. (a -> b) -> a -> b
$ Const -> Maybe Capability
Capability.constCaps Const
c
, Text
""
, ConstDoc -> Text
Syntax.briefDoc (ConstDoc -> Text) -> (ConstInfo -> ConstDoc) -> ConstInfo -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstInfo -> ConstDoc
Syntax.constDoc (ConstInfo -> Text) -> ConstInfo -> Text
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
Syntax.constInfo Const
c
]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> let l :: Text
l = ConstDoc -> Text
Syntax.longDoc (ConstDoc -> Text) -> (ConstInfo -> ConstDoc) -> ConstInfo -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConstInfo -> ConstDoc
Syntax.constDoc (ConstInfo -> Text) -> ConstInfo -> Text
forall a b. (a -> b) -> a -> b
$ Const -> ConstInfo
Syntax.constInfo Const
c
in if Text -> Bool
T.null Text
l then [] else [Text
"", Text
l]
commandsPage :: Text
commandsPage :: Text
commandsPage =
Text -> [Text] -> Text
T.intercalate Text
"\n\n" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
[ Text
"# Commands"
, [Const] -> Text
constTable [Const]
commands
, Text
"# Builtin functions"
, Text
"These functions are evaluated immediately once they have enough arguments."
, [Const] -> Text
constTable [Const]
builtinFunctions
, Text
"# Operators"
, [Const] -> Text
constTable [Const]
operators
, Text
"# Detailed descriptions"
]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> (Const -> Text) -> [Const] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Const -> Text
commandToSection ([Const]
commands [Const] -> [Const] -> [Const]
forall a. Semigroup a => a -> a -> a
<> [Const]
builtinFunctions [Const] -> [Const] -> [Const]
forall a. Semigroup a => a -> a -> a
<> [Const]
operators)
capabilityHeader :: [Text]
= [Text
"Name", Text
"Commands", Text
"Entities"]
capabilityRow :: PageAddress -> EntityMap -> Capability -> [Text]
capabilityRow :: PageAddress -> EntityMap -> Capability -> [Text]
capabilityRow PageAddress {Text
entityAddress :: PageAddress -> Text
commandsAddress :: PageAddress -> Text
capabilityAddress :: PageAddress -> Text
recipesAddress :: PageAddress -> Text
entityAddress :: Text
commandsAddress :: Text
capabilityAddress :: Text
recipesAddress :: Text
..} EntityMap
em Capability
cap =
(Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map
Text -> Text
escapeTable
[ Capability -> Text
Capability.capabilityName Capability
cap
, Text -> [Text] -> Text
T.intercalate Text
", " (Const -> Text
linkCommand (Const -> Text) -> [Const] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Const]
cs)
, Text -> [Text] -> Text
T.intercalate Text
", " (Text -> Text
linkEntity (Text -> Text) -> (Entity -> Text) -> Entity -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting Text Entity Text -> Entity -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Entity Text
Lens' Entity Text
entityName (Entity -> Text) -> [Entity] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Entity]
es)
]
where
linkEntity :: Text -> Text
linkEntity Text
t =
if Text -> Bool
T.null Text
entityAddress
then Text
t
else Text -> Text -> Text
addLink (Text
entityAddress Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
" " Text
"-" Text
t) Text
t
linkCommand :: Const -> Text
linkCommand Const
c =
Bool -> (Text -> Text) -> Text -> Text
forall a. Bool -> (a -> a) -> a -> a
applyWhen (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Bool
T.null Text
commandsAddress) (Text -> Text -> Text
addLink (Text -> Text -> Text) -> Text -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text
commandsAddress Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Const -> Text
forall a. Show a => a -> Text
showT Const
c)
(Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
codeQuote
(Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Const -> Text
constSyntax Const
c
cs :: [Const]
cs = [Const
c | Const
c <- [Const]
Syntax.allConst, let mcap :: Maybe Capability
mcap = Const -> Maybe Capability
Capability.constCaps Const
c, Maybe Capability -> Bool
forall a. Maybe a -> Bool
isJust (Maybe Capability -> Bool) -> Maybe Capability -> Bool
forall a b. (a -> b) -> a -> b
$ (Capability -> Bool) -> Maybe Capability -> Maybe Capability
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find (Capability -> Capability -> Bool
forall a. Eq a => a -> a -> Bool
== Capability
cap) Maybe Capability
mcap]
es :: [Entity]
es = Capability -> EntityMap -> [Entity]
E.devicesForCap Capability
cap EntityMap
em
capabilityTable :: PageAddress -> EntityMap -> [Capability] -> Text
capabilityTable :: PageAddress -> EntityMap -> [Capability] -> Text
capabilityTable PageAddress
a EntityMap
em [Capability]
cs = [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
header [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> ([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> [Text] -> Text
listToRow [Int]
mw) [[Text]]
capabilityRows
where
mw :: [Int]
mw = [[Text]] -> [Int]
maxWidths ([Text]
capabilityHeader [Text] -> [[Text]] -> [[Text]]
forall a. a -> [a] -> [a]
: [[Text]]
capabilityRows)
capabilityRows :: [[Text]]
capabilityRows = (Capability -> [Text]) -> [Capability] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (PageAddress -> EntityMap -> Capability -> [Text]
capabilityRow PageAddress
a EntityMap
em) [Capability]
cs
header :: [Text]
header = [[Int] -> [Text] -> Text
listToRow [Int]
mw [Text]
capabilityHeader, [Int] -> Text
separatingLine [Int]
mw]
capabilityPage :: PageAddress -> EntityMap -> Text
capabilityPage :: PageAddress -> EntityMap -> Text
capabilityPage PageAddress
a EntityMap
em = PageAddress -> EntityMap -> [Capability] -> Text
capabilityTable PageAddress
a EntityMap
em ([Capability] -> Text) -> [Capability] -> Text
forall a b. (a -> b) -> a -> b
$ (Capability -> Bool) -> [Capability] -> [Capability]
forall a. (a -> Bool) -> [a] -> [a]
filter Capability -> Bool
usedCapability [Capability]
forall a. (Enum a, Bounded a) => [a]
enumerate
where
usedCapability :: Capability -> Bool
usedCapability Capability
c = case Capability
c of
Capability.CExecute Const
con -> Const -> Maybe Capability
Capability.constCaps Const
con Maybe Capability -> Maybe Capability -> Bool
forall a. Eq a => a -> a -> Bool
== Capability -> Maybe Capability
forall a. a -> Maybe a
Just Capability
c
Capability
_ -> Bool
True
entityHeader :: [Text]
= [Text
"?", Text
"Name", Text
"Capabilities", Text
"Properties*", Text
"Pickable"]
entityToList :: Entity -> [Text]
entityToList :: Entity -> [Text]
entityToList Entity
e =
(Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map
Text -> Text
escapeTable
[ Text -> Text
codeQuote (Text -> Text) -> (Char -> Text) -> Char -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$ Entity
e Entity -> Getting Char Entity Char -> Char
forall s a. s -> Getting a s a -> a
^. (Display -> Const Char Display) -> Entity -> Const Char Entity
Lens' Entity Display
entityDisplay ((Display -> Const Char Display) -> Entity -> Const Char Entity)
-> ((Char -> Const Char Char) -> Display -> Const Char Display)
-> Getting Char Entity Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Display -> Char)
-> (Char -> Const Char Char) -> Display -> Const Char Display
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Display -> Char
displayChar
, Text -> Text -> Text
addLink (Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
linkID) (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Getting Text Entity Text -> Entity -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Entity Text
Lens' Entity Text
entityName Entity
e
, Text -> [Text] -> Text
T.intercalate Text
", " ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ Capability -> Text
Capability.capabilityName (Capability -> Text) -> [Capability] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Map Capability (ExerciseCost Text) -> [Capability]
forall k a. Map k a -> [k]
Map.keys (SingleEntityCapabilities Text -> Map Capability (ExerciseCost Text)
forall e. Capabilities e -> Map Capability e
D.getMap (SingleEntityCapabilities Text
-> Map Capability (ExerciseCost Text))
-> SingleEntityCapabilities Text
-> Map Capability (ExerciseCost Text)
forall a b. (a -> b) -> a -> b
$ Getting
(SingleEntityCapabilities Text)
Entity
(SingleEntityCapabilities Text)
-> Entity -> SingleEntityCapabilities Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(SingleEntityCapabilities Text)
Entity
(SingleEntityCapabilities Text)
Lens' Entity (SingleEntityCapabilities Text)
E.entityCapabilities Entity
e)
, Text -> [Text] -> Text
T.intercalate Text
", " ([Text] -> Text)
-> ([EntityProperty] -> [Text]) -> [EntityProperty] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EntityProperty -> Text) -> [EntityProperty] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map EntityProperty -> Text
forall a. Show a => a -> Text
showT ([EntityProperty] -> [Text])
-> ([EntityProperty] -> [EntityProperty])
-> [EntityProperty]
-> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (EntityProperty -> Bool) -> [EntityProperty] -> [EntityProperty]
forall a. (a -> Bool) -> [a] -> [a]
filter (EntityProperty -> EntityProperty -> Bool
forall a. Eq a => a -> a -> Bool
/= EntityProperty
E.Pickable) ([EntityProperty] -> Text) -> [EntityProperty] -> Text
forall a b. (a -> b) -> a -> b
$ Set EntityProperty -> [EntityProperty]
forall a. Set a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Set EntityProperty
props
, if EntityProperty
E.Pickable EntityProperty -> Set EntityProperty -> Bool
forall a. Eq a => a -> Set a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` Set EntityProperty
props
then Text
":heavy_check_mark:"
else Text
":negative_squared_cross_mark:"
]
where
props :: Set EntityProperty
props = Getting (Set EntityProperty) Entity (Set EntityProperty)
-> Entity -> Set EntityProperty
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Set EntityProperty) Entity (Set EntityProperty)
Lens' Entity (Set EntityProperty)
E.entityProperties Entity
e
linkID :: Text
linkID = HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
" " Text
"-" (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Getting Text Entity Text -> Entity -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Entity Text
Lens' Entity Text
entityName Entity
e
entityTable :: [Entity] -> Text
entityTable :: [Entity] -> Text
entityTable [Entity]
es = [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
header [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> ([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> [Text] -> Text
listToRow [Int]
mw) [[Text]]
entityRows
where
mw :: [Int]
mw = [[Text]] -> [Int]
maxWidths ([Text]
entityHeader [Text] -> [[Text]] -> [[Text]]
forall a. a -> [a] -> [a]
: [[Text]]
entityRows)
entityRows :: [[Text]]
entityRows = (Entity -> [Text]) -> [Entity] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map Entity -> [Text]
entityToList [Entity]
es
header :: [Text]
header = [[Int] -> [Text] -> Text
listToRow [Int]
mw [Text]
entityHeader, [Int] -> Text
separatingLine [Int]
mw]
entityToSection :: Entity -> Text
entityToSection :: Entity -> Text
entityToSection Entity
e =
[Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
[ Text
"## " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Getting Text Entity Text -> Entity -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Entity Text
Lens' Entity Text
E.entityName Entity
e
, Text
""
, Text
" - Char: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> (Text -> Text
codeQuote (Text -> Text) -> (Char -> Text) -> Char -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
T.singleton (Char -> Text) -> Char -> Text
forall a b. (a -> b) -> a -> b
$ Entity
e Entity -> Getting Char Entity Char -> Char
forall s a. s -> Getting a s a -> a
^. (Display -> Const Char Display) -> Entity -> Const Char Entity
Lens' Entity Display
entityDisplay ((Display -> Const Char Display) -> Entity -> Const Char Entity)
-> ((Char -> Const Char Char) -> Display -> Const Char Display)
-> Getting Char Entity Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Display -> Char)
-> (Char -> Const Char Char) -> Display -> Const Char Display
forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
to Display -> Char
displayChar)
]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
" - Properties: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
", " ((EntityProperty -> Text) -> [EntityProperty] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map EntityProperty -> Text
forall a. Show a => a -> Text
showT ([EntityProperty] -> [Text]) -> [EntityProperty] -> [Text]
forall a b. (a -> b) -> a -> b
$ Set EntityProperty -> [EntityProperty]
forall a. Set a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList Set EntityProperty
props) | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Set EntityProperty -> Bool
forall a. Set a -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Set EntityProperty
props]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
" - Capabilities: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
", " (Capability -> Text
Capability.capabilityName (Capability -> Text) -> [Capability] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Capability]
caps) | Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [Capability] -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [Capability]
caps]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
"\n"]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Document Syntax -> Text
forall a. PrettyPrec a => Document a -> Text
Markdown.docToMark (Document Syntax -> Text) -> Document Syntax -> Text
forall a b. (a -> b) -> a -> b
$ Getting (Document Syntax) Entity (Document Syntax)
-> Entity -> Document Syntax
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Document Syntax) Entity (Document Syntax)
Lens' Entity (Document Syntax)
E.entityDescription Entity
e]
where
props :: Set EntityProperty
props = Getting (Set EntityProperty) Entity (Set EntityProperty)
-> Entity -> Set EntityProperty
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting (Set EntityProperty) Entity (Set EntityProperty)
Lens' Entity (Set EntityProperty)
E.entityProperties Entity
e
caps :: [Capability]
caps = Set Capability -> [Capability]
forall a. Set a -> [a]
S.toList (Set Capability -> [Capability]) -> Set Capability -> [Capability]
forall a b. (a -> b) -> a -> b
$ SingleEntityCapabilities Text -> Set Capability
forall e. Capabilities e -> Set Capability
D.getCapabilitySet (SingleEntityCapabilities Text -> Set Capability)
-> SingleEntityCapabilities Text -> Set Capability
forall a b. (a -> b) -> a -> b
$ Getting
(SingleEntityCapabilities Text)
Entity
(SingleEntityCapabilities Text)
-> Entity -> SingleEntityCapabilities Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(SingleEntityCapabilities Text)
Entity
(SingleEntityCapabilities Text)
Lens' Entity (SingleEntityCapabilities Text)
E.entityCapabilities Entity
e
entitiesPage :: PageAddress -> [Entity] -> Text
entitiesPage :: PageAddress -> [Entity] -> Text
entitiesPage PageAddress
_a [Entity]
es =
Text -> [Text] -> Text
T.intercalate Text
"\n\n" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
[ Text
"# Entities"
, Text
"This is a quick-overview table of entities - click the name for detailed description."
, Text
"*) As a note, most entities have the Pickable property, so we show it in a separate column."
, [Entity] -> Text
entityTable [Entity]
es
]
[Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> (Entity -> Text) -> [Entity] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Entity -> Text
entityToSection [Entity]
es
recipeHeader :: [Text]
= [Text
"In", Text
"Out", Text
"Required", Text
"Time", Text
"Weight"]
recipeRow :: PageAddress -> Recipe Entity -> [Text]
recipeRow :: PageAddress -> Recipe Entity -> [Text]
recipeRow PageAddress {Text
entityAddress :: PageAddress -> Text
commandsAddress :: PageAddress -> Text
capabilityAddress :: PageAddress -> Text
recipesAddress :: PageAddress -> Text
entityAddress :: Text
commandsAddress :: Text
capabilityAddress :: Text
recipesAddress :: Text
..} Recipe Entity
r =
(Text -> Text) -> [Text] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map
Text -> Text
escapeTable
[ Text -> [Text] -> Text
T.intercalate Text
", " (((Int, Entity) -> Text) -> IngredientList Entity -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Entity) -> Text
forall {a}. Show a => (a, Entity) -> Text
formatCE (IngredientList Entity -> [Text])
-> IngredientList Entity -> [Text]
forall a b. (a -> b) -> a -> b
$ Getting
(IngredientList Entity) (Recipe Entity) (IngredientList Entity)
-> Recipe Entity -> IngredientList Entity
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(IngredientList Entity) (Recipe Entity) (IngredientList Entity)
forall e (f :: * -> *).
Functor f =>
(IngredientList e -> f (IngredientList e))
-> Recipe e -> f (Recipe e)
recipeInputs Recipe Entity
r)
, Text -> [Text] -> Text
T.intercalate Text
", " (((Int, Entity) -> Text) -> IngredientList Entity -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Entity) -> Text
forall {a}. Show a => (a, Entity) -> Text
formatCE (IngredientList Entity -> [Text])
-> IngredientList Entity -> [Text]
forall a b. (a -> b) -> a -> b
$ Getting
(IngredientList Entity) (Recipe Entity) (IngredientList Entity)
-> Recipe Entity -> IngredientList Entity
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(IngredientList Entity) (Recipe Entity) (IngredientList Entity)
forall e (f :: * -> *).
Functor f =>
(IngredientList e -> f (IngredientList e))
-> Recipe e -> f (Recipe e)
recipeOutputs Recipe Entity
r)
, Text -> [Text] -> Text
T.intercalate Text
", " (((Int, Entity) -> Text) -> IngredientList Entity -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Entity) -> Text
forall {a}. Show a => (a, Entity) -> Text
formatCE (IngredientList Entity -> [Text])
-> IngredientList Entity -> [Text]
forall a b. (a -> b) -> a -> b
$ Getting
(IngredientList Entity) (Recipe Entity) (IngredientList Entity)
-> Recipe Entity -> IngredientList Entity
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting
(IngredientList Entity) (Recipe Entity) (IngredientList Entity)
forall e (f :: * -> *).
Functor f =>
(IngredientList e -> f (IngredientList e))
-> Recipe e -> f (Recipe e)
recipeCatalysts Recipe Entity
r)
, Integer -> Text
forall a. Show a => a -> Text
showT (Integer -> Text) -> Integer -> Text
forall a b. (a -> b) -> a -> b
$ Getting Integer (Recipe Entity) Integer -> Recipe Entity -> Integer
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Integer (Recipe Entity) Integer
forall e (f :: * -> *).
Functor f =>
(Integer -> f Integer) -> Recipe e -> f (Recipe e)
recipeTime Recipe Entity
r
, Integer -> Text
forall a. Show a => a -> Text
showT (Integer -> Text) -> Integer -> Text
forall a b. (a -> b) -> a -> b
$ Getting Integer (Recipe Entity) Integer -> Recipe Entity -> Integer
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Integer (Recipe Entity) Integer
forall e (f :: * -> *).
Functor f =>
(Integer -> f Integer) -> Recipe e -> f (Recipe e)
recipeWeight Recipe Entity
r
]
where
formatCE :: (a, Entity) -> Text
formatCE (a
c, Entity
e) = [Text] -> Text
T.unwords [a -> Text
forall a. Show a => a -> Text
showT a
c, Text -> Text
linkEntity (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Getting Text Entity Text -> Entity -> Text
forall s (m :: * -> *) a. MonadReader s m => Getting a s a -> m a
view Getting Text Entity Text
Lens' Entity Text
entityName Entity
e]
linkEntity :: Text -> Text
linkEntity Text
t =
if Text -> Bool
T.null Text
entityAddress
then Text
t
else Text -> Text -> Text
addLink (Text
entityAddress Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"#" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> HasCallStack => Text -> Text -> Text -> Text
Text -> Text -> Text -> Text
T.replace Text
" " Text
"-" Text
t) Text
t
recipeTable :: PageAddress -> [Recipe Entity] -> Text
recipeTable :: PageAddress -> [Recipe Entity] -> Text
recipeTable PageAddress
a [Recipe Entity]
rs = [Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [Text]
header [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> ([Text] -> Text) -> [[Text]] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map ([Int] -> [Text] -> Text
listToRow [Int]
mw) [[Text]]
recipeRows
where
mw :: [Int]
mw = [[Text]] -> [Int]
maxWidths ([Text]
recipeHeader [Text] -> [[Text]] -> [[Text]]
forall a. a -> [a] -> [a]
: [[Text]]
recipeRows)
recipeRows :: [[Text]]
recipeRows = (Recipe Entity -> [Text]) -> [Recipe Entity] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (PageAddress -> Recipe Entity -> [Text]
recipeRow PageAddress
a) [Recipe Entity]
rs
header :: [Text]
header = [[Int] -> [Text] -> Text
listToRow [Int]
mw [Text]
recipeHeader, [Int] -> Text
separatingLine [Int]
mw]
recipePage :: PageAddress -> [Recipe Entity] -> Text
recipePage :: PageAddress -> [Recipe Entity] -> Text
recipePage = PageAddress -> [Recipe Entity] -> Text
recipeTable