Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
render functions
Synopsis
- class RenderSQL sql where
- renderSQL :: sql -> ByteString
- printSQL :: (RenderSQL sql, MonadIO io) => sql -> io ()
- escape :: Char -> String
- parenthesized :: ByteString -> ByteString
- bracketed :: ByteString -> ByteString
- (<+>) :: ByteString -> ByteString -> ByteString
- commaSeparated :: [ByteString] -> ByteString
- doubleQuoted :: ByteString -> ByteString
- singleQuotedText :: Text -> ByteString
- singleQuotedUtf8 :: ByteString -> ByteString
- escapeQuotedString :: String -> ByteString
- escapeQuotedText :: Text -> ByteString
- renderCommaSeparated :: SListI xs => (forall x. expression x -> ByteString) -> NP expression xs -> ByteString
- renderCommaSeparatedConstraint :: forall c xs expression. (All c xs, SListI xs) => (forall x. c x => expression x -> ByteString) -> NP expression xs -> ByteString
- renderCommaSeparatedMaybe :: SListI xs => (forall x. expression x -> Maybe ByteString) -> NP expression xs -> ByteString
- renderNat :: forall n. KnownNat n => ByteString
- renderSymbol :: forall s. KnownSymbol s => ByteString
Render
class RenderSQL sql where Source #
A class for rendering SQL
renderSQL :: sql -> ByteString Source #
Instances
parenthesized :: ByteString -> ByteString Source #
Parenthesize a ByteString
.
bracketed :: ByteString -> ByteString Source #
Square bracket a ByteString
(<+>) :: ByteString -> ByteString -> ByteString infixr 7 Source #
Concatenate two ByteString
s with a space between.
commaSeparated :: [ByteString] -> ByteString Source #
Comma separate a list of ByteString
s.
doubleQuoted :: ByteString -> ByteString Source #
Add double quotes around a ByteString
.
singleQuotedText :: Text -> ByteString Source #
Add single quotes around a Text
and escape single quotes within it.
singleQuotedUtf8 :: ByteString -> ByteString Source #
Add single quotes around a ByteString
and escape single quotes within it.
escapeQuotedString :: String -> ByteString Source #
Escape quote a string.
escapeQuotedText :: Text -> ByteString Source #
Escape quote a string.
renderCommaSeparated :: SListI xs => (forall x. expression x -> ByteString) -> NP expression xs -> ByteString Source #
Comma separate the renderings of a heterogeneous list.
renderCommaSeparatedConstraint :: forall c xs expression. (All c xs, SListI xs) => (forall x. c x => expression x -> ByteString) -> NP expression xs -> ByteString Source #
Comma separate the renderings of a heterogeneous list.
renderCommaSeparatedMaybe :: SListI xs => (forall x. expression x -> Maybe ByteString) -> NP expression xs -> ByteString Source #
renderSymbol :: forall s. KnownSymbol s => ByteString Source #
Render a promoted Symbol
.