| HorizontalLine
| List !ListElement
| DefinitionList ![Definition]
- | LeadingSpaced ![InlineElement]
+ | Preformatted ![InlineElement]
| Paragraph ![InlineElement]
deriving (Eq, Show)
data InlineElement
= Text !String
+ | Italic ![InlineElement]
+ | Bold ![InlineElement]
| PageLink {
linkPage :: !(Maybe PageName)
, linkFragment :: !(Maybe String)
DefinitionList list
-> formatDefinitionList -< (baseURI, list)
- LeadingSpaced inlines
- -> formatLeadingSpaced -< (baseURI, inlines)
+ Preformatted inlines
+ -> formatPreformatted -< (baseURI, inlines)
Paragraph inlines
-> formatParagraph -< (baseURI, inlines)
) -< (baseURI, def)
-formatLeadingSpaced :: (ArrowXml a, ArrowChoice a) => a (URI, [InlineElement]) XmlTree
-formatLeadingSpaced
+formatPreformatted :: (ArrowXml a, ArrowChoice a) => a (URI, [InlineElement]) XmlTree
+formatPreformatted
= eelem "pre"
+= ( (arr fst &&& arrL snd)
>>>
Text text
-> mkText -< text
+ Italic inlines
+ -> ( eelem "i"
+ += ( (arr fst &&& arrL snd)
+ >>>
+ formatInline
+ )
+ ) -< (baseURI, inlines)
+
+ Bold inlines
+ -> ( eelem "b"
+ += ( (arr fst &&& arrL snd)
+ >>>
+ formatInline
+ )
+ ) -< (baseURI, inlines)
+
link@(PageLink _ _ _)
-> formatPageLink -< (baseURI, link)
<|>
definitionList
<|>
+ pdata
+ <|>
leadingSpaced
<|>
paragraph
horizontalLine :: Parser BlockElement
-horizontalLine = try $ do count 4 (char '-')
+horizontalLine = try ( do count 4 (char '-')
many (char '-')
ws
eol
return HorizontalLine
+ )
+ <?>
+ "horizontal line"
listElement :: Parser BlockElement
"description of term"
+pdata :: Parser BlockElement
+pdata = do try (string "<![PDATA[")
+ many (oneOf " \t\n")
+ x <- pdata'
+ return (Preformatted [Text x])
+ where
+ pdata' :: Parser String
+ pdata' = do try (many (oneOf " \t\n") >> string "]]>")
+ return []
+ <|>
+ do x <- anyChar
+ xs <- pdata'
+ return (x:xs)
+
+
leadingSpaced :: Parser BlockElement
-leadingSpaced = char ' ' >> leadingSpaced' >>= return . LeadingSpaced
+leadingSpaced = (char ' ' >> leadingSpaced' >>= return . Preformatted)
+ <?>
+ "leading space"
where
leadingSpaced' :: Parser [InlineElement]
leadingSpaced' = do x <- inlineElement
inlineElement :: Parser InlineElement
inlineElement = skipMany comment
>>
- ( try text
+ ( cdata
+ <|>
+ apostrophes
<|>
- try pageLink
+ text
+ <|>
+ pageLink
)
+cdata :: Parser InlineElement
+cdata = try (string "<![CDATA[") >> cdata' >>= return . Text
+ where
+ cdata' :: Parser String
+ cdata' = do try (string "]]>")
+ return []
+ <|>
+ do x <- anyChar
+ xs <- cdata'
+ return (x:xs)
+
+
text :: Parser InlineElement
text = ( char ':'
>>
- many (noneOf ('\n':':':inlineSymbols))
+ many (noneOf ('\n':inlineSymbols))
>>=
return . Text . (':' :)
- -- 定義リストとの關係上、コロンは先頭にしか存在できない。
+ -- 定義リストとの關係上、コロンは先頭にしか來れない。
)
<|>
- ( many1 (noneOf ('\n':':':inlineSymbols))
+ ( many1 (noneOf ('\n':inlineSymbols))
>>=
return . Text
)
+ <?>
+ "text"
+
+
+apostrophes :: Parser InlineElement
+apostrophes = foldr (<|>) pzero (map try [apos1, apos2, apos3, apos4, apos5])
+ where
+ apos1 = apos 1 >> return (Text "'")
+
+ apos2 = do apos 2
+ xs <- many1 inlineElement
+ apos 2
+ return (Italic xs)
+
+ apos3 = do apos 3
+ xs <- many1 inlineElement
+ apos 3
+ return (Bold xs)
+
+ apos4 = apos 4 >> return (Text "'")
+
+ apos5 = do apos 5
+ xs <- many1 inlineElement
+ apos 5
+ return (Italic [Bold xs])
+
+ apos :: Int -> Parser ()
+ apos n = count n (char '\'') >> notFollowedBy (char '\'')
pageLink :: Parser InlineElement
-pageLink = do string "[["
+pageLink = do try (string "[[")
page <- option Nothing
(many1 (noneOf "#|]") >>= return . Just)
fragment <- option Nothing
inlineSymbols :: [Char]
-inlineSymbols = "<["
+inlineSymbols = "<[:'"
-- white space
ws :: Parser ()
===== Heading 5 =====
-== &lt;nowiki&gt; tags ==
-<nowiki>
+== Italic and bold ==
+You can ''italicize text'' by putting 2
+apostrophes on each side.
+
+3 apostrophes will bold '''the text'''.
+
+5 apostrophes will bold and italicize
+'''''the text'''''.
+
+(Using 4 apostrophes doesn't do anything
+special -- there are just '''' left
+over ones'''' that are included as part of the text.)
+
+
+== CDATA section ==
+<![CDATA[
[[Wiki]] markup is ignored here
but the text is reformatted.
-</nowiki>
+]]>
-== &lt;pre&gt; tags ==
-<pre>
+== PDATA section ==
+<![PDATA[
[[Wiki]] markup is ignored here
and reformatting is also disabled.
-</pre>
+]]>
== Leading spaces ==
This
== Horizontal Line ==
----
+== Inline Object ==
+<object data="Foo" float="right" framed="yes">
+ This is a caption containing [[Foo|markups]].
+</object>
+
+blah blah blah...
+
== Quotation ==
<blockquote>
blah blah blah...
Another paragraph...
-= Syntax Help =
+== Italic and bold ==
+You can ''italicize text'' by putting 2
+apostrophes on each side.
-== Heading ==
+3 apostrophes will bold '''the text'''.
-=== Heading 3 ===
+5 apostrophes will bold and italicize
+'''''the text'''''.
-==== Heading 4 ====
+(Using 4 apostrophes doesn't do anything
+special -- there are just '''' left
+over ones'''' that are included as part of the text.)
-===== Heading 5 =====
+== CDATA section ==
+<![CDATA[
+[[Wiki]] markup is ignored here
+but the text is reformatted.
+]]>
+
+== PDATA section ==
+<![PDATA[
+[[Wiki]] markup is ignored here
+ and reformatting is also disabled.
+]]>
== Leading spaces ==
This
preformatted
text.
[[Foo|Wiki markup is interpreted here.]]
-
-== Horizontal Line ==
-----
-
-== Listing ==
-* foo
-* bar
-** baz
-
-aaaaa
-
-# foo
-## bar
-### baz
-
-* foo
-*# bar
-*#* baz
-*# bar
-
-== Definition ==
-; AAA : aaaaaaaaaaaaaaaaa
-; BBBBBBBBB
-: bbb
-: ccccccccccc
-
-== Link ==
-* [[Page]]
-* [[page]]
-* [[space in a page name]]
-* [[Page|Link to "Page"]]
-* [[Page#Heading]]
-* [[#Heading]]
-* [[Page#Heading|Link to "Page#Heading"]]
-* [[#example]]
</textData>
</page>
, (parseWiki " foo"
~?=
- (Right [ LeadingSpaced [ Text "foo" ] ]))
+ (Right [ Preformatted [ Text "foo" ] ]))
, (parseWiki " foo\n bar\n"
~?=
- (Right [ LeadingSpaced [ Text "foo"
- , Text "\n"
- , Text " bar"
- ]
+ (Right [ Preformatted [ Text "foo"
+ , Text "\n"
+ , Text " bar"
+ ]
]))
, (parseWiki "foo\n bar\nbaz"
~?=
- (Right [ Paragraph [ Text "foo" ]
- , LeadingSpaced [ Text "bar" ]
- , Paragraph [ Text "baz" ]
+ (Right [ Paragraph [ Text "foo" ]
+ , Preformatted [ Text "bar" ]
+ , Paragraph [ Text "baz" ]
]))
, (parseWiki "----"
, Text "baz" ]
]
]))
+
+ , (parseWiki "<![CDATA[foo [[bar]] baz]]>"
+ ~?=
+ (Right [ Paragraph [ Text "foo [[bar]] baz" ] ]))
+
+ , (parseWiki "<![PDATA[foo [[bar]] baz]]>"
+ ~?=
+ (Right [ Preformatted [ Text "foo [[bar]] baz" ] ]))
+
+ , (parseWiki "<![PDATA[\nfoo [[bar]] baz\n]]>"
+ ~?=
+ (Right [ Preformatted [ Text "foo [[bar]] baz" ] ]))
+
+ , (parseWiki "foo' bar"
+ ~?=
+ (Right [ Paragraph [ Text "foo"
+ , Text "'"
+ , Text " bar" ]
+ ]))
+
+ , (parseWiki "''foo''"
+ ~?=
+ (Right [ Paragraph [ Italic [Text "foo"] ] ]))
+
+ , (parseWiki "'''foo'''"
+ ~?=
+ (Right [ Paragraph [ Bold [Text "foo"] ] ]))
+
+ , (parseWiki "foo''''"
+ ~?=
+ (Right [ Paragraph [ Text "foo"
+ , Text "'"
+ ]
+ ]))
+
+ , (parseWiki "'''''foo'''''"
+ ~?=
+ (Right [ Paragraph [ Italic [Bold [Text "foo"]] ] ]))
]