{-# LANGUAGE
AllowAmbiguousTypes
, ConstraintKinds
, FlexibleContexts
, LambdaCase
, MagicHash
, OverloadedStrings
, PolyKinds
, RankNTypes
, ScopedTypeVariables
, TypeApplications
#-}
module Squeal.PostgreSQL.Render
(
RenderSQL (..)
, printSQL
, escape
, parenthesized
, bracketed
, (<+>)
, commaSeparated
, doubleQuoted
, singleQuotedText
, singleQuotedUtf8
, renderCommaSeparated
, renderCommaSeparatedConstraint
, renderCommaSeparatedMaybe
, renderNat
, renderSymbol
) where
import Control.Monad.IO.Class (MonadIO (..))
import Data.ByteString (ByteString)
import Data.Maybe (catMaybes)
import Data.Monoid ((<>))
import Data.Text (Text)
import Generics.SOP
import GHC.Exts
import GHC.TypeLits hiding (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Char8 as Char8
parenthesized :: ByteString -> ByteString
parenthesized str = "(" <> str <> ")"
bracketed :: ByteString -> ByteString
bracketed str = "[" <> str <> "]"
(<+>) :: ByteString -> ByteString -> ByteString
infixr 7 <+>
str1 <+> str2 = str1 <> " " <> str2
commaSeparated :: [ByteString] -> ByteString
commaSeparated = ByteString.intercalate ", "
doubleQuoted :: ByteString -> ByteString
doubleQuoted str = "\"" <> str <> "\""
singleQuotedText :: Text -> ByteString
singleQuotedText str =
"'" <> Text.encodeUtf8 (Text.replace "'" "''" str) <> "'"
singleQuotedUtf8 :: ByteString -> ByteString
singleQuotedUtf8 = singleQuotedText . Text.decodeUtf8
renderCommaSeparated
:: SListI xs
=> (forall x. expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated render
= commaSeparated
. hcollapse
. hmap (K . render)
renderCommaSeparatedConstraint
:: forall c xs expression. (All c xs, SListI xs)
=> (forall x. c x => expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparatedConstraint render
= commaSeparated
. hcollapse
. hcmap (Proxy @c) (K . render)
renderCommaSeparatedMaybe
:: SListI xs
=> (forall x. expression x -> Maybe ByteString)
-> NP expression xs -> ByteString
renderCommaSeparatedMaybe render
= commaSeparated
. catMaybes
. hcollapse
. hmap (K . render)
renderNat :: forall n. KnownNat n => ByteString
renderNat = fromString (show (natVal' (proxy# :: Proxy# n)))
renderSymbol :: forall s. KnownSymbol s => ByteString
renderSymbol = fromString (symbolVal' (proxy# :: Proxy# s))
class RenderSQL sql where renderSQL :: sql -> ByteString
printSQL :: (RenderSQL sql, MonadIO io) => sql -> io ()
printSQL = liftIO . Char8.putStrLn . renderSQL
escape :: Char -> String
escape = \case
'\NUL' -> "\\0"
'\'' -> "''"
'"' -> "\\\""
'\b' -> "\\b"
'\n' -> "\\n"
'\r' -> "\\r"
'\t' -> "\\t"
'\\' -> "\\\\"
c -> [c]