module PostgresqlSyntax.Validation where

import qualified Data.Text as Text
import qualified PostgresqlSyntax.KeywordSet as KeywordSet
import qualified PostgresqlSyntax.Predicate as Predicate
import PostgresqlSyntax.Prelude

{-
The operator name is a sequence of up to NAMEDATALEN-1 (63 by default)
characters from the following list:

+ - * / < > = ~ ! @ # % ^ & | ` ?

There are a few restrictions on your choice of name:
-- and /* cannot appear anywhere in an operator name,
since they will be taken as the start of a comment.

A multicharacter operator name cannot end in + or -,
unless the name also contains at least one of these characters:

~ ! @ # % ^ & | ` ?

For example, @- is an allowed operator name, but *- is not.
This restriction allows PostgreSQL to parse SQL-compliant
commands without requiring spaces between tokens.
The use of => as an operator name is deprecated.
It may be disallowed altogether in a future release.

The operator != is mapped to <> on input,
so these two names are always equivalent.
-}
op :: Text -> Maybe Text
op :: Text -> Maybe Text
op Text
a =
  if Text -> Bool
Text.null Text
a
    then forall a. a -> Maybe a
Just (Text
"Operator is empty")
    else
      if Text -> Text -> Bool
Text.isInfixOf Text
"--" Text
a
        then forall a. a -> Maybe a
Just (Text
"Operator contains a prohibited \"--\" sequence: " forall a. Semigroup a => a -> a -> a
<> Text
a)
        else
          if Text -> Text -> Bool
Text.isInfixOf Text
"/*" Text
a
            then forall a. a -> Maybe a
Just (Text
"Operator contains a prohibited \"/*\" sequence: " forall a. Semigroup a => a -> a -> a
<> Text
a)
            else
              if forall a. (Eq a, Hashable a) => HashSet a -> a -> Bool
Predicate.inSet HashSet Text
KeywordSet.nonOp Text
a
                then forall a. a -> Maybe a
Just (Text
"Operator is not generic: " forall a. Semigroup a => a -> a -> a
<> Text
a)
                else
                  if (Char -> Bool) -> Text -> Maybe Char
Text.find Char -> Bool
Predicate.prohibitionLiftingOpChar Text
a forall a b. a -> (a -> b) -> b
& forall a. Maybe a -> Bool
isJust
                    then forall a. Maybe a
Nothing
                    else
                      if Char -> Bool
Predicate.prohibitedOpChar (Text -> Char
Text.last Text
a)
                        then forall a. a -> Maybe a
Just (Text
"Operator ends with a prohibited char: " forall a. Semigroup a => a -> a -> a
<> Text
a)
                        else forall a. Maybe a
Nothing