{-# LINE 1 "src-linux/Posix/Socket/Platform.hsc" #-}
{-# language BangPatterns #-}
{-# language DerivingStrategies #-}
{-# language DuplicateRecordFields #-}
{-# language GeneralizedNewtypeDeriving #-}
{-# language MagicHash #-}
{-# language NamedFieldPuns #-}
{-# language UnboxedTuples #-}
{-# language ScopedTypeVariables #-}
module Posix.Socket.Platform
  ( 
    encodeSocketAddressInternet
  , encodeSocketAddressUnix
    
  , decodeSocketAddressInternet
    
  , sizeofSocketAddressInternet
  ) where
import Control.Monad (when)
import Data.Primitive (ByteArray(..),writeByteArray,indexByteArray)
import Data.Word (Word8)
import Foreign.C.Types (CUShort,CInt)
import GHC.Exts (ByteArray#,State#,RealWorld,runRW#)
import GHC.ST (ST(..))
import Posix.Socket.Types (SocketAddress(..))
import Posix.Socket.Types (SocketAddressInternet(..),SocketAddressUnix(..))
import qualified Data.Primitive as PM
import qualified Foreign.Storable as FS
sizeofSocketAddressInternet :: CInt
sizeofSocketAddressInternet = (16)
{-# LINE 44 "src-linux/Posix/Socket/Platform.hsc" #-}
encodeSocketAddressInternet :: SocketAddressInternet -> SocketAddress
encodeSocketAddressInternet (SocketAddressInternet {port, address}) =
  SocketAddress $ runByteArrayST $ unboxByteArrayST $ do
    bs <- PM.newByteArray (16)
{-# LINE 51 "src-linux/Posix/Socket/Platform.hsc" #-}
    
    
    PM.setByteArray bs 0 (16) (0 :: Word8)
{-# LINE 54 "src-linux/Posix/Socket/Platform.hsc" #-}
    
    
    
    
    
    
    (\hsc_arr -> writeByteArray hsc_arr 0) bs (2 :: CUShort)
{-# LINE 61 "src-linux/Posix/Socket/Platform.hsc" #-}
    
    
    (\hsc_arr -> writeByteArray hsc_arr 1) bs port
{-# LINE 64 "src-linux/Posix/Socket/Platform.hsc" #-}
    (\hsc_arr -> writeByteArray hsc_arr 1) bs address
{-# LINE 65 "src-linux/Posix/Socket/Platform.hsc" #-}
    r <- PM.unsafeFreezeByteArray bs
    pure r
decodeSocketAddressInternet :: SocketAddress -> Maybe SocketAddressInternet
decodeSocketAddressInternet (SocketAddress arr) =
  if PM.sizeofByteArray arr == ((16))
{-# LINE 71 "src-linux/Posix/Socket/Platform.hsc" #-}
    
    
    then if ((\hsc_arr -> indexByteArray hsc_arr 0) arr) == (2 :: CUShort)
{-# LINE 74 "src-linux/Posix/Socket/Platform.hsc" #-}
      then Just $ SocketAddressInternet
        { port = (\hsc_arr -> indexByteArray hsc_arr 1) arr
{-# LINE 76 "src-linux/Posix/Socket/Platform.hsc" #-}
        , address = (\hsc_arr -> indexByteArray hsc_arr 1) arr
{-# LINE 77 "src-linux/Posix/Socket/Platform.hsc" #-}
        }
      else Nothing
    else Nothing
encodeSocketAddressUnix :: SocketAddressUnix -> SocketAddress
encodeSocketAddressUnix (SocketAddressUnix !name) =
  SocketAddress $ runByteArrayST $ unboxByteArrayST $ do
    
    
    
    let pathSize = 108 :: Int
    
    
    let familySize = FS.sizeOf (undefined :: CUShort)
    bs <- PM.newByteArray (pathSize + familySize)
    PM.setByteArray bs familySize pathSize (0 :: Word8)
    PM.writeByteArray bs 0 (1 :: CUShort)
{-# LINE 100 "src-linux/Posix/Socket/Platform.hsc" #-}
    let sz = PM.sizeofByteArray name
    when (sz < pathSize) $ do
      PM.copyByteArray bs familySize name 0 sz
    PM.unsafeFreezeByteArray bs
unboxByteArrayST :: ST s ByteArray -> State# s -> (# State# s, ByteArray# #)
unboxByteArrayST (ST f) s = case f s of
  (# s', ByteArray b #) -> (# s', b #)
runByteArrayST :: (State# RealWorld -> (# State# RealWorld, ByteArray# #)) -> ByteArray
runByteArrayST st_rep = case runRW# st_rep of (# _, a #) -> ByteArray a