1
1
mirror of https://github.com/sdiehl/wiwinwlh.git synced 2024-08-16 23:40:41 +03:00

Write more

This commit is contained in:
sdiehl 2020-01-26 10:02:13 +00:00
parent d7cea6a001
commit 9918ecea82
6 changed files with 117 additions and 19 deletions

View File

@ -2,18 +2,18 @@
\usepackage{geometry}
\usepackage{resources/dtrt}
\geometry{
a4paper,
total={21.59cm,27.94cm},
top=2.8cm,
bottom=2.1cm,
inner=1.91cm,
outer=6.68cm,
% For pdf
left=1.5cm,
right=1.5cm,
% For print
%marginparwidth=4cm,
%marginparsep=0.8cm
a4paper,
total={21.59cm,27.94cm},
top=2.8cm,
bottom=2.1cm,
inner=1.91cm,
outer=6.68cm,
% For pdf
left=1.5cm,
right=1.5cm,
% For print
%marginparwidth=4cm,
%marginparsep=0.8cm
}
\usepackage{lmodern}
\usepackage{xcolor}

View File

@ -0,0 +1,9 @@
{-# LANGUAGE TypeApplications #-}
import Data.Proxy
a :: Proxy Int
a = Proxy @Int
b :: String
b = show (read @Int "42")

View File

@ -0,0 +1,38 @@
{-# LANGUAGE OverloadedStrings #-}
module AES where
import Crypto.Cipher.AES
import Crypto.Cipher.Types
import Crypto.Error
import Crypto.Random.Types
import Data.ByteString
type AesKey = ByteString
genKey :: IO AesKey
genKey = getRandomBytes 32 -- AES256 key size
aesEncrypt :: ByteString -> AesKey -> Either CryptoError ByteString
aesEncrypt input sk =
ctrCombine
<$> init
<*> pure nullIV
<*> pure input
where
init :: Either CryptoError AES256
init = eitherCryptoError $ cipherInit sk
aesDecrypt :: ByteString -> AesKey -> Either CryptoError ByteString
aesDecrypt = aesEncrypt
main :: IO ()
main = do
key <- genKey
let message = "The quick brown fox jumped over the lazy dog."
mcipherText = aesEncrypt message key
case mcipherText of
Right cipherText -> do
print cipherText
print (aesDecrypt cipherText key)
Left err -> print err

View File

@ -0,0 +1,39 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedLists #-}
module Galois where
import Data.Field.Galois
import Prelude hiding ((/))
-- Prime field
type Fq = Prime 2147483647
exampleFq :: IO ()
exampleFq = do
print ((1 + 0x7FFFFFFF16) :: Fq)
print ((10000 * 10000) :: Fq)
print ((1 / 524287) :: Fq)
-- Polynomial term
data P2
-- Extension field
type Fq2 = Extension P2 Fq
-- Irreducublie monic polynomial extension
instance IrreducibleMonic P2 Fq where
poly _ = X2 + 1
-- Polynomial 2*x^2 + 1 over Fq2
p1 :: Fq2
p1 = [1, 2]
p2 :: Fq2
p2 = (p1 + p1) * 2
p3 :: Bool
p3 = p2 / p1 == 4

View File

@ -15,6 +15,7 @@ library
cryptonite >= 0.20 && < 0.30,
pairing >= 1.0 && < 2.0,
elliptic-curve >= 0.3 && < 0.4,
galois-field >= 1.0 && < 1.1,
memory -any,
bytestring -any
default-language: Haskell2010

View File

@ -3889,8 +3889,7 @@ DeriveFunctor
Many instances of functor over datatypes with simple single parameters and
trivial constructors are simply the result of trivially applying a functions
over the single constructor's argument. GHC can derive this boilerplace
automatically in deriving clauses if DeriveFunctor is enabled.
over the single constructor's argument. GHC can derive this boilerplace automatically in deriving clauses if DeriveFunctor is enabled.
~~~~ {.haskell include="src/04-extensions/derive_functor.hs"}
~~~~
@ -4044,6 +4043,9 @@ main = do
print (#foo (MkT True False))
```
This is also used in more advanced libraries like [Selda] which do object
relational mapping between Haskell datatype fields and database columns.
See:
* [OverloadedRecordFields revived](http://www.well-typed.com/blog/2015/03/overloadedrecordfields-revived/)
@ -4094,13 +4096,16 @@ Or on the version of the base library used.
#endif
```
It can also be abused to do terrible things like metaprogramming with strings,
but please don't do this.
One can also use the CPP to emit Haskell source at compile-time. This is used in
some libraries which have massive boiler plate obligations. This can be abused
quite easily and doing this kind of compile-time string-munging is a last
resort.
TypeApplications
----------------
TODO
~~~~ {.haskell include="src/04-extensions/application.hs"}
~~~~
DerivingVia
-----------
@ -10324,12 +10329,18 @@ convertFromBase :: (ByteArrayAccess bin, ByteArray bout) => Base -> bin -> Eithe
AES Ciphers
-----------
TODO
~~~~ {.haskell include="src/32-cryptography/AES.hs"}
~~~~
Galois Fields
-------------
TODO
Many modern cryptographic protocols require the use of finite field arithmetic.
Finite fields are algebraic structures that have algebraic field structure
(addition, multiplication, division) and closure
~~~~ {.haskell include="src/32-cryptography/Galois.hs"}
~~~~
Elliptic Curves
---------------