Hi,

On 16/07/10 07:35, C K Kashyap wrote:
Haskell without using any standard library stuff?

For example, if I wanted an image representation such as this
[[(Int,Int.Int)]] - basically a list of lists of 3 tuples (rgb) and
wanted to do in place replacement to set the pixel values, how could I
go about it.

Break the problem down into parts:

1. replace a single pixel
2. modify an element in a list at a given index using a
   given modification function
3. modify an element in a list of lists at a pair of given
   indices using a given replacement function

I had a stab at it. Without any standard library stuff I couldn't figure out how to print any output, though - so who knows if the code I wrote does what I intended.

The point is, it's libraries all the way down - so use them, study them where necessary for understanding, and write them and share them when you find something missing.


Claude
--
http://claudiusmaximus.goto10.org
{-# LANGUAGE NoImplicitPrelude #-}
module CKKashyap where

-- numbers are in the standard library

data Nat = Zero | Succ Nat

(+) :: Nat -> Nat -> Nat
Zero + y = y
(Succ x) + y = x + Succ y

zero = Zero
one = Succ zero
two = one + one
four = two + two
eight = four + four
sixteen = eight + eight
thirtytwo = sixteen + sixteen
sixtyfour = thirtytwo + thirtytwo
onehundredandtwentyeight = sixtyfour + sixtyfour
twohundredandfiftysix = onehundredandtwentyeight + onehundredandtwentyeight
Succ twohundredandfiftyfive = twohundredandfiftysix

-- booleans are in the standard library

data Bool = False | True

gt :: Nat -> Nat -> Bool
Zero `gt` x = False
Succ x `gt` Zero = True
Succ x `gt` Succ y = x `gt` y

eq :: Nat -> Nat -> Bool
Zero `eq` Zero = True
Succ x `eq` Succ y = x `eq` y
x `eq` y = False

-- lists are in the standard library

data List a = Nil | Cons a (List a)

map :: (a -> b) -> List a -> List b
map f Nil = Nil
map f (Cons x xs) = Cons (f x) (map f xs)

repeat :: a -> List a
repeat x = Cons x (repeat x)

take :: Nat -> List a -> List a
take Zero ys = Nil
take (Succ x) Nil = Nil
take (Succ x) (Cons y ys) = Cons y (take x ys)

foldr :: (a -> b -> b) -> b -> List a -> b
foldr op e Nil = e
foldr op e (Cons x xs) = op x (foldr op e xs)

nats :: List Nat
nats = Cons Zero (map Succ nats)

-- tuples are in the standard library

data Tuple2 a b = Tuple2 a b
data Tuple3 a b c = Tuple3 a b c

zip :: List a -> List b -> List (Tuple2 a b)
zip Nil _ = Nil
zip _ Nil = Nil
zip (Cons a as) (Cons b bs) = Cons (Tuple2 a b) (zip as bs)

-- modify list elements

modifyAtIndex :: (a -> a) -> Nat -> List a -> List a
modifyAtIndex f i as =
  let ias = zip nats as
      g (Tuple2 j a) = case i `eq` j of
                         False -> a
                         True  -> f a
  in  map g ias

modifyAtIndex2 :: (a -> a) -> Nat -> Nat -> List (List a) -> List (List a)
modifyAtIndex2 f i j = modifyAtIndex (modifyAtIndex f i) j

-- images as lists of lists of tuple3 of nat

type Pixel = Tuple3 Nat Nat Nat
black :: Pixel
black = Tuple3 Zero Zero Zero
white :: Pixel
white = Tuple3 twohundredandfiftyfive twohundredandfiftyfive twohundredandfiftyfive

type Scanline = List Pixel
type Image = List Scanline

blank :: Image
blank = take thirtytwo (repeat (take thirtytwo (repeat black)))

plotPixel :: Nat -> Nat -> Image -> Image
plotPixel x y img = modifyAtIndex2 (\_ -> white) x y img

diagonal :: Image
diagonal =
  let is = take thirtytwo nats
      ijs = map (\i -> Tuple2 i i) is
  in  foldr (\(Tuple2 i j) img -> plotPixel i j img) blank ijs
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to