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.Types

Description

 
Synopsis

Documentation

data SocksVersion Source #

Type representing SOCKS protocol versions.

Constructors

SocksVer5

SOCKS Protocol Version 5. The only version implemented by the library.

data SocksCommand Source #

Type representing commands that can be sent or received under the SOCKS protocol.

Constructors

SocksCommandConnect

The CONNECT request.

SocksCommandBind

The BIND request. Not implemented by the library.

SocksCommandUdpAssociate

The UDP ASSOCIATE request. Not implemented by the library.

SocksCommandOther !Word8

Other requests. None are specified by the SOCKS Protocol Version 5.

data SocksMethod Source #

Type representing authentication methods available under the SOCKS protocol.

Only SocksMethodNone is effectively implemented, but other values are enumerated for completeness.

Constructors

SocksMethodNone

NO AUTHENTICATION REQUIRED.

SocksMethodGSSAPI

GSSAPI.

SocksMethodUsernamePassword

USERNAME/PASSWORD.

SocksMethodOther !Word8

IANA ASSIGNED or RESERVED FOR PRIVATE METHODS.

SocksMethodNotAcceptable

NO ACCEPTABLE METHODS.

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 SocksVersionNotSupported Source #

Type representing exceptions.

Constructors

SocksVersionNotSupported

The SOCKS protocol version is not supported. This library only implements SOCKS Protocol Version 5.

Instances

Instances details
Data SocksVersionNotSupported 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) -> SocksVersionNotSupported -> c SocksVersionNotSupported #

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

toConstr :: SocksVersionNotSupported -> Constr #

dataTypeOf :: SocksVersionNotSupported -> DataType #

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

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

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

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

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

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

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

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

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

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

Exception SocksVersionNotSupported Source # 
Instance details

Defined in Network.Socks5.Types

Show SocksVersionNotSupported 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

type SocksFQDN = ByteString Source #

Type synonym representing fully-qualified domain names (FQDN). The SOCKS Protocol Version 5 does not specify an encoding for a FQDN other than there is no terminating NUL octet (byte).

This library's API assumes that FQDN values comprise only ASCII characters. Domain names that include other Unicode code points should be Punycode encoded.