[Haskell-cafe] Haskell implementation of ideas from StandardML as a Metaprogramming language

2010-01-14 Thread CK Kashyap
Hi All,
I was just going over the paper titled - Standard ML as a meta programming 
language by Samuel Kamin - It has a few ideas of generating C++ code from ML. 
The first one being generating C++ top down parser. I wanted to try out the 
sample in Haskell - I was wondering if anyone's already done that - I could 
just look at that implementation for reference.
Regards,
Kashyap


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell implementation of ideas from StandardML as a Metaprogramming language

2010-01-14 Thread CK Kashyap
Thank you very much Stephen ... I'll try and work on the doc plus the code 
you've sent to understand it.
If you do find the parser combinators, please do send it to me.

Thanks and Regards,
Kashyap


- Original Message 
 From: Stephen Tetley stephen.tet...@gmail.com
 Cc: haskell-cafe@haskell.org
 Sent: Fri, January 15, 2010 1:08:20 AM
 Subject: Re: [Haskell-cafe] Haskell implementation of ideas from StandardML 
 as a Metaprogramming language
 
 Hello Kashyap
 
 I can do MSL and Region, maybe I did the parser combinators but I
 can't find them at the moment.
 
 I tried to keep the code close to the original SML, so as Haskell code
 its not pretty. Not having quasiquote was a problem.
 
 Best wishes
 
 Stephen
 
 
 
 -- MSL
 
 
 module MSL where
 
 
 type Expr = String
 type Predicate = Expr
 type Statement = String
 type Fieldname = String
 
 data Bitsource = Source Expr Expr
   deriving Show
 
 
 newbitsource a i  = Source a i
 
 initbs (Source _ i) =  i ++  = 0;
 
 getByte (Source a i)  =  a ++ [ ++  i ++ /8]
 
 getNthByte :: Bitsource - Int - Expr
 getNthByte (Source a i) n
 | n == 0= a ++ [ ++  i ++ /8]
 | otherwise = a ++ [ ++  i ++ /8+ ++ show n ++ ]
 
 advanceByte (Source a i) = i ++  =  ++ i ++ -( ++ i ++ %8)+8;
 
 advanceNBytes (Source a i) n
 | n == 0= 
 | otherwise = i ++  =  ++ i ++ -( ++ i ++ %8)+(8* ++ show n++);
 
 
 data Recordfield = Field Expr [Fieldname]
   deriving Show
 
 recordptr :: Expr - Recordfield
 recordptr e  = Field e []
 
 subfield :: Recordfield - Fieldname - Recordfield
 subfield (Field e fl) f  = Field e (f:fl)
 
 deref :: Recordfield - Expr
 deref (Field e fl)
 = (* ++e++ ) ++ concat ( map cojoin (reverse fl) )
   where
 cojoin :: Fieldname - String
 cojoin s = . ++ s
 
 
 
 type Message = Bitsource - Recordfield - Statement - Statement
 
 infield :: Fieldname - Message - Message
 infield f m src tgt
 = m src (subfield tgt f)
 
 
 c_if :: Expr - Statement - Statement - Statement
 c_if e s1 s2
 = if e==1 || e==(1)
  then s1
  else if(++e++){
 ++ s1
 ++ } ++ if s2 /=  then else { ++ s2 ++ } else 
 
 
 
 seqmsg :: [Message] - Message
 seqmsg (m:ml) src tgt s
   = (m src tgt error_action();) ++  (seqmsg ml src tgt s)
 seqmsg [] _ _ _ = 
 
 asc2Int :: Int - (Int,Int) - Message
 asc2Int w (lo,hi) src tgt s
  = c_if (inrange( ++ (getByte src) ++ , 
 ++ (ms w) ++ ,  ++ (ms lo)
 ++ ,  ++ (ms hi))
 
 s
   where
   ms n = show n
 
 
 alt :: [Message] - Message
 alt (m:ml) src tgt s
   = m src tgt (alt ml src tgt s)
 
 
 delim :: Expr - Message
 delim e src tgt s
   = if ( ++ getByte src ++  ==  ++ e ++)
++ advanceByte src
 
 rangex :: Int - Int - [Int]
 rangex i j
 | i  j = []
 | otherwise = (i:(rangex (i+1) j))
 
 
 c_and [] =  
 c_and [pred] = ( ++ pred ++ )
 c_and (pred1:pred2:preds) = ( ++ pred1 ++++ c_and (pred2:preds) ++ 
 )
 
 asc :: String - String - Message
 asc chars value src tgt s
   = c_if 
  (deref tgt ++  ==  ++ value ++ ; )
  s
 
 skip :: Int - Message
 skip n src tgt s
   = (deref tgt) ++ = 1;
 ++ (advanceNBytes src n)
 
 
 
 bs = newbitsource A bit
 f = recordptr target
 
 
 main = delim 6 bs f abort();
 
 
 to_confidence = alt [ asc HH High
 , asc MM Medium
 , asc LL Low
 , asc NN None
 ]
 
 
 
 -- Region
 
 -- This one doesn't work properly -
 -- CPoints are difficult to manipulate as strings, hence the `hasVar`
 -- problems, it gives some idea of the method though.
 
 
 
 module Region where
 
 import Data.Char ( isAlpha )
 import Data.List ( foldl' )
 
 
 -- Prolog
 type CExpr = String
 type CPred = String
 type CFloat = Float
 
 infixr 6 ++
 (++) :: Show a = String - a - String
 s ++ a = s ++ show a
 
 
 sqrdist _ = 
 
 add :: CPoint - CPoint - CPoint
 add a b = a ++ + ++ b
 
 sub :: CPoint - CPoint - CPoint
 sub a b = a ++ - ++ b
 
 hasVar :: CExpr - Bool
 hasVar = any isAlpha
 
 cfst :: CPoint - CExpr
 cfst a | hasVar a   = a ++ .x
| otherwise  = 1.1
 
 csnd :: CPoint - CExpr
 csnd a | hasVar a   = a ++.y
| otherwise  = 2.2
 
 pt :: (CFloat,CFloat) - CPoint
 pt = show
 
 intersect :: [Region] - Region
 intersect (r:rs) = foldl' (/\) r rs
 intersect [] = error $ intersect on empty list
 
 
 
 -- presentation
 
 type CPoint = CExpr
 type Region = CPoint - CPred
 
 
 circle :: CFloat - Region
 circle n = \p - ( ++ sqrdist p ++  ++ n ++ * ++ n ++ )
 
 halfplane :: CPoint - CPoint - Region
 

[Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread CK Kashyap
Hi All,

I've written this piece of code to do permutations -

perms :: String - [String]
perms []= []
perms (x:[])= [[x]]
perms (x:xs)= concat (f [x] (perms xs))

spread :: String - String - [String] -- interpolate first string at various 
positions of second string
spread str1 str2 = _spread str1 str2 (length str2)
where
_spread str1 str2 0= [str1 ++ str2]
_spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread str1 
str2 (n-1))

f xs = map (spread xs)


The number of outcomes seem to indicate that correctness of the algo .. 
however, I'd be very obliged
if I could get some feedback on the Haskellness etc of this ... also any 
performance pointers ...


Regards,
Kashyap


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Review request for my permutations implementation

2010-01-07 Thread CK Kashyap
Thanks everyone,
Thanks Daniel for this really detailed explanation - thank you very much.

Regards,
Kashyap


From: Daniel Fischer daniel.is.fisc...@web.de
To: haskell-cafe@haskell.org
Cc: CK Kashyap ck_kash...@yahoo.com
Sent: Thu, January 7, 2010 4:16:33 PM
Subject: Re: [Haskell-cafe] Review request for my permutations implementation

 
Am Donnerstag 07 Januar 2010 09:37:42 schrieb CK Kashyap:
 Hi All,

 I've written this piece of code to do permutations -

 perms :: String - [String]
Nothing in the algorithm needs the list elements to be Chars, there's no type 
class involved, so it should be
perms :: [a] - [[a]]
 perms []= []
This should actually be
perms [] = [[]]
 perms (x:[])= [[x]]
That is then superfluous.
 perms (x:xs)= concat (f [x] (perms xs))

'f' is a good name for a function parameter, not for a top level binding.
Why not
perms (x:xs) = concat (map (spread [x]) (perms xs))
whcih you can reformulate as
perms (x:xs) = concatMap (spread [x]) (perms xs)
or, if you like Monads, since concatMap is just the bind operator of the 
[]-monad,
perms (x:xs) = perms xs = spread [x]
Which can be written as a simple do-block:
perms (x:xs) = do
prm - perms xs
spread [x] prm
or a list-comprehension
perms (x:xs) = [permutation | tailPerm - perms xs, permutation - spread [x] 
tailPerm]
 spread :: String - String - [String] -- interpolate first string at
 various positions of second string spread str1 str2 = _spread str1 str2
 (length str2)
 where
 _spread str1 str2 0= [str1 ++ str2]
 _spread str1 str2 n= [(take n str2) ++ str1 ++ (drop n str2)] ++ (_spread
 str1 str2 (n-1))

import Data.List
spread short long = zipWith (\a b - a ++ short ++ b) (inits long) (tails long)
If you only use spread for perms, you never interpolate anything but single 
element lists, so you might consider
spread' :: a - [a] - [[a]]
spread' x xs = zipWith (\a b - a ++ x:b) (inits xs) (tails xs)
But if you import Data.List, you could also say
perms = permutations
and be done with it :) (except if you 1. need the permutations in a particular 
order, which is different from the one Data.List.permutations generates, or 2. 
you need it to be as fast as possible - Data.List.permutations was written to 
also cope with infinite lists, so a few things that could speed up generation 
of permutations for short lists couldn't be used).
 f xs = map (spread xs)


 The number of outcomes seem to indicate that correctness of the algo ..
Apart from the case of empty input, it is correct.
 however, I'd be very obliged if I could get some feedback on the
 Haskellness etc of this ... also any performance pointers ...
Re performance:
I think the repeated (take k) and (drop k) in your spread are likely to be 
slower than using inits and tails, but it would need measuring the performance 
to be sure.
I don't see anything that would automatically give bad performance.
But there's the question of repeated elements.
perms ab
spills out 3628800 permutations, but there are only 252 distinct permutations, 
each of them appearing 120^2 = 14400 times.
If your input may contain repeated elements and you're
1. only interested in the distinct permutations (and 2.) or
2. don't care about the order in which the permutations are generated,
distinctPerms :: Ord a = [a] - [[a]]
distinctPerms = foldr inserts [[]] . group . sort
inserts :: [a] - [[a]] - [[a]]
inserts xs yss = yss = (mingle xs)
mingle :: [a] - [a] - [[a]]
mingle xs [] = [xs]
mingle [] ys = [ys]
mingle xxs@(x:xs) yys@(y:ys) 
= [x:zs | zs - mingle xs yys] ++ [y:zs | zs - mingle xxs ys]
generates the distinct permutations much faster if there are many repeated 
elements;
if you want each distinct permutation repeated the appropriate number of 
times, the modification is easy.


 Regards,
 Kashyap


  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] A question on DSL's

2010-01-04 Thread CK Kashyap
Hi,
I am not sure if I'm using DSL in the right context here but I am referring to 
those solutions that allow us to write code in Haskell and generate a target 
code source code of another language or even object code for that matter. I am 
aware of two ways of achieving this - 
1. Implement functions that emit the target code - that is, when the Haskell 
code is compiled and run, the target code is emitted
2. Modify the Haskell compiler's back end to emit the code - that is when the 
Haskell code is compiled the target code is emitted

I am not sure if there are more ways (hybrid perhaps) ... 

My question is,  when would I chose one approach over the other?

Regards,
Kashyap



  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A question on DSL's

2010-01-04 Thread CK Kashyap
Thanks Jasper ... 
Thanks John,
While most of the use case I had in mind seems to fit the EDSL description, I 
had some in the proper DSL category as well...
So, my prejudice had been towards option one - and I was unable to visualize a 
situation where option 1 would not work - or become too problematic or option 2 
becomes too simple.

I was just thinking of implementing an OS kernel (monolithic to start with) 
using Haskell - via option 1. Then again, if I understand right, House was done 
by modifying GHC ... So, I guess it'll help me if I can see some example 
situations where modifying GHC's back end would be a better/only option.

The main reason I am asking this is to make sure I don't miss out some obvious 
pitfall in my OS implementation via option 1.

Regards,
Kashyap


From: John Van Enk vane...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Mon, January 4, 2010 10:51:06 PM
Subject: Re: [Haskell-cafe] A question on DSL's


To start with, can you clarify that you are looking for an Embedded DSL 
(sometimes called Light Weight DSL)?


A _proper_ DSL has its own interpreter/compiler where an EDSL/LwDSL leverages 
the compiler of a host language (in this case, Haskell).


Assuming you're referring to an EDSL, I'll respond. :)

I don't think the second option is ever used. Modifying the compiler backend 
doesn't seem to make a lot of sense to me. I'm not aware of any circumstance 
where this has been done.


Your first option is closer. Generally, when emitting some sort of target code 
from a large EDSL, you'll have two stages. Your first takes the embedded 
syntax of your EDSL and converts it to an Abstract Syntax Tree. Your second 
stage accepts the AST as input and emits target code.


Take Tom Hawkins' Atom EDSL as an example. When we write Atom code, we're 
building up an AST. After the AST is built up, the compile function converts 
the AST to C code.


For smaller EDSLs, it's more than possible to have the functions themselves 
emit the code we're after (rather than relying on an AST and compile function).


Is this what you're looking for?


/jve


On Mon, Jan 4, 2010 at 12:14 PM, CK Kashyap ck_kash...@yahoo.com wrote:

Hi,
I am not sure if I'm using DSL in the right context here but I am referring 
to those solutions that allow us to write code in Haskell and generate a 
target code source code of another language or even object code for that 
matter. I am aware of two ways of achieving this -

1. Implement functions that emit the target code - that is, when the Haskell 
code is compiled and run, the target code is emitted
2. Modify the Haskell compiler's back end to emit the code - that is when 
the Haskell code is compiled the target code is emitted

I am not sure if there are more ways (hybrid perhaps) ...

My question is,  when would I chose one approach over the other?

Regards,
Kashyap





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Request to review my attempt at understanding Monads

2009-12-29 Thread CK Kashyap
Thanks Jason,


 
   You should make a `Functor' instance since monads are all
   functors (though the typeclass does not enforce this).
 
What are the benefits of making it an instance of Functor?


   You can use `guard' and `when' and other monadic operations.
   The `MonadPlus' instance gives you access to `msum'. It's not
   just about `do' notation :)
 


I'd appreciate it very much if you could give me some pointers on the usages of 
guard, when and msum.

Regards,
Kashyap


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Request to review my attempt at understanding Monads

2009-12-28 Thread CK Kashyap
Hi,
I've been reading the papers titled Comprehending Monads and Monadic Parser 
Combinator to understand Monads and I think I am beginning to
understand it. In my attempt to validate my understanding, I've written my 
version of List data structure with Monadic behaviour -
I'd appreciate answers to the following queries - 
1. Comments about the functions I've written
2. I've used the do notation at the bottom which is a result of my List being a 
Monad - are there any other benefits that comes in because of List being a 
Monad? What would MonadPlus provide me?
3. The comprehension syntax for Lists in Haskell - can that be used in anyway 
for other Monads?

Regards,
Kashyap

import Monad ( MonadPlus(..) )

data List a = Cons a (List a) | Empty
deriving Show

--myMap :: (t - a) - List t - List a
myMap :: (t - a) - List t - List a
myMap f Empty = Empty
myMap f (Cons a rest) = Cons (f a) (myMap f rest)


--myAppend :: List a - List a - List a
myAppend :: List a - List a - List a
myAppend Empty l = l
myAppend l Empty = l
myAppend (Cons a rest) l = Cons a (myAppend rest l)


--myConcat :: List (List a) - List a
myConcat :: List (List a) - List a
myConcat Empty= Empty
myConcat (Cons Empty rest)= myConcat rest
myConcat (Cons list rest)= myAppend list (myConcat rest)

instance Monad List where
return a = Cons a Empty
Empty = f = Empty
l = f = myConcat (myMap f l)

instance MonadPlus List where
p `mplus` q = myAppend p q
mzero= Empty

list2myList :: [a] - List a
list2myList [] = Empty
list2myList (x:xs) = Cons x (list2myList xs)

l1 =  list2myList [1..10]
l2 = do
x - l1
y - Cons (2*x) Empty
return y


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Generating AST using Parsec

2009-12-27 Thread CK Kashyap
Hi All,
I recently came across the paper titled Monadic Parser Combinators - After 
going through it a few times, I think I am beginning to understand monads.
However, the parser developed in the paper does not generate an AST - I feel, 
I'd grasp the whole thing a lot better if I could go over a sample that 
generates an AST from a simple expression (or even a standard language such as 
C or Java) ... Can someone please point me to a sample that generates AST - 
preferably with the simple parser combinator given in the paper.
Regards,
Kashyap


  

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DSL in Haskell

2009-11-16 Thread CK Kashyap
Thanks Don,

I read the PDF. I was not able to figure out how to get the BASIC module. 
Wanted to see a reference implementation.

The DSL I want to start with is a music generation DSL ... It should generate a 
wave file
with music data as input - for example the input could contain
C3 D3 E3 ... - should output a wave file with those notes ... some kind of 
mnemonics for tempo will also be there.
Later I'd like to incorporate parallel sequence generation - where I could get 
chord effect etc ...
I had done a rudimentary implementation in C a while back - 
http://kashyap-1978.tripod.com/Escapades/Goodies/Construct_WAV.html

I'd appreciate it very much if you could give me some pointers on getting 
started.


Regards,
Kashyap



From: Don Stewart d...@galois.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Mon, November 16, 2009 12:57:54 AM
Subject: Re: [Haskell-cafe] DSL in Haskell

ck_kashyap:
 Hi All,
 I was reading a Ruby book and in that it was mentioned that its capability to
 dynamically query and modify classes makes it suitable for implementing DSL's
 ... I am referring to Ruby's reflection and methods like method_missing 
 here.
 It can allow things like not having to define constants for all possible
 unicode code points etc...For example, first use of U0123 could bring such a
 constant definition into existence etc
 
 I see multiple search hits when I look for Haskell and DSL - can someone 
 please
 point me to a good primer or explain to me how equivalent of above mentioned
 features in Ruby can be done in Haskell ... or the Haskell alternative for it.

The Haskell equivalent would be overloading, primarily via type classes.

See Lennart Augusston's BASIC for an example of this in the extreme:


http://augustss.blogspot.com/2009/02/more-basic-not-that-anybody-should-care.html

That's BASIC syntax, in Haskell, relying on overloading numbers, strings
etc. And all statically typed.

For a survey of some of the more recent EDSLs in Haskell, see this brief
overview,

http://www.galois.com/~dons/papers/stewart-2009-edsls.pdf

-- Don



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] DSL in Haskell

2009-11-16 Thread CK Kashyap
Thank you very very much Daryoush ... I had not seen the book ... Looks pretty 
interesting, I saw it mentioning Midi though ...
Thank you Justin for the location of the BASIC module.
Regards,
Kashyap





From: Daryoush Mehrtash dmehrt...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: Don Stewart d...@galois.com; haskell-cafe@haskell.org
Sent: Mon, November 16, 2009 11:19:07 PM
Subject: Re: [Haskell-cafe] DSL in Haskell

Have you seen the Haskell School of Expression book by Paul Hudak?   

The book is available on line, Ch 9 and 10 talks about music.

http://plucky.cs.yale.edu/cs431/HaskoreSoeV-0.7.pdf

Daryoush




On Mon, Nov 16, 2009 at 3:16 AM, CK Kashyap ck_kash...@yahoo.com wrote:

Thanks Don,

I read the PDF. I was not able to figure out how to get the BASIC module. 
Wanted to see a reference implementation.

The DSL I want to start with is a music generation DSL ... It should generate 
a wave file
with music data as input - for example the input could contain
C3 D3 E3 ... - should output a wave file with those notes ... some kind of 
mnemonics for tempo will also be there.
Later I'd like to incorporate parallel sequence generation - where I could 
get chord effect etc ...
I had done a rudimentary implementation in C a while back - 
http://kashyap-1978.tripod.com/Escapades/Goodies/Construct_WAV.html

I'd appreciate
 it very much if you could give me some pointers on getting started.


Regards,
Kashyap



From: Don Stewart d...@galois.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Mon, November 16, 2009 12:57:54 AM
Subject: Re: [Haskell-cafe] DSL in Haskell


ck_kashyap:
 Hi All,
 I was reading a Ruby book and in that it was mentioned that its capability to
 dynamically query and modify classes makes it suitable for implementing DSL's
 ... I am referring to Ruby's reflection and methods like method_missing 
 here.
 It can allow things like not having to define constants for all possible
 unicode code points etc...For example, first use of U0123 could bring such a
 constant definition into existence etc
 
 I see multiple search hits when I look for Haskell and DSL - can someone 
 please
 point me to a good primer or explain to me how equivalent of above mentioned
 features in Ruby can be done in Haskell ... or the Haskell alternative for 
 it.

The Haskell equivalent would be overloading, primarily via type classes.

See Lennart Augusston's BASIC for an example of this in the extreme:


 http://augustss.blogspot.com/2009/02/more-basic-not-that-anybody-should-care.html

That's BASIC syntax, in Haskell, relying on overloading numbers, strings
etc. And all statically typed.

For a survey of some of the more recent EDSLs in Haskell, see this brief
overview,

http://www.galois.com/%7Edons/papers/stewart-2009-edsls.pdf

-- Don


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe




  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] DSL in Haskell

2009-11-15 Thread CK Kashyap
Hi All,
I was reading a Ruby book and in that it was mentioned that its capability to 
dynamically query and modify classes makes it suitable for implementing DSL's 
... I am referring to Ruby's reflection and methods like method_missing here.
It can allow things like not having to define constants for all possible 
unicode code points etc...For example, first use of U0123 could bring such a 
constant definition into existence etc

I see multiple search hits when I look for Haskell and DSL - can someone please 
point me to a good primer or explain to me how equivalent of above mentioned 
features in Ruby can be done in Haskell ... or the Haskell alternative for it.

Regards,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Right way to implement setPixel function

2009-08-21 Thread CK Kashyap
thank you very much Job.
Regards,
Kashyap

On Thu Aug 20th, 2009 1:13 PM EDT Job Vranish wrote:

Opps:
setPixel = State setPixel'

should be:
setPixel x y rgb = State $ setPixel' x y rgb

- Job

On Thu, Aug 20, 2009 at 1:05 PM, Job Vranish jvran...@gmail.com wrote:

 Your setPixel function is almost ready to work in a State monad
 If you modify your setPixel function slightly like so:

 setPixel' :: Int - Int - Color - B.ByteString - ((), B.ByteString)
 setPixel'  x y (r,g,b) image = ((), B.concat [beforePixel, pixel,
 afterPixel])

 and then wrap it in the State monad constructor:

 setPixel = State setPixel'

 then you can do

 drawPixels = do
   setPixel 5 10 (200, 0, 0)
   setPixel 20 1 (0, 200, 0)
   setPixel 90 2 (0, 0, 200)

 modifiedImage = execState drawPixels originalImage

 See! you were already using a monad and didn't even know it! :D

 Performance wise,  B.concat is O(n), which is very not good for your
 purpose. It copies the whole string and the optimizer won't be able to
 magically make it go away. For something that works in O(1), you will have
 to use something like STArrays instead of bytestrings.

 - Job



 On Thu, Aug 20, 2009 at 2:32 AM, CK Kashyap ck_kash...@yahoo.com wrote:

 Hi,
 I had posted a note on line drawing algo with Haskell some time back. Now,
 I am trying to write a PNM image.

 import qualified Data.ByteString as B

 width = 256
 height = 256
 bytesInImage = width * height * 3
 blankImage =  B.pack $ take bytesInImage (repeat 0)

 type Color = (Int,Int,Int)
 setPixel :: B.ByteString - Int - Int - Color - B.ByteString
 setPixel image x y (r,g,b) = B.concat [beforePixel, pixel, afterPixel]
 where
 beforePixel = B.take before image
 afterPixel = B.drop (before+3) image
 pixel=B.pack [(fromIntegral r),(fromIntegral
 g),(fromIntegral b)]
 -- number of bytes before the 3 bytes of
 -- the pixel at x y
 before = (y * width * 3) + (x * 3) - 3

 main = do
 putStrLn P6
 putStrLn ( (show width) ++   ++ (show height) )
 putStrLn 255
 -- Set a red pixel at 100 100
 B.putStr (setPixel blankImage 100 100 (255,0,0))


 Can I please have some review comments on the code above? Would recreating
 the entire ByteString for each setPixel be an overhead?
 Also, I am barely beginning to grasp the Monad conceptI was wondering
 if there could be a monadic style of implementation of this - that could
 potentially have a series of setPixels inside a do block?

 Regards,
 Kashyap


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe






  
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Right way to implement setPixel function

2009-08-20 Thread CK Kashyap
Hi,
I had posted a note on line drawing algo with Haskell some time back. Now, I am 
trying to write a PNM image.

import qualified Data.ByteString as B

width = 256
height = 256
bytesInImage = width * height * 3
blankImage =  B.pack $ take bytesInImage (repeat 0)

type Color = (Int,Int,Int)
setPixel :: B.ByteString - Int - Int - Color - B.ByteString
setPixel image x y (r,g,b) = B.concat [beforePixel, pixel, afterPixel]
where
beforePixel = B.take before image
afterPixel = B.drop (before+3) image
pixel=B.pack [(fromIntegral r),(fromIntegral g),(fromIntegral 
b)]
-- number of bytes before the 3 bytes of
-- the pixel at x y
before = (y * width * 3) + (x * 3) - 3

main = do
putStrLn P6
putStrLn ( (show width) ++   ++ (show height) )
putStrLn 255
-- Set a red pixel at 100 100
B.putStr (setPixel blankImage 100 100 (255,0,0)) 


Can I please have some review comments on the code above? Would recreating the 
entire ByteString for each setPixel be an overhead?
Also, I am barely beginning to grasp the Monad conceptI was wondering if 
there could be a monadic style of implementation of this - that could 
potentially have a series of setPixels inside a do block?

Regards,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: SQL Database in Haskell?

2009-08-05 Thread CK Kashyap
I'd be very interested to see a rdbms implementation in Haskell ... perhaps a 
port of sqlite

Regards,
Kashyap




From: Don Stewart d...@galois.com
To: Günther Schmidt gue.schm...@web.de
Cc: haskell-cafe@haskell.org
Sent: Thursday, August 6, 2009 6:07:48 AM
Subject: Re: [Haskell-cafe] Re: SQL Database in Haskell?

gue.schmidt:
 Hi,

 well I tried to do some stuff in memory, and the app ended up using a  
 couple of gigs. I not only have a very large amount of dynamic data, CSV  
 files, but also quite a large amount of static data, and wasted 3 months  
 trying to do this all in-memory. The problem was finally solved once I  
 used SQLite and SQL.

 The other day I had one last go at trying to compile the static data in a 
 literal list in my haskell code. That was 80.000 rows, it was just not  
 even possible

Don't compile in static data (or if you do, use -Onot, so that GHC won't
try to analyze it)!

Use some kind of binary on-disk storage.

 As far as I'm concerned this discussion is settled in favor of SQL once  
 and for all.

 The part I didn't like about SQLite is encryption, you need to buy that  
 extra and then hope that it fits the current version and future ones too. 
 HSQLDB or Derby for Java give you this option and also with in-memory  
 database, alas they are for Java only.

You might also want to look at the HAppS disk-backed persistence model,

http://hackage.haskell.org/package/HAppS-State

Or the holumbus distributed storage layer,

http://hackage.haskell.org/package/Holumbus-Storage
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Writing a pnm file

2009-08-02 Thread CK Kashyap
Hi,
Now that I've understood how to generate raster points of a line in Haskell - 
the next thing I want to do is generate a pnm file with it. I've done it in 
perl as of now. In perl, I can have a scalar variable $x contain a string of 
256*256*3 bytes (for 24-bit 256x256 image) and set pixels using substr on LHS. 
I was wondering how I could do something similar in Haskell?

sub setPixel{
my($x,$y,$red,$green,$blue)=...@_;
my$pixel=pack CCC,$red,$green,$blue;
my$offset=$WIDTH*$y*3 + $x*3;
substr($image,$offset,3) = $pixel;
}

Regards,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Writing a pnm file

2009-08-02 Thread CK Kashyap
Thanks Sebastian,
ppm module is indeed very useful. So, I guess my question then just boils down 
to, how can I write a function to mimic the setPixel function -

Basically, a blank white image would look like this  (as per ppm module)
[ 
   [ (255, 255, 255)  , (255, 255, 255)  , (255, 255, 255) ] ,  -- 3 columns of 
row 1
   [ (255, 255, 255) , (255, 255, 255) , (255, 255, 255)  ]--- 3 columns of 
row 2
]

setPixel x y r g b when called like this - setPixel 0,0,255,0,0

[ 
   [ (255, 0, 0)  , (255, 255, 255)  , (255, 255, 255) ] ,  -- 3 columns of row 
1
   [ (255, 255, 255) , (255, 255, 255) , (255, 255, 255)  ]--- 3 columns of 
row 2
]

What would be a good way to implement such a function?

Regards,
Kashyap





From: Sebastian Sylvan sebastian.syl...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Sunday, August 2, 2009 9:30:08 PM
Subject: Re: [Haskell-cafe] Writing a pnm file




On Sun, Aug 2, 2009 at 4:00 PM, CK Kashyap ck_kash...@yahoo.com wrote:

Hi,
Now that I've understood how to generate raster points of a line in Haskell - 
the next thing I want to do is generate a pnm file with it. I've done it in 
perl as of now. In perl, I can have a scalar variable $x contain a string of 
256*256*3 bytes (for 24-bit 256x256 image) and set pixels using substr on LHS. 
I was wondering how I could do something similar in Haskell?


sub setPixel{
my($x,$y,$red,$green,$blue)=...@_;
my$pixel=pack CCC,$red,$green,$blue;
my$offset=$WIDTH*$y*3 + $x*3;
substr($image,$offset,3) = $pixel;
}

There's a library on hackage which does this
http://hackage.haskell.org/package/ppm

You can install this by doing
cabal install ppm

Here's an example usage (this uses the binary version of ppm, the docs for ppm 
has an example for the ASCII version):

writePPM fname img = withBinaryFile fname WriteMode (\h - hPutStr h (ppm_p6 
img) ) 

If you're looking for the learning experience, you could always read the source 
for the library (which is pretty tiny).
-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-31 Thread CK Kashyap
I personally find 
map maySwitch (unfoldr go (x1,y1,0)) and map maySwitch $ unfoldr go (x1,y1,0) 
more intuitive.

I can read it as map the maySwitch function over the list generated from the 
unfolding.

Is there any difference in the evaluation steps between the composition version 
and the non-composition version?

Regards,
Kashyap





From: david48 dav.vire+hask...@gmail.com
To: Ryan Ingram ryani.s...@gmail.com
Cc: Johan Tibell johan.tib...@gmail.com; haskell-cafe@haskell.org; CK Kashyap 
ck_kash...@yahoo.com
Sent: Friday, July 31, 2009 11:56:17 AM
Subject: Re: [Haskell-cafe] Need feedback on my Haskell code

On Fri, Jul 31, 2009 at 5:53 AM, Ryan Ingramryani.s...@gmail.com wrote:

 Read ($) as a parenthesis that extends as far to the right as
 possible; so you can write, for example:

That doesn't always work, for example :

map (+2) . map (*1) $ [1,2,3]
= [4,6,8]

Now replacing the $ by a parenthesis that extends as far to the right
as possible :

map (+2) . map (*1) ( [1,2,3] )

interactive:1:11:
Couldn't match expected type `a - [a1]'
   against inferred type `[a2]'
In the second argument of `(.)', namely `map (* 2) ([1, 2, 3])'
In the expression: map (+ 2) . map (* 2) ([1, 2, 3])
In the definition of `it': it = map (+ 2) . map (* 2) ([1, 2, 3])



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-30 Thread CK Kashyap


Thanks David 
Regards,
Kashyap



From: david48 dav.vire+hask...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: Chaddaï Fouché chaddai.fou...@gmail.com; haskell-cafe@haskell.org
Sent: Wednesday, July 29, 2009 4:43:52 PM
Subject: Re: [Haskell-cafe] Need feedback on my Haskell code

On Wed, Jul 29, 2009 at 12:04 PM, CK Kashyapck_kash...@yahoo.com wrote:
 map maySwitch . unfoldr go $ (x1,y1,0)

I'm not an expert and I might say things the wrong way or without the
required rigor, so with this disclaimer here's my explanation :

go calculates a step of the line, given the current coordinates and
the error value
it returns nothing if the line is done.

unfoldr go calculates a list of lines coordinates, keeping calling go,
and stopping when go returns nothing.

maySwitch takes a coordinate, and switches the x and y values
depending on the axis we're following
map maySwitch does the same for the entire list of coordinates.

when you compose the two,
map maySwitch . unfoldr go  is then a function that takes initial
coordinates, makes a list of coordinates and may switch the x's and
y's depending on the axis we're following.


Now (.) takes two functions, namely map maySwitch and unfoldr go. If
you don't write the $, what you actually mean is
(map maySwitch) . ( unfoldr go (x1,y1,0))

this ( unfoldr go (x1,y1,0)) is not of the right type for (.) : it
should take a parameter and return a value, but here it just returns a
value.

so you have to find a way to give (x1,y1,0) to the whole composed
function  map maySwitch . unfoldr go.

the obvious way to do it is by writing:

( map maySwitch . unfoldr go ) (x1,y1,0 )

the $ is just a more readable way to write it : since $ binds with
less priority, in
map maySwitch . unfoldr go $ (x1,y1,0)
what's on the right of $ will be applied to what's on the left

David.



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-29 Thread CK Kashyap
It worked like a charm!!! I'd need more time to get my head around unfoldr
I'd appreciate it very much if you could explain this line  map maySwitch . 
unfoldr go $ (x1,y1,0)
I did not fully understand the $ in that line - I tried putting parenthesis 
in various places to get rid of $ but did not seem to work.

Regards,
Kashyap





From: Chaddaï Fouché chaddai.fou...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Tuesday, July 28, 2009 7:10:38 PM
Subject: Re: [Haskell-cafe] Need feedback on my Haskell code

On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyapck_kash...@yahoo.com wrote:
 Hi Everyone,
 I managed to write up the line drawing function using the following links -
 http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html
 http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell


I tried to simplify your function a little bit :

line :: Point - Point - [Point]
line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0)
  where
steep = abs (yb - ya)  abs (xb - xa)
maySwitch = if steep then (\(x,y) - (y,x)) else id
[(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb]
deltax = x2 - x1
deltay = abs (y2 - y1)
ystep = if y1  y2 then 1 else -1
go (xTemp, yTemp, error)
| xTemp  x2 = Nothing
| otherwise  = Just ((xTemp, yTemp), (xTemp + 1, newY, newError))
where
  tempError = error + deltay
  (newY, newError) = if (2*tempError) = deltax
 then (yTemp+ystep,tempError-deltax)
 else (yTemp,tempError)

I think it will be a bit better, tell me what you think ?

-- 
Jedaï



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Need feedback on my Haskell code

2009-07-28 Thread CK Kashyap
Hi Everyone,
I managed to write up the line drawing function using the following links - 
http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html
http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell

line :: Point - Point - [Point]
line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0
  where 
isSteep = abs (yb - ya)  abs (xb - xa)
(xa',ya',xb',yb') = if isSteep
  then (ya,xa,yb,xb)
  else (xa,ya,xb,yb)
(x1,y1,x2,y2) = if xa'  xb'
  then (xb',yb',xa',ya')
  else (xa',ya',xb',yb')
deltax = x2 - x1
deltay = abs (y2 - y1)
ystep = if y1  y2 then 1 else -1
  

line' :: Point - Point - Integer - Integer - Integer - Bool - Integer - 
[Point]
line' (x1,y1) (x2,y2) deltax deltay ystep isSteep error =
  if x1 == x2
  then if isSteep then [(y1,x1)] else [(x1,y1)]
  else
if isSteep
  then [(y1,x1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep 
newError 
  else [(x1,y1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep isSteep 
newError
where
  newX = x1 + 1
  tempError = error + deltay
  (newY, newError) = if (2*tempError) = deltax then 
(y1+ystep,tempError-deltax) else (y1,tempError)


Can someone please provide feedback on this? In terms of, how do I get more 
Haskell'ism into it.

Regards,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-28 Thread CK Kashyap
Thanks Neil,
That helped. Now the code looks better - I still feel a little bad about the 
way I repeat calls to line' though - I was thinking of using a partially 
applied function with (newX,newY) as the last parameter - but that'll make the 
code less readable.

line :: Point - Point - [Point]
line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0
  where
isSteep = abs (yb - ya)  abs (xb - xa)
(xa',ya',xb',yb') = if isSteep
  then (ya,xa,yb,xb)
  else (xa,ya,xb,yb)
(x1,y1,x2,y2) = if xa'  xb'
  then (xb',yb',xa',ya')
  else (xa',ya',xb',yb')
deltax = x2 - x1
deltay = abs (y2 - y1)
ystep = if y1  y2 then 1 else -1


line' (x1, y1) (x2, y2) deltax deltay ystep isSteep error
  | x1 == x2 = if isSteep then [(y1, x1)] else [(x1, y1)]
  | isSteep =
(y1, x1) :
  line' (newX, newY) (x2, y2) deltax deltay ystep isSteep newError
  | otherwise =
(x1, y1) :
  line' (newX, newY) (x2, y2) deltax deltay ystep isSteep newError
  where newX = x1 + 1
tempError = error + deltay
(newY, newError)
  = if (2 * tempError) = deltax then
  (y1 + ystep, tempError - deltax) else (y1, tempError)

Regards,
Kashyap





From: Neil Mitchell ndmitch...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Tuesday, July 28, 2009 6:44:58 PM
Subject: Re: [Haskell-cafe] Need feedback on my Haskell code

Hi Kashyap,

My first suggestion would be to run HLint over the code
(http://community.haskell.org/~ndm/hlint) - that will spot a few easy
simplifications.

Thanks

Neil

On Tue, Jul 28, 2009 at 2:04 PM, CK Kashyapck_kash...@yahoo.com wrote:
 Hi Everyone,
 I managed to write up the line drawing function using the following links -
 http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html
 http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell

 line :: Point - Point - [Point]
 line (xa,ya) (xb,yb) = line' (x1,y1) (x2,y2) deltax deltay ystep isSteep 0
   where
 isSteep = abs (yb - ya)  abs (xb - xa)
 (xa',ya',xb',yb') = if isSteep
   then (ya,xa,yb,xb)
   else (xa,ya,xb,yb)
 (x1,y1,x2,y2) = if xa'  xb'
   then (xb',yb',xa',ya')
   else (xa',ya',xb',yb')
 deltax = x2 - x1
 deltay = abs (y2 - y1)
 ystep = if y1  y2 then 1 else -1


 line' :: Point - Point - Integer - Integer - Integer - Bool - Integer
 - [Point]
 line' (x1,y1) (x2,y2) deltax deltay ystep isSteep error =
   if x1 == x2
   then if isSteep then [(y1,x1)] else [(x1,y1)]
   else
 if isSteep
   then [(y1,x1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep
 isSteep newError
   else [(x1,y1)] ++ line' (newX,newY) (x2,y2) deltax deltay ystep
 isSteep newError
 where
   newX = x1 + 1
   tempError = error + deltay
   (newY, newError) = if (2*tempError) = deltax then
 (y1+ystep,tempError-deltax) else (y1,tempError)


 Can someone please provide feedback on this? In terms of, how do I get more
 Haskell'ism into it.

 Regards,
 Kashyap


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Need feedback on my Haskell code

2009-07-28 Thread CK Kashyap
Thank you very much Jedai ... this looks much more concise and does not contain 
the repetitions that I had. I'd need to go over it more to understand it better.
I'll ping you if I have any questions about this.

Regards,
Kashyap





From: Chaddaï Fouché chaddai.fou...@gmail.com
To: CK Kashyap ck_kash...@yahoo.com
Cc: haskell-cafe@haskell.org
Sent: Tuesday, July 28, 2009 7:10:38 PM
Subject: Re: [Haskell-cafe] Need feedback on my Haskell code

On Tue, Jul 28, 2009 at 3:04 PM, CK Kashyapck_kash...@yahoo.com wrote:
 Hi Everyone,
 I managed to write up the line drawing function using the following links -
 http://www.cs.helsinki.fi/group/goa/mallinnus/lines/bresenh.html
 http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell


I tried to simplify your function a little bit :

line :: Point - Point - [Point]
line pa@(xa,ya) pb@(xb,yb) = map maySwitch . unfoldr go $ (x1,y1,0)
  where
steep = abs (yb - ya)  abs (xb - xa)
maySwitch = if steep then (\(x,y) - (y,x)) else id
[(x1,y1),(x2,y2)] = sort [maySwitch pa, maySwitch pb]
deltax = x2 - x1
deltay = abs (y2 - y1)
ystep = if y1  y2 then 1 else -1
go (xTemp, yTemp, error)
| xTemp  x2 = Nothing
| otherwise  = Just ((xTemp, yTemp), (xTemp + 1, newY, newError))
where
  tempError = error + deltay
  (newY, newError) = if (2*tempError) = deltax
 then (yTemp+ystep,tempError-deltax)
 else (yTemp,tempError)

I think it will be a bit better, tell me what you think ?

-- 
Jedaï



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Line drawing algorithm

2009-07-17 Thread CK Kashyap
Hi All,

I am working on a diagraming utility in Haskell. I started with line drawing.
I am doing the basic stuff using the y = mx + c formula to draw a line between 
(x1,y1) and (x2,y2)

Here's what I need to do - 
if dx  dy where dx = (x2 - x1) and dy = (y2 - y1) then I need to vary x 
between x1 and x2 and find the various y's
however if dy  dx then I need to vary y beteen y1 and y2 and get various x's 

In the code below, I've only taken care of the situation where dx  dy - I was 
thinking if there was a better way to
do it that takes care of the other condition as well without repeating the code.


type Point = (Integer,Integer)

line :: Point - Point - [Point] -- get all the points in the line
line p1@(x1,y1) p2@(x2,y2) = line' start end start slope
  where
(start,end) = reorderPoints p1 p2
slope = ((fromIntegral (y2-y1)) / (fromIntegral (x2-x1)))
reorderPoints (px1,py1) (px2,py2)
| px1  px2 = (p1,p2)
| otherwise = (p2,p1)

line' :: Point - Point - Point - Double - [Point]
line' start@(x1,y1) end@(x2,y2) point@(x3,y3) slope
  | x3 == x2 = [end]
  | otherwise = [point] ++ line' start end (newX,newY) slope
  where
newX = x3 + 1
newY = y1 + round (slope * (fromIntegral (newX - x1)))


hello = line (1,1) (10,10)


Regards,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Line drawing algorithm

2009-07-17 Thread CK Kashyap
Thanks Neil ... 


 Are you doing this to learn Haskell, learn about drawing lines, or to just 
 get it implemented?  If either of the latter two, when drawing a straight 
 line you shouldn't need to do floating point operations such as this:

Actually, my reasons are first and third.

 newY = y1 + round (slope * (fromIntegral (newX - x1)))

 http://rosettacode.org/wiki/Bresenham%27s_line_algorithm#Haskell

Thanks for the link.

 As to how to cope with the dy  dx case in your code given the dx  dy case, 
 you could just swap the x and y coords at the start, then swap back the x and 
 y coords of all the output points afterwards.  Odd, but effective :-)
Slope would differ right for both case right?

Regards,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Oops in Haskell

2009-07-17 Thread CK Kashyap
Hi,
Can someone please send me a working example based on the contents posted in 
the URL below?
http://yi-editor.blogspot.com/2008/12/prototypes-encoding-oo-style.html
Thanks,
Kashyap



  ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe