[Haskell-cafe] Parse error

2005-03-17 Thread Dmitri Pissarenko
Hello!

In the attachment you will find a file, in which I try to access Java from
Haskell using the Java bridge for functional languages.

For details see

http://sourceforge.net/projects/jvm-bridge/

and

http://dapissarenko.com/resources/2005_02_17_eigenvaluesJava/2005_02_17_eigenva
luesJava.pdf

When I try to compile the attached file using

ghc +RTS -c -RTS -package javavm  -c EigenvalueCalculatorHaskell.hs -o
EigenvalueCalculatorHaskell.o

I get the error

EigenvalueCalculatorHaskell.hs:28: parse error on input `putStrLn'

Unfortunately, I have not the slightest idea about how to fix/isolate it (I
already commented out almost the whole code).

Please tell me what I could try to correct the error. I appreciate ANY hint.

Many thanks in advance


Dmitri Pissarenko

PS: The source code of the files related to EigenvalueCalculatorHaskell.hs is
located at

http://dapissarenko.com/resources/2005_02_17_eigenvaluesJava/2005_02_17_lik.zip

--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
module EigenvalueCalculatorHaskell where
{
import Class_MathLibEigenvalueCalculator;
import EigenvalueCalculatorHaskell_JVM;
	import JVMBridge;
import IO;

calculateEigenvalues :: Array (Int, Int) Double -> [Double]
calculateEigenvalues matrix = (do
		{
calculateEigenvalues_JMathLibEigenvalueCalculator_ArrayArrayJdouble matrix
		} :: JVM ());

-- calculateEigenvalues matrix = (do
		-- {
-- calculateEigenvalues_JMathLibEigenvalueCalculator_ArrayArrayJdouble matrix
		-- } :: JVM ());

	main :: IO ();
	main = runWithClasspath ["./"](do
	{
let matrix1 = (array ((1,1),(3,3)) [((1,1), 0.0), ((1,2), 0.0), ((1,3),-2.0), ((2,1), 0.0), ((2,2), 7.0), ((2,3), 0.0), ((3,1), 0), ((3,2), 0), ((3,3), -3)]);
--let eigenVal = calculateEigenvalues_JMathLibEigenvalueCalculator_ArrayArrayJdouble (matrix1);
-- eigenvalues <- (do {calculateEigenvalues_JMathLibEigenvalueCalculator_ArrayArrayJdouble matrix1} :: JVM ());
--eigenvalues <- (calculateEigenvalues_JMathLibEigenvalueCalculator_ArrayArrayJdouble matrix1);
-- putStrLn "Eigenvalues of matrix1 (start)";
-- putStrLn (show eigenvalues);
putStrLn "Eigenvalues of matrix1 (end)";
-- callIO (putStrLn ("end"));

{- let matrix2 = array ((1,1),(3,3)) [((1,1), 1.0), ((1,2), 0.0), ((1,3), 2.0), ((2,1), 0.0), ((2,2), 5.0), ((2,3), 0.0), ((3,1), 3), ((3,2), 0), ((3,3), 2)];
eigenvalues <- calculateEigenvalues matrix2;
putStrLn "Eigenvalues of matrix2 (start)";
putStrLn (show eigenvalues);
putStrLn "Eigenvalues of matrix2 (end)";

let matrix3 = (array ((1,1),(2,2)) [((1,1), 3.0),
((1,2), 0.0), ((2,1), 4.0), ((2,2), 5.0)]);
eigenvalues <- calculateEigenvalues matrix3;
putStrLn "Eigenvalues of matrix3 (start)";
putStrLn (show eigenvalues);
putStrLn "Eigenvalues of matrix3 (end)";

let matrix4 = (array ((1,1),(2,2)) [((1,1), -1.0),
((1,2), 3.0), ((2,1), -2.0), ((2,2), 4.0)]);
eigenvalues <- calculateEigenvalues matrix4;
putStrLn "Eigenvalues of matrix4 (start)";
putStrLn (show eigenvalues);
putStrLn "Eigenvalues of matrix4 (end)";

let matrix5 = (array ((1,1),(2,2)) [((1,1), 0.0),
((1,2), -2.0), ((2,1), 1.0), ((2,2), -3.0)]);
eigenvalues <- calculateEigenvalues matrix5;
putStrLn "Eigenvalues of matrix5 (start)";
putStrLn (show eigenvalues);
putStrLn "Eigenvalues of matrix5 (end)"; -}
	} :: JVM ());

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


[Haskell-cafe] Parse error

2010-01-17 Thread Andrew Coppin
Is there a specific reason why GHC consistently refuses to accept the 
following perfectly reasonable code snippet?


main = do
 putStrLn "Line 1"
 putStrLn "Line 2"

 let xs = do
   x <- [1..10]
   y <- [1..10]
   return (x+y)

 print xs

No matter which way I rearrange this, it *insists* that there's a parse 
error. This is very frustrating, given that it's utterly clear what I 
want...


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


Re: [Haskell-cafe] Parse error

2005-03-17 Thread Arthur Baars
You need { } around the declaration of matrix1. Otherwise the semicolon  
at the end of its definition is considered to be part of the 'let':

let { matrix1 = (array ((1,1),(3,3)) [((1,1), 0.0), ((1,2), 0.0),  
((1,3),-2.0), ((2,1), 0.0), ((2,2), 7.0),  ((2,3), 0.0), ((3,1), 0),  
((3,2), 0), ((3,3), -3)])} ;

The layout rule will otherwise add { } as follows:
do { let x = 10 ;
 putStr "hello" ;
   }
-->
do { let { x = 10 ;  }
 putStr "hello" ;
   }
which is wrong, because there is no semicolon separating the  
'let'-declaration from the 'putStr' expression.

A solution is to use layout instead of { ; } or write semicolons in  
front of declarations:

do { let x = 10
   ; putStr "hello"
   }
This translates into:
do { let { x = 10 }
   ; putStr "hello"
   }
The semicolon is not part of the 'let' declaration, because it is  
indented less than 'x' .

For more information, see:
http://haskell.org/onlinereport/syntax-iso.html#layout
Hope this helps,
Arthur

On 17-mrt-05, at 20:42, Dmitri Pissarenko wrote:
Hello!
In the attachment you will find a file, in which I try to access Java  
from
Haskell using the Java bridge for functional languages.

For details see
http://sourceforge.net/projects/jvm-bridge/
and
http://dapissarenko.com/resources/2005_02_17_eigenvaluesJava/ 
2005_02_17_eigenva
luesJava.pdf

When I try to compile the attached file using
ghc +RTS -c -RTS -package javavm  -c EigenvalueCalculatorHaskell.hs -o
EigenvalueCalculatorHaskell.o
I get the error
EigenvalueCalculatorHaskell.hs:28: parse error on input `putStrLn'
Unfortunately, I have not the slightest idea about how to fix/isolate  
it (I
already commented out almost the whole code).

Please tell me what I could try to correct the error. I appreciate ANY  
hint.

Many thanks in advance
Dmitri Pissarenko
PS: The source code of the files related to  
EigenvalueCalculatorHaskell.hs is
located at

http://dapissarenko.com/resources/2005_02_17_eigenvaluesJava/ 
2005_02_17_lik.zip

--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___ 

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] Parse error

2005-03-17 Thread Lemmih
On Thu, 17 Mar 2005 20:42:30 +0100, Dmitri Pissarenko
<[EMAIL PROTECTED]> wrote:
> Hello!
> 
> In the attachment you will find a file, in which I try to access Java from
> Haskell using the Java bridge for functional languages.
> 
> For details see
> 
> http://sourceforge.net/projects/jvm-bridge/
> 
> and
> 
> http://dapissarenko.com/resources/2005_02_17_eigenvaluesJava/2005_02_17_eigenva
> luesJava.pdf
> 
> When I try to compile the attached file using
> 
> ghc +RTS -c -RTS -package javavm  -c EigenvalueCalculatorHaskell.hs -o
> EigenvalueCalculatorHaskell.o
> 
> I get the error
> 
> EigenvalueCalculatorHaskell.hs:28: parse error on input `putStrLn'
> 
> Unfortunately, I have not the slightest idea about how to fix/isolate it (I
> already commented out almost the whole code).
> 
> Please tell me what I could try to correct the error. I appreciate ANY hint.

Use 'do {let {foo = baz}; bar }'. And Haskell code look _a lot_
prettier when using the layout to structure the program.

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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread VoidPrayer
let ...
in ...

I guess GHC is finding where "in" is.

在 2010年 1月 17日 星期日 18:05:47,Andrew Coppin 寫道:
> Is there a specific reason why GHC consistently refuses to accept the
> following perfectly reasonable code snippet?
> 
> main = do
>   putStrLn "Line 1"
>   putStrLn "Line 2"
> 
>   let xs = do
> x <- [1..10]
> y <- [1..10]
> return (x+y)
> 
>   print xs
> 
> No matter which way I rearrange this, it *insists* that there's a parse
> error. This is very frustrating, given that it's utterly clear what I
> want...
> 
> ___
> 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] Parse error

2010-01-17 Thread Tony Morris
No, but there's a specific reason why GHC consistently refuses to accept
your perfectly unreasonable code snippet :)

GHC accepts the following perfectly reasonable code snippet:

main = do
 putStrLn "Line 1"
 putStrLn "Line 2"

 let xs = do x <- [1..10]
 y <- [1..10]
 return (x+y)

 print xs

Andrew Coppin wrote:
> Is there a specific reason why GHC consistently refuses to accept the
> following perfectly reasonable code snippet?
>
> main = do
>  putStrLn "Line 1"
>  putStrLn "Line 2"
>
>  let xs = do
>x <- [1..10]
>y <- [1..10]
>return (x+y)
>
>  print xs
>
> No matter which way I rearrange this, it *insists* that there's a
> parse error. This is very frustrating, given that it's utterly clear
> what I want...
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>

-- 
Tony Morris
http://tmorris.net/


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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Daniel Fischer
Am Sonntag 17 Januar 2010 11:05:47 schrieb Andrew Coppin:
> Is there a specific reason why GHC consistently refuses to accept the
> following perfectly reasonable code snippet?

Yes, you violated the layout rule.

>
> main = do
>   putStrLn "Line 1"
>   putStrLn "Line 2"
>
>   let xs = do
> x <- [1..10]
> y <- [1..10]
> return (x+y)
>
>   print xs
>
> No matter which way I rearrange this, it *insists* that there's a parse
> error. This is very frustrating, given that it's utterly clear what I
> want...

It's not.

ACLayout.hs:7:11: Empty 'do' construct

should give a hint (line 7 is "  let xs = do").
The next line after that is indented less than the "xs", so it ends the 
binding for xs (in fact, the entire let binding group) .
You have to indent the lines in the do-block defining xs more than xs 
itself.

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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Andrew Coppin

Tony Morris wrote:

No, but there's a specific reason why GHC consistently refuses to accept
your perfectly unreasonable code snippet :)
  


She sells csh on the sea shore. :-)


GHC accepts the following perfectly reasonable code snippet:

main = do
 putStrLn "Line 1"
 putStrLn "Line 2"

 let xs = do x <- [1..10]
 y <- [1..10]
 return (x+y)

 print xs
  


Urg, but that's *ugly*. Is there no way I can reduce the amount of 
indentation to something more reasonable?


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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Daniel Fischer
Am Sonntag 17 Januar 2010 11:33:45 schrieb Andrew Coppin:
> Tony Morris wrote:
> > No, but there's a specific reason why GHC consistently refuses to
> > accept your perfectly unreasonable code snippet :)
>
> She sells csh on the sea shore. :-)
>
> > GHC accepts the following perfectly reasonable code snippet:
> >
> > main = do
> >  putStrLn "Line 1"
> >  putStrLn "Line 2"
> >
> >  let xs = do x <- [1..10]
> >  y <- [1..10]
> >  return (x+y)
> >
> >  print xs
>
> Urg, but that's *ugly*. Is there no way I can reduce the amount of
> indentation to something more reasonable?


main = do
  putStrLn "Line 1"
  putStrLn "Line 2"

  let xs = do
x <- [1..10]
y <- [1..10]
return (x+y)

  print xs

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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Ross Paterson
On Sun, Jan 17, 2010 at 10:33:45AM +, Andrew Coppin wrote:
> Tony Morris wrote:
> >main = do
> > putStrLn "Line 1"
> > putStrLn "Line 2"
> >
> > let xs = do x <- [1..10]
> > y <- [1..10]
> > return (x+y)
> >
> > print xs
> 
> Urg, but that's *ugly*. Is there no way I can reduce the amount of
> indentation to something more reasonable?

Sure: start a new line and indentation level after every where, let, do or of.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Andrew Coppin

Daniel Fischer wrote:

Am Sonntag 17 Januar 2010 11:33:45 schrieb Andrew Coppin:
  

Urg, but that's *ugly*. Is there no way I can reduce the amount of
indentation to something more reasonable?




main = do
  putStrLn "Line 1"
  putStrLn "Line 2"

  let xs = do
x <- [1..10]
y <- [1..10]
return (x+y)

  print xs

That better?
  


It's an improvement. It's still not pretty, but I guess that's as good 
as it's going to get...


Maybe this is an instance of Haskell trying to tell me "if you need to 
write a 20-line do-block in the middle of your function, you're doing it 
wrong".


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


Re: [Haskell-cafe] Parse error

2010-01-17 Thread Hans Aberg

On 17 Jan 2010, at 11:44, Andrew Coppin wrote:


Urg, but that's *ugly*. Is there no way I can reduce the amount of
indentation to something more reasonable?


main = do
 putStrLn "Line 1"
 putStrLn "Line 2"

 let xs = do
   x <- [1..10]
   y <- [1..10]
   return (x+y)

 print xs

That better?


It's an improvement. It's still not pretty, but I guess that's as  
good as it's going to get...


Maybe this is an instance of Haskell trying to tell me "if you need  
to write a 20-line do-block in the middle of your function, you're  
doing it wrong".


Haskell starts the new indentation level where the following lexeme is  
(Haskell-98 Report, sec. 2.7). So to reduce indentation, one must  
start a new line (already mentioned in this thread). This works in Hugs:

main =
  do
  putStrLn "Line 1"
  putStrLn "Line 2"

  let
xs =
  do
  x <- [1..10]
  y <- [1..10]
  return (x+y)

  print xs

The "xs" on a new line looks a bit unusual, and it takes a bit more  
vertical space, but one gets nice indentation levels.


  Hans


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


Re: [Haskell-cafe] Parse error

2010-01-18 Thread Evan Laforge
> It's an improvement. It's still not pretty, but I guess that's as good as
> it's going to get...
>
> Maybe this is an instance of Haskell trying to tell me "if you need to write
> a 20-line do-block in the middle of your function, you're doing it wrong".

20 lines is a lot, but I have smaller ones all the time.  You need >4
spaces of indent to continue a let.  Here's another way to understand
why:

f = do
let x = some big
expression
y = another big
expression
x y

If you wonder why "multiple let" syntax is needed, well I don't really
know for sure, but consider if x and y were mutually recursive.

I was annoyed at first with all the indentation but got used to it.  I
use 4 space indents so it works out ok.  Binding with <- or in where
can reduce the indentation but is not always appropriate.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Parse error on input "|"

2007-05-31 Thread Akijmo

Hi everyone.
I am new to this Forum, Haskell and i am german, so i am sorry for "noob"
failures or spelling mistakes.

I am currently learning for an informatic exam (11th class) and i tried to
code a function to sum a polynom with a pair of polynoms... (I actually want
to to code a polynomdivision in which i need this)

But I get the parse error mentioned in the headline. It is referring to the
first line of the case differentiation.
Hopefully you can help me, here's the code:

polyplusd :: Polynom -> (Polynom, Polynom) -> Polynom
polyplusd [] p = p
polyplusd p [] = p
polyplusd p@((g1,e1):p1) (n, (q@((g2,e2):p2))
| g1>g2 = (g1,e1):(polyplusd p1 (n,q))
| g2>g1 = (g2,e2):(polyplusd p (n,p2))
| g1==g2 && e1+e2 /=0 =(g1, e1+e2):(polyplusd 
p1 (n,p2))
| otherwise = polyplusd p1 (n,p2)
-- 
View this message in context: 
http://www.nabble.com/Parse-error-on-input-%22%7C%22-tf3847082.html#a10895849
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Parse error on input "|"

2007-05-31 Thread Robin Green
You neglected a ) - remember to count your parentheses in future when
you get an error directly after a parenthesised expression.

-- 
Robin

On Thu, 31 May 2007 08:09:23 -0700 (PDT)
Akijmo <[EMAIL PROTECTED]> wrote:

> 
> Hi everyone.
> I am new to this Forum, Haskell and i am german, so i am sorry for
> "noob" failures or spelling mistakes.
> 
> I am currently learning for an informatic exam (11th class) and i
> tried to code a function to sum a polynom with a pair of polynoms...
> (I actually want to to code a polynomdivision in which i need this)
> 
> But I get the parse error mentioned in the headline. It is referring
> to the first line of the case differentiation.
> Hopefully you can help me, here's the code:
> 
> polyplusd :: Polynom -> (Polynom, Polynom) -> Polynom
> polyplusd [] p = p
> polyplusd p [] = p
> polyplusd p@((g1,e1):p1) (n, (q@((g2,e2):p2))
>   | g1>g2 = (g1,e1):(polyplusd p1 (n,q))
>   | g2>g1 = (g2,e2):(polyplusd p (n,p2))
>   | g1==g2 && e1+e2 /=0 =(g1,
> e1+e2):(polyplusd p1 (n,p2)) | otherwise = polyplusd p1 (n,p2)

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


Re: [Haskell-cafe] Parse error on input "|"

2007-05-31 Thread Dan Weston
The second argument of the second line of the definition does not match 
the expected type. (Polynom,Polynom) is a tuple, not a list, so 
[]::(a,a) is not well typed for any a.


Dan

Akijmo wrote:

Hi everyone.
I am new to this Forum, Haskell and i am german, so i am sorry for "noob"
failures or spelling mistakes.

I am currently learning for an informatic exam (11th class) and i tried to
code a function to sum a polynom with a pair of polynoms... (I actually want
to to code a polynomdivision in which i need this)

But I get the parse error mentioned in the headline. It is referring to the
first line of the case differentiation.
Hopefully you can help me, here's the code:

polyplusd :: Polynom -> (Polynom, Polynom) -> Polynom
polyplusd [] p = p
polyplusd p [] = p
polyplusd p@((g1,e1):p1) (n, (q@((g2,e2):p2))
| g1>g2 = (g1,e1):(polyplusd p1 (n,q))
| g2>g1 = (g2,e2):(polyplusd p (n,p2))
| g1==g2 && e1+e2 /=0 =(g1, e1+e2):(polyplusd 
p1 (n,p2))
| otherwise = polyplusd p1 (n,p2)



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


Re: [Haskell-cafe] Parse error on input "|"

2007-05-31 Thread Akijmo

thx much green... this helped for the parser failure.

Dan you were right too, cause now i got the interfering types [(Int,Int)]
and Polynom for line 2.
But i fixed this by replacing it with ([],[])
So thx much guys :D



greenrd wrote:
> 
> You neglected a ) - remember to count your parentheses in future when
> you get an error directly after a parenthesised expression.
> 
> -- 
> Robin
> 
> On Thu, 31 May 2007 08:09:23 -0700 (PDT)
> Akijmo <[EMAIL PROTECTED]> wrote:
> 
>> 
>> Hi everyone.
>> I am new to this Forum, Haskell and i am german, so i am sorry for
>> "noob" failures or spelling mistakes.
>> 
>> I am currently learning for an informatic exam (11th class) and i
>> tried to code a function to sum a polynom with a pair of polynoms...
>> (I actually want to to code a polynomdivision in which i need this)
>> 
>> But I get the parse error mentioned in the headline. It is referring
>> to the first line of the case differentiation.
>> Hopefully you can help me, here's the code:
>> 
>> polyplusd :: Polynom -> (Polynom, Polynom) -> Polynom
>> polyplusd [] p = p
>> polyplusd p [] = p
>> polyplusd p@((g1,e1):p1) (n, (q@((g2,e2):p2))
>>  | g1>g2 = (g1,e1):(polyplusd p1 (n,q))
>>  | g2>g1 = (g2,e2):(polyplusd p (n,p2))
>>  | g1==g2 && e1+e2 /=0 =(g1,
>> e1+e2):(polyplusd p1 (n,p2)) | otherwise = polyplusd p1 (n,p2)
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 

-- 
View this message in context: 
http://www.nabble.com/Parse-error-on-input-%22%7C%22-tf3847082.html#a10899124
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] Parse error in a package file

2005-02-13 Thread Dmitri Pissarenko
Hello!

I'm building the haskell-jvm-bridge (http://sourceforge.net/projects/jvm-
bridge/).

The final step of the building procedure is to install the package of haskell-
jvm-bridge.

When I enter ghc-pkg -a -f javavm.ghc-pkg I'm getting the error

javavm.ghc-pkg: parse error in package config file

The original file looks as shown below.


Package
{
name = "javavm",
import_dirs  = ["c:/Programme/haskell-jvm-bridge-0.3-
RC1/imports/"],
source_dirs  = [],
library_dirs =
[
"c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/"-L
],
hs_libraries = [],
extra_libraries  =
["stdc++","JVMBridge","JVMInvocation","HaskellJVMBridge"-L,"jvm_imp"],
include_dirs = [],
c_includes   = [],
package_deps = ["lang","concurrent","haskell98"],
extra_ghc_opts   = ["-fglasgow-exts","-fallow-undecidable-instances"],
extra_cc_opts= [],
extra_frameworks = [-L ],
extra_ld_opts=
[
"-Wl,-rpath,c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/"-L
]
}


I noted that some package files have the form [ Package, Package, ... ], and
changed the original file:


[Package
{
name = "javavm",
import_dirs  = ["c:/Programme/haskell-jvm-bridge-0.3-
RC1/imports/"],
source_dirs  = [],
library_dirs =
[
"c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/"-L
],
hs_libraries = [],
extra_libraries  =
["stdc++","JVMBridge","JVMInvocation","HaskellJVMBridge"-L,"jvm_imp"],
include_dirs = [],
c_includes   = [],
package_deps = ["lang","concurrent","haskell98"],
extra_ghc_opts   = ["-fglasgow-exts","-fallow-undecidable-instances"],
extra_cc_opts= [],
extra_frameworks = [-L ],
extra_ld_opts=
[
"-Wl,-rpath,c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/"-L
]
}]


This didn't help me, I got the same error message.

Please tell me what's wrong with this package file.

Thanks in advance

Dmitri Pissarenko
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parse error in a package file

2005-02-13 Thread Isaac Jones
Dmitri Pissarenko <[EMAIL PROTECTED]> writes:

> Hello!
>
> I'm building the haskell-jvm-bridge (http://sourceforge.net/projects/jvm-
> bridge/).
>
> The final step of the building procedure is to install the package of haskell-
> jvm-bridge.
>
> When I enter ghc-pkg -a -f javavm.ghc-pkg I'm getting the error
>
> javavm.ghc-pkg: parse error in package config file

(snip)

> Please tell me what's wrong with this package file.

Looks like there are a bunch of mis-placed "-L"s in the file.  Maybe
they need to be quoted?


peace,

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


Re: [Haskell-cafe] Parse error in a package file

2005-02-14 Thread Dmitri Pissarenko
Looks like there are a bunch of mis-placed "-L"s in the file.  Maybe
they need to be quoted?
Do you mean this
1) Before:
library_dirs =
[
"c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/"-L
],
After:
library_dirs =
[
"c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/", "-L"
],
2) Before:
extra_libraries  =
["stdc++","JVMBridge","JVMInvocation","HaskellJVMBridge"-L,"jvm_imp"],
After:
extra_libraries  =
["stdc++","JVMBridge","JVMInvocation","HaskellJVMBridge","-L",,"jvm_imp"],
3) Before:
extra_ld_opts=
[
"-Wl,-rpath,c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/"-L
]
After:
extra_ld_opts=
[
"-Wl,-rpath,c:/Programme/haskell-jvm-bridge-0.3-RC1/lib/", "-
L"
]
?
Thanks
Dmitri Pissarenko
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] parse error in pattern, and byte code interpreter

2012-01-14 Thread TP
Hi everybody,

I want to test a higher level language than C/C++ (type inference, garbage 
collection), but much faster than Python. So I am naturally led to Haskell or 
OCaml.

I have read and tested tutorials for the two languages. For the time being, my 
preference goes to Haskell, first because it looks more like Python, and also 
because some things appear not so clean in OCaml, at least for a beginner (Put 
a line termination or not? Why have I to put "rec" in the definition of a 
recursive function? Etc.).

I have two questions.

1/ Inspiring from tutorials out there, I have tried to write a small formal 
program which is able to distribute n*(x+y) to n*x+n*y. The OCaml version is 
working (see Post Scriptum). However, I have difficulties to make the Haskell 
version work. This is my code:

{}
data Expr = Plus Expr Expr
  | Minus Expr Expr
  | Times Expr Expr
  | Divide Expr Expr
  | Variable String
deriving ( Show, Eq )

expr_to_string expr = case expr of
Times expr1 expr2 -> "(" ++ ( expr_to_string expr1 ) ++ " * "
++ ( expr_to_string expr2 ) ++ ")"
Plus expr1 expr2 -> "(" ++ ( expr_to_string expr1 ) ++ " + "
++ ( expr_to_string expr2 ) ++ ")"
Variable var -> var

distribute expr = case expr of
 Variable var -> var
 Times expr1 Plus( expr2 expr3 ) ->
 Plus ( Times ( expr1 expr2 ) Times ( expr1 expr3 ) )

main = do
let x = Times ( Variable "n" )
( Plus ( Variable "x" ) ( Variable "y" ) )
print x
print ( expr_to_string x )
{}

When I try to run this code with "runghc", I obtain:

pattern_matching_example.hs:28:24: Parse error in pattern: expr2

Thus it does not like my pattern "Times expr1 Plus( expr2 expr3 )". Why?
How can I obtain the right result, as with the OCaml code below?

2/ It seems there is no possibility to generate bytecode, contrary to OCaml. 
Is it correct? Is there an alternative?
What is interesting with bytecode run with "ocamlrun" is that the process of 
generating the bytecode is very fast, so it is very convenient to test the 
program being written, in an efficient workflow. Only at the end the program is 
compiled to get more execution speed.

Thanks a lot in advance.

TP

PS:
---
To test the OCaml tutorial, type:
$ ocamlc -o pattern_matching_example pattern_matching_example.ml
$ ocamlrun ./pattern_matching_example

(*)
(* from OCaml tutorial, section 'data_types_and_matching.html' *)

(* This is a binary tree *)
type expr = Plus of expr * expr
  | Minus of expr * expr
  | Times of expr * expr
  | Divide of expr * expr
  | Value of string
;;

let v = Times ( Value "n", Plus (Value "x", Value "y") )

let rec to_string e =
match e with
Plus ( left, right ) -> "(" ^ (to_string left ) ^ " + " ^ (to_string 
right) ^ ")"
  | Minus ( left, right ) -> "(" ^ (to_string left ) ^ " - " ^ (to_string 
right) ^ ")"
  | Times ( left, right ) -> "(" ^ (to_string left ) ^ " * " ^ (to_string 
right) ^ ")"
  | Divide ( left, right ) -> "(" ^ (to_string left ) ^ " / " ^ (to_string 
right) ^ ")"
  | Value value -> value
;;

(* by type inference, ocaml knows that e is of type expr just below *)
let print_expr e = print_endline ( to_string e );;

print_expr v;;

let rec distribute e =
match e with
Times ( e1, Plus( e2, e3 ) ) ->
Plus (Times ( distribute e1, distribute e2 )
, Times ( distribute e1, distribute e3 ) )
  | Times ( Plus( e1, e2 ), e3 ) ->
Plus (Times ( distribute e1, distribute e3 )
, Times ( distribute e2, distribute e3 ) )
  | Plus ( left, right ) -> Plus ( distribute left, distribute right )
  | Minus ( left, right ) -> Minus ( distribute left, distribute right )
  | Times ( left, right ) -> Times ( distribute left, distribute right )
  | Divide ( left, right ) -> Divide ( distribute left, distribute right )
  | Value v -> Value v
;;

print_expr ( distribute v );;
(*)

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


Re: [Haskell-cafe] parse error in pattern, and byte code interpreter

2012-01-14 Thread Brandon Allbery
On Sat, Jan 14, 2012 at 18:18, TP  wrote:

> Times expr1 Plus( expr2 expr3 ) ->


OCaml pattern syntax is not the same as Haskell pattern syntax.  The
correct way to write that pattern is

Times expr1 (Plus expr2 expr3)

This is consistent with Haskell not using parentheses for function
parameters, since all calls are curried.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe