Wednesday, September 1, 2010

Algorithms and functions

Consider the following two functions:

f :: () -> ()
f = const ()

g :: () -> ()
g = id


Is there a way to write a function that tells them apart? Given an infinite loop, first will stop and the second will hang. But you can do better, give an exception and check if it was thrown:

data TestException = TestException deriving (Show, Typeable)

instance Exception TestException

test :: (() -> ()) -> Bool
test k = unsafePerformIO $ catch (k (throw TestException) `seq` return True)
(\TestException -> return False)


Is this a safe trick?

On the one hand, it looks rather innocently: a function is given some box, and if it opens it, it's caught red-handed. Such function would hang given infinite loop. A function that doesn't touch the box, yet finishes, is const (). Such 'test' is a nice feature to have.

On the other hand, something is wrong, since f is more defined than g, and test f is not at least as defined as test g. This contradicts monotonicity. By giving two exceptions to (+), you can check which argument is evaluated first:

throw A + throw B

That means flip (+) is not the same as (+). Addition is not commutative!

Which of these points is correct?

The representation of a->b
Internally, the (->) type is a list of instructions - force a thunk, case, perform a primitive instruction like adding integers. In other words, it's an algorithm. You could conceivably write an algebraic datatype that encompassed all those options.
data Instruction a b = Force Thunk | Return Value...
type Algorithm a b = [Instruction a b]


Haskell has an evaluator that takes an algorithm and runs it step by step.
($) :: Algorithm a b -> a -> b


Having access to internal source code of an algorithm, you can write a "debugger" that stops if the function forces its argument. In a sense, this is what the function test is doing.

Lazy IO uses this trick. When a thunk is forced evaluation is stopped momentarily, and IO is performed.

Still, the denotational semantics argument seems disturbing.

The distinction

The solution to the dilemma is:

There are two different ways of interpreting values of type a -> b.


  • functions that assign a value of b to each value of a.

  • algorithms that are recipes how to turn a into b.


In Haskell, the function view is used, but in this post I'll use both to illustrate differences. I'll call the algorithm view "operational" and function view "denotational".

Representing algorithms is possible using ADT, as you seen above. Functions are represented using algorithms:

data Function a b = Function (Algorithm a b)


You can turn an algorithm into a function:

evaluate :: Algorithm a b -> Function a b
evaluate = Function


but the reverse conversion is ill-defined - one function has many representations. evaluate turns an algorithm into a "black box".

Think about rational numbers. You represent them as pairs of integers, even though a rational number is not a pair. Then, you write operations like addition, which don't break 'internal consistency'. Not every operation on pairs can be lifted to operation on rationals. Different pairs may represent same rationals. It's the same with functions stored as algorithms.

Questions:
The questions focus on differences between algorithms and functions.

1. Can you compare values of type a -> b for equality?
Answer


2. How would you show an algorithm? A function?
Answer


3. How would you read an algorithm? A function?
Answer


4. What abstract models of computation correspond to algorithms and functions?
Answer


5. How does semantic order on values a -> b look like?
Answer



6. Is the following function

f :: (() -> ()) -> Bool
"f g = [return True if evaluation of g () halts within 100 evaluation steps]"

well-defined?

Answer


7. What about this?

lub :: (Bool -> ()) -> ()
lub f = [return () if evaluation of f False or f True halts]


Answer


8. Since a->b in Haskell is seen as function type, not algorithm type, anything dependent of "internals" is ambiguous. How does Haskell deal with it?

Answer



Summary
In most languages, 'functions' are algorithms. In Haskell, the emphasis is on functions as in mathematics and referential transparency.

Since Haskell is running on a computer, operational semantics (algorithms) describe how things work on the lower level and you can't do away with them. Things like "debugging", "unsafePerformIO", "measuring time/space complexity of a function", "order of evaluation" are relevant to operational semantics and break the abstraction. Things like "referential transparency" or "functional reactive programming" are valid for functions.

I think this is what makes Haskell different from imperative languages. FP is about functions, not algorithms. This has advantages, like better support for composability - and disadvantages, like more difficult time/space reasoning.

Thursday, July 29, 2010

The universal space

Take (or imagine) a blank sheet of paper. This is a plane. You can put points and vectors on it. A vector connects two points, but it is "movable": if you can translate one vector into another, they are deemed equal. A vector doesn't really have a beginning - you can position it wherever you want.

In this setting, some operations make sense, like

  • vector + point = point:
    Position the vector at a point, and its end will be the result.

  • point - point = vector:
    Join the points to get a vector from A to B. (It's inverse of vector + point = point.)

  • vector + vector = vector:
    Put the beginning of one vector to the end of the second.


But some don't, like adding two points, or subtracting vector - point. With added origin, you can do anything using coordinates, as in (2,1) + (3,0) = (5,1). In fact, with given origin you can consider every point as a vector from the origin. But without it, it's like physical motion - you cannot tell if something is moving without a frame of reference.

Although addition point + point doesn't make sense, (point + point) / 2 should - it's middle between the points. 0.2 point + 0.8 point is somewhere in the 4/5 of the segment. This is known as "affine combination".

An expression like vector + point - point can be computed in two different ways: (vector + point) - point and vector + (point - point) and it turns out the result will be the same. There must be some structure here.

Define mass of a vector as 0, and mass of point as 1. Then,

  • vector + point = point: 0 + 1 = 1

  • point - point = vector: 1 - 1 = 0

  • vector + vector = vector: 0 + 0 = 0

  • (point + point) / 2 = point: (1+1) / 2 = 1


In fact you can enlarge the space. Define an object to be either a vector with mass 0, or a pair (p,m) which is a point p with a nonzero mass m. I'll write a point as m*p. Then multiplication streches a vector, or changes a point's mass: a*(m*p) = (a*m)*p. Addition is done with:

m p + v = m (p + \frac{v}{m})
- translation

m_{1}p_{1} + m_{2}p_{2} = (m_{1}+m_{2}) (\frac{m_{1}}{m_{1}+m_{2}} p_{1} + \frac{m_{2}}{m_{1}+m_{2}} p_{2})
- weighted mean of points

m_{1}p_{1} - m_{1} p_{2} = m_{1} (p_{1} - p_2})
- a vector joining two points

In this space, points and vectors are equal partners, and anything can be added and multiplied by a number. It's a vector space with dimension one more than the original.

In the original space, you assign a meaning to a sum like 0.2a + 0.8b, but not to the summands. In this space, summands make sense and 0.2a + 0.8b is really a sum of 0.2a and 0.8b.

In mathematical terms, this is an assignment of a vector space to every affine space. This construction is known as the universal space. Now, vector spaces and affine spaces have their own meaning of functions. A linear map respects linear combinations: f(cx+dy) = c f(x)+d f(y). An affine map is something that respects affine combinations: f(cx+dy) = cf(x)+ df(y), where c+d=1. It's easy to present a linear map using a matrix. How to present an affine map? The answer is, given affine map, you can extend it to a linear map between universal spaces by f(m*p)=m*f(p) for all m. And that gives a matrix.

For category theory lovers, this construction is the left adjoint of a functor that assigns an affine space to a vector space by forgetting the origin.

Monday, July 26, 2010

Kind polymorphism in action

Ultrecht Haskell Compiler is an experimental Haskell compiler that supports polymorphism on the kind level. This means that in
data Eq a b = Eq (forall f. f a -> f b)

Eq is given kind
Eq :: forall a . a -> a -> *


and both Eq Integer Char and Eq [] Maybe are valid types.

Using kind polymorphism, it is possible to write sigfpe's From monoids to monads using a single type class.

To talk about monoids, you need a category (mor), multiplication (mul) and a unit.

class Monoid mor mul unit m where
one :: mor unit m
mult :: mor (mul m m) m


With mor being (->), mul being (,), unit being () this is a normal monoid (one :: () -> m and mult :: (m,m) -> m.). For example:

instance Monoid (->) (,) () Integer where
one () = 1
mult = uncurry (*)


Now, instead of functions, there will be natural transformations; instead of (,) there will be functor composition; instead of unit there will be identity functor.

data Nat f g = Nat (forall x. f x -> g x)
data Comp f g x = Comp (f (g x))
data Id x = Id x
Nat :: (* -> *) -> (* -> *) -> *
Comp :: (* -> *) -> (* -> *) -> * -> *
Id :: * -> *


And here is the list monad. Notice kinds are different than in the previous case, but it is still an instance of the same type class.

instance Monoid Nat Comp Id [] where
one = Nat $ \(Id x) -> [x] -- one :: Nat Id []
mult = Nat $ \(Comp x) -> concat x -- mult :: Nat (Comp [] []) []


So, monads are really monoids in category of endofunctors.

If you invert the arrows, you get a comonad. Here's the product comonad.


data CoNat f g = CoNat (forall x. g x -> f x)
data CoComp f g x = CoComp (g (f x))
CoNat :: (* -> *) -> (* -> *) -> *
CoComp :: (* -> *) -> (* -> *) -> * -> *

data Product w a = Product w a

instance Monoid CoNat CoComp Id (Product w) where
one = CoNat $ \(Product a b) -> Id b
mult = CoNat $ \(Product a b) -> CoComp $ Product a (Product a b)


Question: what are kinds of mor, mul, unit and m in the Monoid type class definition?

There's a small lie here: monads require also a liftM/fmap function. Not all Haskell types of * -> * are functors, and I used that as a poor replacement.

I didn't write monoid laws, which if translated happen to be monad laws. You're welcome to read sigfpe's original post. It's hard to write them generically since there's no access to fmap.

The code is available on hpaste and can be run in UHC.

Tuesday, May 4, 2010

Denotational semantics

You're given diagrams of some Haskell types ordered by semantic order. Vertices are inhabitants of a datatype, and the lines point upwards, from less defined to more defined. (See Wikibooks for an introduction and examples.) Your objective is to construct a type corresponding to the diagram, or show that is impossible.


I've done the first one - it is obviously Bool. Good luck!

DiagramType


Bool



Solution




Solution




Solution



Solution

Solution

Solution


Solution


Solution


Solution

Solution

Solution

Solution


This is a variant of NaturalsDown and will require cheating a little. Create a module that will export a data type, and only a "smart constructor" that will equate undefined and const undefined.

Solution



Application

A great application of denotational semantics is doing numerical integration exactly.

Monday, April 26, 2010

Conjugating verbs in Haskell


> {-# LANGUAGE RecordWildCards #-}
> import Data.Maybe
> import Data.Default
> import Control.Monad.Writer hiding (First)

I'll show you an English verb conjugator. Although handling inflections is complex, the structure of the language can be expressed idiomatically, using a monad. You'll see that things like "perfect continuous" are really "perfect" on top of "continuous", in code.

First, some boring code and auxiliary functions.

> data Tense = Past | Present | Future
> type Infinitive = String
> data Person = First | Second | Third
> -- plural in English is the same form as second person

> pastForms inf = fromMaybe (inf++"ed", inf++"ed") $
> lookup inf [("do", ("did", "done")),
> ("have", ("had", "had")),
> ("be", ("was", "been")),
> ("drive", ("drove", "driven")),
> ("build", ("built", "built"))]

> presentParticiple inf | last inf == 'e' && inf /= "be" = init inf ++ "ing"
> | otherwise = inf ++ "ing"

> pastParticiple inf = snd $ pastForms inf

> conjugate1 :: Tense -> Person -> Infinitive -> String
> conjugate1 Future p inf = "will " ++ inf
> conjugate1 t p "be" = case (t, p) of
> (Present, First) -> "am"
> (Present, Second) -> "are"
> (Present, Third) -> "is"
> (Past, Second) -> "were"
> (Past, _) -> "was"

> conjugate1 Past p inf = fst $ pastForms inf
> conjugate1 Present Third "have" = "has"
> conjugate1 Present Third "do" = "does"
> conjugate1 Present Third inf = inf ++ "s"
> conjugate1 Present _ inf = inf

We can conjugate verbs in three tenses, and form participles. For example:

> test1 = conjugate1 Future First "drive"
> test2 = conjugate1 Present Third "phone"
> test3 = presentParticiple "have"

Adding "perfect"
Now the fun begins.

Exercise: Allow forming perfect tenses:

> conjugate2 :: Bool -> Tense -> Person -> Infinitive -> String

(For example, conjugate2 True Present Third "drive" should be "has driven")



Solution:

Perfect is "have" + past participle. You can express this directly:

> conjugate2 False tense person inf = conjugate1 tense person inf
> conjugate2 True tense person inf = conjugate1 tense person "have" ++ " " ++ pastParticiple inf


Adding "continuous"
It will be downhill now.

Exercise: Allow forming continuous tenses:

> conjugate3 :: Bool -> Bool -> Tense -> Person -> Infinitive -> String


where the first parameter will be continuous or not. For example, conjugate3 True False Present Third "drive" should be "is driving".



Solution:

It's be + present participle.

> conjugate3 False perf tense person inf = conjugate2 perf tense person inf
> conjugate3 True perf tense person inf = conjugate2 perf tense person "be" ++ " " ++ presentParticiple inf


This composes nicely:

> test4 = "he " ++ conjugate3 True True Present Third "drive"

Adding passive voice
Exercise: Allow forming passive voice:


> conjugate4 :: Bool -> Bool -> Bool -> Tense -> Person -> Infinitive -> String

> test5 = "the house " ++ conjugate4 True True False Present Third "build"




Solution:

> conjugate4 False cont perf tense person inf = conjugate3 cont perf tense person inf
> conjugate4 True cont perf tense person inf = conjugate3 cont perf tense person "be" ++ " " ++ pastParticiple inf


Merging
conjugate2, conjugate3 and conjugate4 can be joined into a single function.
Remembering all arguments in order and specifying them every time is problematic. This is described in Brent Yorgey's Haskell anti-pattern - incremental ad-hoc parameter abstraction. Also there's a lot of repetition.


> conjugate5 :: Bool -> Bool -> Bool -> Tense -> Person -> Infinitive -> String
> conjugate5 True continuous perfect tense person inf =
> conjugate5 False continuous perfect tense person "be" ++ " " ++ pastParticiple inf
> conjugate5 _ True perfect tense person inf =
> conjugate5 False False perfect tense person "be" ++ " " ++ presentParticiple inf
> conjugate5 _ _ True tense person inf =
> conjugate5 False False False tense person "have" ++ " " ++ pastParticiple inf
> conjugate5 _ _ _ tense person inf = conjugate1 tense person inf


Using records


> data ConjugateOptions = ConjugateOptions { passive :: Bool,
> perfect :: Bool,
> continuous :: Bool,
> person :: Person,
> tense :: Tense }

> instance Default ConjugateOptions where
> def = ConjugateOptions False False False First Present

> conjugate6 :: ConjugateOptions -> Infinitive -> String
> conjugate6 (o@ConjugateOptions{ .. }) inf
> | passive = conjugate6 o { passive = False } "be" ++ " " ++ pastParticiple inf
> | continuous = conjugate6 o { continuous = False } "be" ++ " " ++ presentParticiple inf
> | perfect = conjugate6 o { perfect = False } "have" ++ " " ++ pastParticiple inf
> | otherwise = conjugate1 tense person inf

Much better - we can use it like


> test6 = conjugate6 def { perfect=True } "paint"


Using the Writer monad
conjugate6 is doing recursion on some infinitive and adds "remaining part" to the end. The Writer monad can express this.


> plumb :: Infinitive -> (Infinitive -> String) -> Infinitive -> Writer [String] Infinitive
> plumb aux participle inf = Writer (aux, [participle inf])

> passive' = plumb "be" pastParticiple
> continuous' = plumb "be" presentParticiple
> perfect' = plumb "have" pastParticiple

> conjugate7 :: Tense -> Person -> (Infinitive -> Writer [String] Infinitive) -> Infinitive -> String

> conjugate7 tense person tr inf =
> let (a,b) = runWriter (tr inf)
> in unwords $ (conjugate1 tense person a):(reverse b)


You can join those different "higher order verbs" using >=>.


> test7 = "he " ++ conjugate7 Past Third (continuous' >=> perfect') "paint"


and add new new ones instantly:

> learn = plumb "learn" ("to "++)

> test8 = "I " ++ conjugate7 Present First (learn >=> perfect') "love" ++ " Haskell"

Obviously there is a lot missing - inflections ("he goes", "he panicks"), irregular verbs, modal verbs, negation, "used to", "have something done", interrogative mood... It gets dirty then.

You can write such conjugator in similar languages, like German.

Haskell is a great language - imagine how would you write conjugate1 without pattern matching, or writing the plumbing in conjugate5 again, when Writer can do that for you.

Followers