On 6/25/07, Udo Stenzel <u.stenzel@web.de> wrote:
That type signature describes a function that can deliver *anything*
(that is in class Data), whatever you ask from it.


Yes, that is the goal :-)
 
If you do that, you wind up dragging in all the
machinery of Data.Generic

Is reflection hard in Haskell?  In C# its easy, and its one of the most powerful features of C#
 

just to implement what HaXml does with much
simpler technology.  I doubt that's what you actually want.

It is exactly what I want ;-)  haxml needs a DTD.
 
On the other hand, I might be misunderstanding.  In that case,
Data.Generics should have everything you need, in particular gunfold and
friends.

Yes, but I'm kindof stuck giving useful input to makeConstrM, so if anyone has any ideas?
 
kpreid in irc gave me an example of using makeConstrM for a pair of strings , but I cant seem to generalize it to work with a custom data type containing strings and ints ( eg Config{ login :: String, maxLogAgeDays :: Int } )

Current (not working) code looks something like the following. Most of the working bits of testConstrM' / runM' come from kpreid, the rest is my feeble attempts to tweak it.

runM' :: (MonadState [String] m, Monad m, Data a) => m a
runM' = do
   value <- gets head
   modify tail
   -- then one of: (pick the non-working function of your choice ;-)  :
   -- return read (fromJust value)
   -- return (fromJust $ cast value )
   -- return (fst $ head $ gread( "(" ++ value ++ ")" ) )
   -- return (fromConstrM runM' constr)
   -- return (fromConstr contr)

testConstrM' :: (Read a, Data a, Read c, Read b, Data b, Data c) => [String] -> a -> (b,c)
testConstrM' fieldvalues object = evalState( fromConstrM runM' (toConstr object) ) fieldvalues

data Config = Config{ name :: String, age :: Int }
   deriving( Data, Show, Typeable, Ord, Eq, Read )
createConfig = Config "blah" 3

test = testConstrM' ["qsdfqsdf", "7"] createConfig

(I've left out the xml parsing bit, which you can find at: http://www.haskell.org/haskellwiki/HXT section 9.1.1/9.1.2)

Maybe I should escalate the question to the haskell@haskell.org group?