module Burrito.Render
( render
)
where
import qualified Burrito.Type.Expression as Expression
import qualified Burrito.Type.LitChar as LitChar
import qualified Burrito.Type.Literal as Literal
import qualified Burrito.Type.Modifier as Modifier
import qualified Burrito.Type.Name as Name
import qualified Burrito.Type.NonEmpty as NonEmpty
import qualified Burrito.Type.Operator as Operator
import qualified Burrito.Type.Template as Template
import qualified Burrito.Type.Token as Token
import qualified Burrito.Type.VarChar as VarChar
import qualified Burrito.Type.Variable as Variable
import qualified Data.List as List
import qualified Data.Word as Word
import qualified Text.Printf as Printf
render :: Template.Template -> String
render = concatMap renderToken . Template.tokens
renderToken :: Token.Token -> String
renderToken token = case token of
Token.Expression expression -> renderExpression expression
Token.Literal literal -> renderLiteral literal
renderExpression :: Expression.Expression -> String
renderExpression expression = mconcat
[ "{"
, renderOperator $ Expression.operator expression
, renderVariables $ Expression.variables expression
, "}"
]
renderOperator :: Operator.Operator -> String
renderOperator operator = case operator of
Operator.Ampersand -> "&"
Operator.FullStop -> "."
Operator.None -> ""
Operator.NumberSign -> "#"
Operator.PlusSign -> "+"
Operator.QuestionMark -> "?"
Operator.Semicolon -> ";"
Operator.Solidus -> "/"
renderVariables :: NonEmpty.NonEmpty Variable.Variable -> String
renderVariables = List.intercalate "," . fmap renderVariable . NonEmpty.toList
renderVariable :: Variable.Variable -> String
renderVariable variable = mconcat
[ renderName $ Variable.name variable
, renderModifier $ Variable.modifier variable
]
renderName :: Name.Name -> String
renderName name = mconcat
[ renderVarChar $ Name.first name
, concatMap
(\(fullStop, varChar) ->
(if fullStop then "." else "") <> renderVarChar varChar
)
$ Name.rest name
]
renderVarChar :: VarChar.VarChar -> String
renderVarChar varChar = case varChar of
VarChar.Encoded hi lo -> ['%', hi, lo]
VarChar.Unencoded char -> [char]
renderModifier :: Modifier.Modifier -> String
renderModifier modifier = case modifier of
Modifier.Asterisk -> "*"
Modifier.Colon int -> Printf.printf ":%d" int
Modifier.None -> ""
renderLiteral :: Literal.Literal -> String
renderLiteral =
concatMap renderCharacter . NonEmpty.toList . Literal.characters
renderCharacter :: LitChar.LitChar -> String
renderCharacter character = case character of
LitChar.Encoded word8 -> renderEncodedCharacter word8
LitChar.Unencoded char -> renderUnencodedCharacter char
renderEncodedCharacter :: Word.Word8 -> String
renderEncodedCharacter = Printf.printf "%%%02X"
renderUnencodedCharacter :: Char -> String
renderUnencodedCharacter = pure