module ClickHaskell.Connection where
import ClickHaskell.Primitive
import Control.Concurrent (MVar)
import Control.Exception (SomeException, bracketOnError, catch, finally, throwIO)
import Data.Binary.Builder (Builder, toLazyByteString)
import Data.ByteString as BS (ByteString, null)
import Data.IORef (atomicWriteIORef, newIORef, readIORef)
import Data.Maybe (fromMaybe)
import GHC.Exception (Exception)
import Network.Socket
import Network.Socket.ByteString (recv)
import Network.Socket.ByteString.Lazy (sendAll)
import System.Timeout (timeout)
data ConnectionError
= NoAdressResolved
| EstablishTimeout
| ServerClosedConnection
deriving (Int -> ConnectionError -> ShowS
[ConnectionError] -> ShowS
ConnectionError -> String
(Int -> ConnectionError -> ShowS)
-> (ConnectionError -> String)
-> ([ConnectionError] -> ShowS)
-> Show ConnectionError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConnectionError -> ShowS
showsPrec :: Int -> ConnectionError -> ShowS
$cshow :: ConnectionError -> String
show :: ConnectionError -> String
$cshowList :: [ConnectionError] -> ShowS
showList :: [ConnectionError] -> ShowS
Show, Show ConnectionError
Typeable ConnectionError
(Typeable ConnectionError, Show ConnectionError) =>
(ConnectionError -> SomeException)
-> (SomeException -> Maybe ConnectionError)
-> (ConnectionError -> String)
-> (ConnectionError -> Bool)
-> Exception ConnectionError
SomeException -> Maybe ConnectionError
ConnectionError -> Bool
ConnectionError -> String
ConnectionError -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: ConnectionError -> SomeException
toException :: ConnectionError -> SomeException
$cfromException :: SomeException -> Maybe ConnectionError
fromException :: SomeException -> Maybe ConnectionError
$cdisplayException :: ConnectionError -> String
displayException :: ConnectionError -> String
$cbacktraceDesired :: ConnectionError -> Bool
backtraceDesired :: ConnectionError -> Bool
Exception)
data InternalError
= UnexpectedPacketType UVarInt
| DeserializationError String
deriving (Int -> InternalError -> ShowS
[InternalError] -> ShowS
InternalError -> String
(Int -> InternalError -> ShowS)
-> (InternalError -> String)
-> ([InternalError] -> ShowS)
-> Show InternalError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InternalError -> ShowS
showsPrec :: Int -> InternalError -> ShowS
$cshow :: InternalError -> String
show :: InternalError -> String
$cshowList :: [InternalError] -> ShowS
showList :: [InternalError] -> ShowS
Show, Show InternalError
Typeable InternalError
(Typeable InternalError, Show InternalError) =>
(InternalError -> SomeException)
-> (SomeException -> Maybe InternalError)
-> (InternalError -> String)
-> (InternalError -> Bool)
-> Exception InternalError
SomeException -> Maybe InternalError
InternalError -> Bool
InternalError -> String
InternalError -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: InternalError -> SomeException
toException :: InternalError -> SomeException
$cfromException :: SomeException -> Maybe InternalError
fromException :: SomeException -> Maybe InternalError
$cdisplayException :: InternalError -> String
displayException :: InternalError -> String
$cbacktraceDesired :: InternalError -> Bool
backtraceDesired :: InternalError -> Bool
Exception)
writeToConnection :: ConnectionState -> (ProtocolRevision -> Builder) -> IO ()
writeToConnection :: ConnectionState -> (ProtocolRevision -> Builder) -> IO ()
writeToConnection MkConnectionState{ProtocolRevision
revision :: ProtocolRevision
revision :: ConnectionState -> ProtocolRevision
revision, Buffer
buffer :: Buffer
buffer :: ConnectionState -> Buffer
buffer} ProtocolRevision -> Builder
serializer =
(Buffer -> Builder -> IO ()
writeConn Buffer
buffer) (ProtocolRevision -> Builder
serializer ProtocolRevision
revision)
data Connection where MkConnection :: (MVar ConnectionState) -> Connection
data ConnectionState = MkConnectionState
{ ConnectionState -> Buffer
buffer :: Buffer
, ConnectionState -> ProtocolRevision
revision :: ProtocolRevision
, ConnectionState -> ChString
initial_user :: ChString
, ConnectionState -> ChString
os_user :: ChString
, ConnectionState -> ChString
hostname :: ChString
, ConnectionState -> ConnectionArgs
creds :: ConnectionArgs
}
createConnectionState
:: (Buffer -> ConnectionArgs -> IO ConnectionState)
-> ConnectionArgs
-> IO ConnectionState
createConnectionState :: (Buffer -> ConnectionArgs -> IO ConnectionState)
-> ConnectionArgs -> IO ConnectionState
createConnectionState Buffer -> ConnectionArgs -> IO ConnectionState
postInitAction creds :: ConnectionArgs
creds@MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
..} = do
let port :: String
port = String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
defPort Maybe String
mPort
buffer <- BufferArgs -> IO Buffer
mkBuffer (BufferArgs -> IO Buffer) -> IO BufferArgs -> IO Buffer
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> Socket -> IO BufferArgs
mkBufferArgs String
host (Socket -> IO BufferArgs) -> IO Socket -> IO BufferArgs
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< AddrInfo -> IO Socket
initSocket (AddrInfo -> IO Socket) -> IO AddrInfo -> IO Socket
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< String -> String -> IO AddrInfo
resolveHostName String
host String
port
postInitAction buffer creds
recreateConnectionState
:: (Buffer -> ConnectionArgs -> IO ConnectionState)
-> ConnectionState
-> IO ConnectionState
recreateConnectionState :: (Buffer -> ConnectionArgs -> IO ConnectionState)
-> ConnectionState -> IO ConnectionState
recreateConnectionState Buffer -> ConnectionArgs -> IO ConnectionState
postInitAction MkConnectionState{ConnectionArgs
creds :: ConnectionState -> ConnectionArgs
creds :: ConnectionArgs
creds, Buffer
buffer :: ConnectionState -> Buffer
buffer :: Buffer
buffer} = do
Buffer -> IO ()
destroyBuff Buffer
buffer
(Buffer -> ConnectionArgs -> IO ConnectionState)
-> ConnectionArgs -> IO ConnectionState
createConnectionState Buffer -> ConnectionArgs -> IO ConnectionState
postInitAction ConnectionArgs
creds
data Buffer = MkBuffer
{ Buffer -> IO ByteString
readBuff :: IO BS.ByteString
, Buffer -> IO ()
destroyBuff :: IO ()
, Buffer -> ByteString -> IO ()
writeBuff :: BS.ByteString -> IO ()
, Buffer -> Builder -> IO ()
writeConn :: Builder -> IO ()
}
mkBuffer :: BufferArgs -> IO Buffer
mkBuffer :: BufferArgs -> IO Buffer
mkBuffer MkBufferArgs{IO ()
IO ByteString
Builder -> IO ()
readSock :: BufferArgs -> IO ByteString
writeSock :: Builder -> IO ()
readSock :: IO ByteString
closeSock :: IO ()
closeSock :: BufferArgs -> IO ()
writeSock :: BufferArgs -> Builder -> IO ()
..} = do
buff <- ByteString -> IO (IORef ByteString)
forall a. a -> IO (IORef a)
newIORef ByteString
""
let writeBuff ByteString
bs = IORef ByteString -> ByteString -> IO ()
forall a. IORef a -> a -> IO ()
atomicWriteIORef IORef ByteString
buff ByteString
bs
pure MkBuffer
{ writeConn = writeSock
, writeBuff
, readBuff = do
currentBuffer <- readIORef buff
if (not . BS.null) currentBuffer
then writeBuff "" *> pure currentBuffer
else do
sockBytes <- readSock
if BS.null sockBytes
then throwIO ServerClosedConnection
else pure sockBytes
, destroyBuff = do
closeSock
writeBuff ""
}
data BufferArgs = MkBufferArgs
{ BufferArgs -> Builder -> IO ()
writeSock :: Builder -> IO ()
, BufferArgs -> IO ByteString
readSock :: IO ByteString
, BufferArgs -> IO ()
closeSock :: IO ()
}
data ConnectionArgs = MkConnectionArgs
{ ConnectionArgs -> String
user :: String
, ConnectionArgs -> String
pass :: String
, ConnectionArgs -> String
db :: String
, ConnectionArgs -> String
host :: HostName
, ConnectionArgs -> Maybe String
mPort :: Maybe ServiceName
, ConnectionArgs -> String
defPort :: ServiceName
, ConnectionArgs -> ProtocolRevision
maxRevision :: ProtocolRevision
, ConnectionArgs -> Maybe String
mOsUser :: Maybe String
, ConnectionArgs -> Maybe String
mHostname :: Maybe String
, ConnectionArgs -> String -> String -> IO AddrInfo
resolveHostName :: HostName -> ServiceName -> IO AddrInfo
, ConnectionArgs -> String -> Socket -> IO BufferArgs
mkBufferArgs :: HostName -> Socket -> IO BufferArgs
, ConnectionArgs -> AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
}
defaultConnectionArgs :: ConnectionArgs
defaultConnectionArgs :: ConnectionArgs
defaultConnectionArgs = MkConnectionArgs
{ user :: String
user = String
"default"
, pass :: String
pass = String
""
, host :: String
host = String
"localhost"
, db :: String
db = String
"default"
, defPort :: String
defPort = String
"9000"
, mPort :: Maybe String
mPort = Maybe String
forall a. Maybe a
Nothing
, mOsUser :: Maybe String
mOsUser = Maybe String
forall a. Maybe a
Nothing
, mHostname :: Maybe String
mHostname = Maybe String
forall a. Maybe a
Nothing
, maxRevision :: ProtocolRevision
maxRevision = forall (nat :: Nat). KnownNat nat => ProtocolRevision
mkRev @DBMS_TCP_PROTOCOL_VERSION
, resolveHostName :: String -> String -> IO AddrInfo
resolveHostName = String -> String -> IO AddrInfo
defaultResolveHostName
, initSocket :: AddrInfo -> IO Socket
initSocket = AddrInfo -> IO Socket
defaultInitSocket
, mkBufferArgs :: String -> Socket -> IO BufferArgs
mkBufferArgs = String -> Socket -> IO BufferArgs
defaultMkBufferArgs
}
defaultResolveHostName :: HostName -> ServiceName -> IO AddrInfo
defaultResolveHostName :: String -> String -> IO AddrInfo
defaultResolveHostName String
host String
port = do
let hints :: AddrInfo
hints = AddrInfo
defaultHints{addrFlags = [AI_ADDRCONFIG], addrSocketType = Stream}
addrs <- Maybe AddrInfo -> Maybe String -> Maybe String -> IO [AddrInfo]
forall (t :: * -> *).
GetAddrInfo t =>
Maybe AddrInfo -> Maybe String -> Maybe String -> IO (t AddrInfo)
getAddrInfo (AddrInfo -> Maybe AddrInfo
forall a. a -> Maybe a
Just AddrInfo
hints) (String -> Maybe String
forall a. a -> Maybe a
Just String
host) (String -> Maybe String
forall a. a -> Maybe a
Just String
port)
case addrs of
[] -> ConnectionError -> IO AddrInfo
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO ConnectionError
NoAdressResolved
AddrInfo
x:[AddrInfo]
_ -> AddrInfo -> IO AddrInfo
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure AddrInfo
x
defaultInitSocket :: AddrInfo -> IO Socket
defaultInitSocket :: AddrInfo -> IO Socket
defaultInitSocket AddrInfo{[AddrInfoFlag]
Maybe String
ProtocolNumber
SockAddr
Family
SocketType
addrFlags :: AddrInfo -> [AddrInfoFlag]
addrSocketType :: AddrInfo -> SocketType
addrFlags :: [AddrInfoFlag]
addrFamily :: Family
addrSocketType :: SocketType
addrProtocol :: ProtocolNumber
addrAddress :: SockAddr
addrCanonName :: Maybe String
addrCanonName :: AddrInfo -> Maybe String
addrAddress :: AddrInfo -> SockAddr
addrProtocol :: AddrInfo -> ProtocolNumber
addrFamily :: AddrInfo -> Family
..} = do
IO Socket -> (Socket -> IO Socket) -> Maybe Socket -> IO Socket
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (ConnectionError -> IO Socket
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO ConnectionError
EstablishTimeout) Socket -> IO Socket
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe Socket -> IO Socket) -> IO (Maybe Socket) -> IO Socket
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Int -> IO Socket -> IO (Maybe Socket)
forall a. Int -> IO a -> IO (Maybe a)
timeout Int
3_000_000 (
IO Socket
-> (Socket -> IO ()) -> (Socket -> IO Socket) -> IO Socket
forall a b c. IO a -> (a -> IO b) -> (a -> IO c) -> IO c
bracketOnError
(Family -> SocketType -> ProtocolNumber -> IO Socket
socket Family
addrFamily SocketType
addrSocketType ProtocolNumber
addrProtocol)
(\Socket
sock ->
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch @SomeException
(IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
finally (Socket -> ShutdownCmd -> IO ()
shutdown Socket
sock ShutdownCmd
ShutdownBoth) (Socket -> IO ()
close Socket
sock))
(IO () -> SomeException -> IO ()
forall a b. a -> b -> a
const (IO () -> SomeException -> IO ())
-> IO () -> SomeException -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
)
(\Socket
sock -> do
Socket -> SocketOption -> Int -> IO ()
setSocketOption Socket
sock SocketOption
NoDelay Int
1
Socket -> SocketOption -> Int -> IO ()
setSocketOption Socket
sock SocketOption
KeepAlive Int
1
Socket -> SockAddr -> IO ()
connect Socket
sock SockAddr
addrAddress
Socket -> IO Socket
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Socket
sock
)
)
defaultMkBufferArgs :: HostName -> Socket -> IO BufferArgs
defaultMkBufferArgs :: String -> Socket -> IO BufferArgs
defaultMkBufferArgs String
_hostname Socket
sock =
BufferArgs -> IO BufferArgs
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (BufferArgs -> IO BufferArgs) -> BufferArgs -> IO BufferArgs
forall a b. (a -> b) -> a -> b
$
let
writeSock :: Builder -> IO ()
writeSock = Socket -> ByteString -> IO ()
sendAll Socket
sock (ByteString -> IO ())
-> (Builder -> ByteString) -> Builder -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> ByteString
toLazyByteString
readSock :: IO ByteString
readSock = Socket -> Int -> IO ByteString
recv Socket
sock Int
4096
closeSock :: IO ()
closeSock =
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch @SomeException
(IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
finally (Socket -> ShutdownCmd -> IO ()
shutdown Socket
sock ShutdownCmd
ShutdownBoth) (Socket -> IO ()
close Socket
sock))
(IO () -> SomeException -> IO ()
forall a b. a -> b -> a
const (IO () -> SomeException -> IO ())
-> IO () -> SomeException -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
in MkBufferArgs{IO ()
IO ByteString
Builder -> IO ()
readSock :: IO ByteString
closeSock :: IO ()
writeSock :: Builder -> IO ()
writeSock :: Builder -> IO ()
readSock :: IO ByteString
closeSock :: IO ()
..}
setUser :: String -> ConnectionArgs -> ConnectionArgs
setUser :: String -> ConnectionArgs -> ConnectionArgs
setUser String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{user :: String
user=String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
host :: String
db :: String
pass :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
setPassword :: String -> ConnectionArgs -> ConnectionArgs
setPassword :: String -> ConnectionArgs -> ConnectionArgs
setPassword String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{pass :: String
pass=String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
host :: String
db :: String
user :: String
user :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
setHost :: HostName -> ConnectionArgs -> ConnectionArgs
setHost :: String -> ConnectionArgs -> ConnectionArgs
setHost String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{host :: String
host=String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
setPort :: ServiceName -> ConnectionArgs -> ConnectionArgs
setPort :: String -> ConnectionArgs -> ConnectionArgs
setPort String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{mPort :: Maybe String
mPort=String -> Maybe String
forall a. a -> Maybe a
Just String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
host :: String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
host :: String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
setDatabase :: String -> ConnectionArgs -> ConnectionArgs
setDatabase :: String -> ConnectionArgs -> ConnectionArgs
setDatabase String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{db :: String
db=String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
host :: String
pass :: String
user :: String
user :: String
pass :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
overrideHostname :: String -> ConnectionArgs -> ConnectionArgs
overrideHostname :: String -> ConnectionArgs -> ConnectionArgs
overrideHostname String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{mHostname :: Maybe String
mHostname=String -> Maybe String
forall a. a -> Maybe a
Just String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
host :: String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
overrideOsUser :: String -> ConnectionArgs -> ConnectionArgs
overrideOsUser :: String -> ConnectionArgs -> ConnectionArgs
overrideOsUser String
new MkConnectionArgs{String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} = MkConnectionArgs{mOsUser :: Maybe String
mOsUser=String -> Maybe String
forall a. a -> Maybe a
Just String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
host :: String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
overrideInitConnection :: (HostName -> Socket -> IO BufferArgs) -> (ConnectionArgs -> ConnectionArgs)
overrideInitConnection :: (String -> Socket -> IO BufferArgs)
-> ConnectionArgs -> ConnectionArgs
overrideInitConnection String -> Socket -> IO BufferArgs
new MkConnectionArgs {String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} =
MkConnectionArgs{mkBufferArgs :: String -> Socket -> IO BufferArgs
mkBufferArgs = String -> Socket -> IO BufferArgs
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
defPort :: String
mPort :: Maybe String
host :: String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
initSocket :: AddrInfo -> IO Socket
..}
overrideDefaultPort :: ServiceName -> (ConnectionArgs -> ConnectionArgs)
overrideDefaultPort :: String -> ConnectionArgs -> ConnectionArgs
overrideDefaultPort String
new MkConnectionArgs {String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} =
MkConnectionArgs {defPort :: String
defPort = String
new, String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
maxRevision :: ProtocolRevision
mPort :: Maybe String
host :: String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}
overrideMaxRevision :: ProtocolRevision -> (ConnectionArgs -> ConnectionArgs)
overrideMaxRevision :: ProtocolRevision -> ConnectionArgs -> ConnectionArgs
overrideMaxRevision ProtocolRevision
new MkConnectionArgs {String
Maybe String
ProtocolRevision
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: ConnectionArgs -> AddrInfo -> IO Socket
mkBufferArgs :: ConnectionArgs -> String -> Socket -> IO BufferArgs
resolveHostName :: ConnectionArgs -> String -> String -> IO AddrInfo
mHostname :: ConnectionArgs -> Maybe String
mOsUser :: ConnectionArgs -> Maybe String
maxRevision :: ConnectionArgs -> ProtocolRevision
defPort :: ConnectionArgs -> String
mPort :: ConnectionArgs -> Maybe String
host :: ConnectionArgs -> String
db :: ConnectionArgs -> String
pass :: ConnectionArgs -> String
user :: ConnectionArgs -> String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
maxRevision :: ProtocolRevision
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..} =
MkConnectionArgs {maxRevision :: ProtocolRevision
maxRevision = ProtocolRevision
new, String
Maybe String
String -> String -> IO AddrInfo
String -> Socket -> IO BufferArgs
AddrInfo -> IO Socket
initSocket :: AddrInfo -> IO Socket
mkBufferArgs :: String -> Socket -> IO BufferArgs
resolveHostName :: String -> String -> IO AddrInfo
mHostname :: Maybe String
mOsUser :: Maybe String
defPort :: String
mPort :: Maybe String
host :: String
db :: String
pass :: String
user :: String
user :: String
pass :: String
db :: String
host :: String
mPort :: Maybe String
defPort :: String
mOsUser :: Maybe String
mHostname :: Maybe String
resolveHostName :: String -> String -> IO AddrInfo
mkBufferArgs :: String -> Socket -> IO BufferArgs
initSocket :: AddrInfo -> IO Socket
..}