Re: [Haskell-cafe] a question about import and parsec...

2005-04-21 Thread Daniel Fischer
Am Donnerstag, 21. April 2005 03:58 schrieb Greg Wolff:
 I'm new at using Haskell and I'm trying to make use of the parsec
 library.  I've started by working through the examples in the user guide
 which don't work as written in ghci when I run them.  I've made
 modifications that have gotten them working, up to a point.  But now I
 have an error one of the examples that has me stumped and looking in the
 documentation didn't help.

 When I run the following code without the import Data.Char I get an
 error that digitToInt is not defined.  When I put the import in I get a
 large number of errors that weren't there before.

They were there, only ghci stopped on encountering an undefined name and 
didn't look for all errors then.

The errors are all of the same kind, 'lexeme', 'identifier', 'symbol' and 
'semi' - I hope, I haven't overlooked one - are named fields of a TokenParser 
and you try to apply lexeme to a Parser Int. If you insert 'lang' in the code 
after the abovementioned, the code will compile -- whether it'll do what is 
intended, I've no idea, I'd have to look at the sources to see what 
haskellStyle and makeTokenParser actually do (and of course I don't know what 
you want to have).

Hope, that's it,

Daniel


 Can some one explain this to me?  How can I get this code to work?

 --- Here is the code ---

  module Expressionparser where
 
  import Data.Char
  import Text.ParserCombinators.Parsec
  import Text.ParserCombinators.Parsec.Expr
  import Text.ParserCombinators.Parsec.Token
  import Text.ParserCombinators.Parsec.Language
 
  run :: Show a = Parser a - String - IO()
  run p input
  = case(parse p  input) of
  Left err - do { putStr parse error at  ; print err }
  Right x - print x
 
  runLex :: Show a = Parser a - String - IO()
  runLex p
  = run (do{ whiteSpace lang
   ; x - p
   ; eof
   ; return x
   }
)
 
  lang= makeTokenParser
  (haskellStyle{ reservedNames = [return,total]})
 
  expr = buildExpressionParser table factor ? expression
 
  table = [ [op * (*) AssocLeft, op / div AssocLeft]
  , [op + (+) AssocLeft, op - (-) AssocLeft]
  ]
  where
  op s f assoc
  = Infix (do{ symbol lang s; return f } ? operator) assoc
 
  factor = parens lang expr
   | natural lang
   ? simple expression
 
  test1   = do{ n - natural lang
  ; do{ symbol lang +
  ; m - natural lang
  ; return (n+m)
  }
  | return n
  }
 
  ---
 
  price  :: Parser Int   -- this is the price in cents
  price  = lexeme (do{ ds1 - many1 digit
 ; char '.'
 ; ds2 - count 2 digit
 ; return (convert 0 (ds1 ++ ds2))
 })
   ? price
 where
   convert n [] = n
   convert n (d:ds) = convert(10*n + digitToInt d) ds
 
  receipt :: Parser Bool
  receipt = do{ ps - many produkt
  ; p - total
  ; return (sum ps == p)
  }
 
  produkt = do{ symbol return
  ; p - price
  ; semi
  ; return (-p)
  }
| do{ identifier
  ; p - price
  ; semi
  ; return p
  }
? produkt
 
  total = do{ p - price
; symbol total
; return p
}

 --- end code ---

 Here are the errors:
 ___ ___ _
/ _ \ /\  /\/ __(_)
   / /_\// /_/ / /  | |  GHC Interactive, version 6.2.2, for Haskell
  98. / /_\\/ __  / /___| |  http://www.haskell.org/ghc/
  \/\/ /_/\/|_|  Type :? for help.
 
  Loading package base ... linking ... done.
  Prelude :l ~/expression-parser.hs
  Compiling Expressionparser ( /home/greg//expression-parser.hs,
  interpreted )
 
  /home/greg//expression-parser.hs:59:
  Variable not in scope: `digitToInt'
  Failed, modules loaded: none.
  Prelude :r
  Compiling Expressionparser ( /home/greg//expression-parser.hs,
  interpreted )
 
  /home/greg//expression-parser.hs:51:
  Couldn't match
  `GenParser tok st a'
  against
  `CharParser st1 a1 - CharParser st1 a1'
  Expected type: GenParser tok st a
  Inferred type: CharParser st1 a1 - CharParser st1 a1
  Probable cause: `lexeme' is applied to too few arguments in the call
  (lexeme (do
 ds1 - many1 digit
 char '.'
 ds2 - count 2 digit
 return (convert 0 (ds1 ++ ds2
  In the first argument of `(?)', namely
  `lexeme (do
 ds1 - many1 digit
 char '.'
 ds2 - count 2 digit
 return (convert 0 (ds1 ++ ds2)))'
 
  /home/greg//expression-parser.hs:67:
  Couldn't match `GenParser tok st' against `(-) String'
  Expected type: GenParser tok st t
  Inferred type: String - CharParser st1 String
  Probable cause: `symbol' 

[Haskell-cafe] Haskell Questions

2005-04-21 Thread Mike Richards
Hi,

I'm working on a version of Simon Thompson's code from The Craft of Functional 

programming to handle polymorhpic data types.

Heres the question Im working on - Ive tried doing the first part, but i would 

really apprecate it if someone could let me know if ive implemented it wrong.

Mike





import Hugs.Prelude;
import Monad;
import System;
import Control.Monad.Error;
import Char;


{--
 USEFUL AUXILIARY CONSTRUCTS
--}

list2set :: Eq a = [a] - [a]
list2set [] = []
list2set (x:xs)
  | x `elem` xs = list2set xs
  | otherwise   = x : list2set xs

inBrackets :: String - String
inBrackets str = ( ++ str ++ )

inBrackets2 :: String - String - String
inBrackets2 [] s2 = s2
inBrackets2 s1 [] = s1
inBrackets2 s1 s2 = inBrackets (s1 ++   ++ s2)

joinStrings :: String - [String] - String
joinStrings _ []  = 
joinStrings _ [s] = s
joinStrings sep (s:ss) = s ++ sep ++ joinStrings sep ss

char2str :: Char - String
char2str x = [x]

dig2int :: Char - Int
dig2int d = fromEnum d - fromEnum '0'

str2int :: String - Int
str2int s = str2intAux (reverse s)
  where str2intAux [x]= dig2int x
str2intAux (x:xs) = dig2int x + 10*(str2intAux xs)


{--
 PARSING / PATTERN MATCHING
 Code based on Thompson, Section 17.5
--}

infixr 5 *

type Parse a b = [a] - [(b,[a])]

-- Don't match anything
matchNone :: Parse a b
matchNone inp = []

-- Add a symbol into the stream and assert match
matchAndAdd :: b - Parse a b
matchAndAdd val inp = [(val,inp)]

-- Match if next input satisfies a given property
matchProperty :: (a - Bool) - Parse a a
matchProperty p (x:xs)
  | p x = [(x,xs)]
  | otherwise   = []
matchProperty _ []   = []

-- Match the next input symbol
matchInput :: Eq a = a - Parse a a
matchInput t = matchProperty (t==)

-- combine the results of two matchs
-- e.g. (matchLP `alt` matchDigit) checks for an LP or a digit
alt :: (Eq a, Eq b) = Parse a b - Parse a b - Parse a b
alt p1 p2 inp = list2set (p1 inp ++ p2 inp)

-- Chain matches together to recognise strings
(*) :: Parse a b - Parse a c - Parse a (b,c)
(*) p1 p2 inp = [((y,z),rem2) | (y,rem1) - p1 inp, (z,rem2) - p2 rem1 ]

-- Build values from matchd strings
build :: Parse a b - (b - c) - Parse a c
build p f inp = [ (f x, rem) | (x, rem) - p inp ]

-- Match a list of symbols all satisfying the same property
matchList :: (Eq a, Eq b) = Parse a b - Parse a [b]
matchList p = (matchAndAdd []) `alt`
  ((p * matchList p) `build` (uncurry (:)))

-- Match a single symbols satisfying a property
lift :: (Eq a, Eq b) = Parse a b - Parse a [b]
lift p = (p * matchAndAdd []) `build` (uncurry (:))

-- Match a non-empty list of symbols all satifying the same property
matchNEList :: (Eq a, Eq b) = Parse a b - Parse a [b]
matchNEList p = (p * matchList p) `build` (uncurry (:))

-- Match an alphanumeric string of characters
matchAlphaNums :: Parse Char [Char]
matchAlphaNums = matchList matchAlphaNum

-- Match a non-empty string of inputs, one after the other
matchInputs :: Eq a = [a] - Parse a [a]
matchInputs [] = error matchInputs: Empty test string
matchInputs [x] = matchInput x `build` buildMatch1
  where buildMatch1 x = [x]
matchInputs (x:xs) = (matchInput x * matchInputs xs) `build` (uncurry (:))
  where buildMatch2 (x,y) = [x,y]


{--
  PARTICULAR TOKENS OF INTEREST
--}

matchLP = matchInput '('-- left parenthesis
matchRP = matchInput ')'-- right parenthesis
matchCO = matchInput ','-- comma
matchSP = matchInput ' '-- space
matchLB = matchInput '['-- left bracket
matchRB = matchInput ']'-- right bracket
matchPT = matchInput '.'-- point (dot)
matchSQ = matchInput '\''   -- single quote
matchDQ = matchInput ''-- double quote
matchSL = matchInput '\\'   -- slash


matchAny  = matchProperty (\_ - True)
matchAlphaNum = matchProperty isAlphaNum
matchUpper= matchProperty isUpper
matchLower= matchProperty isLower
matchDigit= matchProperty isDigit

matchWhiteSpace = matchList matchSP

matchArrow = (matchWhiteSpace * matchInputs - * matchWhiteSpace)
   `build` buildArrow
  where buildArrow _ = -

matchInt = matchNEList matchDigit

matchFloat = (matchInt * matchPT * matchInt) `build` buildFloat
  where buildFloat (x,(_,y)) = (x ++ . ++ y)

matchChar = (matchSQ *
((matchInputs \\' ) `alt` ((matchProperty ('\'' /=)) `build` 

char2str))
* matchSQ)
  `build` buildChar
  where buildChar 

[Haskell-cafe] a newbie's question

2005-04-21 Thread SCOTT J.



Hi, 

I'm beginning to study Haskell, For the 
following


a = [1,2,3]
b = "there"

do x - a
 y - b
 return (x , y) 
Winhugs cannot run it. Gives
Syntax error in input (unexpected backslash 
(lambda)) 


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


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread Thomas Davie
On Apr 21, 2005, at 3:47 PM, SCOTT J. wrote:
Hi,
I'm beginning to study Haskell, For the following
a = [1,2,3]
b = there
do x - a
  y - b
 return (x , y)
Winhugs cannot run it. Gives
 Syntax error in input (unexpected backslash (
lambda))
Your problem is that you're using monads to grab the contents of a  
and b, while a and b are not monadic... You probably if you're only  
just setting out don't want to pay attention to any of the do  
notation or monadic code.  To get the result it looks like you want,  
all you need to do is this:
(a, b)
you can then define this as a new constant:
c = (a, b)

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


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread Paul Hudak
Thomas Davie wrote:
On Apr 21, 2005, at 3:47 PM, SCOTT J. wrote:
Hi,
I'm beginning to study Haskell, For the following
a = [1,2,3]
b = there
do x - a
   y - b
   return (x , y)
Winhugs cannot run it. Gives
Syntax error in input (unexpected backslash (
lambda))
Your problem is that you're using monads to grab the contents of a  and 
b, while a and b are not monadic... You probably if you're only  just 
setting out don't want to pay attention to any of the do  notation or 
monadic code.  To get the result it looks like you want,  all you need 
to do is this:
(a, b)
you can then define this as a new constant:
c = (a, b)
Hope that helps
Bob
On the other hand, perhaps he wanted all possible combinations of values 
in the lists a and b.  Since a list is a monad, this, for example, works 
fine:

a = [1,2,3]
b = there
abs = do x - a
 y - b
 return (x,y)
In Hugs:
abs ==
[(1,'t'),(1,'h'),(1,'e'),(1,'r'),(1,'e'),(2,'t'),(2,'h'),(2,'e'),(2,'r'),(2,'e')
,(3,'t'),(3,'h'),(3,'e'),(3,'r'),(3,'e')]
-Paul
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] a newbie's question

2005-04-21 Thread SCOTT J.



Hi, I'm trying to investigate the list monad. I 
program


instance Monad [] where
xs = f = concat ( map f xs )
return x = [x]
a = [1,2,3]
b = "there"
do { x - a
y - 
b
 return (x , y) } 
And I get the error
Syntax error in input (unexpected backslash 
(lambda))

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


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread SCOTT J.



Thanks for your assistance. I'm using now 
Notepad.exe . Before I did it in Wordpad. I use Windows XP. I'm trying to solve 
this nasty problem


  - Original Message - 
  From: 
  SCOTT J. 
  To: haskell-cafe@haskell.org 
  Sent: Thursday, April 21, 2005 5:16 
  PM
  Subject: [Haskell-cafe] a newbie's 
  question
  
  Hi, I'm trying to investigate the list monad. I 
  program
  
  
  instance Monad [] where
  xs = f = concat ( map f xs )
  return x = [x]
  a = [1,2,3]
  b = "there"
  do { x - a
  y - 
  b
   return (x , y) } 

  And I get the error
  Syntax error in input (unexpected backslash 
  (lambda))
  
  Jan
  
  

  ___Haskell-Cafe mailing 
  listHaskell-Cafe@haskell.orghttp://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] a newbie's question

2005-04-21 Thread Keith Wansbrough
[sorry if you receive this twice; mailing list problems]
SCOTT J. wrote:
Thanks for your assistance. I'm using now Notepad.exe . Before I did 
it in Wordpad. I use Windows XP. I'm trying to solve this nasty problem
 

WordPad probably saved your file in RTF rather than TXT.  Keep using 
Notepad for now, but you really should find yourself a decent 
programmer's editor - I use Emacs, but maybe some Windows people can 
recommend what they use on that platform.

Also, if you want more helpful error messages, use GHC rather than Hugs.
HTH.
--KW 8-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread Pierre Barbier de Reuille
You may want to have a look there :
http://www.haskell.org/libraries/#ide
It references some tools to develop in haskell ...
Pierre
Keith Wansbrough a écrit :
[sorry if you receive this twice; mailing list problems]
SCOTT J. wrote:
Thanks for your assistance. I'm using now Notepad.exe . Before I did 
it in Wordpad. I use Windows XP. I'm trying to solve this nasty problem
 


WordPad probably saved your file in RTF rather than TXT.  Keep using 
Notepad for now, but you really should find yourself a decent 
programmer's editor - I use Emacs, but maybe some Windows people can 
recommend what they use on that platform.

Also, if you want more helpful error messages, use GHC rather than Hugs.
HTH.
--KW 8-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
--
Pierre Barbier de Reuille
INRA - UMR Cirad/Inra/Cnrs/Univ.MontpellierII AMAP
Botanique et Bio-informatique de l'Architecture des Plantes
TA40/PSII, Boulevard de la Lironde
34398 MONTPELLIER CEDEX 5, France
tel   : (33) 4 67 61 65 77fax   : (33) 4 67 61 56 68
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] a newbie's question

2005-04-21 Thread Alexandre Weffort Thenorio
Well I think one of the best tools to programme on for Windows is UltraEdit,
it will give you colors and other stuff (provided you get the correct file
for it which is out on the net).

Emacs also exists for windows and is not bad, but I don't know if that is
the best tool (I sure like it but I hate when you try tabbing and it does it
all wrong).

Best Regards

NooK

- Original Message - 
From: Keith Wansbrough [EMAIL PROTECTED]
To: SCOTT J. [EMAIL PROTECTED]
Cc: haskell-cafe@haskell.org
Sent: Thursday, April 21, 2005 9:13 PM
Subject: Re: [Haskell-cafe] a newbie's question


 [sorry if you receive this twice; mailing list problems]

 SCOTT J. wrote:

  Thanks for your assistance. I'm using now Notepad.exe . Before I did
  it in Wordpad. I use Windows XP. I'm trying to solve this nasty problem
 



 WordPad probably saved your file in RTF rather than TXT.  Keep using
 Notepad for now, but you really should find yourself a decent
 programmer's editor - I use Emacs, but maybe some Windows people can
 recommend what they use on that platform.

 Also, if you want more helpful error messages, use GHC rather than Hugs.

 HTH.

 --KW 8-)
 ___
 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] read with pattern

2005-04-21 Thread Cale Gibbard
It's not really clear to me what you're asking. The function read is a
method of the typeclass Read, and it has type Read a = String - a.

There are a number of instances of the typeclass Read in the standard
prelude (http://www.haskell.org/onlinereport/standard-prelude.html)

Notably,
instance  Read Int  where ...
instance  (Read a, Read b) = Read (a,b)  where ...
instance  (Read a) = Read [a]  where ...
which, taken together, imply that the type [(Int,Int)] is in the
typeclass Read, and so there is a suitable implementation of read ::
String - [(Int,Int)]  If you want to see how that might be
implemented (though haskell implementations are allowed to do the same
thing in a different way), see the link to the prelude there.

hope this helps,
 - Cale

On 4/21/05, Walt Potter [EMAIL PROTECTED] wrote:
 I'd like to find a reference to reading with patterns such as
 read::[(Int,Int)]
 
 Thanks, Walt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe