aydarbiktimirov

Untitled

Apr 13th, 2014
207
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
  1. -- Rhyme.hs
  2. module Main where
  3.  
  4.     import Data.Char
  5.     import Data.List
  6.     import Data.Array
  7.     import Data.Function
  8.     import Data.List.Split
  9.     import Data.String.Utils
  10.  
  11.     import System.IO
  12.  
  13.     import BestMatching
  14.  
  15.     testInput = "Боже! думает бедняк,\nБедный Ваня еле дышит,\nВесь в поту, от страха бледный,\nВ темноте пред ним собака\n(Вы представьте Вани злость!)\nВаня стал; - шагнуть не может.\nГоре! малый я не сильный;\nЕсли сам земли могильной\nКрасногубый вурдалак.\nКто-то кость, ворча, грызёт.\nНа могиле гложет кость.\nПо могилам; вдруг он слышит, -\nРаз он позднею порой,\nСпотыкаясь, чуть бредёт\nСъест упырь меня совсем,\nТрусоват был Ваня бедный:\nЧрез кладбище шёл домой.\nЧто же? вместо вурдалака -\nЭто, верно, кости гложет\nЯ с молитвою не съем."
  16.     testInputLines = splitOn "\n" testInput
  17.  
  18.     editDistance xs ys = table ! (m, n)
  19.         where
  20.             (m, n) = (length xs, length ys)
  21.             x = array (1, m) (zip [1..] xs)
  22.             y = array (1, n) (zip [1..] ys)
  23.  
  24.             table = array bnds [(ij, dist ij) | ij <- range bnds]
  25.             bnds = ((0, 0), (m, n))
  26.  
  27.             dist (0, j) = j
  28.             dist (i, 0) = i
  29.             dist (i, j) = minimum [table ! (i - 1, j) + 1, table ! (i, j - 1) + 1,
  30.                 if x ! i == y ! j then table ! (i - 1, j - 1) else 1 + table ! (i - 1, j - 1)]
  31.  
  32.     transcription = transcription' . (' ':) . filter (`elem` ' ':'\n':'ё':['а'..'я']) . map toLower
  33.         where
  34.             rules = [
  35.                 ("ьё", "'"), ("ье", "'jэ"), ("ья", "'"), ("ью", "'jу"), ("ъё", "jо"), ("ъе", "jэ"), ("ъя", "jа"), (" ю", "jу"), (" ё", "jо"), (" е", "jэ"),
  36.                 (" я", "jа"), (" ю", "jу"), ("ё", "'о"), ("е", "'э"), ("я", "'а"), ("ю", "'у"), ("й", "j"), ("ъ", ""), ("ь", "'"), ("жи", "жы"), ("ши", "шы")
  37.                 ]
  38.             transcription' s = foldl (\ s (src, dst) -> replace src dst s) s rules
  39.  
  40.     syllableCount = length . filter (`elem` "ёуеыаоэяию") . map toLower
  41.  
  42.     groupBySyllableCount = map (map fst) . groupBy ((==) `on` snd) . sortBy (compare `on` snd) . map (\ s -> (s, syllableCount s))
  43.  
  44.     transcriptionEndingLength = 5
  45.  
  46.     getRhymablePart = take transcriptionEndingLength . filter (`notElem` " ") . reverse . transcription
  47.    
  48.     orderByRhyme = filter (\ (s1, s2) -> s1 < s2) . rhymeMatcher
  49.         where
  50.             rhymeMatcher lines = findBestMatching (\ s1 s2 -> if s1 == s2 then 1000 else (editDistance `on` getRhymablePart) s1 s2) lines lines
  51.  
  52.     solve = concatGroups [] . reorder . map process . splitOn "\n"
  53.         where
  54.             process line = (line, getRhymablePart line, syllableCount line)
  55.             groupLines = map (map (\ (x, _, _) -> x)) . sortBy (compare `on` length) . groupBy (\ (_, _, x1) (_, _, x2) -> x1 == x2) . sortBy (\ (_, _, x1) (_, _, x2) -> compare x2 x1)
  56.             reorder = map reorderGroup . map (map reorderRhyme) . map orderByRhyme . groupLines
  57.             reorderRhyme = id -- not implemented
  58.             reorderGroup = id -- not implemented
  59.             concatGroups acc [] = acc
  60.             concatGroups acc (group:[]) = acc ++ (group >>= (\ (a, b) -> [a, b]))
  61.             concatGroups acc (group1:group2:rest) = concatGroups (acc ++ (zip group1 group2 >>= (\ ((a, b), (c, d)) -> [a, c, b, d]))) rest
  62.  
  63.     main =
  64.         hSetEncoding stdin utf8 >> hSetEncoding stdout utf8 >> getContents >>= mapM putStrLn . solve
  65.  
  66. -- BestMatching.hs
  67. module BestMatching (findBestMatching) where
  68.  
  69.     data NetworkEdge = NetworkEdge { from :: Int, to :: Int, cost :: Int, capacity :: Int, flow :: Int }
  70.         deriving (Show)
  71.  
  72.     infinity = 100000
  73.  
  74.     initNetwork distance xs ys partSize source sink part1Offset part2Offset =
  75.         [0..partSize - 1] >>= (\ v -> [NetworkEdge source (part1Offset + v) 0 1 0, NetworkEdge (part2Offset + v) sink 0 1 0]
  76.             ++ [NetworkEdge (part1Offset + v) (part2Offset + v') (distance (xs !! v) (ys !! v')) 1 0 | v' <- [0..partSize - 1]])
  77.             >>= (\ e@(NetworkEdge x y d _ _) -> [e, NetworkEdge y x (-d) 0 0])
  78.  
  79.     maxExtraFlowOnPath result path i network
  80.         | path !! i == -1 = result
  81.         | otherwise = maxExtraFlowOnPath (min result $ capacity edge - flow edge) path (from edge) network
  82.             where edge = network !! (path !! i)
  83.  
  84.     addFlowOnPath extraFlow path i network
  85.         | path !! i == -1 = network
  86.         | (path !! i) `mod` 2 == 0 =
  87.             let (x, y:y':ys) = splitAt (path !! i) network in
  88.             addFlowOnPath extraFlow path (from y) $ x ++ ((y { flow = flow y + extraFlow }):(y' { flow = flow y' - extraFlow }):ys)
  89.         | otherwise =
  90.             let (x, y':y:ys) = splitAt (path !! i - 1) network in
  91.             addFlowOnPath extraFlow path (from y) $ x ++ (y' { flow = flow y' - extraFlow }):((y { flow = flow y + extraFlow }):ys)
  92.  
  93.     addExtraFlowOnPath path i network = addFlowOnPath (maxExtraFlowOnPath infinity path i network) path i network
  94.  
  95.     findShortestPathInResidualNetwork networkSize = findShortestPathInResidualNetwork' networkSize ([-1,-1..], 0:[infinity, infinity..]) networkSize
  96.         where
  97.             findShortestPathInResidualNetwork' 0 acc _ _ to _ = ((fst acc) !! to /= -1, take networkSize $ fst acc)
  98.             findShortestPathInResidualNetwork' iteration acc networkSize from to network =
  99.                 findShortestPathInResidualNetwork' (iteration - 1) (foldl relax acc $ zip [0..] network) networkSize from to network
  100.             relax acc@(result, distances) (i, edge)
  101.                 | flow edge >= capacity edge || distances !! (from edge) >= infinity || distances !! (to edge) <= (distances !! (from edge)) + cost edge = acc
  102.                 | otherwise =
  103.                     let (resPrev, res:resRest) = splitAt (to edge) result in
  104.                     let (distPrev, dist:distRest) = splitAt (to edge) distances in
  105.                     (resPrev ++ (i:resRest), distPrev ++ ((distances !! (from edge)) + (cost edge):distRest))
  106.  
  107.     findBestMatching distance xs ys
  108.         | length xs /= length ys = error "Lengths should be equal"
  109.         | otherwise = restoreAnswer $ addFlowWhilePossible True [-1, -1..] $ initNetwork distance xs ys partSize source sink part1Offset part2Offset
  110.             where
  111.                 partSize = length xs
  112.                 source = 0
  113.                 sink = 1 + partSize * 2
  114.                 part1Offset = 1
  115.                 part2Offset = 1 + partSize
  116.                 networkSize = 2 + partSize * 2
  117.                 addFlowWhilePossible False _ network = network
  118.                 addFlowWhilePossible True path network =
  119.                     let (hasPath, nextPath) = findShortestPathInResidualNetwork networkSize source sink network in
  120.                     addFlowWhilePossible hasPath nextPath $ addExtraFlowOnPath path sink network
  121.                 restoreAnswer network = filter (\ (NetworkEdge f t _ _ fl) -> fl == 1 && f >= part1Offset && f < part1Offset + partSize && t >= part2Offset && t < part2Offset + partSize && f < t) network
  122.                     >>= (\ (NetworkEdge f t _ _ _) -> [(xs !! (f - part1Offset), ys !! (t - part2Offset))])
Advertisement
Add Comment
Please, Sign In to add comment