3

Given a datatype

data Foo = IFoo Int | SFoo String deriving (Data, Typeable)

what is a simple definition of

gconstr :: (Typeable a, Data t) => a -> t

such that

gconstr (5 :: Int) :: Foo == IFoo 5
gconstr "asdf" :: Foo == SFoo "asdf"
gconstr True :: Foo == _|_

It would be essentially the opposite of syb's gfindtype.

Or does such a thing exist already? I've tried hoogle-ing the type and haven't found much, but the syb types are kind of hard to interpret. A function returning Nothing on error is also acceptable.

Dan
  • 12,409
  • 3
  • 50
  • 87
  • I'm starting to suspect that `Data.Dynamic` would be better for my needs, but I'm still curious about this. – Dan Jul 13 '14 at 19:25

1 Answers1

2

This seems to be possible, though it's not completely trivial.

Preliminaries:

{-# LANGUAGE DeriveDataTypeable #-}
import Control.Monad ( msum )
import Data.Data
import Data.Maybe

First a helper function gconstrn, which tries to do the same thing as required of gconstr, but for a specific constructor only:

gconstrn :: (Typeable a, Data t) => Constr -> a -> Maybe t
gconstrn constr arg = gunfold addArg Just constr
    where
        addArg :: Data b => Maybe (b -> r) -> Maybe r
        addArg Nothing = Nothing
        addArg (Just f) =
            case cast arg of
                Just v -> Just (f v)
                Nothing -> Nothing

The key part is that the addArg function will use arg as an argument to the constructor, if the types match.

Essentially gunfold starts unfolding with Just IFoo or Just SFoo, and then the next step is to try addArg to provide it with its argument.

For multi-argument constructors this would be called repeatedly, so if you defined an IIFoo constructor that took two Ints, it would also get successfully filled in by gconstrn. Obviously with a bit more work you could do something more sophisticated like providing a list of arguments.

Then it's just a question of trying this with all possible constructors. The recursive definition between result and dt is just to get the right type argument for dataTypeOf, the actual value being passed in doesn't matter at all. ScopedTypeVariables would be an alternative for achieving this.

gconstr :: (Typeable a, Data t) => a -> Maybe t
gconstr arg = result
    where result = msum [gconstrn constr arg | constr <- dataTypeConstrs dt]
          dt = dataTypeOf (fromJust result)

As discussed in the comments, both functions can be simplified with <*> from Control.Applicative to the following, though it's a bit harder to see what's going on in the gunfold:

gconstr :: (Typeable a, Data t) => a -> Maybe t
gconstr arg = result
    where
        result = msum $ map (gunfold (<*> cast arg) Just) (dataTypeConstrs dt)
        dt = dataTypeOf (fromJust result)
Ganesh Sittampalam
  • 28,821
  • 4
  • 79
  • 98
  • That appears to work. Also, the `Maybe` monad formulation of `addArg` isn't too bad, it's something like `addArg a = do {f <- a; v <- cast arg; return (f v)}` – Dan Jul 13 '14 at 21:48
  • Actually, an `Applicative` form would be simpler, just `addArg a = a <*> cast arg` – Dan Jul 13 '14 at 21:50
  • Yes, it looks nice, but I think it would have confused me if I'd been reading it that way to begin with. The `Applicative` is more appealing though. – Ganesh Sittampalam Jul 13 '14 at 21:50
  • The `Applicative` also means you can partially apply directly in the `gunfold` call, which in turn makes it reasonable to inline `gconstrn` into `gconstr` - the list comprehension result just becomes `gunfold (<*> cast arg) Just (indexConstr dt n)`. I think that probably swings it. – Ganesh Sittampalam Jul 13 '14 at 21:53
  • Just noticed `dataTypeConstrs` which simplifies things further – Ganesh Sittampalam Jul 13 '14 at 22:26