module Data.EasyTpl.Types where

import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Aeson (Value)

-- | Compiled template.
newtype Template = Template [TemplateToken]        -- ^ Template consists of tokens
                   deriving (Show, Eq)

-- | Template token.
data TemplateToken = ContentToken ByteString       -- ^ Chunk or raw content as is
                   | LiteralToken Expression       -- ^ Computable expression for substitution
                   | ControlToken Control Template -- ^ Control block structure with sub-template
                     deriving (Show, Eq)

-- | Control structure.
data Control = Condition Expression                -- ^ Conditional statement with expression
             | Iteration (Text, Text) Expression   -- ^ Iterational statement with variables and expression
               deriving (Show, Eq)

-- | Expression.
data Expression = Constant Value                   --
                | Variable Text
                | Range Expression Expression Expression
#ifdef WITH_REGEX
                | Regexp ByteString Bool Bool
#endif
                | UnaryOperation UnaryOperator Expression
                | BinaryOperation BinaryOperator Expression Expression
                deriving (Show, Eq)

-- | Unary operator
data UnaryOperator = GetLength -- ^ Length operator `#` (#value)
                   | Stringify -- ^ Stringify operator `\@` (\@value)
                   | Evaluate  -- ^ Evaluate operator `=` (value=)
                   | LogicNot  -- ^ Logical not operator `!` (!value)
                   | Negate    -- ^ Numeric negate operator `-` (-value)
                   | ToNumber  -- ^ Numeric cast operator `+` (+value)
                   | NotNull   -- ^ Not null test operator `?` (value?)
                   deriving (Show, Eq)

-- | Binary operator
data BinaryOperator = LogicOr    -- ^ Logical or operator `||`
                    | LogicAnd   -- ^ Logical and operator `&&`
                    | Equal      -- ^ Generic equality operator `==`
                    | NotEqual   -- ^ Generic non-equality operator `!=`
                    | LessThan   -- ^ Lesser than operator `<`
                    | GreatThan  -- ^ Greater than operator `>`
                    | LessEqual  -- ^ Lesser or equal operator `<=`
                    | GreatEqual -- ^ Greater or equal operator `>=`
                    | Substract  -- ^ Numeric substract operator `-`
                    | Append     -- ^ Generic append operator `+`
                    | Multiply   -- ^ Generic multiply operator `*`
                    | Divide     -- ^ Generic divide operator `/`
                    | IntDivide  -- ^ Generic integral divide operator `:`
                    | Module     -- ^ Numeric module operator `%`
                    | Power      -- ^ Numeric power operator `^`
                    | GetField   -- ^ Container get field operator `.` | `[` `]` (object.field, object[field_name], array[index])
#ifdef WITH_REGEX
                    | RegexTest  -- ^ Regular expression test operator `~` (string ~ /regex/ => bool)
                    | RegexMatch -- ^ Regular expression match operator `~>` (string ~> /regex/ => null | [matches])
                    | RegexSplit -- ^ Regular expression split operator `~:` (string ~: /regex/ => [pieces])
#endif
                    deriving (Show, Eq)