November 08, 2007

Wordpress

I've decided to head off to blogpress, I rather like the setup there better, the blog will now be located at:

http://lowlymath.wordpress.com/

Also, I've started working (no posts yet) on a new blog. The topic is skepticism and critical thinking. I hope to dabble on things from standard pseudoscience (like homeopathy and autism/antivaccination idiocy) to illusionists and magic. Hopefully with some leans to math and computer science (especially with one of Derren Browns excellent tricks and how it relates to genetic algorithms.

In addition, I've been toying with the idea of doing a podcast, mostly on stuff I rant about here. But I'm not sure-

Speaking of podcasts, everyone check out The Skeptics Guide, it's really quite good.

Anyway, thanks all for reading here, hope you'll continue to read at the new site!

October 01, 2007

On Raytracers, The Quantum Kind

Well, maybe not quantum -- but wavestream based light ray tracing software didn't have the same, y'know, ring to it. Let me give you the backstory.

This semester I'm taking one of my requisite natural science classes, In trying
to find a class which looked the least boring, I managed to find an Optics class. In Optics, we learn about the dual nature of light, a subject which has always fascinated me. In much of mathematics and physics, there is an inherent duality, a separation between two objects which simultaneously brings them together. When you get to Optics, we find that light- in on of the weirdest twists ever - manages do be its own dual, separate from itself, if you will. Light, as we (maybe) well know, has both wave-like and particle-like properties. My Optics Professor calls it the "Packet of Wiggling String" interpretation. This interpretation helps to explain things like the double slit experiment. It is this particular experiment that I want to talk about now.

I've fiddled with ray tracers before in my life, but I've never thought to try the double slit experiment in one of them, I cooked up a little pov-ray script to test my theory that, in fact, ray tracing is classical. Granted thats an obvious result to most, but think about it, raytracing is classical. You can't replicate the double slit experiment in Povray, more accurately, you can't treat light as a wave in Povray. only as a particle stream.[1] As far as I can tell, this gross approximation of light-- limited reflection calculation, particle stream vs wave, etc -- was based on limitations of hardware when the technique was invented, they simply _couldn't_ simulate things like the Double slit experiment. Perhaps more surprisingly, Prism's don't work the way they should either, since they won't separate light based on wavelength.

NOTE:: As an aside, probably the most fascinating thing we have learned in optics so far is how prisms separate light into its component colors. I thought a short description might pique your interest, so here you have it.

When light travels through certain substances (usuall called media (singular medium)), it slows down and actually bends due to a phenomenon called refraction. Refraction is really just an application of Fermat's Principle (that light will always take the fastest path between two points[2]). The easiest way to see refraction is by looking through a magnifying glass, a magnifying glass is a medium made of glass, which has a special, dimensionless number called an "index of refraction" at around 1.5, air has a IOR of about 1, and a vacuum (like space, not like a hoover) has a IOR of exactly 1, there is no substance with an IOR



n * sin(I) = n' * sin(I')



where n, n' are the IOR's of the two media (n being the IOR of the medium from which the light originated.)
and I,I' the angles at which the light (or lifeguard) "impacts" the medium

This equation, called Snell's Law (not snail, snell, it rhymes with "sell"), gives us a simple way to solve the lifeguard problem. By knowing the distances from shore both we, and the victim are[5] we can determine a shortest path using some trigonometry, which I'll leave as an exercise to the reader, since I don't have any good visualization software to draw all the necessary pictures (xpaint will _not_ be sufficient, and the 15 minute time limit on Cinderella2 is beyond
annoying.) Regardless, this is the same math that governs refraction, however, there is something I have not explained.

n is not a constant.

This shook my soul, at first, how can n not be a constant? If we have one uniform material, we assume no inconsistencies in the material when we do our math- the only possible thing it could depend on would be light itself, but if light is a uniform particle stream then this couldn't be the case.

Shocking revelation number two, light isn't a particle stream.

Refraction works on a particle stream, it makes _sense_ on a particle stream, in fact, the very reason for refraction really doesn't make sense on a standing wave- because how can a infinitely long wave slow down? Thats just silly. So really, this whole refraction business leads us to a more quantum interpretation, but for simplicity, we'll pretend it all works with waves.

n is a function of the wavelength of the light approaching the medium, this is important, because it tells us something interesting about light. Consider the prism, we all have seen how the prism can split apart light in an amazing display of party trickery into all its very pretty colors. Prism's truly are the life of the optical party, useful for all sorts of stuff, from periscopes to spectrometers. In any case, how can a prism split white light into a bunch of different wavelengths? We can't create something out of nothing, so we are left with only one explaination, white light _is_ all of the component colors. This leads us to see that really- when we see white light, we are seeing the superposition of many different wavelengths of light, and this gives us why a prism works. If n is just a function of wavelength, and white light is a superposition of different wavelengths, then each wavelength will bend more or less depending on _its_ own value for n, this means that when the light exits the prism, due to it's shape[6], it will remain separated, and create a beautiful collage of colorfulness on whatever the light happens to land on.

So, enough rambling about Optics, what has all this got to do with raytracing? Well, I realized that you can't build a prism in a raytracer, because it treats its light not only as a simple particle stream, but also as having a unique wavelength (of sorts) for each of its colors. In Povray, you specify color as a vector, nothing special, just a vector. Why not treat color as a series of wavelengths? Heck, we don't even need to give up our lovely RGB method, theres
very likely a way to convert from wavelengths to RGB and back. We would have a problem with the way Raytracers currently treat light and color, since we say that objects and light _have_ color, when in reality light is usually white, and the things it touches _absorb_ color and have some amount of transparency, which gives the illusion of colored light. Potentially we could specify the color of light which is emitted and the color(s) of light which are absorbed by the surfaces we create- but the latter of that bit might be more difficult. This is besides the point[7]. I suppose what I am suggesting is that we consider ways to incorporate the wave nature of light into our raytracers, since we could potentially add quite a bit of very interesting new capabilities, like prisms, interference effects, etc. It would also add to the wonderful photorealism effects, I think, since the light would be specified in a way that is more like
reality.

Just thoughts, I suppose, I'm certainly no expert in Raytracing. However, oh dear Lazyintarweb, if you are, please- tell me whether this could actually work, maybe I'll try to build it, someday.


[1] In fact, only as a particle. Since we only view the ray's reflections once.
[2] In reality, the principle is stated (mostly) as follows: Light will always
seek the path which minimizes its travel time. There is a subtle difference, but I think for our purposes, the simpler statement suffices. Also note that fastest doesn't necessarily mean shortest, since we're dealing with speed changes too.
[3] I don't think I'm wrong, but maybe exotic substances or whatever creates wormhole things might? I'm not sure how that works, I'm just a mathematician who likes pretty lightshows, not a physicist.
[4] Yes, I know there is the whole non-euclidean geometry of space thing, geodesics and whatnot, but bear with me.
[5] I never realized lifeguarding was such a deep realm of math.
[6] Namely, the triangluar shape of the classic prism prevents the light from bending back towards the normal, and reforming the normal white light. A thoroughly less satisfying party trick, to be sure.
[7] In fact, at this point, I have practically forgotten what the point was.

August 10, 2007

Why Testing code should be Laissez-faire

I've been working on the HFA Library some more, and got to the point now were I really want to start testing it deeply. Since HFA is in Haskell, the weapon of choice for testing pure code is QuickCheck. The interesting bit about QC is that test data is fundamental random. This is great for two reasons.

1) It forces you to actually test for _general_ properties of objects/functions, rather than specific properties of certain instances of those structures, like a unit test does
2) By Generating Random Data, you don't have to worry about being too nice or too mean to your program, as with unit testing.

I'll state it now, for the record, Unit Testing is great. I wouldn't test my Java (or soon enough, Scala, ^_^) programs with (mostly) anything else. However, when you have referential transparency on your side, QuickCheck is a superior system.

The real brilliance of QuickCheck though, is that it is extensible enough that you can define new "checkable" items, that is, instead of having to use the standard checkable types when checking a function, you can define how QuickCheck can generate random data for a particular type by making it an instance of the Arbitrary class, which is defined by QuickCheck. This means that, as long as you can define a couple of methods for your datatype, it is damn near trivial to have QC generate examples of your datatype and test them quickly.

Why is this good? Well, consider you're writing unit tests for your code. You've been intimately involved with this mangled peice of imperatively worded text for days and weeks. You know every inch of it, and you have in your mind the next new feature you want to add. It is not uncommon (at least for me) to begin writing and toying with the code in your mind, figuring out where potential bugs might be. As a human being, you are typically not looking to make things harder for yourself than needbe. So maybe, when you're writing those unit-tests that will guide your programming to ensure that the code is written correctly, you -- maybe subconciously, maybe not -- decide to make those few unit tests a little bit easier on the part of the code that you think is more fragile. I'm guilty of this, certainly, and I'm sure if you're honest with yourself and you've developed a good bit of code with the test-first methodology (which I like only mildly less than the test-shortly-after-you-realize-you're-supposed-to-write-tests-first methodology), that you would find that you've done it too. QuickCheck fixes that wagon pretty quickly, you don't get to reason about how hard some tests will be on the code, QuickCheck enforces a "Hands Off" or "Laissez-faire" (I'm french, and I like history, sue me.) form of testing. You don't get to decide what is tested, just what the result should be, which is how it _should_ be done. I _shouldn't_ be thinking about what data I want to test, I shouldn't have to write all the test-data, ideally, I should only have to say, "minimizing a DFA twice is equivalent to minimizing a DFA once" or "if the regular expression foo is generated by DFA f, and the expression foo' is generated by the minimized version of f, then foo == foo' for all f::DFA." I guess the point is, the computer is unbiased, it won't be nice to the code, it won't be mean to it, it'll be fair. Is that to say that coders will be biased towards or against their code? Yes, it is, we spend alot of time with these projects, we develop a vested interest in seeing them work, finding out that you did something wrong can be discouraging. Granted, small things may not devastate you, like using the wrong function name, or misplacing a variable. But if you're unit test catches a major flaw in the structure of a program you designed, that represents alot of work that just got blown to peices. At the very least, if not for your pride, testing systems like QC are good for your productivity, they allow you to test a (potentially) huge number of arbitrary cases every time you run your program. Heck, you could even have QC running live against your code in the background, telling you in real time what tests your failing, what cases gave you failures, etc. All of that is Automatic and Vital data, its 24/7/365 testing of your code, for free. Slowly building assurance that your code is, in fact, doing the right thing on all inputs.

By the way, Yes, I know many, many people have written about QuickCheck before, and about how wonderful it is, but I think it's always worth saying again. Good Ideas deserve to be talked about, QuickCheck is a _very_ good idea.

August 05, 2007

DFAs, Categories, and Typecheckers.

I've recently started reading (in parallel) "Type and Programming Languages" and "Basic Category for Computer Scientists." The latter of which is really only interesting if you're a math junky, like me. It's somewhat dry, and very matter-of-fact, but the subject is terribly interesting.

Whilst reading these books, I've also been working on a library for Haskell called "HFA" (pronounced: "Huffa", or if your feeling silly, "Hoffa"), for "Haskell Finite Automata." The library's purpose is to create a simple to use, generic, relatively fast implementation of various Automata (Notably (D|N)FA's, PDAs, Turing Machines, etc.), so that anyone intending to use these abstractions will be able to without knowing much about the internal theory, eg how to minimize a DFA, or how to convert an NFA to a DFA, etc. It's also intended to be available as a easy to understand tool for learning/teaching about automata, it will eventually have the ability to display Automata as Graphviz graphs, and is currently capable of generating state diagrams (with some extensions to mark final, initial, and initial-final states).

Recently, I had just finished writing some refactor code for HFA, and decided to take a break and read "Basic Category Theory" for a while, it dawned on me upon looking at the diagram of a category that what I was looking at was essentially a DFA, with all states final, and the arrows between them being processing parts of the Delta Functions. That is, if a Category is defined as a a set of objects, and a set of arrows (where an arrow is defined as f : A -> B, where A and B are objects in the category), then the equivalency is as follows:


Category DFA
Objects States
Arrows Transitions

with delta(S,x) = S' iff there is an arrow between x is an arrow between S and S'.

Notably, we can also define a DFA as a Category by simply reversing the definition. I'm pretty sure this fact has been discovered before, its to obvious to believe otherwise (though it would be cool I could name this "The Fredette Isomorphism", ^_^). The interesting thing about this Isomorphism is that, if we can generalize a DFA, whats to say that we couldn't generalize the category in the same way? Take Imperative languages for instance. I don't know if it works out (and I certainly don't have the skill to prove it if it does work out, at least not yet), but it is a hypuothesis of mine that an imperative program can be represented in a category with multiple arrows going from one object to another simultaneously, that is, an imperative program is a kind of "Nondeterministic" category. Ring any bells? We know (by the simple fact of Turing completeness) that a TC imperative language program can be written in a TC Pure Functional language (assuming there's a Pure Functional way to deal with State, eg Monads). Similarly (and this is almost to much of a guess to even _think_ of it as a hypothesis) if a TC Imperative Language is a "Nondeterministic" (ND) category, then if a ND Category is isomorphic to a NFA, then we know that NFA's are isomorphic to DFA's, and we know that Pure Functional Languages are isomorphic to operations withing a "Deterministic" Category, eg a "DFA", so that would "prove" (I use that term _very_ loosely) that any old TC Imperative program has an equivalent TC Pure Functional Program.

Pretty Neat, huh? It probably doesn't work somewhere, but still- it's cool.

We can further use the DFA<=>Category relationship as a kind of simple "composition" checker.

If the States of our DFA are types in a language, and the transitions functions mapping one type to another, then we can say that if the delta function is defined as above, and in the case there is no defined transition between some state S and some other state S', and if such a transition is called for in the delta function, then we simply send the output to a non-accepting "fail" state.


Here, the simple language consists of the following.


The Category contains:

Objects = {Int, Float, Char, Bool, Unit}
Arrows = {isZero :: Int -> Bool,
,ord :: Char -> Int
,asc :: Int -> Char
,sin :: Float -> Float
,not :: Bool -> Bool}
Values = {zero :: Int, true :: Bool,
,false :: Bool, unit :: Unit}

The corresponding DFA works something like this

f1,f2, ... fn are symbols which have type an -> bn,
where n is the same value as the nth symbol, and a and b are not type variables, eg: f1 :: Int -> Char, a1 = Int, b1 = Char
v is a type


(f1 . f2 . f3 . ... . fn) v
=> ([f1, f2, ..., fn], v)
=> [a1,b1,a2,b2, ..., an,bn,v]
=> [(init,a1),(b1,a2),(b2,a3),...,(bn,v)]


given this list of pairs, we define the DFA trace function as follows, this presumes a list like the one from above.


trace :: State -> [(Sym,Sym)] -> Bool
trace st [] = (st /= failState)
trace st [(s1,s2):syms]
| s1 /= s2 = False
| otherwise = trace (delta st (head syms)) syms


where failState is a pseudonym for whatever the magic non-accepting failure state is

and where delta simply points to the next state (be it the fail state, or otherwise). I'll cover that in more detail in my next post (I'm actually going to build this little guy for a simple language like the one above.)

I've digressed a bit from my topic, my goal was to show that Categories are really terribly neat, and apparently related to automata, which most people understand pretty easily, if they are explained well. I don't pretend to be an authority here, but hell, implementing a (very) simple type checker is a pretty cool feat, considering It was only a few months ago I started learning Haskell. I know that this isn't a robust, powerful mechanism, but as far as I know, given Compose (the (.) function in Haskell) apply (($) in Haskell) and a few other functions, you have a TC language, a la Backus' FP or FL systems.

Anyway, next time I intend to implement this little type checker, and (hopefully) eventually implement a (full) type checker for something akin to FP or FL, using this DFA style approach. Heck, I'd also be able to play with parsing (another automata rich subject).

Also, for those interesting in looking at HFA, it's available at

http://code.haskell.org/HFA/testing

you can just do a darcs get to pull everything down.




###DISCLAIMER###
I don't intend to present any of this as proven, either formally or by any other means, the ideas and conjectures in this post are just that, conjectures. Please, don't believe I'm an expert, I'm still learning about all these things, and I don't want to lead anyone down the wrong paths under the assumption I actually _know_ what I'm doing.

That said, I do think the conjectures made have some validity, if you know otherwise, please inform me. Thanks

~~Joe

July 28, 2007

Peano's Axioms IV: Advanced Functions and Integers

So here's the last installment, we'll make use of all the infrastructure we've build up to define primality, and associated functions like, a divisor function, totient, and sigma and whatever else I can come up with.

as always this is a literate source, save to Peano3.lhs and make sure you have the previous posts, execute with:


$> ghci Peano3.lhs


and have fun.

No big preambles this time, Lets go.



> module Peano3 where
> import Peano2
> import Data.List



First, all this stuff will boil down to prime numbers. So lets come up with a way to test if a number is prime or not.

An easy method is to create a seive of all prime numbers, then our isPrime function is just a search on the list, is it the fastest method in the world? Not really, does it work? You bet it does.



> natPrimes :: [Nat]
> natPrimes = sieve [S(S(Z))..]

> sieve :: [Nat] -> [Nat]
> sieve [] = []
> sieve (x:xs) = x : sieve [y | y <- xs, y `mod` x /= 0]



Awesome, we all know about Haskell's powerful List Comprehensions. Now lets implement that simple linear search on the list.



> isPrime :: Nat -> Bool
> isPrime x = isPrime' x natPrimes
> where
> isPrime' x (p:ps)
> | (p < x) = (p == x) || seq' (isPrime' x ps)
> | otherwise = (p == x)




EDIT: augustss mentioned that my use of seq was pointless, theoretically, it would be more efficient to use strict evaluation here, but it won't till I learn how to do that. It's unfortunate ghc/hugs won't recognize tail-recursion and make it strict automatically :/


Cool, all we're doing here is building up a chain of "does element p_k equal the given number?

Now what? Well, since we've defined prime numbers over the naturals, we can do some handy things like create a factorization function. We'll just use trial division to determine the factors



> factorize :: Nat -> [Nat]
> factorize x
> -- if the number is prime, we're done.
> | isPrime x = [x]
> -- if not, then we know we just need to find the first
> -- factor, and then recurse on the number `div` the factor
> | otherwise = firstFactor
> : (factorize (x `div` firstFactor))
> where
> divides x y = (y `mod` x) == 0
> firstFactor = head
> $ dropWhile (\p -> not (p `divides` x)) natPrimes



Fast? Hell no, it takes quite some time to factorize 210, and I didn't even bother to wait till it finished 2310, but it does work.

We know we can create a generic "closure" function, which takes a list and a operation on the elements of that list and recursively applies that function till the list is "closed" that is, applying closure again returns the same list. Lets write that quickly.



> closure :: Ord a => (a -> a -> a) -> [a] -> [a]
> closure f ls = closure' f ls []

> -- closure' is just a helper function which keeps track of the
> -- last list for comparasion against the closed list
> closure' :: Ord a => (a -> a -> a) -> [a] -> [a] -> [a]
> closure' f ls old
> -- if the old list is the same as the new list, return the
> -- list
> | ls == old = sort ls
> | otherwise = closure' f (performClosure f ls) ls

> performClosure :: Eq a => (a -> a -> a) -> [a] -> [a]
> performClosure _ [] = []
> performClosure f (x:xs) = [x]
> `union` (map (f x) xs)
> `union` (performClosure f xs)



Well, okay- it wasn't that simple. However, using this, we can write the "divisors" function, which returns a set of all numbers which divide a given number. We're going to use a nifty trick here too, I'll take a moment to explain it.

Normally, we see closed sets defined with a "mod" function, as in the group of integers mod 10, etc. We can define the closure operation (in Haskell's lambda notation) as being:

\ x y -> (x + y) `mod` k

for some constant k. However, this really doesn't work well when trying to come up with a closure operator for divisors. What we need is a function which will dynamicly limit the power to which each factor is raised. Fortunately, a nice mathematician named Euclid came up with a handy algorithm for creating a function just like this, it is called the greatest common divisor, the GCD.

Upon examination, you'll note that the function:

\ x y -> (x * y) `gcd` k

will force the product to only contain appropriately sized factors, because if the multiplication creates a number with an factor with an exponent greater than that of the same factor in k, then it will simply return the factor to the lower of the two powers.

So now, lets create a divisors function based on that concept and previously defined functions, we need to add 1 to the list because our factorization function won't return that.


> divisors :: Nat -> [Nat]
> divisors k = S(Z) : closure closer (factorize k)
> where closer x y = (x*y) `gcd` k



Pretty simple, just one more reason to love Haskell. Lets define sigma, which is the sum of divisors to a power function. That is



> sigma :: Nat -> Nat -> Nat
> sigma k p = sum (map (^p) (divisors k))



Hmm, lets do one more big one, how about Totient, that is, the total number of all numbers x less than k that satisfy the property gcd(x,k) == 1

 

> totient :: Nat -> [Nat]
> totient k = length [x | x <- [S(Z)..(k-1)], gcd x k == 1]



List comprehensions are awesome, aren't they?


Okay, last thing on our list, Integers. So far, we've been dealing with Naturals so far, and as such, have not had negative numbers to deal with. What I intend create a "Smart" Datatype which can cleverly increment and decrement without much difficulty. The problem with Integers is that the naive method for creating them, using the standard data types, is that when we try to decrement a positive number (or vice versa) we have to ensure that we just remove one of the increment/decrement symbols. Rather than just add a new one.

Heres the Datatype, you'll note its similarity to Nat.



data ZZ = Pre ZZ -- decrement an integer
| Z -- Zero is an integer
| Suc ZZ -- increment an integer



Note that all we really did was relax the "0 is the successor of no number" axiom. Much of mathematics is discovered by this method of removing the restrictions imposed by some axiom, or assuming an axioms converse/inverse, etc. The most popular example is that of Geometry, for many years, Euclidean Geometry was all there was. However, in the 19th century, Janos Bolyai and Nikolai Ivanovich Lobachesevky (the same mathematician of Tom Lehrer's "Lobachevsky") independently published papers about Hyperbolic Geometry, which changed the infamous "parallel" postulate of Euclidean Geometry to say that, instead of only one line, that there are two lines which pass through a point P not on a line L that do not intersect L. Riemannian, or Ellipic Geometry, states that instead of two lines, that there are no lines. In fact, you can imagine an infinite number of geometries based on the number of lines that can be parallel to a given line. For more about Euclidean and Non-Euclidean Geometries, wikipedia has some very nice articles, links are at the bottom of the post.

So the real test is to create some smarter constructors than what is provided, then we already have. The first thing, really, is to note that we can, in fact, pattern match on functions, eg



> precInt :: Int -> Int -> Int
> precInt (x + 1) = x



works just fine. So lets use that to create two functions, s and p, which are successor and predecessor over the Integers. We'll start a new module for this, this should be placed in a separate .lhs file called "ZZ.lhs"



> module ZZ(ZZ(Z), s, p) where

> data ZZ = P ZZ
> | Z
> | S ZZ
> deriving (Show, Eq, Ord) -- that'll allow us to skip ahead a bit



Notice how we don't have to deal with s(Z) or p(Z) that happens automagically for us.



> s :: ZZ -> ZZ
> -- if we're incrementing a negative number, we can just eliminate a P
> s (P x) = x
> -- these take care of the normal cases, just like in the Nats
> s x = (S x)

> p :: ZZ -> ZZ
> -- Now we just do p, in a similar way.
> p (S x) = x
> p x = (P x)



so now we can define addition, which is all we'll define over the Integers, most of it will be the same or similar to the Naturals, and if you'd like to see it, I encourage you to try it, I'd love to see it working.

Here it is, Addition:



> addZZ :: ZZ -> ZZ -> ZZ
> addZZ Z y = y
> addZZ x y
> | y < x = addZZ y x
> | x == Z = y
> | y == Z = x
> | x < Z = addZZ (s(x)) (p(y))
> | x > Z = addZZ (p(x)) (s(y))



Notably, this also defines subtraction, given the capability of negation, anyway. Hopefully you've enjoyed seeing the buildup from a simple concept of Z and S(x::Nat) to a powerful arithmetic. I think the next stop on my list is dealing with DFA/NFA and PDA evaluator and eventually a Regex Recognizer DFA automata, ala Thompson's NFA, then maybe I'll build a Turing Machine Interpreter. All plans are subject to change randomly for no reason at all, Stay Tuned!


~~Joe

Wikipedia articles about various geometry stuff.
Geometry
Euclidean Geometry
Non-Euclidean Geometry
Elliptic Geometry
Hyperbolic Geometry

EDIT: fixed some indentation errors

July 21, 2007

Peano's Axioms Part III: Making use of Haskell's Powerful Polymorphism

This time, we'll be looking at making use of the polymorphic capabilties of Haskell's type system.

In Haskell, Polymorphism is provided via type variables. That is, you may have a function



foo :: (a -> b) -> [a] -> [b]



which requires a function of any type to any other type, and a list of elements of the first type, and it returns a list of elements of the second type. Most people call this function map, though it can represent others.

So in addition to getting the functions defined in the typeclass, we get all the prelude functions with variable type signatures.

But wait- theres more. When we define certain types of functions, we often want to limit the scope of the function to only operate on certain variables. Like defining an instance of an interface in Java, we can specify a "scope" (though thats an abuse of the term) for a type variable. As in the following:



foo2 :: Ord a => a -> a -> a



Here, we state that a must be an instance of the typeclass Ord (and by inheritance, an instance of Eq too.) So now we know that foo2 takes two comparable elements and returns a comparable element.

Polymorphism is nothing new to any language. However, I think that Haskell really has an advantage not in the area of semantics, which are pretty much uniform -- at least in the case of polymorphism. I think that Haskell's advantage is in the syntax of polymorphism. Type signatures are easily wonderfully simple ways to express polymorphism. Both this basic kind of polymorphism (called rank-1 polymorphism), as well as higher order polymorphism (rank-2, rank-3, rank-n).

The point of this post is to show the rich library of polymorphic functions which become available with just a few (I think we're up to 7, one derived, 6 implemented) type classes. This, as always, is a literate file, just cut and paste to a .lhs and run


$> ghci .lhs






> module Peano2 (Nat(..)) where
> import Peano
> import Data.Ratio




==============================================================
Continuing on which defining math in terms of Peano's axioms
==============================================================

Last time I noted that we'd be working on exp, div, mod, and some other
higher-level functions. I also mentioned that we "sortof" got exp for free, in
that

S(S(S(Z)))^k,

where k is an integer, works fine, but what if we k be a natural. we'll notice
readily that this will fail, with the error that theres no instance of
Integral Nat.

Why is that a problem? because (^) isn't in Num, its defined elsewhere, its
signature is



(^) :: (Num a, Integral b) => a -> b -> a



Okay, so now what we should do is define Nat to be an Integral Type. So, lets go
for it.


=======================================

so, for Integral, we need quot, rem, and toInteger. We have the last of these, from the last time. Its quot and rem that we need. So, how do we define these?

well, we know that quot and rem are (effectively) just mod and div, in fact, not having negative numbers means that they are exactly the same. Lets then realize that mod is just repeated subtraction until we hit modulus > remnant. further, we relize that div is just the same, but the count of times we subtracted till we met that condition.



> quotNat :: Nat -> Nat -> Nat
> quotNat k m
> | k == m = 1
> | k < m = 0
> | otherwise = 1 + (quotNat (k-m) m)

> remNat :: Nat -> Nat -> Nat
> remNat k m
> | k == m = 0
> | k < m = k
> | otherwise = remNat (k-m) m

> quotRemNat :: Nat -> Nat -> (Nat, Nat)
> quotRemNat k m = ((quotNat k m), (remNat k m))



now, we just instantiate integral



> instance Integral Nat where
> toInteger = ntoi
> quotRem = quotRemNat
> -- this fixes a problem that arises from Nats not having
> -- negative numbers defined.
> divMod = quotRemNat



=======================================

but now we need to instantiate Enum and Real, oh my. Lets go for Enum first.

Enum requires just toEnum and fromEnum, thats pretty easy, to and from enum are just to and from Integer, which we have.



> instance Enum Nat where
> toEnum = integerToNat
> fromEnum = natToInteger



Real is actually relatively easy, we're just projecting into a superset of the
Naturals, notably, the Rationals, so we do this simply by pushing the value
into a ratio of itself to 1, that is

toRational S(S(S(S(Z)))) ==> S(S(S(S(Z)))) % 1



> instance Real Nat where
> toRational k = (ntoi k) % 1


=======================================

Next time, we'll go for primes.

oh- and by the way, pushing Nat into Integral gave us lots of neat things, notably even/odd, gcd/lcm, the ability to do ranges like [(Z)..], and all the appropriate functions that go with that.

So far, I've spent about 1 hour making all this work, you can imagine how this speed could be useful if you have defined your problem as having certain properties. Type classes are an extremely powerful tool, which can help make your code both clean, as well as powerful. In one hour, I've managed to build up a simple bit of code, based on some fairly primitive axioms, and create a huge amount of powerful math around it.

Imagine if you could define these same relations around data? What if you were able to define strings as having properties of numbers, heres an Idea:

Imagine you have some strings, you can define the gcd of two strings as the least common substring of two strings. If you can sensically define the product of two strings, then you can get a concept of lcm as well. Granted, the may not be the best example. But you can just imagine the power you can push into your data by defining an arithmetic, (not even an algebra!) on them. Imagine creating an arithmetic of music (been done, sortof, check out Haskore) or pictures? I use
arithmetic,because what I'm implementing here is only a little peice of the power you can instill. _This_ is why Haskell is powerful. Not because its purely functional, not even because its lazy. It's the _math_ that makes Haskell capable of doing this. The type theory upon which Haskell rests makes Haskell powerful.

Remember, next time, Primes and Totients and Number Theory, and a datatype
representing the Integers,
Oh my!

July 18, 2007

Intermezzo: Mental Vomit.

Phew, it's been a long few days, I have the last few posts in the Peano series coming up, and I've been planning out a new series of posts about a project I've been toying with- a Haskore-esque Music system. By the looks of it, Haskore is no longer being mantained, so maybe someday I'll this project will actually turn into something useful, but really- I'm just looking to do something nifty with Haskell.

Today, though, I'm just going to brain-vomit and talk about some random thoughts I had.

Programming the Universe, by Seth Lloyd.

Excellent book, I'm about halfway through it. It's really brilliantly written, very engaging, though its occasionally a little too conversational for my tastes. It's also relatively thin, which is good, because it makes me feel proud to say I'm halfway through in less than 3 days, even though halfway through is 100 pages. It's also kind of unfortunate, as I'll be done with it soon, though I suppose if you have to have some problem, not wanting the book to end because your enjoying it to much is probably a good one to have. The book, principly, is about how the universe can be described as a giant quantum computer, it goes into information theory and its relation to thermodynamics and entropy. It talks about Quantum Logical Operations, though (at least up till now) not in any real detail, althoug h I saw some Bra-ket notation in later chapters. I'm not very knowledgable about Quantum Computing in general, so I hope to pick up some basic understanding from this, or at least enough language so I know where to look for more info. I figure, in 10 years, this technology will be relatively grown up, and I'll need to know it to stay current. Might as well start now.

I am a Strange Loop, by Douglas Hofstadter

I'm a Hofstadter fanboy, I'll admit it. GEB is the best book ever. Metamagical Themas is the second best book, and hopefully, this will be the third best. I didn't even read the back cover when I bought this, I saw "Hofstadter" and I actually squealed a little. Yes, I squealed, but honestly, DH is quite possibly my favorite non-fiction writer ever. I'm allowed to be a fanboy. It was a manly squeal. Shut up. :P

I haven't started reading it yet, but my first impression (from my random flipopen to one of the pages) is that it'll be a entertaining read, to say the least. I opened to a section headed with "Is W one letter or two?" I think it'll be good, and the cover art is really quite nice.

Reinventing the Wheel, and why It's a good thing.

Now a little more on topic. I've been hearing more and more, or maybe I'm just noticing that people say this more and more, that we -- as programmers, mathematicians, etc -- should not try to reinvent the wheel. For the most part, I agree. Some problems are solved, but should we discourage people from reinventing the wheel entirely? I think there is something to be said for reinventing the wheel every now and again, especially for new programmers. For instance, the recent posts about Peano's Axioms. This has probably been done to death by other Haskeller's out there, but why do I do it now? Partially because it shows the wonders of type classes, but also because the exercise of solving this already solved problem is an excellent way to learn about how the solution works, and furthermore how to apply those concepts to other problems. I mean, maybe I'm just ranting, but don't we reinvent the wheel over and over? Insertion sort is a perfectly good sorting algorithm, it does the job, heck, it even does it far quicker than we could. However, if it weren't for the fact that someone sat down and said, "Maybe this wheel isn't as great as it could be" and reinvented it, and came up with quicksort, or radix sort, or count sort, then where would our applications be? Even looking at the actual wheel, how many times has it been reinvented? It started out as some big stone, then it was probably wood, then wood with metal plating, then mostly metal, now its a complex part with alloys and rubber and all sorts of different materials. I m guess what I'm trying to say is maybe instead of "never reinventing the wheel" we should, "Never reinvent the wheel, except in cases where reinventing the wheel would give us a better solution." I suppose its the logical resolution to the problem presented from trying to combine this adage with the adage:

"Never say never, ever again."

Anyway, It's time to get back to procrastinating, or not, I guess I'll do it later.

PhD. Procrastinate.

July 11, 2007

Peano's Axioms Part II: Orderability and Code

So, lets get started with this Peano arithmetic stuff. For those who do not know what Peano's axioms are, heres a brief explaination.

Peano's Axioms define a formal system for deriving arithmetic operations and procedures over the set of "Natural" numbers. Peanos Axiom's are most often stated as follows, though variants do exist.

1) 0 is a natural number. (Base Case)
2) If x is a natural number, S x is a natural number (Successor)
3) There is no number S x = 0 (0 is the successor of no number)
4a) 0 is only equal to 0.
4b) Two natural numbers Sx and Sy are equal iff x and y are equal.
4c) If x,y are natural numbers, then either (x == y /\ y == x) or (x /= y /\ y /= x)
5) If you have a subset K, and 0 is in K. Then if some Proposition P holds for 0, and Sx for all x in K, then K contains the naturals. (Induction, from Wikipedia)

(see Peano's Axioms Wikipedia Entry)

The goal of this post is to define Equality, Orderability, and basic arithmetic over the Naturals. We'll also see how the standard Peano numbers. Lets talk about Orderability, for a second.

Equality is provided for by the axioms, but what is orderability? When we think about something being ordered, we can think about a "total" ordering, or a "partial" ordering. A Total Ordering is one that satisfies the following conditions.

For some Binary relation R(x,y), (notated xRy),
1) R is antisymmetric:
(xRy /\ yRx) iff (x==y), where == is equality.
2) R is transitive:
if (aRb /\ bRc) then (aRc)
3) and R is total:
(xRy \/ yRx)

a partial order only lacks in the third axiom. What does all this mean though? Well, axiom 1 gives us an important link to equality. We can actually use this fact to either define Equality from Orderability, or vice versa. Also, Axiom 1 gives us the ability to make the MRD for the Ord class very succint, only requiring (<=) at the very least. In Haskell, the Ord class is a subclass of Eq, so we need to define equality first in Haskell. This is not a problem, as we can always use Axiom 1 to define an equality function retroactively. That is, define (<=) as a function external to the type class, over the naturals. Then define (==) as ((x<=y)&&(y<=x)). We can then instance the both classes together. Axiom 2 is pretty self explainatory, it allows us to infer an ordering of two elements from two separate orderings. One neat thing this does, that not many people point out, is this is the axiom that allows for the concept of sorting. Since effectively, when we sort, we want to chain orderings together so we can have a list with elements of the type with the property of: k_1 <= k_2 &&amp;amp; k_2 <= k_3 && ... && k_(n-1) <= k_n => k_1 <= k_n that is, element 1 is less than element 2, and so on, such that the first element of the list is ordered with the last. It's relatively trivial to realize, so much so that most people don't even bother to mention it, but it certainly is interesting to see. Axiom 3 is the defining feature of total orderings, it's similar to the law of the excluded middle. We can see how certain relations are non-total, take for instance the relation (<). That is, the relation x < sx ="=" sy ="=">
> {-# OPTIONS -fglasgow-exts #-}
> module Peano (Nat(..), one, p,
>    iton, ntoi, natToInteger,
>    integerToNat) where

=============================================
Defining Arithmetic based on Peano's Axioms
=============================================

===============================================================================
First, we'll define Nat, the set of natural numbers w/ 0,

This covers Axiom 1,2, and 3.

> data Nat = Z | S Nat
>   deriving Show

This encodes the concept of Natural Numbers, we aren't going to use Haskell's
deriving capabilities for Eq, but Show thats fine, it'd just be
tedious.


Handy bits.

> one :: Nat
> one = (S Z)



===============================================================================
Now lets build up Eq, the Equality of two numbers, this covers Axioms
2,3,4,5,7, and 8


> instance Eq Nat where

every number is equal to itself, we only need to define it for Zero, the rest
will come w/ recursion for free.

>   Z == Z = True

No number's successor equals zero, and the inverse is also true, zero is the
successor of no number

>   S x == Z = False -- no successor to zero
>   Z == S x = False -- zero is no number's successor

Two numbers are equal iff there successors are equal, here, we state it
backwards,

>   S x == S y = (x == y)

And that, my friends, it Eq for Nat

===============================================================================

Now, lets define orderability, these two things will give us some extra power
when pushing Nat into Num.

> instance Ord Nat where
>   compare Z Z = EQ
>   compare (S x) Z = GT
>   compare Z (S x) = LT
>   compare (S x) (S y) = compare x y

Easy as pie, follows from Axioms 1,2 and 8.
===============================================================================

Now, we can push this bad boy into Num, which will give us all your basic
arithmetic functions

First, lets write (p), the magic predecessor function

> p :: Nat -> Nat
> p Z = Z -- A kludge, we're at the limit of the system here.
>    -- We'll come back to this when we start playing with ZZ
>    -- (the integers)
> p (S x) = x

=======================================

Heres (+) in terms of repeated incrementing.

> addNat :: Nat -> Nat -> Nat

First, we know that Z + Z = Z, but that will follow from the following
definitions

> addNat x Z = x
> addNat Z y = y
> addNat (S x) (S y)
>   | (S x) <= (S y) = addNat x (S (S y)) > | otherwise = addNat y (S (S x))

=======================================

Heres (*)

> mulNat :: Nat -> Nat -> Nat

Simple, here are our rules
y' = y
Z * Sx = Sx * Z = Z
SZ * Sx = Sx * SZ = x
Sx * y = (x) * (y+y')


> mulNat _ Z = Z
> mulNat Z _ = Z
> mulNat a b
>   | a <= b = mulNat' a b b > | otherwise = mulNat' b a a
>   where
>    mulNat' x@(S a) y orig
>     | x == one = y
>     | otherwise = mulNat' a (addNat orig y) orig


=======================================

We're gonna stop and do integerToNat and natToInteger just quick.

> natToInteger :: Integral a => Nat -> a
> natToInteger Z = 0
> natToInteger (S x) = 1 + (natToInteger x)

easy enough, heres integerToNat

> integerToNat :: Integral a => a -> Nat
> integerToNat 0 = Z
> integerToNat k = S (integerToNat (k-1))


pretty nice, huh? Lets add a couple of aliases.

> iton = integerToNat
> ntoi = natToInteger

=======================================

Now we just need (-), we'll talk about abs and signum in a second

> subNat :: Nat -> Nat -> Nat
> subNat x Z = x
> subNat Z x = Z
> subNat x y
>   | x <= y = Z > | otherwise = subNat (p x) (p y)

=======================================

Few, after all that, we just need to define signum. abs is pointless in Nat,
because all numbers are either positive or Z,

so signum is equally easy. since nothing is less than Z, then we know the
following

> sigNat :: Nat -> Nat
> sigNat Z = Z
> sigNat (S x) = one

and abs is then just id on Nats

> absNat :: Nat -> Nat
> absNat = id

===============================================================================

After all that, we can now create an instance of Num

> instance Num Nat where
>   (+) = addNat
>   (*) = mulNat
>   (-) = subNat
>   signum = sigNat
>   abs = absNat
>   negate x = Z -- we don't _technically_ need this, but its pretty obvious
>   fromInteger = integerToNat

Phew, that was fun. Next time- we'll play with Exp, Div and Mod, and maybe some
more fun stuff.

Quick note, pushing Peano into Num gives us (^) for free (sortof.), but we'll
define it next time anyway

July 08, 2007

Peano's Axioms Part I: Haskell and Type Theory, and Object Oriented Programming

Well, the title's a little misleading, this has very little to do with type signatures, I decided to start a little series on what I think is the most powerful aspect of Haskell. Of course, I think that the most part is Math. Specifically in the realm of Type Classes. I'll give you a little background here.

I'm primarily familiar with Java's class system. Notably, upon reading about and toying with other class inheritance systems, Java stood out to me as being my favorite. It feels the most algebraic. One thing that should be noted is that typically, the only "real" difference between these systems (I'm generalizing wildly.) is in the world of multiple inheritance. Java, in particular, uses interfaces, which I intend to show as being a kind of type class, in fact, it is about one step away from being a real live type class.

Now, Lets start talking about inheritance.

Assume we have an Object Joe. Joe is a "Reified" (to borrow some language from type theory) object, that is. He's a finite, usable, object, with real methods, that do real things. Effectively, he's material, you can "poke" him, as it were.

Lets now say Joe has some Children, Jack and Emily. These are also Reified objects. However, they have a special property, they have a "Parent" object, namely Joe. This "special property" allows them to inherit properties from Joe, (say... devilishly good looks, and powerful intellect?). By now, the female readers are probably moaning, "Those have to come from the mother." And thats a good point, how do we get the Mom in on this? We need Multiple Inheritence. Before we get there though, lets talk about a different kind of object, an Abstract object.

An Abstract Object describes some underlying property of an object, but it does so through this Parent/Child relationship. An Abstract Object in our setting might be something like "Ancestor" or even "Parent". Notable things about Abstract objects is that they don't contain any "Reified" methods, that is, methods containing code. The contain stubs which describe the signature of a method, but not the method itself. So we might have a Abstract class "Parent" which contains a method "getChildren" which has a signature void -> List, its purpose is to return a list of the extending classe's (like Joe) Children. The important thing is, it doesn't force that to be the result, it only enforces a type of the content, not the content itself.

But what about Multiple Inheritence. Assume we have another object called "Sarah" which also extends the parent class, and also assume that Jack and Emily are Sarah's children too. Lets assume further that Sarah implements getChildren differently than Joe does. How then do Jack and Emily access there respective parents getChildren Methods? If they are fundamentally different implementations, then how can they choose which to use? Further, what if we want to have Parents for Joe, but we also want Joe to extend the Ancestor class? Now we have a mess...

How do we fix it? Well, the answer is to create a super version of Abstract classes, lets call them interfaces.

What does an Interface do? Well-- in Java, no class is allowed to inherit from more than one parent class. Abstract or Reified. Interfaces exist outside of the usual inheritance tree, and can therefore give information about the tree as a whole. For instance, we can now create our inheritance tree by saying that each ancestor class implements the "hasChildren" interface, which forces the ancestor to have the void -> List method, we can then say that the Children found in that list are instances of the Child class, rather than the class itself, this gives us a solution to the problem by forcing us to access Jack through the Sarah object.

Could we have done this with normal Abstract/Reified classes, sure. Would it work as well? Probably not.

So why are interfaces cool? Well- you can think of an Interface as a way to describe a set of classes. Classes which meet certain properties. Indeed, they use interfaces like this all the time. For instance, Java has a interface called "Comparable" which- as the name suggests, means that any class that implements Comparable can compare instances of itself in a meaninful way. Comparable doesn't say how to do the actual comparison, it just says that there must be a method compare which has type: (using Haskell-esque syntax)


compare :: Comparable a => a -> a -> {-1,0,+1}


The Javadocs recommends that it should have 0 mean that x == y, but that its not required. The interface only defines the kind of interaction you can have.

Why is this cool? Well, consider the obvious example, what if I wanted to write quicksort over a generic list of elements? How do I ensure that I have a sortable list? Lets say we have an Object Foo, which has no ordering, and another Object Bar, which can. I have a magic method qsort which will actually do the sorting, but how do I write the method such that I know that the list is sortable? That is if I write tests:


assertFail(qsort(List = {foo1, foo2, ...}));
assertPass(qsort(List = {bar1, bar2, ...}));


How can I ensure those both succeed (with the assumption, of course, that those testing constructs exist)? Well, the easy answer is to define qsort as having the method signature:


List qsort(List);

(I think thats the right syntax, it's been a while since I wrote Java.)

This will prevent (at compile time, no less) the use of qsort on List, because Foo doesn't implement Comparable. Running it on List is Fine, because its comparable, like we said before.

So now how is this different from Type Classes. Well, principly, there is one difference. Type Classes can not only specify methods the Type must have defined on it, but it can also define other methods derived from those methods. A seemingly trivial extension to Interfaces. However, that one simple change gives you enormous power in creating data abstractions. For instance, given the Haskell equivalent of Comparable, which is the pair of classes Eq and Ord (for Equality and Orderability, resp.), which require only 2 definitions total (== or /=, and compare or <=, /= is not equal). We get for free, about 20-30 functions including: all your comparison and equality operators, the ability to put items implementing the class in a set, the ability to use them as a key in a finite map, sorting of implementing items, some extra list functions, and more. All that, from 2 definitions, in two type classes, along with the Prelude and Haskell's own polymorphism capabilities.

How does that work? Well, lets dissect some code, here's the Ord class:

ignore the '.''s, they're just for spacing.


class (Eq a) => Ord a where
........compare :: a -> a -> Ordering
........(<), (<=), (>=),(>) :: a -> a -> Bool
........max, min :: a -> a -> a
................--minimal complete definition:
................-- (<=) or compare
................-- using compare can be more efficient for complex types.
........compare x y
.............| x == y = EQ
.............| x <= y = LT
.............| otherwise = GT
........x <= y = compare x y /= GT
........x < y = compare x y == LT
........x >= y = compare x y /= LT
........x > y = compare x y == GT
........-- note that (min x y, max x y) = (x,y) or (y,x)
........max x y
.............| x <= y = y
.............| otherwise = x
........min x y
.............| x <= y = x
.............| otherwise = y



So, lets dissect.

First, we declare what the class implements, that is, what methods are required to exist if the class is implemented. However, this is not the same as saying that all those methods must be defined over the structure before we can say it implements the class. We instead only need the "MRD/MCD" or "Minimal Requisite/Complete Definition" that is, the minimal number of functions needed to define all the other functions the class provides. How do we know what the MRD is? Well- thats up to you to decide. We do that by defining each function of the class in terms of other functions in the class, even cyclicly if necessary. I like to call this set of cyclic definitions the "internal definitions" of the set. These internal definitions provide the real power of the type class. Also note how, in the class definition, we have an inheritance bit, in that of Eq a => Ord a. This allows us to assume that we have basic equality functions provided by Eq.

In the next few posts in this series, I'll be implementing Peano Arithmetic in Haskell, principly by pushing one simple data type:


Nat = Z | S Nat


Into as many type classes as I can, as of this writing, I have two more posts planned, and have pushed Nat into Eq, Ord, Num, Integral, Enum, and Real, I hope to get it into Rational and Fractional which will turn it into Nat-QQ (Natural Rationals (that is, all the Positive Rationals)), and maybe then refactor Nat into ZZ (the integers), and get the Regular Rationals out of that.

July 05, 2007

Human Error Bugs

I fixed comments not coming up, and such. Thanks for pointing them out, folks.

An Analogy for Functional versus Imperative programming.

I was thinking the other day, about many things, as we drove back from my Aunt and Uncles in NY. I had been discussing with my father about C vs Haskell and, more generally, about functional versus imperative programming. I had been trying to explain why Functional programming is useful, particularly in areas relating to parallelism and concurrent code. To put this in perspective, my father has been writing low level system verification code for a very long time. (he started way back in the 70s) so he's pretty situated in the imperative world, with a (vast) knowledge of C and languages like Verilog and stuff. Me, I've only been writing code since I was 14-15. I have far more knowledge in languages like Scheme, Haskell, and to an extent, the ML family. I also regularly use Java and friends, So it's safe to say that trying to cross our respective expertises is most often quite difficult. Anyway, I came up with a pretty clever analogy, I think, for how Functional and Imperative programs relate.

Factorys

I have no idea if this analogy has been used before, but if it has, kudos to whoever came up with it, basically, it goes like this.

an imperative language is monolithic. it effectively can be modelled as one giant state machine that gets permuted. Like a Rube Goldberg machine, you don't design an imperative program to manipulate inputs, you design it for its side effects.

Here in Massachusetts, we have the Boston science museum, in which, there is a rube goldberg machine (RGM). It is, (next to the math room), by far one of my favorite exhibits. But what does an RGM do? Put simply, its just a while(1) loop. It ferries some bowling balls or whatnot to the top, and then drops then. The interesting part is the side effects. The bangs and whizzes and clanking and ratcheting of the chain as various balls drop and gears spin and cogs do whatever they do, cogulate, I guess. The point of the RGM is to manipulate the world indirectly. Someone, at some point, "said" to the machine, "start." From thence, it has worked to make noise and spin and do all that nifty stuff.

So, RGM's, you say, are mildly useless, right? Well. We'll come back to that in a minute, but suffice to say, like everything else in the world, they have there place.

So if an Imperative language is Like a RGM, whats a functional language?

Well, lets realize that effectively, all a program does is turn some set of inputs, to some set of outputs. Kind of like how a factory may take in some raw material, (steel, plastics, etc.) and create a new, better "material" from those outputs, (eg, a car). A language does the same thing, a user "inputs" a query to a database server (technically, he, or someone else, have given the program the database, too. Kind of like currying, here. hmm). Then after your query, you get back a database entry or list thereof which match your search parameters. Now, a RGM-type machine, or more accurately, a monolithic program, which are typically written in imperative languages (though you can write monolithic functional programs) take an input, and, completely internally, turn that input to an output. Kind of like a whole factory in a box. useful, yes, reusable not necessarily. A functional approach, on the other hand, is like the components that make up a factory. When I write a program in Haskell, I have a series of functions which map input data to intermediate data, and functions which map intermediate data to intermediate data, and then finally functions which take intermediate data and map it to output data. For instance, if I want to create a function which takes a list and returns it along with its reversal, in Haskell, I'd write:


myReverse :: [a] -> [a]
retPair :: [a] -> ([a],[a])

myReverse [] = []
myReverse (x:xs) = myReverse xs : x

retPair ls = (ls , myReverse ls)


So you can see how retPair starts the chain by taking input. copies ls and sends it to an output, and then sends the other copy to another "machine" in the factory, which turns a list of anything '[a]' to a list of anything. The result is then sent to output with the original as a pair '([a],[a])'

You can see this in the diagram:


..........................myReverse..............................
................/---------[a]->[a]-------\...they get............
input...........|........................|...rejoined............
>---------------|split ls................|---([a],[a])-->output..
................|........................|.......................
................\---------[a]->[a]-------/.......................
..........................identity...............................
..........................function...............................


So what does this "individual machine method" give us? For one, its free to reuse, its very easy to pull apart this "factory" of "machines" and reuse any given "machine" in some other "factory". It would not be as easy to do if we had written it procedurally, as in C/C++. I can hear the screams of imperative programmers now, "We would have written exactly the same thing, more or less!" and I know this, and don't get me wrong, you _can_ write this "factory style" code in C/C++, but what about less trivial examples? In Haskell, I can only write pure functional code (barring monads, which are borderline non-functional). Whereas in C/C++, writing this kind of reusable code is often hard. In a functional language, writing this kind of code is almost implicit to the nature of how you think about code. The point I'm trying to make is simply this, FP-style languages force you to write (more or less) reusable code. Imperative languages in many cases force you to write once-off code you'll never see again. I'm not saying this makes FP better, in fact, in a huge number of cases, I, as an FP programmer, have to write one-off imperative-esque state mangling RGM's to get things done. The point is Haskell helps me avoid those things, which makes for more reusable code.

Another thing, FP is famous for being "good" at concurrency. This analogy works wonders at explaining why. Think about the factory example, when I split ls into two copies, I split the program into two "threads". I effectively set up an assembly line, when I send done the copy of ls to the myReverse function, you can imagine a little factory worker turning the list around pi/2 radians so that it was backwards, and sending it down the line... You can even imagine the type constrictions as another little worker who hits a siren when you send down the wrong material. Imagine, however, trying to parallelize an RGM. RGM's are often dependent on the inability to be made concurrent, even if that wasn't the programmers intention. Imperative programs fight the programmer with things like deadlocks (two balls in the RGM get stuck in the same spot) and race conditions (two balls in the RGM racing towards the conveyor belt, with no way of determining who will win, how do you handle that?) whereas FP implicitly allows multiple "workers" to manipulate there own personal materials to make there own personal products at there station. In a purely functional program, each function is implicitly a process, you could even go so far as to give it its own thread. Each machine's thread would just yield until it got something to work on, at which point it would do its work, and go back to waiting, it doesn't matter which information gets to the next machine first, because it will just wait till it has all the information it needs to execute. Bottlenecking (a common problem in all code) is easier to see in this "factory" style view, since a bottle neck will (*gasp*) look like a bottle neck, all the functions will output to a single function. Thats a sign that its time to break it up, or have two copies of it running in parallel. FP makes this stuff simple, which makes FP powerful. Because for a language to have true power, it must make it so the programmer has to only think about what he wants to do, and not how to do it.

On the other hand, Imperative programming world. You have a number of excellent things going for you. Imperative code is remarkably good at clever manipulations of the machine itself. It is, in some ways, "closer" to the machine than a Functional language could ever be. So even though you have your share of problems, (parallelism and code reuse are the two I think are the biggest.) you have benefits to. Code in C is well know to be very fast, Object Oriented Languages are, I think, best described imperatively, and OO is a wonderfully intuitive way to think about programming. Imperative Programming is also makes it infinitely easier to deal with state, which can be a good thing, if use properly. Don't get me wrong, I love monads, but even the cleverness of monads can't compare to the ease of I/O in Perl, C, Java, Bash, or any other imperative language.

Hopefully this was enlightening, again, I want to say, Imperative programming isn't Bad, just different. I like FP because it solves some big problems in Imperative Programming. Other people are of course allowed to disagree. It's not like I'm Jake or anything.

June 01, 2007

Programming Lanugages Part II: Beginner Friendly

Title says it all, really, I'm not asking for much.

Recently, my girlfriend asked about what languages were good for a beginner to learn. Her sister is interested in computers and is going to be going to community college soon, and wants (or at least, is wanted) to prepare for possible classes in programming by learning a simple language which will teach her the fundamentals.

Myself, being born of a number of languages, Common Lisp and VB6 as well as others, immediately thought, "Scheme." I soon realized though that, if this girl is going to community college, chances are they don't really want to teach her to be a brilliant, deep thinking, professorial type of person, but rather a run-of the mill, decent, get the job frakking done coder. Now I want to say, run-of-the-mill coders are not run-of-the-mill intelligent people, they are often orders of magnitude smarter than most. Maybe I'm bias, but to give some perspective, I consider my father, who has a Bachelors degree from Northeastern University in Boston, and about 25 years of experience in the field, to be a run-of-the-mill coder. There is noone on the planet who I think is smarter than my father, not even me. Now that you have that nice perspective thing. Realize that though Scheme is a wonderful language for learning about CS as Theory, and even Math to some extent. It presents an unfortunately distorted world view. In the real world, we write code in an imperative style (though thats slowly changing, and I'm quite happy of that). In the real world, we write code in C, Java, or similar languages. In the real world, we write mostly object oriented code. In the real world, we generally solve problems iteratively using arrays as a principal data-structure-- not recursively with lists as a principal data-structure. So I said to my girlfriend, "Well, you have a few options." I continued to think about what makes a good languages, heres my list:

  • Easy to Setup
Chance are, if this is your first programming language ever, you might not understand all the intricacies of setting up a compiler/editor chain, or an IDE, or whatever, so this is obviously critical. You can't use a language you can't set up. This is why languages like VB are so popular, in my day, Visual Studio was trivial to install and use, and thats why I used it. I could have just as easily learned C or C++, my brain was plenty big enough for them, but I couldn't grasp all the arcane mysticism of the GCC compiler at that time, so how was I supposed to do anything? In this area, I think Scheme beats Java, Notably, mzscheme's DrScheme, which I still use when I write scheme code. It is an excellent, intuitive IDE for Scheme, It just works. It's as easy (if not easier) than VS was to install, and I really wish I had found it before Dad's copy of VS. Java, though I think a better "real world" option, is a little tougher to set up, obviously a editor/compiler chain, though a wonderful, no-frills way to write code, is not necessarily as intuitive to a complete beginner as a nice IDE. Since Eclipse (admittedly, the only Java IDE I've ever used) is not designed (like DrScheme is) to be used as a learning tool, there are alot of superfluous things that I, as a seasoned Java programmer, might use, but to a beginner, these things are just clutter. Clutter, as far as I'm concerned, means confusion.
  • Good Errors
I've known many languages in my time, and many-- many of them had the worst, most inconceivably bad error messages in the world. It's getting better, but even now -- with languages designed for teaching, like haskell-- the error messages are archaic and often unreadable. Now mind you, they are only such to the uninitiated haskellers, and as such, I don't have a problem with trying to decipher "ambiguous type variables" and type errors and other such things. But to a beginner, all these kind of errors perpetrate is the myth that writing code is hard, and something that should be left to the realm of the ubergeek. So my opinion here is pretty standard, Good Errors => Good Beginner language.
  • Results Oriented
By "Results Oriented" I mean that it should be easy to see the results of your work. The Idea is simple, when someone is learning a language, they want to see there helloworld program just work. The don't want to go through the work of writing line after line of code and then 12 different commands to compile the code, and then finally get to type that brilliant ./a.out command and see that you misspelt hello as hewwo. The point is, a beginner programmer, more than anything, needs encouragement. If a language can't give a beginner a positive boost every time they do something right-- then its not a good language for a beginner. HTML/Javascript are both wonderful examples of 100% results oriented languages. If I write an html file, and look at it in a browser, then I know immediately whether I did it correctly or not. I know exactly if it looks and reads the way I think its supposed to. Similarly with Javascript, its trivial for me to see whether my script works or not. This kind of language allows the newbie programmer to just get results, and thats the best thing a newbie programmer can have.


So, by now, you probably want to know what I thought was the best language to learn, well- I didn't pick just one, but for what its worth, here is my list of the top few good beginner languages:

  1. HTML/Javascript
  2. Python
  3. Ruby
  4. Scheme or Java
  5. Other Web Languages (PHP, ASP, etc)
  6. C
  7. C++
  8. Perl
  9. Haskell/Erlang/ML et al
  10. Assembler?
Those rate from one being the absolute best language I think a beginner should learn to 10 being the absolute worst language for a beginner, I split up C/C++ because the object oriented stuff in C++ makes it even more complicated than just C alone with its pointers. Between gcc's mild, jovial inanity, and pointers, makes C just a little to tough to make me think it's a good option for a beginner. I want to mention that I am not judging these languages absolutely, I know most of them (though I have considerably less experience than I would like in most of them) and think that they are all quite wonderful. I'd especially like to learn Python soon. It's been a while since I picked up an imperative language.

Oh, by that way-- I only tossed Assembler on the list to make the list an even ten. Assembler is a terribly confusing subject to the uninitiated, and makes a good +infinity on the list. I suppose the list should also have a 0, which would be the metamagical mythical languages of "JustRight" where no matter what you type, there are never any bugs, it compiles and runs in optimal space and time, all NP problems become P, and magical unicorns prance in fields of cotton candy and happiness outside your cube.

Then again, you could argue JustRight would present a distorted realworld view too.

~~Joe

May 21, 2007

God, get the frak out of my Barne's and Nobel section.

Scientists, please, I beg you, stop with this God vs Science bull already.

I went into my local Barne's and Nobel today, and started to casually browse through my favorite section of the bookstore--

The Science Section.

Last time I checked, Books about God fell under the "Religion" category. Furthermore, I am pretty sure that Science, in fact, is not religion. Now, I like reading philosophical books, religious texts, etc, just as much as the next guy -- heck, I even like reading things like the Bible or the Koran. But why the hell does my community feel it necessary to invade on religion's ground? Leave God alone, I don't want to hear about him, I don't want books about him in my section of the bookstore.

Scientists reading this right now are screaming something like, "But Jooooe! They do it to us all the time!!!" Here's my reply, Let them. If they feel that they, in order to be validated, need to shove their beliefs down other peoples throats, treat them like they act. You don't get a toddler to stop whining about not getting what they want. Religious types want you to believe what they believe. The way you teach a toddler to stop crying about not getting their way is by letting them cry themselves out. If you continuously argue with them, they will lose. The people slamming science don't take time to be unbiased about science, and unfortunately, I think that most of the people slamming Religion back are not taking the time to be unbiased about religion either. Aren't we, as scientists, supposed to be unbiased about all ideas?

I'm annoyed that people who call themselves scientists are wasting there time on this whole God business, I'm annoyed that the religious community isn't reigning in the idiots who are stepping outside there bounds. It's a community's responsibility to regulate itself. So, Science community, consider yourselves regulated. Religious community, take a hint.

~~Joe




May 20, 2007

Annoyances with Blogger.

I'm Mildly annoyed that blogger does not seem to recognized that when I put in some indented code, it replaces things with &nbsp's and other gibberish. The same thing occurs with other punctuation. It's bothersome.



C'est la vie.





~~Joe

May 18, 2007

Programming Languages Part I: Syntactic Similarity

I like languages. when I was younger, I remember reading The Hobbit and spending more time reading the first two preface pages about the Moon Runes, A gussied up version of the Futhark, than actually reading the book. For a good bit of time after that, I wanted to be a Linguist, and not a mathematician.

But Alas, over time my interests went from Natural Language to Formal, from Formal Language to Abstract Language, and from there to the wide world of Algebra and Logic. A good transition, I think. Nevertheless I still love Languages, and that love has now been turned to specifically Programming languages. I like these languages because they are first and foremost utilitarian. They are designed from the start to do one thing, get a point across to an idiot. Lets face it, Programmers and Computers alike are pretty damn dumb. The language is the smart thing. A Programmer has no capability to tell a computer what to do without the help of a good language, and a Computer can't do anything it isn't told to do. So the most fundamental piece of Computer Technology is that of the Language, the layer that binds Programmer with Programmee.

I love languages, but I often hate them too. Take, for instance, Java. Java is an exceptionally pretty language, but it's also ugly as your Aunt Anita Maykovar (May - ko - var). Java effectively boils down to one syntactic structure, the class. Every Java file revolves around it, and in some ways, this is really good. The fundamental commonality this structure brings allows Java code to be easier to learn to read. Your brain is good at processing things that are similar, the pathways it has to draw are all about the same-- so it's easier to optimize up there. The issue I have with Java actually is that, sometimes its too good at looking the same. To the point where I forget where I am. I get lost in my own neural pathways while I try to figure out whether I'm looking at an Abstract class or an Interface, or if I'm looking at a dirty hack of a databearing class or if I'm looking at something more legitimate. C/C++ is great at making this distinction, but it's also, IMO, ugly as shit, uglier even. I like C often for its ability to compartmentalize things, but I think it takes it to far, nothing looks alike, even if it should. One of my peeves with C vs Java is they're taking extreme views on something which should be easily decided. I'd like to sum it up as a fundamental rule I want to see in all programming languages (though that will probably never happen). Here it is:

Syntacticly similar things should be Semantically similar things, and vice versa, according to the proportion of similarity.

That is, If I want to create an object called "List" which implements a linked list, and then I want to create an interface (which is really just a Type Class, I've come to realize, but thats a story for another day.) called "Listable" which, when implemented, forces a object to have list-like properties. These things should have some similar structure. However, this is not to say we should copy Java. Java takes this too far, I think. In that, Java follows the rule: "If things are Semantically similar, they are Structurally almost Identictal." This is bad, Interfaces should look different than Classes, but only in a minor way. I'd like Java Interfaces, heck, Java in general if I could specify type signatures ala Haskell. I think Haskell has got it right when it comes to how types should work syntactically. The brilliance of this comes in when you try to write a Java Method with this Type Sig ala Haskell type syntax, here's Fibonacci:

fib :: public, static :: int -&gt; int

fib(nth) {
(nth == 1) ? 1 : fib(nth-1) + fib(nth-2);
}

(I think that'll work, but it's been a while, so I might have it wrong.)

Granted, there are issues with this. Notably, Java has things like side effects, but these could be built into the type signatures. I think that the ultimate benefit of this kind of type signaturing is a separation of concerns syntactually. I think that overall, this would make the language as a whole a lot cleaner. As interfaces would no longer have stubs like:

public static int fib(int nth);

which, though nice, doesn't carry the same amount of information that could be held in something like:

fib :: public, static :: int -> int

Syntactually, the latter structure is more extensible, it could allow for the incorporation things like side effect tracking, or thread signatures, which might look like:

fib :: public, static, threaded :: int -> (int, int, ...) -> int

which says that effectively fib is a method with takes a int to a unspecified number of threads, to an integer.

I'm really just spitballing at the end here, with some neat ideas I think that a small change in Java's syntactic structure could bring.

Just my thoughts.

PS: I don't know if the Syntactic/Semantic Similarity rule is well known, but either way, its a damn good idea.

May 01, 2007

Haskell: The Good, Bad, and Ugliness of Types

I've started to learn Haskell, for those who don't know, Haskell is a wonderful little language which is based on Lazy Evaluation, Pure Functional Programming, and Type Calculus.

Effectively, this means that, like Erlang and other sister languages, If I write a function foo in Haskell, and evaluate it at line 10 in my program. Then I evaluate it again at Line 10000, or 10000000, or any other point in my code. It will-- given the same input-- always return the same value. Furthermore, if I write a function to generate an arbitrary list of one's, like this:

listOfOnes = 1 : listOfOnes

Haskell just accepts it as valid. No Questions asked. Schemer's and ML'ers of the world are probably cowering in fear. Recursive data types are scary in an Eager language, But Haskell is lazy. Where the equivalent definition in scheme:

(define list-of-ones
(cons 1 list-of-ones))

would explode and probably crash your computer, (that is, if the interpreter didn't catch it first.) in Haskell, its not evaluated till its needed, so until I ask Haskell to start working on the listOfOnes structure, it won't. I like Languages like that, IMO, if a language is at least as lazy as I am, its good.

The third really neat thing about Haskell, and what really drew me to it in the first place, is the Type Checker. I've used Scheme for a while now, and I love it to death. Sometimes, though- Scheme annoys me. For instance, I was working on a function like this once:

;count-when-true : [bool] x [num] -&gt; num
;supposed to be a helper for filter, I want do a conditional sum. So I pass in (filter foo some-list-of-numbers) and some-list-of-numbers,
; and I should get out a sum of the elements
(define (count-when-true list-of-bools list-of-numbers)
;or-list : ([a] -> bool) x [[a]] -> bool
;applys a filter across a list of lists and ors the results
(cond [(or-list nil? (list-of-bools list-of-numbers)) 0]
[(car x) (+ (car list-of-number) (count-when-true (cdr list-of-bools) (cdr list-of-numbers)))]
[else (count-when-true (cdr list-of-bools) (cdr list-of-numbers))]))

This probably has bugs in it, doesn't work right, etc. but the idea is to return a conditional sum, now. I want to use this on lists, thats how its defined, but sometimes the calling function would try to call it on atoms, instead of lists. Big problem? not really, pain in the ass to find, you bet. The issue was, when I was trying to figure out what was wrong, Scheme didn't realize that the type of the inputs were wrong. This would have made the error obvious, but Scheme doesn't care about types, thats it's principle strength, until it starts making bugs hard to find. I HATE it when its hard to find bugs.

Lets face it, as programmers, we suck, we write lots of buggy functions, things are generally done wrong the first (two or three... thousand) times. Programming is a recursive process, we write some code, run it, check for bugs, fix bugs, run it, check, fix, etc. Until we get tired of finding bugs/the program doesn't come up with any. IMO, languages should not be designed to force programmers to write bug-free code, which seems to be the consensus today. At least, thats what I gather from the interweb and such. The goal should be to make all bugs so blatently obvious, that when the programmer sits down and trys to debug his program, he can't help but to smack himself in the face and proclaim, "!@#$, I missed that!" This is where Haskell Shines.

When I write Scheme, I typically don't want to be burdened by knowing which types go where. Scheme is great at this, however, it takes things to far, I think, in that it forces you to never have types. Sure, typed schemes exist, but most of them suck, because scheme isn't designed for types. Don't get me wrong, typed schemes are wicked cool, I've used types in CL too, and they're great, especially when you want to compile. So to solve the problem of not having types, we invented contracts, which are cool. For the unenlightened: a contract is a specification of what the given datastructure or function does in terms of its arguments. eg:

+ : num * num -> num
toASCII : string -> num
toCHAR : num ->; string

etc.

These can be read as follows:

literally:

+ is num cross num to num
etc

in english

+ is a function which takes two numbers and returns another number.


In Scheme, these contracts are basically comments, so Type checking is left to the programmer. This is all well and good, but I find it often leads to the practice of what I like to call single-typing. In which the programmer attempts to force all of his data to have the same type, or lists of the same type, or lists of lists, or etc. Typically, this results in convoluted datastructures which give FP in general a bad name. I've seen some horrible code written by single-typers, its bad, horrific even, It makes me want to gauge out my eyes with a pencil and tear my brain out... Okay, maybe its not that bad. Still, single-typing is most often bad. So how does Haskell fix it?

By not changing a thing.

Contracts are a wonderful Idea, they work, they just don't work in Scheme. Because it was designed that way. Haskell has type inference, you don't ever need to touch the Type Calculus capabilities of Haskell, You can-- more or less-- literally translate Scheme to Haskell with minimal difficulty. (Though, it may be easier just to write scheme in haskell.) But the brilliance of haskell is this:

Heres the Standard Factorial function in Scheme:

;Fac : int -> int

(define (fac x)
(cond [(= 0 x) 1]
[else (* n (fac (-n 1)))]))

Here it is in Haskell:

fac :: Int -> Int
fac(x)
| (x == 0) 1
| otherwise x * fac(x - 1)

(I used a ML style to make things look the same.)

The only real difference (besides some syntax changes) is the lack of the semicolon in front of the contract.

But what does all this do? Well, the difference comes during evaluation, watch this:

In Scheme:

(fac 1.414)

we have an infinite recursion, because:

(fac 1.414) -> 1 * fac(0.414) -> 1 * 0.414 * (fac -0.586) ...



In Haskell:

fac 1.414

is a type error, and the whole thing kersplodes. Over, Evaluation Done, Haskell has Denied your function the right to evaluate.

In short, you have been rejected.Enough about the wonderfulness of the Type system. My title says the Good -> Bad -> Ugliness, obviously we've seen the good. How about the Bad?

Type Errors in Haskell:

Type errors in haskell suck, easy as that. They're hard to understand, and in general, not very helpful. Further, alot of the differences between types are very subtle. For instance, consider the factorial function again, (just the type contracts for succinctness)

fac0 :: Int -> Int
fac1 :: Num -> Num


The look equivalent, right? Wrong. Num != Int, it includes Reals too.* So no lovely type errors here. These things are unfortunate, yes, but nothings really perfect. I could deal with this, but what I can't deal with is exactly the problem I hoped to solve with Haskell, My bugs are hard to find. Not only that, they're not hard to locate, I know exactly where they are, I just can't decipher the cryptic text from the Haskell error stream to know exactly what the bug is. So I have to resort to piecing through the code bit by bit, trying to figure it out.

Silly.

Type Signatures are Ugly:

I Like Contracts, but Haskell doesn't technically use them. Haskell has type signatures. Which are different.

So far, I've written contracts like this:

F : S * T * U * ... -> D

I could also have:

F : S * T * ... -> (D1, D2, ...)

or if I wanted HOF's

F : (G : X -> Y) * ... -> (D, ...)

these are all pretty easy to understand, (if you know how to read the shorthand). We know exactly what the arguments should be, elements of the set of elements of type S, or T etc. We also know exactly what the return types are, elements of the typed-set D, or ordered k-tuples of elements of typesets D1 through Dn, etc. Equivalent signatures in Haskell are:

(assuming f = F, and any capital letter is a valid type, and that ...'s would be replaced with types in the end result.)**

f :: S -> T -> U -> ... -> D
f :: S -> T -> ... -> (D1, D2, ...)
f :: (X -> Y) -> ... -> (D, ...)

Now, I understand that, since Haskell is Lazily evaluated, we want the type signatures to be heavily curried, hence the load of arrows. Honestly though, how hard is it to convert all that to a form Haskell can use? I'm not saying get rid of the arrow version, maybe just add an option to provide a "normal form" version, I shouldn't have to add these in my code as comments, solely so I can understand whats going on. I understand that the implication method more accurately reflects what the compiler is doing, but as a programmer, I don't really give a rats ass what the compiler is doing. As a mathematician,

foo :: Int -> String -> Num -> Bool

looks ugly, do I know what it means? Yes. Do I like the way it looks? No. I grasp that, as a Haskell Compiler, reading these type of signatures in makes things easier, and further, that these definitions make things easier to prove correct*** but damnit Haskell, I'm a mathematician, not a miracle worker, I want to be able to read those definitions intuitively, and not have to muddle around trying to figure out exactly what that signature represents. It's ugly, fix it.



On that note, I am beginning to work on some Haskell Code which will convert a Type Signature of the form:

f :: S^n1 * T^n2 * ... -> (D1,D2, ... Dn)

to the form:

f :: S -> S -> .. n1 times .. -> T -> T -> ..n2 times.. -> (D1, D2, ... Dn)

and hopefully, given some user input, the latter to the former as well. (This is not harder, sortof, but I can't know what the normal form of the type signature should be without some user input about the in-arity (arity) and out-arity (ority) of the function.

Anywho, Haskell is awesome, go play with it.

~~Joe







*=
Aside: I'm quite glad Haskell calls them Reals and not
something silly like Float (though that is allowed) or Double. Us
Mathematicians have had these names for years, IEEE can call the format
Double precision floating point of w/e the hell they want, they're
reals, not doubles. Silly computer scientists...

Edit: Note that in fact I understand that floats != reals, but its about state of mind. I know I'm working on a computer, and so I'm not going to treat things as reals, but I want to be thinking as if I'm not limited, so that when I work with my code, I'm not tuning the algorithm to work with the computer, I'm tuning the computer to work with my algorithm. In this way, the problem becomes a problem of making the compiler better, rather than hacking my algorithm to work.

**= Haskell doesn't really like capitalized function names.

***= Proofs of correctness are done through the Curry-Howard Isomorphism, which effectively states that if the contract of a given function is a valid statement of Logic, then the function is correct, otherwise its not. Note that this requires the Signature to be correctly written, ie:

concatString :: String -> String -. String as a signature for a function which zipped two strings together would be "correct" but only in the sense that the contract would be satisfied. A Proof of correctness means that the function of that type can exist, there are other methods related to this Isomorphism which allow for a better proof of the semantic correctness, as opposed to the more syntactual flare of Curry-Howard