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

import           Zydis.Util

data ExceptionClass
  = ExceptionClassNone
  | ExceptionClassSse1
  | ExceptionClassSse2
  | ExceptionClassSse3
  | ExceptionClassSse4
  | ExceptionClassSse5
  | ExceptionClassSse7
  | ExceptionClassAvx1
  | ExceptionClassAvx2
  | ExceptionClassAvx3
  | ExceptionClassAvx4
  | ExceptionClassAvx5
  | ExceptionClassAvx6
  | ExceptionClassAvx7
  | ExceptionClassAvx8
  | ExceptionClassAvx11
  | ExceptionClassAvx12
  | ExceptionClassE1
  | ExceptionClassE1Nf
  | ExceptionClassE2
  | ExceptionClassE2Nf
  | ExceptionClassE3
  | ExceptionClassE3Nf
  | ExceptionClassE4
  | ExceptionClassE4Nf
  | ExceptionClassE5
  | ExceptionClassE5Nf
  | ExceptionClassE6
  | ExceptionClassE6Nf
  | ExceptionClassE7Nm
  | ExceptionClassE7Nm128
  | ExceptionClassE9Nf
  | ExceptionClassE10
  | ExceptionClassE10Nf
  | ExceptionClassE11
  | ExceptionClassE11Nf
  | ExceptionClassE12
  | ExceptionClassE12Np
  | ExceptionClassK20
  | ExceptionClassK21
  deriving stock (Int -> ExceptionClass -> ShowS
[ExceptionClass] -> ShowS
ExceptionClass -> String
(Int -> ExceptionClass -> ShowS)
-> (ExceptionClass -> String)
-> ([ExceptionClass] -> ShowS)
-> Show ExceptionClass
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExceptionClass] -> ShowS
$cshowList :: [ExceptionClass] -> ShowS
show :: ExceptionClass -> String
$cshow :: ExceptionClass -> String
showsPrec :: Int -> ExceptionClass -> ShowS
$cshowsPrec :: Int -> ExceptionClass -> ShowS
Show, ExceptionClass -> ExceptionClass -> Bool
(ExceptionClass -> ExceptionClass -> Bool)
-> (ExceptionClass -> ExceptionClass -> Bool) -> Eq ExceptionClass
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExceptionClass -> ExceptionClass -> Bool
$c/= :: ExceptionClass -> ExceptionClass -> Bool
== :: ExceptionClass -> ExceptionClass -> Bool
$c== :: ExceptionClass -> ExceptionClass -> Bool
Eq, ExceptionClass
ExceptionClass -> ExceptionClass -> Bounded ExceptionClass
forall a. a -> a -> Bounded a
maxBound :: ExceptionClass
$cmaxBound :: ExceptionClass
minBound :: ExceptionClass
$cminBound :: ExceptionClass
Bounded, Int -> ExceptionClass
ExceptionClass -> Int
ExceptionClass -> [ExceptionClass]
ExceptionClass -> ExceptionClass
ExceptionClass -> ExceptionClass -> [ExceptionClass]
ExceptionClass
-> ExceptionClass -> ExceptionClass -> [ExceptionClass]
(ExceptionClass -> ExceptionClass)
-> (ExceptionClass -> ExceptionClass)
-> (Int -> ExceptionClass)
-> (ExceptionClass -> Int)
-> (ExceptionClass -> [ExceptionClass])
-> (ExceptionClass -> ExceptionClass -> [ExceptionClass])
-> (ExceptionClass -> ExceptionClass -> [ExceptionClass])
-> (ExceptionClass
    -> ExceptionClass -> ExceptionClass -> [ExceptionClass])
-> Enum ExceptionClass
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 :: ExceptionClass
-> ExceptionClass -> ExceptionClass -> [ExceptionClass]
$cenumFromThenTo :: ExceptionClass
-> ExceptionClass -> ExceptionClass -> [ExceptionClass]
enumFromTo :: ExceptionClass -> ExceptionClass -> [ExceptionClass]
$cenumFromTo :: ExceptionClass -> ExceptionClass -> [ExceptionClass]
enumFromThen :: ExceptionClass -> ExceptionClass -> [ExceptionClass]
$cenumFromThen :: ExceptionClass -> ExceptionClass -> [ExceptionClass]
enumFrom :: ExceptionClass -> [ExceptionClass]
$cenumFrom :: ExceptionClass -> [ExceptionClass]
fromEnum :: ExceptionClass -> Int
$cfromEnum :: ExceptionClass -> Int
toEnum :: Int -> ExceptionClass
$ctoEnum :: Int -> ExceptionClass
pred :: ExceptionClass -> ExceptionClass
$cpred :: ExceptionClass -> ExceptionClass
succ :: ExceptionClass -> ExceptionClass
$csucc :: ExceptionClass -> ExceptionClass
Enum)
  deriving Ptr b -> Int -> IO ExceptionClass
Ptr b -> Int -> ExceptionClass -> IO ()
Ptr ExceptionClass -> IO ExceptionClass
Ptr ExceptionClass -> Int -> IO ExceptionClass
Ptr ExceptionClass -> Int -> ExceptionClass -> IO ()
Ptr ExceptionClass -> ExceptionClass -> IO ()
ExceptionClass -> Int
(ExceptionClass -> Int)
-> (ExceptionClass -> Int)
-> (Ptr ExceptionClass -> Int -> IO ExceptionClass)
-> (Ptr ExceptionClass -> Int -> ExceptionClass -> IO ())
-> (forall b. Ptr b -> Int -> IO ExceptionClass)
-> (forall b. Ptr b -> Int -> ExceptionClass -> IO ())
-> (Ptr ExceptionClass -> IO ExceptionClass)
-> (Ptr ExceptionClass -> ExceptionClass -> IO ())
-> Storable ExceptionClass
forall b. Ptr b -> Int -> IO ExceptionClass
forall b. Ptr b -> Int -> ExceptionClass -> 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 ExceptionClass -> ExceptionClass -> IO ()
$cpoke :: Ptr ExceptionClass -> ExceptionClass -> IO ()
peek :: Ptr ExceptionClass -> IO ExceptionClass
$cpeek :: Ptr ExceptionClass -> IO ExceptionClass
pokeByteOff :: Ptr b -> Int -> ExceptionClass -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> ExceptionClass -> IO ()
peekByteOff :: Ptr b -> Int -> IO ExceptionClass
$cpeekByteOff :: forall b. Ptr b -> Int -> IO ExceptionClass
pokeElemOff :: Ptr ExceptionClass -> Int -> ExceptionClass -> IO ()
$cpokeElemOff :: Ptr ExceptionClass -> Int -> ExceptionClass -> IO ()
peekElemOff :: Ptr ExceptionClass -> Int -> IO ExceptionClass
$cpeekElemOff :: Ptr ExceptionClass -> Int -> IO ExceptionClass
alignment :: ExceptionClass -> Int
$calignment :: ExceptionClass -> Int
sizeOf :: ExceptionClass -> Int
$csizeOf :: ExceptionClass -> Int
Storable via StorableExt ExceptionClass