0

I have a system in haskell that uses Data.Dynamic and Type.Reflection to perform inference and calculations. I would like to be able to generate dynamic data randomly.

Generating dynamic data is easy when the type is known.

goo :: SomeTypeRep -> IO (Dynamic)
goo str = case tyConName . someTypeRepTyCon $ str of
            "Int"  -> return . toDyn . randomRIO $ (-20, 100::Int)
            "Bool" -> return . toDyn . randomRIO $ (True, False)
            _      -> error "no chance"      

But having a new line for every type is impractical when handling tuples.

Is there a way to combine n dynamics into a tuple? Or is there another way to generate the tuples dynamically?

TheJohnMajor01
  • 333
  • 1
  • 9
  • Answer is likely related to another [question](https://stackoverflow.com/questions/48951745/printing-dynamic-data) I posted earlier – TheJohnMajor01 Feb 23 '18 at 17:34
  • I don't think that code does what you think it does. `return . toDyn . randomRIO $ (-20, 100)` does not create a random `Int`, convert it to `Dynamic`, and return that value. It converts *the `IO` action that creates a random `Int`* to `Dynamic`. You almost certainly want `toDyn <$> randomRIO (-20, 100)` instead (and similarly for the next line). – Daniel Wagner Feb 23 '18 at 19:07

1 Answers1

3

Generally when working with Type.Reflection you want to leave your quantification as "late" as possible. With that in mind, the following seems to work:

{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE GADTs #-}
import Control.Applicative
import Data.Dynamic
import System.Random
import Type.Reflection

goo :: TypeRep a -> IO a
goo tr = case tr of
    App (App comma a) b | Just HRefl <- eqTypeRep (typeRep @(,)) comma
        -> liftA2 (,) (goo a) (goo b)
    _ | Just HRefl <- eqTypeRep (typeRep @Int) tr -> randomRIO (-20, 100)
      | Just HRefl <- eqTypeRep (typeRep @Bool) tr -> randomIO
      | otherwise -> fail "dunno lol"

You might object that you want to take an existing Dynamic and produce a new, matching, random one, and that this doesn't work:

gooBad :: Dynamic -> IO Dynamic
gooBad d = case dynTypeRep d of
    SomeTypeRep tr -> toDyn <$> goo tr

That's true: the SomeTypeRep type existentially quantifies over the kind of its TypeRep, which is unfortunate, since we know that it's going to be representing a type of kind *. Luckily, Data.Dynamic exports enough information to do it yourself without dynTypeRep:

gooDyn :: Dynamic -> IO Dynamic
gooDyn (Dynamic tr _) = Dynamic tr <$> goo tr
Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • It looks like there's also `typeRepKind :: TypeRep (a :: k) -> TypeRep k`, so if it's *really* necessary to take a `SomeTypeRep` as the argument for some reason it looks like it should be possible with a bit of hand-wringing. Let me know if that seems useful and I can write a few comments about that. – Daniel Wagner Feb 23 '18 at 22:10
  • Hey I'm not sure why but I'm getting some errors when trying to compile goo. [link](https://imgur.com/a/DZNzs) any ideas? – TheJohnMajor01 Feb 24 '18 at 04:06
  • @TheJohnMajor01 Whoops, that's embarrassing. Must have introduced that while trying out some alternate formattings. Should be fixed -- it was just a parenthesis that had migrated. – Daniel Wagner Feb 24 '18 at 04:55