[ltp] detecting hardware mute?
Mark T.B. Carroll
linux-thinkpad@linux-thinkpad.org
Mon, 27 Mar 2006 19:35:57 -0500
Ho ho. Although you have better solutions now, in that time I wrote a
little programme for figuring out which bit(s) in the BIOS seem to show
state changes. The way it works is that you take some copies of
/dev/nvram with the machine in one state (call these 1 2 3 4 5 6 7 8),
then you take some more copies of it in another state (call these a b c
d e f) and you use,
./a.out 1 2 3 4 5 6 7 8 / a b c d e f
with the / separating the files from one state from the files from the
other state. Then it tells you which bit looks like the one you want. On
my R40 with a new BIOS with screwed-up ACPI, it says the mute state's
bit 6 of byte 96 (both numbered from 0) and, indeed, judging by "watch
od -j 96 -N 1 -h /dev/nvram" it does seem to be. Bit 7's interesting to
watch too.
Anyhow, in case anyone needs to find BIOS bits for other purposes, I'll
share the programme anyway. It's in Haskell, I'm afraid, and somewhat
dirty as I just knocked it together for the task at hand. Still,
hopefully it'll be useful for any other probing of the BIOS state.
module FindBit where
import Control.Monad
import Data.Bits
import Data.List
import Data.Word
import Foreign.Marshal.Alloc
import Foreign.Storable
import System.Environment
import System.IO
bitsOf :: (Bits a, Storable a) => a -> [Bool]
bitsOf value = [ testBit value bit | bit <- [ 0 .. sizeOf value * 8 - 1 ] ]
bufferSize :: Int
bufferSize = 1024
readBinaryFile :: FilePath -> IO [Word8]
readBinaryFile filePath =
do handle <- openBinaryFile filePath ReadMode
contents <- allocaBytes bufferSize (readContents handle)
hClose handle
return contents
where
readContents handle buffer =
do bytesRead <- hGetBuf handle buffer bufferSize
if bytesRead == 0 then return []
else do values <- mapM (peekElemOff buffer)
[0 .. bytesRead-1]
remainder <- readContents handle buffer
return (values ++ remainder)
readAllFiles :: [String] -> IO [[Bool]]
readAllFiles [] = return []
readAllFiles ("/" : files) =
liftM (map (map not)) (readAllFiles files)
readAllFiles (file : files) =
do fileContents <- readBinaryFile file
otherContents <- readAllFiles files
return (concatMap bitsOf fileContents : otherContents)
bitLocations :: [String]
bitLocations =
concatMap bitStrings [ "byte " ++ show byte | byte <- [0 ..] ]
where
bitStrings byteString =
[ "bit " ++ show bit ++ " of " ++ byteString | bit <- [0 .. 7] ]
goodBits :: [(String, [Bool])] -> [String]
goodBits bitCandidates =
[ bitName | (bitName, (bitStream : bitStreams)) <- bitCandidates,
all (== bitStream) bitStreams ]
main =
do filesNames <- getArgs
filesContents <- readAllFiles filesNames
mapM_ putStrLn (goodBits (zip bitLocations (transpose filesContents)))