Re: [Haskell-cafe] Bencoding in Haskell

2005-04-20 Thread Sebastian Sylvan
Yeah, you probably want the main parser to be many beParser and not
just beParser:

-- main parser function
parseBencoded :: String - Maybe [Bencode]
parseBencode str = case parse (many beParse)  str of
Left err - Nothing
Right val - Just val

On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 4/20/05, Tommi Airikka [EMAIL PROTECTED] wrote:
  Hi!
 
  I was just wondering if there are any good ways to represent a bencoded
  (http://en.wikipedia.org/wiki/Bencoding) message in Haskell? Any
  suggestions?
 
 
 Not that I know of, but it should be very easy to write a parser using
 the parser library Parsec.
 
 You'll need a datatype, something like this:
 
 data Bencode = BEInteger Integer |
 BEString String |
 BEList [Bencode] |
 BEDictionary (Data.Map String Bencode)
 deriving (Show, Eq)
 
 Which should be sufficient to represent any Bencoded message (if I
 didn't make a misstake).
 Then you could probably use the standard char-parser in parsec to
 parse it quite easily. Read the docs, they're quite straightforward.
 
 I'm a bit rusty but something like this:
 
 -- just parse an integer, parsec might have one of these already
 number :: Parser Integer
 number =
   do n_str - many1 digit -- parse a number
let n = read n_str  -- convert to an Int
return n   -- return the number
 
 beString :: Parser Bencode
 beString =
   do n - number -- the length prefix
   char ':'  -- now a ':'
   str - count n anyChar   -- and now n number of letters
   return (BEString str)   -- return the string wrapped up as a
 BEString
 
 beInt :: Parser Bencode
 beInt =
   do char 'i'
n - number
char 'e'
return n
 
 -- parse any Bencoded value
 beParse :: Parser Bencode
 beParse =
   do beInt | beString | beDictionary | beList
 
 beList :: Parser Bencode
 beList =
   do char 'l'
xs - many beParse -- parse many bencoded values
char 'e'
return (BEList xs)
 
 beDictionary :: Parser Bencode
 beDictionary =
   do char 'd'
key - beString
val - beParse
m - beDictionary | char 'e'  return Data.Map.empty
return (Data.Map.insert key val m)
 
 -- main parser function
 parseBencoded :: String - Maybe Bencode
 parseBencode str = case parse beParse  str of
  Left err - Nothing
  Right val - Just val
 
 Note: This is all untested code that I just scribbled down real quick.
 There's probably tons of misstakes, but you should get the picture.
 Read the Parsec docs and then write your own.
 
 /S
 --
 Sebastian Sylvan
 +46(0)736-818655
 UIN: 44640862
 


-- 
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] Bencoding in Haskell

2005-04-20 Thread Sebastian Sylvan
I was bored so I ran it through ghci and fixed the small errors I
found, here's the working version, I don't really have much of test
data to play with, but it seems to be working with the small examples
I copy-n-pasted from the wiki and the bittorrent website:

import qualified Data.Map as Map
import Data.Map(Map)
import Text.ParserCombinators.Parsec

data Bencode = BEInteger Integer 
 | BEString String 
 | BEList [Bencode] 
 | BEDictionary (Map String Bencode)
 deriving (Show, Eq)

number :: Parser Integer
number = 
do n_str - many1 digit 
   let n = read n_str
   return n

beString :: Parser Bencode
beString =
do n - number 
   char ':'
   str - count (fromInteger n) anyChar
   return (BEString str) 


beInt :: Parser Bencode
beInt =
do char 'i'
   n - number
   char 'e'
   return (BEInteger n)

-- parse any Bencoded value
beParse :: Parser Bencode
beParse = beInt | beString | beDictionary | beList

beList :: Parser Bencode
beList =
do char 'l'
   xs - many beParse -- parse many bencoded values
   char 'e'
   return (BEList xs)

beDictionary :: Parser Bencode
beDictionary =
do char 'd'
   (BEString key) - beString
   val - beParse
   (BEDictionary m) - beDictionary 
   | do char 'e'
  return (BEDictionary Map.empty)

   return (BEDictionary (Map.insert key val m))

-- main parser function
parseBencoded :: String - Maybe [Bencode]
parseBencoded str = case parse (many beParse)  str of
Left err - Nothing
Right val - Just val



/S

On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 Yeah, you probably want the main parser to be many beParser and not
 just beParser:
 
 -- main parser function
 parseBencoded :: String - Maybe [Bencode]
 parseBencode str = case parse (many beParse)  str of
 Left err - Nothing
 Right val - Just val
 
 On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  On 4/20/05, Tommi Airikka [EMAIL PROTECTED] wrote:
   Hi!
  
   I was just wondering if there are any good ways to represent a bencoded
   (http://en.wikipedia.org/wiki/Bencoding) message in Haskell? Any
   suggestions?
  
 
  Not that I know of, but it should be very easy to write a parser using
  the parser library Parsec.
 
  You'll need a datatype, something like this:
 
  data Bencode = BEInteger Integer |
  BEString String |
  BEList [Bencode] |
  BEDictionary (Data.Map String Bencode)
  deriving (Show, Eq)
 
  Which should be sufficient to represent any Bencoded message (if I
  didn't make a misstake).
  Then you could probably use the standard char-parser in parsec to
  parse it quite easily. Read the docs, they're quite straightforward.
 
  I'm a bit rusty but something like this:
 
  -- just parse an integer, parsec might have one of these already
  number :: Parser Integer
  number =
do n_str - many1 digit -- parse a number
 let n = read n_str  -- convert to an Int
 return n   -- return the number
 
  beString :: Parser Bencode
  beString =
do n - number -- the length prefix
char ':'  -- now a ':'
str - count n anyChar   -- and now n number of letters
return (BEString str)   -- return the string wrapped up as a
  BEString
 
  beInt :: Parser Bencode
  beInt =
do char 'i'
 n - number
 char 'e'
 return n
 
  -- parse any Bencoded value
  beParse :: Parser Bencode
  beParse =
do beInt | beString | beDictionary | beList
 
  beList :: Parser Bencode
  beList =
do char 'l'
 xs - many beParse -- parse many bencoded values
 char 'e'
 return (BEList xs)
 
  beDictionary :: Parser Bencode
  beDictionary =
do char 'd'
 key - beString
 val - beParse
 m - beDictionary | char 'e'  return Data.Map.empty
 return (Data.Map.insert key val m)
 
  -- main parser function
  parseBencoded :: String - Maybe Bencode
  parseBencode str = case parse beParse  str of
   Left err - Nothing
   Right val - Just val
 
  Note: This is all untested code that I just scribbled down real quick.
  There's probably tons of misstakes, but you should get the picture.
  Read the Parsec docs and then write your own.
 
  /S
  --
  Sebastian Sylvan
  +46(0)736-818655
  UIN: 44640862
 
 
 --
 Sebastian Sylvan
 +46(0)736-818655
 UIN: 44640862
 


-- 
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] Bencoding in Haskell

2005-04-20 Thread Tommi Airikka
Thank you very much! I really appreciate your help!
I have to read a little bit more about Parsec to fully understand what
your code does, but it seems to be what I was looking for.

Regards,
Tommi

On Wed, Apr 20, 2005 at 08:58:41PM +0200, Sebastian Sylvan wrote:
 I was bored so I ran it through ghci and fixed the small errors I
 found, here's the working version, I don't really have much of test
 data to play with, but it seems to be working with the small examples
 I copy-n-pasted from the wiki and the bittorrent website:
 
 import qualified Data.Map as Map
 import Data.Map(Map)
 import Text.ParserCombinators.Parsec
 
 data Bencode = BEInteger Integer 
  | BEString String 
  | BEList [Bencode] 
  | BEDictionary (Map String Bencode)
  deriving (Show, Eq)
 
 number :: Parser Integer
 number = 
 do n_str - many1 digit 
let n = read n_str
return n
 
 beString :: Parser Bencode
 beString =
 do n - number 
char ':'
str - count (fromInteger n) anyChar
return (BEString str) 
 
 
 beInt :: Parser Bencode
 beInt =
 do char 'i'
n - number
char 'e'
return (BEInteger n)
 
 -- parse any Bencoded value
 beParse :: Parser Bencode
 beParse = beInt | beString | beDictionary | beList
 
 beList :: Parser Bencode
 beList =
 do char 'l'
xs - many beParse -- parse many bencoded values
char 'e'
return (BEList xs)
 
 beDictionary :: Parser Bencode
 beDictionary =
 do char 'd'
(BEString key) - beString
val - beParse
(BEDictionary m) - beDictionary 
| do char 'e'
   return (BEDictionary Map.empty)
 
return (BEDictionary (Map.insert key val m))
 
 -- main parser function
 parseBencoded :: String - Maybe [Bencode]
 parseBencoded str = case parse (many beParse)  str of
 Left err - Nothing
 Right val - Just val
 
 
 
 /S
 
 On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  Yeah, you probably want the main parser to be many beParser and not
  just beParser:
  
  -- main parser function
  parseBencoded :: String - Maybe [Bencode]
  parseBencode str = case parse (many beParse)  str of
  Left err - Nothing
  Right val - Just val
  
  On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
   On 4/20/05, Tommi Airikka [EMAIL PROTECTED] wrote:
Hi!
   
I was just wondering if there are any good ways to represent a bencoded
(http://en.wikipedia.org/wiki/Bencoding) message in Haskell? Any
suggestions?
   
  
   Not that I know of, but it should be very easy to write a parser using
   the parser library Parsec.
  
   You'll need a datatype, something like this:
  
   data Bencode = BEInteger Integer |
   BEString String |
   BEList [Bencode] |
   BEDictionary (Data.Map String Bencode)
   deriving (Show, Eq)
  
   Which should be sufficient to represent any Bencoded message (if I
   didn't make a misstake).
   Then you could probably use the standard char-parser in parsec to
   parse it quite easily. Read the docs, they're quite straightforward.
  
   I'm a bit rusty but something like this:
  
   -- just parse an integer, parsec might have one of these already
   number :: Parser Integer
   number =
 do n_str - many1 digit -- parse a number
  let n = read n_str  -- convert to an Int
  return n   -- return the number
  
   beString :: Parser Bencode
   beString =
 do n - number -- the length prefix
 char ':'  -- now a ':'
 str - count n anyChar   -- and now n number of letters
 return (BEString str)   -- return the string wrapped up as a
   BEString
  
   beInt :: Parser Bencode
   beInt =
 do char 'i'
  n - number
  char 'e'
  return n
  
   -- parse any Bencoded value
   beParse :: Parser Bencode
   beParse =
 do beInt | beString | beDictionary | beList
  
   beList :: Parser Bencode
   beList =
 do char 'l'
  xs - many beParse -- parse many bencoded values
  char 'e'
  return (BEList xs)
  
   beDictionary :: Parser Bencode
   beDictionary =
 do char 'd'
  key - beString
  val - beParse
  m - beDictionary | char 'e'  return Data.Map.empty
  return (Data.Map.insert key val m)
  
   -- main parser function
   parseBencoded :: String - Maybe Bencode
   parseBencode str = case parse beParse  str of
Left err - Nothing
Right val - Just val
  
   Note: This is all untested code that I just scribbled down real quick.
   There's probably tons of misstakes, but you should get the picture.
   

[Haskell-cafe] Haskell Assistance Question

2005-04-20 Thread Mike Richards
Hi,

Im currently working on a haskell constraint parser for polymorhpic data types 
for a group of third year programmers, and was wondering if there was a help 
resource, or board on the internet for haskell programmers to ask questions 
about code they're working on. Any help or links would be much appreciated.

Thanks a lot

Mike 

[EMAIL PROTECTED]



-- 
___
Get your free email from http://mail.oxygen.ie

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


Re: [Haskell-cafe] Bencoding in Haskell

2005-04-20 Thread Sebastian Sylvan
beDictionary is wrong, though. It will only find dictionaries with a
single entry.

This next parser should do the trick (again, untested!).
It basically reads a d and then a list of (key,value) pairs (which
is now a separate parser) and then an e, and then it returns a Map
String Bencode.

Should be something like this

-- parses an association list of the contents
-- of a dictionary
beDicContents :: Parser (String, Bencode)
beDicContents = 
 do (BEString key) - beString
 val - beParse
 return (String, Bencode)

beDictionary :: Parser Bencode
beDictionary =
   do char 'd'
xs - many beDicContents  
char 'e'
return (BEDictionary (Map.fromAscList xs))

On 4/20/05, Tommi Airikka [EMAIL PROTECTED] wrote:
 Thank you very much! I really appreciate your help!
 I have to read a little bit more about Parsec to fully understand what
 your code does, but it seems to be what I was looking for.
 
 Regards,
 Tommi
 
 On Wed, Apr 20, 2005 at 08:58:41PM +0200, Sebastian Sylvan wrote:
  I was bored so I ran it through ghci and fixed the small errors I
  found, here's the working version, I don't really have much of test
  data to play with, but it seems to be working with the small examples
  I copy-n-pasted from the wiki and the bittorrent website:
 
  import qualified Data.Map as Map
  import Data.Map(Map)
  import Text.ParserCombinators.Parsec
 
  data Bencode = BEInteger Integer
   | BEString String
   | BEList [Bencode]
   | BEDictionary (Map String Bencode)
   deriving (Show, Eq)
 
  number :: Parser Integer
  number =
  do n_str - many1 digit
 let n = read n_str
 return n
 
  beString :: Parser Bencode
  beString =
  do n - number
 char ':'
 str - count (fromInteger n) anyChar
 return (BEString str)
 
 
  beInt :: Parser Bencode
  beInt =
  do char 'i'
 n - number
 char 'e'
 return (BEInteger n)
 
  -- parse any Bencoded value
  beParse :: Parser Bencode
  beParse = beInt | beString | beDictionary | beList
 
  beList :: Parser Bencode
  beList =
  do char 'l'
 xs - many beParse -- parse many bencoded values
 char 'e'
 return (BEList xs)
 
  beDictionary :: Parser Bencode
  beDictionary =
  do char 'd'
 (BEString key) - beString
 val - beParse
 (BEDictionary m) - beDictionary
 | do char 'e'
return (BEDictionary Map.empty)
 
 return (BEDictionary (Map.insert key val m))
 
  -- main parser function
  parseBencoded :: String - Maybe [Bencode]
  parseBencoded str = case parse (many beParse)  str of
  Left err - Nothing
  Right val - Just val
 
 
 
  /S
 
  On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
   Yeah, you probably want the main parser to be many beParser and not
   just beParser:
  
   -- main parser function
   parseBencoded :: String - Maybe [Bencode]
   parseBencode str = case parse (many beParse)  str of
   Left err - Nothing
   Right val - Just val
  
   On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
On 4/20/05, Tommi Airikka [EMAIL PROTECTED] wrote:
 Hi!

 I was just wondering if there are any good ways to represent a 
 bencoded
 (http://en.wikipedia.org/wiki/Bencoding) message in Haskell? Any
 suggestions?

   
Not that I know of, but it should be very easy to write a parser using
the parser library Parsec.
   
You'll need a datatype, something like this:
   
data Bencode = BEInteger Integer |
BEString String |
BEList [Bencode] |
BEDictionary (Data.Map String Bencode)
deriving (Show, Eq)
   
Which should be sufficient to represent any Bencoded message (if I
didn't make a misstake).
Then you could probably use the standard char-parser in parsec to
parse it quite easily. Read the docs, they're quite straightforward.
   
I'm a bit rusty but something like this:
   
-- just parse an integer, parsec might have one of these already
number :: Parser Integer
number =
  do n_str - many1 digit -- parse a number
   let n = read n_str  -- convert to an Int
   return n   -- return the number
   
beString :: Parser Bencode
beString =
  do n - number -- the length prefix
  char ':'  -- now a ':'
  str - count n anyChar   -- and now n number of letters
  return (BEString str)   -- return the string wrapped up as a
BEString
   
beInt :: Parser Bencode
beInt =
  do char 'i'
   n - number
   char 'e'
   return n
   
-- parse any Bencoded value

Re: [Haskell-cafe] Bencoding in Haskell

2005-04-20 Thread Sebastian Sylvan
On 4/20/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 -- parses an association list of the contents
 -- of a dictionary
 beDicContents :: Parser (String, Bencode)
 beDicContents =
  do (BEString key) - beString
  val - beParse
  return (String, Bencode)

bah, I should get some sleep :-)
That should be return (key, val)


/S

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


[Haskell-cafe] Re: [Haskell] Going nuts

2005-04-20 Thread Albert Lai
Alexandre Weffort Thenorio [EMAIL PROTECTED] writes:

 outputLine keyno key orgFile = do
 part1 - getLeft keyno orgFile
 part2 - getRight keyno orgFile
 total - part1 ++ (strUpper key) ++ part2 ++ \n
 newHexFile - openFileEx newfile (BinaryMode WriteMode)
  hPutStrLn newHexFile (orgFile!!0 ++ \n ++ total ++ unlines (drop 2
 orgFile))

outputLine keyno key orgFile = do
let part1 = getLeft keyno orgFile
let part2 = getRight keyno orgFile
let total = part1 ++ (strUpper key) ++ part2 ++ \n
newHexFile - openFileEx newfile (BinaryMode WriteMode)
hPutStrLn newHexFile (orgFile!!0 ++ \n ++ total ++ unlines (drop 2 
orgFile))

let ... = instead of - because getLeft et al. aren't IO commands.

(Why type error rather than syntax error then? Because getLeft returns
a list, and list is a monad too. E.g.,

  do { part1 - getLeft keyno orgFile; return part1 }
= [ part1 | part1 - getLeft keyno orgFile ]

so part1 is inferred to be a Char.)

There will be another problem.  The type of orgFile is expected to be
String here, but the callsite gives it lines(hexFile) of type [String].

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


[Haskell-cafe] embedded interpreters

2005-04-20 Thread Tim Docker
[I've asked this question on lambda-the-ultimate, but it remained unanswered,
 and it's probably more appropriate here in any case]

The papers referenced here:

http://lambda-the-ultimate.org/node/view/552

describe a means of projecting values in an implementation
language to and from values in an embedded interpreted language. The papers
use ML, but Derek Elkin gives a straightforward translation to haskell, via
a typeclass. An excerpt is here:

 data U = UF !(U - U) | UP !U !U | UU | UB !Bool | UI !Int | US !String
 deriving Show
 
 class EmbedProject a where
 embed :: a - U
 project :: U - a
 
 instance EmbedProject Int where
 embed = UI
 project (UI i) = i
 
 instance (EmbedProject a, EmbedProject b) = EmbedProject (a - b) where
 embed f = UF (embed . f . project)
 project (UF f) = project . f . embed

This is nice and tidy. However, the project function can fail in practise - in
the above, this results in pattern matching failures. I'd like have more control
of this, which suggests the following:

 class EmbedProject a where
 embed :: a - U
 project :: U - Maybe a
 
 instance EmbedProject Int where
 embed = UI
 project (UI i) = Just i
 project _  = Nothing

...etc, until it comes to to defining the instance of EmbedProject for 
functions.
embed is ok - incorrect parameters map to return values of the UU type. But I'm
lost as to what needs to happen with the project function. The definition belows
doesn't compile because (project.f.embed) has type a-Maybe b, but I need 
something
of type Maybe (a-b):

 instance (EmbedProject a, EmbedProject b) = EmbedProject (a - b) where
  embed f = UF (\a - maybe UU (embed.f) (project a) )
  project (UF f) = project.f.embed
  project _ = Nothing

Any suggestions? Is there something obvious (or non-obvious!) that I am missing?

Thanks,

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


[Haskell-cafe] Re: [Haskell] Y in haskell?

2005-04-20 Thread Albert Lai
Bernard Pope [EMAIL PROTECTED] writes:

 I also meant to add that I think these solutions are not what Lloyd is
 after, because they rely on recursive equations, which I believe was
 avoided in Lloyd's SML code.

Those recursive equations are avoided in SML because SML is eager - y
f = f (y f) never terminates - and an SML programmer has to thunk by
hand; the obfuscation shows.  In Haskell there is no such need.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe