radius-0.6.0.2: 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 Header Source #

Instances
Eq Header Source # 
Instance details

Defined in Network.RADIUS.Types

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Show Header Source # 
Instance details

Defined in Network.RADIUS.Types

data Packet Source #

Instances
Eq Packet Source # 
Instance details

Defined in Network.RADIUS.Types

Methods

(==) :: Packet -> Packet -> Bool #

(/=) :: Packet -> Packet -> Bool #

Show Packet Source # 
Instance details

Defined in Network.RADIUS.Types

Binary Packet Source # 
Instance details

Defined in Network.RADIUS.Encoding

Methods

put :: Packet -> Put #

get :: Get Packet #

putList :: [Packet] -> Put #

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 
DelegatedIPv6Prefix 
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 
AcctStatusTypeAttribute 
AcctDelayTimeAttribute 
AcctInputOctetsAttribute 
AcctOutputOctetsAttribute 
AcctSessionIdAttribute 
AcctAuthenticAttribute 
AcctSessionTimeAttribute 
AcctInputPacketsAttribute 
AcctOutputPacketsAttribute 
AcctTerminateCauseAttribute 
AcctMultiSessionIdAttribute 
AcctLinkCountAttribute 
UnknownAttribute 
Instances
Eq PacketAttribute Source # 
Instance details

Defined in Network.RADIUS.Types

Data PacketAttribute Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary PacketAttribute Source # 
Instance details

Defined in Network.RADIUS.Encoding

data StatusType Source #

Instances
Enum StatusType Source # 
Instance details

Defined in Network.RADIUS.Types

Eq StatusType Source # 
Instance details

Defined in Network.RADIUS.Types

Data StatusType Source # 
Instance details

Defined in Network.RADIUS.Types

Methods

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

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

toConstr :: StatusType -> Constr #

dataTypeOf :: StatusType -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusType Source # 
Instance details

Defined in Network.RADIUS.Types

Binary StatusType Source # 
Instance details

Defined in Network.RADIUS.Encoding

data Authentic Source #

Instances
Enum Authentic Source # 
Instance details

Defined in Network.RADIUS.Types

Eq Authentic Source # 
Instance details

Defined in Network.RADIUS.Types

Data Authentic Source # 
Instance details

Defined in Network.RADIUS.Types

Methods

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

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

toConstr :: Authentic -> Constr #

dataTypeOf :: Authentic -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Authentic Source # 
Instance details

Defined in Network.RADIUS.Types

Binary Authentic Source # 
Instance details

Defined in Network.RADIUS.Encoding

data TerminateCause Source #

Instances
Enum TerminateCause Source # 
Instance details

Defined in Network.RADIUS.Types

Eq TerminateCause Source # 
Instance details

Defined in Network.RADIUS.Types

Data TerminateCause Source # 
Instance details

Defined in Network.RADIUS.Types

Methods

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

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

toConstr :: TerminateCause -> Constr #

dataTypeOf :: TerminateCause -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TerminateCause Source # 
Instance details

Defined in Network.RADIUS.Types

Binary TerminateCause Source # 
Instance details

Defined in Network.RADIUS.Encoding

data ServiceType Source #

Instances
Enum ServiceType Source # 
Instance details

Defined in Network.RADIUS.Types

Eq ServiceType Source # 
Instance details

Defined in Network.RADIUS.Types

Data ServiceType Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary ServiceType Source # 
Instance details

Defined in Network.RADIUS.Encoding

data FramedProtocol Source #

Instances
Enum FramedProtocol Source # 
Instance details

Defined in Network.RADIUS.Types

Eq FramedProtocol Source # 
Instance details

Defined in Network.RADIUS.Types

Data FramedProtocol Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary FramedProtocol Source # 
Instance details

Defined in Network.RADIUS.Encoding

data FramedRouting Source #

Instances
Enum FramedRouting Source # 
Instance details

Defined in Network.RADIUS.Types

Eq FramedRouting Source # 
Instance details

Defined in Network.RADIUS.Types

Data FramedRouting Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary FramedRouting Source # 
Instance details

Defined in Network.RADIUS.Encoding

data FramedCompression Source #

Instances
Enum FramedCompression Source # 
Instance details

Defined in Network.RADIUS.Types

Eq FramedCompression Source # 
Instance details

Defined in Network.RADIUS.Types

Data FramedCompression Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary FramedCompression Source # 
Instance details

Defined in Network.RADIUS.Encoding

data LoginService Source #

Instances
Enum LoginService Source # 
Instance details

Defined in Network.RADIUS.Types

Eq LoginService Source # 
Instance details

Defined in Network.RADIUS.Types

Data LoginService Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary LoginService Source # 
Instance details

Defined in Network.RADIUS.Encoding

data TerminationAction Source #

Instances
Enum TerminationAction Source # 
Instance details

Defined in Network.RADIUS.Types

Eq TerminationAction Source # 
Instance details

Defined in Network.RADIUS.Types

Data TerminationAction Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary TerminationAction Source # 
Instance details

Defined in Network.RADIUS.Encoding

data NASPortType Source #

Instances
Enum NASPortType Source # 
Instance details

Defined in Network.RADIUS.Types

Eq NASPortType Source # 
Instance details

Defined in Network.RADIUS.Types

Data NASPortType Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary NASPortType Source # 
Instance details

Defined in Network.RADIUS.Encoding

data ARAPZoneAccess Source #

Instances
Enum ARAPZoneAccess Source # 
Instance details

Defined in Network.RADIUS.Types

Eq ARAPZoneAccess Source # 
Instance details

Defined in Network.RADIUS.Types

Data ARAPZoneAccess Source # 
Instance details

Defined in Network.RADIUS.Types

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 # 
Instance details

Defined in Network.RADIUS.Types

Binary ARAPZoneAccess Source # 
Instance details

Defined in Network.RADIUS.Encoding