{-# LANGUAGE OverloadedStrings #-} {-| Module : HsLua.ObjectOrientation.Operation Copyright : © 2020-2021 Albert Krewinkel License : MIT Maintainer : Albert Krewinkel <tarleb+hslua@zeitkraut.de> Binary and unary object operations. -} module HsLua.ObjectOrientation.Operation ( Operation (..) , metamethodName ) where import HsLua.Core (Name) -- | Lua metadata operation types. data Operation = Add -- ^ the addition (@+@) operation. If any operand for an -- addition is not a number (nor a string coercible to a -- number), Lua will try to call a metamethod. First, Lua will -- check the first operand (even if it is valid). If that -- operand does not define a metamethod for @__add@, then Lua -- will check the second operand. If Lua can find a -- metamethod, it calls the metamethod with the two operands -- as arguments, and the result of the call (adjusted to one -- value) is the result of the operation. Otherwise, it raises -- an error. | Sub -- ^ the subtraction (@-@) operation. Behavior similar to the -- addition operation. | Mul -- ^ the multiplication (@*@) operation. Behavior similar to the -- addition operation. | Div -- ^ the division (@/@) operation. Behavior similar to the -- addition operation. | Mod -- ^ the modulo (@%@) operation. Behavior similar to the -- addition operation. | Pow -- ^ the exponentiation (@^@) operation. Behavior similar to the -- addition operation. | Unm -- ^ the negation (unary @-@) operation. Behavior similar to the -- addition operation. | Idiv -- ^ the floor division (@//@) operation. Behavior similar to -- the addition operation. | Band -- ^ the bitwise AND (@&@) operation. Behavior similar to the -- addition operation, except that Lua will try a metamethod -- if any operand is neither an integer nor a value coercible -- to an integer (see §3.4.3). | Bor -- ^ the bitwise OR (@|@) operation. Behavior similar to the -- bitwise AND operation. | Bxor -- ^ the bitwise exclusive OR (binary @~@) operation. Behavior -- similar to the bitwise AND operation. | Bnot -- ^ the bitwise NOT (unary @~@) operation. Behavior similar to -- the bitwise AND operation. | Shl -- ^ the bitwise left shift (@<<@) operation. Behavior similar -- to the bitwise AND operation. | Shr -- ^ the bitwise right shift (@>>@) operation. Behavior -- similar to the bitwise AND operation. | Concat -- ^ the concatenation (@..@) operation. Behavior similar to -- the addition operation, except that Lua will try a -- metamethod if any operand is neither a string nor a number -- (which is always coercible to a string). | Len -- ^ the length (@#@) operation. If the object is not a string, -- Lua will try its metamethod. If there is a metamethod, Lua -- calls it with the object as argument, and the result of the -- call (always adjusted to one value) is the result of the -- operation. If there is no metamethod but the object is a -- table, then Lua uses the table length operation (see -- §3.4.7). Otherwise, Lua raises an error. | Eq -- ^ the equal (@==@) operation. Behavior similar to the -- addition operation, except that Lua will try a metamethod -- only when the values being compared are either both tables -- or both full userdata and they are not primitively equal. -- The result of the call is always converted to a boolean. | Lt -- ^ the less than (@<@) operation. Behavior similar to the -- addition operation, except that Lua will try a metamethod -- only when the values being compared are neither both -- numbers nor both strings. The result of the call is always -- converted to a boolean. | Le -- ^ the less equal (@<=@) operation. Unlike other operations, -- the less-equal operation can use two different events. -- First, Lua looks for the @__le@ metamethod in both -- operands, like in the less than operation. If it cannot -- find such a metamethod, then it will try the @__lt@ -- metamethod, assuming that a <= b is equivalent to not (b < -- a). As with the other comparison operators, the result is -- always a boolean. (This use of the @__lt@ event can be -- removed in future versions; it is also slower than a real -- __le metamethod.) | Index -- ^ The indexing access operation @table[key]@. This event -- happens when table is not a table or when key is not -- present in table. The metamethod is looked up in table. | Newindex -- ^ The indexing assignment @table[key] = value@. Like the -- index event, this event happens when table is not a table -- or when key is not present in table. The metamethod is -- looked up in table. | Call -- ^ The call operation @func(args)@. This event happens when -- Lua tries to call a non-function value (that is, func is -- not a function). The metamethod is looked up in func. If -- present, the metamethod is called with func as its first -- argument, followed by the arguments of the original call -- (args). All results of the call are the result of the -- operation. (This is the only metamethod that allows -- multiple results.) | Tostring -- ^ The operation used to create a string representation of -- the object. | Pairs -- ^ the operation of iterating over the object's key-value -- pairs. | CustomOperation Name -- ^ a custom operation, with the metamethod name as -- parameter. deriving (Operation -> Operation -> Bool (Operation -> Operation -> Bool) -> (Operation -> Operation -> Bool) -> Eq Operation forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: Operation -> Operation -> Bool $c/= :: Operation -> Operation -> Bool == :: Operation -> Operation -> Bool $c== :: Operation -> Operation -> Bool Eq, Eq Operation Eq Operation -> (Operation -> Operation -> Ordering) -> (Operation -> Operation -> Bool) -> (Operation -> Operation -> Bool) -> (Operation -> Operation -> Bool) -> (Operation -> Operation -> Bool) -> (Operation -> Operation -> Operation) -> (Operation -> Operation -> Operation) -> Ord Operation Operation -> Operation -> Bool Operation -> Operation -> Ordering Operation -> Operation -> Operation forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: Operation -> Operation -> Operation $cmin :: Operation -> Operation -> Operation max :: Operation -> Operation -> Operation $cmax :: Operation -> Operation -> Operation >= :: Operation -> Operation -> Bool $c>= :: Operation -> Operation -> Bool > :: Operation -> Operation -> Bool $c> :: Operation -> Operation -> Bool <= :: Operation -> Operation -> Bool $c<= :: Operation -> Operation -> Bool < :: Operation -> Operation -> Bool $c< :: Operation -> Operation -> Bool compare :: Operation -> Operation -> Ordering $ccompare :: Operation -> Operation -> Ordering $cp1Ord :: Eq Operation Ord, Int -> Operation -> ShowS [Operation] -> ShowS Operation -> String (Int -> Operation -> ShowS) -> (Operation -> String) -> ([Operation] -> ShowS) -> Show Operation forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [Operation] -> ShowS $cshowList :: [Operation] -> ShowS show :: Operation -> String $cshow :: Operation -> String showsPrec :: Int -> Operation -> ShowS $cshowsPrec :: Int -> Operation -> ShowS Show) -- | Returns the metamethod name used to control this operation. metamethodName :: Operation -> Name metamethodName :: Operation -> Name metamethodName = \case Operation Add -> Name "__add" Operation Sub -> Name "__sub" Operation Mul -> Name "__mul" Operation Div -> Name "__div" Operation Mod -> Name "__mod" Operation Pow -> Name "__pow" Operation Unm -> Name "__unm" Operation Idiv -> Name "__idiv" Operation Band -> Name "__band" Operation Bor -> Name "__bor" Operation Bxor -> Name "__bxor" Operation Bnot -> Name "__bnot" Operation Shl -> Name "__shl" Operation Shr -> Name "__shr" Operation Concat -> Name "__concat" Operation Len -> Name "__len" Operation Eq -> Name "__eq" Operation Lt -> Name "__lt" Operation Le -> Name "__le" Operation Index -> Name "__index" Operation Newindex -> Name "__newindex" Operation Call -> Name "__call" Operation Tostring -> Name "__tostring" Operation Pairs -> Name "__pairs" CustomOperation Name x -> Name x