Tuesday, December 13, 2011

Arm Board Second Try.

I built a new arm board because I mangled my last one removing the jtag header. The old one still works, but using jtag on it won't work. I can test firmware out on the fully functional one first I guess.

I took photos of halfway through, and of the final product.


Nearly all the through hole components are connectors. The only non-connectors are the two crystals, and 3 switches.

In other news, I got USART printouts working, and got polled debounced input from the switches working. The led's pulse, but turn off while you hold the switch.

Thursday, November 24, 2011

BJT H-Bridge.

Suppose you needed for current to be able to flow two directions through a component. Then you need 4
 switches around the component to form an H-bridge. You can do this with 4 transistors as well, 2 NPN or 2 PNP. You could also use FET's in a similar arrangement.

I recently realized that you could control both switches in the pair if you hooked it up right. Play with it on the Circuit Simulator.

I plan on using this arrangement to drive a two way latching a relay. A Brief pulse on one side sets the relay, and a brief pulse on the other side resets it.

ARM Development Board.

I built this ARM development board:


It includes everything you need to start programming the board. The board can be programmed via a serial bootloader, or via JTAG.

I'm programming it with completely custom firmware, so I figured out how to write a linker script, how to build a cross compiler for it, and how to setup the firmware so it starts executing.

I've done some simple exercises with it to make sure I understand how to use the devices.
I know how to use and setup the clocks, the dma controller, the general purpose IO's, the timers, the external interrupt controller. Next I'd like to get it to have the usart working so I can have debug printf's and status messages.

My motivation for building it was twofold. I wanted to learn to do surface mount soldering (check the full size image), and I wanted to learn to do micro-controller programming. Super powered arm chips like this one start at $2.00, so for many things where you would have used individual transistors or logic gates in the past, there's not many reasons left not to just use a micro controller.

Next up: Switch debouncing.

Friday, August 12, 2011

Enumerating all binary trees with n nodes.

An interesting problem came up when a colleague asked me to cleanly enumerate all binary trees of n nodes. They can be described as binary strings where 1 represents a non-null node, and 0 represents a null node, then you write out the tree in a pre-order traversal.

Here are some trees and their encodings:

Left to right, top to bottom:

11000  10100
1110000  1101000  1100100  1011000  1010100


It turns out this is related to a whole family of combinatorics problems, and it was easiest to frame it terms of another one: The grid description for monotonic paths that don't cross the diagonal here. The solution is to enumerate all the monotonic paths, but to stop as soon as the diagonal is crossed. It comes out cleanly in haskell:


module BinTreeEnum where

import Data.List
import Data.Monoid

data TStruct = NonEmpty | Empty deriving (Enum, Show)
type TreeDef = [TStruct]

printTStruct :: TStruct -> Char
printTStruct NonEmpty = '1'
printTStruct Empty = '0'

printTreeDef :: TreeDef -> String
printTreeDef = map printTStruct

enumBinTrees :: Int -> [TreeDef]
enumBinTrees n = enumBinTrees' n n where
  enumBinTrees' ups rights | rights < ups = mempty
  enumBinTrees' 0   rights = return (replicate (rights+1) Empty)
  enumBinTrees' ups rights = do
    step <- enumFrom (toEnum 0)
    let suffixes =
          case step of
            NonEmpty -> enumBinTrees' (ups - 1) rights
            Empty -> enumBinTrees' ups (rights - 1)
    suffix <- suffixes
    return (step:suffix)

mainExample = do
  print $ map printTreeDef $ enumBinTrees 4


Here's what you get when you run it:

print $ map printTreeDef $ enumBinTrees 3
["1110000","1101000","1100100","1011000","1010100"]


Which exactly maps to the list of binary trees from above.
It was a fun little problem.

Sunday, April 24, 2011

Composability of Iteratees.

For this post, we'll consider composition within the same stream as vertical composition, and transforming one stream to another as horizontal composition. Think of streams flowing down the page. For category theorists, these aren't the standard horizontal vertical, but they work here.

The composability of the three main types in the enumerator package can be summarized as follows:


EnumeratorEnumerateeIteratee
EnumeratorMonoid (Vertical)
EnumerateeEnumerator (Horizontal)  Category (Horizontal)
IterateeIteratee (Vertical)Iteratee (Horizontal) Monad (Vertical)

Let's start with the diagonals.

Enumerators form a Monoid.
Enumerators form a Monoid, via concatenation, similar to lists. The instance declaration is straightforward:

instance (Monad m) => Monoid (Enumerator a m b) where
  mempty = returnI
  mappend = (>==>)

>==> is defined in the standard enumerator package:

(>==>) e1 e2 s = e1 s >>== e2

Simply, given the two enumerators to join, and a step, feed the first one to the step, and then the second one. This is a horizontal composition.
Enumeratees form the arrows of a Category.
Don't get scared, that simply means that
a) there is an identity Enumeratee
b) Enumeratees can be composed like functions.

The identity Enumeratee:

idEnumeratee :: (Monad m) => Enumeratee a a m b
idEnumeratee = checkDone (continue . step) where
  step k EOF = yield (Continue k) EOF
  step k (Chunks xs) = k (Chunks xs) >>== checkDone (continue . step)

That was the simple part. Now the composition of Enumeratees:

(.=) :: forall m ao am ai. (Monad m) =>
  (forall b. Enumeratee am ai m b)
  -> (forall b. Enumeratee ao am m b)
  -> (forall b. Enumeratee ao ai m b)

en_mi .= en_om = \step_i -> joinI $ en_om $$ en_mi step_i

Here, i is the inner type (stream data goes from out to in) m is the middle type, and o is the outer type. The type signature is slightly complex because the eventual result of the consumer is independent of composing the streams.

Now to go through the definition. The types of various pieces explain what's going on.

en_mi step_i :: Iteratee am m (Step ai m b)
en_om $$ en_mi step_i :: Iteratee ao (Step am (Step ai m b))
joinI :: Iteratee ao (Step am m z) -> Iteratee ao m z
joinI $ en_om $$ en_mi step_i :: Iteratee ao (Step ai m b)
-- replace z with (Step ai m b)

joinI simply sends EOF to the inner iteratee when the outer one yields, removing the chance for feeding it anything else. We use it here to remove the chance to feed any more am's to the stream, because the result type doesn't have any reference to am.
Iteratees form a Monad.
This is covered in the code, and in a previous post

Now for the off diagonal entries.


For all the joining operators, = represents an Enumeratee (think of = as looking like a pipe), and $ represents a consumer or producer.
Enumeratee + Iteratee == Iteratee.
Thinking of it like pipes sources and sinks, a pipe connected to a sink is still a sink. The operator defined in the enumerator package is =$. Thinking of data flowing from left to right, that looks like a pipe hooked up to a right end. This is a horizontal composition.
Enumerator + Enumeratee == Enumerator.
This is symmetrical to the above case, as is the operator $=. Here the end is on the left, and the pipe is on the right. This is also a horizontal composition
Enumerator + Iteratee == Iteratee.
This returns the partially completed Iteratee. More data can be fed to the result iteratee as kind of concatenation after the fact. The operator matches the mnemonic above $$ matches both ends of the pipe. This is a vertical composition.
Example concatenation:
enum2 $$ enum1 $$ iter == (enum1 `mappend` enum2) $$ iter
-- note the order reversal.

Sunday, April 17, 2011

The Monad instance for Iteratees

I'd like to walk through the Monad instance for Iteratees. Understanding the monad instance makes it easier to understand whats happening when you try and write a moderately complex iteratee


>instance Monad m => Monad (Iteratee a m) where
> return x = yield x (Chunks [])


The definition of return should be straightforward. Return creates an iteratee that is immediately ready to yield x without any accepting any data, and without adding any extra data.


($ m0) $ applies m0 to the giant function that follows.
fix $ \bind m creates a recursive function named bind, with m0 passed as m initially. note the type for bind:

bind :: Iteratee a m b -> Iteratee a m c, this will be useful later


> m0 >>= f = ($ m0) $ fix $



Iteratee $ runIteratee m is standard unwrapping. The >>= is for the inner Monad.



> \bind m -> Iteratee $ runIteratee m >>= \r1 ->
> case r1 of


Here the iteratee hasn't returned yet, so we compose the continuation with bind, creating essentially a while loop. While the first iteratee hasn't returned yet, keep asking for data, and checking its result. Also note the types:
>>= :: Iteratee a m b -> (b -> Iteratee a m c) -> Iteratee a m c
k :: a -> Iteratee a m b
(bind . k) :: a -> Iteratee a m c


> Continue k -> return (Continue (bind . k))
> Error err -> return (Error err)


If the source Iteratee finally yields, with no extra data then (f x) is the iteratee we want to return.


> Yield x (Chunks []) -> runIteratee (f x)


If there's any extra data, we first grab the step from the inner Monad. If it's a Continuation, we feed it the extra before returning. Otherwise, we pass along the extra.


> Yield x extra -> runIteratee (f x) >>= \r2 ->
> case r2 of
> Continue k -> runIteratee (k extra)
> Error err -> return (Error err)
> Yield x' _ -> return (Yield x' extra)


An important thing to note is what happens in the case of EOF. The EOF would be on returned along with the Yield, and then fed to the second Iteratee. It's possible that a chain of Iteratees could be resolved like this.


Another important thing to note is that the type a remains fixed. The monad instance of an Iteratee allows you to compose functions that read from the same stream. It's also possible to transform streams, but that's not  what's going on here.

Implementing scanl for Iteratees

In looking over Data.Enumerator.List, I noticed that scanl was missing, So I set out to write it. I'm posting it as a literate Haskell file. I intend to create a patch for the maintainer.

Start with a standard module declaration


>module Data.Enumerator.Scanl where
>
>import Prelude hiding (scanl, scanl1)
>import Data.Enumerator
>import qualified Data.Enumerator.List as EL


The code seems strangely devoid of an operator for repeatedly chaining enumeratees together, so I created one.


>infixl 0 $|
>($|) :: Monad m
>      => Enumerator ao m (Step ai m b)
>      -> Enumeratee ao ai m b
>      -> Enumerator ai m b
>($|) = joinE


scanl takes a function and a seed value, and combines the seed and any input to get a new seed. The seeds (including the first) are fed along the pipe.


>scanl :: (Monad m) => (ai -> ao -> ai) -> ai -> Enumeratee ao ai m b


I borrowed the structure of Data.Enumerator.List.map for most of this. CheckDone is a common construction for Enumeratees, if the inner iteratee yields, the outer one yields as well.


>scanl op ai0 = checkDone (continue . step ai0) where


The final step here is important. For map it is:


  step k EOF = yield (Continue k) EOF


For scanl, we have one more piece of data (the last seed) that needs to be fed into the iteratee.


>  step ai0 k EOF = k (Chunks [ai0]) >>== \step -> yield step EOF
>  step ai0 k (Chunks xs) = loop ai0 k xs
>
>  loop ai0 k [] = continue (step ai0 k)


Note that we compute the next seed and store it, but send the old seed to the iteratee.


>  loop ai0 k (x:xs) = case ai0 `op` x of
>    ai1 -> k (Chunks [ai0]) >>==
>      checkDoneEx (Chunks xs) (\k' -> loop ai1 k' xs)


And now, some test code:


>cubes :: Monad m => Enumerator Integer m b
>cubes = EL.replicate 7 6 $| scanl (+) 12 $| scanl (+) 7 $| scanl (+) 1


The important thing about the test code is that there should be exactly 10 cubes in the list. Each scanl adds exactly one element, and we start with 7 repetitions of 6, so we should (and do) have 10 cubes.
and to test:

>main = do
>  list <- run_ $ cubes $$ EL.take 10
>  print list

Friday, April 15, 2011

Iteratees part II

I'd like to go over the basics of the enumerator package for Haskell, covering the types, and re-solving the cube-permutation problem from the last post. I'm not the first to cover this, see this explanation of the enumerator package.

The first datatype defined in the enumerator package is Stream:



data Stream a
= Chunks [a]
| EOF
deriving (Show, Eq)

Which is fairly straightforward. Next is a Step:



data Step a m b
= Continue (Stream a -> Iteratee a m b)
| Yield b (Stream a)
| Error Exc.SomeException



I'll explain what an Iteratee is next. A step is one of 3 states: Continue, it can accept more data. Yield, it can't accept any more data, and Error, an error occured. Note that unlike EarlyFoldable, a Step doesn't have a type for the state, instead it passes a continuation that holds the state.


So what is an Iteratee? It's simply a Step wrapped in a Monad.



newtype Iteratee a m b = Iteratee
{ runIteratee :: m (Step a m b)
}

Let's see if we can solve the cube problem using an iteratee.




module Main where


import Data.List
import Data.Enumerator hiding (head, foldl', repeat)
import qualified Data.Enumerator.List as EL (head)
import qualified Data.Map as M


digitize :: (Integral a) => a -> [a]
digitize 0 = [0]
digitize n = (reverse . (unfoldr strip_digit)) n
    where 
        strip_digit 0 = Nothing
        strip_digit a =
            case (a `divMod` 10) of
                (a,b)  -> Just (b,a)


undigitize :: Integral a => [a] -> a
undigitize = foldl' (\x y -> x*10+y) 0


--digitize and undigitize are for number processing


cubes :: [Integer]
cubes = scanl (+) 1 $ scanl (+) 7 $ scanl (+) 12 $ repeat 6


make_key :: Integer -> Integer
make_key = undigitize . sortBy (flip compare) . digitize


update_map :: Integer -> M.Map Integer (Integer, Int) -> M.Map Integer (Integer, Int)
update_map n = M.insertWith
  (\(n2, count2) (n1, count1) -> (n1, (count1+count2)))
  (make_key n) (n, 1)


--cubes, make_key and update_map are the same as from last time.


cube_perm_iteratee :: (Monad m) => Iteratee Integer m Integer
cube_perm_iteratee = go M.empty
  where
    go m = do -- Iteratee's are a Monad, to be covered later.
      (Just n) <- EL.head --EL.head reads at most one element.
      case update_map n m of
        m' | (snd $ m' M.! (make_key n)) == 5 ->
          yield (fst $ m' M.! (make_key n)) (Chunks [])
        m' -> go m'


main = do
  -- The driver code will be covered on another article on Iteratees
  result <- run_ $ (enumList 100 cubes) $$ cube_perm_iteratee
  print result



Wednesday, April 13, 2011

Putting an early terminating left fold to work.

I'd like to go over a piece of code that I wrote a while ago to solve a simple problem: Find the first cube to have 5 permutations of its digits that are also cubes. It's a project euler problem. My solution:

class EarlyFoldable f where
    earlyFoldlc :: (a -> b -> Either c a) -> a -> c -> f b -> c
    earlyFoldl :: (a -> b -> Either a a) -> a -> f b -> a
    earlyFoldl h a f = earlyFoldlc h a a f
    {-# INLINE earlyFoldl #-}

instance EarlyFoldable [] where
    earlyFoldlc f a c [] = c
    earlyFoldlc f a c (b:bs) =
        case (f a b) of 
            Left c' -> c'
            Right a' -> earlyFoldlc f a' c bs

p62_cubes = scanl (+) 1 $ scanl (+) 7 $ scanl (+) 12 $ repeat 6
p62_make_key = undigitize . sortBy (flip compare) . digitize
p62_update_map n = M.insertWith (+) (p62_make_key n) 1
p62_early_update m n =
    case p62_update_map n m of
        m' | m' M.! (p62_make_key n) == 5 -> Left n
        m' -> Right m'

p62 = earlyFoldlc p62_early_update M.empty 0 p62_cubes.

Now, some explanation. I defined a type class for an early terminating fold, with the obvious instance for list. earlyFoldlc returns Either c a, where c is the return type, and a is an intermediate state: an accumulator. The definition of p62_cubes should be familiar from a previous post. p62_make_key simply makes an integer key out of an integer. (It sorts the values in descending order so that zeros aren't lost.) p62_update_map is a simple helper. This is a case where we can't use a standard left or right fold. We can't use a standard left fold because the list is infinitely long, and we can't use a right fold because we need to look at the accumulated value before deciding to return.

Sunday, April 10, 2011

Computing Integer powers without multiplication.

An interesting fact about the squares is that if you're computing a list of them, you can do it without multiplication. A quick examination of the squares and their differences shows how:

 3 5 7  9  11  13  15  17  19
1 4 9 16 25  36  49  64  81  100


Cursory examination shows that the differences of the differences is 2. We could exploit this to create an infinite list of the squares in Haskell:


squares = scanl (+) 1 $ scanl (+) 3 $ repeat 2


scanl is a cousin to foldl, but it computes all the intermediate results as well. (If this is unfamiliar, scans and folds are fairly simple ways to learn a little Haskell.)


For a programming task, I needed a list of all the cubes. It turns out that you can do something similar with the cubes.

    6   6   6   6    6
  12  18  24  30   36    42 
 7  19  37  61   91   127   169
1 8   27  64  125  216   343  512  729  1000


cubes = scanl (+) 1 $ scanl (+) 7 $ scanl (+) 12 $ repeat 6


In order to do the cubes, you have to have one more level of indirection. Being curious, I wanted to figure out where the inital values came from, and If we could generalize to any integer power of integers. I calculated out the values for n^4, and the starting values were 1,15,50,60,24. This, combined with the initial values for cubes, made me think of the Stirling numbers. It looks like the starting values are:

{n} * k!
{k}


Where n is the power, and k is the row, bottom first. You can prove this is true for any n. Consider the operator ∆: ∆f(x) = f(x+1) - f(x). (∆ is the h-derivative for h = 1). ∆(xn) is hard to compute, but the function x to the n falling: xn = x*(x-1)*(x-2)*...*(x-n) is much nicer. ∆xn = nxn-1. The Stirling numbers relate ordinary powers to falling powers. xn = ∑{n k}xk


Applying ∆ to the above equation, we get:
1xn = ∑k>1k{n k}xn-1 + 1!{n 1}.
Repeating, we get
2xn = ∑k>2k(k-1){n k}xn-2 + 2!{n 2}.
By extension,
j(xn) = ∑k>jk!/(k-j)!{n k}xn-l + j!{n j}.
n(xn) = n!{n n} = n!.

A quick test on n = 5 helps to verify this. The stirling numbers for n = 5 are: 1, 31, 90, 65, 15, 1. So the starting coefficients for n = 5 are 1*0! = 1, 31*1! = 31, 90 * 2! = 180, 65 * 3! = 390, 15 * 4! = 360, 1 * 5! = 120.


            120
         360   480
      390   750    1330
   180   570   1320    2550
 31   211   781    2101    4651
1   32   243   1024    3125    7776


Yep, everything looks like 5th powers.

Saturday, April 9, 2011

On Iteratee's, part I

There's a concept that's been explored recently in Haskell, the idea of enumerated IO. I'd like to go over the idea in detail.

Folds.

The basic idea is that of a fold. In Haskell, there are two basic folds over lists.

foldr :: (b->a->a) -> a -> [b] -> a
foldr f y0 [] = y0 -- folding an empty list returns the base case.
foldr f y0 (x:xs) = f x (foldr f y0 xs)


-- Note that outermost is f. This is important in Haskell.
-- You can right fold over an infinite list, but not a left fold.


foldl :: (a->b->a) -> a -> [b] -> a
foldl f y0 [] = y0 -- folding an empty list returns the base case.
foldl f y0 (x:xs) = foldl (f x y0) xs


-- There's also a strict version foldl'.


Read "foldr ::" as "foldr has the type". foldr takes a function, a value of type a, a list of b's, and returns an a.
foldl is similar. For this post, we'll mainly deal with left folds. A good example to start with is the function sum:


sum :: [Int] -> Int  --sum maps a list of Ints to an Int
sum xs = foldl (+) 0 xs


reverse :: [a] -> a
reverse as = foldl (flip (:)) [] as


A left fold has the advantage that it uses an accumulating parameter. It gets compiled down to a tight loop. You would write sum as a strict left fold. A right fold has the advantage that it can skip part of the input. You would write and as a right fold.

and :: [Bool] -> Bool
and as = foldr (&&) True as.


This has the nice property that it returns as soon as it sees a False (short circuit evaluation).
There's a way to get both properties in a left fold. It's called an early terminating left fold.

etfoldl :: (a->b->(a, Bool)) -> a -> [b] -> a
etfoldl f y0 [] = y0
etfoldl f y0 (x:xs) =
  case (f y0 x) of
    (y, True) -> y  -- True means we're done.
    (y, False) -> etfoldl f y xs


I used it to solve some problems where I was looking for the smallest value that satisfied some condition, but I had to chain some data structure along. Early terminating folds are a good place to stop.


Next up, Iteratees, A generalization of early terminating folds.
                          

Friday, April 8, 2011

Blog Title

A few of my readers may be wondering: "What is a zeppelin bend?" It's a knot.
It gets more nerdy. The reason I chose a knot, is because one of the coolest things you'll encounter if you learn Haskell is Knot Tying, which is essentially passing the result of a computation into the computation, (Think like a credit card, buy now, pay later). It works as long as you don't peek at the result. You can use it to create loops in data structures in a pure way. In most other languages, you would just use mutable state.

My work on RestyGWT

For those that aren't in the know about Java and Google, GWT is the Google Web Toolkit. It's a magical framework that turns Java into JavaScript, and wishes into rainbows. One cool feature is that you can write server rpc's that have the same interface in Java and JavaScript.  This works great if you only intend to write your server in Java, or your clients in GWT.  I didn't want that constraint, so I looked around and found RestyGWT, which does similar magic to allow you to call REST interfaces just like they were java methods.

I added the ability to send and receive overlay types, which get compiled to native javascript objects. Basically you use the JSON data returned via rest as is, rather than processing into a Java Object, which is a little more heavy weight. It's also useful in cases where the server and client don't share a codebase, or even the same language. Since you'd have to model the data in Java anyway, it might as well be an overlay type.

Wednesday, April 6, 2011

Dummy components for soldering practice.

Short answer: Don't bother.

If you're a single person trying to learn to surface mount solder, you might think "Hey rather than waste real chips when I screw up, maybe I should get blanks or dead chips to practice with." I looked into it. You're better off ordering cheap breakout boards and cheap live chips. The main producers of dummy chips are Topline, and Practical Components. Neither list their prices online, meaning you have to email a sales representative to figure out if their prices are even within reason for what you want. Both sites have $50 minimum orders, but practical components will charge you $10 if you order less than $50. Topline just has a minimum. I only looked at Topline's prices, as I didn't want to have to do the whole "sales rep" thing again. Their kits are ridiculously expensive, one kit they wanted $90 for 4 chips and a pcb to solder them to. Their dummies are closer to reality, but still outside of it. With a minimum order of $50, They want $2.50 for an lqfp-64 0.5mm chip. I can get a real microcontroller from mouser 10 at a time for less than that.  Get some breakout boards from Futurelec, and some cheap chips from Mouser or DigiKey. I'm sure these guys have a place in larger companies, but if it's just you, don't bother. They don't want your business anyway.

The magic of + in gmail.

I learned at work the other day that gmail supports address tags. Basically you put user+tag@gmail.com, and the email gets delivered to you, just like if it were to user@gmail.com. Some websites won't accept '+' in email, but for sites that do, when you sign up for something and they ask for an email, you should place +sitename at the end. What does this get you? You can find out who's giving out your email address to third parties. It also makes writing filters easier. If you want all your amazon related email to get tagged as amazon, it's not enough to just use from: @amazon.com, because if you buy something from the marketplace, often the seller will email you. Here, you can just filter on user+amazon@gmail.com. This would be useful for mailing lists as well, as often the "you have subscribed" emails come from a different address.

This feature became useful for me recently. Since I started working at google, I haven't been checking my gmail quite as frequently. So I set up a forward to Tanya for all of my mail. This creates a problem if I want to order something for her birthday. So I changed my amazon email address to me+secret@gmail.com, and then made the forward only work for emails not delivered to me+secret.

Try it out.