module Propellor.Types.PrivData where
import Propellor.Types.OS
import Utility.PartialPrelude
import Utility.FileSystemEncoding
import Data.Maybe
import qualified Data.ByteString.Lazy as L
data PrivDataField
= DockerAuthentication
| SshPubKey SshKeyType UserName
| SshPrivKey SshKeyType UserName
| SshAuthorizedKeys UserName
| Password UserName
| CryptPassword UserName
| PrivFile FilePath
| GpgKey
| DnsSec DnsSecKey
deriving (Read, Show, Ord, Eq)
data PrivDataSource
= PrivDataSourceFile PrivDataField FilePath
| PrivDataSourceFileFromCommand PrivDataField FilePath String
| PrivDataSource PrivDataField String
type PrivDataSourceDesc = String
class IsPrivDataSource s where
privDataField :: s -> PrivDataField
describePrivDataSource :: s -> Maybe PrivDataSourceDesc
instance IsPrivDataSource PrivDataField where
privDataField = id
describePrivDataSource _ = Nothing
instance IsPrivDataSource PrivDataSource where
privDataField s = case s of
PrivDataSourceFile f _ -> f
PrivDataSourceFileFromCommand f _ _ -> f
PrivDataSource f _ -> f
describePrivDataSource s = Just $ case s of
PrivDataSourceFile _ f -> "< " ++ f
PrivDataSourceFileFromCommand _ f c ->
"< " ++ f ++ " (created by running, for example, `" ++ c ++ "` )"
PrivDataSource _ d -> "< (" ++ d ++ ")"
newtype Context = Context String
deriving (Read, Show, Ord, Eq)
newtype HostContext = HostContext { mkHostContext :: HostName -> Context }
instance Show HostContext where
show hc = show $ mkHostContext hc "<hostname>"
instance Ord HostContext where
a <= b = show a <= show b
instance Eq HostContext where
a == b = show a == show b
class IsContext c where
asContext :: HostName -> c -> Context
asHostContext :: c -> HostContext
instance IsContext HostContext where
asContext = flip mkHostContext
asHostContext = id
instance IsContext Context where
asContext _ c = c
asHostContext = HostContext . const
anyContext :: Context
anyContext = Context "any"
hostContext :: HostContext
hostContext = HostContext Context
newtype PrivData = PrivData String
privDataLines :: PrivData -> [String]
privDataLines (PrivData s) = lines s
privDataVal :: PrivData -> String
privDataVal (PrivData s) = fromMaybe "" (headMaybe (lines s))
privDataByteString :: PrivData -> L.ByteString
privDataByteString (PrivData s) = encodeBS s
data SshKeyType = SshRsa | SshDsa | SshEcdsa | SshEd25519
deriving (Read, Show, Ord, Eq, Enum, Bounded)
sshKeyTypeParam :: SshKeyType -> String
sshKeyTypeParam SshRsa = "RSA"
sshKeyTypeParam SshDsa = "DSA"
sshKeyTypeParam SshEcdsa = "ECDSA"
sshKeyTypeParam SshEd25519 = "ED25519"
data DnsSecKey
= PubZSK
| PrivZSK
| PubKSK
| PrivKSK
deriving (Read, Show, Ord, Eq, Bounded, Enum)