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

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

Authenticator.Vault

Contents

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 # 

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode Source # 

Associated Types

type Rep Mode :: * -> * #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

ToJSON Mode Source # 
ToJSON SomeSecretState Source # 
Binary Mode Source # 

Methods

put :: Mode -> Put #

get :: Get Mode #

putList :: [Mode] -> Put #

Binary SomeSecretState Source # 
SingKind Mode Source # 

Associated Types

type DemoteRep Mode :: * #

SingI Mode HOTP Source # 

Methods

sing :: Sing HOTP a #

SingI Mode TOTP Source # 

Methods

sing :: Sing TOTP a #

type Rep Mode Source # 
type Rep Mode = D1 (MetaData "Mode" "Authenticator.Vault" "otp-authenticator-0.1.0.1-6m9CjvDGB2e3igWXZqP3sU" False) ((:+:) (C1 (MetaCons "HOTP" PrefixI False) U1) (C1 (MetaCons "TOTP" PrefixI False) U1))
data Sing Mode Source # 
data Sing Mode where
type DemoteRep Mode Source # 

data family Sing k (a :: k) :: * #

The singleton kind-indexed data family.

Instances

ToJSON SomeSecretState # 
Binary SomeSecretState # 
data Sing Bool 
data Sing Bool where
data Sing Ordering 
data Sing Nat 
data Sing Nat where
data Sing Symbol 
data Sing Symbol where
data Sing () 
data Sing () where
data Sing Mode # 
data Sing Mode where
data Sing [a0] 
data Sing [a0] where
data Sing (Maybe a0) 
data Sing (Maybe a0) where
data Sing (NonEmpty a0) 
data Sing (NonEmpty a0) where
data Sing (Either a0 b0) 
data Sing (Either a0 b0) where
data Sing (a0, b0) 
data Sing (a0, b0) where
data Sing ((~>) k1 k2) 
data Sing ((~>) k1 k2) = SLambda {}
data Sing (a0, b0, c0) 
data Sing (a0, b0, c0) where
data Sing (a0, b0, c0, d0) 
data Sing (a0, b0, c0, d0) where
data Sing (a0, b0, c0, d0, e0) 
data Sing (a0, b0, c0, d0, e0) where
data Sing (a0, b0, c0, d0, e0, f0) 
data Sing (a0, b0, c0, d0, e0, f0) where
data Sing (a0, b0, c0, d0, e0, f0, g0) 
data Sing (a0, b0, c0, d0, e0, f0, g0) where

type SMode = (Sing :: Mode -> Type) Source #

data HashAlgo Source #

Which OTP-approved hash algorithm to use?

Constructors

HASHA1 
HASHA256 
HASHA512 

Instances

Show HashAlgo Source # 
Generic HashAlgo Source # 

Associated Types

type Rep HashAlgo :: * -> * #

Methods

from :: HashAlgo -> Rep HashAlgo x #

to :: Rep HashAlgo x -> HashAlgo #

ToJSON HashAlgo Source # 
Binary HashAlgo Source # 

Methods

put :: HashAlgo -> Put #

get :: Get HashAlgo #

putList :: [HashAlgo] -> Put #

type Rep HashAlgo Source # 
type Rep HashAlgo = D1 (MetaData "HashAlgo" "Authenticator.Vault" "otp-authenticator-0.1.0.1-6m9CjvDGB2e3igWXZqP3sU" False) ((:+:) (C1 (MetaCons "HASHA1" PrefixI False) U1) ((:+:) (C1 (MetaCons "HASHA256" PrefixI False) U1) (C1 (MetaCons "HASHA512" PrefixI False) U1)))

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 :: {..} -> Secret m 

Instances

ToJSON SomeSecretState Source # 
Binary SomeSecretState Source # 
Show (Secret a) Source # 

Methods

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

show :: Secret a -> String #

showList :: [Secret a] -> ShowS #

Generic (Secret a) Source # 

Associated Types

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

Methods

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

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

ToJSON (Secret m) Source # 
Binary (Secret m) Source # 

Methods

put :: Secret m -> Put #

get :: Get (Secret m) #

putList :: [Secret m] -> Put #

type Rep (Secret a) Source # 

data family ModeState :: Mode -> Type Source #

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

Instances

ToJSON SomeSecretState Source # 
Binary SomeSecretState Source # 
Show (ModeState HOTP) Source # 
Show (ModeState TOTP) Source # 
Generic (ModeState HOTP) Source # 

Associated Types

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

Generic (ModeState TOTP) Source # 

Associated Types

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

ToJSON (ModeState HOTP) Source # 
ToJSON (ModeState TOTP) Source # 
Binary (ModeState HOTP) Source # 
Binary (ModeState TOTP) Source # 
data ModeState HOTP Source #

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

data ModeState TOTP Source #

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

type Rep (ModeState HOTP) Source # 
type Rep (ModeState HOTP) = D1 (MetaData "ModeState" "Authenticator.Vault" "otp-authenticator-0.1.0.1-6m9CjvDGB2e3igWXZqP3sU" False) (C1 (MetaCons "HOTPState" PrefixI True) (S1 (MetaSel (Just Symbol "hotpCounter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64)))
type Rep (ModeState TOTP) Source # 
type Rep (ModeState TOTP) = D1 (MetaData "ModeState" "Authenticator.Vault" "otp-authenticator-0.1.0.1-6m9CjvDGB2e3igWXZqP3sU" False) (C1 (MetaCons "TOTPState" PrefixI False) U1)

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

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

data Vault Source #

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

Constructors

Vault 

Instances

Generic Vault Source # 

Associated Types

type Rep Vault :: * -> * #

Methods

from :: Vault -> Rep Vault x #

to :: Rep Vault x -> Vault #

ToJSON Vault Source # 
Binary Vault Source # 

Methods

put :: Vault -> Put #

get :: Get Vault #

putList :: [Vault] -> Put #

type Rep Vault Source # 
type Rep Vault = D1 (MetaData "Vault" "Authenticator.Vault" "otp-authenticator-0.1.0.1-6m9CjvDGB2e3igWXZqP3sU" False) (C1 (MetaCons "Vault" PrefixI True) (S1 (MetaSel (Just Symbol "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 -> UTCTime -> Text Source #

(Purely) generate a TOTP (time-based) code, for a given time.

otp :: forall m. SingI m => Secret m -> ModeState m -> IO (Text, ModeState m) Source #

Abstract over both hotp and totp.

someSecret :: Functor f => (forall m. SingI 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. SingI 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.

Orphan instances

(Functor f, Functor g) => Functor ((:.:) * * f g) Source # 

Methods

fmap :: (a -> b) -> (* :.: *) f g a -> (* :.: *) f g b #

(<$) :: a -> (* :.: *) f g b -> (* :.: *) f g a #