Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Prose type: arbitrary length non-empty text that is trimmed.
Synopsis
- data Prose
- mkProse :: Text -> Maybe Prose
- compileProse :: QuasiQuoter
- type IsProse s = (KnownSymbol s, SymbolWithNoSpaceAround s)
- literalProse :: forall (s :: Symbol). IsProse s => Prose
- proseToText :: Prose -> Text
- proseFromNonEmptyText :: NonEmptyText n -> Prose
Documentation
Whitespace-trimmed, non-empty text, for use with API endpoints.
The rationale is that there are many situations where if a client sends
text that is empty or all whitespace, there's probably a client error.
Not suitable for database fields, as there is no character limit (see
ProsePersistFieldMsg
).
Instances
FromJSON Prose Source # | |
ToJSON Prose Source # | |
Defined in Data.StringVariants.Prose.Internal | |
ToJSONKey Prose Source # | |
Defined in Data.StringVariants.Prose.Internal | |
Semigroup Prose Source # | |
Show Prose Source # | |
Eq Prose Source # | |
Ord Prose Source # | |
ConvertibleStrings Prose Text Source # | |
Defined in Data.StringVariants.Prose.Internal convertString :: Prose -> Text # | |
ConvertibleStrings Prose Text Source # | |
Defined in Data.StringVariants.Prose.Internal convertString :: Prose -> Text # | |
Lift Prose Source # | |
type IsProse s = (KnownSymbol s, SymbolWithNoSpaceAround s) Source #
proseToText :: Prose -> Text Source #
proseFromNonEmptyText :: NonEmptyText n -> Prose Source #