radius-0.1.0.0: Remote Authentication Dial In User Service (RADIUS)

Copyright(c) Erick Gonzalez 2017
LicenseBSD3
Maintainererick@codemonkeylabs.de
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Network.RADIUS.Types

Description

This module compiles the RADIUS packet definitions and different attributes as specified in RFC 2865. The naming conventions from the RFC have been preserved as much as possible, so it should be straightforward to look up a particular element and understand what it means etc.

RADIUS extensions in RFC 2869 are also supported, as well as RFC 3162 for IPv6 related attributes

Documentation

data PacketAttribute Source #

Constructors

UserNameAttribute 
UserPasswordAttribute 
CHAPPassword 
NASIPAddress 
NASIPv6Address 
NASPortAttribute 
ServiceTypeAttribute 
FramedProtocolAttribute 
FramedIPAddressAttribute 
FramedIPNetmaskAttribute 
FramedRoutingAttribute 
FramedInterfaceIdAttribute 
FramedIPv6Prefix 
FramedIPv6Route 
FramedIPv6Pool 
FilterIdAttribute 
FramedMTUAttribute 
FramedCompressionAttribute 
LoginIPHostAttribute 
LoginIPv6HostAttribute 
LoginServiceAttribute 
LoginTCPPortAttribute 
ReplyMessageAttribute 
CallbackNumberAttribute 
CallbackIdAttribute 
FramedRouteAttribute 
FramedIPXNetworkAttribute 
StateAttribute 
ClassAttribute 
VendorSpecificAttribute 
SessionTimeoutAttribute 
IdleTimeoutAttribute 
TerminationActionAttribute 
CalledStationIdAttribute 
CallingStationIdAttribute 
NASIdentifierAttribute 
ProxyStateAttribute 
LoginLATServiceAttribute 
LoginLATNodeAttribute 
LoginLATGroupAttribute 
FramedAppleTalkLinkAttribute 
FramedAppleTalkNetworkAttribute 
FramedAppleTalkZoneAttribute 
CHAPChallengeAttribute 
NASPortTypeAttribute 
PortLimitAttribute 
LoginLATPortAttribute 
AccountInputGigawordsAttribute 
AccountOutputGigawordsAttribute 
EventTimeStampAttribute 
ARAPPasswordAttribute 
ARAPFeaturesAttribute 
ARAPZoneAccessAttribute 
ARAPSecurityAttribute 
ARAPSecurityDataAttribute 
PasswordRetryAttribute 
PromptAttribute 
ConnectInfoAttribute 
ConfigurationTokenAttribute 
EAPMessageAttribute 
MessageAuthenticatorAttribute 
ARAPChallengeResponseAttribute 
AcctInterimIntervalAttribute 
NASPortIdAttribute 
FramedPoolAttribute 

Instances

Eq PacketAttribute Source # 
Data PacketAttribute Source # 

Methods

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

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

toConstr :: PacketAttribute -> Constr #

dataTypeOf :: PacketAttribute -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PacketAttribute Source # 

data ServiceType Source #

Instances

Enum ServiceType Source # 
Eq ServiceType Source # 
Data ServiceType Source # 

Methods

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

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

toConstr :: ServiceType -> Constr #

dataTypeOf :: ServiceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ServiceType Source # 

data FramedProtocol Source #

Instances

Enum FramedProtocol Source # 
Eq FramedProtocol Source # 
Data FramedProtocol Source # 

Methods

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

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

toConstr :: FramedProtocol -> Constr #

dataTypeOf :: FramedProtocol -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FramedProtocol Source # 

data FramedRouting Source #

Instances

Enum FramedRouting Source # 
Eq FramedRouting Source # 
Data FramedRouting Source # 

Methods

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

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

toConstr :: FramedRouting -> Constr #

dataTypeOf :: FramedRouting -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FramedRouting Source # 

data FramedCompression Source #

Instances

Enum FramedCompression Source # 
Eq FramedCompression Source # 
Data FramedCompression Source # 

Methods

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

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

toConstr :: FramedCompression -> Constr #

dataTypeOf :: FramedCompression -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FramedCompression Source # 

data LoginService Source #

Instances

Enum LoginService Source # 
Eq LoginService Source # 
Data LoginService Source # 

Methods

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

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

toConstr :: LoginService -> Constr #

dataTypeOf :: LoginService -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LoginService Source # 

data TerminationAction Source #

Instances

Enum TerminationAction Source # 
Eq TerminationAction Source # 
Data TerminationAction Source # 

Methods

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

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

toConstr :: TerminationAction -> Constr #

dataTypeOf :: TerminationAction -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TerminationAction Source # 

data NASPortType Source #

Instances

Enum NASPortType Source # 
Eq NASPortType Source # 
Data NASPortType Source # 

Methods

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

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

toConstr :: NASPortType -> Constr #

dataTypeOf :: NASPortType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NASPortType Source # 

data ARAPZoneAccess Source #

Instances

Enum ARAPZoneAccess Source # 
Eq ARAPZoneAccess Source # 
Data ARAPZoneAccess Source # 

Methods

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

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

toConstr :: ARAPZoneAccess -> Constr #

dataTypeOf :: ARAPZoneAccess -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ARAPZoneAccess Source #