mirror of
https://github.com/ilyakooo0/urbit.git
synced 2025-01-01 19:46:36 +03:00
king: fix lane format; vere: don't crash on bad lane
This commit is contained in:
parent
f7697719fb
commit
ac00ea43f8
@ -26,6 +26,7 @@ import Urbit.Prelude
|
||||
|
||||
import Control.Monad.Fail (fail)
|
||||
import Data.Bits
|
||||
import Data.Serialize
|
||||
|
||||
import qualified Network.HTTP.Types.Method as H
|
||||
import qualified Urbit.Ob as Ob
|
||||
@ -185,14 +186,27 @@ type Galaxy = Patp Word8
|
||||
instance Integral a => Show (Patp a) where
|
||||
show = show . Ob.renderPatp . Ob.patp . fromIntegral . unPatp
|
||||
|
||||
data AmesAddress
|
||||
= AAIpv4 Ipv4 Port
|
||||
| AAVoid Void
|
||||
data AmesAddress = AAIpv4 Ipv4 Port
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
deriveNoun ''AmesAddress
|
||||
instance Serialize AmesAddress where
|
||||
get = AAIpv4 <$> (Ipv4 <$> getWord32le) <*> (Port <$> getWord16le)
|
||||
put (AAIpv4 (Ipv4 ip) (Port port)) = putWord32le ip >> putWord16le port
|
||||
|
||||
type AmesDest = Each Galaxy (Jammed AmesAddress)
|
||||
instance FromNoun AmesAddress where
|
||||
parseNoun = named "AmesAddress" . \case
|
||||
A (atomBytes -> bs)
|
||||
-- Atoms lose leading 0s, but since lsb, these become trailing NULs
|
||||
| length bs <= 6 -> case decode $ bs <> replicate (6 - length bs) 0 of
|
||||
Right aa -> pure aa
|
||||
Left msg -> fail msg
|
||||
| otherwise -> fail ("putative address " <> show bs <> " too long")
|
||||
C{} -> fail "unexpected cell in ames address"
|
||||
|
||||
instance ToNoun AmesAddress where
|
||||
toNoun = A . bytesAtom . encode
|
||||
|
||||
type AmesDest = Each Galaxy AmesAddress
|
||||
|
||||
|
||||
-- Path+Tagged Restructuring ---------------------------------------------------
|
||||
|
@ -80,15 +80,13 @@ modeAddress = \case
|
||||
|
||||
okFakeAddr :: AmesDest -> Bool
|
||||
okFakeAddr = \case
|
||||
EachYes _ -> True
|
||||
EachNo (Jammed (AAIpv4 (Ipv4 a) _)) -> a == localhost
|
||||
EachNo (Jammed (AAVoid v )) -> absurd v
|
||||
EachYes _ -> True
|
||||
EachNo (AAIpv4 (Ipv4 a) _) -> a == localhost
|
||||
|
||||
localAddr :: NetworkMode -> AmesDest -> SockAddr
|
||||
localAddr mode = \case
|
||||
EachYes g -> SockAddrInet (galaxyPort mode g) localhost
|
||||
EachNo (Jammed (AAIpv4 _ p)) -> SockAddrInet (fromIntegral p) localhost
|
||||
EachNo (Jammed (AAVoid v )) -> absurd v
|
||||
EachYes g -> SockAddrInet (galaxyPort mode g) localhost
|
||||
EachNo (AAIpv4 _ p) -> SockAddrInet (fromIntegral p) localhost
|
||||
|
||||
bornEv :: KingId -> Ev
|
||||
bornEv inst = EvBlip $ BlipEvNewt $ NewtEvBorn (fromIntegral inst, ()) ()
|
||||
@ -98,7 +96,7 @@ hearEv p a bs =
|
||||
EvBlip $ BlipEvAmes $ AmesEvHear () (ipDest p a) (MkBytes bs)
|
||||
|
||||
ipDest :: PortNumber -> HostAddress -> AmesDest
|
||||
ipDest p a = EachNo $ Jammed $ AAIpv4 (Ipv4 a) (fromIntegral p)
|
||||
ipDest p a = EachNo $ AAIpv4 (Ipv4 a) (fromIntegral p)
|
||||
|
||||
|
||||
--------------------------------------------------------------------------------
|
||||
@ -367,5 +365,4 @@ ames env who isFake stat scry enqueueEv stderr = (initialEvents, runAmes)
|
||||
-> RIO e (Maybe [AmesDest])
|
||||
scryLane ship = scryNow scry "ax" "" ["peers", tshow ship, "forward-lane"]
|
||||
|
||||
ipv4Addr (Jammed (AAVoid v )) = absurd v
|
||||
ipv4Addr (Jammed (AAIpv4 a p)) = SockAddrInet (fromIntegral p) (unIpv4 a)
|
||||
ipv4Addr (AAIpv4 a p) = SockAddrInet (fromIntegral p) (unIpv4 a)
|
||||
|
@ -15,6 +15,9 @@ import Urbit.Noun.Time
|
||||
import Urbit.Prelude
|
||||
import Urbit.Vere.Pier.Types
|
||||
|
||||
import System.IO.Unsafe
|
||||
import Data.Serialize
|
||||
|
||||
import Control.Concurrent (runInBoundThread, threadDelay)
|
||||
import Data.LargeWord (LargeKey(..))
|
||||
import GHC.Natural (Natural)
|
||||
|
@ -494,7 +494,7 @@ instance Show BigTape where
|
||||
-- Bytes -----------------------------------------------------------------------
|
||||
|
||||
newtype Bytes = MkBytes { unBytes :: ByteString }
|
||||
deriving newtype (Eq, Ord, Show)
|
||||
deriving newtype (Eq, Ord, Show, IsString)
|
||||
|
||||
instance ToNoun Bytes where
|
||||
toNoun = Atom . bytesAtom . unBytes
|
||||
|
@ -398,14 +398,17 @@ _ames_send(u3_pact* pac_u)
|
||||
}
|
||||
}
|
||||
|
||||
/* u3_ames_decode_lane(): deserialize noun to lane
|
||||
/* u3_ames_decode_lane(): deserialize noun to lane; 0.0.0.0:0 if invalid
|
||||
*/
|
||||
u3_lane
|
||||
u3_ames_decode_lane(u3_atom lan) {
|
||||
u3_lane lan_u;
|
||||
c3_d lan_d;
|
||||
|
||||
c3_assert( c3y == u3r_safe_chub(lan, &lan_d) );
|
||||
if ( c3n == u3r_safe_chub(lan, &lan_d) || (lan_d >> 48) != 0 ) {
|
||||
return (u3_lane){0, 0};
|
||||
}
|
||||
|
||||
u3z(lan);
|
||||
|
||||
lan_u.pip_w = (c3_w)lan_d;
|
||||
@ -727,6 +730,11 @@ _ames_ef_send(u3_ames* sam_u, u3_noun lan, u3_noun pac)
|
||||
if ( (c3n == u3_Host.ops_u.net) && (0x7f000001 != lan_u.pip_w) ) {
|
||||
_ames_pact_free(pac_u);
|
||||
}
|
||||
// if the lane is uninterpretable, silently drop the packet
|
||||
//
|
||||
else if ( 0 == lan_u.por_s ) {
|
||||
_ames_pact_free(pac_u);
|
||||
}
|
||||
// otherwise, mutate destination and send packet
|
||||
//
|
||||
else {
|
||||
|
Loading…
Reference in New Issue
Block a user