{-# LANGUAGE NumericUnderscores #-} {-# LANGUAGE OverloadedStrings #-} module Generators where import Data.Int (Int64) import Data.ByteString (ByteString) import Hedgehog (MonadGen) import qualified Hedgehog.Gen as Gen import qualified Hedgehog.Range as Range import Data.Text (Text) import qualified Data.Text as X import Squeather (SQLData(SQLNull, SQLText, SQLBlob, SQLInteger, SQLFloat)) import qualified Squeather sqlData :: MonadGen m => m SQLData sqlData = Gen.choice [pure SQLNull, int, txt, blb, flt] where txt = fmap SQLText $ Gen.text (Range.exponential 0 1_000) (Gen.frequency [(4, Gen.ascii), (1, Gen.unicode)]) blb = fmap SQLBlob $ Gen.bytes (Range.exponential 0 1_000) int = fmap SQLInteger $ Gen.int64 Range.exponentialBounded flt = fmap SQLFloat $ Gen.double (Range.exponentialFloatFrom 0 (-1_000) 1_000) blob :: MonadGen m => m ByteString blob = Gen.bytes (Range.exponential 0 1024) text :: MonadGen m => m Text text = Gen.text (Range.exponential 0 1000) (Gen.frequency [(4, Gen.ascii), (1, Gen.unicode)]) integer :: MonadGen m => m Int64 integer = Gen.int64 Range.exponentialBounded double :: MonadGen m => m Double double = Gen.double (Range.exponentialFloatFrom 0 (-1_000) 1_000) -- | Creates an SQL statement which produces a table with the given -- number of columns. Each column is named @cNUM@, where C is the -- index, starting at 0, such as @c0@, @c1@, etc. The table is -- named @t@. createTableStatement :: Int -- ^ Number of columns. Must be at least 1; otherwise 'error' is -- applied. -> Text createTableStatement nCols | nCols < 1 = error $ "createTableStatement: applied to less than one column: " ++ show nCols | otherwise = "CREATE TABLE t (c0" <> cols <> ");" where nOver1 = nCols - 1 cols = X.concat . map mkCol $ [1..nOver1] mkCol n = ",c" `X.append` (X.pack . show $ n) insertStatement :: Int -- ^ Number of columns -> Text insertStatement nCols | nCols < 1 = error $ "insertStatement: applied to less than one column: " ++ show nCols | otherwise = "INSERT INTO t (c0" <> cols <> ") VALUES (:c0" <> colParams <> ");" where nOver1 = nCols - 1 cols = X.concat . map mkCol $ [1..nOver1] mkCol n = ",c" `X.append` (X.pack . show $ n) colParams = X.concat . map mkParamCol $ [1..nOver1] mkParamCol n = ",:c" `X.append` (X.pack . show $ n) -- | Pair 'SQLData' with column labels. addColumnLabels :: [a] -> [(Text, a)] addColumnLabels = zipWith f ([0..] :: [Int]) where f num item = (X.pack $ ":c" <> show num, item) directOnly :: MonadGen m => m Squeather.DirectOnly directOnly = Gen.choice [pure Squeather.DirectOnly, pure Squeather.NotDirectOnly]