summaryrefslogtreecommitdiffhomepage
path: root/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Types.hs')
-rw-r--r--Types.hs54
1 files changed, 16 insertions, 38 deletions
diff --git a/Types.hs b/Types.hs
index 3a04f64..d1cb513 100644
--- a/Types.hs
+++ b/Types.hs
@@ -1,14 +1,14 @@
-{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveGeneric, FlexibleInstances, OverloadedStrings #-}
+{-# LANGUAGE DeriveGeneric, FlexibleInstances #-}
-module Types where
+module Types (
+ module Types,
+ Val(..)
+) where
+
+import Val
-import Data.ByteString
import GHC.Generics (Generic)
import Data.Aeson
-import Data.Aeson.Types
-import qualified Codec.Binary.Base64 as B64
-import qualified Data.Text as T
-import qualified Data.Text.Encoding as T
-- | Things that the developer sees.
data Seen = Seen
@@ -35,9 +35,11 @@ instance FromJSON Entered
-- to the Activity before this one.
--
-- The Signature is over both the data in the activity, and its pointer.
-data Activity a
- = Activity a HashPointer Signature
- | StartActivity a Signature
+data Activity a = Activity
+ { activity :: a
+ , prevActivity :: (Maybe HashPointer)
+ , signature :: Signature
+ }
deriving (Show, Generic)
instance ToJSON (Activity Seen)
@@ -45,13 +47,7 @@ instance FromJSON (Activity Seen)
instance ToJSON (Activity Entered)
instance FromJSON (Activity Entered)
-activityContent :: Activity a -> a
-activityContent (Activity a _ _) = a
-activityContent (StartActivity a _) = a
-
-data Signature = Signature
- { signature :: Val
- }
+newtype Signature = Signature Val
deriving (Show, Generic)
instance ToJSON Signature
@@ -67,28 +63,10 @@ data HashPointer = HashPointer
instance ToJSON HashPointer
instance FromJSON HashPointer
-data HashMethod = SHA256
+-- | We use SHA256. (SHA3 is included to future proof, and because it
+-- improves the generated JSON.)
+data HashMethod = SHA256 | SHA3
deriving (Show, Generic, Eq)
instance ToJSON HashMethod
instance FromJSON HashMethod
-
--- | Newtype of ByteString so we can have JSON instances without orphans.
-newtype Val = Val { val :: ByteString }
- deriving (Show, Generic, Eq, Monoid)
-
--- | JSON instances for Val, using base64 encoding.
-instance ToJSON Val where
- toJSON (Val b) = object [ "b" .= b64 b ]
-instance FromJSON Val where
- parseJSON (Object v) = Val <$> (unb64 =<< v .: "b")
- parseJSON invalid = typeMismatch "ByteString" invalid
-
-b64 :: ByteString -> T.Text
-b64 = T.decodeUtf8 . B64.encode
-
-unb64 :: Monad m => T.Text -> m ByteString
-unb64 t = either
- (\_ -> fail "bad base64 data")
- return
- ( B64.decode $ T.encodeUtf8 t)