-- | Exports.
--
-- 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.Export where

import Binaryen.ExternalKind
import Foreign (Ptr, Storable)
import Foreign.C (CChar)

newtype Export = Export (Ptr Export)
  deriving (Export -> Export -> Bool
(Export -> Export -> Bool)
-> (Export -> Export -> Bool) -> Eq Export
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Export -> Export -> Bool
$c/= :: Export -> Export -> Bool
== :: Export -> Export -> Bool
$c== :: Export -> Export -> Bool
Eq, Int -> Export -> ShowS
[Export] -> ShowS
Export -> String
(Int -> Export -> ShowS)
-> (Export -> String) -> ([Export] -> ShowS) -> Show Export
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Export] -> ShowS
$cshowList :: [Export] -> ShowS
show :: Export -> String
$cshow :: Export -> String
showsPrec :: Int -> Export -> ShowS
$cshowsPrec :: Int -> Export -> ShowS
Show, Ptr b -> Int -> IO Export
Ptr b -> Int -> Export -> IO ()
Ptr Export -> IO Export
Ptr Export -> Int -> IO Export
Ptr Export -> Int -> Export -> IO ()
Ptr Export -> Export -> IO ()
Export -> Int
(Export -> Int)
-> (Export -> Int)
-> (Ptr Export -> Int -> IO Export)
-> (Ptr Export -> Int -> Export -> IO ())
-> (forall b. Ptr b -> Int -> IO Export)
-> (forall b. Ptr b -> Int -> Export -> IO ())
-> (Ptr Export -> IO Export)
-> (Ptr Export -> Export -> IO ())
-> Storable Export
forall b. Ptr b -> Int -> IO Export
forall b. Ptr b -> Int -> Export -> 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 Export -> Export -> IO ()
$cpoke :: Ptr Export -> Export -> IO ()
peek :: Ptr Export -> IO Export
$cpeek :: Ptr Export -> IO Export
pokeByteOff :: Ptr b -> Int -> Export -> IO ()
$cpokeByteOff :: forall b. Ptr b -> Int -> Export -> IO ()
peekByteOff :: Ptr b -> Int -> IO Export
$cpeekByteOff :: forall b. Ptr b -> Int -> IO Export
pokeElemOff :: Ptr Export -> Int -> Export -> IO ()
$cpokeElemOff :: Ptr Export -> Int -> Export -> IO ()
peekElemOff :: Ptr Export -> Int -> IO Export
$cpeekElemOff :: Ptr Export -> Int -> IO Export
alignment :: Export -> Int
$calignment :: Export -> Int
sizeOf :: Export -> Int
$csizeOf :: Export -> Int
Storable)

foreign import ccall unsafe "BinaryenExportGetKind"
  getKind ::
    Export -> IO ExternalKind

foreign import ccall unsafe "BinaryenExportGetName"
  getName ::
    Export -> IO (Ptr CChar)

foreign import ccall unsafe "BinaryenExportGetValue"
  getValue ::
    Export -> IO (Ptr CChar)