Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype NullableNonEmptyText n = NullableNonEmptyText (Maybe (NonEmptyText n))
- mkNonEmptyTextWithTruncate :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NonEmptyText n)
- compileNullableNonEmptyText :: Integer -> QuasiQuoter
- type IsNullableNonEmptyText n s = (KnownSymbol s, KnownNat n, SymbolNonEmpty s, SymbolWithNoSpaceAround s, SymbolNoLongerThan s n)
- literalNullableNonEmptyText :: forall (s :: Symbol) (n :: Nat). IsNullableNonEmptyText n s => NullableNonEmptyText n
- mkNullableNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NullableNonEmptyText n)
- parseNullableNonEmptyText :: (KnownNat n, 1 <= n) => Text -> Object -> Parser (NullableNonEmptyText n)
- nullNonEmptyText :: NullableNonEmptyText n
- maybeTextToTruncateNullableNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Maybe Text -> NullableNonEmptyText n
- nonEmptyTextToNullable :: NonEmptyText n -> NullableNonEmptyText n
- maybeNonEmptyTextToNullable :: Maybe (NonEmptyText n) -> NullableNonEmptyText n
- nullableNonEmptyTextToMaybeText :: NullableNonEmptyText n -> Maybe Text
- nullableNonEmptyTextToMaybeNonEmptyText :: NullableNonEmptyText n -> Maybe (NonEmptyText n)
- fromMaybeNullableText :: Maybe (NullableNonEmptyText n) -> NullableNonEmptyText n
- isNullNonEmptyText :: NullableNonEmptyText n -> Bool
Documentation
newtype NullableNonEmptyText n Source #
Newtype wrapper around Maybe NonEmptyText that converts empty string to Nothing
.
is used in API types to represent optional text fields when you do not want an empty string to fail to parse.
Like NullableNonEmptyText
nNonEmptyText
, the payload Text
is guaranteed to be non-empty, within the character limit, and stripped of whitespace.
Unlike NonEmptyText
, it will successfully parse empty strings as nullNonEmptyText
.
Since Aeson version 2.2, fields of this type maybe be missing, null
, or empty without failing to parse.
Avoid using Maybe (NullableNonEmptyText n)
in API types, since it creates unnecessary edge cases that complicate the code.
NB: When using a version of Aeson prior to 2.2, you must use Maybe (NullableNonEmptyText n)
if you want to allow missing or null fields to parse.
data Person = Person { name ::NonEmptyText
50 , catchphrase ::NullableNonEmptyText
500 }
With this type definition, these four JSON objects below are valid and parse as Person Daniel nullNonEmptyText
.
{"name": "Daniel"} {"name": "Daniel", catchphrase: null} {"name": "Daniel", catchphrase: ""} {"name": "Daniel", catchphrase: " "}
These two JSON objects parses as Person Daniel (mkNullableNonEmptyText "Yabba-Dabba Do!")
{"name": "Daniel", catchphrase: "Yabba-Dabba Do!"} {"name": "Daniel", catchphrase: " Yabba-Dabba Do! "}
Use nullableNonEmptyTextToMaybeNonEmptyText
to extract Maybe (NonEmptyText n)
from NullableNonEmptyText n
.
Instances
Constructing
mkNonEmptyTextWithTruncate :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NonEmptyText n) Source #
type IsNullableNonEmptyText n s = (KnownSymbol s, KnownNat n, SymbolNonEmpty s, SymbolWithNoSpaceAround s, SymbolNoLongerThan s n) Source #
literalNullableNonEmptyText :: forall (s :: Symbol) (n :: Nat). IsNullableNonEmptyText n s => NullableNonEmptyText n Source #
This requires the text to be non-empty. For the empty text just use the constructor `NullableNonEmptyText Nothing`
mkNullableNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NullableNonEmptyText n) Source #
parseNullableNonEmptyText :: (KnownNat n, 1 <= n) => Text -> Object -> Parser (NullableNonEmptyText n) Source #
Conversion
maybeTextToTruncateNullableNonEmptyText :: forall n. (KnownNat n, 1 <= n) => Maybe Text -> NullableNonEmptyText n Source #
nullableNonEmptyTextToMaybeNonEmptyText :: NullableNonEmptyText n -> Maybe (NonEmptyText n) Source #