<div dir="ltr"><div><div><div>What about Data.Typeable.typeRepArgs ?<br><br>typeRepArgs :: TypeRep -> [TypeRep]<br><br>Prelude Data.Data> typeRepArgs (typeOf Foo)<br>[Int,Foo]<br><br></div>For any function type, the head of typeRepArgs should be the type of the first parameter.  For non-function types, it looks like typeRepArgs returns an empty list.<br>
<br></div>For anything more complicated, I suspect you'll need Data/Generic/Template Haskell.<br><br></div>John L.<br></div><div class="gmail_extra"><br><br><div class="gmail_quote">On Mon, Oct 28, 2013 at 7:15 PM, AntC <span dir="ltr"><<a href="mailto:anthony_clayden@clear.net.nz" target="_blank">anthony_clayden@clear.net.nz</a>></span> wrote:<br>
<blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">[reposted from Beginners, where it met stoney silence.]<br>
<br>
So I have (or rather the user of my package has):<br>
<br>
> {-# LANGUAGE  DeriveDataTypeable    #-}<br>
><br>
>    newtype Foo = Foo Int    deriving (Read, Show, Typeable, Data, ...)<br>
>    someFoo     = Foo 7<br>
><br>
<br>
Note:<br>
* the `newtype` could be `data` -- if that would help.<br>
* this is _not_ a parameterised type, but a 'baked in' `Int`.<br>
* the data constr is named same as the type -- if that would help.<br>
<br>
I can ask for `typeOf someFoo` and get `Foo` OK.<br>
I can ask for `typeOf Foo`  and get `Int -> Foo` OK.<br>
<br>
If I ask for `typeOf (typeOf someFoo)` I get `TypeRep`.<br>
`typeOf (show $ typeOf someFoo`) gets me `[Char]` (aka `String`)<br>
<br>
So far very logical, but not very helpful.<br>
<br>
What I want is to get the based-on type baked inside `someFoo`<br>
-- that is: `Int`<br>
(It would also be handy to get the name of the data constr, just in case<br>
it's different to the type.)<br>
<br>
Do I need to get into `deriving (..., Generic)` ?<br>
<br>
That looks like serious machinery!<br>
<br>
Thanks<br>
AntC<br>
<br>
<br>
<br>
<br>
_______________________________________________<br>
Haskell-Cafe mailing list<br>
<a href="mailto:Haskell-Cafe@haskell.org">Haskell-Cafe@haskell.org</a><br>
<a href="http://www.haskell.org/mailman/listinfo/haskell-cafe" target="_blank">http://www.haskell.org/mailman/listinfo/haskell-cafe</a><br>
</blockquote></div><br></div>