-- OperandType.hs ---

-- Copyright (C) 2020 Nerd Ed

-- Author: Nerd Ed <nerded.nerded@gmail.com>

-- This program is free software; you can redistribute it and/or
-- modify it under the terms of the GNU General Public License
-- as published by the Free Software Foundation; either version 3
-- of the License, or (at your option) any later version.

-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-- GNU General Public License for more details.

-- You should have received a copy of the GNU General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.

{-# LANGUAGE DerivingVia #-}

module Zydis.OperandType
  ( OperandType(..)
  )
where

import           Zydis.Util

data OperandType
  = OperandTypeUnused
  | OperandTypeRegister
  | OperandTypeMemory
  | OperandTypePointer
  | OperandTypeImmediate
  deriving stock (Int -> OperandType -> ShowS
[OperandType] -> ShowS
OperandType -> String
(Int -> OperandType -> ShowS)
-> (OperandType -> String)
-> ([OperandType] -> ShowS)
-> Show OperandType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [OperandType] -> ShowS
$cshowList :: [OperandType] -> ShowS
show :: OperandType -> String
$cshow :: OperandType -> String
showsPrec :: Int -> OperandType -> ShowS
$cshowsPrec :: Int -> OperandType -> ShowS
Show, OperandType -> OperandType -> Bool
(OperandType -> OperandType -> Bool)
-> (OperandType -> OperandType -> Bool) -> Eq OperandType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperandType -> OperandType -> Bool
$c/= :: OperandType -> OperandType -> Bool
== :: OperandType -> OperandType -> Bool
$c== :: OperandType -> OperandType -> Bool
Eq, OperandType
OperandType -> OperandType -> Bounded OperandType
forall a. a -> a -> Bounded a
maxBound :: OperandType
$cmaxBound :: OperandType
minBound :: OperandType
$cminBound :: OperandType
Bounded, Int -> OperandType
OperandType -> Int
OperandType -> [OperandType]
OperandType -> OperandType
OperandType -> OperandType -> [OperandType]
OperandType -> OperandType -> OperandType -> [OperandType]
(OperandType -> OperandType)
-> (OperandType -> OperandType)
-> (Int -> OperandType)
-> (OperandType -> Int)
-> (OperandType -> [OperandType])
-> (OperandType -> OperandType -> [OperandType])
-> (OperandType -> OperandType -> [OperandType])
-> (OperandType -> OperandType -> OperandType -> [OperandType])
-> Enum OperandType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: OperandType -> OperandType -> OperandType -> [OperandType]
$cenumFromThenTo :: OperandType -> OperandType -> OperandType -> [OperandType]
enumFromTo :: OperandType -> OperandType -> [OperandType]
$cenumFromTo :: OperandType -> OperandType -> [OperandType]
enumFromThen :: OperandType -> OperandType -> [OperandType]
$cenumFromThen :: OperandType -> OperandType -> [OperandType]
enumFrom :: OperandType -> [OperandType]
$cenumFrom :: OperandType -> [OperandType]
fromEnum :: OperandType -> Int
$cfromEnum :: OperandType -> Int
toEnum :: Int -> OperandType
$ctoEnum :: Int -> OperandType
pred :: OperandType -> OperandType
$cpred :: OperandType -> OperandType
succ :: OperandType -> OperandType
$csucc :: OperandType -> OperandType
Enum)
  deriving Ptr b -> Int -> IO OperandType
Ptr b -> Int -> OperandType -> IO ()
Ptr OperandType -> IO OperandType
Ptr OperandType -> Int -> IO OperandType
Ptr OperandType -> Int -> OperandType -> IO ()
Ptr OperandType -> OperandType -> IO ()
OperandType -> Int
(OperandType -> Int)
-> (OperandType -> Int)
-> (Ptr OperandType -> Int -> IO OperandType)
-> (Ptr OperandType -> Int -> OperandType -> IO ())
-> (forall b. Ptr b -> Int -> IO OperandType)
-> (forall b. Ptr b -> Int -> OperandType -> IO ())
-> (Ptr OperandType -> IO OperandType)
-> (Ptr OperandType -> OperandType -> IO ())
-> Storable OperandType
forall b. Ptr b -> Int -> IO OperandType
forall b. Ptr b -> Int -> OperandType -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
poke :: Ptr OperandType -> OperandType -> IO ()
$cpoke :: Ptr OperandType -> OperandType -> IO ()
peek :: Ptr OperandType -> IO OperandType
$cpeek :: Ptr OperandType -> IO OperandType
pokeByteOff :: Ptr b -> Int -> OperandType -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> OperandType -> IO ()
peekByteOff :: Ptr b -> Int -> IO OperandType
$cpeekByteOff :: forall b. Ptr b -> Int -> IO OperandType
pokeElemOff :: Ptr OperandType -> Int -> OperandType -> IO ()
$cpokeElemOff :: Ptr OperandType -> Int -> OperandType -> IO ()
peekElemOff :: Ptr OperandType -> Int -> IO OperandType
$cpeekElemOff :: Ptr OperandType -> Int -> IO OperandType
alignment :: OperandType -> Int
$calignment :: OperandType -> Int
sizeOf :: OperandType -> Int
$csizeOf :: OperandType -> Int
Storable via StorableExt OperandType