bbdb-0.2: Ability to read, write, and examine BBDB files

Database.BBDB

Description

This module can read and write BBDB files, and provides a few handy functions for getting at fields inside of BBDB data.

BBDB (http://bbdb.sourceforge.net/) is short for the Insidious Big Brother Database, which is a contact management utility that can be integrated into Emacs (the one true editor.) Since bbdb.el is implemented in elisp, it can be difficult to "get at" the data inside a .bbdb file with external programs. Many years ago, I wrote a BBDB interface for perl, but having experience enlightenment at the hands of the category gods, I`m now dabbling with Haskell. But having been a loyal Emacs user for many years now, I wanted a way to spam my friends while still using my favorite programming language. Hence the module Data.BBDB.

The following is the data layout for a BBDB record. I have created a sample record with my own data. Each field is just separated by a space. I have added comments to the right

 ["Henry"                                   The first name - a string
 "Laxen"                                    The last name - a string
 ("Henry, Enrique")                         Also Known As - comma separated list
 "Elegant Solutions"                        Business name - a string
 (
  ["reno" 775 624 1851 0]                   Phone number field - US style
  ["chapala" "011-52-376-765-3181"]         Phone number field - International style
 ) 
 (
  ["mailing"                                The address location, then a list
  ("10580 N. McCarran Blvd." "#115-396")    for the street address, then one each
  "Reno" "Nevada" "89503" "USA"             for City, State, Zip Code, and country
 ] 
  ["home"                                   another Address field
  ("Via Alta #6" "Gaviotas #10")            The street list
  "Chapala" "Jalisco"                       City State
  "45900" "Mexico"                          Zip and country
 ]) 
 (
  "nadine.and.henry@pobox.com"              the net addresses - a list of strings
  "nadinelaxen@pobox.com"
 ) 
 (
  (notes . "Always split aces and eights")  The notes field - a list of alists
  (creation-date . "2010-09-03") 
  (timestamp . "2010-09-03")
  (birthday . "6/15")
 ) 
 nil                                        The cache vector - always nil
 ]

Inside the .bbdb file, this looks like: ["Henry" "Laxen" ("Henry, Enrique") "Elegant Solutions" (["reno" 775 624 1851 0] ["chapala" "011-52-376-765-3181"]) (["mailing" ("10580 N. McCarran Blvd." "#115-396") "Reno" "Nevada" "89503" "USA"] ["home" ("Via Alta 10") "Chapala" "Jalisco" "45900" "Mexico"]) ("nadine.and.henry@pobox.com" "nadinelaxen@pobox.com") ((notes . "Always split aces and eights") (creation-date . "2010-09-03") (timestamp . "2010-09-03") (birthday . "6/15")) nil]

When parsed, this is represented inside Haskell as:

      BBDBEntry
        (BBDB{firstName = Just "Henry", lastName = Just "Laxen",
              aka = Just ["Henry, Enrique"], company = Just "Elegant Solutions",
              phone =
                Just
                  [USStyle "reno" ["775", "624", "1851", "0"],
                   InternationalStyle "chapala" "011-52-376-765-3181"],
              address =
                Just
                  [Address{location = "mailing",
                           streets =
                             Just ["10580 N. McCarran Blvd.", "#115-396"],
                           city = Just "Reno", state = Just "Nevada",
                           zipcode = Just "89503", country = Just "USA"},
                   Address{location = "home",
                           streets = Just ["Via Alta #6", "Gaviotas #10"],
                           city = Just "Chapala", state = Just "Jalisco",
                           zipcode = Just "45900", country = Just "Mexico"}],
              net = Just ["nadine.and.henry@pobox.com", "nadinelaxen@pobox.com"],
              notes =
                Just
                  (Note{unnote =
                          [("notes", "Always split aces and eights"),
                           ("creation-date", "2010-09-03"),
                           ("timestamp", "2010-09-03"),
                           ("birthday", "6/15")]})})]
 

Synopsis

Documentation

type Location = StringSource

A Location is just a synonym for String. Each BBDB Address and Phone field must be associated with a location, such as home or work

type Street = StringSource

A Street is also a synonym for String. Each Address may have a list of Streets associated with it.

type Symbol = StringSource

A Symbol is just a String, but Lisp only wants alphanumerics and the characters _ (underscore) and - (dash)

data Address Source

An Address must have a location, and may have associated streets, a city, a state, a zipcode, and an country.

type Alist = (Symbol, String)Source

An Alist is an Association List. Lisp writes these as (key . value) We convert these to a tuple in haskell where fst is key and snd is value.

data Note Source

The Note field of a BBDB record is just a list of associations. If you don't provide a your own key, the BBDB will use the word "note"

Constructors

Note 

Fields

unnote :: [Alist]
 

data Phone Source

For some unknow reason, BBDB can have phones in two different formats. In USStyle, the phone is list of integers, in the form of Area code, Prefix, Number, and Extension. I don't bother to convert the strings of digits to actual integers. In InternationalStyle, the phone number is just a String.

data BBDB Source

Constructors

BBDB 

Fields

firstName :: Maybe String

the first name. Why is this a Maybe? Because sometimes you just have a company, and not a specific first name

lastName :: Maybe String
 
aka :: Maybe [String]

aka = Also Known As. Sometimes the same email address can match several users, so BBDB gives you the option of remembering different names for the same address

company :: Maybe String

The company if any

phone :: Maybe [Phone]

A list of phone numbers, either in US Style or International Style

address :: Maybe [Address]

A list of addresses, keyed by location

net :: Maybe [String]

A list of email addresses. BBDB uses the first element of this field when you create a new email

notes :: Maybe Note

Any number of key, value pairs. Great for random data.

data BBDBFile Source

At the beginning of a BBDB file are a variable number of comments, which specify the encoding type and the version. We just ignore them. Comments starts with a ; (semi-colon) and continue to end of line

Instances

Eq BBDBFile 
Ord BBDBFile 
Show BBDBFile 
LispAble BBDBFile 
LispAble [BBDBFile]

the inverse of bbdbFileParse

class LispAble s whereSource

convert a Haskell string to a string that Lisp likes

LispAble is how we convert from our internal representation of a BBDB record, to one that will make Lisp and Emacs happy. (Sans bugs)

 testInverse = do
   let inFile = "/home/henry/.bbdb"
   actualBBDBFile <- readFile inFile
   parsedBBDBdata <- readBBDB inFile
   let bbdbDataOut = asLisp parsedBBDBdata
   print $ actualBBDBFile == bbdbDataOut
  

should print True

Methods

asLisp :: s -> StringSource

key :: (x, y) -> xSource

Given an Alist, return the key

value :: (x, y) -> ySource

Given an Alist, return the value

bbdbFileParse :: Parser [BBDBFile]Source

The Parser for a BBDB file, as it is written on disk. If you read a .bbdb file with:

 testParse :: FilePath -> IO (Either ParseError [BBDBFile])
 testParse filename = do
   b <- readFile filename
   return $  parse bbdbFileParse "bbdb" b

You will get IO (Right [BBDBFile]) if the parse went ok

justEntry :: BBDBFile -> Maybe BBDBSource

converts a BBDB comment to nothing, and a BBDB entry to just the entry

justEntries :: [BBDBFile] -> [BBDB]Source

returns a list of only the actual bbdb entries, removing the comments

readBBDB :: String -> IO [BBDBFile]Source

read the given file and call error if the parse failed, otherwise return the entire file as a list of BBDBFile records.

wantNote :: (Alist -> Bool) -> BBDB -> BoolSource

Notes inside a BBDB record are awkward to get at. This helper function digs into the record and applies a function to each Alist element of the record. It returns true if it any of the Alists in the note return true. For example:

 hasBirthday :: BBDB -> Bool
 hasBirthday = wantNote (\x -> key x == "birthday")

will return True for any BBDB record that has a "birthday" key in it's notes field

getNote :: String -> BBDB -> Maybe StringSource

Lookup the value whose key is the given string. If found returns Just the value, otherwise Nothing For example:

 getBirthday :: BBDB -> Maybe String
 getBirthday = getNote "birthday"

mapBBDB :: (BBDB -> BBDB) -> [BBDBFile] -> [BBDBFile]Source

This and filterBBDB are the main functions you should use to manipulate a set of BBDB entries. You supply a function that applies a transformation on a BBDB record, and this function will apply that transformation to every BBDBEntry in a BBDB file. Sample usage:

 starCompanies = do
   b <- readBBDB "/home/henry/.bbdb"
   writeFile "/home/henry/.bbdb-new" $ asLisp . mapBBDB starCompany $ b
   where
     starCompany x = case (company x) of
       Nothing -> x
       Just y -> x { company = Just ("*" ++ y) }

Prepend a star ("*") to each company field of a BBDB file and write the result out as a new bbdb file.

filterBBDB :: (BBDB -> Bool) -> [BBDBFile] -> [BBDBFile]Source

Just like mapBBDB except it filters. You supply a function that takes a BBDB record to a Bool, and filterBBDB will return a new list of BBDBFile that satisfy that condition. Sample usage:

 import Text.Regex.Posix
 -- do regex matching while ignoring case, so "reno" matches "Reno"
 matches x = match (makeRegexOpts compIgnoreCase defaultExecOpt x :: Regex)
 getReno = do
   b <- readBBDB "/home/henry/.bbdb"
   let c = justEntries . filterBBDB hasReno $ b
   mapM_ print $ map (\a -> (firstName a, lastName a, address a)) c
   where
     isReno :: Maybe String -> Bool
     isReno = maybe False (matches "reno")
     anyAddressHasReno :: [Address] -> Bool
     anyAddressHasReno = any id . map (isReno . city)
     hasReno :: BBDB -> Bool
     hasReno = maybe False anyAddressHasReno . address

print the name and all addresses of anyone in the BBDB file who live in Reno.