--- /dev/null
+module CryptoFoleo
+ (
+ rsa_keygen,
+ rsa_import,
+ rsa_export
+ )
+where
+import System.IO as IO
+import Foreign
+import Foreign.C.Types
+import Foreign.C.String
+import Data.ByteString
+import Data.ByteString.Internal
+import Data.Word
+import Data.ByteString.Unsafe
+import Control.DeepSeq
+import qualified Data.ByteString.Internal as BI
+import qualified Foreign.Marshal.Utils as MU
+import qualified Data.ByteString.Char8 as C8
+
+foreign import ccall unsafe "foleo_rsa_keysize"
+ c_rsa_keysize :: IO (CUShort)
+
+foreign import ccall unsafe "foleo_rsa_keygen"
+ c_rsa_keygen :: CUShort -> Ptr () -> Ptr () -> IO ()
+
+foreign import ccall unsafe "foleo_rsa_export"
+ c_rsa_export :: Ptr () -> IO (Ptr (CUChar))
+
+foreign import ccall unsafe "foleo_rsa_import"
+ c_rsa_import :: Ptr (CUChar) -> Ptr () -> IO ()
+
+foreign import ccall unsafe "foleo_rsa_free"
+ c_rsa_free :: Ptr () -> IO ()
+
+foreign import ccall unsafe "free"
+ c_free :: Ptr a -> IO ()
+
+rsa_keygen :: Word16 -> (ByteString -> ByteString -> IO ()) -> IO ()
+rsa_keygen n fn = do
+ sRsaSize <- c_rsa_keysize
+ let rsaSize :: Int
+ rsaSize = fromIntegral sRsaSize
+ allocaBytes rsaSize $ \pubKeyPtr ->
+ allocaBytes rsaSize $ \prvKeyPtr -> do
+ c_rsa_keygen (fromIntegral n) pubKeyPtr prvKeyPtr
+ pubKey <- BI.create rsaSize (\ptr -> MU.copyBytes ptr (castPtr pubKeyPtr) rsaSize)
+ prvKey <- BI.create rsaSize (\ptr -> MU.copyBytes ptr (castPtr prvKeyPtr) rsaSize)
+ fn pubKey prvKey
+ rsa_free pubKey
+ rsa_free prvKey
+
+rsa_import :: String -> (ByteString -> IO ()) -> IO ()
+rsa_import n fn = do
+ sRsaSize <- c_rsa_keysize
+ let rsaSize :: Int
+ rsaSize = fromIntegral sRsaSize
+ unsafeUseAsCStringLen (C8.pack n) $ \(bsPtr, len) -> do
+ allocaBytes rsaSize $ \keyPtr -> do
+ c_rsa_import (castPtr bsPtr) keyPtr
+ key <- BI.create rsaSize(\ptr -> MU.copyBytes ptr (castPtr keyPtr) rsaSize)
+ fn key
+ rsa_free key
+
+rsa_export :: ByteString -> IO(String)
+rsa_export blob = do
+ useAsCString blob $ \blobPtr -> do
+ cStrPtr <- c_rsa_export (castPtr blobPtr)
+ cStr <- peekCString (castPtr cStrPtr)
+ c_free cStrPtr
+ return cStr
+
+rsa_free :: ByteString -> IO()
+rsa_free blob = useAsCString blob $ \ptr -> c_rsa_free (castPtr ptr)
+
+--main :: IO()
+--main = do
+-- rsa_keygen 2048 $ \pub prv -> do
+-- spub <- rsa_export pub
+-- IO.putStr spub
+
+byteStringToInteger :: ByteString -> Integer
+byteStringToInteger = foldl' (\acc byte -> acc * 256 + fromIntegral byte) 0
import System.IO as IO
-import Foreign
-import Foreign.C.Types
-import Foreign.C.String
-import Data.ByteString
-import Data.ByteString.Internal
-import Data.Word
-import Data.ByteString.Unsafe
-import Control.DeepSeq
-import qualified Data.ByteString.Internal as BI
-import qualified Foreign.Marshal.Utils as MU
-import qualified Data.ByteString.Char8 as C8
-
-foreign import ccall unsafe "foleo_rsa_keysize"
- c_rsa_keysize :: IO(CUShort)
-
-foreign import ccall unsafe "foleo_rsa_keygen"
- c_rsa_keygen :: CUShort -> Ptr() -> Ptr() -> IO()
-
-foreign import ccall unsafe "foleo_rsa_export"
- c_rsa_export :: Ptr () -> IO (Ptr CUChar)
-
-foreign import ccall unsafe "foleo_rsa_free"
- c_rsa_free :: Ptr () -> IO ()
-foreign import ccall unsafe "free"
- c_free :: Ptr a -> IO ()
-
-rsa_keygen :: Word16 -> (ByteString -> ByteString -> IO()) -> IO()
-rsa_keygen n fn = do
- sRsaSize <- c_rsa_keysize
- let rsaSize :: Int
- rsaSize = fromIntegral sRsaSize
- allocaBytes rsaSize $ \pubKeyPtr ->
- allocaBytes rsaSize $ \prvKeyPtr -> do
- c_rsa_keygen (fromIntegral n) pubKeyPtr prvKeyPtr
- pubKey <- BI.create rsaSize (\ptr -> MU.copyBytes ptr (castPtr pubKeyPtr) rsaSize)
- prvKey <- BI.create rsaSize (\ptr -> MU.copyBytes ptr (castPtr prvKeyPtr) rsaSize)
- fn pubKey prvKey
- rsa_free pubKey
- rsa_free prvKey
-
-rsa_export :: ByteString -> IO(String)
-rsa_export blob = do
- useAsCString blob $ \blobPtr -> do
- cStrPtr <- c_rsa_export (castPtr blobPtr)
- cStr <- peekCString (castPtr cStrPtr)
- c_free cStrPtr
- return cStr
-
-rsa_free :: ByteString -> IO()
-rsa_free blob = useAsCString blob $ \ptr -> c_rsa_free (castPtr ptr)
+import System.Directory
+import Control.Monad
+import CryptoFoleo
main :: IO()
main = do
- rsa_keygen 2048 $ \pub prv -> do
- spub <- rsa_export pub
- IO.putStr spub
+ existsPub <- doesFileExist "pub.key"
+ existsPrv <- doesFileExist "prv.key"
+ unless (existsPub && existsPrv) $ do
+ rsa_keygen 2048 $ \pub prv -> do
+ spub <- rsa_export pub
+ sprv <- rsa_export prv
+ writeFile "pub.key" spub
+ writeFile "prv.key" sprv
+
+ spub <- readFile "pub.key"
+ rsa_import spub $ \pubKey -> do
+ sspub <- rsa_export pubKey
+ putStrLn sspub
+ putStrLn spub
-byteStringToInteger :: ByteString -> Integer
-byteStringToInteger = foldl' (\acc byte -> acc * 256 + fromIntegral byte) 0
--- /dev/null
++-------[RSA Private Key]--------+
+|#.[/[@$%#,\~%=@<[<(^,(&$:~'}<}``|
+|%$>(;&&%'($;')`#e~"},<<)@),^}%"<|
+|.%(?`]._*?@!e/@[*:)]/ex*},>~[s/(|
+|#;}#`*{=";[\,(=>.${x,:>!x(\"=]=&|
+|"%){"&x#>~}e]{^~\s'`'}><xx];s!@}|
+|<;_#,xx#?@#(}@\#`#:$!e}(:\#~#@>"|
+|$^]~%!`^~".\@<<{,@#<&;x")}:]{'^~|
+|`!@).{%.{}>e!/s:>`_es^?=(/}<]_*=|
+|]{@(s>.&\!`"$x@!{]>==s`.`$@{@`/<|
+|^??^/}^*['_<:@(^?]/:`~[[={*[_@#]|
+|::]}*@!)?}/`]=`/e#\';#(}[!,&<!e_|
+|\}>:"`>!{'x!*./!,x;_%{^<]:<)$""^|
+|;x[[^&!?e?=__']s~<?x*\#)_s $`,^_|
+|=^`s\e#^e,>.,`,$&!?`:)/{\}!&!\{/|
+|`#:`)x%)"e`?,[s.)e=>>^`(;,$}'(<:|
+|%."{(=_,%^!ex,$,_x>*`%^,ex;]x_$;|
+|!.!.#.x]e/}*~;<,s/{~?e`@}!~$)e_.|
+|;,s),s@.{$ex{@=<s?\_/]/=*(\`'%=`|
+|!/~?][](.=x="'&^{s`(,?$}))&;)(x;|
+|{[(;`>;];:{/(}$^.%(&;%\x!{}<,x!{|
+|!<={'/}x?^'.s&;$(*~*")ses`},!:;*|
+|e;s&~.:`;xx&_,}[};x@e=){]s&%'[_:|
+|%!!\_%{(!`(;^/_:<^?@,=@%)>,/$)<s|
+|}`!#*~/{`'*"/[?$_]"?#?:s'}*=>@,_|
+|[.~!<\!<&.`%}^=s/?@_x=":'{~[_={)|
+|\*$~~?.#};"`\[)[\[~;s |
++--------------------------------+
--- /dev/null
++--------[RSA Public Key]--------+
+|(^:/# $`,^_=^`s\e#^e,>.,`,$&!?`:|
+|)/{\}!&!\{/`#:`)x%)"e`?,[s.)e=>>|
+|^`(;,$}'(<:%."{(=_,%^!ex,$,_x>*`|
+|%^,ex;]x_$;!.!.#.x]e/}*~;<,s/{~?|
+|e`@}!~$)e_.;,s),s@.{$ex{@=<s?\_/|
+|]/=*(\`'%=`!/~?][](.=x="'&^{s`(,|
+|?$}))&;)(x;{[(;`>;];:{/(}$^.%(&;|
+|%\x!{}<,x!{!<={'/}x?^'.s&;$(*~*"|
+|)ses`},!:;*e;s&~.:`;xx&_,}[};x@e|
+|=){]s&%'[_:%!!\_%{(!`(;^/_:<^?@,|
+|=@%)>,/$)<s}`!#*~/{`'*"/[?$_]"?#|
+|?:s'}*=>@,_[.~!<\!<&.`%}^=s/?@_x|
+|=":'{~[_={)\*$~~?.#};"`\[)[\[~;s|
++--------------------------------+