Map-to-integer for ciphers? (edited)

박신환 ndospark320 at naver.com
Sun Jul 29 09:50:24 UTC 2018


For use of ciphers (SHA-256, RSA-2048, etc.), a type must be able to be injectively mapped to integers. It seems `Enum` is currently the closest thing that does this.

But `Enum` is supposed to be for arithmetic sequences, so it seems better to define a new typeclass. (Here named `Cipherable`)
 
Here, `Cipherable` has `deCipher :: Natural -> a` and `enCipher :: a -> Natural`.

There are some types that aren't members of `Enum`. For example, `Maybe`, `[]`, etc. They seem okay to be Cipherable. Hence:

 

 
{-# LANGUAGE ScopedTypeVariables #-}
 
instance Cipherable a => Cipherable (Maybe a) where
    deCipher 0 = Nothing
    deCipher n = Just (deCipher (n-1))
    enCipher Nothing  = 0
    enCipher (Just x) = 1 + enCipher x

instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where
    deCipher 0 = []
    deCipher n = let
        (q,r) = (n-1) `quotRem` (1 + enCipher (maxBound :: a))
        in deCipher r : deCipher q
    enCipher []     = 0
    enCipher (x:xs) = 1 + enCipher x + (1 + enCipher (maxBound :: a)) * fromEnum xs

instance Cipherable Void where
    deCipher = errorWithoutStackTrace "Cipher.Cipherable.Void.deCipher"
    enCipher = absurd
 
 
(Besides, it is possible to re-write that of `[]` without ScopedTypeVariables? I see no way...)
 
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/libraries/attachments/20180729/5cb0a2fc/attachment.html>


More information about the Libraries mailing list