module Text.Commonmark.Syntax
( Doc(..)
, Blocks
, Block(..)
, HeadingLevel(..)
, ListType(..)
, Delimiter(..)
, BulletMarker(..)
, Inlines
, Inline(..)
, normalize
, asText
) where
import Control.DeepSeq (NFData)
import Data.Data (Data, Typeable)
import Data.Monoid
import Data.Sequence (Seq, ViewL(..), viewl, (<|))
import Data.String (IsString(..))
import GHC.Generics (Generic)
newtype Doc t = Doc (Blocks t)
deriving ( Show, Read, Eq
, Typeable, Data, Generic
, Functor, Foldable, Traversable
)
instance NFData t => NFData (Doc t)
instance Monoid t => Monoid (Doc t) where
mempty = Doc mempty
(Doc bs1 ) `mappend` (Doc bs2) = Doc (bs1 `mappend` bs2)
type Blocks t = Seq (Block t)
data Block t
= ThematicBreak
| Heading HeadingLevel (Inlines t)
| CodeBlock (Maybe t) t
| HtmlBlock t
| Para (Inlines t)
| Quote (Blocks t)
| List ListType Bool (Seq (Blocks t))
deriving
( Show, Read, Eq, Ord
, Typeable, Data, Generic
, Functor, Foldable, Traversable
)
instance (NFData t) => NFData (Block t)
data HeadingLevel
= Heading1
| Heading2
| Heading3
| Heading4
| Heading5
| Heading6
deriving
( Show, Read, Eq, Ord
, Typeable, Data, Generic
)
instance NFData HeadingLevel
data ListType
= Ordered Delimiter Int
| Bullet BulletMarker
deriving
( Show, Read, Eq, Ord
, Typeable, Data, Generic
)
instance NFData ListType
data Delimiter
= Period
| Paren
deriving
( Show, Read, Eq, Ord
, Typeable, Data, Generic
)
instance NFData Delimiter
data BulletMarker
= Minus
| Plus
| Asterisk
deriving
( Show, Read, Eq, Ord
, Typeable, Data, Generic
)
instance NFData BulletMarker
type Inlines t = Seq (Inline t)
data Inline t
= Str t
| Code t
| Emph (Inlines t)
| Strong (Inlines t)
| Link (Inlines t) t (Maybe t)
| Image (Inlines t) t (Maybe t)
| RawHtml t
| SoftBreak
| HardBreak
deriving
( Show, Read, Eq, Ord
, Typeable, Data, Generic
, Functor, Foldable, Traversable
)
instance IsString t => IsString (Inline t) where
fromString = Str . fromString
instance NFData t => NFData (Inline t)
normalize :: Monoid t => Inlines t -> Inlines t
normalize inlines = case viewl inlines of
Str t :< (viewl -> Str ts :< is) -> normalize (Str (t <> ts) <| is)
Image i u t :< is -> Image (normalize i) u t <| normalize is
Link i u t :< is -> Link (normalize i) u t <| normalize is
Emph i :< is -> Emph (normalize i) <| normalize is
Strong i :< is -> Strong (normalize i) <| normalize is
i :< is -> i <| normalize is
EmptyL -> mempty
asText :: (Monoid a, IsString a) => Inline a -> a
asText (Str t) = t
asText (Emph is) = foldMap asText is
asText (Strong is) = foldMap asText is
asText (Code t) = t
asText (Link is _ _) = foldMap asText is
asText (Image is _ _) = foldMap asText is
asText (RawHtml t) = t
asText SoftBreak = " "
asText HardBreak = "\n"