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

Safe HaskellNone
LanguageHaskell2010

Authenticator.Vault

Contents

Synopsis

Documentation

data Mode Source #

Constructors

HOTP 
TOTP 

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 # 
Binary Mode Source # 

Methods

put :: Mode -> Put #

get :: Get Mode #

putList :: [Mode] -> Put #

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 #

ToJSON (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) Source # 
Binary (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) Source # 
type Rep Mode Source # 
type Rep Mode = D1 (MetaData "Mode" "Authenticator.Vault" "otp-authenticator-0.1.0.0-BSCTJlTxmg85yc13Q26PHJ" 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 (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) # 
Binary (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) # 
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 #

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.0-BSCTJlTxmg85yc13Q26PHJ" False) ((:+:) (C1 (MetaCons "HASHA1" PrefixI False) U1) ((:+:) (C1 (MetaCons "HASHA256" PrefixI False) U1) (C1 (MetaCons "HASHA512" PrefixI False) U1)))

data Secret :: Mode -> Type where Source #

Constructors

Sec :: {..} -> Secret m 

Instances

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 #

ToJSON (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) Source # 
Binary (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) Source # 
type Rep (Secret a) Source # 

data family ModeState :: Mode -> Type Source #

Instances

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 # 
ToJSON (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) Source # 
Binary (DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)) Source # 
data ModeState HOTP Source # 
data ModeState TOTP Source # 
type Rep (ModeState HOTP) Source # 
type Rep (ModeState HOTP) = D1 (MetaData "ModeState" "Authenticator.Vault" "otp-authenticator-0.1.0.0-BSCTJlTxmg85yc13Q26PHJ" 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.0-BSCTJlTxmg85yc13Q26PHJ" False) (C1 (MetaCons "TOTPState" PrefixI False) U1)

data Vault Source #

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.0-BSCTJlTxmg85yc13Q26PHJ" False) (C1 (MetaCons "Vault" PrefixI True) (S1 (MetaSel (Just Symbol "vaultList") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [DSum Mode (Sing Mode) ((:&:) Mode Secret ModeState)])))

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

someSecret :: Functor f => (forall m. SingI m => Secret m -> ModeState m -> f (ModeState m)) -> DSum Sing (Secret :&: ModeState) -> f (DSum Sing (Secret :&: ModeState)) Source #

vaultSecrets :: Applicative f => (forall m. SingI m => Secret m -> ModeState m -> f (ModeState m)) -> Vault -> f Vault Source #

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 #