urbit/pkg/hs/urbit-king/lib/Urbit/Arvo/Event.hs

408 lines
11 KiB
Haskell
Raw Normal View History

{-# LANGUAGE StrictData #-}
-- This is required due to the use of 'Void' in a constructor slot in
-- combination with 'deriveNoun' which generates an unreachable pattern.
{-# OPTIONS_GHC -Wno-overlapping-patterns #-}
2020-01-23 07:16:09 +03:00
{-|
Event Types and Noun Conversion
-}
module Urbit.Arvo.Event where
2020-12-19 04:00:56 +03:00
import Urbit.Prelude
import Control.Monad.Fail (fail)
2020-12-03 21:41:03 +03:00
import Urbit.Arvo.Common (KingId(..), ServId(..), Vere(..))
import Urbit.Arvo.Common (Desk, Mime)
import Urbit.Arvo.Common (Header(..), HttpEvent)
import Urbit.Arvo.Common (AmesDest, Ipv4, Ipv6, Port, Turf)
import Urbit.Arvo.Common (ReOrg(..), reorgThroughNoun)
import qualified Crypto.Sign.Ed25519 as Ed
2019-09-25 03:15:00 +03:00
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C
import qualified Network.HTTP.Types.Method as H
-- Misc Types ------------------------------------------------------------------
type Rift = Atom -- Continuity number
type Life = Word -- Number of Azimoth key revs.
type Bloq = Atom -- TODO
type Oath = Atom -- Signature
-- Parsed URLs -----------------------------------------------------------------
2019-12-10 05:45:19 +03:00
type Host = Each Turf Ipv4
2019-07-21 07:36:25 +03:00
type Hart = (Bool, Maybe Atom, Host)
2019-07-22 21:10:27 +03:00
type Pork = (Maybe Knot, [Cord])
type Quay = [(Cord, Cord)]
2019-07-21 07:36:25 +03:00
data PUrl = PUrl Hart Pork Quay
2019-07-21 07:36:25 +03:00
deriving (Eq, Ord, Show)
deriveNoun ''PUrl
-- Dawn Records ----------------------------------------------------------------
2019-09-25 03:15:00 +03:00
padByteString :: BS.ByteString -> Int -> BS.ByteString
padByteString bs length | remaining > 0 = bs <> (BS.replicate remaining 0)
| otherwise = bs
where remaining = (length - (BS.length bs))
-- A Pass is the Atom concatenation of 'b', the public encryption key, and the
-- public authentication key. (see +pass-from-eth.)
data Pass = Pass { passSign :: Ed.PublicKey, passCrypt :: Ed.PublicKey }
deriving (Eq, Ord, Show)
2019-10-09 23:39:11 +03:00
passToBS :: Pass -> BS.ByteString
passToBS Pass{..} = C.singleton 'b' <>
(Ed.unPublicKey passSign) <>
(Ed.unPublicKey passCrypt)
2019-10-09 23:39:11 +03:00
instance ToNoun Pass where
toNoun = Atom . bytesAtom . passToBS
instance FromNoun Pass where
parseNoun n = named "Pass" $ do
2019-09-25 03:15:00 +03:00
MkBytes unpadded <- parseNoun n
let bs = padByteString unpadded 65
when ((C.head bs) /= 'b') $ do
fail "Expecting 'b' prefix in public key structure"
let removedPrefix = C.tail bs
let passSign = Ed.PublicKey (take 32 removedPrefix)
let passCrypt = Ed.PublicKey (drop 32 removedPrefix)
unless ((length $ Ed.unPublicKey passSign) == 32) $
error "Sign pubkey not 32 bytes"
unless ((length $ Ed.unPublicKey passCrypt) == 32) $
error "Crypt pubkey not 32 bytes"
2019-09-25 03:15:00 +03:00
pure $ Pass{..}
-- A Ring isn't the secret keys: it's the ByteString input which generates both
-- the public key and the secret key. A Ring is the concatenation of 'B', the
-- encryption key derivation seed, and the authentication key derivation
-- seed. These aren't actually private keys, but public/private keypairs which
-- can be derived from these seeds.
2019-10-09 23:39:11 +03:00
data Ring = Ring { ringSign :: BS.ByteString, ringCrypt :: BS.ByteString }
2019-09-26 01:16:48 +03:00
deriving (Eq)
2019-09-25 03:15:00 +03:00
instance ToNoun Ring where
toNoun Ring{..} =
Atom $ bytesAtom (C.singleton 'B' <> ringSign <> ringCrypt)
2019-09-25 03:15:00 +03:00
instance FromNoun Ring where
parseNoun n = named "Ring" $ do
MkBytes unpadded <- parseNoun n
let bs = padByteString unpadded 65
when ((C.head bs) /= 'B') $ do
fail "Expecting 'B' prefix in public key structure"
let removedPrefix = C.tail bs
let ringSign = (take 32 removedPrefix)
let ringCrypt = (drop 32 removedPrefix)
unless ((length ringSign) == 32) $
error "Sign seed not 32 bytes"
unless ((length ringCrypt) == 32) $
error "Crypt seed not 32 bytes"
2019-09-25 03:15:00 +03:00
pure $ Ring ringSign ringCrypt
2019-09-26 01:16:48 +03:00
instance Show Ring where
show r = "(Ring <<seed>> <<seed>>)"
data Seed = Seed
{ sShip :: Ship
, sLife :: Life
, sRing :: Ring
, sOath :: (Maybe Oath)
}
2019-09-25 03:15:00 +03:00
deriving (Eq, Show)
2021-06-03 02:04:45 +03:00
data Feed
= Feed0 Seed
| Feed1 [Seed]
deriving (Eq, Show)
--NOTE reify type environment
$(pure [])
instance ToNoun Feed where
toNoun = \case
Feed0 s -> toSeed s
Feed1 s -> C (C (A 1) (A 0)) $ toList s
where
toList :: [Seed] -> Noun
toList [] = A 0
toList (x:xs) = C (toSeed x) (toList xs)
toSeed = $(deriveToNounFunc ''Seed)
instance FromNoun Feed where
parseNoun = \case
(C (C (A 1) (A 0)) s) -> Feed1 <$> parseList s
n -> Feed0 <$> parseSeed n
where
parseList = \case
Atom 0 -> pure []
Atom _ -> fail "list terminated with non-null atom"
Cell l r -> (:) <$> parseSeed l <*> parseList r
parseSeed = $(deriveFromNounFunc ''Seed)
type Public = (Life, HoonMap Life Pass)
data Dnses = Dnses { dPri::Cord, dSec::Cord, dTer::Cord }
deriving (Eq, Ord, Show)
2019-09-21 02:10:03 +03:00
type EthAddr = Atom --Bytes -- 20 bytes
type ContNum = Word
data EthPoint = EthPoint
{ epOwn :: (EthAddr, EthAddr, EthAddr, EthAddr)
, epNet :: Maybe (Life, Pass, ContNum, (Bool, Ship), Maybe Ship)
, epKid :: Maybe (EthAddr, HoonSet Ship)
}
deriving (Eq, Show)
data Dawn = MkDawn
2021-06-03 02:04:45 +03:00
{ dFeed :: (Life, Feed)
, dSponsor :: [(Ship, EthPoint)]
, dCzar :: HoonMap Ship (Rift, Life, Pass)
2019-09-21 02:10:03 +03:00
, dTurf :: [Turf]
, dBloq :: Bloq
, dNode :: (Maybe PUrl)
}
deriving (Eq, Show)
deriveNoun ''Dnses
deriveNoun ''EthPoint
2019-07-21 07:36:25 +03:00
deriveNoun ''Seed
deriveNoun ''Dawn
2019-07-21 07:36:25 +03:00
-- HTTP ------------------------------------------------------------------------
2019-07-21 07:36:25 +03:00
type ServerId = Atom
data Address
= AIpv4 Ipv4
| AIpv6 Ipv6
| AAmes Ship
deriving (Eq, Ord, Show)
data HttpRequest = HttpRequest
{ reqMeth :: H.StdMethod
2019-07-22 21:10:27 +03:00
, reqUrl :: Cord
, reqHead :: [Header]
, reqBody :: Maybe File
}
deriving (Eq, Ord, Show)
2019-07-23 03:46:06 +03:00
data HttpServerReq = HttpServerReq
{ hsrSecure :: Bool
, hsrAddress :: Address
, hsrRequest :: HttpRequest
}
deriving (Eq, Ord, Show)
data HttpClientEv
2019-08-02 08:07:20 +03:00
= HttpClientEvReceive (KingId, ()) ServerId HttpEvent
| HttpClientEvBorn (KingId, ()) ()
| HttpClientEvCrud Path Noun
deriving (Eq, Ord, Show)
data HttpServerEv
2019-12-19 22:30:09 +03:00
= HttpServerEvRequest (ServId, UD, UD, ()) HttpServerReq
| HttpServerEvCancelRequest (ServId, UD, UD, ()) ()
| HttpServerEvRequestLocal (ServId, UD, UD, ()) HttpServerReq
| HttpServerEvLive (ServId, ()) Port (Maybe Port)
| HttpServerEvBorn (KingId, ()) ()
| HttpServerEvCrud Path Noun
deriving (Eq, Ord, Show)
2019-07-21 07:36:25 +03:00
deriveNoun ''Address
deriveNoun ''HttpClientEv
2019-07-23 03:46:06 +03:00
deriveNoun ''HttpRequest
deriveNoun ''HttpServerEv
2019-07-23 03:46:06 +03:00
deriveNoun ''HttpServerReq
2019-07-21 07:36:25 +03:00
-- Ames ------------------------------------------------------------------------
data AmesEv
= AmesEvHear () AmesDest Bytes
2019-12-10 05:45:19 +03:00
| AmesEvHole () AmesDest Bytes
| AmesEvCrud Path Noun
deriving (Eq, Ord, Show)
deriveNoun ''AmesEv
2019-07-21 07:36:25 +03:00
-- Arvo Events -----------------------------------------------------------------
newtype Entropy = Entropy { entropyBits :: Word512 }
deriving newtype (Eq, Ord, FromNoun, ToNoun)
instance Show Entropy where
show = const "\"ENTROPY (secret)\""
data ArvoEv
= ArvoEvWhom () Ship
| ArvoEvWack () Entropy
| ArvoEvWyrd () Vere
2020-12-19 04:00:56 +03:00
| ArvoEvCrud Path Noun
| ArvoEvTrim UD
| ArvoEvWhat [Noun]
| ArvoEvWhey ()
| ArvoEvVerb (Maybe Bool)
deriving (Eq, Ord, Show)
deriveNoun ''ArvoEv
2019-07-21 07:36:25 +03:00
-- Boat Events -----------------------------------------------------------------
data BoatEv
= BoatEvBoat () ()
| BoatEvCrud Path Noun
2019-07-21 07:36:25 +03:00
deriving (Eq, Ord, Show)
deriveNoun ''BoatEv
2019-07-21 07:36:25 +03:00
-- Timer Events ----------------------------------------------------------------
data BehnEv
= BehnEvWake () ()
| BehnEvBorn (KingId, ()) ()
| BehnEvCrud Path Noun
deriving (Eq, Ord, Show)
deriveNoun ''BehnEv
2019-07-21 07:36:25 +03:00
-- Newt Events -----------------------------------------------------------------
data NewtEv
2019-12-10 05:45:19 +03:00
= NewtEvBorn (KingId, ()) ()
| NewtEvCrud Path Noun
deriving (Eq, Ord, Show)
deriveNoun ''NewtEv
2019-07-21 07:36:25 +03:00
-- FileSystem Events -----------------------------------------------------------
data SyncEv
= SyncEvInto (Nullable (KingId, ())) Desk Bool [(Path, Maybe Mime)]
| SyncEvCrud Path Noun
deriving (Eq, Ord, Show)
deriveNoun ''SyncEv
2019-07-21 07:36:25 +03:00
-- Terminal Events -------------------------------------------------------------
data LegacyBootEvent
= Fake Ship
| Dawn Dawn
deriving (Eq, Show)
2019-07-21 07:36:25 +03:00
data ArrowKey = D | L | R | U
deriving (Eq, Ord, Show)
data Belt
= Aro ArrowKey
| Bac ()
| Ctl Cord
| Del ()
| Met Cord
| Ret ()
2019-07-21 07:36:25 +03:00
| Txt Tour
deriving (Eq, Ord, Show)
data TermEv
= TermEvBelt (UD, ()) Belt
| TermEvBlew (UD, ()) Word Word
| TermEvBoot (UD, ()) Bool LegacyBootEvent
| TermEvHail (UD, ()) ()
| TermEvCrud Path Noun
deriving (Eq, Show)
2019-07-21 07:36:25 +03:00
deriveNoun ''LegacyBootEvent
deriveNoun ''ArrowKey
deriveNoun ''Belt
deriveNoun ''TermEv
2019-07-21 07:36:25 +03:00
-- Events for Device Drivers ---------------------------------------------------
data BlipEv
= BlipEvAmes AmesEv
| BlipEvArvo ArvoEv
| BlipEvBehn BehnEv
| BlipEvBoat BoatEv
| BlipEvHttpClient HttpClientEv
| BlipEvHttpServer HttpServerEv
| BlipEvNewt NewtEv
| BlipEvSync SyncEv
| BlipEvTerm TermEv
deriving (Eq, Show)
deriveNoun ''BlipEv
2019-07-21 07:36:25 +03:00
-- The Main Event Type ---------------------------------------------------------
2019-07-21 07:36:25 +03:00
data Ev
= EvBlip BlipEv
deriving (Eq, Show)
2019-07-21 07:36:25 +03:00
instance ToNoun Ev where
toNoun = toNoun . \case
EvBlip v@BlipEvAmes{} -> reorgThroughNoun ("ames", v)
EvBlip v@BlipEvArvo{} -> reorgThroughNoun ("", v)
EvBlip v@BlipEvBehn{} -> reorgThroughNoun ("behn", v)
EvBlip v@BlipEvBoat{} -> reorgThroughNoun ("clay", v)
EvBlip v@BlipEvHttpClient{} -> reorgThroughNoun ("iris", v)
EvBlip v@BlipEvHttpServer{} -> reorgThroughNoun ("eyre", v)
EvBlip v@BlipEvNewt{} -> reorgThroughNoun ("ames", v)
EvBlip v@BlipEvSync{} -> reorgThroughNoun ("clay", v)
EvBlip v@BlipEvTerm{} -> reorgThroughNoun ("dill", v)
-- XX We really should check the first path element, but since this is used only
-- in the event browser, which otherwise is broken, I don't care right now.
instance FromNoun Ev where
parseNoun = parseNoun >=> \case
ReOrg _ s t p v -> fmap EvBlip $ parseNoun $ toNoun (s,t,p,v)
-- Short Event Names -----------------------------------------------------------
2019-09-18 07:41:31 +03:00
{-
In the case of the user hitting enter, the cause is technically a
terminal event, but we don't display any name because the cause is
really the user.
-}
getSpinnerNameForEvent :: Ev -> Maybe Text
getSpinnerNameForEvent = \case
2019-09-18 07:41:31 +03:00
EvBlip b -> case b of
BlipEvAmes _ -> Just "ames"
BlipEvArvo _ -> Just "arvo"
BlipEvBehn _ -> Just "behn"
BlipEvBoat _ -> Just "boat"
BlipEvHttpClient _ -> Just "iris"
BlipEvHttpServer _ -> Just "eyre"
BlipEvNewt _ -> Just "newt"
BlipEvSync _ -> Just "clay"
BlipEvTerm t | isRet t -> Nothing
BlipEvTerm t -> Just "term"
where
isRet (TermEvBelt _ (Ret ())) = True
isRet _ = False
2020-06-11 05:02:09 +03:00
summarizeEvent :: Ev -> Text
summarizeEvent ev =
fromNoun (toNoun ev) & \case
Nothing -> "//invalid %event"
Just (pax :: [Cord], tag :: Cord, val :: Noun) ->
"/" <> intercalate "/" (unCord <$> pax) <> " %" <> unCord tag