<html>
  <head>
    <meta http-equiv="Content-Type" content="text/html; charset=UTF-8">
  </head>
  <body text="#000000" bgcolor="#FFFFFF">
    I'm sorry, the formatting got mangled in my last message, because I
    was using MarkdownHere. I'll try again without converting it to
    HTML.<br>
    <br>
    I'm a fan of `regex-applicative`. It's a combinator library modelled
    on the parsec family but because it parses only regular languages
    rather than context-free ones, it's a bit simpler to use and is a
    better match for some tasks. It uses `OverloadedStrings` to make it
    easier to include literal string matches and provides a non-greedy
    repeating combinator called `few` that avoids having to specify
    exclusive matches. I think it solves this problem quite nicely:<br>
    <br>
    ```haskell<br>
    {-# LANGUAGE OverloadedStrings #-}<br>
    <br>
    import Text.Regex.Applicative<br>
    <br>
    -- This is just <*> with right associativity<br>
    (<&>) :: Applicative f => f (a -> b) -> f a ->
    f b<br>
    (<&>) = (<*>)<br>
    infixr 3 <&><br>
    <br>
    type Item = (String, String)<br>
    <br>
    item :: String -> RE Char ([Item] -> [Item])<br>
    item key = (:) . (,) key <$> few anySym<br>
    <br>
    -- ${year}/${month}/${day} ${hour}:${minute} User ${username} runs
    command ${command}.<br>
    pattern :: RE Char [Item]<br>
    pattern =<br>
        item "year" <* "/" <&> item "month" <* "/"
    <&> item "day" <* " " <&><br>
        item "hour" <* ":" <&> item "minute" <* " User "
    <&><br>
        item "username" <* " runs command " <&> item
    "command" <* "." <&><br>
        pure []<br>
    <br>
    input :: String<br>
    input = "2019/04/17 17:27 User magicloud runs command ls."<br>
    <br>
    output :: Maybe [Item]<br>
    output = match pattern input<br>
    -- Just
[("year","2019"),("month","04"),("day","17"),("hour","17"),("minute","27"),("username","magicloud"),("command","ls")]<br>
    ```<br>
    <br>
    (Also available as a
[gist](<a class="moz-txt-link-freetext" href="https://gist.github.com/neilmayhew/e4fc90b7eaeb7bbcfeb6d6938544ecc9">https://gist.github.com/neilmayhew/e4fc90b7eaeb7bbcfeb6d6938544ecc9</a>).)<br>
    <br>
    Obviously the combinator version is less compact and therefore could
    be considered less readable, but the implementation details could
    probably be tweaked a bit. It would also be relatively easy to write
    a quasi-quoter that turns the original input syntax (with
    `${variable}`) into the equivalent I've shown here.<br>
  </body>
</html>