Copyright | (c) Erick Gonzalez 2019 |
---|---|
License | BSD3 |
Maintainer | erick@codemonkeylabs.de |
Safe Haskell | None |
Language | Haskell2010 |
This library allows for the manipulation of strongSwan connection configuration stored in a MySQL database in a manner that is compatible with the strongSwan SQL plugin for charon.
How to use this module:
The strongSwan IPsec package offers the means to store connection configuration in a SQL database. This module offers some facilities to manipulate these config elements from Haskell code in a simplified abstracted way. This library offers two approaches to manipulating strongswan configuration in an SQL database as expected by the SQL plugin. See Managed vs Manual API below.
Synopsis
- mkContext :: (Failable m, MonadIO m) => Settings -> m Context
- writeIPSecSettings :: (Failable m, MonadIO m) => IPSecSettings -> Context -> m IPSecSettings
- findIPSecSettings :: (Failable m, MonadIO m) => Text -> Context -> m IPSecSettings
- lookupIPSecSettings :: (Failable m, MonadIO m) => Text -> Context -> m (Maybe IPSecSettings)
- deleteIPSecSettings :: (Failable m, MonadIO m) => IPSecSettings -> Context -> m IPSecSettings
- addSecret :: (Failable m, MonadIO m) => Identity -> SharedSecret -> Context -> m Identity
- removeSecret :: (Failable m, MonadIO m) => Identity -> SharedSecretType -> Context -> m ()
- removeIdentity :: (Failable m, MonadIO m) => Identity -> Context -> m ()
- writeChild2TSConfig :: (Failable m, MonadIO m) => Child2TSConfig -> Context -> m (Result (Int, Int))
- writeChildSAConfig :: (Failable m, MonadIO m) => ChildSAConfig -> Context -> m (Result Int)
- writeIdentity :: (Failable m, MonadIO m) => Identity -> Context -> m (Result Int)
- writeIKEConfig :: (Failable m, MonadIO m) => IKEConfig -> Context -> m (Result Int)
- writePeerConfig :: (Failable m, MonadIO m) => PeerConfig -> Context -> m (Result Int)
- writePeer2ChildConfig :: (Failable m, MonadIO m) => Peer2ChildConfig -> Context -> m (Result (Int, Int))
- writeSharedSecret :: (Failable m, MonadIO m) => SharedSecret -> Context -> m (Result Int)
- writeSSIdentity :: (Failable m, MonadIO m) => SharedSecretIdentity -> Context -> m (Result (Int, Int))
- writeTrafficSelector :: (Failable m, MonadIO m) => TrafficSelector -> Context -> m (Result Int)
- lookupChild2TSConfig :: (Failable m, MonadIO m) => Int -> Context -> m [Child2TSConfig]
- findChildSAConfig :: (Failable m, MonadIO m) => Int -> Context -> m ChildSAConfig
- findChildSAConfigByName :: (Failable m, MonadIO m) => Text -> Context -> m [ChildSAConfig]
- findIdentity :: (Failable m, MonadIO m) => Int -> Context -> m Identity
- findIdentityBySelf :: (Failable m, MonadIO m) => Identity -> Context -> m Identity
- findIKEConfig :: (Failable m, MonadIO m) => Int -> Context -> m IKEConfig
- findPeerConfig :: (Failable m, MonadIO m) => Int -> Context -> m PeerConfig
- findPeerConfigByName :: (Failable m, MonadIO m) => Text -> Context -> m [PeerConfig]
- findPeer2ChildConfig :: (Failable m, MonadIO m) => Int -> Int -> Context -> m Peer2ChildConfig
- findSharedSecret :: (Failable m, MonadIO m) => Int -> Context -> m SharedSecret
- findSSIdentity :: (Failable m, MonadIO m) => Int -> Context -> m [SharedSecretIdentity]
- findTrafficSelector :: (Failable m, MonadIO m) => Int -> Context -> m TrafficSelector
- lookupChildSAConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe ChildSAConfig)
- lookupIdentity :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe Identity)
- lookupIdentityBySelf :: (Failable m, MonadIO m) => Identity -> Context -> m (Maybe Identity)
- lookupIKEConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe IKEConfig)
- lookupPeerConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe PeerConfig)
- lookupPeer2ChildConfig :: (Failable m, MonadIO m) => Int -> Int -> Context -> m (Maybe Peer2ChildConfig)
- lookupSharedSecret :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe SharedSecret)
- lookupTrafficSelector :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe TrafficSelector)
- deleteChild2TSConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Result Int)
- deleteChildSAConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Result Int)
- deleteIdentity :: (Failable m, MonadIO m) => Int -> Context -> m (Result Int)
- deleteIKEConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Result Int)
- deleteSharedSecret :: (Failable m, MonadIO m) => Int -> Context -> m (Result Int)
- deleteSSIdentity :: (Failable m, MonadIO m) => SharedSecretIdentity -> Context -> m (Result (Int, Int))
- deletePeer2ChildConfig :: (Failable m, MonadIO m) => Int -> Int -> Context -> m (Result (Int, Int))
- deletePeerConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Result Int)
- ikeReqCert :: Lens' IKEConfig Bool
- ikeRemoteAddress :: Lens' IKEConfig Text
- ikeLocalAddress :: Lens' IKEConfig Text
- ikeId :: Lens' IKEConfig (Maybe Int)
- ikeForceEncap :: Lens' IKEConfig Bool
- childSAUpDown :: Lens' ChildSAConfig (Maybe Text)
- childSAStartAction :: Lens' ChildSAConfig SAAction
- childSAReqID :: Lens' ChildSAConfig Word32
- childSARekeyTime :: Lens' ChildSAConfig Word32
- childSAName :: Lens' ChildSAConfig Text
- childSAMode :: Lens' ChildSAConfig SAMode
- childSAMark :: Lens' ChildSAConfig (Maybe Text)
- childSALifeTime :: Lens' ChildSAConfig Word32
- childSAJitter :: Lens' ChildSAConfig Word32
- childSAId :: Lens' ChildSAConfig (Maybe Int)
- childSAIPCompression :: Lens' ChildSAConfig Bool
- childSAHostAccess :: Lens' ChildSAConfig Bool
- childSADPDAction :: Lens' ChildSAConfig SAAction
- childSACloseAction :: Lens' ChildSAConfig SAAction
- peerCfgVirtual :: Lens' PeerConfig (Maybe Text)
- peerCfgUniqueIds :: Lens' PeerConfig Bool
- peerCfgRemoteId :: Lens' PeerConfig (Maybe Int)
- peerCfgRekeyTime :: Lens' PeerConfig Word32
- peerCfgReauthTime :: Lens' PeerConfig Word32
- peerCfgPool :: Lens' PeerConfig (Maybe Text)
- peerCfgPeerId :: Lens' PeerConfig Int
- peerCfgOverTime :: Lens' PeerConfig Word32
- peerCfgName :: Lens' PeerConfig Text
- peerCfgMobike :: Lens' PeerConfig Bool
- peerCfgMediation :: Lens' PeerConfig Bool
- peerCfgMediatedBy :: Lens' PeerConfig Int
- peerCfgLocalId :: Lens' PeerConfig (Maybe Int)
- peerCfgKeyingTries :: Lens' PeerConfig Word8
- peerCfgJitter :: Lens' PeerConfig Word32
- peerCfgId :: Lens' PeerConfig (Maybe Int)
- peerCfgIKEVersion :: Lens' PeerConfig Word8
- peerCfgIKEConfigId :: Lens' PeerConfig (Maybe Int)
- peerCfgEAPVendor :: Lens' PeerConfig Word16
- peerCfgEAPType :: Lens' PeerConfig EAPType
- peerCfgDPDDelay :: Lens' PeerConfig Word32
- peerCfgCertPolicy :: Lens' PeerConfig CertPolicy
- peerCfgAuthMethod :: Lens' PeerConfig AuthMethod
- tsType :: Lens' TrafficSelector TrafficSelectorType
- tsStartPort :: Lens' TrafficSelector PortNumber
- tsStartAddr :: Lens' TrafficSelector IP
- tsProtocol :: Lens' TrafficSelector Word16
- tsId :: Lens' TrafficSelector (Maybe Int)
- tsEndPort :: Lens' TrafficSelector PortNumber
- tsEndAddr :: Lens' TrafficSelector IP
- ssType :: Lens' SharedSecret SharedSecretType
- ssId :: Lens' SharedSecret (Maybe Int)
- ssData :: Lens' SharedSecret ByteString
- sharedSecretId :: Lens' SharedSecretIdentity Int
- identityId :: Lens' SharedSecretIdentity Int
- getRemoteTrafficSelector :: Lens' IPSecSettings TrafficSelector
- getRemoteIdentity :: Lens' IPSecSettings Identity
- getPeerConfig :: Lens' IPSecSettings PeerConfig
- getLocalTrafficSelector :: Lens' IPSecSettings TrafficSelector
- getLocalIdentity :: Lens' IPSecSettings Identity
- getIPSecCfgName :: Lens' IPSecSettings Text
- getIKEConfig :: Lens' IPSecSettings IKEConfig
- getChildSAConfig :: Lens' IPSecSettings ChildSAConfig
- dbHost :: Lens' Settings HostName
- dbPort :: Lens' Settings PortNumber
- dbName :: Lens' Settings String
- dbUser :: Lens' Settings String
- dbPassword :: Lens' Settings String
- dbCharSet :: Lens' Settings MySQLCharacterEncoding
- data AuthMethod
- data ChildSAConfig = ChildSAConfig {
- _childSAId :: Maybe Int
- _childSAName :: Text
- _childSALifeTime :: Word32
- _childSARekeyTime :: Word32
- _childSAJitter :: Word32
- _childSAUpDown :: Maybe Text
- _childSAHostAccess :: Bool
- _childSAMode :: SAMode
- _childSAStartAction :: SAAction
- _childSADPDAction :: SAAction
- _childSACloseAction :: SAAction
- _childSAIPCompression :: Bool
- _childSAReqID :: Word32
- _childSAMark :: Maybe Text
- data Child2TSConfig = Child2TSConfig {}
- data CertPolicy
- type Context = MVar Context_
- data EAPType
- = EAPUnspecified
- | EAPMD5
- | EAPGTC
- | EAPTLS
- | EAPSIM
- | EAPTTLS
- | EAPAKA
- | EAPMSCHAPV2
- | EAPTNC
- | EAPRADIUS
- data Error
- = UnknownCharacterEncoding Int
- | UnknownSAMode Int
- | UnknownSAAction Int
- | UnknownCertPolicy Int
- | UnknownAuthMethod Int
- | UnknownEAPType Int
- | UnknownTrafficSelectorType Int
- | UnknownTrafficSelectorKind Int
- | UnknownSharedSecretType Int
- | InvalidValueForType String String
- | SQLValuesMismatch String String
- | NotFound Text
- | MultipleResults Text String
- | FailedOperation Text
- data Identity
- data IKEConfig = IKEConfig {}
- data IPSecSettings = IPSecSettings {}
- data PeerConfig = PeerConfig {
- _peerCfgId :: Maybe Int
- _peerCfgName :: Text
- _peerCfgIKEVersion :: Word8
- _peerCfgIKEConfigId :: Maybe Int
- _peerCfgLocalId :: Maybe Int
- _peerCfgRemoteId :: Maybe Int
- _peerCfgCertPolicy :: CertPolicy
- _peerCfgUniqueIds :: Bool
- _peerCfgAuthMethod :: AuthMethod
- _peerCfgEAPType :: EAPType
- _peerCfgEAPVendor :: Word16
- _peerCfgKeyingTries :: Word8
- _peerCfgRekeyTime :: Word32
- _peerCfgReauthTime :: Word32
- _peerCfgJitter :: Word32
- _peerCfgOverTime :: Word32
- _peerCfgMobike :: Bool
- _peerCfgDPDDelay :: Word32
- _peerCfgVirtual :: Maybe Text
- _peerCfgPool :: Maybe Text
- _peerCfgMediation :: Bool
- _peerCfgMediatedBy :: Int
- _peerCfgPeerId :: Int
- data Peer2ChildConfig = Peer2ChildConfig {
- p2cPeerCfgId :: Int
- p2cChildCfgId :: Int
- data Result a = Result {
- lastModifiedKey :: a
- response :: OK
- data SAAction
- data SAMode
- data Settings = Settings {
- _dbName :: String
- _dbHost :: HostName
- _dbPort :: PortNumber
- _dbUser :: String
- _dbPassword :: String
- _dbCharSet :: MySQLCharacterEncoding
- data SharedSecret = SharedSecret {}
- data SharedSecretIdentity = SharedSecretIdentity {
- _sharedSecretId :: Int
- _identityId :: Int
- data SharedSecretType
- data OK = OK {
- okAffectedRows :: !Int
- okLastInsertID :: !Int
- okStatus :: !Word16
- okWarningCnt :: !Word16
- class SQLRow a
- data TrafficSelector = TrafficSelector {}
- data TrafficSelectorType
- data TrafficSelectorKind
Initialization
Managed API
Since managing each configuration object per hand and establishing the relationships
amongst them can be tricky and demands internal knowledge of the SQL plugin inner workings,
a special API is offered in which all configuration parameters are bundled together
in a single type (see IPSecSettings
). The simplified API allows then for writing, reading
and deleting these, while behind bars the required elements are created and linked
together unbeknownst to the caller. This of course greatly simplifies things but the
catch is that the ability to share configuration elements amongst connections is of
course lost. Each managed connection configuration gets a separate IKE, Child SA, Peer
config etc and no attempt is made to reuse them amongst managed connections.
writeIPSecSettings :: (Failable m, MonadIO m) => IPSecSettings -> Context -> m IPSecSettings Source #
Pushes an IPsec configuration into the DB specified in the given context. Note that if there are any
existing elements in the configuration, they are first released (and their inter relationships in the
SQL DB removed), before creating them. As a result the different IDs inside the elements etc will probably
change. This is the reason why a new IPSecSettings
value is returned as a result of the operation and
the value "pushed" to the DB originally should not be used any further.
findIPSecSettings :: (Failable m, MonadIO m) => Text -> Context -> m IPSecSettings Source #
Search for an IPsec connection configuration by its unique name. Take note of the Failable
context,
which means that unless it is desired that this function throws an asynchronous exception upon not finding
a configuration, you probably want to run this inside a monadic transformer such as MaybeT
or ExceptT
lookupIPSecSettings :: (Failable m, MonadIO m) => Text -> Context -> m (Maybe IPSecSettings) Source #
deleteIPSecSettings :: (Failable m, MonadIO m) => IPSecSettings -> Context -> m IPSecSettings Source #
Removes the specified IPSecSettings
from the DB, releasing all linked elements. The returned
IPSecSettings will contain now "unlinked" elements (i.e. no IDs, etc).
addSecret :: (Failable m, MonadIO m) => Identity -> SharedSecret -> Context -> m Identity Source #
Adds a shared secret to a given identity. If the identity doesn't exist it will get created. If the identity already exists and it already has a secret of the same type, it will be overwritten. This means there can only be one secret of any given type per identity (which makes sense of course from strongswan's perspective).
removeSecret :: (Failable m, MonadIO m) => Identity -> SharedSecretType -> Context -> m () Source #
Removes a secret of the given type (if present) from the specified identity
removeIdentity :: (Failable m, MonadIO m) => Identity -> Context -> m () Source #
Removes an identity and its secrets and related entries altogether
Manual API
The different strongswan configuration elements are mapped to a Haskell type and they can be manually written or read from the SQL database. This offers utmost control in terms of what elements get created and how they are interlinked. So for example one can create a single IKE session configuration to be shared for all connections or have some child SA configurations being shared amongst peers of a given type, etc. The downside of course to this level of control is that it requires for the user of the library to be familiar with the (poorly documented) way in which the plugin expects the relationships to be expressed in terms of entries in the SQL tables etc.
The manual API has been reverse engineered based on the SQL table definitions available here
- Child SA : All configuration parameters related to an IPsec SA.
- IKE Configuration : Configuration applicable to the IKE session (phase 1 in IKEv1 parlance).
- Peer Configuration : All elements related to configuration of a peering connection.
A peer connection links to a specific IKE configuration (by means of ID), and it is
furthermore associated to the Child SA by means of a
Peer2ChildConfig
type. - Traffic Selectors: These are independent values linked to a Child SA by means of a
Child2TSConfig
type.
The manual API consists mainly of one writeXXX
, findXXX
, lookupXXX
and a deleteXXX
function for each object to be stored as an SQL row in its respective table. The writeXXX
functions trigger an insertion or an update of the given row in the SQL database depending
on whether the given object owns a key already or not (usually an ID). The search functions
(findXXX
and lookupXXX
) perform a search in the DB for the given key. The difference is
that a findXXX
will trigger a failure
in the Failable
context with a NotFound
error
and that the lookupXXX
functions simply return Nothing
if a key doesn't exist in the DB
(they can of course trigger other errors in the Failable context)
writeChild2TSConfig :: (Failable m, MonadIO m) => Child2TSConfig -> Context -> m (Result (Int, Int)) Source #
writeChildSAConfig :: (Failable m, MonadIO m) => ChildSAConfig -> Context -> m (Result Int) Source #
writePeerConfig :: (Failable m, MonadIO m) => PeerConfig -> Context -> m (Result Int) Source #
writePeer2ChildConfig :: (Failable m, MonadIO m) => Peer2ChildConfig -> Context -> m (Result (Int, Int)) Source #
writeSharedSecret :: (Failable m, MonadIO m) => SharedSecret -> Context -> m (Result Int) Source #
writeSSIdentity :: (Failable m, MonadIO m) => SharedSecretIdentity -> Context -> m (Result (Int, Int)) Source #
writeTrafficSelector :: (Failable m, MonadIO m) => TrafficSelector -> Context -> m (Result Int) Source #
lookupChild2TSConfig :: (Failable m, MonadIO m) => Int -> Context -> m [Child2TSConfig] Source #
findChildSAConfig :: (Failable m, MonadIO m) => Int -> Context -> m ChildSAConfig Source #
findChildSAConfigByName :: (Failable m, MonadIO m) => Text -> Context -> m [ChildSAConfig] Source #
findPeerConfig :: (Failable m, MonadIO m) => Int -> Context -> m PeerConfig Source #
findPeerConfigByName :: (Failable m, MonadIO m) => Text -> Context -> m [PeerConfig] Source #
findPeer2ChildConfig :: (Failable m, MonadIO m) => Int -> Int -> Context -> m Peer2ChildConfig Source #
findSharedSecret :: (Failable m, MonadIO m) => Int -> Context -> m SharedSecret Source #
findSSIdentity :: (Failable m, MonadIO m) => Int -> Context -> m [SharedSecretIdentity] Source #
findTrafficSelector :: (Failable m, MonadIO m) => Int -> Context -> m TrafficSelector Source #
lookupChildSAConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe ChildSAConfig) Source #
lookupIdentityBySelf :: (Failable m, MonadIO m) => Identity -> Context -> m (Maybe Identity) Source #
lookupPeerConfig :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe PeerConfig) Source #
lookupPeer2ChildConfig :: (Failable m, MonadIO m) => Int -> Int -> Context -> m (Maybe Peer2ChildConfig) Source #
lookupSharedSecret :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe SharedSecret) Source #
lookupTrafficSelector :: (Failable m, MonadIO m) => Int -> Context -> m (Maybe TrafficSelector) Source #
deleteSSIdentity :: (Failable m, MonadIO m) => SharedSecretIdentity -> Context -> m (Result (Int, Int)) Source #
deletePeer2ChildConfig :: (Failable m, MonadIO m) => Int -> Int -> Context -> m (Result (Int, Int)) Source #
Lenses
There are lenses exported to facilitate access to the records in the type section below.
peerCfgPool :: Lens' PeerConfig (Maybe Text) Source #
peerCfgLocalId :: Lens' PeerConfig (Maybe Int) Source #
Types
data AuthMethod Source #
Instances
Enum AuthMethod Source # | |
Defined in StrongSwan.SQL.Types succ :: AuthMethod -> AuthMethod # pred :: AuthMethod -> AuthMethod # toEnum :: Int -> AuthMethod # fromEnum :: AuthMethod -> Int # enumFrom :: AuthMethod -> [AuthMethod] # enumFromThen :: AuthMethod -> AuthMethod -> [AuthMethod] # enumFromTo :: AuthMethod -> AuthMethod -> [AuthMethod] # enumFromThenTo :: AuthMethod -> AuthMethod -> AuthMethod -> [AuthMethod] # | |
Eq AuthMethod Source # | |
Defined in StrongSwan.SQL.Types (==) :: AuthMethod -> AuthMethod -> Bool # (/=) :: AuthMethod -> AuthMethod -> Bool # | |
Show AuthMethod Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> AuthMethod -> ShowS # show :: AuthMethod -> String # showList :: [AuthMethod] -> ShowS # |
data ChildSAConfig Source #
Instances
Eq ChildSAConfig Source # | |
Defined in StrongSwan.SQL.Types (==) :: ChildSAConfig -> ChildSAConfig -> Bool # (/=) :: ChildSAConfig -> ChildSAConfig -> Bool # | |
Show ChildSAConfig Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> ChildSAConfig -> ShowS # show :: ChildSAConfig -> String # showList :: [ChildSAConfig] -> ShowS # | |
Default ChildSAConfig Source # | |
Defined in StrongSwan.SQL.Types def :: ChildSAConfig # | |
SQLRow ChildSAConfig Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: ChildSAConfig -> [MySQLValue] fromValues :: [MySQLValue] -> ChildSAConfig |
data Child2TSConfig Source #
Instances
Show Child2TSConfig Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> Child2TSConfig -> ShowS # show :: Child2TSConfig -> String # showList :: [Child2TSConfig] -> ShowS # | |
SQLRow Child2TSConfig Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: Child2TSConfig -> [MySQLValue] fromValues :: [MySQLValue] -> Child2TSConfig |
data CertPolicy Source #
Instances
Enum CertPolicy Source # | |
Defined in StrongSwan.SQL.Types succ :: CertPolicy -> CertPolicy # pred :: CertPolicy -> CertPolicy # toEnum :: Int -> CertPolicy # fromEnum :: CertPolicy -> Int # enumFrom :: CertPolicy -> [CertPolicy] # enumFromThen :: CertPolicy -> CertPolicy -> [CertPolicy] # enumFromTo :: CertPolicy -> CertPolicy -> [CertPolicy] # enumFromThenTo :: CertPolicy -> CertPolicy -> CertPolicy -> [CertPolicy] # | |
Eq CertPolicy Source # | |
Defined in StrongSwan.SQL.Types (==) :: CertPolicy -> CertPolicy -> Bool # (/=) :: CertPolicy -> CertPolicy -> Bool # | |
Show CertPolicy Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> CertPolicy -> ShowS # show :: CertPolicy -> String # showList :: [CertPolicy] -> ShowS # |
Instances
Show Error Source # | |
Exception Error Source # | |
Defined in StrongSwan.SQL.Types toException :: Error -> SomeException # fromException :: SomeException -> Maybe Error # displayException :: Error -> String # |
AnyID (Maybe Int) | |
IPv4AddrID (Maybe Int) IPv4 | |
NameID (Maybe Int) Text | |
EmailID (Maybe Int) Text Text | RFC 822 Email Address mailbox@domain |
IPv6AddrID (Maybe Int) IPv6 | |
ASN1ID (Maybe Int) [ASN1] | |
OpaqueID (Maybe Int) ByteString |
Instances
Eq Identity Source # | |
Show Identity Source # | |
Default Identity Source # | |
Defined in StrongSwan.SQL.Types | |
SQLRow Identity Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: Identity -> [MySQLValue] fromValues :: [MySQLValue] -> Identity |
IKEConfig | |
|
Instances
Eq IKEConfig Source # | |
Show IKEConfig Source # | |
Default IKEConfig Source # | |
Defined in StrongSwan.SQL.Types | |
SQLRow IKEConfig Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: IKEConfig -> [MySQLValue] fromValues :: [MySQLValue] -> IKEConfig |
data IPSecSettings Source #
The managed IPsec configuration type encompasses a complete set of elements which are pushed and interlinked as necessary by the Managed API (see above). Note that there are lenses available to facilitate accessing all these fields (see StrongSwan.SQL.Lenses)
Instances
Eq IPSecSettings Source # | |
Defined in StrongSwan.SQL.Types (==) :: IPSecSettings -> IPSecSettings -> Bool # (/=) :: IPSecSettings -> IPSecSettings -> Bool # | |
Show IPSecSettings Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> IPSecSettings -> ShowS # show :: IPSecSettings -> String # showList :: [IPSecSettings] -> ShowS # | |
Default IPSecSettings Source # | |
Defined in StrongSwan.SQL.Types def :: IPSecSettings # |
data PeerConfig Source #
Instances
Eq PeerConfig Source # | |
Defined in StrongSwan.SQL.Types (==) :: PeerConfig -> PeerConfig -> Bool # (/=) :: PeerConfig -> PeerConfig -> Bool # | |
Show PeerConfig Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> PeerConfig -> ShowS # show :: PeerConfig -> String # showList :: [PeerConfig] -> ShowS # | |
Default PeerConfig Source # | |
Defined in StrongSwan.SQL.Types def :: PeerConfig # | |
SQLRow PeerConfig Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: PeerConfig -> [MySQLValue] fromValues :: [MySQLValue] -> PeerConfig |
data Peer2ChildConfig Source #
Instances
Show Peer2ChildConfig Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> Peer2ChildConfig -> ShowS # show :: Peer2ChildConfig -> String # showList :: [Peer2ChildConfig] -> ShowS # | |
SQLRow Peer2ChildConfig Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: Peer2ChildConfig -> [MySQLValue] fromValues :: [MySQLValue] -> Peer2ChildConfig |
Instances
Enum SAAction Source # | |
Eq SAAction Source # | |
Show SAAction Source # | |
Settings | |
|
data SharedSecret Source #
You may get interested in OK
packet because it provides information about
successful operations.
OK | |
|
toValues, fromValues
Instances
data TrafficSelector Source #
TrafficSelector | |
|
Instances
Eq TrafficSelector Source # | |
Defined in StrongSwan.SQL.Types (==) :: TrafficSelector -> TrafficSelector -> Bool # (/=) :: TrafficSelector -> TrafficSelector -> Bool # | |
Show TrafficSelector Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> TrafficSelector -> ShowS # show :: TrafficSelector -> String # showList :: [TrafficSelector] -> ShowS # | |
Default TrafficSelector Source # | |
Defined in StrongSwan.SQL.Types def :: TrafficSelector # | |
SQLRow TrafficSelector Source # | |
Defined in StrongSwan.SQL.Encoding toValues :: TrafficSelector -> [MySQLValue] fromValues :: [MySQLValue] -> TrafficSelector |
data TrafficSelectorType Source #
Instances
Enum TrafficSelectorType Source # | |
Defined in StrongSwan.SQL.Types succ :: TrafficSelectorType -> TrafficSelectorType # pred :: TrafficSelectorType -> TrafficSelectorType # toEnum :: Int -> TrafficSelectorType # fromEnum :: TrafficSelectorType -> Int # enumFrom :: TrafficSelectorType -> [TrafficSelectorType] # enumFromThen :: TrafficSelectorType -> TrafficSelectorType -> [TrafficSelectorType] # enumFromTo :: TrafficSelectorType -> TrafficSelectorType -> [TrafficSelectorType] # enumFromThenTo :: TrafficSelectorType -> TrafficSelectorType -> TrafficSelectorType -> [TrafficSelectorType] # | |
Eq TrafficSelectorType Source # | |
Defined in StrongSwan.SQL.Types (==) :: TrafficSelectorType -> TrafficSelectorType -> Bool # (/=) :: TrafficSelectorType -> TrafficSelectorType -> Bool # | |
Show TrafficSelectorType Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> TrafficSelectorType -> ShowS # show :: TrafficSelectorType -> String # showList :: [TrafficSelectorType] -> ShowS # |
data TrafficSelectorKind Source #
Instances
Enum TrafficSelectorKind Source # | |
Defined in StrongSwan.SQL.Types succ :: TrafficSelectorKind -> TrafficSelectorKind # pred :: TrafficSelectorKind -> TrafficSelectorKind # toEnum :: Int -> TrafficSelectorKind # fromEnum :: TrafficSelectorKind -> Int # enumFrom :: TrafficSelectorKind -> [TrafficSelectorKind] # enumFromThen :: TrafficSelectorKind -> TrafficSelectorKind -> [TrafficSelectorKind] # enumFromTo :: TrafficSelectorKind -> TrafficSelectorKind -> [TrafficSelectorKind] # enumFromThenTo :: TrafficSelectorKind -> TrafficSelectorKind -> TrafficSelectorKind -> [TrafficSelectorKind] # | |
Eq TrafficSelectorKind Source # | |
Defined in StrongSwan.SQL.Types (==) :: TrafficSelectorKind -> TrafficSelectorKind -> Bool # (/=) :: TrafficSelectorKind -> TrafficSelectorKind -> Bool # | |
Show TrafficSelectorKind Source # | |
Defined in StrongSwan.SQL.Types showsPrec :: Int -> TrafficSelectorKind -> ShowS # show :: TrafficSelectorKind -> String # showList :: [TrafficSelectorKind] -> ShowS # |