module PostgresqlSyntax.CharSet where import qualified Data.Text as Text import qualified PostgresqlSyntax.KeywordSet as KeywordSet import PostgresqlSyntax.Prelude {-# NOINLINE symbolicBinOp #-} symbolicBinOp :: HashSet Char symbolicBinOp :: HashSet Char symbolicBinOp = HashSet Text KeywordSet.symbolicBinOp forall a b. a -> (a -> b) -> b & forall (t :: * -> *) a. Foldable t => t a -> [a] toList forall a b. a -> (a -> b) -> b & forall a. Monoid a => [a] -> a mconcat forall a b. a -> (a -> b) -> b & Text -> [Char] Text.unpack forall a b. a -> (a -> b) -> b & forall l. IsList l => [Item l] -> l fromList {-# NOINLINE hexDigit #-} hexDigit :: HashSet Char hexDigit :: HashSet Char hexDigit = forall l. IsList l => [Item l] -> l fromList [Char] "0123456789abcdefABCDEF" {-# NOINLINE op #-} op :: HashSet Char op :: HashSet Char op = forall l. IsList l => [Item l] -> l fromList [Char] "+-*/<>=~!@#%^&|`?" {-# NOINLINE prohibitionLiftingOp #-} prohibitionLiftingOp :: HashSet Char prohibitionLiftingOp :: HashSet Char prohibitionLiftingOp = forall l. IsList l => [Item l] -> l fromList [Char] "~!@#%^&|`?"