Skip to content

Commit

Permalink
refactor(lib): Create a Utils module
Browse files Browse the repository at this point in the history
  • Loading branch information
sgillespie committed Feb 11, 2024
1 parent b72e223 commit 3b09af0
Show file tree
Hide file tree
Showing 5 changed files with 142 additions and 63 deletions.
4 changes: 3 additions & 1 deletion gibberish.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -103,7 +103,8 @@ library
Data.Gibberish.GenPass,
Data.Gibberish.MonadPass,
Data.Gibberish.Trigraph,
Data.Gibberish.Types
Data.Gibberish.Types,
Data.Gibberish.Utils
other-modules:
Paths_gibberish
build-depends:
Expand Down Expand Up @@ -166,6 +167,7 @@ test-suite spec
Data.Gibberish.GenPassSpec
Data.Gibberish.TrigraphSpec
Data.Gibberish.TypesSpec
Data.Gibberish.UtilsSpec
Paths_gibberish
other-extensions:
OverloadedLists
Expand Down
61 changes: 2 additions & 59 deletions src/Data/Gibberish/GenPass.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,11 +3,11 @@

module Data.Gibberish.GenPass
( genPassword,
numeralConversions,
) where

import Data.Gibberish.MonadPass (MonadRandom ())
import Data.Gibberish.Types
import Data.Gibberish.Utils

import Control.Arrow ((>>>))
import Control.Monad ((>=>))
Expand Down Expand Up @@ -107,69 +107,12 @@ digitize1 _ t
| null candidates = pure t
| otherwise = digitize1' =<< uniform candidates
where
candidates :: [Int]
candidates = findIndices (`elem` Map.keys numeralConversions) t
digitize1' :: MonadRandom m => Int -> m Text
digitize1' pos = update1 (uniform . toDigit) t pos
digitize1' = update1 (uniform . toDigit) t

digitizeR :: MonadRandom m => Text -> m Text
digitizeR = updateR (uniform . toDigit) (1 % 6)

-- | A mapping from letters to numbers that look like them
numeralConversions :: Map Char [Char]
numeralConversions =
Map.fromList
[ ('o', ['0']),
('l', ['1']),
('z', ['2']),
('e', ['3']),
('a', ['4']),
('s', ['5']),
('g', ['6', '9']),
('t', ['7']),
('b', ['8'])
]

-- | Map a letter to one or more digits, if possible
toDigit :: Char -> [Char]
toDigit c = fromMaybe [c] (numeralConversions Map.!? c)

-- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the
-- indices of all elements satisfying the predicate, in ascending order.
findIndices :: (Char -> Bool) -> Text -> [Int]
findIndices p = loop 0
where
loop !n !qs = case Text.findIndex p qs of
Just !i ->
let !j = n + i
in j : loop (j + 1) (Text.drop (i + 1) qs)
Nothing -> []
{-# INLINE [1] findIndices #-}

update1 :: Monad m => (Char -> m Char) -> Text -> Int -> m Text
update1 f t pos =
case Text.splitAt pos t of
(prefix, suffix) ->
case Text.uncons suffix of
Nothing -> pure t
Just (ch, suffix') -> do
ch' <- f ch
pure $ prefix `Text.append` (ch' `Text.cons` suffix')

updateR :: MonadRandom m => (Char -> m Char) -> Rational -> Text -> m Text
updateR f prob t = textTraverse updateR' t
where
updateR' ch = do
ch' <- f ch
fromList
[ (ch, toRational $ denominator prob),
(ch', toRational $ numerator prob)
]

textTraverse :: Monad m => (Char -> m Char) -> Text -> m Text
textTraverse f = Text.foldr folder (pure Text.empty)
where
folder c accum = do
accum' <- accum
c' <- f c
pure $ Text.cons c' accum'
69 changes: 69 additions & 0 deletions src/Data/Gibberish/Utils.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,69 @@
module Data.Gibberish.Utils
( numeralConversions,
update1,
updateR,
findIndices,
textTraverse,
) where

import Control.Monad.Random (MonadRandom (), fromList)
import Data.Map (Map ())
import Data.Map qualified as Map
import Data.Ratio (denominator, numerator)
import Data.Text (Text ())
import Data.Text qualified as Text

-- | A mapping from letters to numbers that look like them
numeralConversions :: Map Char [Char]
numeralConversions =
Map.fromList
[ ('o', ['0']),
('l', ['1']),
('z', ['2']),
('e', ['3']),
('a', ['4']),
('s', ['5']),
('g', ['6', '9']),
('t', ['7']),
('b', ['8'])
]

update1 :: Monad m => (Char -> m Char) -> Text -> Int -> m Text
update1 f t pos =
case Text.splitAt pos t of
(prefix, suffix) ->
case Text.uncons suffix of
Nothing -> pure t
Just (ch, suffix') -> do
ch' <- f ch
pure $ prefix `Text.append` (ch' `Text.cons` suffix')

updateR :: MonadRandom m => (Char -> m Char) -> Rational -> Text -> m Text
updateR f prob = textTraverse updateR'
where
updateR' ch = do
ch' <- f ch
fromList
[ (ch, toRational $ denominator prob),
(ch', toRational $ numerator prob)
]

-- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the
-- indices of all elements satisfying the predicate, in ascending order.
findIndices :: (Char -> Bool) -> Text -> [Int]
findIndices p = loop 0
where
loop !n !qs = case Text.findIndex p qs of
Just !i ->
let !j = n + i
in j : loop (j + 1) (Text.drop (i + 1) qs)
Nothing -> []
{-# INLINE [1] findIndices #-}

textTraverse :: Monad m => (Char -> m Char) -> Text -> m Text
textTraverse f = Text.foldr folder (pure Text.empty)
where
folder c accum = do
accum' <- accum
c' <- f c
pure $ Text.cons c' accum'
6 changes: 3 additions & 3 deletions test/Data/Gibberish/GenPassSpec.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,14 @@
module Data.Gibberish.GenPassSpec (spec) where

import Data.Gibberish.GenPass (genPassword, numeralConversions)
import Data.Gibberish.GenPass (genPassword)
import Data.Gibberish.MonadPass (usingPass)
import Data.Gibberish.Trigraph (Language (..), loadTrigraph)
import Data.Gibberish.Types (GenPassOptions (..), Word (..))
import Data.Gibberish.Utils (numeralConversions)
import Test.Gibberish.Gen qualified as Gen

import Control.Monad.IO.Class (liftIO)
import Data.Char
import Data.Map (Map ())
import Data.Map qualified as Map
import Data.Text qualified as Text
import Hedgehog
Expand Down Expand Up @@ -89,5 +89,5 @@ spec = do
annotateShow pass

assert $
Text.any (\c -> isNumber c) pass
Text.any isNumber pass
|| Text.all (`Map.notMember` numeralConversions) pass
65 changes: 65 additions & 0 deletions test/Data/Gibberish/UtilsSpec.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,65 @@
module Data.Gibberish.UtilsSpec (spec) where

import Data.Gibberish.MonadPass (usingPass)
import Data.Gibberish.Utils
import Test.Gibberish.Gen qualified as Gen

import Data.Char (isLowerCase, isUpperCase, toUpper)
import Data.Maybe (listToMaybe)
import Data.Ratio ((%))
import Data.Text qualified as Text
import Hedgehog
import Hedgehog.Gen qualified as Gen
import Hedgehog.Range qualified as Range
import Test.Hspec
import Test.Hspec.Hedgehog

spec :: Spec
spec = do
describe "update1" $ do
it "updates at index" $ hedgehog $ do
t <- forAll $ Gen.text (Range.linear 1 250) Gen.lower
ix <- forAll $ Gen.int (Range.linear 0 (Text.length t - 1))
res <- update1 (pure . toUpper) t ix

assert $ isUpperCase (Text.index res ix)

describe "updateR" $ do
it "updates everything when ratio is infinity" $ hedgehog $ do
t <- forAll $ Gen.text (Range.linear 1 250) Gen.lower
randomGen <- forAll Gen.stdGen

-- Make numerator absurdly high since we can't use 0 in the denominator
let prob = fromIntegral (maxBound :: Int) % 1
(res, _) = usingPass randomGen (updateR (pure . toUpper) prob t)
annotateShow res

assert $ Text.all isUpperCase res

it "updates nothing when ratio is zero" $ hedgehog $ do
t <- forAll $ Gen.text (Range.linear 1 250) Gen.lower
randomGen <- forAll Gen.stdGen

let (res, _) = usingPass randomGen (updateR (pure . toUpper) (0 % 1) t)
annotateShow res

assert $ Text.all isLowerCase res

describe "findIndices" $ do
it "agrees with findIndex" $ hedgehog $ do
t <- forAll $ Gen.text (Range.linear 1 250) Gen.digit
let mapper = (<= '5')
listToMaybe (findIndices mapper t) === Text.findIndex mapper t

it "agrees with filter" $ hedgehog $ do
t <- forAll $ Gen.text (Range.linear 1 250) Gen.digit
let p = (<= '5')
map (t `Text.index`) (findIndices p t) === Text.unpack (Text.filter p t)

describe "textTraverse" $ do
it "agrees with map" $ hedgehog $ do
t <- forAll $ Gen.text (Range.linear 1 250) Gen.lower
let mapper = pure . toUpper
res <- textTraverse mapper t

res === Text.map toUpper t

0 comments on commit 3b09af0

Please sign in to comment.