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

import           Zydis.Util

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