module Data.Streaming.Network.Internal
    ( ServerSettings (..)
    , ClientSettings (..)
    , HostPreference (..)
    , Message (..)
    , AppData (..)
#if !WINDOWS
    , ServerSettingsUnix (..)
    , ClientSettingsUnix (..)
    , AppDataUnix (..)
#endif
    ) where
import Data.String (IsString (..))
import Data.ByteString (ByteString)
import Network.Socket (Socket, SockAddr, Family)
data ServerSettings = ServerSettings
    { serverPort :: !Int
    , serverHost :: !HostPreference
    , serverSocket :: !(Maybe Socket) 
    , serverAfterBind :: !(Socket -> IO ())
    , serverNeedLocalAddr :: !Bool
    , serverReadBufferSize :: !Int
    }
data ClientSettings = ClientSettings
    { clientPort :: !Int
    , clientHost :: !ByteString
    , clientAddrFamily :: !Family
    , clientReadBufferSize :: !Int
    }
data HostPreference =
    HostAny
  | HostIPv4
  | HostIPv4Only
  | HostIPv6
  | HostIPv6Only
  | Host String
    deriving (Eq, Ord, Show, Read)
instance IsString HostPreference where
    fromString "*" = HostAny
    fromString "*4" = HostIPv4
    fromString "!4" = HostIPv4Only
    fromString "*6" = HostIPv6
    fromString "!6" = HostIPv6Only
    fromString s = Host s
#if !WINDOWS
data ServerSettingsUnix = ServerSettingsUnix
    { serverPath :: !FilePath
    , serverAfterBindUnix :: !(Socket -> IO ())
    , serverReadBufferSizeUnix :: !Int
    }
data ClientSettingsUnix = ClientSettingsUnix
    { clientPath :: !FilePath
    , clientReadBufferSizeUnix :: !Int
    }
data AppDataUnix = AppDataUnix
    { appReadUnix :: !(IO ByteString)
    , appWriteUnix :: !(ByteString -> IO ())
    }
#endif
data Message = Message { msgData ::  !ByteString
                       , msgSender :: !SockAddr
                       }
data AppData = AppData
    { appRead' :: !(IO ByteString)
    , appWrite' :: !(ByteString -> IO ())
    , appSockAddr' :: !SockAddr
    , appLocalAddr' :: !(Maybe SockAddr)
    , appCloseConnection' :: !(IO ())
    , appRawSocket' :: Maybe Socket
    }