3

これは、 InterviewStreetのString Similarityの課題を解決するための最善の試みです。

import Control.Monad
import Data.Text as T
import qualified Data.Text.IO as TIO


sumSimilarities s = (T.length s) + (sum $ Prelude.map (similarity s) (Prelude.tail $ tails s))

similarity :: Text -> Text -> Int
similarity a b = case commonPrefixes a b of
                     Just (x,_,_) -> T.length x
                     Nothing -> 0

main = do
    cases <- fmap read getLine
    inputs <- replicateM cases TIO.getLine
    forM_ inputs $ print . sumSimilarities

テストケースの 7/10 しかパスしません。テスト ケース 7、8、および 9 は、割り当てられた実行時間を超過したため失敗しました。

私はこれが実際に Haskell で解決できることを検証しようとしているところと、最適化された Haskell プログラムがどのように見えるかを探しているところです。

ありがとう!タイラー

4

1 に答える 1

5

user5402のように、同等の(同等の特定の値の)Cプログラムが制限時間内に終了するのか、それともタイムアウトするのか知りたいです。もしそうなら、ByteStringsを使用した同等のプログラムが時間内に終了できるかどうかを確認するのは興味深いでしょう。ByteString-s自体が。よりも高速であるというわけではありませんが、入力をwhileTextの内部表現に変換する必要があるため、違いが生じる可能性があります。テストマシンに32ビットGHCがある場合、sが高速になる可能性があるもう1つの考えられる理由は、そのテキストです。TextByteStringByteStringのフュージョンは、少なくとも、完全な利益を得るために32ビットアーキテクチャで一般的に利用可能なレジスタよりも多くのレジスタを必要としていました[昔、text-0.5からtext-0.7の時代、私の32ビットボックスでは、バイト文字列はかなり高速ですが、それが新しいテキストバージョンにも当てはまるかどうかはわかりません]。

さて、user5402はナイーブアルゴリズムがCで十分に高速であることを確認したので、先に進んで、 ByteStringsを使用してナイーブアルゴリズムの実装を作成しました。

{-# LANGUAGE BangPatterns #-}
module Main (main) where

import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Unsafe as U
import Control.Monad
import Data.Word

main :: IO ()
main = do
    cl <- C.getLine
    case C.readInt cl of
      Just (cases,_) -> replicateM_ cases (C.getLine >>= print . similarity)
      Nothing -> return ()

-- Just to keep the condition readable.
(?) :: B.ByteString -> Int -> Word8
(?) = U.unsafeIndex

similarity :: B.ByteString -> Int
similarity bs
    | len == 0  = 0
    | otherwise = go len 1
      where
        !len = B.length bs
        go !acc i
            | i < len   = go (acc + prf 0 i) (i+1)
            | otherwise = acc
        prf !k j
            | j < len && bs ? k == bs ? j   = prf (k+1) (j+1)
            | otherwise = k

いくつかの悪いケースでそれをOPのTextバージョンと比較しました。私の箱では、それはバージョンより4倍以上速いTextので、それが十分に速いかどうかは興味深いでしょう(Cバージョンはさらに4.5倍速いので、そうではないかもしれません)。

ただし、二次最悪の場合の動作を行うナイーブアルゴリズムを使用しているため、制限時間を超えている可能性が高いと思います。おそらく、ナイーブアルゴリズムの最悪のケースを呼び起こすテストケースがあります。

したがって、解決策は、より適切にスケーリングし、最適に線形になるアルゴリズムを使用することです。文字列の類似性を計算するための1つの線形アルゴリズムは、Zアルゴリズムです。

アイデアは単純です(ただし、ほとんどの優れたアイデアと同様に、簡単に作成することはできません)。文字列のプレフィックスでもある(空でない)サブストリングをprefix-substringと呼びましょう。再計算を回避するために、アルゴリズムは、現在考慮されているインデックスの前から始まり、最も右に伸びるプレフィックスサブストリングのウィンドウを使用します(最初は、ウィンドウは空です)。

使用される変数とアルゴリズムの不変量:

  • i、検討中のインデックスは、1から始まり(0ベースのインデックスの場合、文字列全体は考慮されません)、次のように増分されます。length - 1
  • leftおよびright、prefix-substringウィンドウの最初と最後のインデックス。不変量:
    1. left < i、、またはleft <= right < length(S)、、_left > 0right < 1
    2. の場合left > 0S[left .. right]はとの最大の共通プレフィックスでSありS[left .. ]
    3. 1 <= j < iおよびS[j .. k]がの接頭辞である場合Sk <= right
  • 配列Z、invariant:for 1 <= k < iZ[k]には、との最長の共通プレフィックスの長さが含まれS[k .. ]ますS

アルゴリズム:

  1. を設定i = 1left = right = 0(任意の値を使用できます)、すべてのインデックスleft <= right < 1に設定します。Z[j] = 01 <= j < length(S)
  2. の場合i == length(S)、停止します。
  3. の場合、との最長の共通プレフィックスのi > right長さを見つけて、に格納します。前よりも右に伸びるウィンドウが見つかった場合は、設定して、それ以外の場合は変更しないでください。インクリメントして2に進みます。lSS[i .. ]Z[i]l > 0left = iright = i+l-1i
  4. ここleft < i <= rightで、部分文字列S[i .. right]は既知です-はのS[left .. right]プレフィックスであるSため、はに等しくなりS[i-left .. right-left]ます。

    Sここで、インデックスで始まる部分文字列を持つの最長の共通プレフィックスについて考えてみますi - left。その長さはZ[i-left]、したがってS[k] = S[i-left + k]0 <= k < Z[i-left]および
    S[Z[i-left]] ≠ S[i-left+Z[i-left]]です。さて、もし、ならZ[i-left] <= right-i、それi + Z[i-left]は既知のウィンドウの中にあるので、

    S[i + Z[i-left]] = S[i-left + Z[i-left]] ≠ S[Z[i-left]]
    S[i + k]         = S[i-left + k]         = S[k]   for 0 <= k < Z[i-left]
    

    そして、との最長の共通接頭辞の長さが長さであることがSわかりS[i .. ]ますZ[i-left]。次に、を設定Z[i] = Z[i-left]し、インクリメントiして、2に進みます。

    それ以外の場合、S[i .. right]はの接頭辞でSあり、それがどこまで拡張されているかを確認し、インデックスright+1との文字の比較を開始しますright+1 - i。長さを。としますl。、、、インクリメントを設定Z[i] = lし、2に進みます。left = iright = i + l - 1i

ウィンドウが左に移動することはなく、比較は常にウィンドウの終了後に開始されるため、文字列内の各文字は、文字列内の前の文字と最大1回正常に比較され、開始インデックスごとに最大1つの失敗があります。したがって、アルゴリズムは線形です。

コード(ByteString習慣から使用して、簡単に移植できるはずですText):

{-# LANGUAGE BangPatterns #-}
module Main (main) where

import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Unsafe as U
import Data.Array.ST
import Data.Array.Base
import Control.Monad.ST
import Control.Monad
import Data.Word

main :: IO ()
main = do
    cl <- C.getLine
    case C.readInt cl of
      Just (cases,_) -> replicateM_ cases (C.getLine >>= print . similarity)
      Nothing -> return ()

-- Just to keep the condition readable.
(?) :: B.ByteString -> Int -> Word8
(?) = U.unsafeIndex

-- Calculate the similarity of a string using the Z-algorithm
similarity :: B.ByteString -> Int
similarity bs
    | len == 0  = 0
    | otherwise = runST getSim
      where
        !len = B.length bs
        getSim = do
            za <- newArray (0,len-1) 0 :: ST s (STUArray s Int Int)
            -- The common prefix of the string with itself is entire string.
            unsafeWrite za 0 len
            let -- Find the length of the common prefix.
                go !k j
                    | j < len && (bs ? j == bs ? k) = go (k+1) (j+1)
                    | otherwise = return k
                -- The window with indices in [left .. right] is the prefix-substring
                -- starting before i that extends farthest.
                loop !left !right i
                    | i >= len  = count 0 0 -- when done, sum
                    | i > right = do
                        -- We're outside the window, simply
                        -- find the length of the common prefix
                        -- and store it in the Z-array.
                        w <- go 0 i
                        unsafeWrite za i w
                        if w > 0
                          -- We got a non-empty common prefix and a new window.
                          then loop i (i+w-1) (i+1)
                          -- No new window, same procedure at next index.
                          else loop left right (i+1)
                    | otherwise = do
                        -- We're inside the window, so the substring starting at
                        -- (i - left) has a common prefix with the substring
                        -- starting at i of length at least (right - i + 1)
                        -- (since the [left .. right] window is a prefix of bs).
                        -- But we already know how long the common prefix
                        -- starting at (i - left) is.
                        z <- unsafeRead za (i-left)
                        let !s = right-i+1 -- length of known prefix starting at i
                        if z < s
                          -- If the common prefix of the substring starting at
                          -- (i - left) is shorter than the rest of the window,
                          -- the common prefix of the substring starting at i
                          -- is the same. Store it and move on with the same window.
                          then do
                              unsafeWrite za i z
                              loop left right (i+1)
                          else do
                              -- Otherwise, find out how far the common prefix
                              -- extends, starting at (right + 1) == s + i.
                              w <- go s (s+i)
                              unsafeWrite za i w
                              loop i (i+w-1) (i+1)
                count !acc i
                    | i == len  = return acc
                    | otherwise = do
                        n <- unsafeRead za i
                        count (acc+n) (i+1)
            loop 0 0 1
于 2012-09-03T00:20:42.470 に答える