Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Fake a = FakeT IO a
- newtype FakeT m a where
- FakeT {
- runFakeT :: FakerSettings -> m a
- pattern Fake :: (FakerSettings -> IO a) -> Fake a
- FakeT {
- data FakerSettings
- data FakerException
- defaultFakerSettings :: FakerSettings
- setLocale :: Text -> FakerSettings -> FakerSettings
- setRandomGen :: StdGen -> FakerSettings -> FakerSettings
- setDeterministic :: FakerSettings -> FakerSettings
- setNonDeterministic :: FakerSettings -> FakerSettings
- setCacheField :: HashMap CacheFieldKey (Vector Text) -> FakerSettings -> IO ()
- setCacheFile :: HashMap CacheFileKey Value -> FakerSettings -> IO ()
- replaceCacheField :: HashMap CacheFieldKey (Vector Text) -> FakerSettings -> IO FakerSettings
- replaceCacheFile :: HashMap CacheFileKey Value -> FakerSettings -> IO FakerSettings
- getRandomGen :: FakerSettings -> StdGen
- getLocale :: FakerSettings -> Text
- getDeterministic :: FakerSettings -> Bool
- getCacheField :: FakerSettings -> IO (HashMap CacheFieldKey (Vector Text))
- getCacheFile :: FakerSettings -> IO (HashMap CacheFileKey Value)
- generate :: MonadIO m => FakeT m a -> m a
- generateNonDeterministic :: MonadIO m => FakeT m a -> m a
- generateWithSettings :: MonadIO m => FakerSettings -> FakeT m a -> m a
Types
type Fake a = FakeT IO a Source #
Fake data type. This is the type you will be using to produce fake values.
FakeT | |
|
pattern Fake :: (FakerSettings -> IO a) -> Fake a |
Instances
Monad m => Monad (FakeT m) Source # | |
Monad m => Functor (FakeT m) Source # | |
Monad m => Applicative (FakeT m) Source # | |
MonadIO m => MonadIO (FakeT m) Source # | |
MonadIO m => MonadFake (FakeT m) Source # | |
(Semigroup a, Monad m) => Semigroup (FakeT m a) Source # | Since: 0.6.1 |
(Monoid a, Monad m) => Monoid (FakeT m a) Source # | Since: 0.6.1 |
data FakerSettings Source #
Instances
Show FakerSettings Source # | |
Defined in Faker showsPrec :: Int -> FakerSettings -> ShowS # show :: FakerSettings -> String # showList :: [FakerSettings] -> ShowS # |
data FakerException Source #
InvalidLocale String | This is thrown when it is not able to find the fake data source for your localization. |
InvalidField String Text | The |
NoDataFound FakerSettings | This is thrown when you have no
data. This may likely happen for
locales other than |
ParseError String | This is thrown when the parsing step
fails. The |
Instances
Show FakerException Source # | |
Defined in Faker showsPrec :: Int -> FakerException -> ShowS # show :: FakerException -> String # showList :: [FakerException] -> ShowS # | |
Exception FakerException Source # | |
Defined in Faker |
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"
setCacheField :: HashMap CacheFieldKey (Vector Text) -> FakerSettings -> IO () Source #
setCacheFile :: HashMap CacheFileKey Value -> FakerSettings -> IO () Source #
replaceCacheField :: HashMap CacheFieldKey (Vector Text) -> FakerSettings -> IO FakerSettings Source #
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.
getCacheField :: FakerSettings -> IO (HashMap CacheFieldKey (Vector Text)) Source #
getCacheFile :: FakerSettings -> IO (HashMap CacheFileKey Value) Source #
Generators
generate :: MonadIO m => FakeT m a -> m a Source #
Generate fake value with defaultFakerSettings
λ> 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
generateWithSettings :: MonadIO m => FakerSettings -> FakeT m a -> m a Source #
Generate fake value with supplied FakerSettings
λ> generateWithSettings defaultFakerSettings FN.name "Antony Langosh"