, Option [] ["disable-stderr-log"]
(NoArg OptDisableStderrLog)
- ("Disable logging to stderr.")
+ "Disable logging to stderr."
, Option [] ["rebuild-index"]
(NoArg OptRebuildIndex)
- ("Rebuild the index database.")
+ "Rebuild the index database."
, Option ['h'] ["help"]
(NoArg OptHelp)
withSubversion $
do (opts, nonOpts, errors) <- return . getOpt Permute options =<< getArgs
- when (not $ null errors)
+ unless (null errors)
$ do mapM_ putStr errors
exitWith $ ExitFailure 1
$ do printUsage
exitWith ExitSuccess
- when (not $ null nonOpts)
+ unless (null nonOpts)
$ do printUsage
exitWith $ ExitFailure 1
loadUserMap path
= do exist <- doesFileExist path
m <- if exist then
- readFile path
- >>=
- return . M.fromList . map decodePair . fromJust . deserializeStringPairs
+ liftM (M.fromList . map decodePair . fromJust . deserializeStringPairs)
+ (readFile path)
else
return M.empty
sha1 <- return . fromJust =<< getDigestByName "SHA1"
storage <- mkStorage lsdir repos (makeDraft' interpTable)
authDB <- mkAuthDB lsdir
- return $ Environment {
+ return Environment {
envLocalStateDir = lsdir
, envLucuConf = lucuConf
, envRepository = repos
findChangedPages :: Repository -> RevNum -> RevNum -> IO (Set PageName)
findChangedPages repos 0 newRev = findAllPages repos newRev
findChangedPages repos oldRev newRev
- = mapM (findChangedPagesAtRevision repos) [oldRev + 1 .. newRev]
- >>=
- return . S.unions
+ = liftM S.unions (mapM (findChangedPagesAtRevision repos) [oldRev + 1 .. newRev])
getDirContents' :: Repository -> PageName -> Maybe RevNum -> IO [PageName]
fromId words docId
= do uri <- getDocURI index docId
rev <- unsafeInterleaveIO $
- getDocAttr index docId "rakka:revision"
- >>=
- return . read . fromJust
+ liftM (read . fromJust)
+ (getDocAttr index docId "rakka:revision")
lastMod <- unsafeInterleaveIO $
- getDocAttr index docId "@mdate"
- >>=
- return . zonedTimeToUTC . fromJust . parseW3CDateTime . fromJust
+ liftM (zonedTimeToUTC . fromJust . parseW3CDateTime . fromJust)
+ (getDocAttr index docId "@mdate")
summary <- unsafeInterleaveIO $
getDocAttr index docId "rakka:summary"
snippet <- unsafeInterleaveIO $
rev <- if eof then
return 0
else
- hGetLine h >>= return . read
+ liftM read (hGetLine h)
rev' <- f rev
hSeek h AbsoluteSeek 0
hSetFileSize h 0
traverse :: FilePath -> Rev (Set PageName)
traverse dir
- = getDirEntries dir >>= mapM (traverse' dir) >>= return . S.unions
+ = liftM S.unions (getDirEntries dir >>= mapM (traverse' dir))
traverse' :: FilePath -> DirEntry -> Rev (Set PageName)
traverse' dir entry
path = mkDirPath dir
getDir' :: Rev [PageName]
- getDir' = getDirEntries path >>= return . map entToName
+ getDir' = liftM (map entToName) (getDirEntries path)
entToName :: DirEntry -> PageName
entToName = (dir </>) . decodePageName . dropExtension . entName
findChangedPagesAtRevision repos rev
= do fs <- getRepositoryFS repos
withRevision fs rev
- $ getPathsChanged >>= return . foldl accumulatePages S.empty . map fst
+ $ liftM (foldl accumulatePages S.empty . map fst) getPathsChanged
where
accumulatePages :: Set PageName -> FilePath -> Set PageName
accumulatePages s path
$ fmap chomp (lookup "svn:mime-type" props)
lastMod <- unsafeIOToFS $
- getRevisionProp' fs pageRev "svn:date"
- >>= return . fromJust . parseW3CDateTime . chomp . fromJust
+ liftM (fromJust . parseW3CDateTime . chomp . fromJust)
+ (getRevisionProp' fs pageRev "svn:date")
return Entity {
entityName = name
dest = chomp $ decodeString content
lastMod <- unsafeIOToFS $
- getRevisionProp' fs pageRev "svn:date"
- >>= return . fromJust . parseW3CDateTime . chomp . fromJust
+ liftM (fromJust . parseW3CDateTime . chomp . fromJust)
+ (getRevisionProp' fs pageRev "svn:date")
- isLocked <- getNodeProp path "rakka:isLocked"
- >>= return . isJust
+ isLocked <- liftM isJust (getNodeProp path "rakka:isLocked")
return Redirection {
redirName = name
case uiOldName ui of
Nothing -> return ()
Just oldName -> do exists <- isFile (mkPagePath oldName)
- when (exists)
+ when exists
$ do movePage (uiOldRevision ui) oldName name
moveAttachments (uiOldRevision ui) oldName name
exists <- isFile (mkPagePath name)
- unless (exists)
+ unless exists
$ createPage name
updatePage name
case ret of
path = mkAttachmentPath pName aName
loadAttachment' :: Rev a
- loadAttachment' = getFileContents path >>= return . deserializeFromString . decodeString
+ loadAttachment' = liftM (deserializeFromString . decodeString) (getFileContents path)
putAttachmentIntoRepository :: Attachment a =>
= let code = svnErrCode err
msg = svnErrMsg err
in
- fail $ "SvnError: " ++ (show code) ++ ": " ++ msg
+ fail $ "SvnError: " ++ show code ++ ": " ++ msg
mkSystemConfig :: LC.Config -> Repository -> IO SystemConfig
mkSystemConfig lc repos
= do cache <- newTVarIO M.empty
- return $ SystemConfig {
+ return SystemConfig {
scLucuConf = lc
, scRepository = repos
, scCache = cache
deserializeStringPairs :: String -> Maybe [(String, String)]
-deserializeStringPairs = sequence . map deserializePair' . lines
+deserializeStringPairs = mapM deserializePair' . lines
where
deserializePair' :: String -> Maybe (String, String)
deserializePair' s = case break (== ' ') s of
instance SysConfValue SiteName where
confPath _ = "siteName"
serialize (SiteName name) = name
- deserialize name = Just (SiteName name)
+ deserialize = Just . SiteName
defaultValue _ = SiteName "Rakka"
instance SysConfValue DefaultPage where
confPath _ = "defaultPage"
serialize (DefaultPage name) = name
- deserialize name = Just (DefaultPage name)
+ deserialize = Just . DefaultPage
defaultValue _ = DefaultPage "MainPage"
instance SysConfValue StyleSheet where
confPath _ = "styleSheet"
serialize (StyleSheet name) = name
- deserialize name = Just (StyleSheet name)
+ deserialize = Just . StyleSheet
defaultValue _ = StyleSheet "StyleSheet/Default"
instance SysConfValue Languages where
confPath _ = "languages"
serialize (Languages langs) = serializeStringPairs (M.toList langs)
- deserialize langs = fmap (Languages . M.fromList) (deserializeStringPairs langs)
+ deserialize = fmap (Languages . M.fromList) . deserializeStringPairs
defaultValue _
= Languages $ M.fromList [ ("en", "English" )
, ("es", "Español" )
timeOfDay = localTimeOfDay localTime
(secInt, secFrac) = properFraction (todSec timeOfDay)
in
- (printf "%04d-%02d-%02dT%02d:%02d:%02d"
- year
- month
- day
- (todHour timeOfDay)
- (todMin timeOfDay)
- (secInt :: Int))
+ printf "%04d-%02d-%02dT%02d:%02d:%02d"
+ year
+ month
+ day
+ (todHour timeOfDay)
+ (todMin timeOfDay)
+ (secInt :: Int))
++
(if secFrac == 0
then ""
formatTimeZone :: TimeZone -> String
formatTimeZone tz
= case timeZoneMinutes tz of
- offset | offset < 0 -> '-':(showTZ $ negate offset)
+ offset | offset < 0 -> '-' : (showTZ $ negate offset)
| offset == 0 -> "Z"
- | otherwise -> '+':(showTZ offset)
+ | otherwise -> '+' : showTZ offset
showTZ :: Int -> String
showTZ offset
show2 hour ++ ":" ++ show2 minute
show2 :: Int -> String
- show2 n | n < 10 = '0':(show n)
+ show2 n | n < 10 = '0' : show n
| otherwise = show n
(langName, name) : mergeTables m xs
mkLangList :: [(LanguageName, PageName)] -> BlockElement
- mkLangList xs = List Bullet (map mkLangLink xs)
+ mkLangList = List Bullet . map mkLangLink
mkLangLink :: (LanguageName, PageName) -> ListItem
mkLangLink (langName, name)
mkOutline tree = fst (mkOutline' emptyOutline 1 headings)
where
headings :: [BlockElement]
- headings = concat (map collectInBlock tree)
+ headings = concatMap collectInBlock tree
collectInBlock :: BlockElement -> [BlockElement]
collectInBlock hd@(Heading _ _)
= [hd]
collectInBlock (Div _ xs)
- = concat $ map collectInBlock $ catMaybes (map castToBlock xs)
+ = concatMap collectInBlock $ catMaybes (map castToBlock xs)
collectInBlock (BlockCmd (BlockCommand _ _ xs))
- = concat $ map collectInBlock xs
+ = concatMap collectInBlock xs
collectInBlock _
= []
mkListItem :: Bool -> HitPage -> IO ListItem
mkListItem showSummary page
= do lastMod <- utcToLocalZonedTime (hpLastMod page)
- return ( [ Inline ( PageLink {
- linkPage = Just (hpPageName page)
- , linkFragment = Nothing
- , linkText = Nothing
- }
- )
+ return ( [ Inline PageLink {
+ linkPage = Just (hpPageName page)
+ , linkFragment = Nothing
+ , linkText = Nothing
+ }
, Block ( Div [("class", "date")]
[Inline (Text (formatRFC1123DateTime lastMod))]
)
Nothing
-> return []
Just name
- -> getAttachment (ctxStorage ctx) name "trackbacks" Nothing
- >>=
- return . fromMaybe []
+ -> liftM (fromMaybe [])
+ (getAttachment (ctxStorage ctx) name "trackbacks" Nothing)
items <- mapM mkListItem trackbacks
let divElem = Div [("class", "trackbacks")] [list]
x <- notFollowedBy (char '=') >> anyChar
xs <- manyTill anyChar (try $ ws >> ( count n (char '=')
<?>
- ("trailing " ++ take n (repeat '='))
+ ("trailing " ++ replicate n '=')
)
)
ws
$ try $ do skipMany comment
newline
string stack
- listElement' stack >>= return . Just
+ liftM Just (listElement' stack)
rest <- items stack
return $ (map Inline xs ++ map Block (catMaybes [nested])) : rest
<|>
definitionList :: CommandTypeOf -> Parser BlockElement
-definitionList cmdTypeOf = many1 definition >>= return . DefinitionList
+definitionList cmdTypeOf = liftM DefinitionList (many1 definition)
where
definition :: Parser Definition
definition = do char ';'
leadingSpaced :: CommandTypeOf -> Parser BlockElement
-leadingSpaced cmdTypeOf = (char ' ' >> leadingSpaced' >>= return . Preformatted)
+leadingSpaced cmdTypeOf = liftM Preformatted (char ' ' >> leadingSpaced')
<?>
"leading space"
where
xs <- leadingSpaced'
return (x:xs)
<|>
- try ( newline
- >>
- char ' '
- >>
- leadingSpaced'
- >>=
- return . (Text "\n" :)
+ try ( liftM (Text "\n" :) ( newline
+ >>
+ char ' '
+ >>
+ leadingSpaced'
+ )
)
<|>
return []
paragraph :: CommandTypeOf -> Parser BlockElement
-paragraph cmdTypeOf = paragraph' >>= return . Paragraph
+paragraph cmdTypeOf = liftM Paragraph paragraph'
where
paragraph' :: Parser [InlineElement]
paragraph' = do x <- inlineElement cmdTypeOf
Just BlockCommandType
-> do xs <- contents
closeTag tagName
- return $ BlockCmd $ BlockCommand {
+ return $ BlockCmd BlockCommand {
bCmdName = tagName
, bCmdAttributes = tagAttrs
, bCmdContents = xs
(try $ do (tagName, tagAttrs) <- emptyTag
case cmdTypeOf tagName of
Just BlockCommandType
- -> return $ BlockCmd $ BlockCommand {
+ -> return $ BlockCmd BlockCommand {
bCmdName = tagName
, bCmdAttributes = tagAttrs
, bCmdContents = []
nowiki :: Parser InlineElement
-nowiki = try (string "<!nowiki[") >> nowiki' >>= return . Text
+nowiki = liftM Text (try (string "<!nowiki[") >> nowiki')
where
nowiki' :: Parser String
nowiki' = do try (string "]>")
text :: Parser InlineElement
-text = ( char ':'
- >>
- many (noneOf ('\n':inlineSymbols))
- >>=
- return . Text . (':' :)
- -- 定義リストとの關係上、コロンは先頭にしか來れない。
- )
+text = liftM (Text . (':' :)) ( char ':'
+ >>
+ many (noneOf ('\n':inlineSymbols))
+ )
+ -- 定義リストとの關係上、コロンは先頭にしか來られない。
<|>
- ( many1 (noneOf ('\n':inlineSymbols))
- >>=
- return . Text
- )
+ liftM Text (many1 (noneOf ('\n':inlineSymbols)))
<?>
"text"
objLink = do try (string "[[[")
page <- many1 (noneOf "|]")
label <- option Nothing
- (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
+ (liftM Just (char '|' >> many1 (satisfy (/= ']'))))
string "]]]"
return $ ObjectLink page label
<?>
pageLink :: Parser InlineElement
pageLink = do try (string "[[")
page <- option Nothing
- (many1 (noneOf "#|]") >>= return . Just)
+ (liftM Just (many1 (noneOf "#|]")))
fragment <- option Nothing
- (char '#' >> many1 (noneOf "|]") >>= return . Just)
+ (liftM Just (char '#' >> many1 (noneOf "|]")))
label <- option Nothing
- (char '|' >> many1 (satisfy (/= ']')) >>= return . Just)
+ (liftM Just (char '|' >> many1 (satisfy (/= ']'))))
case (page, fragment) of
(Nothing, Nothing) -> pzero
uriStr <- many1 (noneOf " \t]")
skipMany (oneOf " \t")
label <- option Nothing
- (many1 (noneOf "]") >>= return . Just)
+ (liftM Just (many1 (noneOf "]")))
case parseURI uriStr of
Just uri -> char ']' >> return (ExternalLink uri label)
Just InlineCommandType
-> do xs <- contents
closeTag tagName
- return $ InlineCmd $ InlineCommand {
+ return $ InlineCmd InlineCommand {
iCmdName = tagName
, iCmdAttributes = tagAttrs
, iCmdContents = xs
(try $ do (tagName, tagAttrs) <- emptyTag
case cmdTypeOf tagName of
Just InlineCommandType
- -> return $ InlineCmd $ InlineCommand {
+ -> return $ InlineCmd InlineCommand {
iCmdName = tagName
, iCmdAttributes = tagAttrs
, iCmdContents = []
<|>
(comment >> contents)
<|>
- (newline >> contents >>= return . (Text "\n" :))
+ liftM (Text "\n" :) (newline >> contents)
<|>
return []
"comment"
where
skipTillEnd :: Int -> Parser ()
- skipTillEnd level = ( (try (string "<!--") >> skipTillEnd (level + 1))
- <|>
- (try (string "-->") >> case level of
- 1 -> return ()
- n -> skipTillEnd (n - 1))
- <|>
- (anyChar >> skipTillEnd level)
- )
+ skipTillEnd level = (try (string "<!--") >> skipTillEnd (level + 1))
+ <|>
+ (try (string "-->") >> case level of
+ 1 -> return ()
+ n -> skipTillEnd (n - 1))
+ <|>
+ (anyChar >> skipTillEnd level)
blockSymbols :: [Char]
-- end of line
eol :: Parser ()
-eol = ( (newline >> return ())
- <|>
- eof
- )
+eol = (newline >> return ())
+ <|>
+ eof
testData :: [Test]
testData = [ (parseWiki ""
~?=
- (Right []))
+ Right [])
, (parseWiki "\n"
~?=
- (Right []))
+ Right [])
, (parseWiki "=heading="
~?=
- (Right [ Heading 1 "heading" ]))
+ Right [ Heading 1 "heading" ])
, (parseWiki "== heading == \n"
~?=
- (Right [ Heading 2 "heading" ]))
+ Right [ Heading 2 "heading" ])
, (parseWiki "===== hello world =====\n"
~?=
- (Right [ Heading 5 "hello world" ]))
+ Right [ Heading 5 "hello world" ])
, (parseWiki "a =not a heading="
~?=
- (Right [ Paragraph [ Text "a =not a heading=" ]
- ]))
+ Right [ Paragraph [ Text "a =not a heading=" ]
+ ])
, (parseWiki "=h=\n\n=h="
~?=
- (Right [ Heading 1 "h"
- , Heading 1 "h"
- ]))
+ Right [ Heading 1 "h"
+ , Heading 1 "h"
+ ])
, (parseWiki "foo\nbar"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text "\n"
- , Text "bar"
- ]
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text "\n"
+ , Text "bar"
+ ]
+ ])
, (parseWiki "foo\nbar\n\nbaz\n"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text "\n"
- , Text "bar"
- ]
- , Paragraph [ Text "baz"
- ]
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text "\n"
+ , Text "bar"
+ ]
+ , Paragraph [ Text "baz"
+ ]
+ ])
, (parseWiki "foo\n\n\nbar"
~?=
- (Right [ Paragraph [ Text "foo" ]
- , Paragraph [ Text "bar" ]
- ]))
+ Right [ Paragraph [ Text "foo" ]
+ , Paragraph [ Text "bar" ]
+ ])
, (parseWiki "foo\n=h="
~?=
- (Right [ Paragraph [ Text "foo" ]
- , Heading 1 "h"
- ]))
+ Right [ Paragraph [ Text "foo" ]
+ , Heading 1 "h"
+ ])
, (parseWiki "<!-- comment -->"
~?=
- (Right []))
+ Right [])
, (parseWiki "<!-- comment -->foo"
~?=
- (Right [ Paragraph [ Text "foo" ]
- ]))
+ Right [ Paragraph [ Text "foo" ]
+ ])
, (parseWiki "bar<!-- comment -->"
~?=
- (Right [ Paragraph [ Text "bar" ]
- ]))
+ Right [ Paragraph [ Text "bar" ]
+ ])
, (parseWiki "foo<!-- comment -->bar"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text "bar"
- ]
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text "bar"
+ ]
+ ])
, (parseWiki "<!-- comment -->=h="
~?=
- (Right [ Heading 1 "h" ]))
+ Right [ Heading 1 "h" ])
, (parseWiki "=h= <!---->"
~?=
- (Right [ Heading 1 "h" ]))
+ Right [ Heading 1 "h" ])
, (parseWiki "<!-- <!-- nested --> comment -->"
~?=
- (Right []))
+ Right [])
, (parseWiki "[[[Page]]]"
~?=
- (Right [ Paragraph [ ObjectLink "Page" Nothing ] ]))
+ Right [ Paragraph [ ObjectLink "Page" Nothing ] ])
, (parseWiki "[[[Page|foo]]]"
~?=
- (Right [ Paragraph [ ObjectLink "Page" (Just "foo") ] ]))
+ Right [ Paragraph [ ObjectLink "Page" (Just "foo") ] ])
, (parseWiki "[[Page]]"
~?=
- (Right [ Paragraph [ PageLink (Just "Page") Nothing Nothing ]
- ]))
+ Right [ Paragraph [ PageLink (Just "Page") Nothing Nothing ]
+ ])
, (parseWiki "[[Page|Link to \"Page\"]]"
~?=
- (Right [ Paragraph [ PageLink (Just "Page") Nothing (Just "Link to \"Page\"") ]
- ]))
+ Right [ Paragraph [ PageLink (Just "Page") Nothing (Just "Link to \"Page\"") ]
+ ])
, (parseWiki "[[Page#foo]]"
~?=
- (Right [ Paragraph [ PageLink (Just "Page") (Just "foo") Nothing ]
- ]))
+ Right [ Paragraph [ PageLink (Just "Page") (Just "foo") Nothing ]
+ ])
, (parseWiki "[[#foo]]"
~?=
- (Right [ Paragraph [ PageLink Nothing (Just "foo") Nothing ]
- ]))
+ Right [ Paragraph [ PageLink Nothing (Just "foo") Nothing ]
+ ])
, (parseWiki "[[Page#foo|Link to \"Page#foo\"]]"
~?=
- (Right [ Paragraph [ PageLink (Just "Page") (Just "foo") (Just "Link to \"Page#foo\"") ]
- ]))
+ Right [ Paragraph [ PageLink (Just "Page") (Just "foo") (Just "Link to \"Page#foo\"") ]
+ ])
, (parseWiki "foo [[Bar]] baz"
~?=
- (Right [ Paragraph [ Text "foo "
- , PageLink (Just "Bar") Nothing Nothing
- , Text " baz"
- ]
- ]))
+ Right [ Paragraph [ Text "foo "
+ , PageLink (Just "Bar") Nothing Nothing
+ , Text " baz"
+ ]
+ ])
, (parseWiki "[[Foo]]\n[[Bar]]"
~?=
- (Right [ Paragraph [ PageLink (Just "Foo") Nothing Nothing
- , Text "\n"
- , PageLink (Just "Bar") Nothing Nothing
- ]
- ]))
+ Right [ Paragraph [ PageLink (Just "Foo") Nothing Nothing
+ , Text "\n"
+ , PageLink (Just "Bar") Nothing Nothing
+ ]
+ ])
, (parseWiki " foo"
~?=
- (Right [ Preformatted [ Text "foo" ] ]))
+ Right [ Preformatted [ Text "foo" ] ])
, (parseWiki " foo\n bar\n"
~?=
- (Right [ Preformatted [ Text "foo"
- , Text "\n"
- , Text " bar"
- ]
- ]))
+ Right [ Preformatted [ Text "foo"
+ , Text "\n"
+ , Text " bar"
+ ]
+ ])
, (parseWiki "foo\n bar\nbaz"
~?=
- (Right [ Paragraph [ Text "foo" ]
- , Preformatted [ Text "bar" ]
- , Paragraph [ Text "baz" ]
- ]))
+ Right [ Paragraph [ Text "foo" ]
+ , Preformatted [ Text "bar" ]
+ , Paragraph [ Text "baz" ]
+ ])
, (parseWiki "----"
~?=
- (Right [ HorizontalLine ]))
+ Right [ HorizontalLine ])
, (parseWiki "\nfoo\nbar\n----\n"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text "\n"
- , Text "bar"
- ]
- , HorizontalLine
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text "\n"
+ , Text "bar"
+ ]
+ , HorizontalLine
+ ])
, (parseWiki "a----b"
~?=
- (Right [ Paragraph [ Text "a----b" ] ]))
+ Right [ Paragraph [ Text "a----b" ] ])
, (parseWiki "* a"
~?=
- (Right [ List Bullet [[Inline (Text "a")]] ]))
+ Right [ List Bullet [[Inline (Text "a")]] ])
, (parseWiki "* a*"
~?=
- (Right [ List Bullet [[Inline (Text "a*")]] ]))
+ Right [ List Bullet [[Inline (Text "a*")]] ])
, (parseWiki "* a\n* b\n"
~?=
- (Right [ List Bullet [ [Inline (Text "a")]
- , [Inline (Text "b")]
- ]
- ]))
+ Right [ List Bullet [ [Inline (Text "a")]
+ , [Inline (Text "b")]
+ ]
+ ])
, (parseWiki "*a\n*#b\n*#c\n"
~?=
- (Right [ List Bullet [ [ Inline (Text "a")
- , Block (List Numbered [ [Inline (Text "b")]
- , [Inline (Text "c")]
- ])
- ]
- ]
- ]))
+ Right [ List Bullet [ [ Inline (Text "a")
+ , Block (List Numbered [ [Inline (Text "b")]
+ , [Inline (Text "c")]
+ ])
+ ]
+ ]
+ ])
, (parseWiki "*a\n#b"
~?=
- (Right [ List Bullet [ [Inline (Text "a")] ]
- , List Numbered [ [Inline (Text "b")] ]
- ]))
+ Right [ List Bullet [ [Inline (Text "a")] ]
+ , List Numbered [ [Inline (Text "b")] ]
+ ])
, (parseWiki "*a<!-- comment -->"
~?=
- (Right [ List Bullet [ [Inline (Text "a")] ] ]))
+ Right [ List Bullet [ [Inline (Text "a")] ] ])
, (parseWiki "*a<!-- comment -->\n*b"
~?=
- (Right [ List Bullet [ [Inline (Text "a")]
- , [Inline (Text "b")]
- ]
- ]))
+ Right [ List Bullet [ [Inline (Text "a")]
+ , [Inline (Text "b")]
+ ]
+ ])
, (parseWiki "foo:bar"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text ":bar"
- ]
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text ":bar"
+ ]
+ ])
, (parseWiki "; foo: bar"
~?=
- (Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ]))
+ Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ])
, (parseWiki "; foo: bar\n"
~?=
- (Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ]))
+ Right [ DefinitionList [Definition [Text "foo"] [Text "bar"]] ])
, (parseWiki "; foo\n: bar\n; bar\n: baz\n: baz"
~?=
- (Right [ DefinitionList [ Definition [Text "foo"] [ Text "bar" ]
- , Definition [Text "bar"] [ Text "baz"
- , Text "\n"
- , Text "baz" ]
- ]
- ]))
+ Right [ DefinitionList [ Definition [Text "foo"] [ Text "bar" ]
+ , Definition [Text "bar"] [ Text "baz"
+ , Text "\n"
+ , Text "baz" ]
+ ]
+ ])
, (parseWiki "<!nowiki[foo [[bar]] baz]>"
~?=
- (Right [ Paragraph [ Text "foo [[bar]] baz" ] ]))
+ Right [ Paragraph [ Text "foo [[bar]] baz" ] ])
, (parseWiki "<!verbatim[foo [[bar]] baz]>"
~?=
- (Right [ Preformatted [ Text "foo [[bar]] baz" ] ]))
+ Right [ Preformatted [ Text "foo [[bar]] baz" ] ])
, (parseWiki "<!verbatim[\nfoo [[bar]] baz\n]>"
~?=
- (Right [ Preformatted [ Text "foo [[bar]] baz" ] ]))
+ Right [ Preformatted [ Text "foo [[bar]] baz" ] ])
, (parseWiki "foo' bar"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text "'"
- , Text " bar" ]
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text "'"
+ , Text " bar" ]
+ ])
, (parseWiki "''foo''"
~?=
- (Right [ Paragraph [ Italic [Text "foo"] ] ]))
+ Right [ Paragraph [ Italic [Text "foo"] ] ])
, (parseWiki "'''foo'''"
~?=
- (Right [ Paragraph [ Bold [Text "foo"] ] ]))
+ Right [ Paragraph [ Bold [Text "foo"] ] ])
, (parseWiki "foo''''"
~?=
- (Right [ Paragraph [ Text "foo"
- , Text "'"
- ]
- ]))
+ Right [ Paragraph [ Text "foo"
+ , Text "'"
+ ]
+ ])
, (parseWiki "'''''foo'''''"
~?=
- (Right [ Paragraph [ Italic [Bold [Text "foo"]] ] ]))
+ Right [ Paragraph [ Italic [Bold [Text "foo"]] ] ])
, (parseWiki "<br />"
~?=
- (Right [ Paragraph [ InlineCmd (InlineCommand "br" [] []) ] ]))
+ Right [ Paragraph [ InlineCmd (InlineCommand "br" [] []) ] ])
, (parseWiki "<br style=\"clear: both\"/>"
~?=
- (Right [ Paragraph [ InlineCmd (InlineCommand "br" [("style", "clear: both")] []) ] ]))
+ Right [ Paragraph [ InlineCmd (InlineCommand "br" [("style", "clear: both")] []) ] ])
, (parseWiki "<i><b>foo</b></i>"
~?=
- (Right [ Paragraph [ InlineCmd (InlineCommand "i" []
- [ InlineCmd (InlineCommand "b" [] [ Text "foo" ]) ]) ] ]))
+ Right [ Paragraph [ InlineCmd (InlineCommand "i" []
+ [ InlineCmd (InlineCommand "b" [] [ Text "foo" ]) ]) ] ])
, (parseWiki "<i>\nfoo\n<!-- comment -->\nbar</i>"
~?=
- (Right [ Paragraph [ InlineCmd (InlineCommand "i" []
- [ Text "\n"
- , Text "foo"
- , Text "\n"
- , Text "\n"
- , Text "bar"
- ]) ] ]))
+ Right [ Paragraph [ InlineCmd (InlineCommand "i" []
+ [ Text "\n"
+ , Text "foo"
+ , Text "\n"
+ , Text "\n"
+ , Text "bar"
+ ]) ] ])
, (parseWiki "<div>foo</div>"
~?=
- (Right [ BlockCmd (BlockCommand "div" []
- [ Paragraph [Text "foo"] ]) ]))
+ Right [ BlockCmd (BlockCommand "div" []
+ [ Paragraph [Text "foo"] ]) ])
, (parseWiki "<div>\nbar\n</div>"
~?=
- (Right [ BlockCmd (BlockCommand "div" []
- [ Paragraph [Text "bar"] ]) ]))
+ Right [ BlockCmd (BlockCommand "div" []
+ [ Paragraph [Text "bar"] ]) ])
, (parseWiki "<div><!-- comment --></div>"
~?=
- (Right [ BlockCmd (BlockCommand "div" [] []) ]))
+ Right [ BlockCmd (BlockCommand "div" [] []) ])
, (parseWiki "foo<div id=\"bar\"/>"
~?=
- (Right [ Paragraph [Text "foo"]
- , BlockCmd (BlockCommand "div" [("id", "bar")] [])
- ]))
+ Right [ Paragraph [Text "foo"]
+ , BlockCmd (BlockCommand "div" [("id", "bar")] [])
+ ])
, (parseWiki "[http://example.org/]"
~?=
- (Right [ Paragraph [ExternalLink (fromJust $ parseURI "http://example.org/") Nothing] ]))
+ Right [ Paragraph [ExternalLink (fromJust $ parseURI "http://example.org/") Nothing] ])
, (parseWiki "[http://example.org/ example.org]"
~?=
- (Right [ Paragraph [ExternalLink
- (fromJust $ parseURI "http://example.org/")
- (Just "example.org")
- ]
- ]))
+ Right [ Paragraph [ExternalLink
+ (fromJust $ parseURI "http://example.org/")
+ (Just "example.org")
+ ]
+ ])
]