mirror of
https://github.com/ilyakooo0/urbit.git
synced 2024-12-15 01:52:42 +03:00
Merge branch 'release/next-vere' into jb/slab
* release/next-vere: (23 commits) kh: abolish unicode syntax in favor of ascii vere: use cue/test handles for repeated packet parsing ur: adds missing serial.h include u3: updates u3s_cue_xeno() to return error, not bail on oversized atoms u3: factors atoms/backrefs back into u3s_cue_xeno() u3: renames u3s_cue_sill* to u3s_cue_xeno* u3: removes u3s_cue_xeno() u3: removes unused atom measurement function in urth.c vere: use u3s_cue_sill() for ivory pill vere: use u3s_cue_sill for ipc $plea's serf: use u3s_cue_sill() for ipc $writ's u3: use u3s_cue_sill_with() in u3u_uncram() u3: adds u3s_cue_fill and handle-based api u3: factors atoms/backrefs out of u3s_cue_xeno u3: refactors u3s_cue_bytes() to use road-stack api ur: removes unused variables in tests ur: cleans up ur_bsr_log() ur: cleans up ur_met(), atom measurement ur: refactors unsafe jam into a handle-based api ur: adds walk_fore variant with a handle-based api for repeated traversal ...
This commit is contained in:
commit
854279772a
@ -79,61 +79,61 @@ data Mode = Wide | Tall
|
|||||||
|
|
||||||
type Parser = StateT Mode (Parsec Void Text)
|
type Parser = StateT Mode (Parsec Void Text)
|
||||||
|
|
||||||
withLocalState ∷ Monad m => s → StateT s m a → StateT s m a
|
withLocalState :: Monad m => s -> StateT s m a -> StateT s m a
|
||||||
withLocalState val x = do { old <- get; put val; x <* put old }
|
withLocalState val x = do { old <- get; put val; x <* put old }
|
||||||
|
|
||||||
inWideMode ∷ Parser a → Parser a
|
inWideMode :: Parser a -> Parser a
|
||||||
inWideMode = withLocalState Wide
|
inWideMode = withLocalState Wide
|
||||||
|
|
||||||
ace, pal, par ∷ Parser ()
|
ace, pal, par :: Parser ()
|
||||||
ace = void (char ' ')
|
ace = void (char ' ')
|
||||||
pal = void (char '(')
|
pal = void (char '(')
|
||||||
par = void (char ')')
|
par = void (char ')')
|
||||||
|
|
||||||
-- Simple Lexers ---------------------------------------------------------------
|
-- Simple Lexers ---------------------------------------------------------------
|
||||||
|
|
||||||
gap ∷ Parser ()
|
gap :: Parser ()
|
||||||
gap = choice [ char ' ' >> void (some spaceChar)
|
gap = choice [ char ' ' >> void (some spaceChar)
|
||||||
, newline >> void (many spaceChar)
|
, newline >> void (many spaceChar)
|
||||||
]
|
]
|
||||||
|
|
||||||
whitespace ∷ Parser ()
|
whitespace :: Parser ()
|
||||||
whitespace = ace <|> void gap
|
whitespace = ace <|> void gap
|
||||||
|
|
||||||
|
|
||||||
-- Literals --------------------------------------------------------------------
|
-- Literals --------------------------------------------------------------------
|
||||||
|
|
||||||
alpha ∷ Parser Char
|
alpha :: Parser Char
|
||||||
alpha = oneOf (['a'..'z'] ++ ['A'..'Z'])
|
alpha = oneOf (['a'..'z'] ++ ['A'..'Z'])
|
||||||
|
|
||||||
sym ∷ Parser Sym
|
sym :: Parser Sym
|
||||||
sym = bucSym <|> pack <$> some alpha
|
sym = bucSym <|> pack <$> some alpha
|
||||||
where bucSym = char '$' *> pure ""
|
where bucSym = char '$' *> pure ""
|
||||||
|
|
||||||
atom ∷ Parser Nat
|
atom :: Parser Nat
|
||||||
atom = do
|
atom = do
|
||||||
init ← some digitChar
|
init <- some digitChar
|
||||||
rest ← many (char '.' *> some digitChar)
|
rest <- many (char '.' *> some digitChar)
|
||||||
guard True -- TODO Validate '.'s
|
guard True -- TODO Validate '.'s
|
||||||
pure (Prelude.read $ concat $ init:rest)
|
pure (Prelude.read $ concat $ init:rest)
|
||||||
|
|
||||||
nat ∷ Parser Nat
|
nat :: Parser Nat
|
||||||
nat = Prelude.read <$> some digitChar
|
nat = Prelude.read <$> some digitChar
|
||||||
|
|
||||||
tape ∷ Parser Text
|
tape :: Parser Text
|
||||||
tape = do
|
tape = do
|
||||||
between (char '"') (char '"') $
|
between (char '"') (char '"') $
|
||||||
pack <$> many (label "tape char" (anySingleBut '"'))
|
pack <$> many (label "tape char" (anySingleBut '"'))
|
||||||
|
|
||||||
cord ∷ Parser Text
|
cord :: Parser Text
|
||||||
cord = do
|
cord = do
|
||||||
between (char '\'') (char '\'') $
|
between (char '\'') (char '\'') $
|
||||||
pack <$> many (label "cord char" (anySingleBut '\''))
|
pack <$> many (label "cord char" (anySingleBut '\''))
|
||||||
|
|
||||||
tag ∷ Parser Text
|
tag :: Parser Text
|
||||||
tag = try (char '%' >> sym)
|
tag = try (char '%' >> sym)
|
||||||
|
|
||||||
literal ∷ Parser CST
|
literal :: Parser CST
|
||||||
literal = choice
|
literal = choice
|
||||||
[ Yes <$ string "%.y"
|
[ Yes <$ string "%.y"
|
||||||
, No <$ string "%.n"
|
, No <$ string "%.n"
|
||||||
@ -156,48 +156,48 @@ literal = choice
|
|||||||
- accept the `tall` form or:
|
- accept the `tall` form or:
|
||||||
- swich to `Wide` mode and then accept the wide form.
|
- swich to `Wide` mode and then accept the wide form.
|
||||||
-}
|
-}
|
||||||
parseRune ∷ Parser a → Parser a → Parser a
|
parseRune :: Parser a -> Parser a -> Parser a
|
||||||
parseRune tall wide = get >>= \case
|
parseRune tall wide = get >>= \case
|
||||||
Wide → wide
|
Wide -> wide
|
||||||
Tall → tall <|> inWideMode wide
|
Tall -> tall <|> inWideMode wide
|
||||||
|
|
||||||
rune0 ∷ a → Parser a
|
rune0 :: a -> Parser a
|
||||||
rune0 = pure
|
rune0 = pure
|
||||||
|
|
||||||
rune1 ∷ (a→b) → Parser a → Parser b
|
rune1 :: (a->b) -> Parser a -> Parser b
|
||||||
rune1 node x = parseRune tall wide
|
rune1 node x = parseRune tall wide
|
||||||
where tall = do gap; p←x; pure (node p)
|
where tall = do gap; p<-x; pure (node p)
|
||||||
wide = do pal; p←x; par; pure (node p)
|
wide = do pal; p<-x; par; pure (node p)
|
||||||
|
|
||||||
rune2 ∷ (a→b→c) → Parser a → Parser b → Parser c
|
rune2 :: (a->b->c) -> Parser a -> Parser b -> Parser c
|
||||||
rune2 node x y = parseRune tall wide
|
rune2 node x y = parseRune tall wide
|
||||||
where tall = do gap; p←x; gap; q←y; pure (node p q)
|
where tall = do gap; p<-x; gap; q<-y; pure (node p q)
|
||||||
wide = do pal; p←x; ace; q←y; par; pure (node p q)
|
wide = do pal; p<-x; ace; q<-y; par; pure (node p q)
|
||||||
|
|
||||||
rune3 ∷ (a→b→c→d) → Parser a → Parser b → Parser c → Parser d
|
rune3 :: (a->b->c->d) -> Parser a -> Parser b -> Parser c -> Parser d
|
||||||
rune3 node x y z = parseRune tall wide
|
rune3 node x y z = parseRune tall wide
|
||||||
where tall = do gap; p←x; gap; q←y; gap; r←z; pure (node p q r)
|
where tall = do gap; p<-x; gap; q<-y; gap; r<-z; pure (node p q r)
|
||||||
wide = do pal; p←x; ace; q←y; ace; r←z; par; pure (node p q r)
|
wide = do pal; p<-x; ace; q<-y; ace; r<-z; par; pure (node p q r)
|
||||||
|
|
||||||
rune4 ∷ (a→b→c→d→e) → Parser a → Parser b → Parser c → Parser d → Parser e
|
rune4 :: (a->b->c->d->e) -> Parser a -> Parser b -> Parser c -> Parser d -> Parser e
|
||||||
rune4 node x y z g = parseRune tall wide
|
rune4 node x y z g = parseRune tall wide
|
||||||
where tall = do gap; p←x; gap; q←y; gap; r←z; gap; s←g; pure (node p q r s)
|
where tall = do gap; p<-x; gap; q<-y; gap; r<-z; gap; s<-g; pure (node p q r s)
|
||||||
wide = do pal; p←x; ace; q←y; ace; r←z; ace; s←g; pure (node p q r s)
|
wide = do pal; p<-x; ace; q<-y; ace; r<-z; ace; s<-g; pure (node p q r s)
|
||||||
|
|
||||||
runeN ∷ ([a]→b) → Parser a → Parser b
|
runeN :: ([a]->b) -> Parser a -> Parser b
|
||||||
runeN node elem = node <$> parseRune tall wide
|
runeN node elem = node <$> parseRune tall wide
|
||||||
where tall = gap >> elems
|
where tall = gap >> elems
|
||||||
where elems = term <|> elemAnd
|
where elems = term <|> elemAnd
|
||||||
elemAnd = do x ← elem; gap; xs ← elems; pure (x:xs)
|
elemAnd = do x <- elem; gap; xs <- elems; pure (x:xs)
|
||||||
term = string "==" *> pure []
|
term = string "==" *> pure []
|
||||||
wide = pal *> option [] elems <* par
|
wide = pal *> option [] elems <* par
|
||||||
where elems = (:) <$> elem <*> many (ace >> elem)
|
where elems = (:) <$> elem <*> many (ace >> elem)
|
||||||
|
|
||||||
runeNE ∷ (NonEmpty a → b) → Parser a → Parser b
|
runeNE :: (NonEmpty a -> b) -> Parser a -> Parser b
|
||||||
runeNE node elem = node <$> parseRune tall wide
|
runeNE node elem = node <$> parseRune tall wide
|
||||||
where tall = do
|
where tall = do
|
||||||
let elems = term <|> elemAnd
|
let elems = term <|> elemAnd
|
||||||
elemAnd = do x ← elem; gap; xs ← elems; pure (x:xs)
|
elemAnd = do x <- elem; gap; xs <- elems; pure (x:xs)
|
||||||
term = string "==" *> pure []
|
term = string "==" *> pure []
|
||||||
fst <- gap *> elem
|
fst <- gap *> elem
|
||||||
rst <- gap *> elems
|
rst <- gap *> elems
|
||||||
@ -206,36 +206,36 @@ runeNE node elem = node <$> parseRune tall wide
|
|||||||
|
|
||||||
-- Irregular Syntax ------------------------------------------------------------
|
-- Irregular Syntax ------------------------------------------------------------
|
||||||
|
|
||||||
inc ∷ Parser CST -- +(3)
|
inc :: Parser CST -- +(3)
|
||||||
inc = do
|
inc = do
|
||||||
string "+("
|
string "+("
|
||||||
h ← cst
|
h <- cst
|
||||||
char ')'
|
char ')'
|
||||||
pure h
|
pure h
|
||||||
|
|
||||||
equals ∷ Parser (CST, CST) -- =(3 4)
|
equals :: Parser (CST, CST) -- =(3 4)
|
||||||
equals = do
|
equals = do
|
||||||
string "=("
|
string "=("
|
||||||
x ← cst
|
x <- cst
|
||||||
ace
|
ace
|
||||||
y ← cst
|
y <- cst
|
||||||
char ')'
|
char ')'
|
||||||
pure (x, y)
|
pure (x, y)
|
||||||
|
|
||||||
tuple ∷ ∀a. Parser a → Parser [a]
|
tuple :: forall a. Parser a -> Parser [a]
|
||||||
tuple p = char '[' >> elems
|
tuple p = char '[' >> elems
|
||||||
where
|
where
|
||||||
xs ∷ Parser [a]
|
xs :: Parser [a]
|
||||||
xs = do { x ← p; (x:) <$> tail }
|
xs = do { x <- p; (x:) <$> tail }
|
||||||
|
|
||||||
tail ∷ Parser [a]
|
tail :: Parser [a]
|
||||||
tail = (pure [] <* char ']')
|
tail = (pure [] <* char ']')
|
||||||
<|> (ace >> elems)
|
<|> (ace >> elems)
|
||||||
|
|
||||||
elems ∷ Parser [a]
|
elems :: Parser [a]
|
||||||
elems = (pure [] <* char ']') <|> xs
|
elems = (pure [] <* char ']') <|> xs
|
||||||
|
|
||||||
appIrr ∷ Parser CST
|
appIrr :: Parser CST
|
||||||
appIrr = do
|
appIrr = do
|
||||||
char '('
|
char '('
|
||||||
x <- cst
|
x <- cst
|
||||||
@ -244,7 +244,7 @@ appIrr = do
|
|||||||
char ')'
|
char ')'
|
||||||
pure (AppIrr x y)
|
pure (AppIrr x y)
|
||||||
|
|
||||||
irregular ∷ Parser CST
|
irregular :: Parser CST
|
||||||
irregular =
|
irregular =
|
||||||
inWideMode $
|
inWideMode $
|
||||||
choice [ Tupl <$> tuple cst
|
choice [ Tupl <$> tuple cst
|
||||||
@ -255,14 +255,14 @@ irregular =
|
|||||||
|
|
||||||
-- Runes -----------------------------------------------------------------------
|
-- Runes -----------------------------------------------------------------------
|
||||||
|
|
||||||
pat ∷ Parser Pat
|
pat :: Parser Pat
|
||||||
pat = choice [ PatTag <$> tag
|
pat = choice [ PatTag <$> tag
|
||||||
, char '*' $> PatTar
|
, char '*' $> PatTar
|
||||||
]
|
]
|
||||||
|
|
||||||
cases ∷ Parser [(Pat, CST)]
|
cases :: Parser [(Pat, CST)]
|
||||||
cases = do
|
cases = do
|
||||||
mode ← get
|
mode <- get
|
||||||
guard (mode == Tall)
|
guard (mode == Tall)
|
||||||
end <|> lop
|
end <|> lop
|
||||||
where
|
where
|
||||||
@ -270,9 +270,9 @@ cases = do
|
|||||||
end = string "==" $> []
|
end = string "==" $> []
|
||||||
lop = do { p <- pat; gap; b <- cst; gap; ((p,b):) <$> goo }
|
lop = do { p <- pat; gap; b <- cst; gap; ((p,b):) <$> goo }
|
||||||
|
|
||||||
wutHep ∷ Parser CST
|
wutHep :: Parser CST
|
||||||
wutHep = do
|
wutHep = do
|
||||||
mode ← get
|
mode <- get
|
||||||
guard (mode == Tall)
|
guard (mode == Tall)
|
||||||
gap
|
gap
|
||||||
ex <- cst
|
ex <- cst
|
||||||
@ -280,15 +280,15 @@ wutHep = do
|
|||||||
cs <- cases
|
cs <- cases
|
||||||
pure (WutHep ex cs)
|
pure (WutHep ex cs)
|
||||||
|
|
||||||
barCen ∷ Parser CST
|
barCen :: Parser CST
|
||||||
barCen = do
|
barCen = do
|
||||||
mode ← get
|
mode <- get
|
||||||
guard (mode == Tall)
|
guard (mode == Tall)
|
||||||
gap
|
gap
|
||||||
cs <- cases
|
cs <- cases
|
||||||
pure (BarCen cs)
|
pure (BarCen cs)
|
||||||
|
|
||||||
rune ∷ Parser CST
|
rune :: Parser CST
|
||||||
rune = runeSwitch [ ("|=", rune2 BarTis sym cst)
|
rune = runeSwitch [ ("|=", rune2 BarTis sym cst)
|
||||||
, ("|-", rune4 BarHep sym sym cst cst)
|
, ("|-", rune4 BarHep sym sym cst cst)
|
||||||
, (":-", rune2 ColHep cst cst)
|
, (":-", rune2 ColHep cst cst)
|
||||||
@ -313,13 +313,13 @@ rune = runeSwitch [ ("|=", rune2 BarTis sym cst)
|
|||||||
, ("~/", rune2 SigFas cst cst)
|
, ("~/", rune2 SigFas cst cst)
|
||||||
]
|
]
|
||||||
|
|
||||||
runeSwitch ∷ [(Text, Parser a)] → Parser a
|
runeSwitch :: [(Text, Parser a)] -> Parser a
|
||||||
runeSwitch = choice . fmap (\(s, p) → string s *> p)
|
runeSwitch = choice . fmap (\(s, p) -> string s *> p)
|
||||||
|
|
||||||
|
|
||||||
-- CST Parser ------------------------------------------------------------------
|
-- CST Parser ------------------------------------------------------------------
|
||||||
|
|
||||||
cst ∷ Parser CST
|
cst :: Parser CST
|
||||||
cst = irregular <|> rune <|> literal
|
cst = irregular <|> rune <|> literal
|
||||||
|
|
||||||
|
|
||||||
@ -327,19 +327,19 @@ cst = irregular <|> rune <|> literal
|
|||||||
|
|
||||||
hoonFile = do
|
hoonFile = do
|
||||||
option () whitespace
|
option () whitespace
|
||||||
h ← cst
|
h <- cst
|
||||||
option () whitespace
|
option () whitespace
|
||||||
eof
|
eof
|
||||||
pure h
|
pure h
|
||||||
|
|
||||||
parse ∷ Text → Either Text CST
|
parse :: Text -> Either Text CST
|
||||||
parse txt =
|
parse txt =
|
||||||
runParser (evalStateT hoonFile Tall) "stdin" txt & \case
|
runParser (evalStateT hoonFile Tall) "stdin" txt & \case
|
||||||
Left e → Left (pack $ errorBundlePretty e)
|
Left e -> Left (pack $ errorBundlePretty e)
|
||||||
Right x → pure x
|
Right x -> pure x
|
||||||
|
|
||||||
parseHoonTest ∷ Text → IO ()
|
parseHoonTest :: Text -> IO ()
|
||||||
parseHoonTest = parseTest (evalStateT hoonFile Tall)
|
parseHoonTest = parseTest (evalStateT hoonFile Tall)
|
||||||
|
|
||||||
main ∷ IO ()
|
main :: IO ()
|
||||||
main = (head <$> getArgs) >>= parseHoonTest
|
main = (head <$> getArgs) >>= parseHoonTest
|
||||||
|
@ -300,7 +300,7 @@ streamEvents log first = do
|
|||||||
for_ batch yield
|
for_ batch yield
|
||||||
streamEvents log (first + word (length batch))
|
streamEvents log (first + word (length batch))
|
||||||
|
|
||||||
streamEffectsRows :: ∀e. HasLogFunc e
|
streamEffectsRows :: forall e. HasLogFunc e
|
||||||
=> EventLog -> Word64
|
=> EventLog -> Word64
|
||||||
-> ConduitT () (Word64, ByteString) (RIO e) ()
|
-> ConduitT () (Word64, ByteString) (RIO e) ()
|
||||||
streamEffectsRows log = go
|
streamEffectsRows log = go
|
||||||
@ -352,7 +352,7 @@ readBatch log first = start
|
|||||||
{-|
|
{-|
|
||||||
Read 1000 rows from the database, starting from key `first`.
|
Read 1000 rows from the database, starting from key `first`.
|
||||||
-}
|
-}
|
||||||
readRowsBatch :: ∀e. HasLogFunc e
|
readRowsBatch :: forall e. HasLogFunc e
|
||||||
=> Env -> Dbi -> Word64 -> RIO e (V.Vector (Word64, ByteString))
|
=> Env -> Dbi -> Word64 -> RIO e (V.Vector (Word64, ByteString))
|
||||||
readRowsBatch env dbi first = readRows
|
readRowsBatch env dbi first = readRows
|
||||||
where
|
where
|
||||||
|
@ -835,7 +835,7 @@ runMultipleShips ships = do
|
|||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
connTerm :: ∀e. HasLogFunc e => FilePath -> RIO e ()
|
connTerm :: forall e. HasLogFunc e => FilePath -> RIO e ()
|
||||||
connTerm = Term.runTerminalClient
|
connTerm = Term.runTerminalClient
|
||||||
|
|
||||||
|
|
||||||
|
@ -169,7 +169,7 @@ streamEvents log first = do
|
|||||||
for_ batch yield
|
for_ batch yield
|
||||||
streamEvents log (first + word (length batch))
|
streamEvents log (first + word (length batch))
|
||||||
|
|
||||||
streamEffectsRows :: ∀e. HasLogFunc e
|
streamEffectsRows :: forall e. HasLogFunc e
|
||||||
=> EventLog -> EventId
|
=> EventLog -> EventId
|
||||||
-> ConduitT () (Word64, ByteString) (RIO e) ()
|
-> ConduitT () (Word64, ByteString) (RIO e) ()
|
||||||
streamEffectsRows log = go
|
streamEffectsRows log = go
|
||||||
@ -221,7 +221,7 @@ readBatch log first = start
|
|||||||
{-
|
{-
|
||||||
Read 1000 rows from the database, starting from key `first`.
|
Read 1000 rows from the database, starting from key `first`.
|
||||||
-}
|
-}
|
||||||
readRowsBatch :: ∀e. HasLogFunc e
|
readRowsBatch :: forall e. HasLogFunc e
|
||||||
=> Env -> Dbi -> Word64 -> RIO e (V.Vector (Word64, ByteString))
|
=> Env -> Dbi -> Word64 -> RIO e (V.Vector (Word64, ByteString))
|
||||||
readRowsBatch env dbi first = readRows
|
readRowsBatch env dbi first = readRows
|
||||||
where
|
where
|
||||||
|
@ -44,7 +44,7 @@ data Server i o a = Server
|
|||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
withRIOThread ∷ RIO e a → RIO e (Async a)
|
withRIOThread :: RIO e a -> RIO e (Async a)
|
||||||
withRIOThread act = do
|
withRIOThread act = do
|
||||||
env <- ask
|
env <- ask
|
||||||
io $ async $ runRIO env $ act
|
io $ async $ runRIO env $ act
|
||||||
@ -87,7 +87,7 @@ wsConn pre inp out wsc = do
|
|||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
wsClient :: ∀i o e. (ToNoun o, FromNoun i, Show o, Show i, HasLogFunc e)
|
wsClient :: forall i o e. (ToNoun o, FromNoun i, Show o, Show i, HasLogFunc e)
|
||||||
=> Text -> W.Port -> RIO e (Client i o)
|
=> Text -> W.Port -> RIO e (Client i o)
|
||||||
wsClient pax por = do
|
wsClient pax por = do
|
||||||
env <- ask
|
env <- ask
|
||||||
@ -118,7 +118,7 @@ wsServApp cb pen = do
|
|||||||
atomically $ cb (mkConn inp out)
|
atomically $ cb (mkConn inp out)
|
||||||
wsConn "NOUNSERV (wsServ) " inp out wsc
|
wsConn "NOUNSERV (wsServ) " inp out wsc
|
||||||
|
|
||||||
wsServer :: ∀i o e. (ToNoun o, FromNoun i, Show i, Show o, HasLogFunc e)
|
wsServer :: forall i o e. (ToNoun o, FromNoun i, Show i, Show o, HasLogFunc e)
|
||||||
=> RIO e (Server i o W.Port)
|
=> RIO e (Server i o W.Port)
|
||||||
wsServer = do
|
wsServer = do
|
||||||
con <- io $ newTBMChanIO 5
|
con <- io $ newTBMChanIO 5
|
||||||
|
@ -104,7 +104,7 @@ connClient c = Client
|
|||||||
, take = Serv.cRecv c
|
, take = Serv.cRecv c
|
||||||
}
|
}
|
||||||
|
|
||||||
connectToRemote :: ∀e. HasLogFunc e
|
connectToRemote :: forall e. HasLogFunc e
|
||||||
=> Port
|
=> Port
|
||||||
-> Client
|
-> Client
|
||||||
-> RAcquire e (Async (), Async ())
|
-> RAcquire e (Async (), Async ())
|
||||||
@ -130,7 +130,7 @@ data HackConfigDir = HCD { _hcdPax :: FilePath }
|
|||||||
makeLenses ''HackConfigDir
|
makeLenses ''HackConfigDir
|
||||||
instance HasPierPath HackConfigDir where pierPathL = hcdPax
|
instance HasPierPath HackConfigDir where pierPathL = hcdPax
|
||||||
|
|
||||||
runTerminalClient :: ∀e. HasLogFunc e => FilePath -> RIO e ()
|
runTerminalClient :: forall e. HasLogFunc e => FilePath -> RIO e ()
|
||||||
runTerminalClient pier = runRAcquire $ do
|
runTerminalClient pier = runRAcquire $ do
|
||||||
mPort <- runRIO (HCD pier) readPortsFile
|
mPort <- runRIO (HCD pier) readPortsFile
|
||||||
port <- maybe (error "Can't connect") pure mPort
|
port <- maybe (error "Can't connect") pure mPort
|
||||||
@ -173,7 +173,7 @@ _spin_idle_us = 500000
|
|||||||
{-|
|
{-|
|
||||||
Initializes the generalized input/output parts of the terminal.
|
Initializes the generalized input/output parts of the terminal.
|
||||||
-}
|
-}
|
||||||
localClient :: ∀e. HasLogFunc e
|
localClient :: forall e. HasLogFunc e
|
||||||
=> STM ()
|
=> STM ()
|
||||||
-> RAcquire e (TermSize, Client)
|
-> RAcquire e (TermSize, Client)
|
||||||
localClient doneSignal = fst <$> mkRAcquire start stop
|
localClient doneSignal = fst <$> mkRAcquire start stop
|
||||||
@ -415,7 +415,7 @@ localClient doneSignal = fst <$> mkRAcquire start stop
|
|||||||
|
|
||||||
-- Moves the cursor left without any mutation of the LineState. Used only
|
-- Moves the cursor left without any mutation of the LineState. Used only
|
||||||
-- in cursor spinning.
|
-- in cursor spinning.
|
||||||
_termSpinnerMoveLeft :: Int → RIO e ()
|
_termSpinnerMoveLeft :: Int -> RIO e ()
|
||||||
_termSpinnerMoveLeft = T.cursorLeft
|
_termSpinnerMoveLeft = T.cursorLeft
|
||||||
|
|
||||||
-- Displays and sets the current line
|
-- Displays and sets the current line
|
||||||
|
@ -16,17 +16,17 @@ import qualified System.Console.ANSI as ANSI
|
|||||||
|
|
||||||
-- Types -----------------------------------------------------------------------
|
-- Types -----------------------------------------------------------------------
|
||||||
|
|
||||||
clearScreen ∷ MonadIO m ⇒ m ()
|
clearScreen :: MonadIO m => m ()
|
||||||
clearScreen = liftIO $ ANSI.clearScreen
|
clearScreen = liftIO $ ANSI.clearScreen
|
||||||
|
|
||||||
clearLine ∷ MonadIO m ⇒ m ()
|
clearLine :: MonadIO m => m ()
|
||||||
clearLine = liftIO $ ANSI.clearLine
|
clearLine = liftIO $ ANSI.clearLine
|
||||||
|
|
||||||
soundBell ∷ MonadIO m ⇒ m ()
|
soundBell :: MonadIO m => m ()
|
||||||
soundBell = liftIO $ putStr "\a"
|
soundBell = liftIO $ putStr "\a"
|
||||||
|
|
||||||
cursorLeft ∷ MonadIO m ⇒ Int → m ()
|
cursorLeft :: MonadIO m => Int -> m ()
|
||||||
cursorLeft = liftIO . ANSI.cursorBackward
|
cursorLeft = liftIO . ANSI.cursorBackward
|
||||||
|
|
||||||
cursorRight ∷ MonadIO m ⇒ Int → m ()
|
cursorRight :: MonadIO m => Int -> m ()
|
||||||
cursorRight = liftIO . ANSI.cursorForward
|
cursorRight = liftIO . ANSI.cursorForward
|
||||||
|
@ -38,7 +38,7 @@ type TreeTests = [TreeTest]
|
|||||||
|
|
||||||
-- Utils -----------------------------------------------------------------------
|
-- Utils -----------------------------------------------------------------------
|
||||||
|
|
||||||
roundTrip :: ∀a. Eq a => (a -> a) -> a -> Bool
|
roundTrip :: forall a. Eq a => (a -> a) -> a -> Bool
|
||||||
roundTrip f x = f x == x
|
roundTrip f x = f x == x
|
||||||
|
|
||||||
|
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
{-# OPTIONS_GHC -O2 #-}
|
{-# OPTIONS_GHC -O2 #-}
|
||||||
|
|
||||||
{-|
|
{-|
|
||||||
Fast implementation of Jam (Noun → Atom).
|
Fast implementation of Jam (Noun -> Atom).
|
||||||
|
|
||||||
This is based on the implementation of `flat`.
|
This is based on the implementation of `flat`.
|
||||||
-}
|
-}
|
||||||
|
@ -49,7 +49,7 @@ data LoadErr
|
|||||||
|
|
||||||
instance Exception LoadErr
|
instance Exception LoadErr
|
||||||
|
|
||||||
loadFile :: ∀a. FromNoun a => FilePath -> IO (Either LoadErr a)
|
loadFile :: forall a. FromNoun a => FilePath -> IO (Either LoadErr a)
|
||||||
loadFile pax = try $ do
|
loadFile pax = try $ do
|
||||||
byt <- try (readFile pax) >>= either (throwIO . FileErr) pure
|
byt <- try (readFile pax) >>= either (throwIO . FileErr) pure
|
||||||
non <- cueBS byt & either (throwIO . CueErr) pure
|
non <- cueBS byt & either (throwIO . CueErr) pure
|
||||||
|
@ -27,14 +27,14 @@ import GHC.Natural (Natural)
|
|||||||
-- Types -----------------------------------------------------------------------
|
-- Types -----------------------------------------------------------------------
|
||||||
|
|
||||||
data NounVal a = NounVal
|
data NounVal a = NounVal
|
||||||
{ non ∷ Noun
|
{ non :: Noun
|
||||||
, val ∷ !a
|
, val :: !a
|
||||||
}
|
}
|
||||||
|
|
||||||
data HoonTreeNode a = NTN
|
data HoonTreeNode a = NTN
|
||||||
{ n ∷ NounVal a
|
{ n :: NounVal a
|
||||||
, l ∷ HoonTree a
|
, l :: HoonTree a
|
||||||
, r ∷ HoonTree a
|
, r :: HoonTree a
|
||||||
}
|
}
|
||||||
deriving (Eq, Ord, Show)
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
@ -43,10 +43,10 @@ data HoonTree a = E | Node (HoonTreeNode a)
|
|||||||
|
|
||||||
pattern N n l r = Node (NTN n l r)
|
pattern N n l r = Node (NTN n l r)
|
||||||
|
|
||||||
newtype HoonSet a = HoonSet { unHoonSet ∷ HoonTree a }
|
newtype HoonSet a = HoonSet { unHoonSet :: HoonTree a }
|
||||||
deriving newtype (Eq, Ord, Show, FromNoun, ToNoun)
|
deriving newtype (Eq, Ord, Show, FromNoun, ToNoun)
|
||||||
|
|
||||||
newtype HoonMap k v = HoonMap { unHoonMap ∷ HoonTree (k, v) }
|
newtype HoonMap k v = HoonMap { unHoonMap :: HoonTree (k, v) }
|
||||||
deriving newtype (Eq, Ord, Show, FromNoun, ToNoun)
|
deriving newtype (Eq, Ord, Show, FromNoun, ToNoun)
|
||||||
|
|
||||||
|
|
||||||
@ -61,17 +61,17 @@ instance Ord (NounVal a) where
|
|||||||
instance ToNoun (NounVal a) where
|
instance ToNoun (NounVal a) where
|
||||||
toNoun = non
|
toNoun = non
|
||||||
|
|
||||||
instance Show a ⇒ Show (NounVal a) where
|
instance Show a => Show (NounVal a) where
|
||||||
show = show . val
|
show = show . val
|
||||||
|
|
||||||
instance FromNoun a ⇒ FromNoun (NounVal a) where
|
instance FromNoun a => FromNoun (NounVal a) where
|
||||||
parseNoun x = NounVal x <$> parseNoun x
|
parseNoun x = NounVal x <$> parseNoun x
|
||||||
|
|
||||||
instance ToNoun a ⇒ ToNoun (HoonTree a) where
|
instance ToNoun a => ToNoun (HoonTree a) where
|
||||||
toNoun E = A 0
|
toNoun E = A 0
|
||||||
toNoun (Node n) = toNoun n
|
toNoun (Node n) = toNoun n
|
||||||
|
|
||||||
instance FromNoun a ⇒ FromNoun (HoonTree a) where
|
instance FromNoun a => FromNoun (HoonTree a) where
|
||||||
parseNoun (A 0) = pure E
|
parseNoun (A 0) = pure E
|
||||||
parseNoun n = Node <$> parseNoun n
|
parseNoun n = Node <$> parseNoun n
|
||||||
|
|
||||||
@ -82,60 +82,60 @@ deriveNoun ''HoonTreeNode
|
|||||||
|
|
||||||
type Nat = Natural
|
type Nat = Natural
|
||||||
|
|
||||||
slowMug ∷ Noun → Nat
|
slowMug :: Noun -> Nat
|
||||||
slowMug = trim 0xcafe_babe . \case
|
slowMug = trim 0xcafe_babe . \case
|
||||||
A a → a
|
A a -> a
|
||||||
C h t → mix (slowMug h) $ mix 0x7fff_ffff (slowMug t)
|
C h t -> mix (slowMug h) $ mix 0x7fff_ffff (slowMug t)
|
||||||
where
|
where
|
||||||
trim ∷ Nat → Nat → Nat
|
trim :: Nat -> Nat -> Nat
|
||||||
trim syd key =
|
trim syd key =
|
||||||
if 0/=ham then ham else trim (succ syd) key
|
if 0/=ham then ham else trim (succ syd) key
|
||||||
where
|
where
|
||||||
haz = muk syd (met 3 key) key
|
haz = muk syd (met 3 key) key
|
||||||
ham = mix (rsh 0 31 haz) (end 0 31 haz)
|
ham = mix (rsh 0 31 haz) (end 0 31 haz)
|
||||||
|
|
||||||
mix ∷ Nat → Nat → Nat
|
mix :: Nat -> Nat -> Nat
|
||||||
mix = xor
|
mix = xor
|
||||||
|
|
||||||
-- Murmur3
|
-- Murmur3
|
||||||
muk ∷ Nat → Nat → Nat → Nat
|
muk :: Nat -> Nat -> Nat -> Nat
|
||||||
muk seed len =
|
muk seed len =
|
||||||
fromIntegral . murmur3 (word32 seed) . resize . atomBytes
|
fromIntegral . murmur3 (word32 seed) . resize . atomBytes
|
||||||
where
|
where
|
||||||
resize ∷ ByteString → ByteString
|
resize :: ByteString -> ByteString
|
||||||
resize buf =
|
resize buf =
|
||||||
case compare (length buf) (int len) of
|
case compare (length buf) (int len) of
|
||||||
EQ → buf
|
EQ -> buf
|
||||||
LT → error "bad-muk"
|
LT -> error "bad-muk"
|
||||||
GT → error "bad-muk"
|
GT -> error "bad-muk"
|
||||||
-- LT → buf <> replicate (len - length buf) 0
|
-- LT -> buf <> replicate (len - length buf) 0
|
||||||
-- GT → take len buf
|
-- GT -> take len buf
|
||||||
|
|
||||||
int ∷ Integral i ⇒ i → Int
|
int :: Integral i => i -> Int
|
||||||
int = fromIntegral
|
int = fromIntegral
|
||||||
|
|
||||||
word32 ∷ Integral i ⇒ i → Word32
|
word32 :: Integral i => i -> Word32
|
||||||
word32 = fromIntegral
|
word32 = fromIntegral
|
||||||
|
|
||||||
bex ∷ Nat → Nat
|
bex :: Nat -> Nat
|
||||||
bex = (2^)
|
bex = (2^)
|
||||||
|
|
||||||
end ∷ Nat → Nat → Nat → Nat
|
end :: Nat -> Nat -> Nat -> Nat
|
||||||
end blockSize blocks n =
|
end blockSize blocks n =
|
||||||
n `mod` (bex (bex blockSize * blocks))
|
n `mod` (bex (bex blockSize * blocks))
|
||||||
|
|
||||||
rsh ∷ Nat → Nat → Nat → Nat
|
rsh :: Nat -> Nat -> Nat -> Nat
|
||||||
rsh blockSize blocks n =
|
rsh blockSize blocks n =
|
||||||
shiftR n $ fromIntegral $ (bex blockSize * blocks)
|
shiftR n $ fromIntegral $ (bex blockSize * blocks)
|
||||||
|
|
||||||
met ∷ Nat → Nat → Nat
|
met :: Nat -> Nat -> Nat
|
||||||
met bloq = go 0
|
met bloq = go 0
|
||||||
where
|
where
|
||||||
go c 0 = c
|
go c 0 = c
|
||||||
go c n = go (succ c) (rsh bloq 1 n)
|
go c n = go (succ c) (rsh bloq 1 n)
|
||||||
|
|
||||||
-- XX TODO
|
-- XX TODO
|
||||||
mug ∷ Noun → Nat
|
mug :: Noun -> Nat
|
||||||
mug = slowMug
|
mug = slowMug
|
||||||
|
|
||||||
|
|
||||||
@ -144,7 +144,7 @@ mug = slowMug
|
|||||||
{-
|
{-
|
||||||
Orders in ascending double mug hash order, collisions fall back to dor.
|
Orders in ascending double mug hash order, collisions fall back to dor.
|
||||||
-}
|
-}
|
||||||
mor ∷ Noun → Noun → Bool
|
mor :: Noun -> Noun -> Bool
|
||||||
mor a b = if c == d then dor a b else c < d
|
mor a b = if c == d then dor a b else c < d
|
||||||
where
|
where
|
||||||
c = mug $ A $ mug a
|
c = mug $ A $ mug a
|
||||||
@ -153,7 +153,7 @@ mor a b = if c == d then dor a b else c < d
|
|||||||
{-
|
{-
|
||||||
Orders in ascending tree depth.
|
Orders in ascending tree depth.
|
||||||
-}
|
-}
|
||||||
dor ∷ Noun → Noun → Bool
|
dor :: Noun -> Noun -> Bool
|
||||||
dor a b | a == b = True
|
dor a b | a == b = True
|
||||||
dor (A a) (C _ _) = True
|
dor (A a) (C _ _) = True
|
||||||
dor (C x y) (A b) = False
|
dor (C x y) (A b) = False
|
||||||
@ -166,80 +166,80 @@ dor (C x y) (C p q) = dor x p
|
|||||||
|
|
||||||
Collisions fall back to dor.
|
Collisions fall back to dor.
|
||||||
-}
|
-}
|
||||||
gor ∷ Noun → Noun → Bool
|
gor :: Noun -> Noun -> Bool
|
||||||
gor a b = if c==d then dor a b else c<d
|
gor a b = if c==d then dor a b else c<d
|
||||||
where (c, d) = (mug a, mug b)
|
where (c, d) = (mug a, mug b)
|
||||||
|
|
||||||
morVal, gorVal ∷ NounVal a → NounVal a → Bool
|
morVal, gorVal :: NounVal a -> NounVal a -> Bool
|
||||||
morVal = on mor non
|
morVal = on mor non
|
||||||
gorVal = on gor non
|
gorVal = on gor non
|
||||||
|
|
||||||
|
|
||||||
--------------------------------------------------------------------------------
|
--------------------------------------------------------------------------------
|
||||||
|
|
||||||
nounVal ∷ ToNoun a ⇒ Iso' a (NounVal a)
|
nounVal :: ToNoun a => Iso' a (NounVal a)
|
||||||
nounVal = iso to val
|
nounVal = iso to val
|
||||||
where
|
where
|
||||||
to x = NounVal (toNoun x) x
|
to x = NounVal (toNoun x) x
|
||||||
|
|
||||||
treeToList ∷ ∀a. HoonTree a → [a]
|
treeToList :: forall a. HoonTree a -> [a]
|
||||||
treeToList = go []
|
treeToList = go []
|
||||||
where
|
where
|
||||||
go ∷ [a] → HoonTree a → [a]
|
go :: [a] -> HoonTree a -> [a]
|
||||||
go acc = \case
|
go acc = \case
|
||||||
E → acc
|
E -> acc
|
||||||
Node (NTN v l r) → go (go (val v : acc) l) r
|
Node (NTN v l r) -> go (go (val v : acc) l) r
|
||||||
|
|
||||||
setFromHoonSet ∷ Ord a ⇒ HoonSet a → Set a
|
setFromHoonSet :: Ord a => HoonSet a -> Set a
|
||||||
setFromHoonSet = setFromList . treeToList . unHoonSet
|
setFromHoonSet = setFromList . treeToList . unHoonSet
|
||||||
|
|
||||||
mapFromHoonMap ∷ Ord k ⇒ HoonMap k v → Map k v
|
mapFromHoonMap :: Ord k => HoonMap k v -> Map k v
|
||||||
mapFromHoonMap = mapFromList . treeToList . unHoonMap
|
mapFromHoonMap = mapFromList . treeToList . unHoonMap
|
||||||
|
|
||||||
setToHoonSet ∷ ∀a. (Ord a, ToNoun a) ⇒ Set a → HoonSet a
|
setToHoonSet :: forall a. (Ord a, ToNoun a) => Set a -> HoonSet a
|
||||||
setToHoonSet = HoonSet . foldr put E . fmap (view nounVal) . setToList
|
setToHoonSet = HoonSet . foldr put E . fmap (view nounVal) . setToList
|
||||||
where
|
where
|
||||||
put x = \case
|
put x = \case
|
||||||
E → N x E E
|
E -> N x E E
|
||||||
Node a | x == n a → Node a
|
Node a | x == n a -> Node a
|
||||||
Node a | gorVal x (n a) → lef x a
|
Node a | gorVal x (n a) -> lef x a
|
||||||
Node a → rit x a
|
Node a -> rit x a
|
||||||
|
|
||||||
rit x a = put x (r a) & \case
|
rit x a = put x (r a) & \case
|
||||||
E → error "bad-put-set"
|
E -> error "bad-put-set"
|
||||||
Node c | morVal (n a) (n c) → N (n a) (l a) (Node c)
|
Node c | morVal (n a) (n c) -> N (n a) (l a) (Node c)
|
||||||
Node c → N (n c) (N (n a) (l a) (l c)) (r c)
|
Node c -> N (n c) (N (n a) (l a) (l c)) (r c)
|
||||||
|
|
||||||
lef x a = put x (l a) & \case
|
lef x a = put x (l a) & \case
|
||||||
E → error "bad-put-set"
|
E -> error "bad-put-set"
|
||||||
Node c | morVal (n a) (n c) → N (n a) (Node c) (r a)
|
Node c | morVal (n a) (n c) -> N (n a) (Node c) (r a)
|
||||||
Node c → N (n c) (l c) (N (n a) (r c) (r a))
|
Node c -> N (n c) (l c) (N (n a) (r c) (r a))
|
||||||
|
|
||||||
p ∷ (ToNoun a, ToNoun b) ⇒ NounVal (a,b) → NounVal a
|
p :: (ToNoun a, ToNoun b) => NounVal (a,b) -> NounVal a
|
||||||
p = view (from nounVal . to fst . nounVal)
|
p = view (from nounVal . to fst . nounVal)
|
||||||
|
|
||||||
pq ∷ (ToNoun a, ToNoun b) ⇒ NounVal (a,b) → (NounVal a, NounVal b)
|
pq :: (ToNoun a, ToNoun b) => NounVal (a,b) -> (NounVal a, NounVal b)
|
||||||
pq = boof . view (from nounVal)
|
pq = boof . view (from nounVal)
|
||||||
where
|
where
|
||||||
boof (x, y) = (x ^. nounVal, y ^. nounVal)
|
boof (x, y) = (x ^. nounVal, y ^. nounVal)
|
||||||
|
|
||||||
mapToHoonMap ∷ ∀k v. (ToNoun k, ToNoun v, Ord k, Ord v) ⇒ Map k v → HoonMap k v
|
mapToHoonMap :: forall k v. (ToNoun k, ToNoun v, Ord k, Ord v) => Map k v -> HoonMap k v
|
||||||
mapToHoonMap = HoonMap . foldr put E . fmap (view nounVal) . mapToList
|
mapToHoonMap = HoonMap . foldr put E . fmap (view nounVal) . mapToList
|
||||||
where
|
where
|
||||||
put ∷ NounVal (k, v) → HoonTree (k, v) → HoonTree (k, v)
|
put :: NounVal (k, v) -> HoonTree (k, v) -> HoonTree (k, v)
|
||||||
put kv@(pq -> (b, c)) = \case
|
put kv@(pq -> (b, c)) = \case
|
||||||
E → N kv E E
|
E -> N kv E E
|
||||||
Node a | kv == n a → Node a
|
Node a | kv == n a -> Node a
|
||||||
Node a | b == p (n a) → N kv (l a) (r a)
|
Node a | b == p (n a) -> N kv (l a) (r a)
|
||||||
Node a | gorVal b (p $ n a) → lef kv a
|
Node a | gorVal b (p $ n a) -> lef kv a
|
||||||
Node a → rit kv a
|
Node a -> rit kv a
|
||||||
|
|
||||||
lef kv@(pq -> (b, c)) a = put kv (l a) & \case
|
lef kv@(pq -> (b, c)) a = put kv (l a) & \case
|
||||||
E → error "bad-put-map"
|
E -> error "bad-put-map"
|
||||||
Node d | morVal (p $ n a) (p $ n d) → N (n a) (Node d) (r a)
|
Node d | morVal (p $ n a) (p $ n d) -> N (n a) (Node d) (r a)
|
||||||
Node d → N (n d) (l d) (N (n a) (r d) (r a))
|
Node d -> N (n d) (l d) (N (n a) (r d) (r a))
|
||||||
|
|
||||||
rit kv@(pq -> (b, c)) a = put kv (r a) & \case
|
rit kv@(pq -> (b, c)) a = put kv (r a) & \case
|
||||||
E → error "bad-put-map"
|
E -> error "bad-put-map"
|
||||||
Node d | morVal (p $ n a) (p $ n d) → N (n a) (l a) (Node d)
|
Node d | morVal (p $ n a) (p $ n d) -> N (n a) (l a) (Node d)
|
||||||
Node d → N (n d) (N (n a) (l a) (l d)) (r d)
|
Node d -> N (n d) (N (n a) (l a) (l d)) (r d)
|
||||||
|
@ -117,25 +117,22 @@ _jam_bench(void)
|
|||||||
gettimeofday(&b4, 0);
|
gettimeofday(&b4, 0);
|
||||||
|
|
||||||
{
|
{
|
||||||
ur_dict64_t dic_u = {0};
|
ur_jam_t *jam_u = ur_jam_init(rot_u);
|
||||||
c3_d len_d;
|
c3_d len_d;
|
||||||
c3_y* byt_y;
|
c3_y* byt_y;
|
||||||
|
|
||||||
ur_dict64_grow((ur_root_t*)0, &dic_u, ur_fib10, ur_fib11);
|
|
||||||
|
|
||||||
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
||||||
ur_jam_unsafe(rot_u, ref, &dic_u, &len_d, &byt_y);
|
ur_jam_with(jam_u, ref, &len_d, &byt_y);
|
||||||
c3_free(byt_y);
|
c3_free(byt_y);
|
||||||
ur_dict64_wipe(&dic_u);
|
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
ur_jam_done(jam_u);
|
||||||
}
|
}
|
||||||
|
|
||||||
gettimeofday(&f2, 0);
|
gettimeofday(&f2, 0);
|
||||||
timersub(&f2, &b4, &d0);
|
timersub(&f2, &b4, &d0);
|
||||||
mil_w = (d0.tv_sec * 1000) + (d0.tv_usec / 1000);
|
mil_w = (d0.tv_sec * 1000) + (d0.tv_usec / 1000);
|
||||||
fprintf(stderr, " jam cons unsafe: %u ms\r\n", mil_w);
|
fprintf(stderr, " jam cons with: %u ms\r\n", mil_w);
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_root_free(rot_u);
|
ur_root_free(rot_u);
|
||||||
@ -184,7 +181,6 @@ _cue_bench(void)
|
|||||||
gettimeofday(&b4, 0);
|
gettimeofday(&b4, 0);
|
||||||
|
|
||||||
{
|
{
|
||||||
u3_noun out;
|
|
||||||
c3_w len_w = u3r_met(3, vat);
|
c3_w len_w = u3r_met(3, vat);
|
||||||
// XX assumes little-endian
|
// XX assumes little-endian
|
||||||
//
|
//
|
||||||
@ -193,8 +189,7 @@ _cue_bench(void)
|
|||||||
: (c3_y*)((u3a_atom*)u3a_to_ptr(vat))->buf_w;
|
: (c3_y*)((u3a_atom*)u3a_to_ptr(vat))->buf_w;
|
||||||
|
|
||||||
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
||||||
u3s_cue_xeno(len_w, byt_y, &out);
|
u3z(u3s_cue_xeno(len_w, byt_y));
|
||||||
u3z(out);
|
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -208,8 +203,7 @@ _cue_bench(void)
|
|||||||
gettimeofday(&b4, 0);
|
gettimeofday(&b4, 0);
|
||||||
|
|
||||||
{
|
{
|
||||||
ur_dict32_t dic_u = {0};
|
u3_cue_xeno* sil_u = u3s_cue_xeno_init();
|
||||||
u3_noun out;
|
|
||||||
|
|
||||||
c3_w len_w = u3r_met(3, vat);
|
c3_w len_w = u3r_met(3, vat);
|
||||||
// XX assumes little-endian
|
// XX assumes little-endian
|
||||||
@ -218,21 +212,17 @@ _cue_bench(void)
|
|||||||
? (c3_y*)&vat
|
? (c3_y*)&vat
|
||||||
: (c3_y*)((u3a_atom*)u3a_to_ptr(vat))->buf_w;
|
: (c3_y*)((u3a_atom*)u3a_to_ptr(vat))->buf_w;
|
||||||
|
|
||||||
ur_dict32_grow((ur_root_t*)0, &dic_u, ur_fib10, ur_fib11);
|
|
||||||
|
|
||||||
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
||||||
u3s_cue_xeno_unsafe(&dic_u, len_w, byt_y, &out);
|
u3z(u3s_cue_xeno_with(sil_u, len_w, byt_y));
|
||||||
u3z(out);
|
|
||||||
ur_dict32_wipe(&dic_u);
|
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
u3s_cue_xeno_done(sil_u);
|
||||||
}
|
}
|
||||||
|
|
||||||
gettimeofday(&f2, 0);
|
gettimeofday(&f2, 0);
|
||||||
timersub(&f2, &b4, &d0);
|
timersub(&f2, &b4, &d0);
|
||||||
mil_w = (d0.tv_sec * 1000) + (d0.tv_usec / 1000);
|
mil_w = (d0.tv_sec * 1000) + (d0.tv_usec / 1000);
|
||||||
fprintf(stderr, " cue xeno unsafe: %u ms\r\n", mil_w);
|
fprintf(stderr, " cue xeno with: %u ms\r\n", mil_w);
|
||||||
}
|
}
|
||||||
|
|
||||||
{
|
{
|
||||||
@ -261,8 +251,7 @@ _cue_bench(void)
|
|||||||
gettimeofday(&b4, 0);
|
gettimeofday(&b4, 0);
|
||||||
|
|
||||||
{
|
{
|
||||||
ur_dict_t dic_u = {0};
|
ur_cue_test_t *t = ur_cue_test_init();
|
||||||
u3_noun out;
|
|
||||||
|
|
||||||
c3_w len_w = u3r_met(3, vat);
|
c3_w len_w = u3r_met(3, vat);
|
||||||
// XX assumes little-endian
|
// XX assumes little-endian
|
||||||
@ -271,20 +260,17 @@ _cue_bench(void)
|
|||||||
? (c3_y*)&vat
|
? (c3_y*)&vat
|
||||||
: (c3_y*)((u3a_atom*)u3a_to_ptr(vat))->buf_w;
|
: (c3_y*)((u3a_atom*)u3a_to_ptr(vat))->buf_w;
|
||||||
|
|
||||||
ur_dict_grow((ur_root_t*)0, &dic_u, ur_fib10, ur_fib11);
|
|
||||||
|
|
||||||
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
for ( i_w = 0; i_w < max_w; i_w++ ) {
|
||||||
ur_cue_test_unsafe(&dic_u, len_w, byt_y);
|
ur_cue_test_with(t, len_w, byt_y);
|
||||||
ur_dict_wipe(&dic_u);
|
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_dict_free(&dic_u);
|
ur_cue_test_done(t);
|
||||||
}
|
}
|
||||||
|
|
||||||
gettimeofday(&f2, 0);
|
gettimeofday(&f2, 0);
|
||||||
timersub(&f2, &b4, &d0);
|
timersub(&f2, &b4, &d0);
|
||||||
mil_w = (d0.tv_sec * 1000) + (d0.tv_usec / 1000);
|
mil_w = (d0.tv_sec * 1000) + (d0.tv_usec / 1000);
|
||||||
fprintf(stderr, " cue test unsafe: %u ms\r\n", mil_w);
|
fprintf(stderr, " cue test with: %u ms\r\n", mil_w);
|
||||||
}
|
}
|
||||||
|
|
||||||
{
|
{
|
||||||
|
@ -1,11 +1,11 @@
|
|||||||
/* i/n/serial.h
|
/* i/n/serial.h
|
||||||
**
|
**
|
||||||
*/
|
*/
|
||||||
/* forward declarations
|
/* opaque handles
|
||||||
*/
|
*/
|
||||||
/* ur_dict32_s: off-loom 32-bit dictionary.
|
/* u3_cue_xeno: handle for cue-ing with an off-loom dictionary.
|
||||||
*/
|
*/
|
||||||
struct ur_dict32_s;
|
typedef struct _u3_cue_xeno u3_cue_xeno;
|
||||||
|
|
||||||
/* Noun serialization. All noun arguments RETAINED.
|
/* Noun serialization. All noun arguments RETAINED.
|
||||||
*/
|
*/
|
||||||
@ -28,18 +28,33 @@
|
|||||||
u3_noun
|
u3_noun
|
||||||
u3s_cue(u3_atom a);
|
u3s_cue(u3_atom a);
|
||||||
|
|
||||||
/* u3s_cue_xeno_unsafe(): cue onto the loom, all bookkeeping off-loom.
|
/* u3s_cue_xeno_init_with(): initialize a cue_xeno handle as specified.
|
||||||
*/
|
*/
|
||||||
c3_o
|
u3_cue_xeno*
|
||||||
u3s_cue_xeno_unsafe(struct ur_dict32_s* dic_u,
|
u3s_cue_xeno_init_with(c3_d pre_d, c3_d siz_d);
|
||||||
c3_d len_d,
|
|
||||||
const c3_y* byt_y,
|
|
||||||
u3_noun* out);
|
|
||||||
|
|
||||||
/* u3s_cue_xeno(): cue onto the loom, bookkeeping off the loom.
|
/* u3s_cue_xeno_init(): initialize a cue_xeno handle.
|
||||||
*/
|
*/
|
||||||
c3_o
|
u3_cue_xeno*
|
||||||
u3s_cue_xeno(c3_d len_d, const c3_y* byt_y, u3_noun* out);
|
u3s_cue_xeno_init(void);
|
||||||
|
|
||||||
|
/* u3s_cue_xeno_init(): cue on-loom, with off-loom dictionary in handle.
|
||||||
|
*/
|
||||||
|
u3_weak
|
||||||
|
u3s_cue_xeno_with(u3_cue_xeno* sil_u,
|
||||||
|
c3_d len_d,
|
||||||
|
const c3_y* byt_y);
|
||||||
|
|
||||||
|
/* u3s_cue_xeno_init(): dispose cue_xeno handle.
|
||||||
|
*/
|
||||||
|
void
|
||||||
|
u3s_cue_xeno_done(u3_cue_xeno* sil_u);
|
||||||
|
|
||||||
|
/* u3s_cue_xeno(): cue on-loom, with off-loom dictionary.
|
||||||
|
*/
|
||||||
|
u3_weak
|
||||||
|
u3s_cue_xeno(c3_d len_d,
|
||||||
|
const c3_y* byt_y);
|
||||||
|
|
||||||
/* u3s_cue_bytes(): cue bytes onto the loom.
|
/* u3s_cue_bytes(): cue bytes onto the loom.
|
||||||
*/
|
*/
|
||||||
|
@ -130,6 +130,12 @@ ur_bsr_log(ur_bsr_t *bsr, uint8_t *out);
|
|||||||
ur_cue_res_e
|
ur_cue_res_e
|
||||||
ur_bsr_rub_len(ur_bsr_t *bsr, uint64_t *out);
|
ur_bsr_rub_len(ur_bsr_t *bsr, uint64_t *out);
|
||||||
|
|
||||||
|
/*
|
||||||
|
** initialize bitstream-writer with prev/size for fibonacci growth.
|
||||||
|
*/
|
||||||
|
void
|
||||||
|
ur_bsw_init(ur_bsw_t *bsw, uint64_t prev, uint64_t size);
|
||||||
|
|
||||||
/*
|
/*
|
||||||
** reallocate bitstream write buffer with max(fibonacci, step) growth.
|
** reallocate bitstream write buffer with max(fibonacci, step) growth.
|
||||||
*/
|
*/
|
||||||
@ -142,6 +148,12 @@ ur_bsw_grow(ur_bsw_t *bsw, uint64_t step);
|
|||||||
ur_bool_t
|
ur_bool_t
|
||||||
ur_bsw_sane(ur_bsw_t *bsw);
|
ur_bsw_sane(ur_bsw_t *bsw);
|
||||||
|
|
||||||
|
/*
|
||||||
|
** return bit-length, produce byte-buffer.
|
||||||
|
*/
|
||||||
|
uint64_t
|
||||||
|
ur_bsw_done(ur_bsw_t *bsw, uint64_t *len, uint8_t **byt);
|
||||||
|
|
||||||
/*
|
/*
|
||||||
** write a bit
|
** write a bit
|
||||||
*/
|
*/
|
||||||
|
@ -111,6 +111,11 @@ typedef struct ur_nvec_s {
|
|||||||
ur_nref* refs;
|
ur_nref* refs;
|
||||||
} ur_nvec_t;
|
} ur_nvec_t;
|
||||||
|
|
||||||
|
/*
|
||||||
|
** opaque handle for repeated traversal.
|
||||||
|
*/
|
||||||
|
typedef struct ur_walk_fore_s ur_walk_fore_t;
|
||||||
|
|
||||||
/*
|
/*
|
||||||
** type-specific dictionary operations.
|
** type-specific dictionary operations.
|
||||||
**
|
**
|
||||||
@ -231,4 +236,22 @@ ur_walk_fore(ur_root_t *r,
|
|||||||
void (*atom)(ur_root_t*, ur_nref, void*),
|
void (*atom)(ur_root_t*, ur_nref, void*),
|
||||||
ur_bool_t (*cell)(ur_root_t*, ur_nref, void*));
|
ur_bool_t (*cell)(ur_root_t*, ur_nref, void*));
|
||||||
|
|
||||||
|
ur_walk_fore_t*
|
||||||
|
ur_walk_fore_init_with(ur_root_t *r,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size);
|
||||||
|
|
||||||
|
ur_walk_fore_t*
|
||||||
|
ur_walk_fore_init(ur_root_t *r);
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_walk_fore_with(ur_walk_fore_t *w,
|
||||||
|
ur_nref ref,
|
||||||
|
void *v,
|
||||||
|
void (*atom)(ur_root_t*, ur_nref, void*),
|
||||||
|
ur_bool_t (*cell)(ur_root_t*, ur_nref, void*));
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_walk_fore_done(ur_walk_fore_t *w);
|
||||||
|
|
||||||
#endif
|
#endif
|
||||||
|
@ -4,16 +4,20 @@
|
|||||||
#include <inttypes.h>
|
#include <inttypes.h>
|
||||||
#include <ur/defs.h>
|
#include <ur/defs.h>
|
||||||
#include <ur/bitstream.h>
|
#include <ur/bitstream.h>
|
||||||
|
#include <ur/hashcons.h>
|
||||||
|
|
||||||
/*
|
/*
|
||||||
** bit-wise serialization of a noun into a byte-buffer.
|
** bit-wise serialization of a noun into a byte-buffer.
|
||||||
** supports up to 64-bits of bit-addressed output (nearly 2 EiB).
|
** supports up to 64-bits of bit-addressed output (nearly 2 EiB).
|
||||||
** (as this is an impractical volume data, cursor overflow is not checked.)
|
** (as this is an impractical volume data, cursor overflow is not checked.)
|
||||||
**
|
**
|
||||||
** unsafe variant is unsafe wrt its [dict] parameter, which must be empty,
|
** jam_with* api factors out stack/dict (re)allocation,
|
||||||
** but can be passed in order to skip reallocation inside hot loops.
|
** for better performance inside hot loops.
|
||||||
**
|
**
|
||||||
*/
|
*/
|
||||||
|
|
||||||
|
typedef struct ur_jam_s ur_jam_t;
|
||||||
|
|
||||||
uint64_t
|
uint64_t
|
||||||
ur_jam_unsafe(ur_root_t *r,
|
ur_jam_unsafe(ur_root_t *r,
|
||||||
ur_nref ref,
|
ur_nref ref,
|
||||||
@ -22,35 +26,86 @@ ur_jam_unsafe(ur_root_t *r,
|
|||||||
uint8_t **byt);
|
uint8_t **byt);
|
||||||
|
|
||||||
uint64_t
|
uint64_t
|
||||||
ur_jam(ur_root_t *r, ur_nref ref, uint64_t *len, uint8_t **byt);
|
ur_jam(ur_root_t *r,
|
||||||
|
ur_nref ref,
|
||||||
|
uint64_t *len,
|
||||||
|
uint8_t **byt);
|
||||||
|
|
||||||
|
ur_jam_t*
|
||||||
|
ur_jam_init_with(ur_root_t *r,
|
||||||
|
uint64_t d_prev,
|
||||||
|
uint64_t d_size,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size);
|
||||||
|
|
||||||
|
ur_jam_t*
|
||||||
|
ur_jam_init(ur_root_t *r);
|
||||||
|
|
||||||
|
uint64_t
|
||||||
|
ur_jam_with(ur_jam_t *j,
|
||||||
|
ur_nref ref,
|
||||||
|
uint64_t *len,
|
||||||
|
uint8_t **byt);
|
||||||
|
void
|
||||||
|
ur_jam_done(ur_jam_t *j);
|
||||||
|
|
||||||
/*
|
/*
|
||||||
** bitwise deserialization of a byte-buffer into a noun.
|
** bitwise deserialization of a byte-buffer into a noun.
|
||||||
** supports up to 62-bits of bit-addressed input (511 PiB).
|
** supports up to 62-bits of bit-addressed input (511 PiB).
|
||||||
** returns [ur_cue_good] on success.
|
** returns [ur_cue_good] on success.
|
||||||
**
|
**
|
||||||
** unsafe variant is unsafe wrt its [dict] parameter, which must be empty,
|
** cue_with factors out stack/dict (re)allocation,
|
||||||
** (present in order to skip reallocation inside hot loops).
|
** for better performance of hot loops.
|
||||||
**
|
**
|
||||||
** test variant does not allocate nouns, but merely parses the input.
|
** cue_test does not allocate nouns, but merely parses the input;
|
||||||
|
** cue_test_with* api factors out stack/dict (re)allocation,
|
||||||
|
** for better performance of repeated tests.
|
||||||
**
|
**
|
||||||
*/
|
*/
|
||||||
ur_cue_res_e
|
|
||||||
ur_cue_unsafe(ur_root_t *r,
|
typedef struct ur_cue_test_s ur_cue_test_t;
|
||||||
ur_dict64_t *dict,
|
typedef struct ur_cue_s ur_cue_t;
|
||||||
uint64_t len,
|
|
||||||
const uint8_t *byt,
|
|
||||||
ur_nref *out);
|
|
||||||
|
|
||||||
ur_cue_res_e
|
ur_cue_res_e
|
||||||
ur_cue(ur_root_t *r, uint64_t len, const uint8_t *byt, ur_nref *out);
|
ur_cue(ur_root_t *r, uint64_t len, const uint8_t *byt, ur_nref *out);
|
||||||
|
|
||||||
|
ur_cue_t*
|
||||||
|
ur_cue_init_with(ur_root_t *r,
|
||||||
|
uint64_t d_prev,
|
||||||
|
uint64_t d_size,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size);
|
||||||
|
|
||||||
|
ur_cue_t*
|
||||||
|
ur_cue_init(ur_root_t *r);
|
||||||
|
|
||||||
ur_cue_res_e
|
ur_cue_res_e
|
||||||
ur_cue_test_unsafe(ur_dict_t *dict,
|
ur_cue_with(ur_cue_t *c,
|
||||||
uint64_t len,
|
uint64_t len,
|
||||||
const uint8_t *byt);
|
const uint8_t *byt,
|
||||||
|
ur_nref *out);
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_cue_done(ur_cue_t *c);
|
||||||
|
|
||||||
ur_bool_t
|
ur_bool_t
|
||||||
ur_cue_test(uint64_t len, const uint8_t *byt);
|
ur_cue_test(uint64_t len, const uint8_t *byt);
|
||||||
|
|
||||||
|
ur_cue_test_t*
|
||||||
|
ur_cue_test_init_with(uint64_t d_prev,
|
||||||
|
uint64_t d_size,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size);
|
||||||
|
|
||||||
|
ur_cue_test_t*
|
||||||
|
ur_cue_test_init(void);
|
||||||
|
|
||||||
|
ur_bool_t
|
||||||
|
ur_cue_test_with(ur_cue_test_t *t,
|
||||||
|
uint64_t len,
|
||||||
|
const uint8_t *byt);
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_cue_test_done(ur_cue_test_t *t);
|
||||||
|
|
||||||
#endif
|
#endif
|
||||||
|
@ -470,7 +470,7 @@
|
|||||||
uv_process_t cub_u; // process handle
|
uv_process_t cub_u; // process handle
|
||||||
uv_process_options_t ops_u; // process configuration
|
uv_process_options_t ops_u; // process configuration
|
||||||
uv_stdio_container_t cod_u[3]; // process options
|
uv_stdio_container_t cod_u[3]; // process options
|
||||||
void* dic_u; // cue dictionary
|
u3_cue_xeno* sil_u; // cue handle
|
||||||
time_t wen_t; // process creation time
|
time_t wen_t; // process creation time
|
||||||
u3_mojo inn_u; // client's stdin
|
u3_mojo inn_u; // client's stdin
|
||||||
u3_moat out_u; // client's stdout
|
u3_moat out_u; // client's stdout
|
||||||
|
@ -270,13 +270,10 @@ c3_d
|
|||||||
u3s_jam_xeno(u3_noun a, c3_d* len_d, c3_y** byt_y)
|
u3s_jam_xeno(u3_noun a, c3_d* len_d, c3_y** byt_y)
|
||||||
{
|
{
|
||||||
_jam_xeno_t jam_u = {0};
|
_jam_xeno_t jam_u = {0};
|
||||||
|
ur_bsw_init(&jam_u.rit_u, ur_fib11, ur_fib12);
|
||||||
|
|
||||||
jam_u.har_p = u3h_new();
|
jam_u.har_p = u3h_new();
|
||||||
|
|
||||||
jam_u.rit_u.prev = ur_fib11;
|
|
||||||
jam_u.rit_u.size = ur_fib12;
|
|
||||||
jam_u.rit_u.bytes = c3_calloc(jam_u.rit_u.size);
|
|
||||||
|
|
||||||
// as this is a hot path, we unsafely elide overflow checks
|
// as this is a hot path, we unsafely elide overflow checks
|
||||||
//
|
//
|
||||||
// a page-fault overflow detection system is urgently needed ...
|
// a page-fault overflow detection system is urgently needed ...
|
||||||
@ -284,12 +281,9 @@ u3s_jam_xeno(u3_noun a, c3_d* len_d, c3_y** byt_y)
|
|||||||
u3a_walk_fore_unsafe(a, &jam_u, _cs_jam_xeno_atom,
|
u3a_walk_fore_unsafe(a, &jam_u, _cs_jam_xeno_atom,
|
||||||
_cs_jam_xeno_cell);
|
_cs_jam_xeno_cell);
|
||||||
|
|
||||||
*len_d = jam_u.rit_u.fill + !!jam_u.rit_u.off;
|
|
||||||
*byt_y = jam_u.rit_u.bytes;
|
|
||||||
|
|
||||||
u3h_free(jam_u.har_p);
|
u3h_free(jam_u.har_p);
|
||||||
|
|
||||||
return jam_u.rit_u.bits;
|
return ur_bsw_done(&jam_u.rit_u, len_d, byt_y);
|
||||||
}
|
}
|
||||||
|
|
||||||
#define CUE_ROOT 0
|
#define CUE_ROOT 0
|
||||||
@ -529,17 +523,10 @@ typedef struct _cue_frame_s {
|
|||||||
c3_d bit_d;
|
c3_d bit_d;
|
||||||
} _cue_frame_t;
|
} _cue_frame_t;
|
||||||
|
|
||||||
typedef struct _cue_stack_s {
|
/* _cs_cue_xeno_next(): read next value from bitstream, dictionary off-loom.
|
||||||
c3_w pre_w;
|
|
||||||
c3_w siz_w;
|
|
||||||
c3_w fil_w;
|
|
||||||
_cue_frame_t* fam_u;
|
|
||||||
} _cue_stack_t;
|
|
||||||
|
|
||||||
/* _cs_cue_xeno_next(): read next value from bitstream, bookkeeping off-loom.
|
|
||||||
*/
|
*/
|
||||||
static inline ur_cue_res_e
|
static inline ur_cue_res_e
|
||||||
_cs_cue_xeno_next(_cue_stack_t* tac_u,
|
_cs_cue_xeno_next(u3a_pile* pil_u,
|
||||||
ur_bsr_t* red_u,
|
ur_bsr_t* red_u,
|
||||||
ur_dict32_t* dic_u,
|
ur_dict32_t* dic_u,
|
||||||
u3_noun* out)
|
u3_noun* out)
|
||||||
@ -559,22 +546,11 @@ _cs_cue_xeno_next(_cue_stack_t* tac_u,
|
|||||||
default: c3_assert(0);
|
default: c3_assert(0);
|
||||||
|
|
||||||
case ur_jam_cell: {
|
case ur_jam_cell: {
|
||||||
// reallocate the stack if full
|
_cue_frame_t* fam_u = u3a_push(pil_u);
|
||||||
//
|
u3a_pile_sane(pil_u);
|
||||||
if ( tac_u->fil_w == tac_u->siz_w ) {
|
|
||||||
c3_w nex_w = tac_u->pre_w + tac_u->siz_w;
|
|
||||||
tac_u->fam_u = c3_realloc(tac_u->fam_u, nex_w * sizeof(*tac_u->fam_u));
|
|
||||||
tac_u->pre_w = tac_u->siz_w;
|
|
||||||
tac_u->siz_w = nex_w;
|
|
||||||
}
|
|
||||||
|
|
||||||
// save a head-frame and read the head from the stream
|
|
||||||
//
|
|
||||||
{
|
|
||||||
_cue_frame_t* fam_u = &(tac_u->fam_u[tac_u->fil_w++]);
|
|
||||||
fam_u->ref = u3_none;
|
fam_u->ref = u3_none;
|
||||||
fam_u->bit_d = bit_d;
|
fam_u->bit_d = bit_d;
|
||||||
}
|
|
||||||
continue;
|
continue;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -607,12 +583,18 @@ _cs_cue_xeno_next(_cue_stack_t* tac_u,
|
|||||||
*out = (u3_noun)ur_bsr32_any(red_u, len_d);
|
*out = (u3_noun)ur_bsr32_any(red_u, len_d);
|
||||||
}
|
}
|
||||||
else {
|
else {
|
||||||
|
c3_d byt_d = (len_d + 0x7) >> 3;
|
||||||
u3i_slab sab_u;
|
u3i_slab sab_u;
|
||||||
u3i_slab_init(&sab_u, 0, len_d);
|
|
||||||
|
|
||||||
|
if ( 0xffffffffULL < byt_d) {
|
||||||
|
return ur_cue_meme;
|
||||||
|
}
|
||||||
|
else {
|
||||||
|
u3i_slab_init(&sab_u, 3, byt_d);
|
||||||
ur_bsr_bytes_any(red_u, len_d, sab_u.buf_y);
|
ur_bsr_bytes_any(red_u, len_d, sab_u.buf_y);
|
||||||
*out = u3i_slab_mint_bytes(&sab_u);
|
*out = u3i_slab_mint_bytes(&sab_u);
|
||||||
}
|
}
|
||||||
|
}
|
||||||
|
|
||||||
ur_dict32_put(rot_u, dic_u, bit_d, *out);
|
ur_dict32_put(rot_u, dic_u, bit_d, *out);
|
||||||
return ur_cue_good;
|
return ur_cue_good;
|
||||||
@ -621,21 +603,28 @@ _cs_cue_xeno_next(_cue_stack_t* tac_u,
|
|||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
/* u3s_cue_xeno_unsafe(): cue onto the loom, all bookkeeping off-loom.
|
struct _u3_cue_xeno {
|
||||||
**
|
ur_dict32_t dic_u;
|
||||||
** NB: unsafe wrt to [dic_u], which must be empty.
|
};
|
||||||
|
|
||||||
|
/* _cs_cue_xeno(): cue on-loom, with off-loom dictionary in handle.
|
||||||
*/
|
*/
|
||||||
c3_o
|
static u3_weak
|
||||||
u3s_cue_xeno_unsafe(ur_dict32_t* dic_u,
|
_cs_cue_xeno(u3_cue_xeno* sil_u,
|
||||||
c3_d len_d,
|
c3_d len_d,
|
||||||
const c3_y* byt_y,
|
const c3_y* byt_y)
|
||||||
u3_noun* out)
|
|
||||||
{
|
{
|
||||||
ur_bsr_t red_u = {0};
|
ur_bsr_t red_u = {0};
|
||||||
_cue_stack_t tac_u = {0};
|
ur_dict32_t* dic_u = &sil_u->dic_u;
|
||||||
|
u3a_pile pil_u;
|
||||||
|
_cue_frame_t* fam_u;
|
||||||
ur_cue_res_e res_e;
|
ur_cue_res_e res_e;
|
||||||
u3_noun ref;
|
u3_noun ref;
|
||||||
|
|
||||||
|
// initialize stack control
|
||||||
|
//
|
||||||
|
u3a_pile_prep(&pil_u, sizeof(*fam_u));
|
||||||
|
|
||||||
// init bitstream-reader
|
// init bitstream-reader
|
||||||
//
|
//
|
||||||
if ( ur_cue_good != (res_e = ur_bsr_init(&red_u, len_d, byt_y)) ) {
|
if ( ur_cue_good != (res_e = ur_bsr_init(&red_u, len_d, byt_y)) ) {
|
||||||
@ -647,28 +636,24 @@ u3s_cue_xeno_unsafe(ur_dict32_t* dic_u,
|
|||||||
return c3n;
|
return c3n;
|
||||||
}
|
}
|
||||||
|
|
||||||
// setup stack
|
|
||||||
//
|
|
||||||
tac_u.pre_w = ur_fib10;
|
|
||||||
tac_u.siz_w = ur_fib11;
|
|
||||||
tac_u.fam_u = c3_malloc(tac_u.siz_w * sizeof(*tac_u.fam_u));
|
|
||||||
|
|
||||||
// advance into stream
|
// advance into stream
|
||||||
//
|
//
|
||||||
res_e = _cs_cue_xeno_next(&tac_u, &red_u, dic_u, &ref);
|
res_e = _cs_cue_xeno_next(&pil_u, &red_u, dic_u, &ref);
|
||||||
|
|
||||||
// process result
|
// process cell results
|
||||||
//
|
//
|
||||||
while ( tac_u.fil_w && (ur_cue_good == res_e) ) {
|
if ( (c3n == u3a_pile_done(&pil_u))
|
||||||
// peek at the top of the stack
|
&& (ur_cue_good == res_e) )
|
||||||
//
|
{
|
||||||
_cue_frame_t* fam_u = &(tac_u.fam_u[tac_u.fil_w - 1]);
|
fam_u = u3a_peek(&pil_u);
|
||||||
|
|
||||||
|
do {
|
||||||
// f is a head-frame; stash result and read the tail from the stream
|
// f is a head-frame; stash result and read the tail from the stream
|
||||||
//
|
//
|
||||||
if ( u3_none == fam_u->ref ) {
|
if ( u3_none == fam_u->ref ) {
|
||||||
fam_u->ref = ref;
|
fam_u->ref = ref;
|
||||||
res_e = _cs_cue_xeno_next(&tac_u, &red_u, dic_u, &ref);
|
res_e = _cs_cue_xeno_next(&pil_u, &red_u, dic_u, &ref);
|
||||||
|
fam_u = u3a_peek(&pil_u);
|
||||||
}
|
}
|
||||||
// f is a tail-frame; pop the stack and continue
|
// f is a tail-frame; pop the stack and continue
|
||||||
//
|
//
|
||||||
@ -677,50 +662,94 @@ u3s_cue_xeno_unsafe(ur_dict32_t* dic_u,
|
|||||||
|
|
||||||
ref = u3nc(fam_u->ref, ref);
|
ref = u3nc(fam_u->ref, ref);
|
||||||
ur_dict32_put(rot_u, dic_u, fam_u->bit_d, ref);
|
ur_dict32_put(rot_u, dic_u, fam_u->bit_d, ref);
|
||||||
tac_u.fil_w--;
|
fam_u = u3a_pop(&pil_u);
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
while ( (c3n == u3a_pile_done(&pil_u))
|
||||||
|
&& (ur_cue_good == res_e) );
|
||||||
|
}
|
||||||
|
|
||||||
if ( ur_cue_good == res_e ) {
|
if ( ur_cue_good == res_e ) {
|
||||||
*out = ref;
|
return ref;
|
||||||
c3_free(tac_u.fam_u);
|
|
||||||
return c3y;
|
|
||||||
}
|
}
|
||||||
else {
|
// on failure, unwind the stack and dispose of intermediate nouns
|
||||||
// unwind the stack, disposing intermediate nouns
|
|
||||||
//
|
//
|
||||||
while ( tac_u.fil_w ) {
|
else if ( c3n == u3a_pile_done(&pil_u) ) {
|
||||||
_cue_frame_t* fam_u = &(tac_u.fam_u[--tac_u.fil_w]);
|
do {
|
||||||
|
|
||||||
if ( u3_none != fam_u->ref ) {
|
if ( u3_none != fam_u->ref ) {
|
||||||
u3z(fam_u->ref);
|
u3z(fam_u->ref);
|
||||||
}
|
}
|
||||||
|
fam_u = u3a_pop(&pil_u);
|
||||||
|
}
|
||||||
|
while ( c3n == u3a_pile_done(&pil_u) );
|
||||||
}
|
}
|
||||||
|
|
||||||
c3_free(tac_u.fam_u);
|
return u3_none;
|
||||||
return c3n;
|
|
||||||
}
|
|
||||||
}
|
}
|
||||||
|
|
||||||
/* u3s_cue_xeno(): cue onto the loom, bookkeeping off the loom.
|
/* u3s_cue_xeno_init_with(): initialize a cue_xeno handle as specified.
|
||||||
*/
|
*/
|
||||||
c3_o
|
u3_cue_xeno*
|
||||||
u3s_cue_xeno(c3_d len_d, const c3_y* byt_y, u3_noun* out)
|
u3s_cue_xeno_init_with(c3_d pre_d, c3_d siz_d)
|
||||||
{
|
{
|
||||||
ur_dict32_t dic_u = {0};
|
u3_cue_xeno* sil_u;
|
||||||
c3_o ret_o;
|
|
||||||
|
|
||||||
c3_assert( &(u3H->rod_u) == u3R );
|
c3_assert( &(u3H->rod_u) == u3R );
|
||||||
|
|
||||||
// XX tune the initial dictionary size for less reallocation
|
sil_u = c3_calloc(sizeof(*sil_u));
|
||||||
//
|
ur_dict32_grow((ur_root_t*)0, &sil_u->dic_u, pre_d, siz_d);
|
||||||
ur_dict32_grow((ur_root_t*)0, &dic_u, ur_fib10, ur_fib11);
|
|
||||||
|
|
||||||
ret_o = u3s_cue_xeno_unsafe(&dic_u, len_d, byt_y, out);
|
return sil_u;
|
||||||
|
}
|
||||||
|
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
/* u3s_cue_xeno_init(): initialize a cue_xeno handle.
|
||||||
|
*/
|
||||||
|
u3_cue_xeno*
|
||||||
|
u3s_cue_xeno_init(void)
|
||||||
|
{
|
||||||
|
return u3s_cue_xeno_init_with(ur_fib10, ur_fib11);
|
||||||
|
}
|
||||||
|
|
||||||
return ret_o;
|
/* u3s_cue_xeno_init(): cue on-loom, with off-loom dictionary in handle.
|
||||||
|
*/
|
||||||
|
u3_weak
|
||||||
|
u3s_cue_xeno_with(u3_cue_xeno* sil_u,
|
||||||
|
c3_d len_d,
|
||||||
|
const c3_y* byt_y)
|
||||||
|
{
|
||||||
|
u3_weak som;
|
||||||
|
|
||||||
|
c3_assert( &(u3H->rod_u) == u3R );
|
||||||
|
|
||||||
|
som = _cs_cue_xeno(sil_u, len_d, byt_y);
|
||||||
|
ur_dict32_wipe(&sil_u->dic_u);
|
||||||
|
return som;
|
||||||
|
}
|
||||||
|
|
||||||
|
/* u3s_cue_xeno_init(): dispose cue_xeno handle.
|
||||||
|
*/
|
||||||
|
void
|
||||||
|
u3s_cue_xeno_done(u3_cue_xeno* sil_u)
|
||||||
|
{
|
||||||
|
ur_dict_free((ur_dict_t*)&sil_u->dic_u);
|
||||||
|
c3_free(sil_u);
|
||||||
|
}
|
||||||
|
|
||||||
|
/* u3s_cue_xeno(): cue on-loom, with off-loom dictionary.
|
||||||
|
*/
|
||||||
|
u3_weak
|
||||||
|
u3s_cue_xeno(c3_d len_d,
|
||||||
|
const c3_y* byt_y)
|
||||||
|
{
|
||||||
|
u3_cue_xeno* sil_u;
|
||||||
|
u3_weak som;
|
||||||
|
|
||||||
|
c3_assert( &(u3H->rod_u) == u3R );
|
||||||
|
|
||||||
|
sil_u = u3s_cue_xeno_init();
|
||||||
|
som = _cs_cue_xeno(sil_u, len_d, byt_y);
|
||||||
|
u3s_cue_xeno_done(sil_u);
|
||||||
|
return som;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* _cs_cue_need(): bail on ur_cue_* read failures.
|
/* _cs_cue_need(): bail on ur_cue_* read failures.
|
||||||
@ -759,11 +788,10 @@ _cs_cue_put(u3p(u3h_root) har_p, c3_d key_d, u3_noun val)
|
|||||||
return val;
|
return val;
|
||||||
}
|
}
|
||||||
|
|
||||||
/* _cs_cue_full_next(): read next value from bitstream.
|
/* _cs_cue_bytes_next(): read next value from bitstream.
|
||||||
*/
|
*/
|
||||||
static inline u3_noun
|
static inline u3_noun
|
||||||
_cs_cue_full_next(c3_ys mov,
|
_cs_cue_bytes_next(u3a_pile* pil_u,
|
||||||
c3_ys off,
|
|
||||||
u3p(u3h_root) har_p,
|
u3p(u3h_root) har_p,
|
||||||
ur_bsr_t* red_u)
|
ur_bsr_t* red_u)
|
||||||
{
|
{
|
||||||
@ -777,31 +805,11 @@ _cs_cue_full_next(c3_ys mov,
|
|||||||
default: c3_assert(0);
|
default: c3_assert(0);
|
||||||
|
|
||||||
case ur_jam_cell: {
|
case ur_jam_cell: {
|
||||||
// wind the stack
|
_cue_frame_t* fam_u = u3a_push(pil_u);
|
||||||
//
|
u3a_pile_sane(pil_u);
|
||||||
u3R->cap_p += mov;
|
|
||||||
|
|
||||||
// ensure we haven't overflowed (ie, run into the heap)
|
|
||||||
// (off==0 means we're on a north road)
|
|
||||||
//
|
|
||||||
if ( 0 == off ) {
|
|
||||||
if( !(u3R->cap_p > u3R->hat_p) ) {
|
|
||||||
u3m_bail(c3__meme);
|
|
||||||
}
|
|
||||||
}
|
|
||||||
else {
|
|
||||||
if( !(u3R->cap_p < u3R->hat_p) ) {
|
|
||||||
u3m_bail(c3__meme);
|
|
||||||
}
|
|
||||||
}
|
|
||||||
|
|
||||||
// save a head-frame and read the head from the stream
|
|
||||||
//
|
|
||||||
{
|
|
||||||
_cue_frame_t* fam_u = u3to(_cue_frame_t, u3R->cap_p + off);
|
|
||||||
fam_u->ref = u3_none;
|
fam_u->ref = u3_none;
|
||||||
fam_u->bit_d = bit_d;
|
fam_u->bit_d = bit_d;
|
||||||
}
|
|
||||||
continue;
|
continue;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -846,22 +854,18 @@ u3_noun
|
|||||||
u3s_cue_bytes(c3_d len_d, const c3_y* byt_y)
|
u3s_cue_bytes(c3_d len_d, const c3_y* byt_y)
|
||||||
{
|
{
|
||||||
ur_bsr_t red_u = {0};
|
ur_bsr_t red_u = {0};
|
||||||
|
u3a_pile pil_u;
|
||||||
|
_cue_frame_t* fam_u;
|
||||||
|
u3p(u3h_root) har_p;
|
||||||
u3_noun ref;
|
u3_noun ref;
|
||||||
|
|
||||||
|
// initialize stack control
|
||||||
|
//
|
||||||
|
u3a_pile_prep(&pil_u, sizeof(*fam_u));
|
||||||
|
|
||||||
// initialize a hash table for dereferencing backrefs
|
// initialize a hash table for dereferencing backrefs
|
||||||
//
|
//
|
||||||
u3p(u3h_root) har_p = u3h_new();
|
har_p = u3h_new();
|
||||||
const u3_post top_p = u3R->cap_p;
|
|
||||||
|
|
||||||
// initialize signed stack offsets (relative to north/south road)
|
|
||||||
//
|
|
||||||
c3_ys mov, off;
|
|
||||||
{
|
|
||||||
c3_o nor_o = u3a_is_north(u3R);
|
|
||||||
c3_y wis_y = c3_wiseof(_cue_frame_t);
|
|
||||||
mov = ( c3y == nor_o ? -wis_y : wis_y );
|
|
||||||
off = ( c3y == nor_o ? 0 : -wis_y );
|
|
||||||
}
|
|
||||||
|
|
||||||
// init bitstream-reader
|
// init bitstream-reader
|
||||||
//
|
//
|
||||||
@ -875,29 +879,31 @@ u3s_cue_bytes(c3_d len_d, const c3_y* byt_y)
|
|||||||
|
|
||||||
// advance into stream
|
// advance into stream
|
||||||
//
|
//
|
||||||
ref = _cs_cue_full_next(mov, off, har_p, &red_u);
|
ref = _cs_cue_bytes_next(&pil_u, har_p, &red_u);
|
||||||
|
|
||||||
// process result
|
// process cell results
|
||||||
//
|
//
|
||||||
while ( top_p != u3R->cap_p ) {
|
if ( c3n == u3a_pile_done(&pil_u) ) {
|
||||||
// peek at the top of the stack
|
fam_u = u3a_peek(&pil_u);
|
||||||
//
|
|
||||||
_cue_frame_t* fam_u = u3to(_cue_frame_t, u3R->cap_p + off);
|
|
||||||
|
|
||||||
|
do {
|
||||||
// f is a head-frame; stash result and read the tail from the stream
|
// f is a head-frame; stash result and read the tail from the stream
|
||||||
//
|
//
|
||||||
if ( u3_none == fam_u->ref ) {
|
if ( u3_none == fam_u->ref ) {
|
||||||
fam_u->ref = ref;
|
fam_u->ref = ref;
|
||||||
ref = _cs_cue_full_next(mov, off, har_p, &red_u);
|
ref = _cs_cue_bytes_next(&pil_u, har_p, &red_u);
|
||||||
|
fam_u = u3a_peek(&pil_u);
|
||||||
}
|
}
|
||||||
// f is a tail-frame; pop the stack and continue
|
// f is a tail-frame; pop the stack and continue
|
||||||
//
|
//
|
||||||
else {
|
else {
|
||||||
ref = u3nc(fam_u->ref, ref);
|
ref = u3nc(fam_u->ref, ref);
|
||||||
_cs_cue_put(har_p, fam_u->bit_d, ref);
|
_cs_cue_put(har_p, fam_u->bit_d, ref);
|
||||||
u3R->cap_p -= mov;
|
fam_u = u3a_pop(&pil_u);
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
while ( c3n == u3a_pile_done(&pil_u) );
|
||||||
|
}
|
||||||
|
|
||||||
u3h_free(har_p);
|
u3h_free(har_p);
|
||||||
|
|
||||||
|
@ -9,26 +9,6 @@
|
|||||||
#include "all.h"
|
#include "all.h"
|
||||||
#include "ur/ur.h"
|
#include "ur/ur.h"
|
||||||
|
|
||||||
/* _cu_met_3(): atom bytewidth a la u3r_met(3, ...)
|
|
||||||
*/
|
|
||||||
static inline c3_w
|
|
||||||
_cu_met_3(u3a_atom* vat_u)
|
|
||||||
{
|
|
||||||
c3_w len_w = vat_u->len_w;
|
|
||||||
c3_w* buf_w = vat_u->buf_w;
|
|
||||||
|
|
||||||
if ( !len_w ) {
|
|
||||||
return 0;
|
|
||||||
}
|
|
||||||
else {
|
|
||||||
c3_w gal_w = len_w - 1;
|
|
||||||
c3_w daz_w = buf_w[gal_w];
|
|
||||||
|
|
||||||
return (gal_w << 2)
|
|
||||||
+ ((daz_w >> 24) ? 4 : (daz_w >> 16) ? 3 : (daz_w >> 8) ? 2 : 1);
|
|
||||||
}
|
|
||||||
}
|
|
||||||
|
|
||||||
/* _cu_atom_to_ref(): allocate indirect atom off-loom.
|
/* _cu_atom_to_ref(): allocate indirect atom off-loom.
|
||||||
*/
|
*/
|
||||||
static inline ur_nref
|
static inline ur_nref
|
||||||
@ -860,23 +840,20 @@ u3u_uncram(c3_c* dir_c, c3_d eve_d)
|
|||||||
// XX errors are fatal, barring a full "u3m_reboot"-type operation.
|
// XX errors are fatal, barring a full "u3m_reboot"-type operation.
|
||||||
//
|
//
|
||||||
{
|
{
|
||||||
ur_dict32_t dic_u = {0};
|
|
||||||
u3_noun roc, cod, ref;
|
|
||||||
|
|
||||||
// XX tune the initial dictionary size for less reallocation
|
// XX tune the initial dictionary size for less reallocation
|
||||||
//
|
//
|
||||||
ur_dict32_grow((ur_root_t*)0, &dic_u, ur_fib33, ur_fib34);
|
u3_cue_xeno* sil_u = u3s_cue_xeno_init_with(ur_fib33, ur_fib34);
|
||||||
|
u3_weak ref = u3s_cue_xeno_with(sil_u, len_d, byt_y);
|
||||||
|
u3_noun roc, cod;
|
||||||
|
|
||||||
if ( c3n == u3s_cue_xeno_unsafe(&dic_u, len_d, byt_y, &ref) ) {
|
u3s_cue_xeno_done(sil_u);
|
||||||
|
|
||||||
|
if ( u3_none == ref ) {
|
||||||
fprintf(stderr, "uncram: failed to cue rock\r\n");
|
fprintf(stderr, "uncram: failed to cue rock\r\n");
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
|
||||||
c3_free(nam_c);
|
c3_free(nam_c);
|
||||||
return c3n;
|
return c3n;
|
||||||
}
|
}
|
||||||
|
else if ( c3n == u3r_pq(ref, c3__fast, &roc, &cod) ) {
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
|
||||||
|
|
||||||
if ( c3n == u3r_pq(ref, c3__fast, &roc, &cod) ) {
|
|
||||||
fprintf(stderr, "uncram: failed: invalid rock format\r\n");
|
fprintf(stderr, "uncram: failed: invalid rock format\r\n");
|
||||||
u3z(ref);
|
u3z(ref);
|
||||||
c3_free(nam_c);
|
c3_free(nam_c);
|
||||||
|
@ -367,12 +367,12 @@ _test_cue_spec(const c3_c* cap_c,
|
|||||||
c3_i ret_i = 1;
|
c3_i ret_i = 1;
|
||||||
|
|
||||||
{
|
{
|
||||||
ur_dict32_t dic_u = {0};
|
u3_noun pro = u3m_soft(0, u3s_cue_atom, u3i_bytes(len_w, byt_y));
|
||||||
u3_noun out;
|
u3_noun tag, out;
|
||||||
|
|
||||||
ur_dict32_grow((ur_root_t*)0, &dic_u, ur_fib10, ur_fib11);
|
u3x_cell(pro, &tag, &out);
|
||||||
|
|
||||||
if ( c3n == u3s_cue_xeno_unsafe(&dic_u, len_w, byt_y, &out) ) {
|
if ( u3_blip != tag ) {
|
||||||
fprintf(stderr, "\033[31mcue %s fail 1\033[0m\r\n", cap_c);
|
fprintf(stderr, "\033[31mcue %s fail 1\033[0m\r\n", cap_c);
|
||||||
ret_i = 0;
|
ret_i = 0;
|
||||||
}
|
}
|
||||||
@ -383,17 +383,13 @@ _test_cue_spec(const c3_c* cap_c,
|
|||||||
ret_i = 0;
|
ret_i = 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
u3z(out);
|
u3z(pro);
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
|
||||||
}
|
}
|
||||||
|
|
||||||
{
|
{
|
||||||
u3_noun pro = u3m_soft(0, u3s_cue_atom, u3i_bytes(len_w, byt_y));
|
u3_noun out;
|
||||||
u3_noun tag, out;
|
|
||||||
|
|
||||||
u3x_cell(pro, &tag, &out);
|
if ( u3_none == (out = u3s_cue_xeno(len_w, byt_y)) ) {
|
||||||
|
|
||||||
if ( u3_blip != tag ) {
|
|
||||||
fprintf(stderr, "\033[31mcue %s fail 3\033[0m\r\n", cap_c);
|
fprintf(stderr, "\033[31mcue %s fail 3\033[0m\r\n", cap_c);
|
||||||
ret_i = 0;
|
ret_i = 0;
|
||||||
}
|
}
|
||||||
@ -404,7 +400,7 @@ _test_cue_spec(const c3_c* cap_c,
|
|||||||
ret_i = 0;
|
ret_i = 0;
|
||||||
}
|
}
|
||||||
|
|
||||||
u3z(pro);
|
u3z(out);
|
||||||
}
|
}
|
||||||
|
|
||||||
return ret_i;
|
return ret_i;
|
||||||
|
@ -11,7 +11,7 @@
|
|||||||
** initialize helper for bitstream-writer tests.
|
** initialize helper for bitstream-writer tests.
|
||||||
*/
|
*/
|
||||||
static void
|
static void
|
||||||
_bsw_init(ur_bsw_t *bsw, uint64_t prev, uint64_t size)
|
_bsw_reinit(ur_bsw_t *bsw, uint64_t prev, uint64_t size)
|
||||||
{
|
{
|
||||||
bsw->prev = prev;
|
bsw->prev = prev;
|
||||||
bsw->size = size;
|
bsw->size = size;
|
||||||
@ -58,7 +58,7 @@ _test_bsw_bit_ones(void)
|
|||||||
{
|
{
|
||||||
int ret = 1;
|
int ret = 1;
|
||||||
ur_bsw_t bsw = {0};
|
ur_bsw_t bsw = {0};
|
||||||
_bsw_init(&bsw, 1, 1);
|
_bsw_reinit(&bsw, 1, 1);
|
||||||
|
|
||||||
ret &= _bsw_bit_check("bsw ones init", &bsw, 0x0, 0);
|
ret &= _bsw_bit_check("bsw ones init", &bsw, 0x0, 0);
|
||||||
|
|
||||||
@ -104,7 +104,7 @@ _test_bsw_bit_zeros(void)
|
|||||||
{
|
{
|
||||||
int ret = 1;
|
int ret = 1;
|
||||||
ur_bsw_t bsw = {0};
|
ur_bsw_t bsw = {0};
|
||||||
_bsw_init(&bsw, 1, 1);
|
_bsw_reinit(&bsw, 1, 1);
|
||||||
|
|
||||||
ret &= _bsw_bit_check("bsw zeros init", &bsw, 0x0, 0);
|
ret &= _bsw_bit_check("bsw zeros init", &bsw, 0x0, 0);
|
||||||
|
|
||||||
@ -150,7 +150,7 @@ _test_bsw_bit_alt(void)
|
|||||||
{
|
{
|
||||||
int ret = 1;
|
int ret = 1;
|
||||||
ur_bsw_t bsw = {0};
|
ur_bsw_t bsw = {0};
|
||||||
_bsw_init(&bsw, 1, 1);
|
_bsw_reinit(&bsw, 1, 1);
|
||||||
|
|
||||||
ret &= _bsw_bit_check("bsw alt init", &bsw, 0x0, 0);
|
ret &= _bsw_bit_check("bsw alt init", &bsw, 0x0, 0);
|
||||||
|
|
||||||
@ -286,8 +286,8 @@ _test_bsw8_loop(const char* cap, uint8_t val)
|
|||||||
|
|
||||||
for ( i = 0; i < 8; i++) {
|
for ( i = 0; i < 8; i++) {
|
||||||
for ( j = 0; j <= 8; j++ ) {
|
for ( j = 0; j <= 8; j++ ) {
|
||||||
_bsw_init(&a, 1, 1);
|
_bsw_reinit(&a, 1, 1);
|
||||||
_bsw_init(&b, 1, 1);
|
_bsw_reinit(&b, 1, 1);
|
||||||
a.off = a.bits = b.off = b.bits = i;
|
a.off = a.bits = b.off = b.bits = i;
|
||||||
|
|
||||||
_bsw8_slow(&a, j, val);
|
_bsw8_slow(&a, j, val);
|
||||||
@ -338,8 +338,8 @@ _test_bsw32_loop(const char* cap, uint32_t val)
|
|||||||
|
|
||||||
for ( i = 0; i < 8; i++) {
|
for ( i = 0; i < 8; i++) {
|
||||||
for ( j = 0; j <= 32; j++ ) {
|
for ( j = 0; j <= 32; j++ ) {
|
||||||
_bsw_init(&a, 1, 1);
|
_bsw_reinit(&a, 1, 1);
|
||||||
_bsw_init(&b, 1, 1);
|
_bsw_reinit(&b, 1, 1);
|
||||||
a.off = a.bits = b.off = b.bits = i;
|
a.off = a.bits = b.off = b.bits = i;
|
||||||
|
|
||||||
_bsw32_slow(&a, j, val);
|
_bsw32_slow(&a, j, val);
|
||||||
@ -390,8 +390,8 @@ _test_bsw64_loop(const char* cap, uint64_t val)
|
|||||||
|
|
||||||
for ( i = 0; i < 8; i++) {
|
for ( i = 0; i < 8; i++) {
|
||||||
for ( j = 0; j <= 64; j++ ) {
|
for ( j = 0; j <= 64; j++ ) {
|
||||||
_bsw_init(&a, 1, 1);
|
_bsw_reinit(&a, 1, 1);
|
||||||
_bsw_init(&b, 1, 1);
|
_bsw_reinit(&b, 1, 1);
|
||||||
a.off = a.bits = b.off = b.bits = i;
|
a.off = a.bits = b.off = b.bits = i;
|
||||||
|
|
||||||
_bsw64_slow(&a, j, val);
|
_bsw64_slow(&a, j, val);
|
||||||
@ -447,8 +447,8 @@ _test_bsw_bytes_loop(const char* cap, uint64_t len, uint8_t val)
|
|||||||
|
|
||||||
for ( i = 0; i < 8; i++) {
|
for ( i = 0; i < 8; i++) {
|
||||||
for ( j = 0; j < len_bit; j++ ) {
|
for ( j = 0; j < len_bit; j++ ) {
|
||||||
_bsw_init(&a, 1, 1);
|
_bsw_reinit(&a, 1, 1);
|
||||||
_bsw_init(&b, 1, 1);
|
_bsw_reinit(&b, 1, 1);
|
||||||
a.off = a.bits = b.off = b.bits = i;
|
a.off = a.bits = b.off = b.bits = i;
|
||||||
|
|
||||||
_bsw_bytes_slow(&a, j, byt);
|
_bsw_bytes_slow(&a, j, byt);
|
||||||
@ -501,13 +501,13 @@ _test_bsw_bex()
|
|||||||
int ret = 1;
|
int ret = 1;
|
||||||
ur_bsw_t a = {0};
|
ur_bsw_t a = {0};
|
||||||
ur_bsw_t b = {0};
|
ur_bsw_t b = {0};
|
||||||
uint8_t i, l;
|
uint8_t i;
|
||||||
uint32_t j, k;
|
uint32_t j;
|
||||||
|
|
||||||
for ( i = 0; i < 8; i++) {
|
for ( i = 0; i < 8; i++) {
|
||||||
for ( j = 0; j < 256; j++ ) {
|
for ( j = 0; j < 256; j++ ) {
|
||||||
_bsw_init(&a, 1, 1);
|
_bsw_reinit(&a, 1, 1);
|
||||||
_bsw_init(&b, 1, 1);
|
_bsw_reinit(&b, 1, 1);
|
||||||
a.off = a.bits = b.off = b.bits = i;
|
a.off = a.bits = b.off = b.bits = i;
|
||||||
|
|
||||||
_bsw_bex_slow(&a, j);
|
_bsw_bex_slow(&a, j);
|
||||||
@ -1363,7 +1363,7 @@ _test_bsr_skip_any_loop(const char *cap, uint8_t len, uint8_t val)
|
|||||||
uint64_t max = (len << 3) + 7;
|
uint64_t max = (len << 3) + 7;
|
||||||
ur_bsr_t a, b;
|
ur_bsr_t a, b;
|
||||||
uint8_t *bytes, *c;
|
uint8_t *bytes, *c;
|
||||||
uint8_t i, j, k;
|
uint8_t i, j;
|
||||||
|
|
||||||
c = malloc(1 + len);
|
c = malloc(1 + len);
|
||||||
bytes = malloc(len);
|
bytes = malloc(len);
|
||||||
@ -1510,7 +1510,7 @@ _test_bsr_log_loop(const char *cap, uint8_t len, uint8_t val)
|
|||||||
int ret = 1;
|
int ret = 1;
|
||||||
ur_bsr_t a, b;
|
ur_bsr_t a, b;
|
||||||
uint8_t *bytes, c, d;
|
uint8_t *bytes, c, d;
|
||||||
uint8_t i, j, k;
|
uint8_t i, j;
|
||||||
ur_cue_res_e e, f;
|
ur_cue_res_e e, f;
|
||||||
|
|
||||||
bytes = malloc(len);
|
bytes = malloc(len);
|
||||||
@ -1602,7 +1602,7 @@ _test_bsr_tag_loop(const char *cap, uint8_t len, uint8_t val)
|
|||||||
ur_bsr_t a, b;
|
ur_bsr_t a, b;
|
||||||
uint8_t *bytes;
|
uint8_t *bytes;
|
||||||
ur_cue_tag_e c, d;
|
ur_cue_tag_e c, d;
|
||||||
uint8_t i, j, k;
|
uint8_t i, j;
|
||||||
ur_cue_res_e e, f;
|
ur_cue_res_e e, f;
|
||||||
|
|
||||||
bytes = malloc(len);
|
bytes = malloc(len);
|
||||||
|
@ -615,7 +615,6 @@ ur_bsr_log(ur_bsr_t *bsr, uint8_t *out)
|
|||||||
}
|
}
|
||||||
else {
|
else {
|
||||||
uint8_t off = bsr->off;
|
uint8_t off = bsr->off;
|
||||||
uint8_t rest = 8 - off;
|
|
||||||
const uint8_t *b = bsr->bytes;
|
const uint8_t *b = bsr->bytes;
|
||||||
uint8_t byt = b[0] >> off;
|
uint8_t byt = b[0] >> off;
|
||||||
uint8_t skip = 0;
|
uint8_t skip = 0;
|
||||||
@ -625,13 +624,11 @@ ur_bsr_log(ur_bsr_t *bsr, uint8_t *out)
|
|||||||
return _bsr_log_meme(bsr);
|
return _bsr_log_meme(bsr);
|
||||||
}
|
}
|
||||||
|
|
||||||
skip++;
|
byt = b[++skip];
|
||||||
|
|
||||||
if ( skip == left ) {
|
if ( skip == left ) {
|
||||||
return _bsr_set_gone(bsr, (skip << 3) - off);
|
return _bsr_set_gone(bsr, (skip << 3) - off);
|
||||||
}
|
}
|
||||||
|
|
||||||
byt = b[skip];
|
|
||||||
}
|
}
|
||||||
|
|
||||||
{
|
{
|
||||||
@ -702,6 +699,20 @@ ur_bsr_rub_len(ur_bsr_t *bsr, uint64_t *out)
|
|||||||
** of reallocating the output buffer.
|
** of reallocating the output buffer.
|
||||||
*/
|
*/
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_bsw_init(ur_bsw_t *bsw, uint64_t prev, uint64_t size)
|
||||||
|
{
|
||||||
|
bsw->prev = prev;
|
||||||
|
bsw->size = size;
|
||||||
|
bsw->bytes = calloc(size, 1);
|
||||||
|
|
||||||
|
if ( !bsw->bytes ) {
|
||||||
|
fprintf(stderr,
|
||||||
|
"ur: bitstream-init allocation failed, out of memory\r\n");
|
||||||
|
abort();
|
||||||
|
}
|
||||||
|
}
|
||||||
|
|
||||||
void
|
void
|
||||||
ur_bsw_grow(ur_bsw_t *bsw, uint64_t step)
|
ur_bsw_grow(ur_bsw_t *bsw, uint64_t step)
|
||||||
{
|
{
|
||||||
@ -729,6 +740,19 @@ ur_bsw_sane(ur_bsw_t *bsw)
|
|||||||
&& ((bsw->fill << 3) + bsw->off == bsw->bits) );
|
&& ((bsw->fill << 3) + bsw->off == bsw->bits) );
|
||||||
}
|
}
|
||||||
|
|
||||||
|
uint64_t
|
||||||
|
ur_bsw_done(ur_bsw_t *bsw, uint64_t *len, uint8_t **byt)
|
||||||
|
{
|
||||||
|
uint64_t bits = bsw->bits;
|
||||||
|
|
||||||
|
*len = bsw->fill + !!bsw->off;
|
||||||
|
*byt = bsw->bytes;
|
||||||
|
|
||||||
|
memset(bsw, 0, sizeof(*bsw));
|
||||||
|
|
||||||
|
return bits;
|
||||||
|
}
|
||||||
|
|
||||||
static inline void
|
static inline void
|
||||||
_bsw_bit_unsafe(ur_bsw_t *bsw, uint8_t bit)
|
_bsw_bit_unsafe(ur_bsw_t *bsw, uint8_t bit)
|
||||||
{
|
{
|
||||||
|
@ -526,17 +526,14 @@ ur_met(ur_root_t *r, uint8_t bloq, ur_nref ref)
|
|||||||
case 0: return m_bit;
|
case 0: return m_bit;
|
||||||
case 1: return ur_bloq_up1(m_bit);
|
case 1: return ur_bloq_up1(m_bit);
|
||||||
case 2: return ur_bloq_up2(m_bit);
|
case 2: return ur_bloq_up2(m_bit);
|
||||||
|
case 3: return ur_bloq_up3(m_bit);
|
||||||
|
|
||||||
{
|
|
||||||
uint64_t m_byt = ur_bloq_up3(m_bit);
|
|
||||||
|
|
||||||
case 3: return m_byt;
|
|
||||||
default: {
|
default: {
|
||||||
|
uint64_t m_byt = ur_bloq_up3(m_bit);
|
||||||
uint8_t off = (bloq - 3);
|
uint8_t off = (bloq - 3);
|
||||||
return (m_byt + ((1ULL << off) - 1)) >> off;
|
return (m_byt + ((1ULL << off) - 1)) >> off;
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
}
|
|
||||||
}
|
}
|
||||||
|
|
||||||
static ur_nref
|
static ur_nref
|
||||||
@ -894,6 +891,93 @@ ur_nvec_init(ur_nvec_t *v, uint64_t size)
|
|||||||
v->refs = _oom("nvec_init", calloc(size, sizeof(ur_nref)));
|
v->refs = _oom("nvec_init", calloc(size, sizeof(ur_nref)));
|
||||||
}
|
}
|
||||||
|
|
||||||
|
/*
|
||||||
|
** define opaque struct ur_walk_fore_s (ie, ur_walk_fore_t)
|
||||||
|
*/
|
||||||
|
struct ur_walk_fore_s {
|
||||||
|
ur_root_t *r;
|
||||||
|
uint32_t prev;
|
||||||
|
uint32_t size;
|
||||||
|
uint32_t fill;
|
||||||
|
ur_nref *top;
|
||||||
|
};
|
||||||
|
|
||||||
|
ur_walk_fore_t*
|
||||||
|
ur_walk_fore_init_with(ur_root_t *r,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size)
|
||||||
|
{
|
||||||
|
ur_walk_fore_t *w = _oom("walk_fore", malloc(sizeof(*w)));
|
||||||
|
w->top = _oom("walk_fore", malloc(s_size * sizeof(*w->top)));
|
||||||
|
w->prev = s_prev;
|
||||||
|
w->size = s_size;
|
||||||
|
w->fill = 0;
|
||||||
|
w->r = r;
|
||||||
|
|
||||||
|
return w;
|
||||||
|
}
|
||||||
|
|
||||||
|
ur_walk_fore_t*
|
||||||
|
ur_walk_fore_init(ur_root_t *r)
|
||||||
|
{
|
||||||
|
return ur_walk_fore_init_with(r, ur_fib10, ur_fib11);
|
||||||
|
}
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_walk_fore_with(ur_walk_fore_t *w,
|
||||||
|
ur_nref ref,
|
||||||
|
void *v,
|
||||||
|
void (*atom)(ur_root_t*, ur_nref, void*),
|
||||||
|
ur_bool_t (*cell)(ur_root_t*, ur_nref, void*))
|
||||||
|
{
|
||||||
|
ur_root_t *r = w->r;
|
||||||
|
ur_nref *don = w->top;
|
||||||
|
|
||||||
|
w->top += ++w->fill;
|
||||||
|
*w->top = ref;
|
||||||
|
|
||||||
|
while ( w->top != don ) {
|
||||||
|
// visit atom, pop stack
|
||||||
|
//
|
||||||
|
if ( !ur_deep(ref) ) {
|
||||||
|
atom(r, ref, v);
|
||||||
|
w->top--; w->fill--;
|
||||||
|
}
|
||||||
|
// visit cell, pop stack if false
|
||||||
|
//
|
||||||
|
else if ( !cell(r, ref, v) ) {
|
||||||
|
w->top--; w->fill--;
|
||||||
|
}
|
||||||
|
// push the tail, continue into the head
|
||||||
|
//
|
||||||
|
else {
|
||||||
|
*w->top = ur_tail(r, ref);
|
||||||
|
|
||||||
|
// reallocate "stack" if full
|
||||||
|
//
|
||||||
|
if ( w->size == w->fill ) {
|
||||||
|
uint32_t next = w->prev + w->size;
|
||||||
|
don = _oom("walk_fore", realloc(don, next * sizeof(*don)));
|
||||||
|
w->top = don + w->fill;
|
||||||
|
w->prev = w->size;
|
||||||
|
w->size = next;
|
||||||
|
}
|
||||||
|
|
||||||
|
w->top++; w->fill++;
|
||||||
|
*w->top = ur_head(r, ref);
|
||||||
|
}
|
||||||
|
|
||||||
|
ref = *w->top;
|
||||||
|
}
|
||||||
|
}
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_walk_fore_done(ur_walk_fore_t *w)
|
||||||
|
{
|
||||||
|
free(w->top);
|
||||||
|
free(w);
|
||||||
|
}
|
||||||
|
|
||||||
void
|
void
|
||||||
ur_walk_fore(ur_root_t *r,
|
ur_walk_fore(ur_root_t *r,
|
||||||
ur_nref ref,
|
ur_nref ref,
|
||||||
@ -901,46 +985,7 @@ ur_walk_fore(ur_root_t *r,
|
|||||||
void (*atom)(ur_root_t*, ur_nref, void*),
|
void (*atom)(ur_root_t*, ur_nref, void*),
|
||||||
ur_bool_t (*cell)(ur_root_t*, ur_nref, void*))
|
ur_bool_t (*cell)(ur_root_t*, ur_nref, void*))
|
||||||
{
|
{
|
||||||
uint64_t prev = ur_fib11, size = ur_fib12, fill = 0;
|
ur_walk_fore_t *w = ur_walk_fore_init(r);
|
||||||
ur_nref *top, *don;
|
ur_walk_fore_with(w, ref, v, atom, cell);
|
||||||
|
ur_walk_fore_done(w);
|
||||||
don = _oom("walk_fore", malloc(size * sizeof(*don)));
|
|
||||||
top = don + ++fill;
|
|
||||||
*top = ref;
|
|
||||||
|
|
||||||
while ( top != don ) {
|
|
||||||
// visit atom, pop stack
|
|
||||||
//
|
|
||||||
if ( !ur_deep(ref) ) {
|
|
||||||
atom(r, ref, v);
|
|
||||||
top--; fill--;
|
|
||||||
}
|
|
||||||
// visit cell, pop stack if false
|
|
||||||
//
|
|
||||||
else if ( !cell(r, ref, v) ) {
|
|
||||||
top--; fill--;
|
|
||||||
}
|
|
||||||
// push the tail, continue into the head
|
|
||||||
//
|
|
||||||
else {
|
|
||||||
*top = ur_tail(r, ref);
|
|
||||||
|
|
||||||
// reallocate "stack" if full
|
|
||||||
//
|
|
||||||
if ( size == fill ) {
|
|
||||||
uint64_t next = prev + size;
|
|
||||||
don = _oom("walk_fore", realloc(don, next * sizeof(*don)));
|
|
||||||
top = don + fill;
|
|
||||||
prev = size;
|
|
||||||
size = next;
|
|
||||||
}
|
|
||||||
|
|
||||||
top++; fill++;
|
|
||||||
*top = ur_head(r, ref);
|
|
||||||
}
|
|
||||||
|
|
||||||
ref = *top;
|
|
||||||
}
|
|
||||||
|
|
||||||
free(don);
|
|
||||||
}
|
}
|
||||||
|
@ -30,16 +30,21 @@ _bsw_atom(ur_root_t *r, ur_nref ref, ur_bsw_t *bsw, uint64_t len)
|
|||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
typedef struct _jam_s {
|
/*
|
||||||
ur_dict64_t *dict;
|
** define opaque struct ur_jam_s (ie, ur_jam_t)
|
||||||
|
*/
|
||||||
|
struct ur_jam_s {
|
||||||
|
ur_root_t *r;
|
||||||
|
ur_walk_fore_t *w;
|
||||||
|
ur_dict64_t dict;
|
||||||
ur_bsw_t bsw;
|
ur_bsw_t bsw;
|
||||||
} _jam_t;
|
};
|
||||||
|
|
||||||
static void
|
static void
|
||||||
_jam_atom(ur_root_t *r, ur_nref ref, void *ptr)
|
_jam_atom(ur_root_t *r, ur_nref ref, void *ptr)
|
||||||
{
|
{
|
||||||
_jam_t *j = ptr;
|
ur_jam_t *j = ptr;
|
||||||
ur_dict64_t *dict = j->dict;
|
ur_dict64_t *dict = &j->dict;
|
||||||
ur_bsw_t *bsw = &j->bsw;
|
ur_bsw_t *bsw = &j->bsw;
|
||||||
uint64_t bak, len = ur_met(r, 0, ref);
|
uint64_t bak, len = ur_met(r, 0, ref);
|
||||||
|
|
||||||
@ -63,8 +68,8 @@ _jam_atom(ur_root_t *r, ur_nref ref, void *ptr)
|
|||||||
static ur_bool_t
|
static ur_bool_t
|
||||||
_jam_cell(ur_root_t *r, ur_nref ref, void *ptr)
|
_jam_cell(ur_root_t *r, ur_nref ref, void *ptr)
|
||||||
{
|
{
|
||||||
_jam_t *j = ptr;
|
ur_jam_t *j = ptr;
|
||||||
ur_dict64_t *dict = j->dict;
|
ur_dict64_t *dict = &j->dict;
|
||||||
ur_bsw_t *bsw = &j->bsw;
|
ur_bsw_t *bsw = &j->bsw;
|
||||||
uint64_t bak;
|
uint64_t bak;
|
||||||
|
|
||||||
@ -80,40 +85,69 @@ _jam_cell(ur_root_t *r, ur_nref ref, void *ptr)
|
|||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
uint64_t
|
static uint64_t
|
||||||
ur_jam_unsafe(ur_root_t *r,
|
_jam(ur_jam_t *j,
|
||||||
ur_nref ref,
|
ur_nref ref,
|
||||||
ur_dict64_t *dict,
|
|
||||||
uint64_t *len,
|
uint64_t *len,
|
||||||
uint8_t **byt)
|
uint8_t **byt)
|
||||||
{
|
{
|
||||||
_jam_t j = {0};
|
ur_bsw_init(&j->bsw, ur_fib11, ur_fib12);
|
||||||
|
ur_walk_fore_with(j->w, ref, j, _jam_atom, _jam_cell);
|
||||||
|
return ur_bsw_done(&j->bsw, len, byt);
|
||||||
|
}
|
||||||
|
|
||||||
j.dict = dict;
|
ur_jam_t*
|
||||||
|
ur_jam_init_with(ur_root_t *r,
|
||||||
|
uint64_t d_prev,
|
||||||
|
uint64_t d_size,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size)
|
||||||
|
{
|
||||||
|
ur_jam_t *j = _oom("jam_init", calloc(sizeof(*j), 1));
|
||||||
|
j->w = ur_walk_fore_init_with(r, s_prev, s_size);
|
||||||
|
j->r = r;
|
||||||
|
|
||||||
j.bsw.prev = ur_fib11;
|
ur_dict64_grow(r, &j->dict, d_prev, d_size);
|
||||||
j.bsw.size = ur_fib12;
|
|
||||||
j.bsw.bytes = _oom("jam", calloc(j.bsw.size, 1));
|
|
||||||
|
|
||||||
ur_walk_fore(r, ref, &j, _jam_atom, _jam_cell);
|
return j;
|
||||||
|
}
|
||||||
|
|
||||||
*len = j.bsw.fill + !!j.bsw.off;
|
ur_jam_t*
|
||||||
*byt = j.bsw.bytes;
|
ur_jam_init(ur_root_t *r)
|
||||||
|
{
|
||||||
return j.bsw.bits;
|
return ur_jam_init_with(r, ur_fib11, ur_fib12, // dict sizes
|
||||||
|
ur_fib10, ur_fib11); // stack sizes
|
||||||
}
|
}
|
||||||
|
|
||||||
uint64_t
|
uint64_t
|
||||||
ur_jam(ur_root_t *r, ur_nref ref, uint64_t *len, uint8_t **byt)
|
ur_jam_with(ur_jam_t *j,
|
||||||
|
ur_nref ref,
|
||||||
|
uint64_t *len,
|
||||||
|
uint8_t **byt)
|
||||||
{
|
{
|
||||||
ur_dict64_t dict = {0};
|
uint64_t bits = _jam(j, ref, len, byt);
|
||||||
ur_dict64_grow(r, &dict, ur_fib11, ur_fib12);
|
ur_dict64_wipe(&j->dict);
|
||||||
|
return bits;
|
||||||
{
|
}
|
||||||
uint64_t bits = ur_jam_unsafe(r, ref, &dict, len, byt);
|
|
||||||
ur_dict_free((ur_dict_t*)&dict);
|
void
|
||||||
|
ur_jam_done(ur_jam_t *j)
|
||||||
|
{
|
||||||
|
ur_dict_free((ur_dict_t*)&j->dict);
|
||||||
|
free(j->w);
|
||||||
|
free(j);
|
||||||
|
}
|
||||||
|
|
||||||
|
uint64_t
|
||||||
|
ur_jam(ur_root_t *r,
|
||||||
|
ur_nref ref,
|
||||||
|
uint64_t *len,
|
||||||
|
uint8_t **byt)
|
||||||
|
{
|
||||||
|
ur_jam_t *j = ur_jam_init(r);
|
||||||
|
uint64_t bits = _jam(j, ref, len, byt);
|
||||||
|
ur_jam_done(j);
|
||||||
return bits;
|
return bits;
|
||||||
}
|
|
||||||
}
|
}
|
||||||
|
|
||||||
/*
|
/*
|
||||||
@ -224,15 +258,25 @@ _cue_next(ur_root_t *r,
|
|||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_cue_res_e
|
/*
|
||||||
ur_cue_unsafe(ur_root_t *r,
|
** define opaque struct ur_cue_s (ie, ur_cue_t)
|
||||||
ur_dict64_t *dict,
|
*/
|
||||||
|
struct ur_cue_s {
|
||||||
|
ur_root_t *r;
|
||||||
|
_cue_stack_t s;
|
||||||
|
ur_dict64_t dict;
|
||||||
|
};
|
||||||
|
|
||||||
|
static ur_cue_res_e
|
||||||
|
_cue(ur_cue_t *c,
|
||||||
uint64_t len,
|
uint64_t len,
|
||||||
const uint8_t *byt,
|
const uint8_t *byt,
|
||||||
ur_nref *out)
|
ur_nref *out)
|
||||||
{
|
{
|
||||||
ur_bsr_t bsr = {0};
|
ur_bsr_t bsr = {0};
|
||||||
_cue_stack_t s = {0};
|
ur_root_t *r = c->r;
|
||||||
|
_cue_stack_t *s = &c->s;
|
||||||
|
ur_dict64_t *dict = &c->dict;
|
||||||
ur_cue_res_e res;
|
ur_cue_res_e res;
|
||||||
ur_nref ref;
|
ur_nref ref;
|
||||||
|
|
||||||
@ -247,58 +291,99 @@ ur_cue_unsafe(ur_root_t *r,
|
|||||||
return ur_cue_meme;
|
return ur_cue_meme;
|
||||||
}
|
}
|
||||||
|
|
||||||
// setup stack
|
|
||||||
//
|
|
||||||
s.prev = ur_fib10;
|
|
||||||
s.size = ur_fib11;
|
|
||||||
s.f = _oom("cue stack", malloc(s.size * sizeof(*s.f)));
|
|
||||||
|
|
||||||
// advance into stream
|
// advance into stream
|
||||||
//
|
//
|
||||||
res = _cue_next(r, &s, &bsr, dict, &ref);
|
res = _cue_next(r, s, &bsr, dict, &ref);
|
||||||
|
|
||||||
// process result
|
// process result
|
||||||
//
|
//
|
||||||
while ( s.fill && (ur_cue_good == res) ) {
|
while ( s->fill && (ur_cue_good == res) ) {
|
||||||
// peek at the top of the stack
|
// peek at the top of the stack
|
||||||
//
|
//
|
||||||
_cue_frame_t *f = &(s.f[s.fill - 1]);
|
_cue_frame_t *f = &(s->f[s->fill - 1]);
|
||||||
|
|
||||||
// f is a head-frame; stash result and read the tail from the stream
|
// f is a head-frame; stash result and read the tail from the stream
|
||||||
//
|
//
|
||||||
if ( CUE_HEAD == f->ref ) {
|
if ( CUE_HEAD == f->ref ) {
|
||||||
f->ref = ref;
|
f->ref = ref;
|
||||||
res = _cue_next(r, &s, &bsr, dict, &ref);
|
res = _cue_next(r, s, &bsr, dict, &ref);
|
||||||
}
|
}
|
||||||
// f is a tail-frame; pop the stack and continue
|
// f is a tail-frame; pop the stack and continue
|
||||||
//
|
//
|
||||||
else {
|
else {
|
||||||
ref = ur_cons(r, f->ref, ref);
|
ref = ur_cons(r, f->ref, ref);
|
||||||
ur_dict64_put(r, dict, f->bits, (uint64_t)ref);
|
ur_dict64_put(r, dict, f->bits, (uint64_t)ref);
|
||||||
s.fill--;
|
s->fill--;
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
free(s.f);
|
|
||||||
|
|
||||||
if ( ur_cue_good == res ) {
|
if ( ur_cue_good == res ) {
|
||||||
*out = ref;
|
*out = ref;
|
||||||
}
|
}
|
||||||
return res;
|
return res;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
ur_cue_t*
|
||||||
|
ur_cue_init_with(ur_root_t *r,
|
||||||
|
uint64_t d_prev,
|
||||||
|
uint64_t d_size,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size)
|
||||||
|
{
|
||||||
|
ur_cue_t* c = _oom("cue_init", calloc(sizeof(*c), 1));
|
||||||
|
c->r = r;
|
||||||
|
|
||||||
|
ur_dict64_grow(r, &c->dict, d_prev, d_size);
|
||||||
|
|
||||||
|
c->s.prev = s_prev;
|
||||||
|
c->s.size = s_size;
|
||||||
|
c->s.f = _oom("cue_test_init", malloc(s_size * sizeof(*c->s.f)));
|
||||||
|
|
||||||
|
return c;
|
||||||
|
}
|
||||||
|
|
||||||
|
ur_cue_t*
|
||||||
|
ur_cue_init(ur_root_t *r)
|
||||||
|
{
|
||||||
|
return ur_cue_init_with(r, ur_fib11, ur_fib12, // dict sizes
|
||||||
|
ur_fib10, ur_fib11); // stack sizes
|
||||||
|
}
|
||||||
|
|
||||||
|
ur_cue_res_e
|
||||||
|
ur_cue_with(ur_cue_t *c,
|
||||||
|
uint64_t len,
|
||||||
|
const uint8_t *byt,
|
||||||
|
ur_nref *out)
|
||||||
|
{
|
||||||
|
ur_cue_res_e res = _cue(c, len, byt, out);
|
||||||
|
|
||||||
|
// XX check size, shrink if above threshold
|
||||||
|
//
|
||||||
|
ur_dict64_wipe(&c->dict);
|
||||||
|
c->s.fill = 0;
|
||||||
|
|
||||||
|
return res;
|
||||||
|
}
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_cue_done(ur_cue_t *c)
|
||||||
|
{
|
||||||
|
|
||||||
|
ur_dict_free((ur_dict_t*)&c->dict);
|
||||||
|
free(c->s.f);
|
||||||
|
free(c);
|
||||||
|
}
|
||||||
|
|
||||||
ur_cue_res_e
|
ur_cue_res_e
|
||||||
ur_cue(ur_root_t *r,
|
ur_cue(ur_root_t *r,
|
||||||
uint64_t len,
|
uint64_t len,
|
||||||
const uint8_t *byt,
|
const uint8_t *byt,
|
||||||
ur_nref *out)
|
ur_nref *out)
|
||||||
{
|
{
|
||||||
ur_dict64_t dict = {0};
|
ur_cue_t *c = ur_cue_init(r);
|
||||||
ur_dict64_grow(r, &dict, ur_fib11, ur_fib12);
|
ur_cue_res_e res = _cue(c, len, byt, out);
|
||||||
|
|
||||||
ur_cue_res_e res = ur_cue_unsafe(r, &dict, len, byt, out);
|
ur_cue_done(c);
|
||||||
|
|
||||||
ur_dict_free((ur_dict_t*)&dict);
|
|
||||||
return res;
|
return res;
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -386,13 +471,22 @@ _cue_test_next(_cue_test_stack_t *s,
|
|||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_cue_res_e
|
/*
|
||||||
ur_cue_test_unsafe(ur_dict_t *dict,
|
** define opaque struct ur_cue_test_s (ie, ur_cue_test_t)
|
||||||
|
*/
|
||||||
|
struct ur_cue_test_s {
|
||||||
|
_cue_test_stack_t s;
|
||||||
|
ur_dict_t dict;
|
||||||
|
};
|
||||||
|
|
||||||
|
static ur_cue_res_e
|
||||||
|
_cue_test(ur_cue_test_t *t,
|
||||||
uint64_t len,
|
uint64_t len,
|
||||||
const uint8_t *byt)
|
const uint8_t *byt)
|
||||||
{
|
{
|
||||||
ur_bsr_t bsr = {0};
|
ur_bsr_t bsr = {0};
|
||||||
_cue_test_stack_t s = {0};
|
_cue_test_stack_t *s = &t->s;
|
||||||
|
ur_dict_t *dict = &t->dict;
|
||||||
ur_cue_res_e res;
|
ur_cue_res_e res;
|
||||||
|
|
||||||
// init bitstream-reader
|
// init bitstream-reader
|
||||||
@ -406,50 +500,87 @@ ur_cue_test_unsafe(ur_dict_t *dict,
|
|||||||
return ur_cue_meme;
|
return ur_cue_meme;
|
||||||
}
|
}
|
||||||
|
|
||||||
// setup stack
|
|
||||||
//
|
|
||||||
s.prev = ur_fib10;
|
|
||||||
s.size = ur_fib11;
|
|
||||||
s.f = _oom("cue_test", malloc(s.size * sizeof(*s.f)));
|
|
||||||
|
|
||||||
// advance into stream
|
// advance into stream
|
||||||
//
|
//
|
||||||
res = _cue_test_next(&s, &bsr, dict);
|
res = _cue_test_next(s, &bsr, dict);
|
||||||
|
|
||||||
// process result
|
// process result
|
||||||
//
|
//
|
||||||
while ( s.fill && (ur_cue_good == res) ) {
|
while ( s->fill && (ur_cue_good == res) ) {
|
||||||
// peek at the top of the stack
|
// peek at the top of the stack
|
||||||
//
|
//
|
||||||
_cue_test_frame_t *f = &(s.f[s.fill - 1]);
|
_cue_test_frame_t *f = &(s->f[s->fill - 1]);
|
||||||
|
|
||||||
// f is a head-frame; stash result and read the tail from the stream
|
// f is a head-frame; stash result and read the tail from the stream
|
||||||
//
|
//
|
||||||
if ( !f->tal ) {
|
if ( !f->tal ) {
|
||||||
f->tal = 1;
|
f->tal = 1;
|
||||||
res = _cue_test_next(&s, &bsr, dict);
|
res = _cue_test_next(s, &bsr, dict);
|
||||||
}
|
}
|
||||||
// f is a tail-frame; pop the stack and continue
|
// f is a tail-frame; pop the stack and continue
|
||||||
//
|
//
|
||||||
else {
|
else {
|
||||||
ur_dict_put((ur_root_t*)0, dict, f->bits);
|
ur_dict_put((ur_root_t*)0, dict, f->bits);
|
||||||
s.fill--;
|
s->fill--;
|
||||||
}
|
}
|
||||||
}
|
}
|
||||||
|
|
||||||
free(s.f);
|
|
||||||
|
|
||||||
return res;
|
return res;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
ur_cue_test_t*
|
||||||
|
ur_cue_test_init_with(uint64_t d_prev,
|
||||||
|
uint64_t d_size,
|
||||||
|
uint32_t s_prev,
|
||||||
|
uint32_t s_size)
|
||||||
|
{
|
||||||
|
ur_cue_test_t* t = _oom("cue_test_init", calloc(sizeof(*t), 1));
|
||||||
|
|
||||||
|
ur_dict_grow((ur_root_t*)0, &t->dict, d_prev, d_size);
|
||||||
|
|
||||||
|
t->s.prev = s_prev;
|
||||||
|
t->s.size = s_size;
|
||||||
|
t->s.f = _oom("cue_test_init", malloc(s_size * sizeof(*t->s.f)));
|
||||||
|
|
||||||
|
return t;
|
||||||
|
}
|
||||||
|
|
||||||
|
ur_cue_test_t*
|
||||||
|
ur_cue_test_init(void)
|
||||||
|
{
|
||||||
|
return ur_cue_test_init_with(ur_fib11, ur_fib12, // dict sizes
|
||||||
|
ur_fib10, ur_fib11); // stack sizes
|
||||||
|
}
|
||||||
|
|
||||||
|
ur_bool_t
|
||||||
|
ur_cue_test_with(ur_cue_test_t *t,
|
||||||
|
uint64_t len,
|
||||||
|
const uint8_t *byt)
|
||||||
|
{
|
||||||
|
ur_bool_t ret = ur_cue_good == _cue_test(t, len, byt);
|
||||||
|
|
||||||
|
// XX check size, shrink if above threshold
|
||||||
|
//
|
||||||
|
ur_dict_wipe(&t->dict);
|
||||||
|
t->s.fill = 0;
|
||||||
|
|
||||||
|
return ret;
|
||||||
|
}
|
||||||
|
|
||||||
|
void
|
||||||
|
ur_cue_test_done(ur_cue_test_t *t)
|
||||||
|
{
|
||||||
|
ur_dict_free(&t->dict);
|
||||||
|
free(t->s.f);
|
||||||
|
free(t);
|
||||||
|
}
|
||||||
|
|
||||||
ur_bool_t
|
ur_bool_t
|
||||||
ur_cue_test(uint64_t len, const uint8_t *byt)
|
ur_cue_test(uint64_t len, const uint8_t *byt)
|
||||||
{
|
{
|
||||||
ur_dict_t dict = {0};
|
ur_cue_test_t *t = ur_cue_test_init();
|
||||||
ur_dict_grow((ur_root_t*)0, &dict, ur_fib11, ur_fib12);
|
ur_bool_t ret = ur_cue_good == _cue_test(t, len, byt);
|
||||||
|
|
||||||
ur_bool_t ret = ur_cue_good == ur_cue_test_unsafe(&dict, len, byt);
|
ur_cue_test_done(t);
|
||||||
|
|
||||||
ur_dict_free(&dict);
|
|
||||||
return ret;
|
return ret;
|
||||||
}
|
}
|
||||||
|
@ -12,6 +12,7 @@
|
|||||||
|
|
||||||
#include "all.h"
|
#include "all.h"
|
||||||
#include "vere/vere.h"
|
#include "vere/vere.h"
|
||||||
|
#include "ur/serial.h"
|
||||||
|
|
||||||
/* u3_pact: ames packet, coming or going.
|
/* u3_pact: ames packet, coming or going.
|
||||||
*/
|
*/
|
||||||
@ -35,6 +36,8 @@
|
|||||||
uv_udp_t wax_u; //
|
uv_udp_t wax_u; //
|
||||||
uv_handle_t had_u; //
|
uv_handle_t had_u; //
|
||||||
}; //
|
}; //
|
||||||
|
ur_cue_test_t* tes_u; // cue-test handle
|
||||||
|
u3_cue_xeno* sil_u; // cue handle
|
||||||
c3_c* dns_c; // domain XX multiple/fallback
|
c3_c* dns_c; // domain XX multiple/fallback
|
||||||
c3_d dop_d; // drop count
|
c3_d dop_d; // drop count
|
||||||
c3_d fal_d; // crash count
|
c3_d fal_d; // crash count
|
||||||
@ -365,8 +368,11 @@ _ames_serialize_packet(u3_panc* pac_u, c3_o dop_o)
|
|||||||
u3_noun lon, bod;
|
u3_noun lon, bod;
|
||||||
{
|
{
|
||||||
//NOTE we checked for cue safety in _ames_recv_cb
|
//NOTE we checked for cue safety in _ames_recv_cb
|
||||||
u3_noun old = u3ke_cue(u3i_bytes(pac_u->bod_u.con_w, pac_u->bod_u.con_y));
|
//
|
||||||
u3x_cell(old, &lon, &bod);
|
u3_weak old = u3s_cue_xeno_with(pac_u->sam_u->sil_u,
|
||||||
|
pac_u->bod_u.con_w,
|
||||||
|
pac_u->bod_u.con_y);
|
||||||
|
u3x_cell(u3x_good(old), &lon, &bod);
|
||||||
u3k(lon); u3k(bod);
|
u3k(lon); u3k(bod);
|
||||||
u3z(old);
|
u3z(old);
|
||||||
}
|
}
|
||||||
@ -798,6 +804,7 @@ _ames_recv_cb(uv_udp_t* wax_u,
|
|||||||
c3_d rec_d[2];
|
c3_d rec_d[2];
|
||||||
c3_w con_w = nrd_i - 4 - sen_y - rec_y;
|
c3_w con_w = nrd_i - 4 - sen_y - rec_y;
|
||||||
c3_y* con_y = NULL;
|
c3_y* con_y = NULL;
|
||||||
|
|
||||||
if ( c3y == pas_o ) {
|
if ( c3y == pas_o ) {
|
||||||
u3_noun sen = u3i_bytes(sen_y, bod_y);
|
u3_noun sen = u3i_bytes(sen_y, bod_y);
|
||||||
u3_noun rec = u3i_bytes(rec_y, bod_y + sen_y);
|
u3_noun rec = u3i_bytes(rec_y, bod_y + sen_y);
|
||||||
@ -810,9 +817,7 @@ _ames_recv_cb(uv_udp_t* wax_u,
|
|||||||
|
|
||||||
// ensure the content is cue-able
|
// ensure the content is cue-able
|
||||||
//
|
//
|
||||||
u3_noun pro = u3m_soft(0, u3ke_cue, u3i_bytes(con_w, con_y));
|
pas_o = ur_cue_test_with(sam_u->tes_u, con_w, con_y) ? c3y : c3n;
|
||||||
pas_o = (u3_blip == u3h(pro)) ? c3y : c3n;
|
|
||||||
u3z(pro);
|
|
||||||
}
|
}
|
||||||
|
|
||||||
// if we can scry,
|
// if we can scry,
|
||||||
@ -1165,6 +1170,9 @@ _ames_exit_cb(uv_handle_t* had_u)
|
|||||||
|
|
||||||
u3h_free(sam_u->lax_p);
|
u3h_free(sam_u->lax_p);
|
||||||
|
|
||||||
|
u3s_cue_xeno_done(sam_u->sil_u);
|
||||||
|
ur_cue_test_done(sam_u->tes_u);
|
||||||
|
|
||||||
c3_free(sam_u);
|
c3_free(sam_u);
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -1225,6 +1233,9 @@ u3_ames_io_init(u3_pier* pir_u)
|
|||||||
c3_assert( !uv_udp_init(u3L, &sam_u->wax_u) );
|
c3_assert( !uv_udp_init(u3L, &sam_u->wax_u) );
|
||||||
sam_u->wax_u.data = sam_u;
|
sam_u->wax_u.data = sam_u;
|
||||||
|
|
||||||
|
sam_u->sil_u = u3s_cue_xeno_init();
|
||||||
|
sam_u->tes_u = ur_cue_test_init();
|
||||||
|
|
||||||
// Disable networking for fake ships
|
// Disable networking for fake ships
|
||||||
//
|
//
|
||||||
if ( c3y == sam_u->pir_u->fak_o ) {
|
if ( c3y == sam_u->pir_u->fak_o ) {
|
||||||
|
@ -713,17 +713,15 @@ _king_boot_ivory(void)
|
|||||||
}
|
}
|
||||||
|
|
||||||
{
|
{
|
||||||
ur_dict32_t dic_u = {0};
|
u3_cue_xeno* sil_u = u3s_cue_xeno_init_with(ur_fib27, ur_fib28);
|
||||||
u3_noun pil;
|
u3_weak pil;
|
||||||
|
|
||||||
ur_dict32_grow((ur_root_t*)0, &dic_u, ur_fib27, ur_fib28);
|
if ( u3_none == (pil = u3s_cue_xeno_with(sil_u, len_d, byt_y)) ) {
|
||||||
|
|
||||||
if ( c3n == u3s_cue_xeno_unsafe(&dic_u, len_d, byt_y, &pil) ) {
|
|
||||||
u3l_log("lite: unable to cue ivory pill\r\n");
|
u3l_log("lite: unable to cue ivory pill\r\n");
|
||||||
exit(1);
|
exit(1);
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
u3s_cue_xeno_done(sil_u);
|
||||||
|
|
||||||
if ( c3n == u3v_boot_lite(pil)) {
|
if ( c3n == u3v_boot_lite(pil)) {
|
||||||
u3l_log("lite: boot failed\r\n");
|
u3l_log("lite: boot failed\r\n");
|
||||||
|
@ -74,7 +74,7 @@ _lord_stop_cb(void* ptr_v,
|
|||||||
void (*exit_f)(void*) = god_u->cb_u.exit_f;
|
void (*exit_f)(void*) = god_u->cb_u.exit_f;
|
||||||
void* exit_v = god_u->cb_u.ptr_v;
|
void* exit_v = god_u->cb_u.ptr_v;
|
||||||
|
|
||||||
ur_dict_free((ur_dict_t*)god_u->dic_u);
|
u3s_cue_xeno_done(god_u->sil_u);
|
||||||
c3_free(god_u);
|
c3_free(god_u);
|
||||||
|
|
||||||
if ( exit_f ) {
|
if ( exit_f ) {
|
||||||
@ -675,26 +675,23 @@ static void
|
|||||||
_lord_on_plea(void* ptr_v, c3_d len_d, c3_y* byt_y)
|
_lord_on_plea(void* ptr_v, c3_d len_d, c3_y* byt_y)
|
||||||
{
|
{
|
||||||
u3_lord* god_u = ptr_v;
|
u3_lord* god_u = ptr_v;
|
||||||
ur_dict32_t* dic_u = god_u->dic_u;
|
u3_noun tag, dat;
|
||||||
u3_noun tag, dat, jar = u3_blip;
|
u3_weak jar;
|
||||||
c3_o ret_o;
|
|
||||||
|
|
||||||
#ifdef LORD_TRACE_CUE
|
#ifdef LORD_TRACE_CUE
|
||||||
u3t_event_trace("king ipc cue", 'B');
|
u3t_event_trace("king ipc cue", 'B');
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
ret_o = u3s_cue_xeno_unsafe(dic_u, len_d, byt_y, &jar);
|
jar = u3s_cue_xeno_with(god_u->sil_u, len_d, byt_y);
|
||||||
// XX check if the dictionary grew too much and shrink?
|
|
||||||
//
|
|
||||||
ur_dict32_wipe(dic_u);
|
|
||||||
|
|
||||||
#ifdef LORD_TRACE_CUE
|
#ifdef LORD_TRACE_CUE
|
||||||
u3t_event_trace("king ipc cue", 'E');
|
u3t_event_trace("king ipc cue", 'E');
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
if ( (c3n == ret_o)
|
if ( u3_none == jar ) {
|
||||||
|| (c3n == u3r_cell(jar, &tag, &dat)) )
|
return _lord_plea_foul(god_u, 0, u3_blip);
|
||||||
{
|
}
|
||||||
|
else if ( c3n == u3r_cell(jar, &tag, &dat) ) {
|
||||||
return _lord_plea_foul(god_u, 0, jar);
|
return _lord_plea_foul(god_u, 0, jar);
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -1172,9 +1169,7 @@ u3_lord_init(c3_c* pax_c, c3_w wag_w, c3_d key_d[4], u3_lord_cb cb_u)
|
|||||||
#endif
|
#endif
|
||||||
|
|
||||||
{
|
{
|
||||||
ur_dict32_t* dic_u = c3_calloc(sizeof(*dic_u));
|
god_u->sil_u = u3s_cue_xeno_init();
|
||||||
ur_dict32_grow((ur_root_t*)0, dic_u, ur_fib10, ur_fib11);
|
|
||||||
god_u->dic_u = dic_u;
|
|
||||||
}
|
}
|
||||||
|
|
||||||
// start reading from proc
|
// start reading from proc
|
||||||
|
@ -27,7 +27,7 @@
|
|||||||
static u3_serf u3V; // one serf per process
|
static u3_serf u3V; // one serf per process
|
||||||
static u3_moat inn_u; // input stream
|
static u3_moat inn_u; // input stream
|
||||||
static u3_mojo out_u; // output stream
|
static u3_mojo out_u; // output stream
|
||||||
static ur_dict32_t dic_u; // cue dictionary
|
static u3_cue_xeno* sil_u; // cue handle
|
||||||
|
|
||||||
#undef SERF_TRACE_JAM
|
#undef SERF_TRACE_JAM
|
||||||
#undef SERF_TRACE_CUE
|
#undef SERF_TRACE_CUE
|
||||||
@ -107,8 +107,8 @@ _cw_serf_step_trace(void)
|
|||||||
static void
|
static void
|
||||||
_cw_serf_writ(void* vod_p, c3_d len_d, c3_y* byt_y)
|
_cw_serf_writ(void* vod_p, c3_d len_d, c3_y* byt_y)
|
||||||
{
|
{
|
||||||
u3_noun ret, jar;
|
u3_weak jar;
|
||||||
c3_o ret_o;
|
u3_noun ret;
|
||||||
|
|
||||||
_cw_serf_step_trace();
|
_cw_serf_step_trace();
|
||||||
|
|
||||||
@ -116,16 +116,13 @@ _cw_serf_writ(void* vod_p, c3_d len_d, c3_y* byt_y)
|
|||||||
u3t_event_trace("serf ipc cue", 'B');
|
u3t_event_trace("serf ipc cue", 'B');
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
ret_o = u3s_cue_xeno_unsafe(&dic_u, len_d, byt_y, &jar);
|
jar = u3s_cue_xeno_with(sil_u, len_d, byt_y);
|
||||||
// XX check if the dictionary grew too much and shrink?
|
|
||||||
//
|
|
||||||
ur_dict32_wipe(&dic_u);
|
|
||||||
|
|
||||||
#ifdef SERF_TRACE_CUE
|
#ifdef SERF_TRACE_CUE
|
||||||
u3t_event_trace("serf ipc cue", 'E');
|
u3t_event_trace("serf ipc cue", 'E');
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
if ( (c3n == ret_o)
|
if ( (u3_none == jar)
|
||||||
|| (c3n == u3_serf_writ(&u3V, jar, &ret)) )
|
|| (c3n == u3_serf_writ(&u3V, jar, &ret)) )
|
||||||
{
|
{
|
||||||
_cw_serf_fail(0, -1, "bad jar");
|
_cw_serf_fail(0, -1, "bad jar");
|
||||||
@ -165,7 +162,7 @@ _cw_serf_stdio(c3_i* inn_i, c3_i* out_i)
|
|||||||
static void
|
static void
|
||||||
_cw_serf_exit(void)
|
_cw_serf_exit(void)
|
||||||
{
|
{
|
||||||
ur_dict_free((ur_dict_t*)&dic_u);
|
u3s_cue_xeno_done(sil_u);
|
||||||
u3t_trace_close();
|
u3t_trace_close();
|
||||||
}
|
}
|
||||||
|
|
||||||
@ -239,7 +236,7 @@ _cw_serf_commence(c3_i argc, c3_c* argv[])
|
|||||||
uv_stream_set_blocking((uv_stream_t*)&out_u.pyp_u, 1);
|
uv_stream_set_blocking((uv_stream_t*)&out_u.pyp_u, 1);
|
||||||
}
|
}
|
||||||
|
|
||||||
ur_dict32_grow((ur_root_t*)0, &dic_u, ur_fib10, ur_fib11);
|
sil_u = u3s_cue_xeno_init();
|
||||||
|
|
||||||
// set up writing
|
// set up writing
|
||||||
//
|
//
|
||||||
|
Loading…
Reference in New Issue
Block a user