
Dear cafe, I’m working on a project that reads logic puzzle descriptions from yaml files and renders them using the Diagrams framework (https://github.com/robx/puzzle-draw), and am quite unsure what’s a good way of stringing things together. It’s a bit hard to even express the problem… I’ve tried to break it down with limited success, to the following task: 1. Read YAML data like type: “three” x: 3 y: [3, 4, 5] Type is from a fixed (long) list of strings. This type determines the format of the fields x and y (x is required, y is optional). 2. Do something type-specific to produce output based on the parsed data. Two options, one that depends on the x field only, the second can also consult the y field. My problem is how I should deal with these intermediate types that vary based on the input. My current approach below has parsing and printing functions, and then one big function that strings the matching parsers and printers together. I’ve also thought about using one big sum type, or type classes (Parseable, Printable, but doesn’t really seem to help). So far, all of it has felt a bit awkward. Any suggestions for how to attack this much appreciated. Cheers Rob {-# LANGUAGE OverloadedStrings #-} import Control.Applicative import Data.Yaml type Parsers a b = (Value -> Parser a, Value -> Parser b) parse1 :: Parsers Int Double parse1 = (parseJSON, parseJSON) parse2 :: Parsers String Char parse2 = (parseJSON, parseJSON) -- parse3 :: Parsers Int [Int] -- ... lots more of these type Printers a b = (a -> IO (), a -> b -> IO ()) print1 :: Printers Int Double print1 = (print . show, \x y -> print (show y ++ "..." ++ show x)) print2 :: Printers String Char print2 = (const $ print "hello", \x y -> print (show y)) type Composed = (Value -> Parser (IO ()), Value -> Value -> Parser (IO ())) compose :: Parsers a b -> Printers a b -> Composed compose (pp, ps) (rp, rs) = (\v -> rp <$> pp v, \v w -> rs <$> pp v <*> ps w) composeType :: String -> Composed composeType t = case t of "one" -> compose parse1 print1 "two" -> compose parse2 print2 _ -> (f, const f) where f = fail $ "unknown type: " ++ t parseXY :: (String -> Value -> Value -> Parser a) -> Value -> Parser a parseXY f (Object v) = do t <- v .: "type" x <- v .: "x" y <- v .: "y" f t x y parseX :: (String -> Value -> Parser a) -> Value -> Parser a parseX f (Object v) = do t <- v .: "type" x <- v .: "x" f t x printA :: Value -> Parser (IO ()) printA = parseX (fst . composeType) printB :: Value -> Parser (IO ()) printB = parseXY (snd . composeType) main = do flagB <- return False -- command line flag let p = parseEither $ if flagB then printB else printA mv <- decodeFile "input.yaml" v <- maybe (fail "failed to parse yaml") return mv case p v of Left e -> fail $ "failed to parse data: " ++ e Right x -> x

On Mar 15, 2014, at 0:36 , Robert Vollmert
My problem is how I should deal with these intermediate types that vary based on the input. My current approach below has parsing and printing functions, and then one big function that strings the matching parsers and printers together.
Just wanted to report that I’ve solved this well enough for now. The basic approach looks like: type Parsers a b = … type Printers a b = … type Handler c = forall a b. Parsers a b -> Printers a b -> c compose :: Tag -> Handler c -> c compose Tag1 h = h parsers1 printers1 compose Tag2 h = h parsers2 printers2 … (where type parameters a b differ for the different tags) Then I can define different handlers for different ways of stringing together parsers and printers. I’d still love to know if this is the “right” way to do this… Or if what I’m doing has a name? Cheers Rob

On Fri, Apr 4, 2014 at 10:02 AM, Robert Vollmert
My problem is how I should deal with these intermediate types that vary
On Mar 15, 2014, at 0:36 , Robert Vollmert
wrote: based on the input. My current approach below has parsing and printing functions, and then one big function that strings the matching parsers and printers together. Just wanted to report that I've solved this well enough for now. The basic approach looks like:
type Parsers a b = ... type Printers a b = ...
type Handler c = forall a b. Parsers a b -> Printers a b -> c
compose :: Tag -> Handler c -> c compose Tag1 h = h parsers1 printers1 compose Tag2 h = h parsers2 printers2 ...
(where type parameters a b differ for the different tags)
Then I can define different handlers for different ways of stringing together parsers and printers.
I'd still love to know if this is the "right" way to do this... Or if what I'm doing has a name?
Cheers Rob
It seems to me that you might benefit from a "compiler" approach. In such a design, you parse the input text, turn it into an abstract syntax tree, and then interpret the tree (typically in terms of some monad, but not necessarily). The "intermediate" data type is definitely tricky to get down. If you are having trouble expressing it in a way that fits your other design constraints, you might want to look into stuff like "data types a la carte" or the "syntactic" package. But really, standard Haskell data types are pretty good at this kind of thing. You shouldn't need data types a la carte unless you're trying to make a "pluggable" F-algebra. (That is, a data type that you can "extend" by importing a library)

On Apr 4, 2014, at 19:42 , Alexander Solla
It seems to me that you might benefit from a "compiler" approach. In such a design, you parse the input text, turn it into an abstract syntax tree, and then interpret the tree (typically in terms of some monad, but not necessarily).
Thanks, the program does seem obviously compiler-like now that it’s been suggested! This will at least help thinking about it.
The "intermediate" data type is definitely tricky to get down. If you are having trouble expressing it in a way that fits your other design constraints, you might want to look into stuff like "data types a la carte" or the "syntactic" package. But really, standard Haskell data types are pretty good at this kind of thing.
You shouldn't need data types a la carte unless you're trying to make a "pluggable" F-algebra. (That is, a data type that you can "extend" by importing a library)
Fun, I never had a reason to look at the data types a la carte and friends before. Though I’m not sure to what extent these approaches are a good fit given that my input doesn’t have any recursive structure? I do sort of want to keep the intermediate type “open”, though that may well be a mistake… I’ll keep thinking about it, thanks for the input! Cheers Rob
participants (2)
-
Alexander Solla
-
Robert Vollmert