Skip to content

Instantly share code, notes, and snippets.

@HirotoShioi
Created January 31, 2019 07:16
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save HirotoShioi/ddeaccf09b7545f64883019ea4b94c55 to your computer and use it in GitHub Desktop.
Save HirotoShioi/ddeaccf09b7545f64883019ea4b94c55 to your computer and use it in GitHub Desktop.
module Parser.Test where
import RIO hiding (try, (<|>))
import Text.ParserCombinators.Parsec
data Block = List [Block] | ListItem String
deriving Show
-- | Parser for 'BulletPoint'
-- 100% Evil
bulletPointParser :: Maybe Int -> Parser Block
bulletPointParser mNumOfSpaces = do
whenJust mNumOfSpaces $ \numOfSpace ->
replicateM_ numOfSpace space
-- Look ahead and count the number of spaces
numOfSpaces <- length <$> lookAhead (try $ many1 $ oneOf " \t")
blocks <- many1 $ do
_ <- replicateM_ numOfSpaces (oneOf " \t")
let s = fromMaybe 0 mNumOfSpaces
blockParser (Just $ numOfSpaces + s)
return $ List blocks
itemParser :: Parser Block
itemParser = ListItem <$> manyTill anyChar (try endOfLine)
blockParser :: Maybe Int -> Parser Block
blockParser mNumOfSpaces =
try (bulletPointParser mNumOfSpaces)
<|> try itemParser
-- | End of line parser
endOfLine :: Parser ()
endOfLine = void (char '\n') <|> void (string "\r\n") <|> eof
parseList :: String -> Either ParseError [Block]
parseList = parse (manyTill (blockParser Nothing) eof) "List parser"
exampleList :: String
exampleList = unlines
[ " list1"
, " item1"
, " item2"
, " item3"
, " list2"
, " list3"
]
expecting :: [Block]
expecting = [ List
[ ListItem "list1"
, List
[ ListItem "item1"
, ListItem "item2"
, ListItem "item3"
]
, ListItem "list2"
, ListItem "list3"
]
]
-- | Perform some operation on 'Just', given the field inside the 'Just'.
--
-- > whenJust Nothing print == return ()
-- > whenJust (Just 1) print == print 1
whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m ()
whenJust mg f = maybe (pure ()) f mg
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment