{-# LINE 1 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}




{-# language DataKinds #-}

-- | Setters for assigning fields of @struct addrinfo@:
--
-- > struct addrinfo {
-- >     int              ai_flags;
-- >     int              ai_family;
-- >     int              ai_socktype;
-- >     int              ai_protocol;
-- >     socklen_t        ai_addrlen;
-- >     struct sockaddr *ai_addr;
-- >     char            *ai_canonname;
-- >     struct addrinfo *ai_next;
-- > };
module Posix.Struct.AddressInfo.Poke
  ( flags
  , family
  , socketType
  , protocol
  , addressLength
  , address
  , next
  ) where

import Posix.Socket.Types (AddressInfoFlags(..),SocketAddress,Family,Type,AddressInfo,Protocol)
import Foreign.C.Types (CInt)
import Foreign.Ptr (Ptr)
import Foreign.Storable (pokeByteOff)

-- | Get @ai_flags@.
flags :: Ptr AddressInfo -> AddressInfoFlags -> IO ()
flags :: Ptr AddressInfo -> AddressInfoFlags -> IO ()
flags Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> AddressInfoFlags -> IO ()
forall b. Ptr b -> Int -> AddressInfoFlags -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
0) Ptr AddressInfo
ptr
{-# LINE 37 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}

-- | Get @ai_family@.
family :: Ptr AddressInfo -> Family -> IO ()
family :: Ptr AddressInfo -> Family -> IO ()
family Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> Family -> IO ()
forall b. Ptr b -> Int -> Family -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
4) Ptr AddressInfo
ptr
{-# LINE 41 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}

-- | Get @ai_socktype@.
socketType :: Ptr AddressInfo -> Type -> IO ()
socketType :: Ptr AddressInfo -> Type -> IO ()
socketType Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> Type -> IO ()
forall b. Ptr b -> Int -> Type -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
8) Ptr AddressInfo
ptr
{-# LINE 45 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}

-- | Get @ai_protocol@.
protocol :: Ptr AddressInfo -> Protocol -> IO ()
protocol :: Ptr AddressInfo -> Protocol -> IO ()
protocol Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> Protocol -> IO ()
forall b. Ptr b -> Int -> Protocol -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
12) Ptr AddressInfo
ptr
{-# LINE 49 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}

-- | Get @ai_addrlen@.
addressLength :: Ptr AddressInfo -> CInt -> IO ()
addressLength :: Ptr AddressInfo -> CInt -> IO ()
addressLength Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> CInt -> IO ()
forall b. Ptr b -> Int -> CInt -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
16) Ptr AddressInfo
ptr
{-# LINE 53 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}

-- | Get @ai_addr@.
address :: Ptr AddressInfo -> Ptr SocketAddress -> IO ()
address :: Ptr AddressInfo -> Ptr SocketAddress -> IO ()
address Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> Ptr SocketAddress -> IO ()
forall b. Ptr b -> Int -> Ptr SocketAddress -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
24) Ptr AddressInfo
ptr
{-# LINE 57 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}

-- | Get @ai_next@.
next :: Ptr AddressInfo -> Ptr AddressInfo -> IO ()
next :: Ptr AddressInfo -> Ptr AddressInfo -> IO ()
next Ptr AddressInfo
ptr = (\Ptr AddressInfo
hsc_ptr -> Ptr AddressInfo -> Int -> Ptr AddressInfo -> IO ()
forall b. Ptr b -> Int -> Ptr AddressInfo -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr AddressInfo
hsc_ptr Int
40) Ptr AddressInfo
ptr
{-# LINE 61 "src/Posix/Struct/AddressInfo/Poke.hsc" #-}