Wednesday, February 8, 2012

Cool vim trick.

I have always wanted to be able to replace a word in vim with matching case: if the word to be replaced was capitalized, have the replacement text be capitalized, and vice versa. Well now I can:


%s/\v(l|L)eft/\=(submatch(1) == "L" ? "R" : "r") ."ight"/

sub-replace-expression can be used for lots of other cool techniques too.

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.