[Haskell-cafe] How to improve the running time of my algorithm

Dominik Bollmann dominikbollmann at gmail.com
Sun Jan 14 20:14:02 UTC 2018


Hello Haskell-Cafe,

While playing with dynamic programming problems, I've been trying to
solve the "Abbreviation" problem found on hackerrank.com at
https://www.hackerrank.com/challenges/abbr/problem.

Briefly, this problem asks to decide whether a source string s can be
abbreviated into a target string t by capitalizing some of the
characters in s and deleting its afterwards remaining lowercase
characters. For example, the string s = "aBbdD" can be abbreviated as
target t = "BBD", but target t' = "XYZZ" is not an abbreviation for
source s' = "xyz".

My solution to this problem is the following memoization-based
function `isAbbreviation`:


```
import Control.Monad
import Control.Monad.State
import Data.Char
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe
import Data.String
import Data.Text (Text)
import qualified Data.Text as Text
import System.IO

type Store = Map (Text, Text) Bool

isAbbrMemo :: Text -> Text -> State Store Bool
isAbbrMemo s t
  | Text.null t = extend s t $ return (Text.all isLower s)
  | Text.null s = extend s t $ return False
  | otherwise   =
      let (a, as) = fromJust $ Text.uncons s
          (b, bs) = fromJust $ Text.uncons t
      in extend s t $ matches a as b bs
  where
    matches a as b bs
      | isLower a && toUpper a /= b = isAbbrMemo as (b `Text.cons` bs)
      | isLower a && toUpper a == b = (||) <$> isAbbrMemo as bs
                                           <*> isAbbrMemo as (b `Text.cons` bs)
      | isUpper a && a /= b         = return False
      | isUpper a && a == b         = isAbbrMemo as bs

extend :: Text -> Text -> State Store Bool -> State Store Bool
extend s t m = do
  st <- get
  case Map.lookup (s,t) st of
    Just v  -> return v
    Nothing -> do
      v <- m
      modify $ Map.insert (s,t) v
      return v

isAbbreviation :: Text -> Text -> Bool
isAbbreviation s t = evalState (isAbbrMemo s t) Map.empty

main :: IO ()
main = do
  queries <- readQueries stdin
  let answers = map yesNo $ map (uncurry isAbbreviation) queries
  forM_ answers putStrLn

yesNo :: Bool -> String
yesNo True  = "YES"
yesNo False = "NO"

readQueries :: IsString a => Handle -> IO [(a, a)]
readQueries h = do
  numQueries <- read <$> hGetLine h :: IO Int
  forM [1..numQueries] $ \_qid -> do
    s <- hGetLine h
    t <- hGetLine h
    return (fromString s, fromString t)
```

However, running `isAbbreviation` on Hackerrank's input #13 still
takes around 38 seconds on my machine and is therefore too slow to be an
accepted solution. The input of question is attached as a text file.

My question is therefore: Where could I further improve the running time
of the function `isAbbreviation`? Is there any low-hanging fruit to
improve upon? Or is my dynamic-programming based approach somehow
flawed in general? (in which I should rather rethink the problem?)

Any observations, remarks, and improvements on the above code snippet
are greatly appreciated :-)

Thanks, Dominik.

-------------- next part --------------
An embedded and charset-unspecified text was scrubbed...
Name: 13.input
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20180114/3453bef0/attachment.ksh>


More information about the Haskell-Cafe mailing list