{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
module Cardano.Dictionary.Generic
(
toDictionary
) where
import Basement.Imports
( Bounded (..), Either (..), Maybe (..), error, flip, fromList, ($), (.) )
import Basement.Sized.Vect
( Vect (..), index, toVect )
import Basement.String
( String )
import Crypto.Encoding.BIP39.Dictionary
( Dictionary (..), DictionaryError (..), WordIndex, unWordIndex )
import Data.Maybe
( fromMaybe )
import qualified Data.List as L
toDictionary :: [String] -> Dictionary
toDictionary :: [String] -> Dictionary
toDictionary [String]
wordList = Dictionary
{ dictionaryWordToIndex :: String -> Either DictionaryError WordIndex
dictionaryWordToIndex =
\String
word -> case String -> [(String, WordIndex)] -> Maybe WordIndex
forall a b. Eq a => a -> [(a, b)] -> Maybe b
L.lookup String
word [(String, WordIndex)]
wordsWithIxs of
Just WordIndex
x -> WordIndex -> Either DictionaryError WordIndex
forall a b. b -> Either a b
Right WordIndex
x
Maybe WordIndex
Nothing -> DictionaryError -> Either DictionaryError WordIndex
forall a b. a -> Either a b
Left (DictionaryError -> Either DictionaryError WordIndex)
-> DictionaryError -> Either DictionaryError WordIndex
forall a b. (a -> b) -> a -> b
$ String -> DictionaryError
ErrInvalidDictionaryWord String
word
, dictionaryTestWord :: String -> Bool
dictionaryTestWord = (String -> [String] -> Bool) -> [String] -> String -> Bool
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
L.elem [String]
wordList
, dictionaryIndexToWord :: WordIndex -> String
dictionaryIndexToWord = Vect 2048 String -> Offset String -> String
forall (n :: Nat) ty. Vect n ty -> Offset ty -> ty
index Vect 2048 String
words (Offset String -> String)
-> (WordIndex -> Offset String) -> WordIndex -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. WordIndex -> Offset String
unWordIndex
, dictionaryWordSeparator :: String
dictionaryWordSeparator = String
" "
}
where
wordsWithIxs :: [(String, WordIndex)]
wordsWithIxs :: [(String, WordIndex)]
wordsWithIxs = [String] -> [WordIndex] -> [(String, WordIndex)]
forall a b. [a] -> [b] -> [(a, b)]
L.zip [String]
wordList [WordIndex
forall a. Bounded a => a
minBound..WordIndex
forall a. Bounded a => a
maxBound]
words :: Vect 2048 String
words :: Vect 2048 String
words = Vect 2048 String -> Maybe (Vect 2048 String) -> Vect 2048 String
forall a. a -> Maybe a -> a
fromMaybe (String -> Vect 2048 String
forall a. HasCallStack => String -> a
error String
"invalid vector length") (Maybe (Vect 2048 String) -> Vect 2048 String)
-> Maybe (Vect 2048 String) -> Vect 2048 String
forall a b. (a -> b) -> a -> b
$ Array String -> Maybe (Vect 2048 String)
forall (n :: Nat) ty.
(KnownNat n, Countable ty n) =>
Array ty -> Maybe (Vect n ty)
toVect (Array String -> Maybe (Vect 2048 String))
-> Array String -> Maybe (Vect 2048 String)
forall a b. (a -> b) -> a -> b
$ [Item (Array String)] -> Array String
forall l. IsList l => [Item l] -> l
fromList [Item (Array String)]
[String]
wordList