usb-id-database-0.1: A database of USB identifiersSource codeContentsIndex
System.USB.IDDB
Contents
Types
Acquire database
Export database
Query database
Description

A database of USB identifiers.

Databases with vendor names and identifiers can be loaded from string, file or directly from http://www.usb.org.

Example usage:

module Main where

import System.USB.IDDB
import Data.ByteString.Char8 (pack, unpack)

main :: IO ()
main = do -- Acquire the default database
          db <- vdbDefault
          -- Print the name of vendor 0x1D6B
          putStrLn $ 'maybe "unknown ID!" unpack
                   $ vendorName db 0x1D6B
          -- Print the ID of "The Linux Foundation"
          putStrLn $ maybe "unknown name!" show
                   $ vendorID db (pack "The Linux Foundation")

EBNF grammar of the textual representation of a vendor database:

  vendor database = {row};
  row             = vendor id, "|", vendor name;
  vendor id       = natural number;
  vendor name     = ASCII string;
  natural number  = positive digit, {digit}
  positive digit  = "1" | "2" | "3" | "4" | "5" | "6" | "7" | "8" | "9";
  digit           = "0" | positive digit;
Synopsis
type VendorID = Int
type VendorName = ByteString
type VendorDB = Bimap VendorID VendorName
vdbFromString :: ByteString -> Maybe VendorDB
vdbFromFile :: FilePath -> IO (Maybe VendorDB)
vdbFromUsbDotOrg :: IO (Maybe VendorDB)
vdbDefault :: IO VendorDB
vdbToString :: VendorDB -> ByteString
vdbToFile :: FilePath -> VendorDB -> IO ()
vendorName :: VendorDB -> VendorID -> Maybe VendorName
vendorID :: VendorDB -> VendorName -> Maybe VendorID
Types
type VendorID = IntSource
A numerical identifier for a vendor.
type VendorName = ByteStringSource
The name of a company/entity which has acquired an official ID from the USB Implementors Forum.
type VendorDB = Bimap VendorID VendorNameSource
A database of USB vendors. Associates numerical vendor ID's with vendor names and vice versa.
Acquire database
vdbFromString :: ByteString -> Maybe VendorDBSource
Construct a vendor database from a string.
vdbFromFile :: FilePath -> IO (Maybe VendorDB)Source
Load a vendor database from file. If the file can not be read for some reason an error will be thrown.
vdbFromUsbDotOrg :: IO (Maybe VendorDB)Source
Construct a vendor database from the list of companies available at http://www.usb.org/developers/tools/comp_dump. The website informs us that: "Remember this list changes almost daily, be sure to get a fresh copy when you use the tools". However, the list seems to be quite stable. Using this function more than once a day is probably overkill.
vdbDefault :: IO VendorDBSource
Load a vendor database from a static file which is supplied with the package.
Export database
vdbToString :: VendorDB -> ByteStringSource
Convert a vendor database to its textual representation.
vdbToFile :: FilePath -> VendorDB -> IO ()Source
Write a database to a file. If this file is not accessible an error will be thrown.
Query database
vendorName :: VendorDB -> VendorID -> Maybe VendorNameSource
Retrieve the name of a vendor given its ID.
vendorID :: VendorDB -> VendorName -> Maybe VendorIDSource
Retrieve the ID of a vendor given its name.
Produced by Haddock version 2.4.2