Re: [Haskell-cafe] Infinite loop?

2006-02-19 Thread Barbier de Reuille Pierre
On Fri, 17 Feb 2006 17:26:08 +
Jon Fairbairn [EMAIL PROTECTED] wrote:

 On 2006-02-17 at 09:22PST Jared Updike wrote:
  Yep. change one line to:
  
 entry - if isdir  name /= .  name /= ..
  
  and it does in fact work.
 
 Only if no-one has been tricky with symbolic links.
 

And how can you, in Haskell, detect symbolic links ?

-- 
You have an unusual understanding of the problems of human
relationships.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: libreadline dependency

2006-02-19 Thread Jim Apple

J. Scott Thayer, M.D. wrote:
Haskell wants 
libreadline 4 while I have libreadline 5. 


I'm not sure about SUSE, but Fedora has libreadline_compat packages.

HTH,
Jim

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


Re: [Haskell-cafe] classes inheritance seems not to work.

2006-02-19 Thread Sebastian Sylvan
On 2/18/06, asker [EMAIL PROTECTED] wrote:

 Hi,

 I'm trying to make three haskell classes and an instance this way:
 --
 class (Eq a) = Graph a where
  vert :: [a]
  ady :: a - [a]

 class (Graph a) = Paths a where
  gps :: a - a - [[a]]

 class (Paths a) = Minimum a where
  mgps :: a - a - [a]

 instance Minimum Char where
  vert = ['a' .. 'f'] -- This is the line of the error message.
  ady 'a' = ['b', 'c']
  ady 'b' = ['d', 'c', 'e']
  ady 'd' = ['f']
  gps = bepgr -- bepgr is defined and implemented in other code's part
  mgps = head gps
 --




 When I try to run this I get: ERROR: filepath:line -No member vert in class
 Minimum I don't know why does this happen, am I doing something wrong?


The class Minimum doesn't have a member 'vert', Graph does, though.

You need to instantiate your data type in all three classes
separately. So three separate instance declarations, one for each
class.


--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Infinite loop?

2006-02-19 Thread Donn Cave
Quoth Barbier de Reuille Pierre [EMAIL PROTECTED]:
| On Fri, 17 Feb 2006 17:26:08 +
| Jon Fairbairn [EMAIL PROTECTED] wrote:
|
|  On 2006-02-17 at 09:22PST Jared Updike wrote:
|   Yep. change one line to:
|   
|  entry - if isdir  name /= .  name /= ..
|   
|   and it does in fact work.
|  
|  Only if no-one has been tricky with symbolic links.
|  
|
| And how can you, in Haskell, detect symbolic links ?

I refer you to the documentation in System.Posix.Files, especially
getFileStatus :: FilePath - IO FileStatus, and
isSymbolicLink :: FileStatus - Bool.  I don't think I've used this
function, but it looks promising.

Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Infinite loop?

2006-02-19 Thread Dmitry V'yal
Barbier de Reuille Pierre wrote:
 And how can you, in Haskell, detect symbolic links ?
 
One can use System.Posix.Files.isSymbolicLink function for that purpose.

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


Re: [Haskell-cafe] Infinite loop?

2006-02-19 Thread Mark T.B. Carroll
Barbier de Reuille Pierre [EMAIL PROTECTED] writes:
(snip)
 And how can you, in Haskell, detect symbolic links ?

I use System.Posix.Files.
getSymbolicLinkStatus is like lstat(2) under Unix.
It returns a value to which you can apply the
isSymbolicLink predicate.

Of course, you can't be sure the file won't change in between you
checking and you acting on that result.

-- Mark

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


Re: [Haskell-cafe] GADTs and bar :: Foo t1 - Foo t2

2006-02-19 Thread Daniel McAllansmith
My thanks for the responses received off-list.

Dimitrios pointed out that a 'successor' class solution would require the 
typechecking to depend somehow on whether the lists were empty or not.
Probably a clue that I was on the wrong track.

Both Cale and Dimitrios suggested better solutions involving different data 
types:

data FooA = A
data FooB = B [FooA]
data FooC = C [FooB]
data Foo = FA FooA | FB FooB | FC FooC

or

data Node a = N [a] deriving Show
data Tree a = Zero a | Succ (Tree (Node a)) deriving Show

or

data EXFoo where
  EXFoo :: Foo a - EXFoo


Embarrassingly simple! :)

Thanks
Daniel


On Friday 17 February 2006 19:18, Daniel McAllansmith wrote:
 Hello,

 I have a recursive type

  data Foo = A | B [Foo] | C [Foo]

 that I would like to restrict so that a C can only contain Bs, and a B can
 only contain As.
 If I use a GADT as follows the bar function, understandably, will not type
 check.

  data AType
  data BType
  data CType
 
  data Foo a where
  A :: Foo AType
  B :: [Foo AType] - Foo BType
  C :: [Foo BType] - Foo CType
 
  --get the successor of the Foo
  bar c@(C []   ) = c
  bar   (C (b:_)) = b
  bar b@(B []   ) = b
  bar   (B (a:_)) = a
  bar [EMAIL PROTECTED] = a

 How do I achieve this restriction?  Do I need to have some sort of
 successor class with dependent types?

 Ta
 Daniel
 ___
 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] Shapes Compiling Error

2006-02-19 Thread Chatzianastassiou Achilleas

Hi everybody,

I have written some code for several shapes, and i get a compiling error:

 parse error on input `:'

though I can't find where the error is...

data Shape = Ellipse Radius Radius
| Polygon [Vertex]

deriving Show

type Radius = Float
type Vertex = (Float, Float)


area :: Shape - Float
area (Rectangle s1 s2) = s1 * s2
area (RtTriangle s1 s1) = s1 *s2 /2
area (Ellipse r1 r2) = pi * r1 * r2
area (Polygon(v1:v2:v3:vs))
= triArea v1 v2 v3 + area(Polygon(v1:v3:vs))
area(Polygon _ )
= 0
area (Polygon(v1:vs')) = polyArea vs
where polyArea :: [Vertex] - Float
  polyArea(v2:v3:vs')   = triArea v1 v2 v3
+ 
polyArea(v3:vs')
  polyArea _= 0

triArea :: Vertex - Vertex - Vertex - Float
triArea v1 v2 v3 =  let a = distBeetween v1 v2
b = distBeetween v2 v3
c = distBeetween v3 v1
s = 0.5 * (a + b + c)
in sqrt (s * (s - a) * (s - b) * (s - 
c))

distBeetween :: Vertex - Vertex - Float
distBeetween (x1, y1) (x2, y2)
= sqrt ((x1 - x2) ^ 2 + (y1 - y2) ^ 2)



Any suggestions?

Thanks in advance,

Skag55

_
On the road to retirement? Check out MSN Life Events for advice on how to 
get there! http://lifeevents.msn.com/category.aspx?cid=Retirement


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


Re: [Haskell-cafe] Shapes Compiling Error

2006-02-19 Thread Daniel Fischer
Hi,
Am Sonntag, 19. Februar 2006 22:57 schrieb Chatzianastassiou Achilleas:
 Hi everybody,

 I have written some code for several shapes, and i get a compiling error:

   parse error on input `:'

 though I can't find where the error is...
[snip code]

ever heard of the layout-rule?
You must indent the cases for polyArea to exactly the same level as the 
type-declaration, and all declarations in the let-binding to the same level.
Once the indentation is corrected, you get the real error messages -- those 
you should understand easily.

Cheers,
Daniel
-- 

In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt.
-- Blair P. Houghton

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


Re: [Haskell-cafe] Shapes Compiling Error

2006-02-19 Thread Cale Gibbard
Watch how deeply things are indented. The definitions for polyArea
should be indented to the same level as its type signature. Currently,
they're indented a little more, so the first line of polyArea's
definition is being treated as part of the type signature, which is
why you're getting the error. GHC/GHCi/hugs should be telling you also
what line the error happens on, which should be a good clue here :)

 - Cale

On 19/02/06, Chatzianastassiou Achilleas [EMAIL PROTECTED] wrote:
 Hi everybody,

 I have written some code for several shapes, and i get a compiling error:

   parse error on input `:'

 though I can't find where the error is...

 data Shape = Ellipse Radius Radius
 | Polygon [Vertex]

 deriving Show

 type Radius = Float
 type Vertex = (Float, Float)


 area :: Shape - Float
 area (Rectangle s1 s2) = s1 * s2
 area (RtTriangle s1 s1) = s1 *s2 /2
 area (Ellipse r1 r2) = pi * r1 * r2
 area (Polygon(v1:v2:v3:vs))
 = triArea v1 v2 v3 + area(Polygon(v1:v3:vs))
 area(Polygon _ )
 = 0
 area (Polygon(v1:vs')) = polyArea vs
 where polyArea :: [Vertex] - Float
   polyArea(v2:v3:vs')   = triArea v1 v2 v3
 + 
 polyArea(v3:vs')
   polyArea _= 0

 triArea :: Vertex - Vertex - Vertex - Float
 triArea v1 v2 v3 =  let a = distBeetween v1 v2
 b = distBeetween v2 v3
 c = distBeetween v3 v1
 s = 0.5 * (a + b + c)
 in sqrt (s * (s - a) * (s - b) * (s - 
 c))

 distBeetween :: Vertex - Vertex - Float
 distBeetween (x1, y1) (x2, y2)
 = sqrt ((x1 - x2) ^ 2 + (y1 - y2) ^ 2)



 Any suggestions?

 Thanks in advance,

 Skag55

 _
 On the road to retirement? Check out MSN Life Events for advice on how to
 get there! http://lifeevents.msn.com/category.aspx?cid=Retirement

 ___
 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] Shapes Compiling Error

2006-02-19 Thread Chatzianastassiou Achilleas

Thanks everybody,

I think it was the layout thing that I misstyped plus the
area (RtTriangle s1 s1) = s1 *s2 /2

(silly me!)

Skag55

_
Don’t just search. Find. Check out the new MSN Search! 
http://search.msn.click-url.com/go/onm00200636ave/direct/01/


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


Re: [Haskell-cafe] Re: Unexpected results with simple IO

2006-02-19 Thread Emil Axelsson

What version of GHC are you using?
Your code works for me in rxvt in Cygwin, with GHC 6.4.1. But I remember having 
that same problem earlier (in some earlier GHC version, so it may be fixed by now).


The solution was to run hFlush after each putStr, like so:

  import System.IO (hFlush, stdout)

  do putStr ...
 hHlush stdout
 ...

If I remember correctly, the problem only occurred in GHCi and Hugs -- not when 
compiling the code.


/ Emil



Maurício skrev:
  You're right... I was running the example in rxvt, in cygwin. Now I 
tried in Windows command shell and it works.


  Thanks,
  Maurício

Cale Gibbard wrote:

That doesn't happen for me at all, it works just fine. Maybe it's
something wrong with your terminal? You could possibly try playing
with the buffering settings on stdout, using hSetBuffering in
System.IO.

 - Cale

On 17/02/06, Maurício [EMAIL PROTECTED] wrote:


  Dear Haskell users,

  I have a problem using IO. The small test program below asks the user
to guess from a list of random numbers between 1 and 10. Everything
works well excepts for one problem: all the messages (Guess a
number..., Right... and Wrong...) are printed after the program
finishes, i.e., I have to use it blind. I'm afraid I misunderstand
something important about lazyness or monads... What am I doing wrong?

  Thanks,
  Maurício

module Main where
import Random

main = do
   r_gen - getStdGen --random generator
   let r_list = (randomRs (1,10) r_gen) --random list
   guess_loop (r_list)

guess_loop (r:r_others) = do
   putStrLn Guess a number between 1 and 10:
   n - readLn
   if n==r
  then do
 putStrLn Right! :)
 return ()
  else do
 putStrLn Wrong... :(
 guess_loop r_others

___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe