Friday, February 28, 2014

'Arrow' is spelt 'fizz-buzz'


A little literate Haskell program:

> module Fizzbuzz where

So, fizz-buzz through a functional lens

> import Control.Arrow

Our predicate is for some number, x, we print 'fizz' if it's modulo 3,
or we print 'buzz' if it's modulo 5. N.b.: these predicates are not
exclusive.

So our fizz-buzz predicate follows ('pred'icate 'f'izz-'b'uzz)

> predfb :: String -> Int -> Int -> Either String Int
> predfb str modulo x | x `mod` modulo == 0 = Left str
>                     | otherwise = Right x

so:

> fizz = predfb "fizz" 3
> buzz = predfb "buzz" 5

... that's really all there is so we just split the input number
into the two predicates and then remerge the results following
this rule:

Left str1 (+) Left str2 = str1 ++ str2
Left str (+) _ = str
_ (+) Left str = str
Right x (+) _ = show x

which transliterates quite nicely (it's nice programming requirement specification as implementation-code when your programming language is declarative)

> fbprinter :: (Either String Int, Either String Int) -> String
> fbprinter (Left x, Left y) = x ++ y
> fbprinter (Left x, _) = x
> fbprinter (_, Left y) = y
> fbprinter (Right num, _) = show num

Now the fizz-buzz game: count from 1 to 100 replacing '3's with fizz and '5's
with 'buzz' ... off you go:

> fizzbuzz = [1..100] >>= return . (fizz &&& buzz >>> fbprinter)

There it is. fizzbuzz in, lessee, 8 lines of implementation code. Any questions?

Nope? Q.E.D.

Afterthought:

Well, there is one improvement. If we look at the Either type as a cartesian
product type (which it is), then the print rule looks rather redundant to the
monoidal append operation, for, after all

m0 (+) (anything) = (anything) (order of arguments superfluous); and,
m+ (+) m+ = defined by the semigroupoid-implementation

so, the monoidal addition of lists is

[] (+) lst = lst; and,  (... even if lst == [])
lst1 (+) lst2 = lst1 ++ lst2

Can't we just convert our Either String Int type to be a monoid and have
the special base case of 'show num' for the (Right num (+) Right num) case?

Hm. Yes. I leave this now as an exercise for the reader...

... which is another way of saying that I see a simple solution of

mzero == Right num

and

mplus == Left str

in my head, but how to implement that in Haskell is currently puzzling me.

Intrepid readers, show me the light!

... at any rate, 'running' fizzbuzz gets you all fizzy-buzzy and you can feel good that you've used a little predicate logic, functional programming, programming with arrows, no less, and you didn't have any redundant boolean logic that you see in other implementation for fizz-buzz: Either took care guarding our conditioned results.

Sweet!

p.s. The payoff! The payoff! How could I forget the payoff for those of you who don't have Haskell running natively on your 'iron'?

(Now, why you don't have haskell running on your platform, I don't want to even think about. Not having haskell on hand to feed yourself your functional-programming (daily/hourly/secondly) fix? geophf shudders)

*Fizzbuzz> :l Fizzbuzz.lhs 
[1 of 1] Compiling Fizzbuzz         ( Fizzbuzz.lhs, interpreted )
Ok, modules loaded: Fizzbuzz.
*Fizzbuzz> fizzbuzz 
["1","2","fizz","4","buzz","fizz","7","8","fizz","buzz","11","fizz","13","14","fizzbuzz","16","17","fizz","19","buzz","fizz","22","23","fizz","buzz","26","fizz","28","29","fizzbuzz","31","32","fizz","34","buzz","fizz","37","38","fizz","buzz","41","fizz","43","44","fizzbuzz","46","47","fizz","49","buzz","fizz","52","53","fizz","buzz","56","fizz","58","59","fizzbuzz","61","62","fizz","64","buzz","fizz","67","68","fizz","buzz","71","fizz","73","74","fizzbuzz","76","77","fizz","79","buzz","fizz","82","83","fizz","buzz","86","fizz","88","89","fizzbuzz","91","92","fizz","94","buzz","fizz","97","98","fizz","buzz"]

There ya go!

(this program contains its own solution ... meta-quine, anyone?)

2 comments:

Nathan said...

The monoid instance only kind of works, because there isn't really a good mempty. Yes, it should be a Right num, but what is num? The program assumes the invariant that if you're using mappend on two Right values, they contain the same number, but in the definition of the monoid instance we can't assume this. A moderately hacky way around this is to say that mempty = Right 0, and mappend (Right m) (Right n) = Right (max m n). This works, assuming you only want to fizzbuzz natural numbers. If you want it to work for all integers you could set mempty = Right (-infinity) where infinity = read "Infinity".

Ryan Ingram said...

instance (Monoid l, Monoid r) => Monoid (Either l r) where

mempty = Right mempty

mappend (Left x) (Left y) = Left (mappend x y)

mappend (Left x) (Right _) = Left x
mappend (Right _) (Left x) = Left x
mappend (Right x) (Right y) = Right (mappend x y)


Proving the monoid laws is an exercise for the reader. You can then use whatever monoid on integers you want; I suggest 'Sum'.