-- | WebAssembly features.
--
-- See <https://github.com/WebAssembly/binaryen/blob/master/src/binaryen-c.h>
-- for API documentation.
--
-- This module is intended to be imported qualified.

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

module Binaryen.Features where

import Data.Bits (Bits)
import Data.Word (Word32)
import Foreign (Storable)

newtype Features = Features Word32
  deriving (Eq Features
Features
Eq Features
-> (Features -> Features -> Features)
-> (Features -> Features -> Features)
-> (Features -> Features -> Features)
-> (Features -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> Features
-> (Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Bool)
-> (Features -> Maybe Int)
-> (Features -> Int)
-> (Features -> Bool)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int -> Features)
-> (Features -> Int)
-> Bits Features
Int -> Features
Features -> Bool
Features -> Int
Features -> Maybe Int
Features -> Features
Features -> Int -> Bool
Features -> Int -> Features
Features -> Features -> Features
forall a.
Eq a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
popCount :: Features -> Int
$cpopCount :: Features -> Int
rotateR :: Features -> Int -> Features
$crotateR :: Features -> Int -> Features
rotateL :: Features -> Int -> Features
$crotateL :: Features -> Int -> Features
unsafeShiftR :: Features -> Int -> Features
$cunsafeShiftR :: Features -> Int -> Features
shiftR :: Features -> Int -> Features
$cshiftR :: Features -> Int -> Features
unsafeShiftL :: Features -> Int -> Features
$cunsafeShiftL :: Features -> Int -> Features
shiftL :: Features -> Int -> Features
$cshiftL :: Features -> Int -> Features
isSigned :: Features -> Bool
$cisSigned :: Features -> Bool
bitSize :: Features -> Int
$cbitSize :: Features -> Int
bitSizeMaybe :: Features -> Maybe Int
$cbitSizeMaybe :: Features -> Maybe Int
testBit :: Features -> Int -> Bool
$ctestBit :: Features -> Int -> Bool
complementBit :: Features -> Int -> Features
$ccomplementBit :: Features -> Int -> Features
clearBit :: Features -> Int -> Features
$cclearBit :: Features -> Int -> Features
setBit :: Features -> Int -> Features
$csetBit :: Features -> Int -> Features
bit :: Int -> Features
$cbit :: Int -> Features
zeroBits :: Features
$czeroBits :: Features
rotate :: Features -> Int -> Features
$crotate :: Features -> Int -> Features
shift :: Features -> Int -> Features
$cshift :: Features -> Int -> Features
complement :: Features -> Features
$ccomplement :: Features -> Features
xor :: Features -> Features -> Features
$cxor :: Features -> Features -> Features
.|. :: Features -> Features -> Features
$c.|. :: Features -> Features -> Features
.&. :: Features -> Features -> Features
$c.&. :: Features -> Features -> Features
$cp1Bits :: Eq Features
Bits, Features -> Features -> Bool
(Features -> Features -> Bool)
-> (Features -> Features -> Bool) -> Eq Features
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Features -> Features -> Bool
$c/= :: Features -> Features -> Bool
== :: Features -> Features -> Bool
$c== :: Features -> Features -> Bool
Eq, Int -> Features -> ShowS
[Features] -> ShowS
Features -> String
(Int -> Features -> ShowS)
-> (Features -> String) -> ([Features] -> ShowS) -> Show Features
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Features] -> ShowS
$cshowList :: [Features] -> ShowS
show :: Features -> String
$cshow :: Features -> String
showsPrec :: Int -> Features -> ShowS
$cshowsPrec :: Int -> Features -> ShowS
Show, Ptr b -> Int -> IO Features
Ptr b -> Int -> Features -> IO ()
Ptr Features -> IO Features
Ptr Features -> Int -> IO Features
Ptr Features -> Int -> Features -> IO ()
Ptr Features -> Features -> IO ()
Features -> Int
(Features -> Int)
-> (Features -> Int)
-> (Ptr Features -> Int -> IO Features)
-> (Ptr Features -> Int -> Features -> IO ())
-> (forall b. Ptr b -> Int -> IO Features)
-> (forall b. Ptr b -> Int -> Features -> IO ())
-> (Ptr Features -> IO Features)
-> (Ptr Features -> Features -> IO ())
-> Storable Features
forall b. Ptr b -> Int -> IO Features
forall b. Ptr b -> Int -> Features -> 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 Features -> Features -> IO ()
$cpoke :: Ptr Features -> Features -> IO ()
peek :: Ptr Features -> IO Features
$cpeek :: Ptr Features -> IO Features
pokeByteOff :: Ptr b -> Int -> Features -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Features -> IO ()
peekByteOff :: Ptr b -> Int -> IO Features
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Features
pokeElemOff :: Ptr Features -> Int -> Features -> IO ()
$cpokeElemOff :: Ptr Features -> Int -> Features -> IO ()
peekElemOff :: Ptr Features -> Int -> IO Features
$cpeekElemOff :: Ptr Features -> Int -> IO Features
alignment :: Features -> Int
$calignment :: Features -> Int
sizeOf :: Features -> Int
$csizeOf :: Features -> Int
Storable)

foreign import ccall unsafe "BinaryenFeatureMVP" mvp :: Features
foreign import ccall unsafe "BinaryenFeatureAtomics" atomics :: Features
foreign import ccall unsafe "BinaryenFeatureBulkMemory" bulkMemory :: Features
foreign import ccall unsafe "BinaryenFeatureMutableGlobals" mutableGlobals :: Features
foreign import ccall unsafe "BinaryenFeatureNontrappingFPToInt" nontrappingFPToInt :: Features
foreign import ccall unsafe "BinaryenFeatureSignExt" signExt :: Features
foreign import ccall unsafe "BinaryenFeatureSIMD128" simd128 :: Features
foreign import ccall unsafe "BinaryenFeatureExceptionHandling" exceptionHandling :: Features
foreign import ccall unsafe "BinaryenFeatureTailCall" tailCall :: Features
foreign import ccall unsafe "BinaryenFeatureReferenceTypes" referenceTypes :: Features
foreign import ccall unsafe "BinaryenFeatureAll" all :: Features