4

I have data types with many fields that, if not being manually specified by a JSON configuration file, should be randomly set. I am using Aeson to parse the config file. What is the best way to do this?

Currently, I am setting values equal to some impossible value, and then later checking for said value to edit.

data Example = Example { a :: Int, b :: Int }
default = Example 1 2
instance FromJSON Example where
    parseJSON = withObject "Example" $ \v -> Example
      <$> (v .: "a" <|> return (a default)) 
      <*> (v .: "b" <|> return (b default))

initExample :: Range -> Example -> IO Example
initExample range (Example x y) = do
   a' <- if x == (a default) then randomIO range else return x
   b' <- if y == (b default) then randomIO range else return y
   return $ Example a' b'

What I would like is something along the lines of:

parseJSON = withObject "Example" $ \v -> Example
      <$> (v .: "a" <|> return (randomRIO (1,10))

Is it possible to define Parsers in the IO Monad or thread along some random generator, ideally using Aeson?

3 Answers3

5

Well, I don't know if it's a good idea, and juggling the extra IO layer will certainly get frustrating as heck for larger developments, but the following type-checks:

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
import Control.Applicative
import Data.Aeson
import System.Random

data Example = Example { a :: Int, b :: Int } deriving (Eq, Ord, Read, Show)

instance FromJSON (IO Example) where
    parseJSON = withObject "Example" $ \v -> liftA2 Example
        <$> ((pure <$> (v .: "a")) <|> pure (randomRIO (3, 4)))
        <*> ((pure <$> (v .: "b")) <|> pure (randomRIO (5, 6)))

In each of the last two lines, the first pure is Int -> IO Int, and the second is IO Int -> Parser (IO Int). In ghci:

> sequence (decode "{}") :: IO (Maybe Example)
Just (Example {a = 4, b = 6})
Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • As mentioned by @danidiaz, this is essentially using the `Applicative` and `Alternative` instances for `Compose Parser IO`. One could either use that type directly, or use it as further guidance for writing such code in larger developments. – Daniel Wagner Oct 19 '17 at 16:53
2

I don't know of a good strategy to get where you want to be since the ParseJSON monad is not a transformer or based on IO. What you can more easily do is decode into one type then translate into the second as done in a prior question 'Give a default value for fields not available in json using aeson'.

Since large structures can be cumbersome to reproduce you could make the structure parameterized and instantiate it with either IO Int or Int. For example, let's say you wanted field a from the wire but b as random from the IO monad:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}

import Data.Aeson
import System.Random
import Data.ByteString.Lazy (ByteString)

data Example' a =
        Example { a :: Int
                , b :: a
                } deriving (Show,Functor,Foldable,Traversable)

type Partial = Example' (IO Int)

type Example = Example' Int

instance FromJSON Partial where
    parseJSON (Object o) =
        Example <$> o .: "a"
                <*> pure (randomRIO (1,10))

loadExample :: Partial -> IO Example
loadExample = mapM id

parseExample :: ByteString -> IO (Maybe Example)
parseExample = maybe (pure Nothing) (fmap Just . loadExample) . decode

Notice how loadExample uses our traverse instance to execute the IO actions inside the structure. Here is an example use:

Main> parseExample "{ \"a\" : 1111 }"
Just (Example {a = 1111, b = 5})

Advanced

If you had more than one type of field for which you wanted an IO action you could either

  1. Make one data type for all of them. Instead of b being type IO Int you might make it IO MyComplexRecord. This is the easy solution.

  2. The more complex and fun solution is to use a higher kind type parameter.

For option 2, consider:

 data Example' f = Example { a :: Int
                           , b :: f Int
                           , c :: f String }

You could then use Proxy and Control.Monad.Identity instead of values like IO Int and Int used previously. You'll need to write your own traversal since you can't derive Traverse for this class (which is what gives us the mapM used above). We could make a traversal class with kind (* -> *) -> * using a few extensions (RankNTypes among them) but unless this is done often, and we get some sort of deriving support or TH, I don't think that is worthwhile.

Thomas M. DuBuisson
  • 64,245
  • 7
  • 109
  • 166
  • `the ParseJSON monad is not a transformer or based on IO`. But it's an `Applicative` though, and `Applicative`s compose. Perhaps a solution based on `Data.Functor.Compose IO Parser` could work. – danidiaz Oct 19 '17 at 06:12
  • Sure, I'd love to see that answer too. – Thomas M. DuBuisson Oct 19 '17 at 15:07
  • 1
    @danidiaz In fact in my answer I use only `Applicative` combinators, and am essentially using the `Compose` instances (but without the `Compose` newtype wrapper). But I didn't realize it until you pointed it out, so that's a nice insight and guide for writing the code in a larger development! – Daniel Wagner Oct 19 '17 at 16:51
1

Here is another solution, it involves a bit more manual labour, but the approach is quite straightforward - generate a random IO Example use it to generate a random "parser". Decoding into JSON is done with the usual decode function.

{-# LANGUAGE OverloadedStrings #-}
module Test where

import Data.Aeson
import Data.Aeson.Types
import System.Random

data Example = Example {_a :: Int, _b :: Int} deriving (Show, Ord, Eq)

getExample :: IO (Value -> Maybe Example)
getExample = do
 ex <- randomRIO (Example 1 1, Example 10 100)
 let ex' = withObject "Example" $ \o ->
             do a <- o .:? "a" .!= _a ex
                b <- o .:? "b" .!= _b ex
                return $ Example a b
 return (parseMaybe ex')

instance Random Example where
    randomRIO (low,hi) = Example <$> randomRIO (_a low,_a hi)
                                 <*> randomRIO (_b low,_b hi)
...

main :: IO ()
main = do
    getExample' <- getExample
    let example = getExample' =<< decode "{\"a\": 20}"
    print example

I am not sure but I believe this is the more verbose implementation of @DanielWagner's solution.

epsilonhalbe
  • 15,637
  • 5
  • 46
  • 74
  • re: "I believe this is the more verbose implementation of @DanielWagner's solution", I think our approaches are slightly different (though both interesting); you do some `IO` to generate a parser, while I do some parsing to generate an `IO` action. – Daniel Wagner Oct 19 '17 at 01:23
  • That's an interesting way to break it down. We have three answers that boil down to "Parse and generate an IO action needed executed", "Execute IO to generate a parser", and "Parse to generate an object with embedded IO actions for execution". – Thomas M. DuBuisson Oct 19 '17 at 15:47