fakedata-1.0.3: Library for producing fake data
Safe HaskellNone
LanguageHaskell2010

Faker

Synopsis

Types

type Fake = FakeT IO Source #

Fake data type. This is the type you will be using to produce fake values.

newtype FakeT m a Source #

Constructors

FakeT 

Fields

Bundled Patterns

pattern Fake :: (FakerSettings -> IO a) -> Fake a 

Instances

Instances details
Monad m => Monad (FakeT m) Source # 
Instance details

Defined in Faker

Methods

(>>=) :: FakeT m a -> (a -> FakeT m b) -> FakeT m b #

(>>) :: FakeT m a -> FakeT m b -> FakeT m b #

return :: a -> FakeT m a #

Monad m => Functor (FakeT m) Source # 
Instance details

Defined in Faker

Methods

fmap :: (a -> b) -> FakeT m a -> FakeT m b #

(<$) :: a -> FakeT m b -> FakeT m a #

Monad m => Applicative (FakeT m) Source # 
Instance details

Defined in Faker

Methods

pure :: a -> FakeT m a #

(<*>) :: FakeT m (a -> b) -> FakeT m a -> FakeT m b #

liftA2 :: (a -> b -> c) -> FakeT m a -> FakeT m b -> FakeT m c #

(*>) :: FakeT m a -> FakeT m b -> FakeT m b #

(<*) :: FakeT m a -> FakeT m b -> FakeT m a #

MonadIO m => MonadIO (FakeT m) Source # 
Instance details

Defined in Faker

Methods

liftIO :: IO a -> FakeT m a #

MonadIO m => MonadFake (FakeT m) Source # 
Instance details

Defined in Faker.Class

Methods

liftFake :: Fake a -> FakeT m a Source #

(Semigroup a, Monad m) => Semigroup (FakeT m a) Source #

Since: 0.6.1

Instance details

Defined in Faker

Methods

(<>) :: FakeT m a -> FakeT m a -> FakeT m a #

sconcat :: NonEmpty (FakeT m a) -> FakeT m a #

stimes :: Integral b => b -> FakeT m a -> FakeT m a #

(Monoid a, Monad m) => Monoid (FakeT m a) Source #

Since: 0.6.1

Instance details

Defined in Faker

Methods

mempty :: FakeT m a #

mappend :: FakeT m a -> FakeT m a -> FakeT m a #

mconcat :: [FakeT m a] -> FakeT m a #

data FakerSettings Source #

Instances

Instances details
Show FakerSettings Source # 
Instance details

Defined in Faker

data FakerException Source #

Constructors

InvalidLocale String

This is thrown when it is not able to find the fake data source for your localization.

InvalidField String AesonKey

The String represents the field it is trying to resolve and the Key field is something you passed on.

NoDataFound FakerSettings

This is thrown when you have no data. This may likely happen for locales other than en.

ParseError String

This is thrown when the parsing step fails. The String represents the error message.

data NonDeterministicSeed Source #

NonDeterministicSeed type which controls if a fixed seed is going to be used or if a new seed will be generated each time.

Since: 1.0.3

Constructors

FixedSeed

Always use a fixed seed.

NewSeed

Use a new seed every time.

defaultFakerSettings :: FakerSettings Source #

Default faker settings with locale of "en" and Deterministic output.

Setters

setLocale :: Text -> FakerSettings -> FakerSettings Source #

Sets the locale. Note that for any other locale apart from "en", you need to make sure that the data is acutally present. In case no data is found, NoDataFound exception will be thrown. You can check the presence of the data in a particular locale by inspecting the yml file of the corresponding locale. The file would be bundled along with the particular Hackage release.

setRandomGen :: StdGen -> FakerSettings -> FakerSettings Source #

Sets the initial gen for random generator

setDeterministic :: FakerSettings -> FakerSettings Source #

Set the output of fakedata to be deterministic. With this you will get the same ouput for the functions every time.

λ> import qualified Faker.Name as FN
λ> :t FN.name
FN.name :: Fake Text
λ> generateWithSettings (setDeterministic defaultFakerSettings) FN.name
"Antony Langosh"
λ> generateWithSettings (setDeterministic defaultFakerSettings) FN.name
"Antony Langosh"

setNonDeterministic :: FakerSettings -> FakerSettings Source #

Set the output of fakedata to be non deterministic. With this you will get different ouput for the fake functions.

λ> generateWithSettings (setNonDeterministic defaultFakerSettings) FN.name
"Macy Shanahan"
λ> generateWithSettings (setNonDeterministic defaultFakerSettings) FN.name
"Rudy Dickinson II"

Getters

getRandomGen :: FakerSettings -> StdGen Source #

Get the initial gen for random generator

getLocale :: FakerSettings -> Text Source #

Get the Locale settings for your fake data source

getDeterministic :: FakerSettings -> Bool Source #

Check if the fake data output is deterministic or not. A True value indicates that it is deterministic.

getNonDeterministicSeed :: FakerSettings -> NonDeterministicSeed Source #

Get the NonDeterministicSeed from faker settings. Note that this setting is only applicable when use non deterministic output.

Generators

generate :: MonadIO m => FakeT m a -> m a Source #

Generate fake value with defaultFakerSettings. This produces deterministic output by default.

λ> import qualified Faker.Name as FN
λ> generate FN.name
"Antony Langosh"

generateNonDeterministic :: MonadIO m => FakeT m a -> m a Source #

Generate fake value with defaultFakerSettings but with non deterministic setting.

λ> import qualified Faker.Name as FN
λ> generateNonDeterministic FN.name
"Prof. Antoine O'Conner"
λ> generateNonDeterministic FN.name
"Savannah Buckridge"

Since: 0.8.0

generateNonDeterministicWithFixedSeed :: MonadIO m => FakeT m a -> m a Source #

Generate fake value with NonDeterministicSeed as FixedSeed. The difference between generateNonDeterministic and this function is that this uses a fixed seed set via setRandomGen as it's initial seed value.

Executing this function multiple times will result in generation of same values.

λ> generateNonDeterministicWithFixedSeed $ listOf 5 $ fromRange (1,100)
[98,87,77,33,98]
λ> generateNonDeterministicWithFixedSeed $ listOf 5 $ fromRange (1,100)
[98,87,77,33,98]

Since: 1.0.3

generateWithSettings :: MonadIO m => FakerSettings -> FakeT m a -> m a Source #

Generate fake value with supplied FakerSettings

λ> generateWithSettings defaultFakerSettings FN.name
"Antony Langosh"