Read instance for constructors?

Dear Haskell-cafe, When deriving (Read), only values can be read in. If one wants to be able to read in constructors, too, is there an easy way out? E.g., the code below works, but the extra book-keeping f "A" = A ... is unpleasant — perhaps there's a simpler solution? {-# LANGUAGE FlexibleInstances #-} data D = A Int | B Int deriving (Show,Read) instance Read (Int -> D) where readsPrec = \_ s -> [(f s,"")] where f "A" = A f "B" = B f x = error $ "Invalid constructor " ++ x main = do let x = read "A 1" :: D print x let g s = read s :: (Int -> D) print $ g "B" 2 print $ g "C" 3 Many thanks in advance, Semen -- Семен Тригубенко http://trygub.com

On Mon, 10 Mar 2014 13:11:25 +0000, Semen Trygubenko / Семен Тригубенко
Dear Haskell-cafe,
When deriving (Read), only values can be read in. If one wants to be able to read in constructors, too, is there an easy way out? E.g., the code below works, but the extra book-keeping
f "A" = A ...
is unpleasant — perhaps there's a simpler solution?
You can derive Data using the DeriveDataTypeable extension and then use the toConstr :: Data a => a -> Constr method to obtain the Constr (which has a Show instance that in this case just returns "A", "B" etc.)

On Mon, 10 Mar 2014 14:54:14 +0100, Niklas Haas
You can derive Data using the DeriveDataTypeable extension and then use the toConstr :: Data a => a -> Constr method to obtain the Constr (which has a Show instance that in this case just returns "A", "B" etc.)
Oops, you are asking about the other direction. Well, you're in luck here too - Data has readConstr :: DataType -> String -> Maybe Constr.

Hi Niklas, On Mon, Mar 10, 2014 at 02:59:36PM +0100, Niklas Haas wrote:
On Mon, 10 Mar 2014 14:54:14 +0100, Niklas Haas
wrote: You can derive Data using the DeriveDataTypeable extension and then use the toConstr :: Data a => a -> Constr method to obtain the Constr (which has a Show instance that in this case just returns "A", "B" etc.)
Oops, you are asking about the other direction. Well, you're in luck here too - Data has readConstr :: DataType -> String -> Maybe Constr.
Great! But how do I recover the actual constructor? E.g., f :: String -> Constr f s = fromMaybe (error "error in f") $ readConstr (dataTypeOf $ B 1) s gives me back Data.Data.Constr (not D). I was hoping for something along the lines f "A" $ 1 to get back a value A 1 of type D, etc. Many thanks, S. -- Семен Тригубенко http://trygub.com

Great! But how do I recover the actual constructor? E.g.,
f :: String -> Constr f s = fromMaybe (error "error in f") $ readConstr (dataTypeOf $ B 1) s
gives me back Data.Data.Constr (not D). I was hoping for something along
the lines
f "A" $ 1
to get back a value
A 1
of type D, etc.
Many thanks, S.
Here's one way: import qualified Data.Generics.Builders as B import Data.Generics.Aliases fromConstrB (B.empty `extB` (12::Int)) (f "B")::D
B 12
fromConstrB B.empty (f "B")::D
B 0

On Mon, Mar 10, 2014 at 10:47:26PM +0000, gb wrote:
Great! But how do I recover the actual constructor? E.g.,
f :: String -> Constr f s = fromMaybe (error "error in f") $ readConstr (dataTypeOf $ B 1) s
gives me back Data.Data.Constr (not D). I was hoping for something along
the lines
f "A" $ 1
to get back a value
A 1
of type D, etc.
Many thanks, S.
Here's one way:
import qualified Data.Generics.Builders as B import Data.Generics.Aliases
fromConstrB (B.empty `extB` (12::Int)) (f "B")::D
B 12
fromConstrB B.empty (f "B")::D
B 0
Thank you very much — it works! [and many new useful functions discovered along the way :-)]. I'm fairly happy with this solution (using readConstr as suggested by Niklas, and fromConstrB, as per above). The only wrinkle now is with this term in the definition of f : dataTypeOf $ B 1 We provide a value here (B 1) — is there a way to make it take the constructor (B) instead, or, alternatively, make f aware of the signature of the constructor (Int -> D) and/or the resulting data type (D) somehow? I've hoogled it and also looked through Data.Data with no luck… It's just that constructing a full-blown value of type D might be non-trivial if D is complex, but it seems a bit wasteful as we are after the outer constructor alone. And of course, if D or types D depends on change we need to modify f… Thank you, S. -- Семен Тригубенко http://trygub.com

Thank you very much — it works! [and many new useful functions discovered along the way :-)].
I'm fairly happy with this solution (using readConstr as suggested by Niklas, and fromConstrB, as per above). The only wrinkle now is with this term in the definition of f :
dataTypeOf $ B 1
We provide a value here (B 1) — is there a way to make it take the constructor (B) instead, or, alternatively, make f aware of the signature of the constructor (Int -> D) and/or the resulting data type (D) somehow? I've hoogled it and also looked through Data.Data with no luck…
It's just that constructing a full-blown value of type D might be non-trivial if D is complex, but it seems a bit wasteful as we are after the outer constructor alone. And of course, if D or types D depends on change we need to modify f…
Thank you, S.
The idiomatic way to handle this kind of stuff normally is to pass an abstract proxy that carries the type as a type argument, rather than passing a value of that type itself, eg.:
data Proxy a = Proxy
dataTypeOf :: Data a => Proxy a -> DataTypeOf
or even a more polymorphic version:
dataTypeOf :: Data a => f a -> DataTypeOf
which can be instantiated at any ‘f’, including Proxy, [], Maybe or others. Unfortunately, it does not seem that Data.Data.Data has gone for this route, so my feedback is a bit useless. You could still provide your own wrapper function (that uses ‘undefined’ internally, which we know here to be safe even though it's ugly), though.

On Tue, Mar 11, 2014 at 01:21:01PM +0100, Niklas Haas wrote:
Thank you very much — it works! [and many new useful functions discovered along the way :-)].
I'm fairly happy with this solution (using readConstr as suggested by Niklas, and fromConstrB, as per above). The only wrinkle now is with this term in the definition of f :
dataTypeOf $ B 1
We provide a value here (B 1) — is there a way to make it take the constructor (B) instead, or, alternatively, make f aware of the signature of the constructor (Int -> D) and/or the resulting data type (D) somehow? I've hoogled it and also looked through Data.Data with no luck…
It's just that constructing a full-blown value of type D might be non-trivial if D is complex, but it seems a bit wasteful as we are after the outer constructor alone. And of course, if D or types D depends on change we need to modify f…
Thank you, S.
The idiomatic way to handle this kind of stuff normally is to pass an abstract proxy that carries the type as a type argument, rather than passing a value of that type itself, eg.:
data Proxy a = Proxy
dataTypeOf :: Data a => Proxy a -> DataTypeOf
or even a more polymorphic version:
dataTypeOf :: Data a => f a -> DataTypeOf
which can be instantiated at any ‘f’, including Proxy, [], Maybe or others.
Unfortunately, it does not seem that Data.Data.Data has gone for this route, so my feedback is a bit useless. You could still provide your own wrapper function (that uses ‘undefined’ internally, which we know here to be safe even though it's ugly), though.
Thank you for your reply — I've read it many times, but couldn't translate it into code as of yet. I don't mind ugly as long as it's safe. Specifically, how am I to construct an entity of type DataType (see Data.Data; DataType needs to be fed into readConstr) with the help of a wrapper function you are describing? If someone could in the direction of a skeleton for such a function I might be able to fill in the gaps on my own. But currently I'm stuck… :/ Thanks again, S. -- Семен Тригубенко http://trygub.com

On Tue, 11 Mar 2014 19:41:57 +0000, Semen Trygubenko / Семен Тригубенко
On Tue, Mar 11, 2014 at 01:21:01PM +0100, Niklas Haas wrote:
The idiomatic way to handle this kind of stuff normally is to pass an abstract proxy that carries the type as a type argument, rather than passing a value of that type itself, eg.:
data Proxy a = Proxy
dataTypeOf :: Data a => Proxy a -> DataTypeOf
or even a more polymorphic version:
dataTypeOf :: Data a => f a -> DataTypeOf
Thank you for your reply — I've read it many times, but couldn't translate it into code as of yet.
I don't mind ugly as long as it's safe. Specifically, how am I to construct an entity of type DataType (see Data.Data; DataType needs to be fed into readConstr) with the help of a wrapper function you are describing?
If someone could in the direction of a skeleton for such a function I might be able to fill in the gaps on my own. But currently I'm stuck… :/
Thanks again, S.
Oops, sorry, that was supposed to have been:
dataTypeOf :: Data a => Proxy a -> DataType or dataTypeOf :: Data a => p a -> DataType
As for the implementation, the simplest possible (ie. no language extensions) implementation I can think of looks like this:
dataTypeOf = Data.dataTypeOf . f where f :: p a -> a f _ = error "dataTypeOf: this should never be used"
where Data.dataTypeOf refers to the ‘original’ version of that function.

Dear Niklas, On Wed, Mar 12, 2014 at 01:10:19AM +0100, Niklas Haas wrote:
Oops, sorry, that was supposed to have been:
dataTypeOf :: Data a => Proxy a -> DataType or dataTypeOf :: Data a => p a -> DataType
As for the implementation, the simplest possible (ie. no language extensions) implementation I can think of looks like this:
dataTypeOf = Data.dataTypeOf . f where f :: p a -> a f _ = error "dataTypeOf: this should never be used"
where Data.dataTypeOf refers to the ‘original’ version of that function.
Awesomeness! I see now what you meant by Proxy and that Data.dataTypeOf doesn't even get evaluated, i.e. its sole purpose is to ferry the type information across… Neat. Much obliged, S. -- Семен Тригубенко http://trygub.com

Why not use:
http://hackage.haskell.org/package/ChristmasTree
which supports even infix constructors and runs in linear time,
Doaitse Swierstra
On 10 Mar 2014, at 14:11 , Semen Trygubenko / Семен Тригубенко
Dear Haskell-cafe,
When deriving (Read), only values can be read in. If one wants to be able to read in constructors, too, is there an easy way out? E.g., the code below works, but the extra book-keeping
f "A" = A ...
is unpleasant — perhaps there's a simpler solution?
{-# LANGUAGE FlexibleInstances #-}
data D = A Int | B Int deriving (Show,Read)
instance Read (Int -> D) where readsPrec = \_ s -> [(f s,"")] where f "A" = A f "B" = B f x = error $ "Invalid constructor " ++ x
main = do let x = read "A 1" :: D print x let g s = read s :: (Int -> D) print $ g "B" 2 print $ g "C" 3
Many thanks in advance, Semen
-- Семен Тригубенко http://trygub.com _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (4)
-
gb
-
Niklas Haas
-
S D Swierstra
-
Semen Trygubenko / Семен Тригубен ко