praxis

Various programming exercises.
git clone git://git.jtobin.io/praxis.git
Log | Files | Refs

Blockchain.hs (3451B)


      1 {-# OPTIONS_GHC -Wall #-}
      2 {-# LANGUAGE BangPatterns #-}
      3 {-# LANGUAGE RecordWildCards #-}
      4 {-# LANGUAGE ViewPatterns #-}
      5 
      6 import Data.Char as C
      7 import Data.List as L (foldl')
      8 import Data.Monoid ((<>))
      9 import qualified Data.Map.Strict as MS
     10 
     11 hash8 :: String -> String
     12 hash8 (fmap C.ord -> bytes) = show (L.foldl' alg 0 bytes) where
     13   alg acc byte =
     14     let key = (acc + byte) `mod` 256
     15     in  case MS.lookup key ptable of
     16           Nothing  -> error "hash8: missing key"
     17           Just val -> val
     18 
     19   ptable = MS.fromList $
     20     zip [0..255]
     21       [ 1, 87, 49, 12, 176, 178, 102, 166, 121, 193, 6, 84, 249, 230, 44, 163
     22       , 14, 197, 213, 181, 161, 85, 218, 80, 64, 239, 24, 226, 236, 142, 38
     23       , 200 , 110, 177, 104, 103, 141, 253, 255, 50, 77, 101, 81, 18, 45, 96
     24       , 31, 222 , 25, 107, 190, 70, 86, 237, 240, 34, 72, 242, 20, 214, 244
     25       , 227, 149, 235, 97, 234, 57, 22, 60, 250, 82, 175, 208, 5, 127, 199, 111
     26       , 62, 135, 248 , 174, 169, 211, 58, 66, 154, 106, 195, 245, 171, 17, 187
     27       , 182, 179, 0, 243 , 132, 56, 148, 75, 128, 133, 158, 100, 130, 126, 91
     28       , 13, 153, 246, 216, 219 , 119, 68, 223, 78, 83, 88, 201, 99, 122, 11
     29       , 92, 32, 136, 114, 52, 10, 138, 30, 48, 183, 156, 35, 61, 26, 143, 74
     30       , 251, 94, 129, 162, 63, 152, 170, 7, 115, 167, 241, 206, 3, 150, 55
     31       , 59, 151, 220, 90, 53, 23, 131, 125, 173, 15, 238, 79, 95, 89, 16, 105
     32       , 137, 225, 224, 217, 160, 37, 123, 118, 73, 2, 157, 46, 116, 9, 145
     33       , 134, 228, 207, 212, 202, 215, 69, 229, 27, 188, 67, 124, 168, 252, 42
     34       , 4, 29, 108, 21, 247, 19, 205, 39, 203, 233, 40, 186, 147, 198, 192
     35       , 155, 33, 164, 191, 98, 204, 165, 180, 117, 76, 140, 36, 210, 172, 41
     36       , 54, 159, 8, 185, 232, 113, 196, 231, 47, 146, 120, 51, 65, 28, 144
     37       , 254, 221, 93, 189, 194, 139, 112, 43, 71, 109, 184, 209
     38       ]
     39 
     40 hash16 :: String -> String
     41 hash16 input = hash8 input <> hash8 modified where
     42   modified = fmap C.chr mbytes
     43   mbytes   = case fmap C.ord input of
     44     []    -> []
     45     (h:t) -> (h + 1) `mod` 256 : t
     46 
     47 data Block = Block {
     48     index :: !Int
     49   , datum :: String
     50   , phash :: String
     51   , chash :: String
     52   } deriving Show
     53 
     54 newtype Blockchain = Blockchain {
     55     chain :: [Block]
     56   } deriving Show
     57 
     58 genesis :: Block
     59 genesis = Block {..} where
     60   index = 0
     61   datum = "Something something Times something something bailout"
     62   phash = "0"
     63   chash = hash16 (show index <> datum <> phash)
     64 
     65 adjoin :: String -> Blockchain -> Maybe Blockchain
     66 adjoin str Blockchain {..} = case chain of
     67   [] -> Nothing
     68   (Block {..} : _) -> Just $
     69     let nindex = succ index
     70         ndatum = str
     71         nphash = chash
     72         nchash = hash16 (show nindex <> ndatum <> nphash)
     73         block  = Block nindex ndatum nphash nchash
     74     in  Blockchain (block : chain)
     75 
     76 validate :: Blockchain -> Bool
     77 validate Blockchain {..} = L.foldl' alg True chain where
     78   alg !acc block@Block {..}
     79     | chash == hash16 (show index <> datum <> phash) = acc && True
     80     | otherwise = error ("invalid block: " <> show block)
     81 
     82 test :: Blockchain
     83 test =
     84   let gen = Blockchain [genesis]
     85 
     86       bchain =
     87             adjoin "shawn sends jared two bucks" gen
     88         >>= adjoin "jared sends shawn three bucks"
     89         >>= adjoin "jared sends rachel one buck"
     90         >>= adjoin "rachel sends shawn one buck"
     91 
     92   in  case bchain of
     93         Nothing -> error "impossible"
     94         Just bc -> bc
     95 
     96 main :: IO ()
     97 main = do
     98   mapM_ print (chain test)
     99   print (validate test)
    100