<div dir="ltr">Hello Dominik,<div><br></div><div>I'm not sure what exactly your algorithm is, but one thing that stands out to me is the use of (Text,Text) index pairs instead of something more efficient.</div><div><br></div><div>Here is an algorithm that I wrote which (without any optimization tricks) seems to be fast and correct: <a href="https://pastebin.com/rDxUFbt3">https://pastebin.com/rDxUFbt3</a></div><div><br></div><div>Dynamic Programming in Haskell is a pleasure due to laziness, especially if the choice variables are dense in the integers. </div><div><br></div><div>In this case, I have a Vector (Vector Bool), where the outer vector is indexed by position into the lowercase string and the inner vector is indexed by position into the uppercase string. vec ! i ! j is True iff there is a solution to the problem for the first i characters in the lowercase string and the first j characters in the uppercase string. Because Vectors are lazy (unless you use one of the packed varieties) you can assign each vector element the value corresponding to its solution - before you even know what the solution is!</div><div><br></div><div>To get the final solution, you simply look at the vector element corresponding to using the entirety of both strings. This will force evaluation of the last cell, which will force the evaluation of some other cells, which will force the evaluation of some other cells, etc. etc. If a cell is ever accessed more than once, it still only gets computed one time, so we have memoization.</div><div><br></div><div>This form is a little weird and took me a while to get the first time I saw it, but I was delighted when I fully understood it.</div><div><br></div><div>If your choice variables are not dense in the integers, you can do the same approach using a memo-trie, although there is a constant factor performance loss compared to vectors.</div><div><br></div><div>--Will</div></div><div class="gmail_extra"><br><div class="gmail_quote">On Sun, Jan 14, 2018 at 3:14 PM, Dominik Bollmann <span dir="ltr"><<a href="mailto:dominikbollmann@gmail.com" target="_blank">dominikbollmann@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><br>
Hello Haskell-Cafe,<br>
<br>
While playing with dynamic programming problems, I've been trying to<br>
solve the "Abbreviation" problem found on <a href="http://hackerrank.com" rel="noreferrer" target="_blank">hackerrank.com</a> at<br>
<a href="https://www.hackerrank.com/challenges/abbr/problem" rel="noreferrer" target="_blank">https://www.hackerrank.com/<wbr>challenges/abbr/problem</a>.<br>
<br>
Briefly, this problem asks to decide whether a source string s can be<br>
abbreviated into a target string t by capitalizing some of the<br>
characters in s and deleting its afterwards remaining lowercase<br>
characters. For example, the string s = "aBbdD" can be abbreviated as<br>
target t = "BBD", but target t' = "XYZZ" is not an abbreviation for<br>
source s' = "xyz".<br>
<br>
My solution to this problem is the following memoization-based<br>
function `isAbbreviation`:<br>
<br>
<br>
```<br>
import Control.Monad<br>
import Control.Monad.State<br>
import Data.Char<br>
import Data.Map.Strict (Map)<br>
import qualified Data.Map.Strict as Map<br>
import Data.Maybe<br>
import Data.String<br>
import Data.Text (Text)<br>
import qualified Data.Text as Text<br>
import System.IO<br>
<br>
type Store = Map (Text, Text) Bool<br>
<br>
isAbbrMemo :: Text -> Text -> State Store Bool<br>
isAbbrMemo s t<br>
  | Text.null t = extend s t $ return (Text.all isLower s)<br>
  | Text.null s = extend s t $ return False<br>
  | otherwise   =<br>
      let (a, as) = fromJust $ Text.uncons s<br>
          (b, bs) = fromJust $ Text.uncons t<br>
      in extend s t $ matches a as b bs<br>
  where<br>
    matches a as b bs<br>
      | isLower a && toUpper a /= b = isAbbrMemo as (b `Text.cons` bs)<br>
      | isLower a && toUpper a == b = (||) <$> isAbbrMemo as bs<br>
                                           <*> isAbbrMemo as (b `Text.cons` bs)<br>
      | isUpper a && a /= b         = return False<br>
      | isUpper a && a == b         = isAbbrMemo as bs<br>
<br>
extend :: Text -> Text -> State Store Bool -> State Store Bool<br>
extend s t m = do<br>
  st <- get<br>
  case Map.lookup (s,t) st of<br>
    Just v  -> return v<br>
    Nothing -> do<br>
      v <- m<br>
      modify $ Map.insert (s,t) v<br>
      return v<br>
<br>
isAbbreviation :: Text -> Text -> Bool<br>
isAbbreviation s t = evalState (isAbbrMemo s t) Map.empty<br>
<br>
main :: IO ()<br>
main = do<br>
  queries <- readQueries stdin<br>
  let answers = map yesNo $ map (uncurry isAbbreviation) queries<br>
  forM_ answers putStrLn<br>
<br>
yesNo :: Bool -> String<br>
yesNo True  = "YES"<br>
yesNo False = "NO"<br>
<br>
readQueries :: IsString a => Handle -> IO [(a, a)]<br>
readQueries h = do<br>
  numQueries <- read <$> hGetLine h :: IO Int<br>
  forM [1..numQueries] $ \_qid -> do<br>
    s <- hGetLine h<br>
    t <- hGetLine h<br>
    return (fromString s, fromString t)<br>
```<br>
<br>
However, running `isAbbreviation` on Hackerrank's input #13 still<br>
takes around 38 seconds on my machine and is therefore too slow to be an<br>
accepted solution. The input of question is attached as a text file.<br>
<br>
My question is therefore: Where could I further improve the running time<br>
of the function `isAbbreviation`? Is there any low-hanging fruit to<br>
improve upon? Or is my dynamic-programming based approach somehow<br>
flawed in general? (in which I should rather rethink the problem?)<br>
<br>
Any observations, remarks, and improvements on the above code snippet<br>
are greatly appreciated :-)<br>
<br>
Thanks, Dominik.<br>
<br>
<br>______________________________<wbr>_________________<br>
Haskell-Cafe mailing list<br>
To (un)subscribe, modify options or view archives go to:<br>
<a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-<wbr>bin/mailman/listinfo/haskell-<wbr>cafe</a><br>
Only members subscribed via the mailman list are allowed to post.<br></blockquote></div><br></div>