{-# LANGUAGE LambdaCase #-}
module Text.Jira.Markup
( Block (..)
, Inline (..)
, ListStyle (..)
, URL (..)
, Row (..)
, Cell (..)
, Language (..)
, Parameter (..)
, normalizeInlines
) where
import Data.Text (Text, append)
data Inline
= Anchor Text
| Deleted [Inline]
| Emph [Inline]
| Entity Text
| Image URL
| Inserted [Inline]
| Linebreak
| Link [Inline] URL
| Monospaced [Inline]
| Str Text
| Space
| Strong [Inline]
| Subscript [Inline]
| Superscript [Inline]
deriving (Eq, Ord, Show)
data Block
= Code Language [Parameter] Text
| BlockQuote [Block]
| Header Int [Inline]
| List ListStyle [[Block]]
| NoFormat [Parameter] Text
| Panel [Parameter] [Block]
| Para [Inline]
| Table [Row]
deriving (Eq, Ord, Show)
data ListStyle
= CircleBullets
| SquareBullets
| Enumeration
deriving (Eq, Ord, Show)
newtype URL = URL { fromURL :: Text }
deriving (Eq, Ord, Show)
newtype Row = Row { fromRow :: [Cell] }
deriving (Eq, Ord, Show)
data Cell
= BodyCell [Block]
| HeaderCell [Block]
deriving (Eq, Ord, Show)
newtype Language = Language Text
deriving (Eq, Ord, Show)
data Parameter = Parameter
{ parameterKey :: Text
, parameterValue :: Text
} deriving (Eq, Ord, Show)
normalizeInlines :: [Inline] -> [Inline]
normalizeInlines = \case
[] -> []
[Space] -> []
[Linebreak] -> []
Space : Space : xs -> Space : normalizeInlines xs
Space : Linebreak : xs -> Linebreak : normalizeInlines xs
Linebreak : Space : xs -> Linebreak : normalizeInlines xs
Str s1 : Str s2 : xs -> Str (s1 `append` s2) : normalizeInlines xs
x : xs -> x : normalizeInlines xs