about summary refs log tree commit diff
diff options
context:
space:
mode:
-rw-r--r--.gitignore6
-rw-r--r--.hgignore13
-rw-r--r--.hgtags3
-rw-r--r--run.sh2
-rw-r--r--tools/acid-migrate/Acid.hs279
-rw-r--r--tools/convertdb/Makefile13
-rw-r--r--tools/convertdb/convertdb.go116
-rw-r--r--tools/convertdb/couch.go403
-rw-r--r--tools/fixcomments.hs21
-rw-r--r--tools/music/Makefile10
-rwxr-xr-xtools/music/gettitle4
-rw-r--r--tools/music/iTunes.go79
-rwxr-xr-xtools/music/start1
-rw-r--r--update.sh5
14 files changed, 6 insertions, 949 deletions
diff --git a/.gitignore b/.gitignore
new file mode 100644
index 0000000000..8bfbf2a389
--- /dev/null
+++ b/.gitignore
@@ -0,0 +1,6 @@
+*.o
+*.hi
+BlogState/
+dist/
+.cabal-sandbox/
+*.tar.gz
diff --git a/.hgignore b/.hgignore
deleted file mode 100644
index f0e6fe0d5e..0000000000
--- a/.hgignore
+++ /dev/null
@@ -1,13 +0,0 @@
-syntax: glob
-.DS_Store
-reServe
-convertdb
-music
-*.o
-*.hi
-*.esproj
-*.sublime*
-*.8
-*.geany
-*.orig
-BlogState/
\ No newline at end of file
diff --git a/.hgtags b/.hgtags
deleted file mode 100644
index 089c798fa6..0000000000
--- a/.hgtags
+++ /dev/null
@@ -1,3 +0,0 @@
-7e19f2cc8edf2c77a8dc7258868c06360e80dcd3 4.1
-7e19f2cc8edf2c77a8dc7258868c06360e80dcd3 4.1
-be1d1e09f0727102fc3a41e8218ac1f74c3b4f51 4.1
diff --git a/run.sh b/run.sh
deleted file mode 100644
index 7ac433b60b..0000000000
--- a/run.sh
+++ /dev/null
@@ -1,2 +0,0 @@
-#!/bin/bash
-sudo privbind -u tazjin tazblog --port 80 --statedir $TAZBLOG
\ No newline at end of file
diff --git a/tools/acid-migrate/Acid.hs b/tools/acid-migrate/Acid.hs
deleted file mode 100644
index 10ab3e23d0..0000000000
--- a/tools/acid-migrate/Acid.hs
+++ /dev/null
@@ -1,279 +0,0 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, RecordWildCards, 
-TemplateHaskell, TypeFamilies, OverloadedStrings, ScopedTypeVariables, BangPatterns #-}
-
-module Main where
-import Control.Applicative  ((<$>), optional)
-import Control.Exception    (bracket)
-import Control.Monad        (msum, mzero)
-import Control.Monad.IO.Class (MonadIO)
-import Control.Monad.Reader (ask)
-import Control.Monad.State  (get, put)
-import Control.Monad.Trans  (liftIO)
-import Data.Acid
-import Data.Acid.Advanced 
-import Data.Acid.Local
-import Data.ByteString      (ByteString)
-import Data.Data            (Data, Typeable)
-import Data.IxSet           (Indexable(..), IxSet(..), (@=), Proxy(..), getOne, ixFun, ixSet)
-import Data.SafeCopy        (SafeCopy, base, deriveSafeCopy)
-import Data.Text            (Text, pack)
-import Data.Text.Lazy       (toStrict)
-import Data.Time
-import           System.Environment(getEnv)
-
-
-import qualified Crypto.Hash.SHA512 as SHA (hash)
-import qualified Data.ByteString.Char8 as B
-import qualified Data.ByteString.Base64 as B64 (encode)
-import qualified Data.IxSet as IxSet
-import qualified Data.Text  as Text
-
-
-{-CouchDB imports-}
-
-import Database.CouchDB hiding (runCouchDB')
-import Database.CouchDB.JSON
-import Text.JSON
-import Data.List (intersperse, (\\))
-import System.Locale (defaultTimeLocale)
-
--- data types and acid-state setup
-
-newtype EntryId = EntryId { unEntryId :: Integer }
-    deriving (Eq, Ord, Data, Enum, Typeable, SafeCopy)
-
-instance Show EntryId where
-  show = show . unEntryId
-
-data BlogLang = EN | DE 
-    deriving (Eq, Ord, Data, Typeable)
-
-instance Show BlogLang where
-    show DE = "de"
-    show EN = "en"
-
-$(deriveSafeCopy 0 'base ''BlogLang)
-
-data Comment = Comment {
-    cdate   :: UTCTime,
-    cauthor :: Text,
-    ctext   :: Text
-} deriving (Eq, Ord, Show, Data, Typeable)
-
-$(deriveSafeCopy 0 'base ''Comment)
-
-data Entry = Entry {
-    entryId :: EntryId,
-    lang   :: BlogLang,
-    author :: Text,
-    title  :: Text,
-    btext  :: Text, 
-    mtext  :: Text,
-    edate  :: UTCTime,
-    tags   :: [Text],
-    comments :: [Comment]
-} deriving (Eq, Ord, Show, Data, Typeable)
-
-$(deriveSafeCopy 0 'base ''Entry)
-
--- ixSet requires different datatypes for field indexes, so let's define some
-newtype Author = Author Text   deriving (Eq, Ord, Data, Typeable, SafeCopy)
-newtype Title  = Title Text    deriving (Eq, Ord, Data, Typeable, SafeCopy)
-newtype BText  = BText Text    deriving (Eq, Ord, Data, Typeable, SafeCopy) -- standard text
-newtype MText  = MText Text    deriving (Eq, Ord, Data, Typeable, SafeCopy) -- "read more" text
-newtype Tag    = Tag Text      deriving (Eq, Ord, Data, Typeable, SafeCopy)
-newtype EDate  = EDate UTCTime deriving (Eq, Ord, Data, Typeable, SafeCopy)
-newtype SDate  = SDate UTCTime   deriving (Eq, Ord, Data, Typeable, SafeCopy)
-newtype Username = Username Text deriving (Eq, Ord, Data, Typeable, SafeCopy)
-newtype SessionID = SessionID Text deriving (Eq, Ord, Data, Typeable, SafeCopy)
-
-instance Indexable Entry where 
-    empty = ixSet [ ixFun $ \e -> [ entryId e]
-                  , ixFun $ (:[]) . lang
-                  , ixFun $ \e -> [ Author $ author e ]
-                  , ixFun $ \e -> [ Title $ title e]
-                  , ixFun $ \e -> [ BText $ btext e]
-                  , ixFun $ \e -> [ MText $ mtext e]
-                  , ixFun $ \e -> [ EDate $ edate e]
-                  , ixFun $ \e -> map Tag (tags e)
-                  , ixFun $ comments
-                  ]
-
-data User = User {
-    username :: Text,
-    password :: ByteString
-} deriving (Eq, Ord, Data, Typeable)
-
-$(deriveSafeCopy 0 'base ''User)
-
-data Session = Session {
-    sessionID :: Text,
-    user      :: User,
-    sdate     :: UTCTime
-} deriving (Eq, Ord, Data, Typeable)
-
-$(deriveSafeCopy 0 'base ''Session)
-
-instance Indexable User where
-    empty = ixSet [ ixFun $ \u -> [Username $ username u]
-                  , ixFun $ (:[]) . password 
-                  ]
-
-instance Indexable Session where
-    empty = ixSet [ ixFun $ \s -> [SessionID $ sessionID s]
-                  , ixFun $ (:[]) . user
-                  , ixFun $ \s -> [SDate $ sdate s]
-                  ]
-
-data Blog = Blog {
-    blogSessions :: IxSet Session,
-    blogUsers    :: IxSet User,
-    blogEntries  :: IxSet Entry
-} deriving (Data, Typeable)
-
-$(deriveSafeCopy 0 'base ''Blog)
-
-initialBlogState :: Blog 
-initialBlogState = 
-    Blog { blogSessions = empty
-         , blogUsers = empty
-         , blogEntries = empty }
-
--- acid-state database functions (purity is necessary!)
-
-insertEntry :: Entry -> Update Blog Entry
-insertEntry e = 
-    do b@Blog{..} <- get
-       put $ b { blogEntries = IxSet.insert e blogEntries }
-       return e
-
-updateEntry :: Entry -> Update Blog Entry
-updateEntry e = 
-    do b@Blog{..} <- get
-       put $ b { blogEntries = IxSet.updateIx (entryId e) e blogEntries}
-       return e
-
-getPost :: EntryId -> Query Blog (Maybe Entry)
-getPost eid =
-    do b@Blog{..} <- ask
-       return $ getOne $ blogEntries @= eid
-
-latestPosts :: Query Blog [Entry]
-latestPosts =
-    do b@Blog{..} <- ask
-       return $ IxSet.toDescList (Proxy :: Proxy EDate) $ blogEntries
-
-addSession :: Text -> User -> UTCTime -> Update Blog Session
-addSession sId u t =
-    do b@Blog{..} <- get
-       let s = Session sId u t
-       put $ b { blogSessions = IxSet.insert s blogSessions}
-       return s
-
-addUser :: Text -> String -> Update Blog User
-addUser un pw =
-    do b@Blog{..} <- get
-       let u = User un $ hashString pw
-       put $ b { blogUsers = IxSet.insert u blogUsers}
-       return u
-
--- various functions
-hashString :: String -> ByteString
-hashString = B64.encode .  SHA.hash . B.pack
-
-$(makeAcidic ''Blog
-    [ 'insertEntry
-    , 'updateEntry
-    , 'getPost
-    , 'latestPosts
-    , 'addSession
-    , 'addUser
-    ])
-
--- CouchDB database functions
-
-runCouchDB' :: CouchMonad a -> IO a
-runCouchDB' = runCouchDB "127.0.0.1" 5984
-
-instance JSON Comment where
-    showJSON = undefined
-    readJSON val = do
-        obj <- jsonObject val
-        scauthor <- jsonField "cauthor" obj
-        jsscdate <- jsonField "cdate" obj :: Result JSValue
-        let rcdate = stripResult $ jsonInt jsscdate
-        sctext <- jsonField "ctext" obj
-        return $ Comment (parseSeconds rcdate) (pack scauthor) (pack sctext)
-
-instance JSON Entry where
-    showJSON = undefined
-    readJSON val = do
-        obj <- jsonObject val
-        sauthor <- jsonField "author" obj
-        stitle <- jsonField "title" obj
-        day <- jsonField "day" obj
-        month <- jsonField "month" obj
-        year <- jsonField "year" obj
-        stext <- jsonField "text" obj
-        comments <- jsonField "comments" obj
-        oldid <- jsonField "_id" obj
-        let leTime = parseShittyTime year month day oldid
-        return $ Entry (EntryId $ getUnixTime leTime) DE (pack sauthor) (pack $ stitle \\ "\n") (pack stext) (Text.empty) 
-                        leTime [] comments
-
-
-getUnixTime :: UTCTime -> Integer
-getUnixTime t = read $ formatTime defaultTimeLocale "%s" t
-
-parseSeconds :: Integer -> UTCTime
-parseSeconds t = readTime defaultTimeLocale "%s" $ show t
-
-parseShittyTime :: Int -> Int -> Int -> String -> UTCTime
-parseShittyTime y m d i = readTime defaultTimeLocale "%Y %m %e  %k:%M:%S" newPartTime
-    where
-        firstPart = take 2 i
-        secondPart = take 2 $ drop 2 i
-        thirdPart = drop 4 i
-        newPartTime =  concat $ intersperse " " [show y, showMonth m, show d, " "] ++ 
-                        intersperse ":" [firstPart, secondPart, thirdPart]
-        showMonth mn  
-                | mn < 10 = "0" ++ show mn
-                | otherwise = show mn
-
-getOldEntries = runCouchDB' $ queryView (db "tazblog") (doc "entries") (doc "latestDE") []
-
-parseOldEntries :: IO [Entry]
-parseOldEntries = do
-    queryResult <- getOldEntries
-    let entries = map (stripResult . readJSON . snd) queryResult
-    return entries
-
-stripResult :: Result a -> a
-stripResult (Ok z) = z
-stripResult (Error s) = error $ "JSON error: " ++ s
-
-pasteToDB :: AcidState Blog -> Entry -> IO (EventResult InsertEntry)
-pasteToDB acid !e = update' acid (InsertEntry e)
-
-main :: IO()
-main = do
-    tbDir <- getEnv "TAZBLOG"
-    bracket (openLocalStateFrom (tbDir ++ "/BlogState") initialBlogState)
-            (createCheckpointAndClose)
-            (\acid -> convertEntries acid)
-
-convertEntries acid = do
-    entries <- parseOldEntries
-    let r =  map forceHack entries
-    rs <- sequence r
-    putStrLn $ show rs
-  where
-    forceHack !x = do
-        xy <- pasteToDB acid x
-        return $ show xy
-
-testThis :: IO ()
-testThis = do
-  acid <- openLocalState initialBlogState
-  allE <- query' acid LatestPosts
-  putStrLn $ show allE
\ No newline at end of file
diff --git a/tools/convertdb/Makefile b/tools/convertdb/Makefile
deleted file mode 100644
index eba288ec1d..0000000000
--- a/tools/convertdb/Makefile
+++ /dev/null
@@ -1,13 +0,0 @@
-all: convertdb
-
-convertdb: couch.8 convertdb.8
-			8l -o convertdb convertdb.8
-
-convertdb.8: convertdb.go
-	8g convertdb.go
-
-couch.8: couch.go
-	8g couch.go
-
-clean:
-	rm -rf *.8 convertdb	
diff --git a/tools/convertdb/convertdb.go b/tools/convertdb/convertdb.go
deleted file mode 100644
index f7b94176b4..0000000000
--- a/tools/convertdb/convertdb.go
+++ /dev/null
@@ -1,116 +0,0 @@
-package main
-
-import (
-	"strconv"
-	"fmt"
-	"io/ioutil"
-	"json"
-	"./couch"
-	"os"
-	"time"
-)
-
-//old
-type OldComment struct {
-	Author string
-	Text   string
-	Date   string
-}
-
-type OldEntry struct {
-	Id       string
-	Title    string
-	Author   string
-	Text     string
-	Mtext    string
-	Comments []OldComment
-}
-
-//old
-type Comment struct {
-	Author string 	`json:"cauthor"`
-	Text   string 	`json:"ctext"`
-	Date   int64 	`json:"cdate"`
-}
-
-type Entry struct {
-	Id       string `json:"_id"`
-	Year     int    `json:"year"`
-	Month    int    `json:"month"`
-	Day      int    `json:"day"`
-	Lang     string `json:"lang"`
-	Title    string `json:"title"`
-	Author   string `json:"author"`
-	Text     string `json:"text"`
-	Mtext    string `json:"mtext"`
-	Comments []Comment 	`json:"comments"`
-}
-
-func main() {
-	getAllByYear("2011", 8, 12)
-	getAllByYear("2012", 1, 2)
-}
-
-func getAllByYear(year string, minm, maxm int){
-	db, _ := couch.NewDatabase("127.0.0.1", "5984", "tazblog")
-	for i:=minm;i<=maxm;i++{
-		dirList, err := ioutil.ReadDir(fmt.Sprintf("data/%s/%02d/", year, i))
-		if err != nil {
-			fmt.Println(err.String())
-			os.Exit(1)
-		}
-		for d:=len(dirList)-1; d>-1; d--{
-			content, cErr := ioutil.ReadFile(fmt.Sprintf("data/%s/%02d/%s", year, i, dirList[d].Name))
-			if cErr != nil {
-				fmt.Println(cErr)
-				os.Exit(1)
-			}
-			var oEntry OldEntry
-			jErr := json.Unmarshal(content, &oEntry)
-			if jErr != nil {
-				fmt.Println(jErr.String())
-				os.Exit(1)
-			}
-			nEntry := convertEntry(oEntry, fmt.Sprintf("data/%s/%02d/%s", year, i, dirList[d].Name))
-			eId, _, err := db.Insert(nEntry)
-			if err != nil {
-				fmt.Println(err.String())
-				os.Exit(1)
-			}
-			fmt.Println("Inserted " + eId)
-		}		
-	}
-}
-
-func convertEntry(oEntry OldEntry, p string) Entry{
-	var nEntry Entry
-	nComments := make([]Comment, len(oEntry.Comments))
-	for i:=0;i<len(oEntry.Comments);i++{
-		nComments[i].Author = oEntry.Comments[i].Author
-		nComments[i].Text = oEntry.Comments[i].Text
-		nComments[i].Date = parseDumbTime(oEntry.Comments[i].Date)
-	}
-
-	nEntry.Id 		= oEntry.Id[3:]
-	nEntry.Year, _  = strconv.Atoi(p[5:9])
-	nEntry.Month, _ = strconv.Atoi(p[10:12])
-	nEntry.Day, _	= strconv.Atoi(p[13:15])
-	nEntry.Title  	= oEntry.Title
-	nEntry.Author 	= oEntry.Author
-	nEntry.Mtext 	= oEntry.Mtext
-	nEntry.Text 	= oEntry.Text
-	nEntry.Comments = nComments
-	nEntry.Lang 	= "DE"
-
-	return nEntry
-}
-
-func parseDumbTime(ct string) int64 {
-	x, err := time.Parse("[Am 02.01.2006 um 15:04 Uhr]", ct)
-	if err != nil {
-		fmt.Println(err.String())
-		os.Exit(1)
-	}
-
-	return x.Seconds()
-}
\ No newline at end of file
diff --git a/tools/convertdb/couch.go b/tools/convertdb/couch.go
deleted file mode 100644
index 764eb49a60..0000000000
--- a/tools/convertdb/couch.go
+++ /dev/null
@@ -1,403 +0,0 @@
-// -*- tab-width: 4 -*-
-package couch
-
-import (
-	"bytes"
-	"fmt"
-	"os"
-	"json"
-	"http"
-	"net"
-	"io/ioutil"
-	"url"
-)
-
-var def_hdrs = map[string][]string{}
-
-type buffer struct {
-	b *bytes.Buffer
-}
-
-func (b *buffer) Read(out []byte) (int, os.Error) {
-	return b.b.Read(out)
-}
-
-func (b *buffer) Close() os.Error { return nil }
-
-// Converts given URL to string containing the body of the response.
-func url_to_buf(u string) []byte {
-	if r, err := http.Get(u); err == nil {
-		b, err := ioutil.ReadAll(r.Body)
-		r.Body.Close()
-		if err == nil {
-			return b
-		}
-	}
-	return make([]byte, 0)
-}
-
-type IdAndRev struct {
-	Id  string `json:"_id"`
-	Rev string `json:"_rev"`
-}
-
-// Sends a query to CouchDB and parses the response back.
-// method: the name of the HTTP method (POST, PUT,...)
-// url: the URL to interact with
-// headers: additional headers to pass to the request
-// in: body of the request
-// out: a structure to fill in with the returned JSON document
-func (p Database) interact(method, u string, headers map[string][]string, in []byte, out interface{}) (int, os.Error) {
-	fullHeaders := map[string][]string{}
-	for k, v := range headers {
-		fullHeaders[k] = v
-	}
-	bodyLength := 0
-	if in != nil {
-		bodyLength = len(in)
-		fullHeaders["Content-Type"] = []string{"application/json"}
-	}
-	req := http.Request{
-		Method:        method,
-		ProtoMajor:    1,
-		ProtoMinor:    1,
-		Close:         true,
-		ContentLength: int64(bodyLength),
-		Header:        fullHeaders,
-	}
-	req.TransferEncoding = []string{"chunked"}
-	req.URL, _ = url.Parse(u)
-	if in != nil {
-		req.Body = &buffer{bytes.NewBuffer(in)}
-	}
-	conn, err := net.Dial("tcp", fmt.Sprintf("%s:%s", p.Host, p.Port))
-	if err != nil {
-		return 0, err
-	}
-	http_conn := http.NewClientConn(conn, nil)
-	defer http_conn.Close()
-	if err := http_conn.Write(&req); err != nil {
-		return 0, err
-	}
-	r, err := http_conn.Read(&req)
-	if err != nil {
-		return 0, err
-	}
-	if r.StatusCode < 200 || r.StatusCode >= 300 {
-		b := []byte{}
-		r.Body.Read(b)
-		return r.StatusCode, os.NewError("server said: " + r.Status)
-	}
-	decoder := json.NewDecoder(r.Body)
-	if err = decoder.Decode(out); err != nil {
-		return 0, err
-	}
-	r.Body.Close()
-	return r.StatusCode, nil
-}
-
-type Database struct {
-	Host string
-	Port string
-	Name string
-}
-
-func (p Database) BaseURL() string {
-	return fmt.Sprintf("http://%s:%s", p.Host, p.Port)
-}
-
-func (p Database) DBURL() string {
-	return fmt.Sprintf("%s/%s", p.BaseURL(), p.Name)
-}
-
-// Test whether CouchDB is running (ignores Database.Name)
-func (p Database) Running() bool {
-	u := fmt.Sprintf("%s/%s", p.BaseURL(), "_all_dbs")
-	s := url_to_buf(u)
-	if len(s) > 0 {
-		return true
-	}
-	return false
-}
-
-type database_info struct {
-	Db_name string
-	// other stuff too, ignore for now
-}
-
-// Test whether specified database exists in specified CouchDB instance
-func (p Database) Exists() bool {
-	di := new(database_info)
-	if err := json.Unmarshal(url_to_buf(p.DBURL()), di); err != nil {
-		return false
-	}
-	if di.Db_name != p.Name {
-		return false
-	}
-	return true
-}
-
-func (p Database) create_database() os.Error {
-	ir := response{}
-	if _, err := p.interact("PUT", p.DBURL(), def_hdrs, nil, &ir); err != nil {
-		return err
-	}
-	if !ir.Ok {
-		return os.NewError("Create database operation returned not-OK")
-	}
-	return nil
-}
-
-// Deletes the given database and all documents
-func (p Database) DeleteDatabase() os.Error {
-	ir := response{}
-	if _, err := p.interact("DELETE", p.DBURL(), def_hdrs, nil, &ir); err != nil {
-		return err
-	}
-	if !ir.Ok {
-		return os.NewError("Delete database operation returned not-OK")
-	}
-	return nil
-}
-
-func NewDatabase(host, port, name string) (Database, os.Error) {
-	db := Database{host, port, name}
-	if !db.Running() {
-		return db, os.NewError("CouchDB not running")
-	}
-	if !db.Exists() {
-		if err := db.create_database(); err != nil {
-			return db, err
-		}
-	}
-	return db, nil
-}
-
-// Strip _id and _rev from d, returning them separately if they exist
-func clean_JSON(d interface{}) (json_buf []byte, id, rev string, err os.Error) {
-	json_buf, err = json.Marshal(d)
-	if err != nil {
-		return
-	}
-	m := map[string]interface{}{}
-	err = json.Unmarshal(json_buf, &m)
-	if err != nil {
-		return
-	}
-	id_rev := new(IdAndRev)
-	err = json.Unmarshal(json_buf, &id_rev)
-	if err != nil {
-		return
-	}
-	if _, ok := m["_id"]; ok {
-		id = id_rev.Id
-		m["_id"] = nil, false
-	}
-	if _, ok := m["_rev"]; ok {
-		rev = id_rev.Rev
-		m["_rev"] = nil, false
-	}
-	json_buf, err = json.Marshal(m)
-	return
-}
-
-type response struct {
-	Ok     bool
-	Id     string
-	Rev    string
-	Error  string
-	Reason string
-}
-
-// Inserts document to CouchDB, returning id and rev on success.
-// Document may specify both "_id" and "_rev" fields (will overwrite existing)
-//	or just "_id" (will use that id, but not overwrite existing)
-//	or neither (will use autogenerated id)
-func (p Database) Insert(d interface{}) (string, string, os.Error) {
-	json_buf, id, rev, err := clean_JSON(d)
-	if err != nil {
-		return "", "", err
-	}
-	if id != "" && rev != "" {
-		new_rev, err2 := p.Edit(d)
-		return id, new_rev, err2
-	} else if id != "" {
-		return p.insert_with(json_buf, id)
-	} else if id == "" {
-		return p.insert(json_buf)
-	}
-	return "", "", os.NewError("invalid Document")
-}
-
-// Private implementation of simple autogenerated-id insert
-func (p Database) insert(json_buf []byte) (string, string, os.Error) {
-	ir := response{}
-	if _, err := p.interact("POST", p.DBURL(), def_hdrs, json_buf, &ir); err != nil {
-		return "", "", err
-	}
-	if !ir.Ok {
-		return "", "", os.NewError(fmt.Sprintf("%s: %s", ir.Error, ir.Reason))
-	}
-	return ir.Id, ir.Rev, nil
-}
-
-// Inserts the given document (shouldn't contain "_id" or "_rev" tagged fields)
-// using the passed 'id' as the _id. Will fail if the id already exists.
-func (p Database) InsertWith(d interface{}, id string) (string, string, os.Error) {
-	json_buf, err := json.Marshal(d)
-	if err != nil {
-		return "", "", err
-	}
-	return p.insert_with(json_buf, id)
-}
-
-// Private implementation of insert with given id
-func (p Database) insert_with(json_buf []byte, id string) (string, string, os.Error) {
-	u := fmt.Sprintf("%s/%s", p.DBURL(), url.QueryEscape(id))
-	ir := response{}
-	if _, err := p.interact("PUT", u, def_hdrs, json_buf, &ir); err != nil {
-		return "", "", err
-	}
-	if !ir.Ok {
-		return "", "", os.NewError(fmt.Sprintf("%s: %s", ir.Error, ir.Reason))
-	}
-	return ir.Id, ir.Rev, nil
-}
-
-// Edits the given document, returning the new revision.
-// d must contain "_id" and "_rev" tagged fields.
-func (p Database) Edit(d interface{}) (string, os.Error) {
-	json_buf, err := json.Marshal(d)
-	if err != nil {
-		return "", err
-	}
-	id_rev := new(IdAndRev)
-	err = json.Unmarshal(json_buf, id_rev)
-	if err != nil {
-		return "", err
-	}
-	if id_rev.Id == "" {
-		return "", os.NewError("Id not specified in interface")
-	}
-	if id_rev.Rev == "" {
-		return "", os.NewError("Rev not specified in interface (try InsertWith)")
-	}
-	u := fmt.Sprintf("%s/%s", p.DBURL(), url.QueryEscape(id_rev.Id))
-	ir := response{}
-	if _, err = p.interact("PUT", u, def_hdrs, json_buf, &ir); err != nil {
-		return "", err
-	}
-	return ir.Rev, nil
-}
-
-// Edits the given document, returning the new revision.
-// d should not contain "_id" or "_rev" tagged fields. If it does, they will
-// be overwritten with the passed values.
-func (p Database) EditWith(d interface{}, id, rev string) (string, os.Error) {
-	if id == "" || rev == "" {
-		return "", os.NewError("EditWith: must specify both id and rev")
-	}
-	json_buf, err := json.Marshal(d)
-	if err != nil {
-		return "", err
-	}
-	m := map[string]interface{}{}
-	err = json.Unmarshal(json_buf, &m)
-	if err != nil {
-		return "", err
-	}
-	m["_id"] = id
-	m["_rev"] = rev
-	return p.Edit(m)
-}
-
-// Unmarshals the document matching id to the given interface, returning rev.
-func (p Database) Retrieve(id string, d interface{}) (string, os.Error) {
-	if id == "" {
-		return "", os.NewError("no id specified")
-	}
-	json_buf := url_to_buf(fmt.Sprintf("%s/%s", p.DBURL(), id))
-	id_rev := new(IdAndRev)
-	if err := json.Unmarshal(json_buf, &id_rev); err != nil {
-		return "", err
-	}
-	if id_rev.Id != id {
-		return "", os.NewError("invalid id specified")
-	}
-	return id_rev.Rev, json.Unmarshal(json_buf, d)
-}
-
-// Deletes document given by id and rev.
-func (p Database) Delete(id, rev string) os.Error {
-	headers := map[string][]string{
-		"If-Match": []string{rev},
-	}
-	u := fmt.Sprintf("%s/%s", p.DBURL(), id)
-	ir := response{}
-	if _, err := p.interact("DELETE", u, headers, nil, &ir); err != nil {
-		return err
-	}
-	if !ir.Ok {
-		return os.NewError(fmt.Sprintf("%s: %s", ir.Error, ir.Reason))
-	}
-	return nil
-}
-
-type Row struct {
-	Id  *string
-}
-
-type keyed_view_response struct {
-	Total_rows uint64
-	Offset     uint64
-	Rows       []Row
-}
-
-// Return array of document ids as returned by the given view/options combo.
-// view should be eg. "_design/my_foo/_view/my_bar"
-// options should be eg. { "limit": 10, "key": "baz" }
-func (p Database) QueryIds(view string, options map[string]interface{}) ([]string, os.Error) {
-	kvr := new(keyed_view_response)
-
-	if err := p.Query(view, options, kvr); err != nil {
-		fmt.Println("Query error: " + err.String())
-		return make([]string, 0), err
-	}
-	ids := make([]string, len(kvr.Rows))
-	i := 0
-	for _, row := range kvr.Rows {
-		if row.Id != nil {
-			ids[i] = *row.Id
-			i++
-		}
-	}
-	return ids[:i], nil
-}
-
-func (p Database) Query(view string, options map[string]interface{}, results interface{}) os.Error {
-	if view == "" {
-		return os.NewError("empty view")
-	}
-
-	var parameters string
-	for k, v := range options {
-		switch t := v.(type) {
-		case string:
-			parameters += fmt.Sprintf(`%s=%s&`, k, url.QueryEscape(t))
-		case int:
-			parameters += fmt.Sprintf(`%s=%d&`, k, t)
-		case bool:
-			parameters += fmt.Sprintf(`%s=%v&`, k, t)
-		default:
-			// TODO more types are supported
-			panic(fmt.Sprintf("unsupported value-type %T in Query", t))
-		}
-	}
-	full_url := fmt.Sprintf("%s/%s?%s", p.DBURL(), view, parameters)
-	json_buf := url_to_buf(full_url)
-
-	if err := json.Unmarshal(json_buf, results); err != nil {
-		return err
-	}
-	return nil
-}
diff --git a/tools/fixcomments.hs b/tools/fixcomments.hs
deleted file mode 100644
index dc89dbdd64..0000000000
--- a/tools/fixcomments.hs
+++ /dev/null
@@ -1,21 +0,0 @@
-
-fixComments :: AcidState Blog -> IO ()
-fixComments acid = do
-    entriesDE <- query' acid $ LatestEntries DE
-    entriesEN <- query' acid $ LatestEntries EN
-    filterComments entriesDE
-    filterComments entriesEN
-  where
-    (cDate :: UTCTime) = fromJust $ parseTime defaultTimeLocale "%d.%m.%Y %T" "22.04.2012 21:57:35"
-    foldOp :: [(EntryId, [UTCTime])] -> Entry -> [(EntryId, [UTCTime])]
-    foldOp l e = let c = map cdate $ filter (\c1 -> cdate c1 > cDate) $ comments e
-                 in if null c then l
-                              else (entryId e, c) : l
-    pred :: Entry -> Bool
-    pred e = let f eId [] = False
-                 f eId (c:r) = if (cdate c > cDate) then True
-                                                    else f eId r
-             in f (entryId e) (comments e)
-    filterComments entries = mapM_ removeComments $ foldl foldOp [] $ filter pred entries
-    removeComments :: (EntryId, [UTCTime]) -> IO ()
-    removeComments (eId, comments) = mapM_ (\c -> update' acid $ DeleteComment eId c) comments
\ No newline at end of file
diff --git a/tools/music/Makefile b/tools/music/Makefile
deleted file mode 100644
index 488c7eb1b0..0000000000
--- a/tools/music/Makefile
+++ /dev/null
@@ -1,10 +0,0 @@
-all: music
-
-music: iTunes.8
-			8l -o music iTunes.8
-
-iTunes.8: iTunes.go
-	8g iTunes.go
-
-clean:
-	rm -rf *.8 music
\ No newline at end of file
diff --git a/tools/music/gettitle b/tools/music/gettitle
deleted file mode 100755
index 0bd4cc6979..0000000000
--- a/tools/music/gettitle
+++ /dev/null
@@ -1,4 +0,0 @@
-#!/bin/bash
-
-osascript -e 'tell application "iTunes" to get name of current track'
-osascript -e 'tell application "iTunes" to get artist of current track'
diff --git a/tools/music/iTunes.go b/tools/music/iTunes.go
deleted file mode 100644
index 5eb530f6b3..0000000000
--- a/tools/music/iTunes.go
+++ /dev/null
@@ -1,79 +0,0 @@
-/* This program is free software. It comes without any warranty, to
- * the extent permitted by applicable law. You can redistribute it
- * and/or modify it under the terms of the Do What The Fuck You Want
- * To Do Public License, Version 3, as published by Vincent Ambo. See
- * included COPYING file for more details. */
-
-package main
-
-import( "fmt"
-	    "exec"
-		"strings"
-		"http"
-		"url"
-		"flag"
-		"os"
-		"time"
-)
-
-var authkey, host, c_artist, c_title string
-
-func init(){
-	flag.StringVar(&authkey, "key", "none", "http auth key")
-	flag.StringVar(&host, "host", "http://localhost:8080", "host")
-}
-
-func main(){
-	flag.Parse()
-	fmt.Println("Music updater launching. Update occurs once per minute.")
-	go updaterThread()
-
-	var cc string
-	for {
-		fmt.Println("Type \"exit\" to quit")
-		fmt.Scanf("%s", &cc)
-		switch(cc) {
-			case "exit":
-				os.Exit(1)
-			default:
-				fmt.Println("Type \"exit\" to quit")
-
-		}
-	}
-}
-
-func updaterThread(){
-	rValues := make(url.Values)
-	rValues.Add("artist", "")
-	rValues.Add("title", "")
-	rValues.Add("key", authkey)
-
-	for {
-		title, artist := getTrack()
-		if (title != c_title) || (artist != c_artist) {
-			fmt.Println("Updating to: " + title + " - " + artist)
-			c_artist = artist; c_title = title	
-			rValues.Set("artist", artist)
-			rValues.Set("title", title)
-			_, err := http.PostForm(fmt.Sprint(host + "/setsong"), rValues)
-			if err != nil {
-				fmt.Println(err.String())
-			}
-		}
-		time.Sleep(60000000000)
-	}
-}
-
-func getTrack() (title, artist string){
-	a, err := exec.Command("./gettitle").Output()
-	if err != nil {
-		fmt.Println("err: " + err.String())
-		title = ""
-		artist = ""
-	} else {
-		trackInfo := strings.Split(string(a), "\n")
-		title = trackInfo[0]
-		artist = trackInfo[1]
-	}
-	return
-}
\ No newline at end of file
diff --git a/tools/music/start b/tools/music/start
deleted file mode 100755
index b9f1358e34..0000000000
--- a/tools/music/start
+++ /dev/null
@@ -1 +0,0 @@
-./music -host "http://tazj.in" -key "4058ef41bbca252a7b7e675a61dbf935"
diff --git a/update.sh b/update.sh
deleted file mode 100644
index a4229f941b..0000000000
--- a/update.sh
+++ /dev/null
@@ -1,5 +0,0 @@
-#!/bin/bash
-
-hg pull
-hg update
-cabal install --reinstall
\ No newline at end of file