module Ronn.Render
( ronnToText
, ronnGroupToText
, ronnLineToText
, ronnPartToText
) where
import Prelude
import Data.Text (Text, pack)
import Data.Text qualified as T
import Ronn.AST
ronnToText :: Ronn -> Text
ronnToText :: Ronn -> Text
ronnToText Ronn
ronn =
[Text] -> Text
T.unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
(Group -> Text) -> [Group] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Group -> Text
ronnGroupToText ([Group] -> [Text]) -> [Group] -> [Text]
forall a b. (a -> b) -> a -> b
$
ManRef -> [Part] -> Group
Title Ronn
ronn.name Ronn
ronn.description
Group -> [Group] -> [Group]
forall a. a -> [a] -> [a]
: (Section -> [Group]) -> [Section] -> [Group]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Section -> [Group]
ronnSectionToGroups Ronn
ronn.sections
ronnSectionToGroups :: Section -> [Group]
ronnSectionToGroups :: Section -> [Group]
ronnSectionToGroups Section
section =
Text -> Group
Header Section
section.name Group -> [Group] -> [Group]
forall a. a -> [a] -> [a]
: (Content -> [Group]) -> [Content] -> [Group]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int -> Content -> [Group]
ronnContentToGroups Int
0) Section
section.content
ronnContentToGroups :: Int -> Content -> [Group]
ronnContentToGroups :: Int -> Content -> [Group]
ronnContentToGroups Int
indentLevel = \case
Definitions [Definition]
defns ->
(Definition -> [Group]) -> [Definition] -> [Group]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int -> Definition -> [Group]
ronnDefinitionToGroups (Int -> Definition -> [Group]) -> Int -> Definition -> [Group]
forall a b. (a -> b) -> a -> b
$ Int
indentLevel Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) [Definition]
defns
Groups [Group]
gs -> (Group -> Group) -> [Group] -> [Group]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Group -> Group
indentRonnGroup Int
indentLevel) [Group]
gs
ronnDefinitionToGroups :: Int -> Definition -> [Group]
ronnDefinitionToGroups :: Int -> Definition -> [Group]
ronnDefinitionToGroups Int
indentLevel Definition
defn =
[ [Line] -> Group
Lines
[ Int -> Line -> Line
indentRonnLine Int
indentLevel (Line -> Line) -> Line -> Line
forall a b. (a -> b) -> a -> b
$ [Part] -> Line
Line [Part
"* " Part -> Part -> Part
forall a. Semigroup a => a -> a -> a
<> Definition
defn.name Part -> Part -> Part
forall a. Semigroup a => a -> a -> a
<> Part
":"]
, Int -> Line -> Line
indentRonnLine Int
nextIndentLevel Definition
defn.description
]
]
[Group] -> [Group] -> [Group]
forall a. Semigroup a => a -> a -> a
<> [Group]
nested
where
nested :: [Group]
nested = [Group] -> ([Content] -> [Group]) -> Maybe [Content] -> [Group]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ((Content -> [Group]) -> [Content] -> [Group]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ((Content -> [Group]) -> [Content] -> [Group])
-> (Content -> [Group]) -> [Content] -> [Group]
forall a b. (a -> b) -> a -> b
$ Int -> Content -> [Group]
ronnContentToGroups Int
nextIndentLevel) Definition
defn.content
nextIndentLevel :: Int
nextIndentLevel = Int
indentLevel Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2
ronnGroupToText :: Group -> Text
ronnGroupToText :: Group -> Text
ronnGroupToText = [Text] -> Text
T.unlines ([Text] -> Text) -> (Group -> [Text]) -> Group -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Line -> Text) -> [Line] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Line -> Text
ronnLineToText ([Line] -> [Text]) -> (Group -> [Line]) -> Group -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Group -> [Line]
ronnGroupToLines
ronnGroupToLines :: Group -> [Line]
ronnGroupToLines :: Group -> [Line]
ronnGroupToLines = \case
Title ManRef
ref [Part]
description ->
let nameLine :: Line
nameLine = ManRef -> [Part] -> Line
ronnNameLine ManRef
ref [Part]
description
in [ Line
nameLine
, [Part] -> Line
Line [Text -> Part
Raw (Text -> Part) -> Text -> Part
forall a b. (a -> b) -> a -> b
$ Int -> Text -> Text
T.replicate (Line -> Int
ronnLineLength Line
nameLine) Text
"="]
]
Header Text
name -> [[Part] -> Line
Line [Part
"##", Text -> Part
Raw Text
name]]
Lines [Line]
ls -> [Line]
ls
ronnNameLine :: ManRef -> [Part] -> Line
ronnNameLine :: ManRef -> [Part] -> Line
ronnNameLine ManRef
ref =
[Part] -> Line
Line ([Part] -> Line) -> ([Part] -> [Part]) -> [Part] -> Line
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Part
Raw (ManRef -> Text
manRefToText ManRef
ref) :) ([Part] -> [Part]) -> ([Part] -> [Part]) -> [Part] -> [Part]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Part
"--" :)
ronnLineToText :: Line -> Text
ronnLineToText :: Line -> Text
ronnLineToText = [Text] -> Text
T.unwords ([Text] -> Text) -> (Line -> [Text]) -> Line -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Part -> Text) -> [Part] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Part -> Text
ronnPartToText ([Part] -> [Text]) -> (Line -> [Part]) -> Line -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (.unwrap)
ronnPartToText :: Part -> Text
ronnPartToText :: Part -> Text
ronnPartToText = \case
Concat [Part]
xs -> [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (Part -> Text) -> [Part] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map Part -> Text
ronnPartToText [Part]
xs
Code Part
x -> Text
"`" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"`"
UserInput Part
x -> Text
"`" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"`"
Strong Part
x -> Text
"**" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"**"
Variable Part
x -> Text
"<" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
">"
Ephasis Part
x -> Text
"_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"_"
Brackets Part
x -> Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
Parens Part
x -> Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Part -> Text
ronnPartToText Part
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
Ref ManRef
ref -> Part -> Text
ronnPartToText (Part -> Text) -> Part -> Text
forall a b. (a -> b) -> a -> b
$ Part -> Part
Strong (Part -> Part) -> Part -> Part
forall a b. (a -> b) -> a -> b
$ Text -> Part
Raw (Text -> Part) -> Text -> Part
forall a b. (a -> b) -> a -> b
$ ManRef -> Text
manRefToText ManRef
ref
Raw Text
x -> Text
x
manRefToText :: ManRef -> Text
manRefToText :: ManRef -> Text
manRefToText ManRef
ref =
ManRef
ref.name
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"("
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
pack (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ ManSection -> Int
manSectionNumber ManRef
ref.section)
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
ronnLineLength :: Line -> Int
ronnLineLength :: Line -> Int
ronnLineLength = Text -> Int
T.length (Text -> Int) -> (Line -> Text) -> Line -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Line -> Text
ronnLineToText
indentRonnGroup :: Int -> Group -> Group
indentRonnGroup :: Int -> Group -> Group
indentRonnGroup Int
indentLevel = \case
g :: Group
g@Title {} -> Group
g
g :: Group
g@Header {} -> Group
g
Lines [Line]
ls -> [Line] -> Group
Lines ([Line] -> Group) -> [Line] -> Group
forall a b. (a -> b) -> a -> b
$ (Line -> Line) -> [Line] -> [Line]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Line -> Line
indentRonnLine Int
indentLevel) [Line]
ls
indentRonnLine :: Int -> Line -> Line
indentRonnLine :: Int -> Line -> Line
indentRonnLine Int
n = \case
Line [] -> [Part] -> Line
Line []
Line (Part
p : [Part]
ps) -> [Part] -> Line
Line ([Part] -> Line) -> [Part] -> Line
forall a b. (a -> b) -> a -> b
$ (Part
spaces Part -> Part -> Part
forall a. Semigroup a => a -> a -> a
<> Part
p) Part -> [Part] -> [Part]
forall a. a -> [a] -> [a]
: [Part]
ps
where
spaces :: Part
spaces = Text -> Part
Raw (Text -> Part) -> Text -> Part
forall a b. (a -> b) -> a -> b
$ String -> Text
pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
n Char
' '