[Haskell-cafe] Backpatching
Daniel McAllansmith
dm.maillists at gmail.com
Wed Aug 1 16:51:26 EDT 2007
On Wednesday 01 August 2007 17:44, Thomas Conway wrote:
> This sounds like a common problem type. Is there a well known solution
> to this sort of problem?
Have you looked into Tying the Knot?
http://www.haskell.org/haskellwiki/Tying_the_Knot
A simple example:
module Knot where
import Data.Char
import Data.Maybe
type Input = String
type Output = [(Char, Int)]
type Resolver = (Char -> Int)
resolvingError c = error ("Couldn't resolve: " ++ [c])
parseInput :: Resolver -> Input -> Output
parseInput _ [] = []
parseInput resolve (c:cs) | isUpper c = ((c, fromEnum c) : parseInput f cs)
| otherwise = ((c, resolve c) : parseInput f cs)
makeResolver :: Output -> Resolver
makeResolver o c = fromMaybe (resolvingError c) (lookup (toUpper c) o)
foo :: Input -> Output
foo i = let o = parseInput (makeResolver o) i in o
testGood = foo "CaBcbA"
testBad = foo "CaBcb"
More information about the Haskell-Cafe
mailing list