
Hi All, One of the things I've been working on lately is some ASN.1 stuff.One of the first things I wrote in Haskell was an ASN.1 parser. It only worked for a subset, and I'm revisiting it to make it handle a larger subset. One of the things that gets messy is that in lots of places you can put either a thing or a reference to a thing (i.e. the name of a thing defined elsewhere). For example, consider the production: NamedNumber ::= identifier "(" SignedNumber ")" | identifier "(" DefinedValue ")" If we ignore the second alternative, the natural translation into a Parsec parser would look like: namedNumber = do name <- identifier val <- parens signedNumber return (name, val) Now to handle the second alternative is easy enough: namedNumber = do name <- identifier val <- parens (fmap Left signedNumber <|> fmap Right definedValue) return (name, val) however because names can be used before they are defined the result typegoes from being type NamedNumber = (Name,Integer) to type NamedNumber = (Name,Either Integer Name) Nothing too terrible so far. The messiness comes in when you considerthe number of places that you have to replace a type 't' with (Either t Name). I'd really like to avoid having to do this. If I were using Prolog, I could finesse the problem by introducing afree variable and filling it in when I come across the definition[*]. Logic variable backpatching. :-) So one possibility would be to return a closure: ... return $ \bindings -> (name,resolve val bindings) resolve :: (Either t Name) -> Map Name t -> t or something like that. Then when you get to the end, you apply the bindings and voila, out pops the simple type. I'm not sure this will work quite as well as it sounds. This sounds like a common problem type. Is there a well known solution to this sort of problem? cheers, Tom [*] And then at the end use var/1 to look for undefined names. Urk. Actually, if I were using Prolog in the way most Prolog programmers use it, I wouldn't be thinking about the types. -- Dr Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.

On Wed, Aug 01, 2007 at 03:44:32PM +1000, Thomas Conway wrote:
This sounds like a common problem type. Is there a well known solution to this sort of problem?
Mmm... logic programming? http://citeseer.ist.psu.edu/claessen00typed.html You'll only need the code for logic-variables, and even that can be simplified because your "terms" are non-recursive. (Even in the recursive case, a logic program like a HM typechecker usually only needs ~50 lines of prelude). (If you want an less enlightening answer, Map String (STRef s (Maybe Integer))).. Stefan

On Tue, 2007-07-31 at 23:04 -0700, Stefan O'Rear wrote:
On Wed, Aug 01, 2007 at 03:44:32PM +1000, Thomas Conway wrote:
This sounds like a common problem type. Is there a well known solution to this sort of problem?
Mmm... logic programming?
http://citeseer.ist.psu.edu/claessen00typed.html
You'll only need the code for logic-variables, and even that can be simplified because your "terms" are non-recursive. (Even in the recursive case, a logic program like a HM typechecker usually only needs ~50 lines of prelude).
If someone is interested, I did transcribe and mildly generalize the code from that paper.

Derek Elkins wrote:
On Tue, 2007-07-31 at 23:04 -0700, Stefan O'Rear wrote:
On Wed, Aug 01, 2007 at 03:44:32PM +1000, Thomas Conway wrote:
This sounds like a common problem type. Is there a well known solution to this sort of problem?
Mmm... logic programming?
http://citeseer.ist.psu.edu/claessen00typed.html
You'll only need the code for logic-variables, and even that can be simplified because your "terms" are non-recursive. (Even in the recursive case, a logic program like a HM typechecker usually only needs ~50 lines of prelude).
If someone is interested, I did transcribe and mildly generalize the code from that paper. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Hi Derek, I'd be interested in looking at that -- have you put it online? -- View this message in context: http://www.nabble.com/Backpatching-tf4198168.html#a11945491 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Thomas Conway wrote:
One of the things that gets messy is that in lots of places you can put either a thing or a reference to a thing (i.e. the name of a thing defined elsewhere). For example, consider the production:
NamedNumber ::= identifier "(" SignedNumber ")" | identifier "(" DefinedValue ")"
I like solving this with either a (WriterT Parser) or using the Parsec state to lazily access the final mapping. Here is a working Toy example where 'finalMap' is used during the parsing. Parsec was a bit too strict with the return of 'parseVal' so I had to use a (data Box) to make it lazy:
import Text.ParserCombinators.Parsec
import Data.Maybe import qualified Data.Map as M
data Box a = Box {unBox :: a}
input = unlines $ [ "name(ref)" , "ref=7" ]
data Toy = Toy String Int deriving (Show)
myParse s = toys where result = runParser parser M.empty "Title" s toys = either Left (Right . fst) result
lookupRef r = Box (finalMap M.! r) where finalMap = either undefined snd result
parser = do maybeToyList <- many parseLine defMap <- getState return (catMaybes maybeToyList,defMap)
parseLine = try parseToy <|> parseDef <|> (char '\n' >> return Nothing)
parseToy = do name <- many1 letter val <- between (char '(') (char ')') (try parseVal <|> parseRef) return (Just (Toy name (unBox val)))
parseVal = do s <- many1 digit return (Box (read s))
parseRef = do s <- many1 letter return (lookupRef s)
parseDef = do s <- many1 letter char '=' v <- parseVal defMap <- getState let defMap' = M.insert s (unBox v) defMap setState $! defMap' return Nothing
When I run it in ghci I get:
*Main> myParse input Right [Toy "name" 7]
Cheers, Chris

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"

On 8/2/07, Daniel McAllansmith
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
I'll need to look further, but I'd say this looks to be on the money. In many ways it's isomorphic to the logic variable solution (in Prolog) - it works so long as you don't look at the binding before the symbol table is complete (i.e. at the end of parsing). Neat. Except that the Haskell one does not require evil like var/1 to determine that there are missing bindings. That's pleasing - I knew I walked away from Prolog for a good reason[*]. T. [*] It did take a while though - my first Prolog interpreter was MicroProlog on the Sinclair Spectrum. And that was circa 1980. :-) -- Dr Thomas Conway drtomc@gmail.com Silence is the perfectest herald of joy: I were but little happy, if I could say how much.
participants (6)
-
ChrisK
-
Daniel McAllansmith
-
Derek Elkins
-
Jim Burton
-
Stefan O'Rear
-
Thomas Conway