| Copyright | (c) Erick Gonzalez 2017 |
|---|---|
| License | BSD3 |
| Maintainer | erick@codemonkeylabs.de |
| Stability | experimental |
| Portability | POSIX |
| Safe Haskell | None |
| Language | Haskell2010 |
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
Constructors
| Header | |
Fields | |
data PacketType Source #
Constructors
| AccessRequest | |
| AccessAccept | |
| AccessReject | |
| AccountingRequest | |
| AccountingResponse | |
| AccessChallenge | |
| StatusServer | |
| StatusClient | |
| UnknownPacketType Int |
Instances
| Enum PacketType Source # | |
Defined in Network.RADIUS.Types Methods succ :: PacketType -> PacketType # pred :: PacketType -> PacketType # toEnum :: Int -> PacketType # fromEnum :: PacketType -> Int # enumFrom :: PacketType -> [PacketType] # enumFromThen :: PacketType -> PacketType -> [PacketType] # enumFromTo :: PacketType -> PacketType -> [PacketType] # enumFromThenTo :: PacketType -> PacketType -> PacketType -> [PacketType] # | |
| Eq PacketType Source # | |
Defined in Network.RADIUS.Types | |
| Show PacketType Source # | |
Defined in Network.RADIUS.Types Methods showsPrec :: Int -> PacketType -> ShowS # show :: PacketType -> String # showList :: [PacketType] -> ShowS # | |
| Binary PacketType Source # | |
Defined in Network.RADIUS.Encoding | |
data PacketAttribute Source #
Constructors
Instances
data StatusType Source #
Constructors
| Start | |
| Stop | |
| InterimUpdate | |
| AccountingOn | |
| AccountingOff | |
| Failed | |
| UnknownStatusType Int |
Instances
Constructors
| Radius | |
| Local | |
| Remote | |
| UnknownAuthentic Int |
Instances
| Enum Authentic Source # | |
Defined in Network.RADIUS.Types Methods succ :: Authentic -> Authentic # pred :: Authentic -> Authentic # fromEnum :: Authentic -> Int # enumFrom :: Authentic -> [Authentic] # enumFromThen :: Authentic -> Authentic -> [Authentic] # enumFromTo :: Authentic -> Authentic -> [Authentic] # enumFromThenTo :: Authentic -> Authentic -> Authentic -> [Authentic] # | |
| Eq Authentic Source # | |
| Data Authentic Source # | |
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 # | |
| Binary Authentic Source # | |
data TerminateCause Source #
Constructors
Instances
data ServiceType Source #
Constructors
Instances
data FramedProtocol Source #
Constructors
| PPPFramedProtocol | |
| SLIPFramedProtocol | |
| ARAPFramedProtocol | |
| GandalfFramedProtocol | |
| XylogicsFramedProtocol | |
| X75FramedProtocol | |
| UnknownFramedProtocol Int |
Instances
data FramedRouting Source #
Constructors
| NoneFramedRouting | |
| SendFramedRouting | |
| ListenFramedRouting | |
| SendAndListenFramedRouting | |
| UnknownFramedRouting Int |
Instances
data FramedCompression Source #
Constructors
| NoCompression | |
| VJTCPIPHeaderCompression | |
| IPXHeaderCompression | |
| StacLZSCompression | |
| UnknownFramedCompression Int |
Instances
data LoginService Source #
Constructors
| TelnetService | |
| RloginService | |
| TCPClearService | |
| PortMasterService | |
| LATService | |
| X25PADService | |
| X25T3POSService | |
| UnusedService | |
| TCPClearQuietService | |
| UnknownLoginService Int |
Instances
data TerminationAction Source #
Instances
data NASPortType Source #
Constructors
Instances
data ARAPZoneAccess Source #
Constructors
| DefaultZoneOnlyARAPAccess | |
| UseZoneFilterInclusivelyARAPAccess | |
| UseZoneFilterExclusivelyARAPAccess | |
| UnknownARAPZoneAccess Int |
Instances
_StatusClient :: Prism' PacketType () Source #
_StatusServer :: Prism' PacketType () Source #
_AccessChallenge :: Prism' PacketType () Source #
_AccessReject :: Prism' PacketType () Source #
_AccessAccept :: Prism' PacketType () Source #
_AccessRequest :: Prism' PacketType () Source #
_Failed :: Prism' StatusType () Source #
_AccountingOff :: Prism' StatusType () Source #
_AccountingOn :: Prism' StatusType () Source #
_InterimUpdate :: Prism' StatusType () Source #
_Stop :: Prism' StatusType () Source #
_Start :: Prism' StatusType () Source #
_HostRequest :: Prism' TerminateCause () Source #
_UserError :: Prism' TerminateCause () Source #
_Callback :: Prism' TerminateCause () Source #
_PortUnneeded :: Prism' TerminateCause () Source #
_NASReboot :: Prism' TerminateCause () Source #
_NASRequest :: Prism' TerminateCause () Source #
_NASError :: Prism' TerminateCause () Source #
_PortError :: Prism' TerminateCause () Source #
_AdminReboot :: Prism' TerminateCause () Source #
_AdminReset :: Prism' TerminateCause () Source #
_IdleTimeout :: Prism' TerminateCause () Source #
_LostService :: Prism' TerminateCause () Source #
_LostCarrier :: Prism' TerminateCause () Source #
_UserRequest :: Prism' TerminateCause () Source #
_OutboundService :: Prism' ServiceType () Source #
_FramedService :: Prism' ServiceType () Source #
_LoginService :: Prism' ServiceType () Source #
_UnusedService :: Prism' LoginService () Source #
_X25PADService :: Prism' LoginService () Source #
_LATService :: Prism' LoginService () Source #
_RloginService :: Prism' LoginService () Source #
_TelnetService :: Prism' LoginService () Source #
_CableNASPort :: Prism' NASPortType () Source #
_XDSLNASPort :: Prism' NASPortType () Source #
_EthernetNASPort :: Prism' NASPortType () Source #
_IDSLNASPort :: Prism' NASPortType () Source #
_ADSLDMTNASPort :: Prism' NASPortType () Source #
_ADSLCAPNASPort :: Prism' NASPortType () Source #
_SDSLNASPort :: Prism' NASPortType () Source #
_G3FaxNASPort :: Prism' NASPortType () Source #
_X75NASPort :: Prism' NASPortType () Source #
_X25NASPort :: Prism' NASPortType () Source #
_PIAFSNASPort :: Prism' NASPortType () Source #
_VirtualNASPort :: Prism' NASPortType () Source #
_ISDNSyncPort :: Prism' NASPortType () Source #
_SyncNASPort :: Prism' NASPortType () Source #
_AsyncNASPort :: Prism' NASPortType () Source #