-- OperandMemoryType.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.OperandMemoryType
  ( OperandMemoryType(..)
  )
where

import           Zydis.Util

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