module Text.Pandoc.Lens
(
Pandoc
, body
, meta
, Block
, blockInlines
, _Plain
, _Para
, _CodeBlock
, _BlockQuote
, _OrderedList
, _BulletList
, _DefinitionList
, _Header
, _HorizontalRule
, _Table
, _Div
, _Null
, Inline
, _Str
, _Emph
, _Strong
, _Strikeout
, _Superscript
, _Subscript
, _SmallCaps
, _Quoted
, _Cite
, _Code
, _Space
, _LineBreak
, _Math
, _RawInline
, _Link
, _Image
, _Note
, _Span
, MetaValue
, _MetaMap
, _MetaList
, _MetaBool
, _MetaString
, _MetaInlines
, _MetaBlocks
, HasAttr(..)
, attrIdentifier
, attrClasses
, attrs
) where
import Control.Applicative
import Control.Lens
import Text.Pandoc.Definition
import Data.Map (Map)
body :: Lens' Pandoc [Block]
body = lens (\(Pandoc _ b)->b) (\(Pandoc m _) b->Pandoc m b)
meta :: String -> Traversal' Pandoc MetaValue
meta name = metaL . _Wrapped' . ix name
where
metaL :: Lens' Pandoc Meta
metaL = lens (\(Pandoc m _)->m) (\(Pandoc _ a) m->Pandoc m a)
instance Wrapped Meta where
type Unwrapped Meta = Map String MetaValue
_Wrapped' = iso unMeta Meta
type instance Index Meta = String
type instance IxValue Meta = MetaValue
instance Ixed Meta where
ix k = _Wrapped' . ix k
instance At Meta where
at k = _Wrapped' . at k
_Plain :: Prism' Block [Inline]
_Plain = prism' Plain f
where
f (Plain x) = Just x
f _ = Nothing
_Para :: Prism' Block [Inline]
_Para = prism' Para f
where
f (Para x) = Just x
f _ = Nothing
_CodeBlock :: Prism' Block String
_CodeBlock = prism' (CodeBlock nullAttr) f
where
f (CodeBlock _ x) = Just x
f _ = Nothing
_BlockQuote :: Prism' Block [Block]
_BlockQuote = prism' BlockQuote f
where
f (BlockQuote x) = Just x
f _ = Nothing
_OrderedList :: Prism' Block (ListAttributes, [[Block]])
_OrderedList = prism' (uncurry OrderedList) f
where
f (OrderedList x y) = Just (x, y)
f _ = Nothing
_BulletList :: Prism' Block [[Block]]
_BulletList = prism' BulletList f
where
f (BulletList x) = Just x
f _ = Nothing
_DefinitionList :: Prism' Block [([Inline], [[Block]])]
_DefinitionList = prism' DefinitionList f
where
f (DefinitionList x) = Just x
f _ = Nothing
_Header :: Prism' Block (Int, [Inline])
_Header = prism' (\(a,b) -> Header a nullAttr b) f
where
f (Header a _ b) = Just (a, b)
f _ = Nothing
_HorizontalRule :: Prism' Block ()
_HorizontalRule = prism' (const HorizontalRule) f
where
f HorizontalRule = Just ()
f _ = Nothing
_Table :: Prism' Block ([Inline], [Alignment], [Double], [TableCell], [[TableCell]])
_Table = prism' (\(a, b, c, d, e) -> Table a b c d e) f
where
f (Table a b c d e) = Just (a, b, c, d, e)
f _ = Nothing
_Div :: Prism' Block [Block]
_Div = prism' (Div nullAttr) f
where
f (Div _ a) = Just a
f _ = Nothing
_Null :: Prism' Block ()
_Null = prism' (const Null) f
where
f Null = Just ()
f _ = Nothing
instance Plated Block where
plate f blk =
case blk of
BlockQuote blks -> BlockQuote <$> traverse f blks
OrderedList attrs blks -> OrderedList attrs <$> traverseOf (each . each) f blks
BulletList blks -> BulletList <$> traverseOf (each . each) f blks
DefinitionList blks -> DefinitionList <$> traverseOf (each . _2 . each . each) f blks
Table a b c hdrs rows -> Table a b c <$> traverseOf (each . each) f hdrs
<*> traverseOf (each . each . each) f rows
Div attrs blks -> Div attrs <$> traverseOf each f blks
_ -> pure blk
blockInlines :: Traversal' Block Inline
blockInlines f blk =
case blk of
Plain inls -> Plain <$> traverse f inls
Para inls -> Para <$> traverse f inls
DefinitionList xs -> DefinitionList <$> traverseOf (each . _1 . each) f xs
Header n attr inls -> Header n attr <$> traverse f inls
Table capt a b c d -> Table <$> traverse f capt
<*> pure a <*> pure b <*> pure c <*> pure d
_ -> pure blk
_Str :: Prism' Inline String
_Str = prism' Str f
where
f (Str s) = Just s
f _ = Nothing
_Emph :: Prism' Inline [Inline]
_Emph = prism' Emph f
where
f (Emph s) = Just s
f _ = Nothing
_Strong :: Prism' Inline [Inline]
_Strong = prism' Strong f
where
f (Strong s) = Just s
f _ = Nothing
_Strikeout :: Prism' Inline [Inline]
_Strikeout = prism' Strikeout f
where
f (Strikeout s) = Just s
f _ = Nothing
_Superscript :: Prism' Inline [Inline]
_Superscript = prism' Superscript f
where
f (Superscript s) = Just s
f _ = Nothing
_Subscript :: Prism' Inline [Inline]
_Subscript = prism' Subscript f
where
f (Subscript s) = Just s
f _ = Nothing
_SmallCaps :: Prism' Inline [Inline]
_SmallCaps = prism' SmallCaps f
where
f (SmallCaps s) = Just s
f _ = Nothing
_Quoted :: Prism' Inline (QuoteType, [Inline])
_Quoted = prism' (uncurry Quoted) f
where
f (Quoted a b) = Just (a,b)
f _ = Nothing
_Cite :: Prism' Inline ([Citation], [Inline])
_Cite = prism' (uncurry Cite) f
where
f (Cite a b) = Just (a,b)
f _ = Nothing
_Code :: Prism' Inline String
_Code = prism' (Code nullAttr) f
where
f (Code _ s) = Just s
f _ = Nothing
_Space :: Prism' Inline ()
_Space = prism' (const Space) f
where
f Space = Just ()
f _ = Nothing
_LineBreak :: Prism' Inline ()
_LineBreak = prism' (const LineBreak) f
where
f LineBreak = Just ()
f _ = Nothing
_Math :: Prism' Inline (MathType, String)
_Math = prism' (uncurry Math) f
where
f (Math a b) = Just (a, b)
f _ = Nothing
_RawInline :: Prism' Inline (Format, String)
_RawInline = prism' (uncurry RawInline) f
where
f (RawInline a b) = Just (a, b)
f _ = Nothing
_Link :: Prism' Inline ([Inline], Target)
_Link = prism' (uncurry $ Link nullAttr) f
where
f (Link _ a b) = Just (a, b)
f _ = Nothing
_Image :: Prism' Inline ([Inline], Target)
_Image = prism' (uncurry $ Image nullAttr) f
where
f (Image _ a b) = Just (a, b)
f _ = Nothing
_Note :: Prism' Inline [Block]
_Note = prism' Note f
where
f (Note s) = Just s
f _ = Nothing
_Span :: Prism' Inline [Inline]
_Span = prism' (Span nullAttr) f
where
f (Span _ s) = Just s
f _ = Nothing
instance Plated Inline where
plate f inl =
case inl of
Emph cs -> Emph <$> traverseOf each f cs
Strong cs -> Strong <$> traverseOf each f cs
Strikeout cs -> Strikeout <$> traverseOf each f cs
Superscript cs -> Superscript <$> traverseOf each f cs
Subscript cs -> Subscript <$> traverseOf each f cs
SmallCaps cs -> SmallCaps <$> traverseOf each f cs
Quoted q cs -> Quoted q <$> traverseOf each f cs
Cite cit cs -> Cite cit <$> traverseOf each f cs
Span attrs cs -> Span attrs <$> traverseOf each f cs
_ -> pure inl
_MetaMap :: Prism' MetaValue (Map String MetaValue)
_MetaMap = prism' MetaMap f
where
f (MetaMap x) = Just x
f _ = Nothing
_MetaList :: Prism' MetaValue [MetaValue]
_MetaList = prism' MetaList f
where
f (MetaList x) = Just x
f _ = Nothing
_MetaBool :: Prism' MetaValue Bool
_MetaBool = prism' MetaBool f
where
f (MetaBool x) = Just x
f _ = Nothing
_MetaString :: Prism' MetaValue String
_MetaString = prism' MetaString f
where
f (MetaString x) = Just x
f _ = Nothing
_MetaInlines :: Prism' MetaValue [Inline]
_MetaInlines = prism' MetaInlines f
where
f (MetaInlines x) = Just x
f _ = Nothing
_MetaBlocks :: Prism' MetaValue [Block]
_MetaBlocks = prism' MetaBlocks f
where
f (MetaBlocks x) = Just x
f _ = Nothing
instance Plated MetaValue where
plate f inl =
case inl of
MetaMap cs -> MetaMap <$> traverseOf each f cs
MetaList cs -> MetaList <$> traverseOf each f cs
_ -> pure inl
class HasAttr a where
attributes :: Traversal' a Attr
instance HasAttr Block where
attributes f (CodeBlock a s) = fmap (\a'->CodeBlock a' s) (f a)
attributes f (Header n a s) = fmap (\a'->Header n a' s) (f a)
attributes f (Div a s) = fmap (\a'->Div a' s) (f a)
attributes _ x = pure x
instance HasAttr Inline where
attributes f (Code a s) = fmap (\a'->Code a' s) (f a)
attributes f (Span a s) = fmap (\a'->Span a' s) (f a)
attributes _ x = pure x
attrIdentifier :: Lens' Attr String
attrIdentifier = _1
attrClasses :: Lens' Attr [String]
attrClasses = _2
attrs :: Lens' Attr [(String, String)]
attrs = _3