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
- literalNullableNonEmptyText :: forall (s :: Symbol) (n :: Nat). (KnownSymbol s, KnownNat n, SymbolNonEmpty s, SymbolWithNoSpaceAround s, SymbolNoLongerThan s n) => 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
.
This is aimed primarily at JSON parsing: make it possible to parse empty
string and turn it into Nothing
, in order to convert everything into
Maybe NonEmptyText
at the edge of the system.
While using this for JSON parsing, use Maybe NullableNonEmptyText
. Aeson
special-cases Maybe
to allow nulls, so Maybe
catches the nulls and
NullableNonEmptyText
catches the empty strings.
To extract Maybe NonEmptyText
values from Maybe NullableNonEmptyText
,
use nullableNonEmptyTextToMaybeNonEmptyText
.
Instances
Constructing
mkNonEmptyTextWithTruncate :: forall n. (KnownNat n, 1 <= n) => Text -> Maybe (NonEmptyText n) Source #
literalNullableNonEmptyText :: forall (s :: Symbol) (n :: Nat). (KnownSymbol s, KnownNat n, SymbolNonEmpty s, SymbolWithNoSpaceAround s, SymbolNoLongerThan s n) => 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 #