crypton-socks-0.6.2: SOCKS Protocol Version 5
Copyright(c) 2010-2019 Vincent Hanquez <vincent@snarc.org>
LicenseBSD-style
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Network.Socks5

Description

This is an implementation of the SOCKS Protocol Version 5 as defined in RFC 1928.

In Wikipedia's words:

SOCKS is an Internet protocol that exchanges network packets between a client and server through a proxy server. SOCKS5 optionally provides authentication so only authorized users may access a server. Practically, a SOCKS server proxies TCP connections to an arbitrary IP address, and provides a means for UDP packets to be forwarded. A SOCKS server accepts incoming client connection on TCP port 1080.

BIND and UDP ASSOCIATE messages are not implemented. However the main usage of SOCKS is implemented.

Synopsis

Types

data SocksReply Source #

Type representing replies under the SOCKS protocol.

Constructors

SocksReplySuccess

The server reports that the request succeeded.

SocksReplyError SocksError

The server reports that the request did not succeed.

Instances

Instances details
Data SocksReply Source # 
Instance details

Defined in Network.Socks5.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SocksReply -> c SocksReply #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SocksReply #

toConstr :: SocksReply -> Constr #

dataTypeOf :: SocksReply -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SocksReply) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SocksReply) #

gmapT :: (forall b. Data b => b -> b) -> SocksReply -> SocksReply #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SocksReply -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SocksReply -> r #

gmapQ :: (forall d. Data d => d -> u) -> SocksReply -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SocksReply -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SocksReply -> m SocksReply #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SocksReply -> m SocksReply #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SocksReply -> m SocksReply #

Enum SocksReply Source # 
Instance details

Defined in Network.Socks5.Types

Show SocksReply Source # 
Instance details

Defined in Network.Socks5.Types

Eq SocksReply Source # 
Instance details

Defined in Network.Socks5.Types

Ord SocksReply Source # 
Instance details

Defined in Network.Socks5.Types

data SocksError Source #

Type representing SOCKS errors that can be part of a SOCKS reply.

Constructors

SocksErrorGeneralServerFailure

General SOCKS server failure.

SocksErrorConnectionNotAllowedByRule

Connection not allowed by ruleset.

SocksErrorNetworkUnreachable

Network unreachable.

SocksErrorHostUnreachable

Host unreachable.

SocksErrorConnectionRefused

Connection refused.

SocksErrorTTLExpired

TTL expired.

SocksErrorCommandNotSupported

Command not supported.

SocksErrorAddrTypeNotSupported

Address type not supported.

SocksErrorOther Word8

Other error. Unassigned in SOCKS Protocol Version 5.

Instances

Instances details
Data SocksError Source # 
Instance details

Defined in Network.Socks5.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SocksError -> c SocksError #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SocksError #

toConstr :: SocksError -> Constr #

dataTypeOf :: SocksError -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SocksError) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SocksError) #

gmapT :: (forall b. Data b => b -> b) -> SocksError -> SocksError #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SocksError -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SocksError -> r #

gmapQ :: (forall d. Data d => d -> u) -> SocksError -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SocksError -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SocksError -> m SocksError #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SocksError -> m SocksError #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SocksError -> m SocksError #

Enum SocksError Source # 
Instance details

Defined in Network.Socks5.Types

Exception SocksError Source # 
Instance details

Defined in Network.Socks5.Types

Show SocksError Source # 
Instance details

Defined in Network.Socks5.Types

Eq SocksError Source # 
Instance details

Defined in Network.Socks5.Types

Ord SocksError Source # 
Instance details

Defined in Network.Socks5.Types

Configuration

data SocksConf Source #

Type representing SOCKS identification and configuration structures.

The data constructors may be extended in the future to support authentification. Use the smart constructor defaultSocksConf and socksHost.

Constructors

SocksConf 

Fields

socksHost Source #

Arguments

:: SocksConf

The configuration.

-> SockAddr 

Yield the socket address of the server from the specified configuration.

defaultSocksConf Source #

Arguments

:: SockAddr

The address of the server.

-> SocksConf 

Yield a configuration given the specified socket addresss.

defaultSocksConfFromSockAddr :: SockAddr -> SocksConf Source #

Deprecated: Will be removed from future package versions. Use defaultSocksConf instead.

Same as defaultSocksConf.

Methods

socksConnectWithSocket Source #

Arguments

:: Socket

The socket to use.

-> SocksConf

The SOCKS configuration for the server.

-> SocksAddress

The SOCKS address to connect to.

-> IO (SocksHostAddress, PortNumber) 

Connect a user-specified new socket on the SOCKS server to a destination.

The specified socket needs to be connected to the SOCKS server already.

|socket|-----sockServer----->|server|----destAddr----->|destination|

socksConnect Source #

Arguments

:: SocksConf

The SOCKS configuration for the server.

-> SocksAddress

The SOCKS address to connect to.

-> IO (Socket, (SocksHostAddress, PortNumber)) 

Connect a new socket to a SOCKS server and connect the stream on the server side to the specified SOCKS address.

Variants

socksConnectName Source #

Arguments

:: Socket

The socket to use. The socket must *not* be connected already.

-> SocksConf

The SOCKS configuration for the server.

-> String

Destination FQDN. Should comprise only ASCII characters, otherwise unexpected behaviour will ensure. For FQDN including other Unicode code points, Punycode encoding should be used.

-> PortNumber

The port number to use.

-> IO () 

Connect a new socket to the SOCKS server, and connect the stream to a fully-qualified domain name (FQDN) resolved on the server side.