[Haskell-cafe] Need help with scrap-your-boilerplate

Roman Cheplyaka roma at ro-che.info
Thu Oct 2 21:38:06 UTC 2014


On 02/10/14 16:17, Michael Sperber wrote:
> 
> I'm a casual Haskell user, and am trying to use scrap-your-boilerplate
> to write a transformation - and failing.  The rub is that the base
> function is polymorphic, boiling down to this:
> 
> data Foo a = Foo a
> 
> bar :: Foo a -> Foo a
> bar x = x
> 
> Now, I'm trying to use SYB like so:
> 
> foo :: Typeable a => a -> a
> foo = mkT bar
> 
> ... but I get:
> 
>     Could not deduce (Typeable a0) arising from a use of ‘mkT’
>     from the context (Typeable a)
>       bound by the type signature for foo :: Typeable a => a -> a
>       at foo.hs:...
>     The type variable ‘a0’ is ambiguous
>     Note: there are several potential instances:
> 
> Is there any way I could make this work?
> 
> Any help would be much appreciated!

I assume you want to apply bar to all monomorphic instances of Foo a,
and not just a specific one (which would be much easier).

I think the following should work (with GHC 7.8). But you definitely
should test it — with this kind of code, the fact that it compiles
doesn't really mean much.

  {-# LANGUAGE DeriveDataTypeable #-}
  import Data.Typeable
  import GHC.Prim

  data Foo a = Foo a
    deriving Typeable

  bar :: Foo a -> Foo a
  bar x = x

  getTyCon :: TypeRep -> TyCon
  getTyCon = fst . splitTyConApp

  fooTyCon :: TyCon
  fooTyCon = getTyCon $ typeRep (Proxy :: Proxy Foo)

  foo :: Typeable a => a -> a
  foo x
    | thisTyCon == fooTyCon
        = unsafeCoerce# (bar (unsafeCoerce# x :: Foo Any))
    | otherwise = x
    where
      thisTyCon = getTyCon $ typeOf x

Roman


-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 819 bytes
Desc: OpenPGP digital signature
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20141003/6a0c33d9/attachment.sig>


More information about the Haskell-Cafe mailing list