hookup-0.2.3/0000755000000000000000000000000007346545000011212 5ustar0000000000000000hookup-0.2.3/ChangeLog.md0000755000000000000000000000104707346545000013370 0ustar0000000000000000# Revision history for hookup ## 0.2.3 -- 2019-05 * Added functions to get TLS peer certificate information ## 0.2.1 -- 2018-07 * Added `connectWithSocket`, `recv`, `putBuf`, `defaultTlsParams` ## 0.2 -- 2017-11-22 * Allow connection parameters to specify address family with `cpFamily` field ## 0.1.1.0 -- 2017-05-13 * Better error message for old openssl version * Nicer displayedExceptions * Dropped unused template-haskell dependency * More haddock comments ## 0.1.0.0 -- 2016-10-05 * First version. Released on an unsuspecting world. hookup-0.2.3/LICENSE0000644000000000000000000000133207346545000012216 0ustar0000000000000000Copyright (c) 2016 Eric Mertens Permission to use, copy, modify, and/or distribute this software for any purpose with or without fee is hereby granted, provided that the above copyright notice and this permission notice appear in all copies. THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. hookup-0.2.3/Setup.hs0000644000000000000000000000005607346545000012647 0ustar0000000000000000import Distribution.Simple main = defaultMain hookup-0.2.3/hookup.cabal0000644000000000000000000000264707346545000013514 0ustar0000000000000000name: hookup version: 0.2.3 synopsis: Abstraction over creating network connections with SOCKS5 and TLS description: This package provides an abstraction for communicating with line-oriented network services while abstracting over the use of SOCKS5 and TLS (via OpenSSL) license: ISC license-file: LICENSE author: Eric Mertens maintainer: emertens@gmail.com copyright: 2016 Eric Mertens category: Network build-type: Simple extra-source-files: ChangeLog.md homepage: https://github.com/glguy/irc-core bug-reports: https://github.com/glguy/irc-core/issues tested-with: GHC==8.0.2 cabal-version: >=1.10 source-repository head type: git location: git://github.com/glguy/irc-core.git branch: v2 library exposed-modules: Hookup other-modules: Hookup.OpenSSL, Hookup.Socks5 extra-libraries: ssl build-depends: base >=4.9 && <4.13, network >=2.6 && <3.1, bytestring >=0.10 && <0.11, attoparsec >=0.13 && <0.14, HsOpenSSL >=0.11.2.3 && <0.12, HsOpenSSL-x509-system >=0.1 && <0.2 hs-source-dirs: src default-language: Haskell2010 hookup-0.2.3/src/0000755000000000000000000000000007346545000012001 5ustar0000000000000000hookup-0.2.3/src/Hookup.hs0000644000000000000000000005020007346545000013577 0ustar0000000000000000{-| Module : Hookup Description : Network connections generalized over TLS and SOCKS Copyright : (c) Eric Mertens, 2016 License : ISC Maintainer : emertens@gmail.com This module provides a uniform interface to network connections with optional support for TLS and SOCKS. This library is careful to support both IPv4 and IPv6. It will attempt to all of the addresses that a domain name resolves to until one the first successful connection. Use 'connect' and 'close' to establish and close network connections. Use 'recv', 'recvLine', and 'send' to receive and transmit data on an open network connection. TLS and SOCKS parameters can be provided. When both are provided a connection will first be established to the SOCKS server and then the TLS connection will be established through that proxy server. This is most useful when connecting through a dynamic port forward of an SSH client via the @-D@ flag. -} module Hookup ( -- * Connections Connection, connect, connectWithSocket, close, -- * Reading and writing data recv, recvLine, send, putBuf, -- * Configuration ConnectionParams(..), SocksParams(..), TlsParams(..), defaultFamily, defaultTlsParams, -- * Errors ConnectionFailure(..), CommandReply(..) -- * SSL Information , getPeerCertificate , getPeerCertFingerprintSha1 , getPeerCertFingerprintSha256 , getPeerCertFingerprintSha512 , getPeerPubkeyFingerprintSha1 , getPeerPubkeyFingerprintSha256 , getPeerPubkeyFingerprintSha512 ) where import Control.Concurrent import Control.Exception import Control.Monad import Data.ByteString (ByteString) import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as B8 import Data.Foldable import Data.List (intercalate) import Network.Socket (Socket, AddrInfo, PortNumber, HostName, Family) import qualified Network.Socket as Socket import qualified Network.Socket.ByteString as SocketB import OpenSSL.Session (SSL, SSLContext) import qualified OpenSSL as SSL import qualified OpenSSL.Session as SSL import OpenSSL.X509.SystemStore import OpenSSL.X509 (X509) import qualified OpenSSL.X509 as X509 import qualified OpenSSL.PEM as PEM import qualified OpenSSL.EVP.Digest as Digest import Data.Attoparsec.ByteString (Parser) import qualified Data.Attoparsec.ByteString as Parser import Hookup.OpenSSL (installVerification, getPubKeyDer) import Hookup.Socks5 -- | Parameters for 'connect'. -- -- Common defaults for fields: 'defaultFamily', 'defaultTlsParams' -- -- The address family can be specified in order to force only -- IPv4 or IPv6 to be used. The default behavior is to support both. -- It can be useful to specify exactly one of these in the case that -- the other is misconfigured and a hostname is resolving to both. -- -- When a 'SocksParams' is provided the connection will be established -- using a SOCKS (version 5) proxy. -- -- When a 'TlsParams' is provided the connection negotiate TLS at connect -- time in order to protect the stream. data ConnectionParams = ConnectionParams { cpFamily :: Family -- ^ IP Protocol family (default 'AF_UNSPEC') , cpHost :: HostName -- ^ Destination host , cpPort :: PortNumber -- ^ Destination TCP port , cpSocks :: Maybe SocksParams -- ^ Optional SOCKS parameters , cpTls :: Maybe TlsParams -- ^ Optional TLS parameters } -- | SOCKS connection parameters data SocksParams = SocksParams { spHost :: HostName -- ^ SOCKS server host , spPort :: PortNumber -- ^ SOCKS server port } -- | TLS connection parameters. These parameters are passed to -- OpenSSL when making a secure connection. data TlsParams = TlsParams { tpClientCertificate :: Maybe FilePath -- ^ Path to client certificate , tpClientPrivateKey :: Maybe FilePath -- ^ Path to client private key , tpServerCertificate :: Maybe FilePath -- ^ Path to CA certificate bundle , tpCipherSuite :: String -- ^ OpenSSL cipher suite name (e.g. @\"HIGH\"@) , tpInsecure :: Bool -- ^ Disables certificate checking when 'True' } -- | Type for errors that can be thrown by this package. data ConnectionFailure -- | Failure during 'getAddrInfo' resolving remote host = HostnameResolutionFailure IOError -- | Failure during 'connect' to remote host | ConnectionFailure [IOError] -- | Failure during 'recvLine' | LineTooLong -- | Incomplete line during 'recvLine' | LineTruncated -- | Socks command rejected by server by given reply code | SocksError CommandReply -- | Socks authentication method was not accepted | SocksAuthenticationError -- | Socks server sent an invalid message or no message. | SocksProtocolError -- | Domain name was too long for SOCKS protocol | SocksBadDomainName deriving Show -- | 'displayException' implemented for prettier messages instance Exception ConnectionFailure where displayException LineTruncated = "connection closed while reading line" displayException LineTooLong = "line length exceeded maximum" displayException (ConnectionFailure xs) = "connection attempt failed due to: " ++ intercalate ", " (map displayException xs) displayException (HostnameResolutionFailure x) = "hostname resolution failed: " ++ displayException x displayException SocksAuthenticationError = "SOCKS authentication method rejected" displayException SocksProtocolError = "SOCKS server protocol error" displayException SocksBadDomainName = "SOCKS domain name length limit exceeded" displayException (SocksError reply) = "SOCKS command rejected: " ++ case reply of Succeeded -> "succeeded" GeneralFailure -> "general SOCKS server failure" NotAllowed -> "connection not allowed by ruleset" NetUnreachable -> "network unreachable" HostUnreachable -> "host unreachable" ConnectionRefused -> "connection refused" TTLExpired -> "TTL expired" CmdNotSupported -> "command not supported" AddrNotSupported -> "address type not supported" CommandReply n -> "unknown reply " ++ show n -- | Default 'Family' value is unspecified and allows both INET and INET6. defaultFamily :: Socket.Family defaultFamily = Socket.AF_UNSPEC -- | Default values for TLS that use no client certificates, use -- system CA root, @\"HIGH\"@ cipher suite, and which validate hostnames. defaultTlsParams :: TlsParams defaultTlsParams = TlsParams { tpClientCertificate = Nothing , tpClientPrivateKey = Nothing , tpServerCertificate = Nothing -- use system provided CAs , tpCipherSuite = "HIGH" , tpInsecure = False } ------------------------------------------------------------------------ -- Opening sockets ------------------------------------------------------------------------ -- | Open a socket using the given parameters either directly or -- via a SOCKS server. openSocket :: ConnectionParams -> IO Socket openSocket params = case cpSocks params of Nothing -> openSocket' (cpFamily params) (cpHost params) (cpPort params) Just sp -> do sock <- openSocket' (cpFamily params) (spHost sp) (spPort sp) (sock <$ socksConnect sock (cpHost params) (cpPort params)) `onException` Socket.close sock netParse :: Show a => Socket -> Parser a -> IO a netParse sock parser = do -- receiving 1 byte at a time is not efficient, but these messages -- are very short and we don't want to read any more from the socket -- than is necessary result <- Parser.parseWith (SocketB.recv sock 1) parser B.empty case result of Parser.Done i x | B.null i -> return x _ -> throwIO SocksProtocolError socksConnect :: Socket -> HostName -> PortNumber -> IO () socksConnect sock host port = do SocketB.sendAll sock $ buildClientHello ClientHello { cHelloMethods = [AuthNoAuthenticationRequired] } validateHello =<< netParse sock parseServerHello let dnBytes = B8.pack host unless (B.length dnBytes < 256) (throwIO SocksBadDomainName) SocketB.sendAll sock $ buildRequest Request { reqCommand = Connect , reqAddress = Address (DomainName dnBytes) port } validateResponse =<< netParse sock parseResponse validateHello :: ServerHello -> IO () validateHello hello = unless (sHelloMethod hello == AuthNoAuthenticationRequired) (throwIO SocksAuthenticationError) validateResponse :: Response -> IO () validateResponse response = unless (rspReply response == Succeeded ) (throwIO (SocksError (rspReply response))) openSocket' :: Family -> HostName -> PortNumber -> IO Socket openSocket' family h p = do let hints = Socket.defaultHints { Socket.addrFamily = family , Socket.addrSocketType = Socket.Stream , Socket.addrFlags = [Socket.AI_ADDRCONFIG ,Socket.AI_NUMERICSERV] } res <- try (Socket.getAddrInfo (Just hints) (Just h) (Just (show p))) case res of Right ais -> attemptConnections [] ais Left ioe -> throwIO (HostnameResolutionFailure ioe) -- | Try establishing a connection to the services indicated by -- a given list of 'AddrInfo' values. Either return a socket that -- has successfully connected to one of the candidate 'AddrInfo's -- or throw a 'ConnectionFailure' exception will all of the -- encountered errors. attemptConnections :: [IOError] {- ^ accumulated errors -} -> [Socket.AddrInfo] {- ^ candidate AddrInfos -} -> IO Socket {- ^ connected socket -} attemptConnections exs [] = throwIO (ConnectionFailure exs) attemptConnections exs (ai:ais) = do res <- try (connectToAddrInfo ai) case res of Left ex -> attemptConnections (ex:exs) ais Right s -> return s -- | Create a socket and connect to the service identified -- by the given 'AddrInfo' and return the connected socket. connectToAddrInfo :: AddrInfo -> IO Socket connectToAddrInfo info = bracketOnError (socket' info) Socket.close $ \s -> s <$ Socket.connect s (Socket.addrAddress info) -- | Open a 'Socket' using the parameters from an 'AddrInfo' socket' :: AddrInfo -> IO Socket socket' ai = Socket.socket (Socket.addrFamily ai) (Socket.addrSocketType ai) (Socket.addrProtocol ai) ------------------------------------------------------------------------ -- Generalization of Socket ------------------------------------------------------------------------ data NetworkHandle = SSL SSL | Socket Socket openNetworkHandle :: ConnectionParams {- ^ parameters -} -> IO Socket {- ^ socket creation action -} -> IO NetworkHandle {- ^ open network handle -} openNetworkHandle params mkSocket = case cpTls params of Nothing -> Socket <$> mkSocket Just tls -> SSL <$> startTls tls (cpHost params) mkSocket closeNetworkHandle :: NetworkHandle -> IO () closeNetworkHandle (Socket s) = Socket.close s closeNetworkHandle (SSL s) = do SSL.shutdown s SSL.Unidirectional traverse_ Socket.close (SSL.sslSocket s) networkSend :: NetworkHandle -> ByteString -> IO () networkSend (Socket s) = SocketB.sendAll s networkSend (SSL s) = SSL.write s networkRecv :: NetworkHandle -> Int -> IO ByteString networkRecv (Socket s) = SocketB.recv s networkRecv (SSL s) = SSL.read s ------------------------------------------------------------------------ -- Sockets with a receive buffer ------------------------------------------------------------------------ -- | A connection to a network service along with its read buffer -- used for line-oriented protocols. The connection could be a plain -- network connection, SOCKS connected, or TLS. data Connection = Connection (MVar ByteString) NetworkHandle -- | Open network connection to TCP service specified by -- the given parameters. -- -- The resulting connection MUST be closed with 'close' to avoid leaking -- resources. -- -- Throws 'IOError', 'SocksError', 'SSL.ProtocolError', 'ConnectionFailure' connect :: ConnectionParams {- ^ parameters -} -> IO Connection {- ^ open connection -} connect params = do h <- openNetworkHandle params (openSocket params) b <- newMVar B.empty return (Connection b h) -- | Create a new 'Connection' using an already connected socket. -- This will attempt to start TLS if configured but will ignore -- any SOCKS server settings as it is assumed that the socket -- is already actively connected to the intended service. -- -- Throws 'SSL.ProtocolError' connectWithSocket :: ConnectionParams {- ^ parameters -} -> Socket {- ^ connected socket -} -> IO Connection {- ^ open connection -} connectWithSocket params sock = do h <- openNetworkHandle params (return sock) b <- newMVar B.empty return (Connection b h) -- | Close network connection. close :: Connection {- ^ open connection -} -> IO () close (Connection _ h) = closeNetworkHandle h -- | Receive the next chunk from the stream. This operation will first -- return the buffer if it contains a non-empty chunk. Otherwise it will -- request up to the requested number of bytes from the stream. -- -- Throws: 'IOError', 'SSL.ConnectionAbruptlyTerminated', 'SSL.ProtocolError' recv :: Connection {- ^ open connection -} -> Int {- ^ maximum underlying recv size -} -> IO ByteString {- ^ next chunk from stream -} recv (Connection buf h) n = do bufChunk <- swapMVar buf B.empty if B.null bufChunk then networkRecv h n else return bufChunk -- | Receive a line from the network connection. Both -- @"\\r\\n"@ and @"\\n"@ are recognized. -- -- Returning 'Nothing' means that the peer has closed its half of -- the connection. -- -- Unterminated lines will raise a 'LineTruncated' exception. This -- can happen if the peer transmits some data and closes its end -- without transmitting a line terminator. -- -- Throws: 'SSL.ConnectionAbruptlyTerminated', 'SSL.ProtocolError', 'ConnectionFailure', 'IOError' recvLine :: Connection {- ^ open connection -} -> Int {- ^ maximum line length -} -> IO (Maybe ByteString) {- ^ next line or end-of-stream -} recvLine (Connection buf h) n = modifyMVar buf $ \bs -> go (B.length bs) bs [] where -- bsn: cached length of concatenation of (bs:bss) -- bs : most recent chunk -- bss: other chunks ordered from most to least recent go bsn bs bss = case B8.elemIndex '\n' bs of Just i -> return (B.tail b, -- tail drops newline Just (cleanEnd (B.concat (reverse (a:bss))))) where (a,b) = B.splitAt i bs Nothing -> do when (bsn >= n) (throwIO LineTooLong) more <- networkRecv h n if B.null more -- connection closed then if bsn == 0 then return (B.empty, Nothing) else throwIO LineTruncated else go (bsn + B.length more) more (bs:bss) -- | Push a 'ByteString' onto the buffer so that it will be the first -- bytes to be read on the next receive operation. This could perhaps -- be useful for putting the unused portion of a 'recv' back into the -- buffer for future 'recvLine' or 'recv' operations. putBuf :: Connection {- ^ connection -} -> ByteString {- ^ new head of buffer -} -> IO () putBuf (Connection buf h) bs = modifyMVar_ buf (\old -> return $! B.append bs old) -- | Remove the trailing @'\\r'@ if one is found. cleanEnd :: ByteString -> ByteString cleanEnd bs | B.null bs || B8.last bs /= '\r' = bs | otherwise = B.init bs -- | Send bytes on the network connection. This ensures the whole chunk is -- transmitted, which might take multiple underlying sends. -- -- Throws: 'IOError', 'SSL.ProtocolError' send :: Connection {- ^ open connection -} -> ByteString {- ^ chunk -} -> IO () send (Connection _ h) = networkSend h ------------------------------------------------------------------------ -- | Initiate a TLS session on the given socket destined for -- the given hostname. When successful an active TLS connection -- is returned with certificate verification successful when -- requested. This function requires that the TLSParams component -- of 'ConnectionParams' is set. startTls :: TlsParams {- ^ connection params -} -> String {- ^ hostname -} -> IO Socket {- ^ socket creation action -} -> IO SSL {- ^ connected TLS -} startTls tp hostname mkSocket = SSL.withOpenSSL $ do ctx <- SSL.context -- configure context SSL.contextSetCiphers ctx (tpCipherSuite tp) installVerification ctx hostname SSL.contextSetVerificationMode ctx (verificationMode (tpInsecure tp)) SSL.contextAddOption ctx SSL.SSL_OP_ALL SSL.contextRemoveOption ctx SSL.SSL_OP_DONT_INSERT_EMPTY_FRAGMENTS -- configure certificates setupCaCertificates ctx (tpServerCertificate tp) traverse_ (setupCertificate ctx) (tpClientCertificate tp) traverse_ (setupPrivateKey ctx) (tpClientPrivateKey tp) -- add socket to context -- creation of the socket is delayed until this point to avoid -- leaking the file descriptor in the cases of exceptions above. ssl <- SSL.connection ctx =<< mkSocket -- configure hostname used for certificate validation SSL.setTlsextHostName ssl hostname SSL.connect ssl return ssl setupCaCertificates :: SSLContext -> Maybe FilePath -> IO () setupCaCertificates ctx mbPath = case mbPath of Nothing -> contextLoadSystemCerts ctx Just path -> SSL.contextSetCAFile ctx path setupCertificate :: SSLContext -> FilePath -> IO () setupCertificate ctx path = SSL.contextSetCertificate ctx =<< PEM.readX509 -- EX =<< readFile path setupPrivateKey :: SSLContext -> FilePath -> IO () setupPrivateKey ctx path = do str <- readFile path -- EX key <- PEM.readPrivateKey str PEM.PwNone -- TODO: add password support SSL.contextSetPrivateKey ctx key verificationMode :: Bool {- ^ insecure -} -> SSL.VerificationMode verificationMode insecure | insecure = SSL.VerifyNone | otherwise = SSL.VerifyPeer { SSL.vpFailIfNoPeerCert = True , SSL.vpClientOnce = True , SSL.vpCallback = Nothing } -- | Get peer certificate if one exists. getPeerCertificate :: Connection -> IO (Maybe X509.X509) getPeerCertificate (Connection _ h) = case h of Socket{} -> return Nothing SSL ssl -> SSL.getPeerCertificate ssl getPeerCertFingerprintSha1 :: Connection -> IO (Maybe ByteString) getPeerCertFingerprintSha1 = getPeerCertFingerprint "sha1" getPeerCertFingerprintSha256 :: Connection -> IO (Maybe ByteString) getPeerCertFingerprintSha256 = getPeerCertFingerprint "sha256" getPeerCertFingerprintSha512 :: Connection -> IO (Maybe ByteString) getPeerCertFingerprintSha512 = getPeerCertFingerprint "sha512" getPeerCertFingerprint :: String -> Connection -> IO (Maybe ByteString) getPeerCertFingerprint name h = do mb <- getPeerCertificate h case mb of Nothing -> return Nothing Just x509 -> do der <- X509.writeDerX509 x509 mbdigest <- Digest.getDigestByName name case mbdigest of Nothing -> return Nothing Just digest -> return $! Just $! Digest.digestLBS digest der getPeerPubkeyFingerprintSha1 :: Connection -> IO (Maybe ByteString) getPeerPubkeyFingerprintSha1 = getPeerPubkeyFingerprint "sha1" getPeerPubkeyFingerprintSha256 :: Connection -> IO (Maybe ByteString) getPeerPubkeyFingerprintSha256 = getPeerPubkeyFingerprint "sha256" getPeerPubkeyFingerprintSha512 :: Connection -> IO (Maybe ByteString) getPeerPubkeyFingerprintSha512 = getPeerPubkeyFingerprint "sha512" getPeerPubkeyFingerprint :: String -> Connection -> IO (Maybe ByteString) getPeerPubkeyFingerprint name h = do mb <- getPeerCertificate h case mb of Nothing -> return Nothing Just x509 -> do der <- getPubKeyDer x509 mbdigest <- Digest.getDigestByName name case mbdigest of Nothing -> return Nothing Just digest -> return $! Just $! Digest.digestBS digest der hookup-0.2.3/src/Hookup/0000755000000000000000000000000007346545000013246 5ustar0000000000000000hookup-0.2.3/src/Hookup/OpenSSL.hsc0000644000000000000000000000656507346545000015244 0ustar0000000000000000{-# Language CApiFFI #-} {-| Module : Hookup.OpenSSL Description : Hack into the internals of OpenSSL to add missing functionality Copyright : (c) Eric Mertens, 2016 License : ISC Maintainer : emertens@gmail.com -} #include "openssl/ssl.h" #include "openssl/x509_vfy.h" #include "openssl/x509v3.h" #ifndef X509_CHECK_FLAG_NO_PARTIAL_WILDCARDS #error "OpenSSL 1.0.2 or later is required. This version was released in Jan 2015 and adds hostname verification" #endif module Hookup.OpenSSL (installVerification, getPubKeyDer) where import Control.Monad (unless) import Foreign.C (CString(..), CSize(..), CUInt(..), CInt(..), withCStringLen) import Foreign.Ptr (Ptr, castPtr, nullPtr) import Foreign.Marshal (with) import OpenSSL.Session (SSLContext, SSLContext_, withContext) import OpenSSL.X509 (withX509Ptr, X509, X509_) import Data.ByteString (ByteString) import qualified Data.ByteString.Internal as B ------------------------------------------------------------------------ -- Bindings to hostname verification interface ------------------------------------------------------------------------ data X509_VERIFY_PARAM_ data {-# CTYPE "openssl/ssl.h" "X509_PUBKEY" #-} X509_PUBKEY_ data {-# CTYPE "openssl/ssl.h" "X509" #-} X509__ -- X509_VERIFY_PARAM *SSL_CTX_get0_param(SSL_CTX *ctx); foreign import ccall unsafe "SSL_CTX_get0_param" sslGet0Param :: Ptr SSLContext_ {- ^ ctx -} -> IO (Ptr X509_VERIFY_PARAM_) -- void X509_VERIFY_PARAM_set_hostflags(X509_VERIFY_PARAM *param, unsigned int flags); foreign import ccall unsafe "X509_VERIFY_PARAM_set_hostflags" x509VerifyParamSetHostflags :: Ptr X509_VERIFY_PARAM_ {- ^ param -} -> CUInt {- ^ flags -} -> IO () -- int X509_VERIFY_PARAM_set1_host(X509_VERIFY_PARAM *param, const char *name, size_t namelen); foreign import ccall unsafe "X509_VERIFY_PARAM_set1_host" x509VerifyParamSet1Host :: Ptr X509_VERIFY_PARAM_ {- ^ param -} -> CString {- ^ name -} -> CSize {- ^ namelen -} -> IO CInt {- ^ 1 success, 0 failure -} -- X509_PUBKEY *X509_get_X509_PUBKEY(X509 *x); foreign import capi unsafe "openssl/x509.h X509_get_X509_PUBKEY" x509getX509Pubkey :: Ptr X509__ -> IO (Ptr X509_PUBKEY_) -- int i2d_X509_PUBKEY(X509_PUBKEY *p, unsigned char **ppout); foreign import ccall unsafe "i2d_X509_PUBKEY" i2dX509Pubkey :: Ptr X509_PUBKEY_ -> Ptr CString -> IO CInt getPubKeyDer :: X509 -> IO ByteString getPubKeyDer x509 = withX509Ptr x509 $ \x509ptr -> do pubkey <- x509getX509Pubkey (castPtr x509ptr) len <- fromIntegral <$> i2dX509Pubkey pubkey nullPtr B.create len $ \bsPtr -> with (castPtr bsPtr) $ \ptrPtr -> () <$ i2dX509Pubkey pubkey ptrPtr -- | Add hostname checking to the certificate verification step. -- Partial wildcards matching is disabled. installVerification :: SSLContext -> String {- ^ hostname -} -> IO () installVerification ctx host = withContext ctx $ \ctxPtr -> withCStringLen host $ \(ptr,len) -> do param <- sslGet0Param ctxPtr x509VerifyParamSetHostflags param (#const X509_CHECK_FLAG_NO_PARTIAL_WILDCARDS) success <- x509VerifyParamSet1Host param ptr (fromIntegral len) unless (success == 1) (fail "Unable to set verification host") hookup-0.2.3/src/Hookup/Socks5.hs0000644000000000000000000002557607346545000014770 0ustar0000000000000000{-# Language PatternSynonyms #-} {-# OPTIONS_GHC -Wall -Wno-missing-pattern-synonym-signatures #-} {-| Module : Hookup.Socks5 Description : SOCKS5 network protocol implementation Copyright : (c) Eric Mertens, 2018 License : ISC Maintainer : emertens@gmail.com This module provides types, parsers, and builders for the messages used in the SOCKS5 protocol. See -} module Hookup.Socks5 ( -- * Client hello message ClientHello(..) , buildClientHello , parseClientHello -- * Server hello message , ServerHello(..) , buildServerHello , parseServerHello -- * Command request message , Request(..) , buildRequest , parseRequest -- * Command response message , Response(..) , buildResponse , parseResponse -- * Network address types , Address(..) , Host(..) -- * Authentication methods , AuthMethod ( AuthNoAuthenticationRequired , AuthGssApi , AuthUsernamePassword , AuthNoAcceptableMethods ) -- * Commands , Command ( Connect , Bind , UdpAssociate ) -- * Command reply codes , CommandReply ( CommandReply , Succeeded , GeneralFailure , NotAllowed , NetUnreachable , HostUnreachable , ConnectionRefused , TTLExpired , CmdNotSupported , AddrNotSupported ) ) where import Control.Monad (replicateM) import Data.Attoparsec.ByteString (Parser) import Data.ByteString (ByteString) import Data.ByteString.Builder (Builder) import Data.Word (Word8, Word16) import Network.Socket (HostAddress, HostAddress6, PortNumber, hostAddressToTuple, hostAddress6ToTuple, tupleToHostAddress, tupleToHostAddress6) import qualified Data.Attoparsec.ByteString as Parser import qualified Data.ByteString as B import qualified Data.ByteString.Builder as Builder import qualified Data.ByteString.Lazy as L -- | SOCKS authentication methods newtype AuthMethod = AuthMethod Word8 deriving (Eq, Show) pattern AuthNoAuthenticationRequired = AuthMethod 0x00 pattern AuthGssApi = AuthMethod 0x01 pattern AuthUsernamePassword = AuthMethod 0x02 pattern AuthNoAcceptableMethods = AuthMethod 0xFF -- | SOCKS client commands newtype Command = Command Word8 deriving (Eq, Show) pattern Connect = Command 1 pattern Bind = Command 2 pattern UdpAssociate = Command 3 -- | Tags used in the protocol messages for encoded 'Host' values newtype HostTag = HostTag Word8 deriving (Eq, Show) pattern IPv4Tag = HostTag 1 pattern DomainNameTag = HostTag 3 pattern IPv6Tag = HostTag 4 -- | SOCKS command reply codes newtype CommandReply = CommandReply Word8 deriving (Eq, Show) pattern Succeeded = CommandReply 0 pattern GeneralFailure = CommandReply 1 pattern NotAllowed = CommandReply 2 pattern NetUnreachable = CommandReply 3 pattern HostUnreachable = CommandReply 4 pattern ConnectionRefused = CommandReply 5 pattern TTLExpired = CommandReply 6 pattern CmdNotSupported = CommandReply 7 pattern AddrNotSupported = CommandReply 8 -- | Network host and port number data Address = Address Host PortNumber deriving Show -- | Network host identified by address or domain name. data Host = IPv4 HostAddress -- ^ IPv4 host address | IPv6 HostAddress6 -- ^ IPv6 host address | DomainName ByteString -- ^ Domain name (maximum length 255) deriving Show -- | Initial SOCKS sent by client with proposed list of authentication methods. data ClientHello = ClientHello { cHelloMethods :: [AuthMethod] -- ^ proposed methods (maximum length 255) } deriving Show -- | Initial SOCKS sent by server with chosen authentication method. data ServerHello = ServerHello { sHelloMethod :: AuthMethod } deriving Show -- | Client message used to request a network operation from the SOCKS server. data Request = Request { reqCommand :: Command , reqAddress :: Address } deriving Show -- | Server message used to indicate result of client's request. data Response = Response { rspReply :: CommandReply , rspAddress :: Address } deriving Show -- | Transform a 'Builder' into a strict 'ByteString' runBuilder :: Builder -> ByteString runBuilder = L.toStrict . Builder.toLazyByteString ------------------------------------------------------------------------ buildCommand :: Command -> Builder buildCommand (Command c) = Builder.word8 c parseCommand :: Parser Command parseCommand = Command <$> Parser.anyWord8 ------------------------------------------------------------------------ buildHost :: Host -> Builder buildHost (IPv4 hostAddr) = buildHostTag IPv4Tag <> buildHostAddress hostAddr buildHost (IPv6 hostAddr) = buildHostTag IPv6Tag <> buildHostAddress6 hostAddr buildHost (DomainName dn) = buildHostTag DomainNameTag <> buildDomainName dn parseHost :: Parser Host parseHost = do tag <- parseHostTag case tag of IPv4Tag -> IPv4 <$> parseHostAddress IPv6Tag -> IPv6 <$> parseHostAddress6 DomainNameTag -> DomainName <$> parseDomainName _ -> fail "bad address tag" ------------------------------------------------------------------------ buildAddress :: Address -> Builder buildAddress (Address host port) = buildHost host <> buildPort port parseAddress :: Parser Address parseAddress = Address <$> parseHost <*> parsePort ------------------------------------------------------------------------ buildHostTag :: HostTag -> Builder buildHostTag (HostTag tag) = Builder.word8 tag parseHostTag :: Parser HostTag parseHostTag = HostTag <$> Parser.anyWord8 ------------------------------------------------------------------------ buildHostAddress :: HostAddress -> Builder buildHostAddress hostAddr = case hostAddressToTuple hostAddr of (a1,a2,a3,a4) -> foldMap Builder.word8 [a1,a2,a3,a4] parseHostAddress :: Parser HostAddress parseHostAddress = do [a1,a2,a3,a4] <- replicateM 4 Parser.anyWord8 return $! tupleToHostAddress (a1,a2,a3,a4) ------------------------------------------------------------------------ buildHostAddress6 :: HostAddress6 -> Builder buildHostAddress6 hostAddr = case hostAddress6ToTuple hostAddr of (a1,a2,a3,a4,a5,a6,a7,a8) -> foldMap Builder.word16BE [a1,a2,a3,a4,a5,a6,a7,a8] parseHostAddress6 :: Parser HostAddress6 parseHostAddress6 = do [a1,a2,a3,a4,a5,a6,a7,a8] <- replicateM 8 parseWord16BE return $! tupleToHostAddress6 (a1,a2,a3,a4,a5,a6,a7,a8) ------------------------------------------------------------------------ buildDomainName :: ByteString -> Builder buildDomainName bs | B.length bs < 256 = Builder.word8 (fromIntegral (B.length bs)) <> Builder.byteString bs | otherwise = error "SOCKS5 domain name too long" parseDomainName :: Parser ByteString parseDomainName = do len <- Parser.anyWord8 Parser.take (fromIntegral len) ------------------------------------------------------------------------ buildPort :: PortNumber -> Builder buildPort port = Builder.word16BE (fromIntegral port) parsePort :: Parser PortNumber parsePort = fromIntegral <$> parseWord16BE ------------------------------------------------------------------------ buildVersion :: Builder buildVersion = Builder.word8 5 parseVersion :: Parser () parseVersion = () <$ Parser.word8 5 ------------------------------------------------------------------------ buildAuthMethod :: AuthMethod -> Builder buildAuthMethod (AuthMethod x) = Builder.word8 x parseAuthMethod :: Parser AuthMethod parseAuthMethod = AuthMethod <$> Parser.anyWord8 ------------------------------------------------------------------------ buildReply :: CommandReply -> Builder buildReply (CommandReply x) = Builder.word8 x parseReply :: Parser CommandReply parseReply = CommandReply <$> Parser.anyWord8 ------------------------------------------------------------------------ buildReserved :: Builder buildReserved = Builder.word8 0 parseReserved :: Parser () parseReserved = () <$ Parser.anyWord8 ------------------------------------------------------------------------ -- | Build a list of buildable things prefixing the length of the list -- as a single byte. The list must not be longer than 255 elements. buildListOf :: (a -> Builder) -> [a] -> Builder buildListOf builder xs | length xs < 256 = Builder.word8 (fromIntegral (length xs)) <> foldMap builder xs | otherwise = error "buildListOf: list too long" -- | Parse a list of parsable things where the length of the list -- is encoded as a single byte before the items to be parsed. parseListOf :: Parser a -> Parser [a] parseListOf parser = do n <- Parser.anyWord8 replicateM (fromIntegral n) parser ------------------------------------------------------------------------ buildClientHello :: ClientHello -> ByteString buildClientHello msg = runBuilder $ buildVersion <> buildListOf buildAuthMethod (cHelloMethods msg) parseClientHello :: Parser ClientHello parseClientHello = ClientHello <$ parseVersion <*> parseListOf parseAuthMethod ------------------------------------------------------------------------ buildServerHello :: ServerHello -> ByteString buildServerHello msg = runBuilder $ buildVersion <> buildAuthMethod (sHelloMethod msg) parseServerHello :: Parser ServerHello parseServerHello = ServerHello <$ parseVersion <*> parseAuthMethod ------------------------------------------------------------------------ buildRequest :: Request -> ByteString buildRequest req = runBuilder $ buildVersion <> buildCommand (reqCommand req) <> buildReserved <> buildAddress (reqAddress req) parseRequest :: Parser Request parseRequest = Request <$ parseVersion <*> parseCommand <* parseReserved <*> parseAddress ------------------------------------------------------------------------ buildResponse :: Response -> ByteString buildResponse msg = runBuilder $ buildVersion <> buildReply (rspReply msg) <> buildReserved <> buildAddress (rspAddress msg) parseResponse :: Parser Response parseResponse = Response <$ parseVersion <*> parseReply <* parseReserved <*> parseAddress ------------------------------------------------------------------------ -- | Match a 16-bit, big-endian word. parseWord16BE :: Parser Word16 parseWord16BE = do hi <- Parser.anyWord8 lo <- Parser.anyWord8 return $! fromIntegral hi * 0x100 + fromIntegral lo