otp-authenticator-0.1.1.0: OTP Authenticator (a la google) command line client

Copyright(c) Justin Le 2017
LicenseMIT
Maintainerjustin@jle.im
Stabilityunstable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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

Documentation

data Mode Source #

OTP generation mode

Constructors

HOTP

Counter-based

TOTP

Time-based

Instances
Show Mode Source # 
Instance details

Defined in Authenticator.Vault

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode Source # 
Instance details

Defined in Authenticator.Vault

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

ToJSON SomeSecretState Source # 
Instance details

Defined in Authenticator.Vault

ToJSON Mode Source # 
Instance details

Defined in Authenticator.Vault

Binary SomeSecretState Source # 
Instance details

Defined in Authenticator.Vault

Binary Mode Source # 
Instance details

Defined in Authenticator.Vault

Methods

put :: Mode -> Put #

get :: Get Mode #

putList :: [Mode] -> Put #

GShow SMode Source # 
Instance details

Defined in Authenticator.Vault

Methods

gshowsPrec :: Int -> SMode a -> ShowS #

type Rep Mode Source # 
Instance details

Defined in Authenticator.Vault

type Rep Mode = D1 (MetaData "Mode" "Authenticator.Vault" "otp-authenticator-0.1.1.0-inplace" False) (C1 (MetaCons "HOTP" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "TOTP" PrefixI False) (U1 :: Type -> Type))

data SMode :: Mode -> Type where Source #

Singleton for Mode

Constructors

SHOTP :: SMode HOTP 
STOTP :: SMode TOTP 

withSMode :: Mode -> (forall m. SMode m -> r) -> r Source #

Reify a Mode to its singleton

fromSMode :: SMode m -> Mode Source #

Reflect a SMode to its value.

data HashAlgo Source #

Which OTP-approved hash algorithm to use?

Constructors

HASHA1 
HASHA256 
HASHA512 
Instances
Show HashAlgo Source # 
Instance details

Defined in Authenticator.Vault

Generic HashAlgo Source # 
Instance details

Defined in Authenticator.Vault

Associated Types

type Rep HashAlgo :: Type -> Type #

Methods

from :: HashAlgo -> Rep HashAlgo x #

to :: Rep HashAlgo x -> HashAlgo #

ToJSON HashAlgo Source # 
Instance details

Defined in Authenticator.Vault

Binary HashAlgo Source # 
Instance details

Defined in Authenticator.Vault

Methods

put :: HashAlgo -> Put #

get :: Get HashAlgo #

putList :: [HashAlgo] -> Put #

type Rep HashAlgo Source # 
Instance details

Defined in Authenticator.Vault

type Rep HashAlgo = D1 (MetaData "HashAlgo" "Authenticator.Vault" "otp-authenticator-0.1.1.0-inplace" False) (C1 (MetaCons "HASHA1" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "HASHA256" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "HASHA512" PrefixI False) (U1 :: Type -> Type)))

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 

Fields

Instances
ToJSON SomeSecretState Source # 
Instance details

Defined in Authenticator.Vault

Binary SomeSecretState Source # 
Instance details

Defined in Authenticator.Vault

Show (Secret a) Source # 
Instance details

Defined in Authenticator.Vault

Methods

showsPrec :: Int -> Secret a -> ShowS #

show :: Secret a -> String #

showList :: [Secret a] -> ShowS #

Generic (Secret a) Source # 
Instance details

Defined in Authenticator.Vault

Associated Types

type Rep (Secret a) :: Type -> Type #

Methods

from :: Secret a -> Rep (Secret a) x #

to :: Rep (Secret a) x -> Secret a #

ToJSON (Secret m) Source # 
Instance details

Defined in Authenticator.Vault

Binary (Secret m) Source # 
Instance details

Defined in Authenticator.Vault

Methods

put :: Secret m -> Put #

get :: Get (Secret m) #

putList :: [Secret m] -> Put #

type Rep (Secret a) Source # 
Instance details

Defined in Authenticator.Vault

newtype OTPDigits Source #

Newtype wrapper to provide Eq, Ord, Binary, and ToJSON instances. You can convert to and from this and the Int representation using OTPDigitsInt

Constructors

OTPDigits 

Fields

data family ModeState :: Mode -> Type Source #

A data family consisting of the state required by each mode.

Instances
ToJSON SomeSecretState Source # 
Instance details

Defined in Authenticator.Vault

Binary SomeSecretState Source # 
Instance details

Defined in Authenticator.Vault

Show (ModeState HOTP) Source # 
Instance details

Defined in Authenticator.Vault

Show (ModeState TOTP) Source # 
Instance details

Defined in Authenticator.Vault

Generic (ModeState HOTP) Source # 
Instance details

Defined in Authenticator.Vault

Associated Types

type Rep (ModeState HOTP) :: Type -> Type #

Generic (ModeState TOTP) Source # 
Instance details

Defined in Authenticator.Vault

Associated Types

type Rep (ModeState TOTP) :: Type -> Type #

ToJSON (ModeState HOTP) Source # 
Instance details

Defined in Authenticator.Vault

ToJSON (ModeState TOTP) Source # 
Instance details

Defined in Authenticator.Vault

Binary (ModeState HOTP) Source # 
Instance details

Defined in Authenticator.Vault

Binary (ModeState TOTP) Source # 
Instance details

Defined in Authenticator.Vault

data ModeState HOTP Source #

For HOTP (counter-based) mode, the state is the current counter.

Instance details

Defined in Authenticator.Vault

data ModeState TOTP Source #

For TOTP (time-based) mode, there is no state.

Instance details

Defined in Authenticator.Vault

type Rep (ModeState HOTP) Source # 
Instance details

Defined in Authenticator.Vault

type Rep (ModeState HOTP) = D1 (MetaData "ModeState" "Authenticator.Vault" "otp-authenticator-0.1.1.0-inplace" False) (C1 (MetaCons "HOTPState" PrefixI True) (S1 (MetaSel (Just "hotpCounter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))
type Rep (ModeState TOTP) Source # 
Instance details

Defined in Authenticator.Vault

type Rep (ModeState TOTP) = D1 (MetaData "ModeState" "Authenticator.Vault" "otp-authenticator-0.1.1.0-inplace" False) (C1 (MetaCons "TOTPState" PrefixI False) (U1 :: Type -> Type))

type SomeSecretState = DSum SMode (Secret :*: ModeState) Source #

A Secret coupled with its ModeState, existentially quantified over its Mode.

newtype Vault Source #

A list of secrets and their states, of various modes.

Constructors

Vault 
Instances
Generic Vault Source # 
Instance details

Defined in Authenticator.Vault

Associated Types

type Rep Vault :: Type -> Type #

Methods

from :: Vault -> Rep Vault x #

to :: Rep Vault x -> Vault #

ToJSON Vault Source # 
Instance details

Defined in Authenticator.Vault

Binary Vault Source # 
Instance details

Defined in Authenticator.Vault

Methods

put :: Vault -> Put #

get :: Get Vault #

putList :: [Vault] -> Put #

type Rep Vault Source # 
Instance details

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.

otp :: SMode m -> Secret m -> ModeState m -> IO (Text, ModeState m) Source #

Abstract over both hotp and totp.

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 #

A RankN traversal over all of the Secrets and ModeStates in a Vault.

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.