| Copyright | (c) Justin Le 2017 |
|---|---|
| License | MIT |
| Maintainer | justin@jle.im |
| Stability | unstable |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Authenticator.Vault
Description
Types for storing, serializing, accessing OTP keys. Gratuitous type-level programming here for no reason because I have issues.
Based off of https://github.com/google/google-authenticator.
Synopsis
- data Mode
- data SMode :: Mode -> Type where
- withSMode :: Mode -> (forall m. SMode m -> r) -> r
- fromSMode :: SMode m -> Mode
- data HashAlgo
- parseAlgo :: String -> Maybe HashAlgo
- data Secret :: Mode -> Type where
- newtype OTPDigits = OTPDigits {}
- pattern OTPDigitsInt :: OTPDigits -> Int
- data family ModeState :: Mode -> Type
- type SomeSecretState = DSum SMode (Secret :*: ModeState)
- newtype Vault = Vault {
- vaultList :: [SomeSecretState]
- _Vault :: Functor f => ([SomeSecretState] -> f [SomeSecretState]) -> Vault -> f Vault
- hotp :: Secret HOTP -> ModeState HOTP -> (Text, ModeState HOTP)
- totp :: Secret TOTP -> IO Text
- totp_ :: Secret TOTP -> POSIXTime -> Text
- otp :: SMode m -> Secret m -> ModeState m -> IO (Text, ModeState m)
- someSecret :: Functor f => (forall m. SMode m -> Secret m -> ModeState m -> f (ModeState m)) -> SomeSecretState -> f SomeSecretState
- vaultSecrets :: Applicative f => (forall m. SMode m -> Secret m -> ModeState m -> f (ModeState m)) -> Vault -> f Vault
- describeSecret :: Secret m -> Text
- secretURI :: Parser SomeSecretState
- parseSecretURI :: String -> Either String SomeSecretState
Documentation
OTP generation mode
Instances
| Show Mode Source # | |
| Generic Mode Source # | |
| ToJSON SomeSecretState Source # | |
Defined in Authenticator.Vault Methods toJSON :: SomeSecretState -> Value # toEncoding :: SomeSecretState -> Encoding # toJSONList :: [SomeSecretState] -> Value # toEncodingList :: [SomeSecretState] -> Encoding # | |
| ToJSON Mode Source # | |
Defined in Authenticator.Vault | |
| Binary SomeSecretState Source # | |
Defined in Authenticator.Vault Methods put :: SomeSecretState -> Put # get :: Get SomeSecretState # putList :: [SomeSecretState] -> Put # | |
| Binary Mode Source # | |
| GShow SMode Source # | |
Defined in Authenticator.Vault Methods gshowsPrec :: Int -> SMode a -> ShowS # | |
| type Rep Mode Source # | |
data SMode :: Mode -> Type where Source #
Singleton for Mode
Instances
| ToJSON SomeSecretState Source # | |
Defined in Authenticator.Vault Methods toJSON :: SomeSecretState -> Value # toEncoding :: SomeSecretState -> Encoding # toJSONList :: [SomeSecretState] -> Value # toEncodingList :: [SomeSecretState] -> Encoding # | |
| Binary SomeSecretState Source # | |
Defined in Authenticator.Vault Methods put :: SomeSecretState -> Put # get :: Get SomeSecretState # putList :: [SomeSecretState] -> Put # | |
| GShow SMode Source # | |
Defined in Authenticator.Vault Methods gshowsPrec :: Int -> SMode a -> ShowS # | |
| Show (SMode m) Source # | |
Which OTP-approved hash algorithm to use?
parseAlgo :: String -> Maybe HashAlgo Source #
Parse a hash algorithm string into the appropriate HashAlgo.
data Secret :: Mode -> Type where Source #
A standards-compliant secret key type. Well, almost. It doesn't include configuration for the time period if it's time-based.
Constructors
| Sec | |
Instances
Newtype wrapper to provide Eq, Ord, Binary, and ToJSON
instances. You can convert to and from this and the Int
representation using OTPDigitsInt
Instances
| Eq OTPDigits Source # | |
| Ord OTPDigits Source # | |
| Show OTPDigits Source # | |
| ToJSON OTPDigits Source # | |
Defined in Authenticator.Vault | |
| Binary OTPDigits Source # | |
pattern OTPDigitsInt :: OTPDigits -> Int Source #
data family ModeState :: Mode -> Type Source #
A data family consisting of the state required by each mode.
Instances
| ToJSON SomeSecretState Source # | |
Defined in Authenticator.Vault Methods toJSON :: SomeSecretState -> Value # toEncoding :: SomeSecretState -> Encoding # toJSONList :: [SomeSecretState] -> Value # toEncodingList :: [SomeSecretState] -> Encoding # | |
| Binary SomeSecretState Source # | |
Defined in Authenticator.Vault Methods put :: SomeSecretState -> Put # get :: Get SomeSecretState # putList :: [SomeSecretState] -> Put # | |
| Show (ModeState HOTP) Source # | |
| Show (ModeState TOTP) Source # | |
| Generic (ModeState HOTP) Source # | |
| Generic (ModeState TOTP) Source # | |
| ToJSON (ModeState HOTP) Source # | |
| ToJSON (ModeState TOTP) Source # | |
| Binary (ModeState HOTP) Source # | |
| Binary (ModeState TOTP) Source # | |
| data ModeState HOTP Source # | For |
Defined in Authenticator.Vault | |
| data ModeState TOTP Source # | For |
Defined in Authenticator.Vault | |
| type Rep (ModeState HOTP) Source # | |
Defined in Authenticator.Vault | |
| type Rep (ModeState TOTP) Source # | |
A list of secrets and their states, of various modes.
Constructors
| Vault | |
Fields
| |
Instances
| Generic Vault Source # | |
| ToJSON Vault Source # | |
Defined in Authenticator.Vault | |
| Binary Vault Source # | |
| type Rep Vault Source # | |
Defined in Authenticator.Vault type Rep Vault = D1 (MetaData "Vault" "Authenticator.Vault" "otp-authenticator-0.1.1.0-inplace" True) (C1 (MetaCons "Vault" PrefixI True) (S1 (MetaSel (Just "vaultList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SomeSecretState]))) | |
_Vault :: Functor f => ([SomeSecretState] -> f [SomeSecretState]) -> Vault -> f Vault Source #
A lens into the list of SomeSecretStates in a Vault. Should be an
Iso but we don't want a lens dependency now, do we.
hotp :: Secret HOTP -> ModeState HOTP -> (Text, ModeState HOTP) Source #
Generate an HTOP (counter-based) code, returning a modified state.
totp :: Secret TOTP -> IO Text Source #
Generate a TOTP (time-based) code in IO for the current time.
totp_ :: Secret TOTP -> POSIXTime -> Text Source #
(Purely) generate a TOTP (time-based) code, for a given time.
someSecret :: Functor f => (forall m. SMode m -> Secret m -> ModeState m -> f (ModeState m)) -> SomeSecretState -> f SomeSecretState Source #
Some sort of RankN lens and traversal over a SomeSecret. Allows you
to traverse (effectfully map) over the ModeState in
a SomeSecretState, with access to the Secret as well.
With this you can implement getters and setters. It's also used by the
library to update the ModeState in IO.
vaultSecrets :: Applicative f => (forall m. SMode m -> Secret m -> ModeState m -> f (ModeState m)) -> Vault -> f Vault Source #
describeSecret :: Secret m -> Text Source #
Print out the metadata (account name and issuer) of a Secret.
secretURI :: Parser SomeSecretState Source #
A parser for a otpauth URI.
parseSecretURI :: String -> Either String SomeSecretState Source #
Parse a valid otpauth URI and initialize its state.
See https://github.com/google/google-authenticator/wiki/Key-Uri-Format