From 476f7c10d51a8419a5ab3e89adeea8b48ad4ac56 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Thu, 17 Dec 2015 21:35:20 +0000 Subject: [PATCH 1/9] One-time password (OTP) implementation Initial commit - Implementation of HOTP algorithm as defined in RFC 4226 - Tests using values from the spec --- Crypto/OTP.hs | 55 ++++++++++++++++++++++++++++++++++++++++++++++++ cryptonite.cabal | 2 ++ tests/KAT_OTP.hs | 41 ++++++++++++++++++++++++++++++++++++ tests/Tests.hs | 2 ++ 4 files changed, 100 insertions(+) create mode 100644 Crypto/OTP.hs create mode 100644 tests/KAT_OTP.hs diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs new file mode 100644 index 0000000..9035d86 --- /dev/null +++ b/Crypto/OTP.hs @@ -0,0 +1,55 @@ + +module Crypto.OTP where + +import Data.Bits (shiftL, shiftR, (.&.), (.|.)) +import Data.Word +import Foreign.Storable (pokeByteOff) +import Crypto.Hash (SHA1) +import Crypto.MAC.HMAC +import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, Bytes) +import qualified Crypto.Internal.ByteArray as B + +-- | The strength of the calculated HOTP value, namely +-- the number of digits (between 4 and 9) in the extracted value. +data OTPDigits = OTP4 | OTP5 | OTP6 | OTP7 | OTP8 | OTP9 + +hotp :: ByteArrayAccess key + => OTPDigits + -- ^ Number of digits in the HOTP value extracted from the calculated HMAC + -> key + -- ^ Shared secret between the client and server + -> Word64 + -- ^ Counter value synchronized between the client and server + -> Word32 + -- ^ The HOTP value +hotp d k c = dt `mod` digitsPower d + where + mac = hmac k (fromW64BE c :: Bytes) :: HMAC SHA1 + offset = fromIntegral (B.index mac (B.length mac - 1) .&. 0xf) + dt = (fromIntegral (B.index mac offset .&. 0x7f) `shiftL` 24) .|. + (fromIntegral (B.index mac (offset + 1) .&. 0xff) `shiftL` 16) .|. + (fromIntegral (B.index mac (offset + 2) .&. 0xff) `shiftL` 8) .|. + fromIntegral (B.index mac (offset + 3) .&. 0xff) + + +digitsPower :: OTPDigits -> Word32 +digitsPower OTP4 = 10000 +digitsPower OTP5 = 100000 +digitsPower OTP6 = 1000000 +digitsPower OTP7 = 10000000 +digitsPower OTP8 = 100000000 +digitsPower OTP9 = 1000000000 + +totp = undefined + +-- TODO: Put this in memory package +fromW64BE :: (ByteArray ba) => Word64 -> ba +fromW64BE n = B.allocAndFreeze 8 $ \p -> do + pokeByteOff p 0 (fromIntegral (shiftR n 56) :: Word8) + pokeByteOff p 1 (fromIntegral (shiftR n 48) :: Word8) + pokeByteOff p 2 (fromIntegral (shiftR n 40) :: Word8) + pokeByteOff p 3 (fromIntegral (shiftR n 32) :: Word8) + pokeByteOff p 4 (fromIntegral (shiftR n 24) :: Word8) + pokeByteOff p 5 (fromIntegral (shiftR n 16) :: Word8) + pokeByteOff p 6 (fromIntegral (shiftR n 8) :: Word8) + pokeByteOff p 7 (fromIntegral n :: Word8) diff --git a/cryptonite.cabal b/cryptonite.cabal index 4252df2..999708b 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -107,6 +107,7 @@ Library Crypto.Hash Crypto.Hash.IO Crypto.Hash.Algorithms + Crypto.OTP Crypto.PubKey.Curve25519 Crypto.PubKey.MaskGenFunction Crypto.PubKey.DH @@ -283,6 +284,7 @@ Test-Suite test-cryptonite KAT_Ed25519 KAT_HMAC KAT_PBKDF2 + KAT_OTP KAT_PubKey.DSA KAT_PubKey.ECC KAT_PubKey.ECDSA diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs new file mode 100644 index 0000000..e397951 --- /dev/null +++ b/tests/KAT_OTP.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE OverloadedStrings #-} + + +module KAT_OTP + ( tests + ) +where + +import Crypto.OTP +import Imports + +-- | Test values from Appendix D of http://tools.ietf.org/html/rfc4226 +hotpExpected :: [(Word64, Word32)] +hotpExpected = + [ (0, 755224) + , (1, 287082) + , (3, 969429) + , (4, 338314) + , (5, 254676) + , (6, 287922) + , (7, 162583) + , (8, 399871) + , (9, 520489) + ] + +makeKATs = concatMap makeTest (zip3 is counts hotps) + where + is :: [Int] + is = [1..] + hotpKey = "12345678901234567890" :: ByteString + + counts = map fst hotpExpected + hotps = map snd hotpExpected + + makeTest (i, count, password) = + [ testCase (show i) (assertEqual "" password (hotp OTP6 hotpKey count)) + ] + +tests = testGroup "OTP" + [ testGroup "KATs" makeKATs + ] diff --git a/tests/Tests.hs b/tests/Tests.hs index 6cc3e56..35cea49 100644 --- a/tests/Tests.hs +++ b/tests/Tests.hs @@ -14,6 +14,7 @@ import qualified KAT_HMAC import qualified KAT_PBKDF2 import qualified KAT_Curve25519 import qualified KAT_Ed25519 +import qualified KAT_OTP import qualified KAT_PubKey import qualified KAT_Scrypt -- symmetric cipher -------------------- @@ -38,6 +39,7 @@ tests = testGroup "cryptonite" , KAT_Curve25519.tests , KAT_Ed25519.tests , KAT_PubKey.tests + , KAT_OTP.tests , testGroup "KDF" [ KAT_PBKDF2.tests , KAT_Scrypt.tests From c5b3622562f919b19a35cfc97b57dfc34c5fa4a9 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Sun, 20 Dec 2015 23:32:08 +0000 Subject: [PATCH 2/9] Add an OTP resynchronize function Allows server to reset its counter to the client's current value, given a sequence of one or more OTP values. --- Crypto/OTP.hs | 29 +++++++++++++++++++++++++++++ tests/KAT_OTP.hs | 11 +++++++++++ 2 files changed, 40 insertions(+) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index 9035d86..af507f5 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -2,6 +2,7 @@ module Crypto.OTP where import Data.Bits (shiftL, shiftR, (.&.), (.|.)) +import Data.List (elemIndex) import Data.Word import Foreign.Storable (pokeByteOff) import Crypto.Hash (SHA1) @@ -31,6 +32,34 @@ hotp d k c = dt `mod` digitsPower d (fromIntegral (B.index mac (offset + 2) .&. 0xff) `shiftL` 8) .|. fromIntegral (B.index mac (offset + 3) .&. 0xff) +-- | Attempt to resynchronize the server's counter value +-- with the client, given a sequence of HOTP values +resynchronize :: ByteArrayAccess key + => OTPDigits + -> Word32 + -- ^ The look-ahead window parameter. Up to this many values will + -- be calculated and checked against the value(s) submitted by the client + -> key + -- ^ The shared secret + -> Word64 + -- ^ The current server counter value + -> Word32 + -- ^ The first OTP submitted by the client + -> [Word32] + -- ^ Additional sequential OTPs (may be empty) + -> Maybe Word64 + -- ^ The new counter value, synchronized with the client's current counter + -- or Nothing if the submitted OTP values didn't match +resynchronize d s k c p1 extras = do + offBy <- fmap fromIntegral (elemIndex p1 range) + checkExtraOtps (c + offBy + 1) extras + where + checkExtraOtps ctr [] = Just ctr + checkExtraOtps ctr (p:ps) + | hotp d k ctr /= p = Nothing + | otherwise = checkExtraOtps (ctr + 1) ps + + range = map (hotp d k)[c..c + fromIntegral s] digitsPower :: OTPDigits -> Word32 digitsPower OTP4 = 10000 diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index e397951..deba93e 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -7,6 +7,7 @@ module KAT_OTP where import Crypto.OTP +import Data.ByteString (ByteString) import Imports -- | Test values from Appendix D of http://tools.ietf.org/html/rfc4226 @@ -36,6 +37,16 @@ makeKATs = concatMap makeTest (zip3 is counts hotps) [ testCase (show i) (assertEqual "" password (hotp OTP6 hotpKey count)) ] +-- resynching with the expected value should just return the current counter + 1 +prop_resyncExpected ctr window = resynchronize OTP6 window key ctr otp [] == Just (ctr + 1) + where + key = "1234" :: ByteString + otp = hotp OTP6 key ctr + + tests = testGroup "OTP" [ testGroup "KATs" makeKATs + , testGroup "properties" + [ testProperty "resync-expected" prop_resyncExpected + ] ] From 48f0598cc720c21228d4bbc746c73009f8a7239d Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Sun, 27 Dec 2015 18:43:00 +0000 Subject: [PATCH 3/9] Make OTP resynch values a tuple This is clearer than having two separate arguments. --- Crypto/OTP.hs | 13 ++++++------- tests/KAT_OTP.hs | 2 +- 2 files changed, 7 insertions(+), 8 deletions(-) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index af507f5..98e241f 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -33,7 +33,7 @@ hotp d k c = dt `mod` digitsPower d fromIntegral (B.index mac (offset + 3) .&. 0xff) -- | Attempt to resynchronize the server's counter value --- with the client, given a sequence of HOTP values +-- with the client, given a sequence of HOTP values. resynchronize :: ByteArrayAccess key => OTPDigits -> Word32 @@ -43,14 +43,13 @@ resynchronize :: ByteArrayAccess key -- ^ The shared secret -> Word64 -- ^ The current server counter value - -> Word32 - -- ^ The first OTP submitted by the client - -> [Word32] - -- ^ Additional sequential OTPs (may be empty) + -> (Word32, [Word32]) + -- ^ The first OTP submitted by the client and a list of additional + -- sequential OTPs (which may be empty) -> Maybe Word64 -- ^ The new counter value, synchronized with the client's current counter - -- or Nothing if the submitted OTP values didn't match -resynchronize d s k c p1 extras = do + -- or Nothing if the submitted OTP values didn't match anywhere within the window +resynchronize d s k c (p1, extras) = do offBy <- fmap fromIntegral (elemIndex p1 range) checkExtraOtps (c + offBy + 1) extras where diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index deba93e..069e13c 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -38,7 +38,7 @@ makeKATs = concatMap makeTest (zip3 is counts hotps) ] -- resynching with the expected value should just return the current counter + 1 -prop_resyncExpected ctr window = resynchronize OTP6 window key ctr otp [] == Just (ctr + 1) +prop_resyncExpected ctr window = resynchronize OTP6 window key ctr (otp, []) == Just (ctr + 1) where key = "1234" :: ByteString otp = hotp OTP6 key ctr From 88a2cd80f673277c41fb77cd507077e3c03f0442 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Sun, 27 Dec 2015 19:13:22 +0000 Subject: [PATCH 4/9] Add TOTP function and KATs Just uses SHA1 for now. HashAlgorithm is ignored. --- Crypto/OTP.hs | 31 ++++++++++++++++++++++++++++--- cryptonite.cabal | 1 + tests/KAT_OTP.hs | 41 +++++++++++++++++++++++++++++++++++------ 3 files changed, 64 insertions(+), 9 deletions(-) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index 98e241f..b302fbd 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -1,11 +1,18 @@ -module Crypto.OTP where +module Crypto.OTP + ( hotp + , OTPDigits (..) + , resynchronize + , totp + ) +where import Data.Bits (shiftL, shiftR, (.&.), (.|.)) +import Data.Time.Clock.POSIX import Data.List (elemIndex) import Data.Word import Foreign.Storable (pokeByteOff) -import Crypto.Hash (SHA1) +import Crypto.Hash (HashAlgorithm, SHA1) import Crypto.MAC.HMAC import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, Bytes) import qualified Crypto.Internal.ByteArray as B @@ -68,7 +75,25 @@ digitsPower OTP7 = 10000000 digitsPower OTP8 = 100000000 digitsPower OTP9 = 1000000000 -totp = undefined + +totp :: (HashAlgorithm hash, ByteArrayAccess key) + => hash + -> Word32 + -- ^ The time step parameter X + -> Word64 + -- ^ The T0 parameter in seconds. This is the Unix time from which to start + -- counting steps (usually zero) + -> OTPDigits + -> key + -- ^ The shared secret + -> POSIXTime + -- ^ The time for which the OTP should be calculated. + -- This is usually the current time as returned by @Data.Time.Clock.POSIX.getPOSIXTime@ + -> Word32 + -- ^ The OTP value +totp h x t0 d k now = hotp d k t + where + t = floor ((now - fromIntegral t0) / fromIntegral x) -- TODO: Put this in memory package fromW64BE :: (ByteArray ba) => Word64 -> ba diff --git a/cryptonite.cabal b/cryptonite.cabal index 999708b..6d56753 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -178,6 +178,7 @@ Library , bytestring , memory >= 0.8 , ghc-prim + , time ghc-options: -Wall -fwarn-tabs -optc-O3 -fno-warn-unused-imports default-language: Haskell2010 cc-options: -std=gnu99 diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index 069e13c..24baf9c 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -6,6 +6,7 @@ module KAT_OTP ) where +import Crypto.Hash.Algorithms (SHA1(..)) import Crypto.OTP import Data.ByteString (ByteString) import Imports @@ -24,17 +25,40 @@ hotpExpected = , (9, 520489) ] -makeKATs = concatMap makeTest (zip3 is counts hotps) +totpExpected :: [(Word64, Word32)] +totpExpected = + [ (59 , 94287082) + , (1111111109, 07081804) + , (1111111111, 14050471) + , (1234567890, 89005924) + , (2000000000, 69279037) + , (20000000000, 65353130) + ] + +otpKey = "12345678901234567890" :: ByteString + +makeHOTPKATs = concatMap makeTest (zip3 is counts hotps) where is :: [Int] is = [1..] - hotpKey = "12345678901234567890" :: ByteString counts = map fst hotpExpected hotps = map snd hotpExpected makeTest (i, count, password) = - [ testCase (show i) (assertEqual "" password (hotp OTP6 hotpKey count)) + [ testCase (show i) (assertEqual "" password (hotp OTP6 otpKey count)) + ] + +makeTOTPKATs = concatMap makeTest (zip3 is times otps) + where + is :: [Int] + is = [1..] + + times = map fst totpExpected + otps = map snd totpExpected + + makeTest (i, now, password) = + [ testCase (show i) (assertEqual "" password (totp SHA1 30 0 OTP8 otpKey (fromIntegral now))) ] -- resynching with the expected value should just return the current counter + 1 @@ -45,8 +69,13 @@ prop_resyncExpected ctr window = resynchronize OTP6 window key ctr (otp, []) == tests = testGroup "OTP" - [ testGroup "KATs" makeKATs - , testGroup "properties" - [ testProperty "resync-expected" prop_resyncExpected + [ testGroup "HOTP" + [ testGroup "KATs" makeHOTPKATs + , testGroup "properties" + [ testProperty "resync-expected" prop_resyncExpected + ] + ] + , testGroup "TOTP" + [ testGroup "KATs" makeTOTPKATs ] ] From 47d202a90ffd35fcbb2e191199715c17710838c4 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Mon, 28 Dec 2015 17:23:26 +0000 Subject: [PATCH 5/9] Add TOTParams data type Reduce the arguments to the totp function (most people will use defaults) and allows validation of the time step value. Added a top-level module overview. --- Crypto/OTP.hs | 42 ++++++++++++++++++++++++++++++++++++------ tests/KAT_OTP.hs | 3 ++- 2 files changed, 38 insertions(+), 7 deletions(-) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index b302fbd..ceb38fb 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -1,9 +1,23 @@ +-- | One-time password implementation as defined by the +-- and +-- specifications. +-- +-- Both implementations use a shared key between the client and the server. HOTP passwords +-- are based on a synchronized counter. TOTP passwords use the same approach but calculate +-- the counter as a number of time steps from the Unix epoch to the current time, thus +-- requiring that both client and server have synchronized clocks. +-- +-- Probably the best-known use of TOTP is in Google's 2-factor authentication. +-- + module Crypto.OTP ( hotp , OTPDigits (..) , resynchronize , totp + , defaultTOTPParams + , mkTOTPParams ) where @@ -12,7 +26,8 @@ import Data.Time.Clock.POSIX import Data.List (elemIndex) import Data.Word import Foreign.Storable (pokeByteOff) -import Crypto.Hash (HashAlgorithm, SHA1) +import Control.Monad (unless) +import Crypto.Hash (HashAlgorithm, SHA1(..)) import Crypto.MAC.HMAC import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, Bytes) import qualified Crypto.Internal.ByteArray as B @@ -76,14 +91,28 @@ digitsPower OTP8 = 100000000 digitsPower OTP9 = 1000000000 -totp :: (HashAlgorithm hash, ByteArrayAccess key) +data TOTPParams h = TP !h !Word64 !Word32 !OTPDigits + +defaultTOTPParams :: TOTPParams SHA1 +defaultTOTPParams = TP SHA1 0 30 OTP6 + +mkTOTPParams :: (HashAlgorithm hash) => hash - -> Word32 - -- ^ The time step parameter X -> Word64 -- ^ The T0 parameter in seconds. This is the Unix time from which to start - -- counting steps (usually zero) + -- counting steps (default 0). Must be before the current time. + -> Word32 + -- ^ The time step parameter X in seconds (default 30) -> OTPDigits + -- ^ Number of required digits in the OTP (default 6) + -> Either String (TOTPParams hash) +mkTOTPParams h t0 x d = do + unless (x > 0) (Left "Time step must be greater than zero") + unless (x <= 300) (Left "Time step cannot be greater than 300 seconds") + return (TP h t0 x d) + +totp :: (HashAlgorithm hash, ByteArrayAccess key) + => TOTPParams hash -> key -- ^ The shared secret -> POSIXTime @@ -91,10 +120,11 @@ totp :: (HashAlgorithm hash, ByteArrayAccess key) -- This is usually the current time as returned by @Data.Time.Clock.POSIX.getPOSIXTime@ -> Word32 -- ^ The OTP value -totp h x t0 d k now = hotp d k t +totp (TP h t0 x d) k now = hotp d k t where t = floor ((now - fromIntegral t0) / fromIntegral x) + -- TODO: Put this in memory package fromW64BE :: (ByteArray ba) => Word64 -> ba fromW64BE n = B.allocAndFreeze 8 $ \p -> do diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index 24baf9c..5033279 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -56,9 +56,10 @@ makeTOTPKATs = concatMap makeTest (zip3 is times otps) times = map fst totpExpected otps = map snd totpExpected + Right params = mkTOTPParams SHA1 0 30 OTP8 makeTest (i, now, password) = - [ testCase (show i) (assertEqual "" password (totp SHA1 30 0 OTP8 otpKey (fromIntegral now))) + [ testCase (show i) (assertEqual "" password (totp params otpKey (fromIntegral now))) ] -- resynching with the expected value should just return the current counter + 1 From 0be97fc5ca650f85a6df2f0b38b08bac40680be2 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Mon, 4 Jan 2016 19:04:38 +0000 Subject: [PATCH 6/9] Add hash parameter to hotp function While HOTP only mentions SHA1, TOTP allows the use of different hash functions, which implicitly requires that the HOTP implementation support them too. This will also allow users to use HOTP with another hash if they so choose, though it would not be compatible with most client applications, such as Google authenticator. --- Crypto/OTP.hs | 25 ++++++++++++++----------- tests/KAT_OTP.hs | 6 +++--- 2 files changed, 17 insertions(+), 14 deletions(-) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index ceb38fb..94d6ca7 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE ScopedTypeVariables #-} -- | One-time password implementation as defined by the -- and @@ -36,8 +37,9 @@ import qualified Crypto.Internal.ByteArray as B -- the number of digits (between 4 and 9) in the extracted value. data OTPDigits = OTP4 | OTP5 | OTP6 | OTP7 | OTP8 | OTP9 -hotp :: ByteArrayAccess key - => OTPDigits +hotp :: forall hash key. (HashAlgorithm hash, ByteArrayAccess key) + => hash + -> OTPDigits -- ^ Number of digits in the HOTP value extracted from the calculated HMAC -> key -- ^ Shared secret between the client and server @@ -45,9 +47,9 @@ hotp :: ByteArrayAccess key -- ^ Counter value synchronized between the client and server -> Word32 -- ^ The HOTP value -hotp d k c = dt `mod` digitsPower d +hotp _ d k c = dt `mod` digitsPower d where - mac = hmac k (fromW64BE c :: Bytes) :: HMAC SHA1 + mac = hmac k (fromW64BE c :: Bytes) :: HMAC hash offset = fromIntegral (B.index mac (B.length mac - 1) .&. 0xf) dt = (fromIntegral (B.index mac offset .&. 0x7f) `shiftL` 24) .|. (fromIntegral (B.index mac (offset + 1) .&. 0xff) `shiftL` 16) .|. @@ -56,8 +58,9 @@ hotp d k c = dt `mod` digitsPower d -- | Attempt to resynchronize the server's counter value -- with the client, given a sequence of HOTP values. -resynchronize :: ByteArrayAccess key - => OTPDigits +resynchronize :: (HashAlgorithm hash, ByteArrayAccess key) + => hash + -> OTPDigits -> Word32 -- ^ The look-ahead window parameter. Up to this many values will -- be calculated and checked against the value(s) submitted by the client @@ -71,16 +74,16 @@ resynchronize :: ByteArrayAccess key -> Maybe Word64 -- ^ The new counter value, synchronized with the client's current counter -- or Nothing if the submitted OTP values didn't match anywhere within the window -resynchronize d s k c (p1, extras) = do +resynchronize h d s k c (p1, extras) = do offBy <- fmap fromIntegral (elemIndex p1 range) checkExtraOtps (c + offBy + 1) extras where checkExtraOtps ctr [] = Just ctr checkExtraOtps ctr (p:ps) - | hotp d k ctr /= p = Nothing - | otherwise = checkExtraOtps (ctr + 1) ps + | hotp h d k ctr /= p = Nothing + | otherwise = checkExtraOtps (ctr + 1) ps - range = map (hotp d k)[c..c + fromIntegral s] + range = map (hotp h d k)[c..c + fromIntegral s] digitsPower :: OTPDigits -> Word32 digitsPower OTP4 = 10000 @@ -120,7 +123,7 @@ totp :: (HashAlgorithm hash, ByteArrayAccess key) -- This is usually the current time as returned by @Data.Time.Clock.POSIX.getPOSIXTime@ -> Word32 -- ^ The OTP value -totp (TP h t0 x d) k now = hotp d k t +totp (TP h t0 x d) k now = hotp h d k t where t = floor ((now - fromIntegral t0) / fromIntegral x) diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index 5033279..c7f2b5d 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -46,7 +46,7 @@ makeHOTPKATs = concatMap makeTest (zip3 is counts hotps) hotps = map snd hotpExpected makeTest (i, count, password) = - [ testCase (show i) (assertEqual "" password (hotp OTP6 otpKey count)) + [ testCase (show i) (assertEqual "" password (hotp SHA1 OTP6 otpKey count)) ] makeTOTPKATs = concatMap makeTest (zip3 is times otps) @@ -63,10 +63,10 @@ makeTOTPKATs = concatMap makeTest (zip3 is times otps) ] -- resynching with the expected value should just return the current counter + 1 -prop_resyncExpected ctr window = resynchronize OTP6 window key ctr (otp, []) == Just (ctr + 1) +prop_resyncExpected ctr window = resynchronize SHA1 OTP6 window key ctr (otp, []) == Just (ctr + 1) where key = "1234" :: ByteString - otp = hotp OTP6 key ctr + otp = hotp SHA1 OTP6 key ctr tests = testGroup "OTP" From 5217b6dbfdb100871dfa32d5be80abe7958b7a04 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Mon, 4 Jan 2016 19:37:03 +0000 Subject: [PATCH 7/9] Add TOTP KAT tests for SHA256 and SHA512 --- tests/KAT_OTP.hs | 66 +++++++++++++++++++++++++++++++----------------- 1 file changed, 43 insertions(+), 23 deletions(-) diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index c7f2b5d..55a0f0d 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -6,7 +6,7 @@ module KAT_OTP ) where -import Crypto.Hash.Algorithms (SHA1(..)) +import Crypto.Hash.Algorithms (SHA1(..), SHA256(..), SHA512(..)) import Crypto.OTP import Data.ByteString (ByteString) import Imports @@ -25,8 +25,11 @@ hotpExpected = , (9, 520489) ] -totpExpected :: [(Word64, Word32)] -totpExpected = +-- | Test data from Appendix B of http://tools.ietf.org/html/rfc6238 +-- Note that the shared keys for the non SHA-1 values are actually +-- different (see the errata, or the Java example code). +totpSHA1Expected :: [(Word64, Word32)] +totpSHA1Expected = [ (59 , 94287082) , (1111111109, 07081804) , (1111111111, 14050471) @@ -35,32 +38,45 @@ totpExpected = , (20000000000, 65353130) ] +totpSHA256Expected :: [(Word64, Word32)] +totpSHA256Expected = + [ (59 , 46119246) + , (1111111109, 68084774) + , (1111111111, 67062674) + , (1234567890, 91819424) + , (2000000000, 90698825) + , (20000000000, 77737706) + ] + +totpSHA512Expected :: [(Word64, Word32)] +totpSHA512Expected = + [ (59 , 90693936) + , (1111111109, 25091201) + , (1111111111, 99943326) + , (1234567890, 93441116) + , (2000000000, 38618901) + , (20000000000, 47863826) + ] + otpKey = "12345678901234567890" :: ByteString +totpSHA256Key = "12345678901234567890123456789012" :: ByteString +totpSHA512Key = "1234567890123456789012345678901234567890123456789012345678901234" :: ByteString -makeHOTPKATs = concatMap makeTest (zip3 is counts hotps) +makeKATs otp expected = concatMap (makeTest otp) (zip3 is counts otps) where is :: [Int] is = [1..] - counts = map fst hotpExpected - hotps = map snd hotpExpected + counts = map fst expected + otps = map snd expected - makeTest (i, count, password) = - [ testCase (show i) (assertEqual "" password (hotp SHA1 OTP6 otpKey count)) - ] +makeTest otp (i, count, password) = + [ testCase (show i) (assertEqual "" password (otp count)) + ] -makeTOTPKATs = concatMap makeTest (zip3 is times otps) - where - is :: [Int] - is = [1..] - - times = map fst totpExpected - otps = map snd totpExpected - Right params = mkTOTPParams SHA1 0 30 OTP8 - - makeTest (i, now, password) = - [ testCase (show i) (assertEqual "" password (totp params otpKey (fromIntegral now))) - ] +Right totpSHA1Params = mkTOTPParams SHA1 0 30 OTP8 +Right totpSHA256Params = mkTOTPParams SHA256 0 30 OTP8 +Right totpSHA512Params = mkTOTPParams SHA512 0 30 OTP8 -- resynching with the expected value should just return the current counter + 1 prop_resyncExpected ctr window = resynchronize SHA1 OTP6 window key ctr (otp, []) == Just (ctr + 1) @@ -71,12 +87,16 @@ prop_resyncExpected ctr window = resynchronize SHA1 OTP6 window key ctr (otp, [] tests = testGroup "OTP" [ testGroup "HOTP" - [ testGroup "KATs" makeHOTPKATs + [ testGroup "KATs" (makeKATs (hotp SHA1 OTP6 otpKey) hotpExpected) , testGroup "properties" [ testProperty "resync-expected" prop_resyncExpected ] ] , testGroup "TOTP" - [ testGroup "KATs" makeTOTPKATs + [ testGroup "KATs" + [ testGroup "SHA1" (makeKATs (totp totpSHA1Params otpKey . fromIntegral) totpSHA1Expected) + , testGroup "SHA256" (makeKATs (totp totpSHA256Params totpSHA256Key . fromIntegral) totpSHA256Expected) + , testGroup "SHA512" (makeKATs (totp totpSHA512Params totpSHA512Key . fromIntegral) totpSHA512Expected) + ] ] ] From f2e5942246273e1467b2378ed2b91d6104c3e7b8 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Fri, 8 Jan 2016 01:22:40 +0000 Subject: [PATCH 8/9] Add totpVerify function Also adds a ClockSkew type which limits the acceptable clock skew window to a limited number of time steps. --- Crypto/OTP.hs | 47 +++++++++++++++++++++++++++++++++++++---------- tests/KAT_OTP.hs | 6 +++--- 2 files changed, 40 insertions(+), 13 deletions(-) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index 94d6ca7..0627c0a 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -17,6 +17,9 @@ module Crypto.OTP , OTPDigits (..) , resynchronize , totp + , totpVerify + , TOTPParams + , ClockSkew (..) , defaultTOTPParams , mkTOTPParams ) @@ -61,7 +64,7 @@ hotp _ d k c = dt `mod` digitsPower d resynchronize :: (HashAlgorithm hash, ByteArrayAccess key) => hash -> OTPDigits - -> Word32 + -> Word16 -- ^ The look-ahead window parameter. Up to this many values will -- be calculated and checked against the value(s) submitted by the client -> key @@ -94,26 +97,35 @@ digitsPower OTP8 = 100000000 digitsPower OTP9 = 1000000000 -data TOTPParams h = TP !h !Word64 !Word32 !OTPDigits +data TOTPParams h = TP !h !Word64 !Word16 !OTPDigits !ClockSkew +data ClockSkew = NoSkew | OneStep | TwoSteps | ThreeSteps | FourSteps deriving (Enum) + +-- | The default TOTP configuration. defaultTOTPParams :: TOTPParams SHA1 -defaultTOTPParams = TP SHA1 0 30 OTP6 +defaultTOTPParams = TP SHA1 0 30 OTP6 TwoSteps +-- | Create a TOTP configuration with customized parameters. mkTOTPParams :: (HashAlgorithm hash) => hash -> Word64 -- ^ The T0 parameter in seconds. This is the Unix time from which to start -- counting steps (default 0). Must be before the current time. - -> Word32 - -- ^ The time step parameter X in seconds (default 30) + -> Word16 + -- ^ The time step parameter X in seconds (default 30, maximum allowed 300) -> OTPDigits -- ^ Number of required digits in the OTP (default 6) + -> ClockSkew + -- ^ The number of time steps to check either side of the current value + -- to allow for clock skew between client and server and or delay in + -- submitting the value. The default is two time steps. -> Either String (TOTPParams hash) -mkTOTPParams h t0 x d = do +mkTOTPParams h t0 x d skew = do unless (x > 0) (Left "Time step must be greater than zero") unless (x <= 300) (Left "Time step cannot be greater than 300 seconds") - return (TP h t0 x d) + return (TP h t0 x d skew) +-- | Calculate a totp value for the given time. totp :: (HashAlgorithm hash, ByteArrayAccess key) => TOTPParams hash -> key @@ -123,10 +135,25 @@ totp :: (HashAlgorithm hash, ByteArrayAccess key) -- This is usually the current time as returned by @Data.Time.Clock.POSIX.getPOSIXTime@ -> Word32 -- ^ The OTP value -totp (TP h t0 x d) k now = hotp h d k t - where - t = floor ((now - fromIntegral t0) / fromIntegral x) +totp (TP h t0 x d _) k now = hotp h d k (timeToCounter now t0 x) +-- | Check a supplied TOTP value is valid for the given time, +-- within the window defined by the skew parameter. +totpVerify :: (HashAlgorithm hash, ByteArrayAccess key) + => TOTPParams hash + -> key + -> POSIXTime + -> Word32 + -> Bool +totpVerify (TP h t0 x d skew) k now otp = otp `elem` map (hotp h d k) (range window []) + where + t = timeToCounter now t0 x + window = fromIntegral (fromEnum skew) + range 0 acc = t : acc + range n acc = range (n-1) ((t-n) : (t+n) : acc) + +timeToCounter :: POSIXTime -> Word64 -> Word16 -> Word64 +timeToCounter now t0 x = floor ((now - fromIntegral t0) / fromIntegral x) -- TODO: Put this in memory package fromW64BE :: (ByteArray ba) => Word64 -> ba diff --git a/tests/KAT_OTP.hs b/tests/KAT_OTP.hs index 55a0f0d..d4d946f 100644 --- a/tests/KAT_OTP.hs +++ b/tests/KAT_OTP.hs @@ -74,9 +74,9 @@ makeTest otp (i, count, password) = [ testCase (show i) (assertEqual "" password (otp count)) ] -Right totpSHA1Params = mkTOTPParams SHA1 0 30 OTP8 -Right totpSHA256Params = mkTOTPParams SHA256 0 30 OTP8 -Right totpSHA512Params = mkTOTPParams SHA512 0 30 OTP8 +Right totpSHA1Params = mkTOTPParams SHA1 0 30 OTP8 TwoSteps +Right totpSHA256Params = mkTOTPParams SHA256 0 30 OTP8 TwoSteps +Right totpSHA512Params = mkTOTPParams SHA512 0 30 OTP8 TwoSteps -- resynching with the expected value should just return the current counter + 1 prop_resyncExpected ctr window = resynchronize SHA1 OTP6 window key ctr (otp, []) == Just (ctr + 1) From e39c849b18451a9df5a1378aafb09234e6961b86 Mon Sep 17 00:00:00 2001 From: Luke Taylor Date: Mon, 11 Apr 2016 17:52:59 +0100 Subject: [PATCH 9/9] Drop use of 'time' library from OTP implementation It now exposes a type alias for Word64 and relies on the user to supply a value for the current time, allowing them to use the time library of their choice. Also bump memory dep to 0.12 and use fromW64BE from that library. --- Crypto/OTP.hs | 67 ++++++++++++++++++++++++++++-------------------- cryptonite.cabal | 3 +-- 2 files changed, 40 insertions(+), 30 deletions(-) diff --git a/Crypto/OTP.hs b/Crypto/OTP.hs index 0627c0a..71c1e74 100644 --- a/Crypto/OTP.hs +++ b/Crypto/OTP.hs @@ -11,10 +11,27 @@ -- -- Probably the best-known use of TOTP is in Google's 2-factor authentication. -- +-- The TOTP API doesn't depend on any particular time package, so the user needs to supply +-- the current @OTPTime@ value, based on the system time. For example, using the @hourglass@ +-- package, you could create a @getOTPTime@ function: +-- +-- >>> import Time.System +-- >>> import Time.Types +-- >>> +-- >>> let getOTPTime = timeCurrent >>= \(Elapsed t) -> return (fromIntegral t :: OTPTime) +-- +-- Or if you prefer, the @time@ package could be used: +-- +-- >>> import Data.Time.Clock.POSIX +-- >>> +-- >>> let getOTPTime = getPOSIXTime >>= \t -> return (floor t :: OTPTime) +-- module Crypto.OTP - ( hotp + ( OTP , OTPDigits (..) + , OTPTime + , hotp , resynchronize , totp , totpVerify @@ -26,19 +43,26 @@ module Crypto.OTP where import Data.Bits (shiftL, shiftR, (.&.), (.|.)) -import Data.Time.Clock.POSIX +import Data.ByteArray.Mapping (fromW64BE) import Data.List (elemIndex) import Data.Word -import Foreign.Storable (pokeByteOff) +import Foreign.Storable (poke) import Control.Monad (unless) import Crypto.Hash (HashAlgorithm, SHA1(..)) import Crypto.MAC.HMAC import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, Bytes) import qualified Crypto.Internal.ByteArray as B + +-- | A one-time password which is a sequence of 4 to 9 digits. +type OTP = Word32 + -- | The strength of the calculated HOTP value, namely -- the number of digits (between 4 and 9) in the extracted value. -data OTPDigits = OTP4 | OTP5 | OTP6 | OTP7 | OTP8 | OTP9 +data OTPDigits = OTP4 | OTP5 | OTP6 | OTP7 | OTP8 | OTP9 deriving (Show) + +-- | An integral time value in seconds. +type OTPTime = Word64 hotp :: forall hash key. (HashAlgorithm hash, ByteArrayAccess key) => hash @@ -48,7 +72,7 @@ hotp :: forall hash key. (HashAlgorithm hash, ByteArrayAccess key) -- ^ Shared secret between the client and server -> Word64 -- ^ Counter value synchronized between the client and server - -> Word32 + -> OTP -- ^ The HOTP value hotp _ d k c = dt `mod` digitsPower d where @@ -71,7 +95,7 @@ resynchronize :: (HashAlgorithm hash, ByteArrayAccess key) -- ^ The shared secret -> Word64 -- ^ The current server counter value - -> (Word32, [Word32]) + -> (OTP, [OTP]) -- ^ The first OTP submitted by the client and a list of additional -- sequential OTPs (which may be empty) -> Maybe Word64 @@ -97,9 +121,9 @@ digitsPower OTP8 = 100000000 digitsPower OTP9 = 1000000000 -data TOTPParams h = TP !h !Word64 !Word16 !OTPDigits !ClockSkew +data TOTPParams h = TP !h !OTPTime !Word16 !OTPDigits !ClockSkew deriving (Show) -data ClockSkew = NoSkew | OneStep | TwoSteps | ThreeSteps | FourSteps deriving (Enum) +data ClockSkew = NoSkew | OneStep | TwoSteps | ThreeSteps | FourSteps deriving (Enum, Show) -- | The default TOTP configuration. defaultTOTPParams :: TOTPParams SHA1 @@ -108,7 +132,7 @@ defaultTOTPParams = TP SHA1 0 30 OTP6 TwoSteps -- | Create a TOTP configuration with customized parameters. mkTOTPParams :: (HashAlgorithm hash) => hash - -> Word64 + -> OTPTime -- ^ The T0 parameter in seconds. This is the Unix time from which to start -- counting steps (default 0). Must be before the current time. -> Word16 @@ -130,11 +154,10 @@ totp :: (HashAlgorithm hash, ByteArrayAccess key) => TOTPParams hash -> key -- ^ The shared secret - -> POSIXTime + -> OTPTime -- ^ The time for which the OTP should be calculated. -- This is usually the current time as returned by @Data.Time.Clock.POSIX.getPOSIXTime@ - -> Word32 - -- ^ The OTP value + -> OTP totp (TP h t0 x d _) k now = hotp h d k (timeToCounter now t0 x) -- | Check a supplied TOTP value is valid for the given time, @@ -142,8 +165,8 @@ totp (TP h t0 x d _) k now = hotp h d k (timeToCounter now t0 x) totpVerify :: (HashAlgorithm hash, ByteArrayAccess key) => TOTPParams hash -> key - -> POSIXTime - -> Word32 + -> OTPTime + -> OTP -> Bool totpVerify (TP h t0 x d skew) k now otp = otp `elem` map (hotp h d k) (range window []) where @@ -152,17 +175,5 @@ totpVerify (TP h t0 x d skew) k now otp = otp `elem` map (hotp h d k) (range win range 0 acc = t : acc range n acc = range (n-1) ((t-n) : (t+n) : acc) -timeToCounter :: POSIXTime -> Word64 -> Word16 -> Word64 -timeToCounter now t0 x = floor ((now - fromIntegral t0) / fromIntegral x) - --- TODO: Put this in memory package -fromW64BE :: (ByteArray ba) => Word64 -> ba -fromW64BE n = B.allocAndFreeze 8 $ \p -> do - pokeByteOff p 0 (fromIntegral (shiftR n 56) :: Word8) - pokeByteOff p 1 (fromIntegral (shiftR n 48) :: Word8) - pokeByteOff p 2 (fromIntegral (shiftR n 40) :: Word8) - pokeByteOff p 3 (fromIntegral (shiftR n 32) :: Word8) - pokeByteOff p 4 (fromIntegral (shiftR n 24) :: Word8) - pokeByteOff p 5 (fromIntegral (shiftR n 16) :: Word8) - pokeByteOff p 6 (fromIntegral (shiftR n 8) :: Word8) - pokeByteOff p 7 (fromIntegral n :: Word8) +timeToCounter :: Word64 -> Word64 -> Word16 -> Word64 +timeToCounter now t0 x = (now - t0) `div` fromIntegral x diff --git a/cryptonite.cabal b/cryptonite.cabal index 6d56753..94c37ec 100644 --- a/cryptonite.cabal +++ b/cryptonite.cabal @@ -176,9 +176,8 @@ Library Crypto.Internal.WordArray Build-depends: base >= 4.3 && < 5 , bytestring - , memory >= 0.8 + , memory >= 0.12 , ghc-prim - , time ghc-options: -Wall -fwarn-tabs -optc-O3 -fno-warn-unused-imports default-language: Haskell2010 cc-options: -std=gnu99