Skip to content

Instantly share code, notes, and snippets.

@rampion
Created August 28, 2011 04:14
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save rampion/1176235 to your computer and use it in GitHub Desktop.
Save rampion/1176235 to your computer and use it in GitHub Desktop.
module Main where
import Control.Applicative ((<$>))
import Data.List (tails)
import Data.Map as M
import Data.Set as S
import System.Random
type Triplets = M.Map String (S.Set (String, String))
-- for each word, note the following two words
constructTriplets :: String -> Triplets
constructTriplets s = M.fromListWith (S.union) $ [ (x, S.singleton (y,z)) | x:y:z:_ <- tails $ words s ]
-- reconstruct the triplets into all possible linkings
makeSenseOf :: Triplets -> [String]
makeSenseOf m = do
(x, ps) <- M.assocs m
(unwords . (x:)) <$> findNext' x ps m
findNext' :: String -> S.Set (String, String) -> Triplets -> [[String]]
findNext' x ps m = do
p@(y,z) <- S.toList ps
let ps' = S.delete p ps
let m' = if S.null ps'
then M.delete x m
else M.insert x ps' m
([y,z]++) <$> findNext z m'
findNext :: String -> Triplets -> [[String]]
findNext x m = case M.lookup x m of
Nothing -> return []
Just ps -> findNext' x ps m
main :: IO ()
main = do
l <- getLine
let rs = makeSenseOf $ constructTriplets l
-- choose an arbitrary response from the list of all possible responses
r <- (rs!!) <$> getStdRandom (randomR (0, length rs - 1))
putStrLn r
main
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment