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

import           Zydis.Util

data ISAExt
  = ISAExtInvalid
  | ISAExtAdoxAdcx
  | ISAExtAes
  | ISAExtAmd3Dnow
  | ISAExtAvx
  | ISAExtAvx2
  | ISAExtAvx2Gather
  | ISAExtAvx512Evex
  | ISAExtAvx512Vex
  | ISAExtAvxaes
  | ISAExtBase
  | ISAExtBmi1
  | ISAExtBmi2
  | ISAExtCet
  | ISAExtCldemote
  | ISAExtClflushopt
  | ISAExtClfsh
  | ISAExtClwb
  | ISAExtClzero
  | ISAExtEnqcmd
  | ISAExtF16C
  | ISAExtFma
  | ISAExtFma4
  | ISAExtGfni
  | ISAExtInvpcid
  | ISAExtKnc
  | ISAExtKnce
  | ISAExtKncv
  | ISAExtLongmode
  | ISAExtLzcnt
  | ISAExtMmx
  | ISAExtMonitor
  | ISAExtMonitorx
  | ISAExtMovbe
  | ISAExtMovdir
  | ISAExtMpx
  | ISAExtPadlock
  | ISAExtPause
  | ISAExtPclmulqdq
  | ISAExtPconfig
  | ISAExtPku
  | ISAExtPrefetchwt1
  | ISAExtPt
  | ISAExtRdpid
  | ISAExtRdpru
  | ISAExtRdrand
  | ISAExtRdseed
  | ISAExtRdtscp
  | ISAExtRdwrfsgs
  | ISAExtRtm
  | ISAExtSgx
  | ISAExtSgxEnclv
  | ISAExtSha
  | ISAExtSmap
  | ISAExtSmx
  | ISAExtSse
  | ISAExtSse2
  | ISAExtSse3
  | ISAExtSse4
  | ISAExtSse4A
  | ISAExtSsse3
  | ISAExtSvm
  | ISAExtTbm
  | ISAExtVaes
  | ISAExtVmfunc
  | ISAExtVpclmulqdq
  | ISAExtVtx
  | ISAExtWaitpkg
  | ISAExtX87
  | ISAExtXop
  | ISAExtXsave
  | ISAExtXsavec
  | ISAExtXsaveopt
  | ISAExtXsaves
  deriving stock (Int -> ISAExt -> ShowS
[ISAExt] -> ShowS
ISAExt -> String
(Int -> ISAExt -> ShowS)
-> (ISAExt -> String) -> ([ISAExt] -> ShowS) -> Show ISAExt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ISAExt] -> ShowS
$cshowList :: [ISAExt] -> ShowS
show :: ISAExt -> String
$cshow :: ISAExt -> String
showsPrec :: Int -> ISAExt -> ShowS
$cshowsPrec :: Int -> ISAExt -> ShowS
Show, ISAExt -> ISAExt -> Bool
(ISAExt -> ISAExt -> Bool)
-> (ISAExt -> ISAExt -> Bool) -> Eq ISAExt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ISAExt -> ISAExt -> Bool
$c/= :: ISAExt -> ISAExt -> Bool
== :: ISAExt -> ISAExt -> Bool
$c== :: ISAExt -> ISAExt -> Bool
Eq, ISAExt
ISAExt -> ISAExt -> Bounded ISAExt
forall a. a -> a -> Bounded a
maxBound :: ISAExt
$cmaxBound :: ISAExt
minBound :: ISAExt
$cminBound :: ISAExt
Bounded, Int -> ISAExt
ISAExt -> Int
ISAExt -> [ISAExt]
ISAExt -> ISAExt
ISAExt -> ISAExt -> [ISAExt]
ISAExt -> ISAExt -> ISAExt -> [ISAExt]
(ISAExt -> ISAExt)
-> (ISAExt -> ISAExt)
-> (Int -> ISAExt)
-> (ISAExt -> Int)
-> (ISAExt -> [ISAExt])
-> (ISAExt -> ISAExt -> [ISAExt])
-> (ISAExt -> ISAExt -> [ISAExt])
-> (ISAExt -> ISAExt -> ISAExt -> [ISAExt])
-> Enum ISAExt
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 :: ISAExt -> ISAExt -> ISAExt -> [ISAExt]
$cenumFromThenTo :: ISAExt -> ISAExt -> ISAExt -> [ISAExt]
enumFromTo :: ISAExt -> ISAExt -> [ISAExt]
$cenumFromTo :: ISAExt -> ISAExt -> [ISAExt]
enumFromThen :: ISAExt -> ISAExt -> [ISAExt]
$cenumFromThen :: ISAExt -> ISAExt -> [ISAExt]
enumFrom :: ISAExt -> [ISAExt]
$cenumFrom :: ISAExt -> [ISAExt]
fromEnum :: ISAExt -> Int
$cfromEnum :: ISAExt -> Int
toEnum :: Int -> ISAExt
$ctoEnum :: Int -> ISAExt
pred :: ISAExt -> ISAExt
$cpred :: ISAExt -> ISAExt
succ :: ISAExt -> ISAExt
$csucc :: ISAExt -> ISAExt
Enum)
  deriving Ptr b -> Int -> IO ISAExt
Ptr b -> Int -> ISAExt -> IO ()
Ptr ISAExt -> IO ISAExt
Ptr ISAExt -> Int -> IO ISAExt
Ptr ISAExt -> Int -> ISAExt -> IO ()
Ptr ISAExt -> ISAExt -> IO ()
ISAExt -> Int
(ISAExt -> Int)
-> (ISAExt -> Int)
-> (Ptr ISAExt -> Int -> IO ISAExt)
-> (Ptr ISAExt -> Int -> ISAExt -> IO ())
-> (forall b. Ptr b -> Int -> IO ISAExt)
-> (forall b. Ptr b -> Int -> ISAExt -> IO ())
-> (Ptr ISAExt -> IO ISAExt)
-> (Ptr ISAExt -> ISAExt -> IO ())
-> Storable ISAExt
forall b. Ptr b -> Int -> IO ISAExt
forall b. Ptr b -> Int -> ISAExt -> 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 ISAExt -> ISAExt -> IO ()
$cpoke :: Ptr ISAExt -> ISAExt -> IO ()
peek :: Ptr ISAExt -> IO ISAExt
$cpeek :: Ptr ISAExt -> IO ISAExt
pokeByteOff :: Ptr b -> Int -> ISAExt -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ISAExt -> IO ()
peekByteOff :: Ptr b -> Int -> IO ISAExt
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ISAExt
pokeElemOff :: Ptr ISAExt -> Int -> ISAExt -> IO ()
$cpokeElemOff :: Ptr ISAExt -> Int -> ISAExt -> IO ()
peekElemOff :: Ptr ISAExt -> Int -> IO ISAExt
$cpeekElemOff :: Ptr ISAExt -> Int -> IO ISAExt
alignment :: ISAExt -> Int
$calignment :: ISAExt -> Int
sizeOf :: ISAExt -> Int
$csizeOf :: ISAExt -> Int
Storable via StorableExt ISAExt