Map-to-integer for ciphers?

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`) 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 toEnum 0 = Nothing toEnum n = Just (toEnum n) fromEnum Nothing = 0 fromEnum (Just x) = 1 + fromEnum x instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where toEnum 0 = [] toEnum n = let (q,r) = (n-1) `quotRem` (1 + fromEnum (maxBound :: a)) in toEnum r : toEnum q fromEnum [] = 0 fromEnum (x:xs) = 1 + fromEnum x + (1 + fromEnum (maxBound :: a)) * fromEnum xs instance Cipherable Void where toEnum = errorWithoutStackTrace "Cipher.Cipherable.Void.toEnum" fromEnum = absurd (Besides, it is possible to re-write that of `[]` without ScopedTypeVariables? I see no way...)

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 (toEnum n) enCipher Nothing = 0 enCipher (Just x) = 1 + fromEnum x instance forall a. (Cipherable a, Bounded a) => Cipherable [a] where deCipher 0 = [] deCipher n = let (q,r) = (n-1) `quotRem` (1 + fromEnum (maxBound :: a)) in toEnum r : toEnum q enCipher [] = 0 enCipher (x:xs) = 1 + fromEnum x + (1 + fromEnum (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...)

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...)

On Sun, 29 Jul 2018, 박신환 wrote:
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
let (q,r) = (n-1) `quotRem` (1 + enCipher (maxBound `asTypeOf` rd)) rd = deCipher r in rd : deCipher q
enCipher [] = 0 enCipher (x:xs) = 1 + enCipher x + (1 + enCipher (maxBound :: a)) * fromEnum xs
maxBound `asTypeOf` x
participants (2)
-
Henning Thielemann
-
박신환