From ac00ea43f8c318996a6ed12135e254cfe302e5a0 Mon Sep 17 00:00:00 2001 From: pilfer-pandex <47340789+pilfer-pandex@users.noreply.github.com> Date: Tue, 2 Feb 2021 10:54:07 -0800 Subject: [PATCH 1/5] king: fix lane format; vere: don't crash on bad lane --- pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs | 24 +++++++++++++++---- pkg/hs/urbit-king/lib/Urbit/Vere/Ames.hs | 15 +++++------- pkg/hs/urbit-king/test/ArvoTests.hs | 3 +++ .../urbit-noun/lib/Urbit/Noun/Conversions.hs | 2 +- pkg/urbit/vere/io/ames.c | 12 ++++++++-- 5 files changed, 39 insertions(+), 17 deletions(-) diff --git a/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs b/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs index d91362c24..3f73bee61 100644 --- a/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs +++ b/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs @@ -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 --------------------------------------------------- diff --git a/pkg/hs/urbit-king/lib/Urbit/Vere/Ames.hs b/pkg/hs/urbit-king/lib/Urbit/Vere/Ames.hs index 7efea95f7..af5b9de76 100644 --- a/pkg/hs/urbit-king/lib/Urbit/Vere/Ames.hs +++ b/pkg/hs/urbit-king/lib/Urbit/Vere/Ames.hs @@ -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) diff --git a/pkg/hs/urbit-king/test/ArvoTests.hs b/pkg/hs/urbit-king/test/ArvoTests.hs index bdd87ff3e..5ac04c1d5 100644 --- a/pkg/hs/urbit-king/test/ArvoTests.hs +++ b/pkg/hs/urbit-king/test/ArvoTests.hs @@ -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) diff --git a/pkg/hs/urbit-noun/lib/Urbit/Noun/Conversions.hs b/pkg/hs/urbit-noun/lib/Urbit/Noun/Conversions.hs index b8104a77a..13bc39419 100644 --- a/pkg/hs/urbit-noun/lib/Urbit/Noun/Conversions.hs +++ b/pkg/hs/urbit-noun/lib/Urbit/Noun/Conversions.hs @@ -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 diff --git a/pkg/urbit/vere/io/ames.c b/pkg/urbit/vere/io/ames.c index 8c658afcf..a2154fd90 100644 --- a/pkg/urbit/vere/io/ames.c +++ b/pkg/urbit/vere/io/ames.c @@ -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 { From e70fa2629dabd6f182de0ddf4b38fe37592b967a Mon Sep 17 00:00:00 2001 From: pilfer-pandex <47340789+pilfer-pandex@users.noreply.github.com> Date: Tue, 2 Feb 2021 15:58:30 -0800 Subject: [PATCH 2/5] king: error message for lock file --- pkg/hs/urbit-king/lib/Urbit/Vere/LockFile.hs | 27 ++++++++++++++++---- 1 file changed, 22 insertions(+), 5 deletions(-) diff --git a/pkg/hs/urbit-king/lib/Urbit/Vere/LockFile.hs b/pkg/hs/urbit-king/lib/Urbit/Vere/LockFile.hs index aeaa8f325..c1aef5d45 100644 --- a/pkg/hs/urbit-king/lib/Urbit/Vere/LockFile.hs +++ b/pkg/hs/urbit-king/lib/Urbit/Vere/LockFile.hs @@ -6,25 +6,42 @@ module Urbit.Vere.LockFile (lockFile) where import Urbit.Prelude +import Urbit.King.App.Class + import Data.Default (def) import RIO.Directory (createDirectoryIfMissing) import System.IO.LockFile.Internal (LockingParameters(..), RetryStrategy(..), - lock, unlock) + LockingException(..), lock, unlock) -------------------------------------------------------------------------------- -lockFile :: HasLogFunc e => FilePath -> RAcquire e () +lockFile :: (HasLogFunc e, HasStderrLogFunc e) => FilePath -> RAcquire e () lockFile pax = void $ mkRAcquire start stop where fil = pax <> "/.vere.lock" stop handle = do - logInfo $ display @Text $ ("Releasing lock file: " <> pack fil) - io $ unlock fil handle + logInfo $ display @Text $ ("Releasing lock file: " <> pack fil) + io $ unlock fil handle params = def { retryToAcquireLock = No } start = do createDirectoryIfMissing True pax logInfo $ display @Text $ ("Taking lock file: " <> pack fil) - io (lock params fil) + handle failure $ io (lock params fil) + + failure (e :: LockingException) = do + logStderr $ logError $ display @Text $ + "Cannot acquire lock file " <> pack fil <> "." + logStderr $ logError $ + "Please make sure there are no other instances of this ship running, " + <> "then try again." + logStderr $ logError $ + "If you are sure, you can delete the file and try again." + throwIO e + +logStderr :: HasStderrLogFunc e => RIO LogFunc a -> RIO e a +logStderr action = do + logFunc <- view stderrLogFuncL + runRIO logFunc action From b9cc2edede743dac7c6dedd87965b050bea628d0 Mon Sep 17 00:00:00 2001 From: pilfer-pandex <47340789+pilfer-pandex@users.noreply.github.com> Date: Tue, 2 Feb 2021 15:59:36 -0800 Subject: [PATCH 3/5] king: version number 1.1.1 --- pkg/hs/urbit-king/package.yaml | 2 +- pkg/urbit/version | 2 +- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/pkg/hs/urbit-king/package.yaml b/pkg/hs/urbit-king/package.yaml index 647dda006..1c3a2adb7 100644 --- a/pkg/hs/urbit-king/package.yaml +++ b/pkg/hs/urbit-king/package.yaml @@ -1,5 +1,5 @@ name: urbit-king -version: 1.1 +version: 1.1.1 license: MIT license-file: LICENSE data-files: diff --git a/pkg/urbit/version b/pkg/urbit/version index b123147e2..8cfbc905b 100644 --- a/pkg/urbit/version +++ b/pkg/urbit/version @@ -1 +1 @@ -1.1 \ No newline at end of file +1.1.1 \ No newline at end of file From d625a0e5edbab58bf80a0ebf4a1fa83fe587137c Mon Sep 17 00:00:00 2001 From: pilfer-pandex <47340789+pilfer-pandex@users.noreply.github.com> Date: Wed, 3 Feb 2021 14:50:23 -0800 Subject: [PATCH 4/5] king: address joe and ted --- pkg/hs/urbit-king/package.yaml | 2 +- pkg/urbit/vere/io/ames.c | 3 +++ pkg/urbit/version | 2 +- 3 files changed, 5 insertions(+), 2 deletions(-) diff --git a/pkg/hs/urbit-king/package.yaml b/pkg/hs/urbit-king/package.yaml index 1c3a2adb7..1493ceb49 100644 --- a/pkg/hs/urbit-king/package.yaml +++ b/pkg/hs/urbit-king/package.yaml @@ -1,5 +1,5 @@ name: urbit-king -version: 1.1.1 +version: 1.2 license: MIT license-file: LICENSE data-files: diff --git a/pkg/urbit/vere/io/ames.c b/pkg/urbit/vere/io/ames.c index a2154fd90..64cee5fce 100644 --- a/pkg/urbit/vere/io/ames.c +++ b/pkg/urbit/vere/io/ames.c @@ -733,6 +733,9 @@ _ames_ef_send(u3_ames* sam_u, u3_noun lan, u3_noun pac) // if the lane is uninterpretable, silently drop the packet // else if ( 0 == lan_u.por_s ) { + if ( u3C.wag_w & u3o_verbose ) { + u3l_log("ames: inscrutable lane\n"); + } _ames_pact_free(pac_u); } // otherwise, mutate destination and send packet diff --git a/pkg/urbit/version b/pkg/urbit/version index 8cfbc905b..ea710abb9 100644 --- a/pkg/urbit/version +++ b/pkg/urbit/version @@ -1 +1 @@ -1.1.1 \ No newline at end of file +1.2 \ No newline at end of file From c9c11837b803cfa0c1db7aaded614d45f7de3bea Mon Sep 17 00:00:00 2001 From: pilfer-pandex <47340789+pilfer-pandex@users.noreply.github.com> Date: Wed, 3 Feb 2021 15:26:19 -0800 Subject: [PATCH 5/5] king: fix bug Show Ipv4 --- pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs b/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs index 3f73bee61..cb30b0196 100644 --- a/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs +++ b/pkg/hs/urbit-king/lib/Urbit/Arvo/Common.hs @@ -172,9 +172,9 @@ newtype Ipv4 = Ipv4 { unIpv4 :: Word32 } instance Show Ipv4 where show (Ipv4 i) = - show ((shiftL i 24) .&. 0xff) ++ "." ++ - show ((shiftL i 16) .&. 0xff) ++ "." ++ - show ((shiftL i 8) .&. 0xff) ++ "." ++ + show ((shiftR i 24) .&. 0xff) ++ "." ++ + show ((shiftR i 16) .&. 0xff) ++ "." ++ + show ((shiftR i 8) .&. 0xff) ++ "." ++ show (i .&. 0xff) -- @is