Copyright | Copyright © 2014 AlephCloud Systems, Inc. |
---|---|
License | MIT |
Maintainer | Lars Kuhtz <lars@alephcloud.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Utilities for validating configuration values
- type ConfigValidation α λ = (MonadIO μ, Functor μ, Applicative μ, MonadError Text μ, MonadWriter (λ Text) μ) => α -> μ ()
- validateHttpOrHttpsUrl :: MonadError Text m => Text -> String -> m ()
- validateHttpUrl :: MonadError Text m => Text -> String -> m ()
- validateHttpsUrl :: MonadError Text m => Text -> String -> m ()
- validateUri :: MonadError Text m => Text -> String -> m ()
- validateAbsoluteUri :: MonadError Text m => Text -> String -> m ()
- validateAbsoluteUriFragment :: MonadError Text m => Text -> String -> m ()
- validateIPv4 :: MonadError Text m => Text -> String -> m ()
- validateIPv6 :: MonadError Text m => Text -> String -> m ()
- validatePort :: (MonadError Text m, Integral n, Show n) => Text -> n -> m ()
- validateNonEmpty :: (MonadError Text m, Eq α, Monoid α) => Text -> α -> m ()
- validateLength :: (MonadError Text m, Foldable φ) => Text -> Int -> φ α -> m ()
- validateMinLength :: (MonadError Text m, Foldable φ) => Text -> Int -> φ α -> m ()
- validateMaxLength :: (MonadError Text m, Foldable φ) => Text -> Int -> φ α -> m ()
- validateMinMaxLength :: (MonadError Text m, Foldable φ) => Text -> Int -> Int -> φ α -> m ()
- validateFilePath :: MonadError Text m => Text -> FilePath -> m ()
- validateFile :: (MonadError Text m, MonadIO m) => Text -> FilePath -> m ()
- validateFileReadable :: (MonadError Text m, MonadIO m) => Text -> FilePath -> m ()
- validateFileWritable :: (MonadError Text m, MonadIO m) => Text -> FilePath -> m ()
- validateExecutable :: (Functor m, MonadError Text m, MonadIO m) => Text -> FilePath -> m ()
- validateDirectory :: (MonadError Text m, MonadIO m) => Text -> FilePath -> m ()
- validateConfigFile :: (MonadIO m, MonadError Text m) => String -> m ()
- validateFalse :: MonadError Text m => Text -> Bool -> m ()
- validateTrue :: MonadError Text m => Text -> Bool -> m ()
- validateBool :: MonadError Text m => Text -> Bool -> Bool -> m ()
- validateNonNegative :: (MonadError Text m, Ord α, Num α) => Text -> α -> m ()
- validatePositive :: (MonadError Text m, Ord α, Num α) => Text -> α -> m ()
- validateNonPositive :: (MonadError Text m, Ord α, Num α) => Text -> α -> m ()
- validateNegative :: (MonadError Text m, Ord α, Num α) => Text -> α -> m ()
- validateNonNull :: (MonadError Text m, Eq α, Num α) => Text -> α -> m ()
- validateLess :: (MonadError Text m, Ord α, Show α) => Text -> α -> α -> m ()
- validateLessEq :: (MonadError Text m, Ord α, Show α) => Text -> α -> α -> m ()
- validateGreater :: (MonadError Text m, Ord α, Show α) => Text -> α -> α -> m ()
- validateGreaterEq :: (MonadError Text m, Ord α, Show α) => Text -> α -> α -> m ()
- validateRange :: (MonadError Text m, Ord α, Show α) => Text -> (α, α) -> α -> m ()
Documentation
type ConfigValidation α λ = (MonadIO μ, Functor μ, Applicative μ, MonadError Text μ, MonadWriter (λ Text) μ) => α -> μ () Source
A validation function. The type in the MonadWriter
is excpected to
be a Foldable
structure for collecting warnings.
Networking
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
Validates that a value is an HTTP or HTTPS URL
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
Validates that a value is an HTTP URL
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
Validates that a value is an HTTPS URL
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
Validates that a value is an URI without a fragment identifier
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
Validates that a value is an absolute URI without a fragment identifier
validateAbsoluteUriFragment Source
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
Validates that a value is an absolute URI with an optional fragment identifier
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> String | |
-> m () |
:: (MonadError Text m, Integral n, Show n) | |
=> Text | configuration property name that is used in the error message |
-> n | |
-> m () |
Monoids, Foldables and Co
:: (MonadError Text m, Eq α, Monoid α) | |
=> Text | configuration property name that is used in the error message |
-> α | |
-> m () |
:: (MonadError Text m, Foldable φ) | |
=> Text | configuration property name that is used in the error message |
-> Int | exact length of the validated value |
-> φ α | |
-> m () |
:: (MonadError Text m, Foldable φ) | |
=> Text | configuration property name that is used in the error message |
-> Int | minimum length of the validated value |
-> φ α | |
-> m () |
:: (MonadError Text m, Foldable φ) | |
=> Text | configuration property name that is used in the error message |
-> Int | maximum length of the validated value |
-> φ α | |
-> m () |
Files
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> FilePath | |
-> m () |
:: (MonadError Text m, MonadIO m) | |
=> Text | configuration property name that is used in the error message |
-> FilePath | |
-> m () |
:: (MonadError Text m, MonadIO m) | |
=> Text | configuration property name that is used in the error message |
-> FilePath | |
-> m () |
:: (MonadError Text m, MonadIO m) | |
=> Text | configuration property name that is used in the error message |
-> FilePath | |
-> m () |
:: (Functor m, MonadError Text m, MonadIO m) | |
=> Text | configuration property name that is used in the error message |
-> FilePath | |
-> m () |
Validates if the given executable name can be found in the system and can be executed.
:: (MonadError Text m, MonadIO m) | |
=> Text | configuration property name that is used in the error message |
-> FilePath | |
-> m () |
validateConfigFile :: (MonadIO m, MonadError Text m) => String -> m () Source
Validate that the input is a config file
Boolean Values
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> Bool | |
-> m () |
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> Bool | |
-> m () |
:: MonadError Text m | |
=> Text | configuration property name that is used in the error message |
-> Bool | expected value |
-> Bool | |
-> m () |
Numeric Values
:: (MonadError Text m, Ord α, Num α) | |
=> Text | configuration property name that is used in the error message |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Num α) | |
=> Text | configuration property name that is used in the error message |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Num α) | |
=> Text | configuration property name that is used in the error message |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Num α) | |
=> Text | configuration property name that is used in the error message |
-> α | |
-> m () |
:: (MonadError Text m, Eq α, Num α) | |
=> Text | configuration property name that is used in the error message |
-> α | |
-> m () |
Orders
:: (MonadError Text m, Ord α, Show α) | |
=> Text | configuration property name that is used in the error message |
-> α | a strict upper bound for the configuration value |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Show α) | |
=> Text | configuration property name that is used in the error message |
-> α | a upper bound for the configuration value |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Show α) | |
=> Text | configuration property name that is used in the error message |
-> α | a strict lower bound for the configuration value |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Show α) | |
=> Text | configuration property name that is used in the error message |
-> α | a lower bound for the configuration value |
-> α | |
-> m () |
:: (MonadError Text m, Ord α, Show α) | |
=> Text | configuration property name that is used in the error message |
-> (α, α) | the valid range for the configuration value |
-> α | |
-> m () |