Posts
4417
Following
315
Followers
471
Linux kernel hacker and maintainer etc.

OpenPGP: 3AB05486C7752FE1
@ohmrun Helped me to make all conclusions I ever need to make from that language so I guess it was worth it :-)
1
0
1

@ohmrun I wrote this 2D maze in Haskell circa 2011 (not likely to compile today):

module Maze where

import Control.Monad
import Foreign
import qualified Graphics.UI.SDL as SDL
import System.Random
import Data.List
import Data.Array

data Cell = Cell {
    top :: Bool,
    left :: Bool,
    visited :: Bool
} deriving (Show, Eq)

type Maze = Array (Int, Int) Cell

newCell = Cell {top = True, left = True, visited = False}

newMaze :: Int -> Int -> Maze
newMaze rows columns = listArray ((0, 0), (rows - 1, columns - 1)) (repeat newCell)

genMaze maze (r, c) (seed:seeds)
    | visited (maze ! (r, c)) == True = maze
    | otherwise = foldl traverse maze' ((permutations neighbours) !! index)
    where maze' = maze//[((r, c), (maze ! (r, c)) { visited = True })]
          locs = [(r - 1, c), (r + 1, c), (r, c - 1), (r, c + 1)]
          ((_, _), (rmax, cmax)) = (bounds maze)
          neighbours = [(r', c') | (r', c') <- locs,
                        r' >= 0 && r' <= rmax, c' >= 0 &&  c' <= cmax]
          index = seed `mod` (length neighbours)
          moveTo maze (r, c) (r', c')
              | visited cell'  = maze
              | r' < r = maze//[((r, c), cell { top = False })]
              | r' > r = maze//[((r', c'), cell' { top = False })]
              | c' < c = maze//[((r, c), cell { left = False })]
              | c' > c = maze//[((r', c'), cell' { left = False })]
              | otherwise = error "Invalid move"
              where cell = maze ! (r, c)
                    cell' = maze ! (r', c')
          traverse maze' (r', c') = genMaze (moveTo maze' (r, c) (r', c')) (r', c') seeds

hline :: Int -> Int -> Int -> SDL.Pixel -> SDL.Surface -> IO ()
hline x y width (SDL.Pixel pixel) screen = do
    screenWidth <- return (SDL.surfaceGetWidth screen)
    pixels <- castPtr `liftM` SDL.surfaceGetPixels screen
    forM_ [0..(width - 1)] $ \dx -> do
        pokeElemOff pixels (y * screenWidth + x + dx) pixel

vline :: Int -> Int -> Int -> SDL.Pixel -> SDL.Surface -> IO ()
vline x y height (SDL.Pixel pixel) screen = do
    screenWidth <- return (SDL.surfaceGetWidth screen)
    pixels <- castPtr `liftM` SDL.surfaceGetPixels screen
    forM_ [0..(height - 1)] $ \dy -> do
        pokeElemOff pixels ((y + dy) * screenWidth + x) pixel

main :: IO()
main = do
    startRow <- randomRIO (0 :: Int, rows - 1)
    startColumn <- randomRIO (0 :: Int, columns - 1)
    seeds <- replicateM (rows * columns) (randomRIO (0 :: Int, (max rows columns)))

    maze <- return (genMaze (newMaze rows columns) (startRow, startColumn) seeds)
    SDL.init [SDL.InitEverything]
    screen <- SDL.setVideoMode screenWidth screenHeight 32 []

    hline 0 0 screenWidth whitePixel screen
    hline 0 (screenHeight - 1) screenWidth whitePixel screen
    vline 0 0 screenHeight whitePixel screen
    vline (screenWidth - 1) 0 screenHeight whitePixel screen

    forM (assocs maze) $ \((r, c), cell) ->
        if (top cell) then do
            hline (blockWidth * c) (blockHeight * r) blockWidth whitePixel screen
        else do return ()

    forM (assocs maze) $ \((r, c), cell) ->
        if (left cell) then do
            vline (blockWidth * c) (blockHeight * r) blockHeight whitePixel screen
        else do return ()

    SDL.flip screen
    eventLoop
    SDL.quit

    where
        eventLoop = SDL.waitEvent >>= checkEvent
        checkEvent SDL.Quit = return()
        checkEvent (SDL.KeyUp _) = return()
        checkEvent _ = eventLoop

        blockWidth = 32
        blockHeight = 32
        rows = 16
        columns = 16
        screenWidth = columns * blockWidth
        screenHeight = rows * blockHeight
        whitePixel = SDL.Pixel 0x00FFFFFF

Ur welcome ;-)

1
0
1
@mattdm @pchestek At least my daughter's vespa that i bought for her is in the moped category, which you can drive in Finland before turning 18 (like from 15 years or similar).
0
0
1

Jarkko Sakkinen

Edited 1 year ago
@mjg59 Reported to https://support.signal.org/hc/en-us/requests/new. Not holding my breath, probably will be plain ignored...

Also "protecting from 3rd parties via SGX" does not hold in the case of Signal as they have their own data centers. Physical machine is already an enclave if you own it. Plain TPM2 would do.

So there's no actual scenario with SGX for Signal that make sense, plain and simple. Providing CPU attestation to client user would be such scenario, or if Signal was using 3rd party data centers. So it is provably only marketing that they use SGX, and has been that since 2017 when Moxie was around.

Fake marketing scam by definition.
0
0
0
My bug fixes to the paging code where included to the upstream of the project so not all went wrong!
0
0
1
Obviously not for mainline but since the project compiles the full kernel it would be easier to carry downstream kernel patch rather than have separate OOT driver. Tried to explain this but it went to deaf ears...
1
0
0

Jarkko Sakkinen

Edited 1 year ago

I fixed some bugs in page tables of RISC-V Keystone enclaves (bootstrapping code of page tables) last Fall to get them working with CVA6 RISC-V CPU, and now I get steadily emails from people who are trying to use Keystone but cannot get it working for various reasons.

Not blaming those people but clearly the project is not too community oriented 🤷 I try respond politely that I don’t have the bandwidth.

Does not come as surprise tho because I wrote a trivial in-kernel driver PoC to which project showed no interest, still continuing with their OOT-drver:

Cannot recall which one was newer version because it is such a long time since I wrote these :-)

#riscv #keystone #enclave #linux

1
0
4

I love it that my play stats on Bandcamp look like an MSEG envelope curve.

0
1
0

Jarkko Sakkinen

Submitted a security issue to Signal App about the privacy issue on how they use Intel SGX :-) Let's see how this goes...
1
0
1

⚡️ 🇦🇷 A theft of a radioactive material capsule in Buenos Aires, Argentina has raised concerns among the population. The capsule contained a 45ml container of radioactive liquid and was stolen from a nuclear medicine company. Authorities have been alerted and are investigating the incident. https://www.riskmap.com/incidents/2132301/articles/222305988/

0
2
0
@ChrisF Yeah, exactly, totally misguided advice...
0
0
1

New development policy: code generated by a large language model or similar technology (e.g. ChatGPT, GitHub Copilot) is presumed to be tainted (i.e. of unclear copyright, not fitting NetBSD's licensing goals) and cannot be committed to NetBSD.

https://www.NetBSD.org/developers/commit-guidelines.html

1
21
3
And yeah, be skeptical towards people who categorize other people as hobbyists and engineers :-)
0
0
2

Jarkko Sakkinen

Edited 1 year ago
"No Arduino! If you aim to master embedded systems, Arduino won’t cut it. It’s a playground for hobbyists, not the battleground for engineers. The purpose is not to scare you — It’s to help you out. It is to give you a proper direction." -https://medium.com/@umerfarooqai/embedded-engineering-roadmap-say-no-to-arduino-a0eed8e1bf10

Well, that at least scares me. How I think is that one should take the simplest possible tool to get a PoC.

Otherwise, all energy might be consumed in useless and pointless battles. Conserving energy, prioritizing and picking the right battles is what engineers IMHO do.

#arduino #engineer
2
0
2

Jarkko Sakkinen

Last bit from my side for TPM2 asymmetric keys: https://lore.kernel.org/linux-crypto/20240515150213.32491-1-jarkko@kernel.org/T/#u

Now I'll wait for some patches from James Prestwood based on his previous work: https://lore.kernel.org/keyrings/20200518172704.29608-1-prestwoj@gmail.com/
0
0
1

Jarkko Sakkinen

Edited 1 year ago
0
0
2

Jarkko Sakkinen

Edited 1 year ago
Pull request 4/4 pulled this time for asymmetric keys :-) https://lkml.org/lkml/2024/5/15/699

My PR's were in chaos about a year ago, and Linus also complained about the quality. This was mostly because the startup I was in went out of business and lots of stuff going on in life overall but I've gradually improved my process to make it more fail-safe. Results start to show and four PR's to four subsystems was a non-issue :-)

In the next life crisis: I'm prepared
0
0
1
@pid_eins tiny embedded, Kernel QA, testing pre-production hardware that is in FPGA (not yet ASIC) the sweet spot is a static multi-call binary. And also sort of like Chrome web browser works :-)

I'd really have to actually try the upstream to get a better picture what is going on. as said, i only really know what the distro enables for me so i might be totally lost with this.

Also in the higher end of the scale, i.e. latest Xeon and EPYC server hardware a static mult-call binary would bring a *huge* security benefit: systemd could be bootstrapped as it is inside SGX/TDX/SNP enclave and fully attested, encrypted and integrity protected. It would bring "infrastructure security" to systemd that can protect from many attack vectors due software bugs.
0
0
0
Show older