[Haskell] A few newbie questions about tracing/debugging and order
of execution
Hunter Kelly
retnuh at gmail.com
Wed Dec 28 06:10:10 EST 2005
Heya, I decided to play around with Haskell and see what it's like.
I used a small problem to explore it. Basically, given two words,
find the least number of 1 letter changes that will go from one
word to the other (e.g. for "fig" and "dog" either fig -> fog -> dog or
fig -> dig -> dog).
I came up with a solution, but I have to say it was quite difficult to
get any debugging information, and when I did, the result was fairly
surprising!
Here's the out put I got:
dagger:~/stuff$ ./figt /usr/share/dic/twords fig dog
Word: dog
visited:
["bit","bin","bid","bib","bug","bog","beg","bag","fix","fit","fir","fin","fie","fib","fog","fag","wig","rig","pig","jig","gig","dig","big","fig"]
Word: dig
visited: ["big","fig"]
Word: fig
visited: []
fig -> dig -> dog
The first thing I found surprising was that the debug output comes in
the "reverse" order - I would have expected it to be the output for
fig, then dig, then dog.
Secondly, I'm not entirely sure why I only got output for the
statements along the "solution" path. If I try a combination that has
no solution, I get no output at all.
I got the program working, and I'm quite intrigued, but I figure it's
probably important to figure out why the above things happen...
I'm using GHC 6.4.1, but I get the same thing if I use runhugs.
Thanks!
--------- figt.hs --------------
import System
import System.IO
import Data.Set
import Debug.Trace
type Word = String
data Path = None | Path Word Path
instance Show Path where
showsPrec _ path = showsPath path
where
showsPath :: Path -> ShowS
showsPath None = ("<None>"++)
showsPath (Path w None) = (w ++)
showsPath (Path w p) = (showsPath p) . ((" -> " ++ w)++)
findPath :: Word -> Word -> Set String -> Path
findPath orig target allWords =
let gen = singleton orig
in iteratePath [(Path orig None)] gen []
where
iteratePath :: [Path] -> Set String -> [String] -> Path
iteratePath [] _ _ = None
iteratePath (None: _) _ _ = None
iteratePath (fullPath@(Path w _):remain) generated visited =
let
allPossibilities = findPossibleWords w
existant = Prelude.filter (\p -> member p allWords)
allPossibilities
new = Prelude.filter (\e -> not (member e generated)) existant
marked = foldl (\x y -> insert y x) generated new
thingum = trace ("Word: " ++ w ++ "\n\tvisited: " ++
(show visited) ++ "\n") fullPath
todo = remain ++ Prelude.map (\u -> (Path u thingum)) new
in if target == w
then thingum
else if length todo > 0 then iteratePath todo marked (w:visited)
else None
findPossibleWords :: String -> [String]
findPossibleWords word = concatMap enumChars (splits)
where enumChars (prefix, _:cs) = Prelude.map (\c -> prefix ++ [c]
++ cs) ['a'..'z']
splits = Prelude.map (\x -> splitAt x word) [0..((length word) -1)]
findAllWordsSizeN :: String -> Int -> Set String
findAllWordsSizeN content wordLength =
fromDistinctAscList (Prelude.filter (\x -> wordLength == (length
x)) (lines content))
main :: IO ()
main = do [wordsFile, orig, target] <- getArgs
contents <- readFile wordsFile
allWordsSizeN <- (return (findAllWordsSizeN contents (length orig)))
putStrLn (show (findPath orig target allWordsSizeN ))
More information about the Haskell
mailing list