Re: [Haskell-cafe] A weird bug of regex-pcre

2012-12-18 Thread José Romildo Malaquias
On Tue, Dec 18, 2012 at 02:28:26PM +0800, Magicloud Magiclouds wrote:
 Attachment is the test text file.
 And I tested my regexp as this:
 
 Prelude :m + Text.Regex.PCRE
 Prelude Text.Regex.PCRE z - readFile test.html
 Prelude Text.Regex.PCRE let (b, m ,a, ss) = z =~ a
 href=\(.*?)\.*?img class=\article-image\ :: (String, String, String,
 [String])
 Prelude Text.Regex.PCRE b
 ...
 n of the Triumvirate/td\r\ntd class=\small\David Rapoza/td\r\n
td class=\small\\r\n  iReturn to Ravnica/i\r\n/td\r\n
td class=\small\10/31/2012/td\r\n  /trtr\r\n  td
 class=\small\
 Prelude Text.Regex.PCRE m
 a href=\/magic/magazine/article.aspx?x=mtg/daily/activity/1088\img
 class=\article-image\ 
 
 From the value of b and m, it was weird that the matching was moved forward
 by 1 char ( the ss (sub matching) was even worse, 2 chars ). Rematch to a
 and so on gave correct results. It was only the first matching that was
 broken.
 Tested with regex-posix (with modified regexp), everything is OK.

I have a similar issue with non-ascii strings. It seems that the
internal representation used by Haskell and pcre are different and one
of them is counting bytes and the other is counting code points. So they
diverge when a multi-byte representation (like utf8) is used.

It has been reported previously. See these threads:

http://www.haskell.org/pipermail/haskell-cafe/2012-August/thread.html#102959
http://www.haskell.org/pipermail/haskell-cafe/2012-August/thread.html#103029

I am still waiting for a new release of regex-pcre that fixes this
issue.

Romildo

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


[Haskell-cafe] regex-pcre and ghc-7.4.2 is not working with UTF-8

2012-08-23 Thread José Romildo Malaquias
Hello.

I think I have an explanation for the problem with regex-pcre, ghc-7.4.2
and UTF Strings.

The Text.Regex.PCRE.String module uses the withCString and
withCStringLen from the module Foreign.C.String to pass a Haskell string
to the C library pcre functions that compile regular expressions, and
execute regular expressions to match some text.

Recent versions of ghc have withCString and withCStringLen definitions
that uses the current system locale to define the marshalling of a
Haskell string into a NUL terminated C string using temporary storage.

With a UTF-8 locale the length of the C string will be greater than the
length of the corresponding Haskell string in the presence with
characters outside of the ASCII range. Therefore positions of
corresponding characters in both strings do not match.

In order to compute matching positions, regex-pcre functions use C
strings. But to compute matching strings they use those positions with
Haskell strings.

That gives the mismatch shown earlier and repeated here with the
attached program run on a system with a UTF-8 locale:


   $ LANG=en_US.UTF-8  ./test1
   getForeignEncoding: UTF-8

   regex: país:(.*):(.*)
   text : país:Brasília:Brasil
   String matchOnce : Just (array (0,2) [(0,(0,22)),(1,(6,9)),(2,(16,6))])
   String match : [[pa\237s:Bras\237lia:Brasil,ras\237lia:B,asil]]

   $ LANG=en_US.ISO-8859-1  ./test1
   getForeignEncoding: ISO-8859-1

   regex: pa�s:(.*):(.*)
   text : pa�s:Bras�lia:Brasil
   String matchOnce : Just (array (0,2) [(0,(0,20)),(1,(5,8)),(2,(14,6))])
   String match : [[pa\237s:Bras\237lia:Brasil,Bras\237lia,Brasil]]


I see two ways of fixing this bug:

1. make the matching functions compute the text using the C string and
   the positions calculated by the C function, and convert the text back
   to a Haskell string.

2. map the positions in the C string (if possible) to the corresponding
   positions in the Haskell string; this way the current definitions of
   the matching functions returning text will just work.

I hope this would help fixing the issue.


Regards,

Romildo
module Main where

import GHC.IO.Encoding (getForeignEncoding)
import Data.Bits (Bits((..)))
import Text.Regex.PCRE

testpcre re text = do putStrLn (regex:  ++ re)
  putStrLn (text :  ++ text)
  putStrLn (String matchOnce :  ++ show mo)
  putStrLn (String match :  ++ show m)
  where
c = defaultCompOpt .. compUTF8
e = defaultExecOpt
regex = makeRegexOpts c e re :: Regex
mo = matchOnce regex text
m = match regex text :: [[String]]

main = do enc - getForeignEncoding
  putStrLn (getForeignEncoding:  ++ show enc)
  putStrLn 
  testpcre país:(.*):(.*) país:Brasília:Brasil

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


Re: [Haskell-cafe] regex-pcre and ghc-7.4.2 is not working with UTF-8

2012-08-23 Thread José Romildo Malaquias
On Thu, Aug 23, 2012 at 08:59:52AM -0300, José Romildo Malaquias wrote:
 Hello.
 
 I think I have an explanation for the problem with regex-pcre, ghc-7.4.2
 and UTF Strings.
 
 The Text.Regex.PCRE.String module uses the withCString and
 withCStringLen from the module Foreign.C.String to pass a Haskell string
 to the C library pcre functions that compile regular expressions, and
 execute regular expressions to match some text.
 
 Recent versions of ghc have withCString and withCStringLen definitions
 that uses the current system locale to define the marshalling of a
 Haskell string into a NUL terminated C string using temporary storage.
 
 With a UTF-8 locale the length of the C string will be greater than the
 length of the corresponding Haskell string in the presence with
 characters outside of the ASCII range. Therefore positions of
 corresponding characters in both strings do not match.
 
 In order to compute matching positions, regex-pcre functions use C
 strings. But to compute matching strings they use those positions with
 Haskell strings.
 
 That gives the mismatch shown earlier and repeated here with the
 attached program run on a system with a UTF-8 locale:
 
 
$ LANG=en_US.UTF-8  ./test1
getForeignEncoding: UTF-8
 
regex: país:(.*):(.*)
text : país:Brasília:Brasil
String matchOnce : Just (array (0,2) [(0,(0,22)),(1,(6,9)),(2,(16,6))])
String match : [[pa\237s:Bras\237lia:Brasil,ras\237lia:B,asil]]
 
$ LANG=en_US.ISO-8859-1  ./test1
getForeignEncoding: ISO-8859-1
 
regex: pa�s:(.*):(.*)
text : pa�s:Bras�lia:Brasil
String matchOnce : Just (array (0,2) [(0,(0,20)),(1,(5,8)),(2,(14,6))])
String match : [[pa\237s:Bras\237lia:Brasil,Bras\237lia,Brasil]]
 
 
 I see two ways of fixing this bug:
 
 1. make the matching functions compute the text using the C string and
the positions calculated by the C function, and convert the text back
to a Haskell string.
 
 2. map the positions in the C string (if possible) to the corresponding
positions in the Haskell string; this way the current definitions of
the matching functions returning text will just work.
 
 I hope this would help fixing the issue.


I have a fix for this bug and it would be nice if others take a look at
it and see if it is ok. It is based on the second way presented above.

Romildo
diff -ur regex-pcre-0.94.4.orig/Text/Regex/PCRE/String.hs 
regex-pcre-0.94.4/Text/Regex/PCRE/String.hs
--- regex-pcre-0.94.4.orig/Text/Regex/PCRE/String.hs2012-05-30 
18:44:14.0 -0300
+++ regex-pcre-0.94.4/Text/Regex/PCRE/String.hs 2012-08-23 17:22:14.114641657 
-0300
@@ -46,11 +46,16 @@
   ) where
 
 import Text.Regex.PCRE.Wrap -- all
-import Foreign.C.String(withCStringLen,withCString)
-import Data.Array(Array,listArray)
+import Foreign.C.String(CStringLen,withCStringLen,withCString)
+import Foreign.Storable(peekByteOff)
+import Data.Word(Word8)
+import Data.Array.IO(IOUArray,newArray,readArray,writeArray)
+import Data.Array(Array,listArray,bounds,elems)
 import System.IO.Unsafe(unsafePerformIO)
-import 
Text.Regex.Base.RegexLike(RegexMaker(..),RegexLike(..),RegexContext(..),MatchLength,MatchOffset)
+import 
Text.Regex.Base.RegexLike(RegexMaker(..),RegexLike(..),RegexContext(..),MatchLength,MatchOffset,MatchArray)
 import Text.Regex.Base.Impl(polymatch,polymatchM)
+import GHC.IO.Encoding(getForeignEncoding,textEncodingName)
+import Control.Monad(forM)
 
 instance RegexContext Regex String String where
   match = polymatch
@@ -72,7 +77,7 @@
   matchOnce regex str = unsafePerformIO $
 execute regex str = unwrap
   matchAll regex str = unsafePerformIO $ 
-withCStringLen str (wrapMatchAll regex) = unwrap
+withCStringLen str (wrapMatchAllFixPos regex) = unwrap
   matchCount regex str = unsafePerformIO $ 
 withCStringLen str (wrapCount regex) = unwrap
 
@@ -91,7 +96,7 @@
 -- string, or:
 --   'Just' an array of (offset,length) pairs where index 0 is 
whole match, and the rest are the captured subexpressions.
 execute regex str = do
-  maybeStartEnd - withCStringLen str (wrapMatch 0 regex)
+  maybeStartEnd - withCStringLen str (wrapMatchFixPos 0 regex)
   case maybeStartEnd of
 Right Nothing - return (Right Nothing)
 --  Right (Just []) - fail got [] back! -- should never happen
@@ -115,9 +120,94 @@
 ,getSub matchedStartStop
 ,drop stop str
 ,map getSub subStartStop)
-  maybeStartEnd - withCStringLen str (wrapMatch 0 regex)
+  maybeStartEnd - withCStringLen str (wrapMatchFixPos 0 regex)
   case maybeStartEnd of
 Right Nothing - return (Right Nothing)
 --  Right (Just []) - fail got [] back! -- should never happen
 Right (Just parts) - return . Right . Just . matchedParts $ parts
 Left err - return (Left err)
+
+
+
+-- | wrapMatchFixPos calls wrapMatch and fixes the string offsets
+-- in the result so that they are valid in the original Haskell string

Re: [Haskell-cafe] regex-pcre is not working with UTF-8

2012-08-22 Thread José Romildo Malaquias
On Tue, Aug 21, 2012 at 05:50:44PM -0300, José Romildo Malaquias wrote:
 On Tue, Aug 21, 2012 at 04:05:28PM +0100, Chris Kuklewicz wrote:
  I do not have time to test this myself right now.  But I will unravel my 
  code a
  bit for you.
  
   By November 2011 it worked without problems in my application. Now that
   I have resumed developping the application, I have been faced with this
   behaviour. As it used to work before, I believe it is a bug in
   regex-pcre or libpcre.
  
  I believe it may be problem in String - ByteString conversion.  The base
  library may have changed and your LOCALE information may be different or 
  may be
  being used differently by base.
  
   The (temporary) workaround I found is to convert the strings to
   byte-strings before matching, and then convert the results back to
   strings. With byte-strings it works well.
  
  That is an excellent sign that it is your LOCALE settings being picked up by
  GHC's base package, see explanation below.
[...]
 I have written an application to test those things. There are 2 source
 files: test.hs and seestr.c, which are attached.
 
 The test does the following:
 
1. shows the getForeignEncoding
 
2. uses a C function to show the characters from a String (using
   withCString) and from a ByteString (using useAsCString)
 
3. matches a PCRE regular expression using String and ByteString
 
 The test is run twice, with different LANG settings, and its output
 follows.
[...]
 As can be seen, regular expression matching does not work with
 en_US.UTF-8. But it works with en_US.ISO-8859-1.
 
 The test shows that withCString is working as expected too. This
 may suggest the problem is really with regex-pcre.

The previous tests were run on an gentoo linux with ghc-7.4.1.

I have also run the tests on Fedora 17 with ghc-7.0.4, which does not
have the bug. The sources are attached. The tests output follows:

   $ LANG=en_US.ISO-8859-1  ./test 
   testing with String
   code:   70, char: p
   code:   61, char: a
   code: ffed, char: 
   code:   73, char: s
   result: 4

   testing with ByteString
   code:   70, char: p
   code:   61, char: a
   code: ffed, char: 
   code:   73, char: s
   result: 4

   regex: pa�s:(.*)
   text : pa�s:Brasil
   String match : [[pa\237s:Brasil,Brasil]]
   ByteString match : [[pa\237s:Brasil,Brasil]]


   $ LANG=en_US.UTF-8  ./test
   testing with String
   code:   70, char: p
   code:   61, char: a
   code: ffed, char: 
   code:   73, char: s
   result: 4

   testing with ByteString
   code:   70, char: p
   code:   61, char: a
   code: ffed, char: 
   code:   73, char: s
   result: 4

   regex: país:(.*)
   text : país:Brasil
   String match : [[pa\237s:Brasil,Brasil]]
   ByteString match : [[pa\237s:Brasil,Brasil]]


Clearly witchCString has changed from ghc-7.0.4 to ghc-7.4.1. It seems
that With ghc-7.0.4 withCString does not obey the UTF-8 locale and
generates a latin1 C string.

Regards,

Romildo
module Main where

--import GHC.IO.Encoding (getForeignEncoding)
import Data.Bits (Bits((..)))
import Foreign.C.Types (CChar, CInt(..))
import Foreign.C.String
import Foreign.Ptr
import Text.Regex.PCRE
import qualified Data.ByteString.Char8 as B

foreign import ccall seestr
seestr :: Ptr CChar - IO CInt

seeStr :: String - IO Int
seeStr s = do ci - withCString s seestr
  return $ fromInteger (toInteger ci)

seeChar8 :: B.ByteString - IO Int
seeChar8 s = do ci - B.useAsCString s seestr
return $ fromInteger (toInteger ci)

test :: String - IO ()
test s = do putStrLn testing with String
x - seeStr s
putStrLn (result:  ++ show x)
putStrLn 
putStrLn testing with ByteString
x - seeChar8 (B.pack s)
putStrLn (result:  ++ show x)

testpcre re text = do putStrLn (regex:  ++ re)
  putStrLn (text :  ++ text)
  putStrLn (String match :  ++ show m1)
  putStrLn (ByteString match :  ++ show m2)
  where
c = defaultCompOpt .. compUTF8
e = defaultExecOpt
m1 = match (makeRegexOpts c e re :: Regex) text :: [[String]]
m2 = match (makeRegexOpts c e (B.pack re) :: Regex) (B.pack text) :: [[B.ByteString]]

main = do --enc - getForeignEncoding
  --putStrLn (getForeignEncoding:  ++ show enc)
  --putStrLn 
  test país
  putStrLn 
  testpcre país:(.*) país:Brasil

#include stdio.h

int seestr(const char *str)
{
   int counter = 0;

   while (*str)
   {
  printf(code: %8x, char: %c\n, *str, *str);
  counter ++;
  str ++;
   }

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


Re: [Haskell-cafe] regex-pcre is not working with UTF-8

2012-08-21 Thread José Romildo Malaquias
On Tue, Aug 21, 2012 at 10:25:53PM +0300, Konstantin Litvinenko wrote:
 On 08/18/2012 06:16 PM, José Romildo Malaquias wrote:
  Hello.
 
  It seems that the regex-pcre has a bug dealing with utf-8:
 
  I hope this bug can be fixed soon.
 
  Is there a bug tracker to report the bug? If so, what is it?
 
 You need something like that
 
 let pat = makeRegexOpts (compUTF8 .|. defaultCompOpt) defaultExecOpt 
 (@'(.+?)'@ :: B.ByteString)
 
 and than pat will match correctly.

The bug is related to String (not ByteString) in a UTF-8 locale.

Until it is fixed, I am using the workaround of converting the regular
expression and the text to ByteString, doing the matching, and then
converting the results back to String.

Romildo

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


[Haskell-cafe] Regex string replacement

2012-08-18 Thread José Romildo Malaquias
Hello.

I am looking for a substring replacement based on Perl like regular
expressions that would let me use part of the original string in the
replacement string. Something like:

   reReplace name is (.*)\\. hi \1! my name is john.

which would result in

   hy john!

Any help?

Romildo

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


Re: [Haskell-cafe] Regex string replacement

2012-08-18 Thread José Romildo Malaquias
On Sat, Aug 18, 2012 at 09:39:01AM -0300, Marco Túlio Pimenta Gontijo wrote:
 Hi Romildo.
 
 On Sat, Aug 18, 2012 at 9:18 AM, José Romildo Malaquias j.romi...@gmail.com
 wrote:
 (...)
  I am looking for a substring replacement based on Perl like regular
  expressions that would let me use part of the original string in the
  replacement string. Something like:
 
 reReplace name is (.*)\\. hi \1! my name is john.
 
  which would result in
 
 hy john!
 
 It's not exactly what you're looking for, but I'd simply do something like 
 this,
 using Text.Regex.TDFA or any other:
 
 let [[_, name]] = my name is john. =~ name is (.*)\\. in hi  ++
 name ++ !

Thanks for the tip. It was useful to solve my original problem.

Romildo

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


[Haskell-cafe] regex-pcre is not working with UTF-8

2012-08-18 Thread José Romildo Malaquias
Hello.

It seems that the regex-pcre has a bug dealing with utf-8:

   Prelude :m + Text.Regex.PCRE

   Prelude Text.Regex.PCRE país:Brasil =~ país:(.*) :: 
(String,String,String,[String])
   (,pa\237s:Brasil,,[rasil])

Notice the missing 'B' in the result of the regex matching.

With regex-posix this does not happen:

   Prelude :m + Text.Regex.Posix

   Prelude Text.Regex.Posix país:Brasil =~ país:(.*) 
::(String,String,String,[String])
   (,pa\237s:Brasil,,[Brasil])

I hope this bug can be fixed soon.

Is there a bug tracker to report the bug? If so, what is it?

Romildo

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


[Haskell-cafe] Annotaing abstract syntax trees

2012-05-08 Thread José Romildo Malaquias
Hello.

I am reading Martijn's MSc Thesis Generic Selections of
Subexpressions, where one can found some discussions about annotating
abstract syntax trees (AST).

In order to follow the discussion I wrote the attached Haskell program,
which is an interpreter for an simple typed expression language. The
Annotations package is used.

The expression pattern is represented by a single recursive data
type. Annotations are used for positions in the input source, and also
for the type of expressions and subexpressions.

I would like somebody to review the code and comment on it, as I am not
sure I am using the concepts right.

Also I would like the type checker to produce an expression annotated
with both positions and calculated types. Currently it discards the
position annotations. Any sugestions on how to modify it is welcome.

Next step is adding a new form of expression to introduce local variable
bindings.

After that I want to start working with ASTs represented by mutually
recursive data types. Then I will need multirec...

Romildo
{-# LANGUAGE FlexibleContexts #-}

module Main where

import Control.Applicative (Applicative(pure,(*)),($),($),(*))
import Data.Traversable (Traversable(traverse))
import Data.Foldable (Foldable(foldr))
import Text.Parsec hiding (chainl1)
import Data.Char (isDigit,isAlpha,isAlphaNum)
import Data.Tree (Tree(Node),drawTree)

import Annotations.F.Fixpoints
import Annotations.F.Annotated
import Annotations.Except

-- the goal is to implement an interpreter for a simple language of
-- typed expressions using annotations on recursive data types

-- type of expressions
data ExprType
  = NUMERIC
  | LOGIC
  deriving (Show)

-- value of an expression
data ExprValue
  = Numeric Double
  | Logic Bool
  deriving (Show)

-- identifiers are strings
type Id = String

-- binary operators used in expressions
data Op
  = Add | Sub | Mul | Div -- arithmetic
  | Eq | Ne | Gt | Ge | Lt | Le   -- relational
  | And | Or  -- logical
  deriving (Show)

-- pattern of an expression
data ExprF r
  = Num Double -- numeric literal
  | Log Bool   -- logical literal
  | Var Id -- variable
  | Bin Op r r -- binary operation
  deriving (Show)

-- mapping a function over an expression pattern
instance Functor ExprF where
  fmap _ (Num n)  = Num n
  fmap _ (Log b)  = Log b
  fmap _ (Var v)  = Var v
  fmap f (Bin op x y) = Bin op (f x) (f y)

-- traversing an expression pattern
instance Traversable ExprF where
  traverse _ (Num n)  = pure (Num n)
  traverse _ (Log b)  = pure (Log b)
  traverse _ (Var v)  = pure (Var v)
  traverse f (Bin op x y) = Bin op $ f x * f y

-- folding an expression pattern
instance Foldable ExprF where
  foldr _ z (Num _)  = z
  foldr _ z (Log _)  = z
  foldr _ z (Var _)  = z
  foldr f z (Bin op l r) = f l (f r z)

-- bare expressions
newtype Expr
  = Expr { runExpr :: Fix ExprF }
  deriving (Show)


-- range of source positions: used to delimit where something appeared
-- in a source input
data Range
  = Range SourcePos SourcePos

instance Show Range where
  show (Range p1 p2)
| n1 == n2  = if null n1
  then showLC lc1 ++ - ++ showLC lc2
  else showN n1 ++   ++ showLC lc1 ++ - ++ showLC lc2
| otherwise = showN n1 ++   ++ showLC lc1 ++ - ++ showN n2 ++   ++ showLC lc2
where
  n1 = sourceName p1
  lc1 = (sourceLine p1,sourceColumn p1)
  n2 = sourceName p2
  lc2 = (sourceLine p2,sourceColumn p2)
  showN n = \ ++ n ++ \
  showLC (l,c) = show l ++ : ++ show c

-- expressions annoted with positions
newtype PosExpr
  = PosExpr { runPosExpr :: Fix (Ann Range ExprF) }
  deriving (Show)

-- convert an expression to a rose tree of strings
-- this helps to visualize the expression structure
exprTree :: Algebra ExprF (Tree String)
exprTree (Num n) = Node (Num:  ++ show n) []
exprTree (Log b) = Node (Log:  ++ show b) []
exprTree (Var v) = Node (Var:  ++ v) []
exprTree (Bin op l r) = Node (Bin:  ++ show op) [l,r]

-- convert an annotated expression to a tree of strings
-- this helps to visualize the annotated expression structure
annExprTree :: Show a = Algebra (Ann a ExprF) (Tree String)
annExprTree (Ann z expr) =
  case expr of
Num n  - Node (annot (Num:  ++ show n)) []
Log b  - Node (annot (Log:  ++ show b)) []
Var v  - Node (annot (Var:  ++ v)) []
Bin op l r - Node (annot (Bin:  ++ show op)) [l,r]
  where
annot x = x ++   ++ show z

-- a memory is just an association list between
-- variable names and values
type Memory = [(Id,ExprValue)]

-- an algebra to find the value of an expression annotated with
-- positions, given a memory
exprEval :: Memory - ErrorAlgebra ExprF String ExprValue
exprEval _ (Num n) = Right (Numeric n)
exprEval _ (Log b) = Right (Logic b)
exprEval m (Var v) = case lookup v m of
   Just x  - Right x;
   Nothing - Left (undefined 

[Haskell-cafe] Parameters and patterns

2011-10-01 Thread José Romildo Malaquias
Hello.

When studing programming languages I have learned that parameter is a
variable (name) that appears in a function definition and denotes the
value to which the function is applied when the function is called.

Argument is the value to which the function is applied.

The parameter allows the manipulation of the argument in the body of the
funtion definition in order to produce the result.

Now I am not sure how to apply these concepts to Haskell, as Haskell
uses pattern matching to deal with argument passing to functions.

For instance, in the definition

  f x = 2 * x + 1

x is a parameter, and in the application

  f 34

34 is an argument.

But in the definition

  g (_:xs) = xs

what is the parameter of the function g? Is it the pattern (_:xs)? If so
then a parameter is not necessarily a variable anymore, and that seems
very strange. And what is xs? Is it a parameter, although it does not
denote the value to which the function is aplied, but just part of it?

I am writing some slides to use in my functional programming classes,
but I am not sure how to deal with these terms.

Any comments?

Romildo
--
DECOM - ICEB - UFOP

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


[Haskell-cafe] ghc-mtl and ghc-7.2.1

2011-09-07 Thread José Romildo Malaquias
Hello.

In order to compile ghc-mtl-1.0.1.0 (the latest released version) with
ghc-7.2.1, I would apply the attached patch, which removes any
references to WarnLogMonad.

ghc-7.2.1 does not have the monad WarnLogMonad anymore.

As I do not know the details of the GHC api, I am not sure if this is
enough to use ghc-mtl with ghc-7.2.1.

I want ghc-mtl in order do build lambdabot.

Any thoughts?

Romildo
diff -ur ghc-mtl-1.0.1.0.orig/Control/Monad/Ghc.hs 
ghc-mtl-1.0.1.0/Control/Monad/Ghc.hs
--- ghc-mtl-1.0.1.0.orig/Control/Monad/Ghc.hs   2011-09-07 07:38:20.297885351 
-0300
+++ ghc-mtl-1.0.1.0/Control/Monad/Ghc.hs2011-09-07 08:31:44.132815320 
-0300
@@ -12,13 +12,15 @@
 import Control.Monad.CatchIO
 
 import qualified GHC ( runGhc, runGhcT )
-import qualified HscTypes   as GHC
+-- import qualified HscTypes   as GHC
+import qualified GhcMonad   as GHC
 import qualified MonadUtils as GHC
 import qualified Exception  as GHC
 
 newtype Ghc a = Ghc (GHC.Ghc a)
 deriving (Functor, Monad,
-  GHC.WarnLogMonad, GHC.ExceptionMonad, GHC.MonadIO, GHC.GhcMonad)
+  -- GHC.WarnLogMonad, 
+  GHC.ExceptionMonad, GHC.MonadIO, GHC.GhcMonad)
 
 instance MTL.MonadIO Ghc where
 liftIO = GHC.liftIO
@@ -56,9 +58,9 @@
 gblock   = block
 gunblock = unblock
 
-instance MTL.MonadIO m = GHC.WarnLogMonad (GhcT m) where
-setWarnings = GhcT . GHC.setWarnings
-getWarnings = GhcT GHC.getWarnings
+-- instance MTL.MonadIO m = GHC.WarnLogMonad (GhcT m) where
+-- setWarnings = GhcT . GHC.setWarnings
+-- getWarnings = GhcT GHC.getWarnings
 
 instance (Functor m, MonadCatchIO m) = GHC.GhcMonad (GhcT m) where
 getSession = GhcT GHC.getSession
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Subtitles for Programming in Haskell videos

2011-08-13 Thread José Romildo Malaquias
Hello.

Are there subtitles (in English or Portuguese) for the video lectures[1]
given by Erik Meijer using the book Programming in Haskell, by Graham
Hutton?

[1] http://www.cs.nott.ac.uk/~gmh/book.html

Romildo

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


Re: [Haskell-cafe] error with nanocurses-1.5.2

2011-07-10 Thread José Romildo Malaquias
On Sat, Jul 09, 2011 at 01:59:12PM -0300, José Romildo Malaquias wrote:
 Hello.
 
 When trying to install nanocurses-1.5.2 on my Fedora Linux system, I am
 getting the following error:
 
 $ cabal install nanocurses
 Resolving dependencies...
 Configuring nanocurses-1.5.2...
 Preprocessing library nanocurses-1.5.2...
 In file included from Curses.hsc:42:0:
 cbits/utils.h:7:20: fatal error: config.h: No such file or directory
 compilation terminated.
 compiling dist/build/UI/Nanocurses/Curses_hsc_make.c failed (exit code 1)
 command was: /usr/bin/gcc -c dist/build/UI/Nanocurses/Curses_hsc_make.c
 -o dist/build/UI/Nanocurses/Curses_hsc_make.o -fno-stack-protector
 -fno-stack-protector -D__GLASGOW_HASKELL__=700 -Dlinux_BUILD_OS
 -Dlinux_HOST_OS -Dx86_64_BUILD_ARCH -Dx86_64_HOST_ARCH -Icbits
 -I/usr/lib64/ghc-7.0.2/unix-2.4.2.0/include
 -I/usr/lib64/ghc-7.0.2/bytestring-0.9.1.10/include
 -I/usr/lib64/ghc-7.0.2/base-4.3.1.0/include
 -I/usr/lib64/ghc-7.0.2/include -I/usr/lib64/ghc-7.0.2/include/
 cabal: Error: some packages failed to install:
 nanocurses-1.5.2 failed during the building phase. The exception was:
 ExitFailure 1
 
 It would be nice to have this buf fixed.

The attached patch fixes the compilation issues. Basically it changes
the build type from simple to configure in the cabal file, and it
renames the function getline in cbits/utils.{h,c} to mygetline.

If appropriate, please release a new version with the fixes.

Romildo
diff -ur nanocurses-1.5.2.orig/cbits/utils.c nanocurses-1.5.2/cbits/utils.c
--- nanocurses-1.5.2.orig/cbits/utils.c 2008-05-18 18:09:23.0 -0300
+++ nanocurses-1.5.2/cbits/utils.c  2011-07-10 11:23:02.082418889 -0300
@@ -38,7 +38,7 @@
 }
 
 /* sometimes we write to the wrong spot after a refresh */
-int getline(char *buf, FILE *hdl) { 
+int mygetline(char *buf, FILE *hdl) { 
 char *p;
 int c;
 
@@ -52,7 +52,7 @@
 
 while (c != '\n') 
 c = getc(hdl);
-return getline(buf,hdl);/* read another line */
+return mygetline(buf,hdl);/* read another line */
 
 /* normal packet */
 } else {
@@ -60,7 +60,7 @@
 
 p = fgets(buf+1, BUFLEN-1, hdl);  /* read rest of line */
 if (p == NULL) {
-//  perror(getline failed\n);
+//  perror(mygetline failed\n);
 return (-1);
 }
 buf[0] = c; /* drop the '@' */
diff -ur nanocurses-1.5.2.orig/cbits/utils.h nanocurses-1.5.2/cbits/utils.h
--- nanocurses-1.5.2.orig/cbits/utils.h 2008-05-18 18:09:23.0 -0300
+++ nanocurses-1.5.2/cbits/utils.h  2011-07-10 11:22:18.180418821 -0300
@@ -12,5 +12,5 @@
 
 /* packed string IO */
 FILE *openfd(int fd);
-int getline(char *buf, FILE *hdl);
+int mygetline(char *buf, FILE *hdl);
 void forcenext(void);
diff -ur nanocurses-1.5.2.orig/nanocurses.cabal 
nanocurses-1.5.2/nanocurses.cabal
--- nanocurses-1.5.2.orig/nanocurses.cabal  2008-05-18 18:09:23.0 
-0300
+++ nanocurses-1.5.2/nanocurses.cabal   2011-07-10 11:21:43.256418788 -0300
@@ -21,7 +21,7 @@
  (It does not differ significantly from Hmp3's Curses 
binding, as the Curses.hsc
  in Nanocurses is essentially extracted from Hmp3.)
 
-build-type: Simple
+build-type: Configure
 build-depends:  base3, unix, bytestring
 tested-with:GHC==6.8.2
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] unbuffered raw keyboard input on Windows

2011-07-10 Thread José Romildo Malaquias
On Wed, Jul 06, 2011 at 02:48:47PM -0700, David Barbour wrote:
 You could try the SDL package to support user input.

Unfortunatly it does not run on a terminal.

 2011/7/6 José Romildo Malaquias j.romi...@gmail.com
 
  Hello.
 
  I want to write a Haskell console application (a game) in ghc where the
  user will interact using the keyboard. I need to read the keys as soon
  as they are typed and without echoing to the console.
 
  Although Haskell provides this capability in the standard libraries
  (using hSetEcho and hSetBuffering from System.IO), it does not work on
  Windows due to a bug (http://hackage.haskell.org/trac/ghc/ticket/2189).
 
  I have tried installing packages like vty, hscurses, and ncurses, but
  they did not install on Windows.
 
  Which workarounds are available for that?
 
  Romildo
 
  ___
  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] unbuffered raw keyboard input on Windows

2011-07-10 Thread José Romildo Malaquias
On Wed, Jul 06, 2011 at 06:46:32PM -0300, José Romildo Malaquias wrote:
 Hello.
 
 I want to write a Haskell console application (a game) in ghc where the
 user will interact using the keyboard. I need to read the keys as soon
 as they are typed and without echoing to the console.
 
 Although Haskell provides this capability in the standard libraries
 (using hSetEcho and hSetBuffering from System.IO), it does not work on
 Windows due to a bug (http://hackage.haskell.org/trac/ghc/ticket/2189).
 
 I have tried installing packages like vty, hscurses, and ncurses, but
 they did not install on Windows.

Considering that there are curses for Windows (pdcurses[1] and the
latest ncurses[2]), would it be too difficult to port such libraries to
Windows?

[1] http://pdcurses.sourceforge.net/
[2] http://www.gnu.org/software/ncurses/

Romildo

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


[Haskell-cafe] unbuffered raw keyboard input on Windows

2011-07-06 Thread José Romildo Malaquias
Hello.

I want to write a Haskell console application (a game) in ghc where the
user will interact using the keyboard. I need to read the keys as soon
as they are typed and without echoing to the console.

Although Haskell provides this capability in the standard libraries
(using hSetEcho and hSetBuffering from System.IO), it does not work on
Windows due to a bug (http://hackage.haskell.org/trac/ghc/ticket/2189).

I have tried installing packages like vty, hscurses, and ncurses, but
they did not install on Windows.

Which workarounds are available for that?

Romildo

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


[Haskell-cafe] GHC and MinGW

2011-02-12 Thread José Romildo Malaquias
Hello.

How do I make ghc use my installation of MinGW on Windows? I have
ghc-7.0.1 installed and the latest MinGW packages. I want ghc to
automatically find libraries installed by the MinGW installer.

Currently I am getting the error with my application:

Linking Gui.exe ...
C:\Program 
Files\Haskell\iconv-0.4.1.0\ghc-7.0.1/libHSiconv-0.4.1.0.a(hsiconv.o):hsiconv.c:(.text+0x8):
 undefined reference to `libiconv_open'

where libiconv has been installed with the command

mingw-get install mingw32-libiconv

and the library is available at c:/devel/MinGW/lib/


Romildo

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


Re: [Haskell-cafe] GHC and MinGW

2011-02-12 Thread José Romildo Malaquias
On Sat, Feb 12, 2011 at 01:12:22PM -0200, José Romildo Malaquias wrote:
 Hello.
 
 How do I make ghc use my installation of MinGW on Windows? I have
 ghc-7.0.1 installed and the latest MinGW packages. I want ghc to
 automatically find libraries installed by the MinGW installer.
 
 Currently I am getting the error with my application:
 
 Linking Gui.exe ...
 C:\Program 
 Files\Haskell\iconv-0.4.1.0\ghc-7.0.1/libHSiconv-0.4.1.0.a(hsiconv.o):hsiconv.c:(.text+0x8):
  undefined reference to `libiconv_open'
 
 where libiconv has been installed with the command
 
 mingw-get install mingw32-libiconv
 
 and the library is available at c:/devel/MinGW/lib/

Looking at iconv.cabal from the iconv package, I found this:

  if os(darwin) || os(freebsd)
-- on many systems the iconv api is part of the standard C library
-- but on some others we have to link to an external libiconv:
extra-libraries: iconv

So the problem is that the extra library iconv is not been considered
for the windows os.

Changing the line above to consider the windows os solves the problem:

  if os(darwin) || os(freebsd) || os(windows)
-- on many systems the iconv api is part of the standard C library
-- but on some others we have to link to an external libiconv:
extra-libraries: iconv


Therefore the mantainer of the iconv package should fix this issue.

Romildo

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


Re: [Haskell-cafe] regex libraries: matching operators (=~) and (=~~) are not methods

2010-12-04 Thread José Romildo Malaquias
On Tue, Nov 30, 2010 at 05:50:02PM -0200, José Romildo Malaquias wrote:
 Hello.
 
 When learning how to use the many regular expression libraries for
 Haskell, I noticed that the interface API from the regex-base package
 introduces several high level operations that are abstracted from the
 implementations (backends). This is done by means of classes.
 
 For instance, there are methods for compiling an external representation
 (like a string or a bytestring) into a regular expression. There are
 also methods for matching a regular expression and some text (like a
 string, or a bytestring).
 
 But the most high level functions for pattern matching using regular
 expressions, (=~) and (=~~), are not defined as methods in a class.
 They are independent functions defined for each backend in the
 corresponding package.
 
 This prevents one from writing a general function using these operators
 without deliberately choosing a regex backend.
 
 Why are those operators not defined as methods, like all other relevant
 functions?

I think I have found the reason for that.

Let's consider the operator (=~ ). Its type in the Text.Regex.TDFA is:

( RegexMaker Regex CompOption ExecOption source
, RegexContext Regex source1 target
) =
source1 - source - target

It has two arguments: the text and the regex (in a textual format) used
in matching. They may be both of type String, or ByteString, for
instance. Therefore there is no way to infer which regex engine to use
when the regex text is compiled to an internal format. So the regex
engine cannot be deduced automatically from the arguments. Because of
that each regex backend has to define his own function, and a class is
of no help.

Romildo

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


[Haskell-cafe] regex libraries: matching operators (=~) and (=~~) are not methods

2010-11-30 Thread José Romildo Malaquias
Hello.

When learning how to use the many regular expression libraries for
Haskell, I noticed that the interface API from the regex-base package
introduces several high level operations that are abstracted from the
implementations (backends). This is done by means of classes.

For instance, there are methods for compiling an external representation
(like a string or a bytestring) into a regular expression. There are
also methods for matching a regular expression and some text (like a
string, or a bytestring).

But the most high level functions for pattern matching using regular
expressions, (=~) and (=~~), are not defined as methods in a class.
They are independent functions defined for each backend in the
corresponding package.

This prevents one from writing a general function using these operators
without deliberately choosing a regex backend.

Why are those operators not defined as methods, like all other relevant
functions?

Romildo

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


[Haskell-cafe] version of findIndex that works with a monadic predicate

2010-11-26 Thread José Romildo Malaquias
Hello.

I need a function findIndexM, similar to findIndex from the standard
module Data.List, but which works with a monadic predicate to test list
elements.

findIndex :: (a - Bool) - [a] - Maybe Int

findIndexM :: (Monad m, Num a) = (t - m Bool) - [t] - m (Maybe a)

findIndexM p xs = go 0 xs
  where
go _ [] = return Nothing
go n (x:xs) = do res - p x
 if res then return (Just n) else go (n+1) xs


How can this function be rewritten using combinators?


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


[Haskell-cafe] Wrong Package-URL in regex-tdfa.cabal

2010-11-23 Thread José Romildo Malaquias
Hello.

The cabal file for the regex-tddfa-1.1.6 package seems to have an
invalid URL for the Package-URL field:

Package-URL: http://darcs.haskell.org/packages/regex-unstable/regex-tdfa/

It should be fixed.

Regards.

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


[Haskell-cafe] looking for tagsoup-parsec examples

2010-11-22 Thread José Romildo Malaquias
Hello.

I am looking for some examples of code using Text.HTML.TagSoup.Parsec,
from the tagsoup-parsec package.

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


Re: [Haskell-cafe] looking for tagsoup-parsec examples

2010-11-22 Thread José Romildo Malaquias
On Mon, Nov 22, 2010 at 02:20:22PM -0200, José Romildo Malaquias wrote:
 
 I am looking for some examples of code using Text.HTML.TagSoup.Parsec,
 from the tagsoup-parsec package.

In an attempt to learn how to use tagsoup together with parsec in order
to do web scrapping, I rewrote the application that displays the
Haskell.org hit count, explained in the Drinking TagSoup by Example
tutorial [1]. The source code is attached.

First I tried to use tagsoup-parsec [2], but it was not too
helpful. Therefore I wrote a few parser combinators myself (inspired by
tagsoup-parsec, and the TagSoup, meet Parsec! blog post [3].

I am posting the program here so that other Haskell programmers can
comment on it.

I would like also to do some suggestions to the author of
tagsoup-parsec:

a) export more functions, like tagEater, which may be needed in order to
define new parsers or parser combinators; I needed them, but they were
no usable because they are not exported;

b) add more basic parsers and parser combinators (at least the ones I
have defined in my program).

c) add some examples

d) use parsec version 3


[1] http://community.haskell.org/~ndm/darcs/tagsoup/tagsoup.htm
[2] http://hackage.haskell.org/package/tagsoup-parsec
[3] http://therning.org/magnus/archives/367

Regards,

Romildo
module Main (main) where

import Text.Parsec hiding (satisfy)
import Text.HTML.TagSoup (parseTags, Tag(TagText), (~==))
import Text.HTML.Download (openURL)
import Data.Char (isDigit)
import Data.List (findIndex)

main =
  do src - openURL http://www.haskell.org/haskellwiki/Haskell;
 let x = tagParse counter (parseTags src)
 putStrLn $ haskell.org has been hit  ++ show x ++  times


counter =
  do skipTo (tag div class=printfooter)
 count 2 (skipTo (tag p))
 s - tagText 
 let ss = words s
 case findIndex (== times.) ss of
   Just i - let num = ss !! (i - 1)
 in return (read (filter isDigit num) :: Int)
   Nothing - parserZero


--
-- tag parser library
--

tagParse p ts =
  either ( error . show ) id $ parse p tagsoup ts

tagEater matcher =
  tokenPrim show (\pos t ts - incSourceLine pos 1) matcher

anyTag = tagEater Just

satisfy f =
  tagEater (\t - if f t then Just t else Nothing)

tag t = satisfy (~== t) ? show t

tagText str = do TagText x - tag (TagText str)
 return x

skipTo p = try p | (anyTag  skipTo p)

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


[Haskell-cafe] Tooltips on tree view rows

2010-11-21 Thread José Romildo Malaquias
Hello.

I need the gtk_tree_view_set_tooltip_column from Gtk+, but it seems tht
it has not been ported to gtk2hs. Is it the case?

How can I easily add tooltips to rows in a TreeView?

Regards,

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


[Haskell-cafe] Downloading web page in Haskell

2010-11-20 Thread José Romildo Malaquias
In order to download a given web page, I wrote the attached program. The
problem is that the page is not being full downloaded. It is being
somehow intettupted.

Any clues on how to solve this problem?

Romildo
module Main where

import Network.HTTP (getResponseBody, getRequest, simpleHTTP)

openURL x = simpleHTTP (getRequest x) = getResponseBody

main =
  do src - openURL http://www.adorocinema.com/common/search/search_by_film/?criteria=Bourne;
 writeFile test.html src
 putStrLn src
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Downloading web page in Haskell

2010-11-20 Thread José Romildo Malaquias
On Sat, Nov 20, 2010 at 10:26:49PM +0100, Daniel Fischer wrote:
 On Saturday 20 November 2010 21:47:52, Don Stewart wrote:
   2010/11/20 José Romildo Malaquias j.romi...@gmail.com:
In order to download a given web page, I wrote the attached program.
The problem is that the page is not being full downloaded. It is
being somehow intettupted.
   
Any clues on how to solve this problem?
 
  FWIW, with this url, I get the same problem using the Curl package
 
 Just for the record, wget also gets a truncated (at the same point) file, 
 so it's not a Haskell problem.

Web browsers like Firefox and Opera does not seem to have the same
problem with this web page.

I would like to be able to download this page from Haskell.

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


[Haskell-cafe] ghc panic when compiling blaze-builder

2010-11-20 Thread José Romildo Malaquias
When compiling blaze-builder-0.2.0.1 with ghc-7.0.1 on my ~amd64 gentoo
system, I am getting the shown below.

Any clues?

Romildo


[...]
Building blaze-builder-0.2.0.1...
[1 of 8] Compiling Blaze.ByteString.Builder.Internal ( 
Blaze/ByteString/Builder/Internal.hs, 
dist/build/Blaze/ByteString/Builder/Internal.o )
ghc: panic! (the 'impossible' happened)
  (GHC version 7.0.1 for x86_64-unknown-linux):
dsLet: unlifted
AbsBinds
[b{tv aUH} [sk]]
[]
[pe{v axd} [lid] = [b{tv aUH} [sk]] pe{v aUG} [lid]]
  pe{v axd} [lid]
:: forall b{tv aUH} [sk]. base:GHC.Ptr.Ptr{tc 33A} b{tv aUH} [sk]
  [LclId]
  { {273:19-54}
{273:19-54}
!((pe{v aUG} [lid] :: base:GHC.Ptr.Ptr{tc 33A} b{tv aUH} [sk]))
  = {273:30-54}
{273:33-41}
(base:GHC.Ptr.plusPtr{v r4X} [gid]) @ base:GHC.Word.Word8{tc 32U}
@ b{tv aUH} [sk]
  pf{v axc} [lid] firstBufSize{v arR} [lid] }
EvBinds{{}}
base:GHC.Base.={v 01P} [gid[ClassOp]]
  @ ntghc-prim:GHC.Types.IO{tc 32I}
  $dMonad{v aUI} [lid]
  @ blaze-builder-0.2.0.1:Blaze.ByteString.Builder.Internal.BuildSignal{tc 
rre}
  @ bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5}
  (step0{v arY} [lid]
 pf{v axc} [lid] (pe{v axd} [lid] @ base:GHC.Word.Word8{tc 32U}))
  (\ (next{v axT} [lid]
:: 
blaze-builder-0.2.0.1:Blaze.ByteString.Builder.Internal.BuildSignal{tc rre}) -
 let {
   ds_d15b{v} [lid]
 :: 
blaze-builder-0.2.0.1:Blaze.ByteString.Builder.Internal.BuildSignal{tc rre}
   [LclId]
   ds_d15b{v} [lid] = next{v axT} [lid] } in
 case ds_d15b{v} [lid] {ghc-prim:GHC.Types.IO{tc 32I}
  
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5}}
 of (wild_B1{v} [lid]
   :: 
blaze-builder-0.2.0.1:Blaze.ByteString.Builder.Internal.BuildSignal{tc rre}) {
   blaze-builder-0.2.0.1:Blaze.ByteString.Builder.Internal.Done{d rrk} 
(rb_d15l{v} [lid]

  :: ghc-prim:GHC.Prim.Addr#{(w) tc 33}) -
 let {
   pf'{v axU} [lid]
 :: base:GHC.Ptr.Ptr{tc 33A} base:GHC.Word.Word8{tc 32U}
   [LclId]
   pf'{v axU} [lid] =
 base:GHC.Ptr.Ptr{v rcP} [gid[DataCon]]
   @ base:GHC.Word.Word8{tc 32U} rb_d15l{v} [lid] } in
 let {
   fail_d15c{v} [lid]
 :: ghc-prim:GHC.Prim.State#{(w) tc 32q}
  ghc-prim:GHC.Prim.RealWorld{(w) tc 31E}
- ghc-prim:GHC.Types.IO{tc 32I}
 
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5}
   [LclId]
   fail_d15c{v} [lid] =
 \ (ds_d15d{v} [lid]
  :: ghc-prim:GHC.Prim.State#{(w) tc 32q}
   ghc-prim:GHC.Prim.RealWorld{(w) tc 31E}) -
   base:GHC.Base.${v 019} [gid]
 @ 
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5}
 @ (ghc-prim:GHC.Types.IO{tc 32I}
  
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5})
 (base:GHC.Base.return{v 01T} [gid[ClassOp]]
@ ntghc-prim:GHC.Types.IO{tc 32I}
$dMonad{v aUN} [lid]
@ 
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5})
 
(bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.$WChunk{v reF} 
[gid[DataConWrapper]]
(mkbs{v axe} [lid] @ base:GHC.Word.Word8{tc 32U} pf'{v 
axU} [lid])
k{v arT} [lid]) } in
 case base:GHC.Classes.=={v 01L} [gid[ClassOp]]
@ (base:GHC.Ptr.Ptr{tc 33A} base:GHC.Word.Word8{tc 32U})
$dEq{v aUK} [lid]
pf'{v axU} [lid]
pf{v axc} [lid] {ghc-prim:GHC.Types.IO{tc 32I}
   
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5}}
 of (wild_B1{v} [lid] :: ghc-prim:GHC.Bool.Bool{(w) tc 3c}) {
   ghc-prim:GHC.Bool.False{(w) d 68} -
 fail_d15c{v} [lid] ghc-prim:GHC.Prim.realWorld#{(w) v 0o} 
[gid];
   ghc-prim:GHC.Bool.True{(w) d 6u} -
 base:GHC.Base.return{v 01T} [gid[ClassOp]]
   @ ntghc-prim:GHC.Types.IO{tc 32I}
   $dMonad{v aUL} [lid]
   @ 
bytestring-0.9.1.8:Data.ByteString.Lazy.Internal.ByteString{tc rg5}
   k{v arT} [lid]
 };
   blaze-builder-0.2.0.1:Blaze.ByteString.Builder.Internal.BufferFull{d 
rri} (rb_d15n{v} [lid]

:: 

Re: [Haskell-cafe] Tiger compiler in Haskell: annotating abstract syntax tree

2010-07-23 Thread José Romildo Malaquias
On Tue, Jul 20, 2010 at 09:17:15AM +0200, José Pedro Magalhães wrote:
 
 2010/7/19 José Romildo Malaquias j.romi...@gmail.com
 
 
  I am writing here to ask suggestions on how to annotate an ast with
  types (or any other information that would be relevant in a compiler
  phase) in Haskell.
 
 Indeed I would suggest the method described in our paper:
 
 Martijn van Steenbergen, José Pedro Magalhães, and Johan Jeuring. Generic
 selections of subexpressions.
 Paper link: http://dreixel.net/research/pdf/gss_draft.pdf
 Related hackage package: http://hackage.haskell.org/package/Annotations

Annotations-0.1 requires base ==4.1.* and parsec ==3.0.*, but I have
base-4.2.0.2 and parsec-3.1.0 on my Gentoo Linux system. Would it work
with these new versions of base and parsec?

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


[Haskell-cafe] List manager and duplicate copies of messsages

2010-07-21 Thread José Romildo Malaquias
Hello.

I have noticed that I do not receive duplicate copies of messages from
haskell-cafe, although Avoid duplicate copies of messages? is set to
No in the mailing list membership configuration.

I want the copies because I archive all the mailing list messages with
procmail based on the X-BeenThere header line.

Has anybody else seen this behaviour, or am I missing anything?

Is there any problems with the mailing list manager?

Regards,

Romildo
--
Computer Science Department
Universidade Federal de Ouro Preto, Brasil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List manager and duplicate copies of messsages

2010-07-21 Thread José Romildo Malaquias
On Wed, Jul 21, 2010 at 02:42:37PM +0200, Martijn van Steenbergen wrote:
 On 7/21/10 12:48, José Romildo Malaquias wrote:
  Hello.
 
  I have noticed that I do not receive duplicate copies of messages from
  haskell-cafe, although Avoid duplicate copies of messages? is set to
  No in the mailing list membership configuration.
 
  I want the copies because I archive all the mailing list messages with
  procmail based on the X-BeenThere header line.
 
  Has anybody else seen this behaviour, or am I missing anything?
 
  Is there any problems with the mailing list manager?
 
 You're using gmail. See:
 
 http://www.google.com/support/forum/p/gmail/thread?tid=2d5dbc1f28270634

I am talking about answers to messages that I post to haskell-cafe. If
somebody reply to my message sending it both to the mailing list and to
me, I am receiving only the copy sent to me. The one sent to the mailing
list (with the X-BeenThere in the header used for archiving) is not
arriving to my inbox.

It works with other mailing lists I subscribe with this same email
address from gmail.

Nontheless I will subscribe with another email address not from gmail
and see if it works as expected.

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


[Haskell-cafe] Test. Ignore.

2010-07-21 Thread José Romildo Malaquias
Please, ignore this message.

Romildo

-- 
___
Surf the Web in a faster, safer and easier way:
Download Opera 9 at http://www.opera.com

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


Re: [Haskell-cafe] Test. Ignore.

2010-07-21 Thread José Romildo Malaquias
On Wed, Jul 21, 2010 at 12:53:53PM -0300, José Romildo Malaquias wrote:
 Please, ignore this message.

Replying to the list and to the sender, to see if he gets both messages
using a non gmail account.

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


Re: [Haskell-cafe] Test. Ignore.

2010-07-21 Thread José Romildo Malaquias
 - Original Message -
 From: José Romildo Malaquias j.romi...@gmail.com
 To: José Romildo Malaquias romi...@operamail.com
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Test. Ignore.
 Date: Wed, 21 Jul 2010 13:01:03 -0300
 
 
 On Wed, Jul 21, 2010 at 12:53:53PM -0300, José Romildo Malaquias wrote:
  Please, ignore this message.
 
 Replying to the list and to the sender, to see if he gets both messages
 using a non gmail account.

I confirm that I received only one copy of the above message, that was sent 
directly to my email address at operamail.com. I did not receive any copy from 
the mailing list manager.

Romildo (at opera.com)

-- 
___
Surf the Web in a faster, safer and easier way:
Download Opera 9 at http://www.opera.com

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


Re: [Haskell-cafe] Test. Ignore.

2010-07-21 Thread José Romildo Malaquias
 - Original Message -
 From: José Romildo Malaquias romi...@operamail.com
 To: José Romildo Malaquias j.romi...@gmail.com
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Test. Ignore.
 Date: Wed, 21 Jul 2010 13:09:16 -0300
 
 
  - Original Message -
  From: José Romildo Malaquias j.romi...@gmail.com
  To: José Romildo Malaquias romi...@operamail.com
  Cc: haskell-cafe@haskell.org
  Subject: Re: [Haskell-cafe] Test. Ignore.
  Date: Wed, 21 Jul 2010 13:01:03 -0300
 
 
  On Wed, Jul 21, 2010 at 12:53:53PM -0300, José Romildo Malaquias wrote:
   Please, ignore this message.
 
  Replying to the list and to the sender, to see if he gets both messages
  using a non gmail account.
 
 I confirm that I received only one copy of the above message, that 
 was sent directly to my email address at operamail.com. I did not 
 receive any copy from the mailing list manager.
 
 Romildo (at opera.com)

That was expected, as by default the Avoid duplicate copies of messages? 
option is set to Yes in the mailing list membership configuration. Now I have 
just set it to No, and I expect to receive both copies next time someone from 
the mailing list replies to all to one of my messages.

Romildo at operamail.com

-- 
___
Surf the Web in a faster, safer and easier way:
Download Opera 9 at http://www.opera.com

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


Re: [Haskell-cafe] Test. Ignore.

2010-07-21 Thread José Romildo Malaquias
On Wed, Jul 21, 2010 at 01:25:19PM -0300, José Romildo Malaquias wrote:
  - Original Message -
  From: José Romildo Malaquias romi...@operamail.com
  To: José Romildo Malaquias j.romi...@gmail.com
  Cc: haskell-cafe@haskell.org
  Subject: Re: [Haskell-cafe] Test. Ignore.
  Date: Wed, 21 Jul 2010 13:09:16 -0300
  
  
   - Original Message -
   From: José Romildo Malaquias j.romi...@gmail.com
   To: José Romildo Malaquias romi...@operamail.com
   Cc: haskell-cafe@haskell.org
   Subject: Re: [Haskell-cafe] Test. Ignore.
   Date: Wed, 21 Jul 2010 13:01:03 -0300
  
  
   On Wed, Jul 21, 2010 at 12:53:53PM -0300, José Romildo Malaquias wrote:
Please, ignore this message.
  
   Replying to the list and to the sender, to see if he gets both messages
   using a non gmail account.
  
  I confirm that I received only one copy of the above message, that 
  was sent directly to my email address at operamail.com. I did not 
  receive any copy from the mailing list manager.
  
  Romildo (at opera.com)
 
 That was expected, as by default the Avoid duplicate copies of
 messages? option is set to Yes in the mailing list membership
 configuration. Now I have just set it to No, and I expect to receive
 both copies next time someone from the mailing list replies to all
 to one of my messages.
 
 Romildo at operamail.com

Replying to all.

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


Re: [Haskell-cafe] Test. Ignore.

2010-07-21 Thread José Romildo Malaquias

 - Original Message -
 From: José Romildo Malaquias j.romi...@gmail.com
 To: José Romildo Malaquias romi...@operamail.com
 Cc: haskell-cafe@haskell.org
 Subject: Re: [Haskell-cafe] Test. Ignore.
 Date: Wed, 21 Jul 2010 13:33:34 -0300
 
 
 On Wed, Jul 21, 2010 at 01:25:19PM -0300, José Romildo Malaquias wrote:
   - Original Message -
   From: José Romildo Malaquias romi...@operamail.com
   To: José Romildo Malaquias j.romi...@gmail.com
   Cc: haskell-cafe@haskell.org
   Subject: Re: [Haskell-cafe] Test. Ignore.
   Date: Wed, 21 Jul 2010 13:09:16 -0300
  - Original Message -
From: José Romildo Malaquias j.romi...@gmail.com
To: José Romildo Malaquias romi...@operamail.com
Cc: haskell-cafe@haskell.org
Subject: Re: [Haskell-cafe] Test. Ignore.
Date: Wed, 21 Jul 2010 13:01:03 -0300
   
   
On Wed, Jul 21, 2010 at 12:53:53PM -0300, José Romildo Malaquias 
wrote:
 Please, ignore this message.
   
Replying to the list and to the sender, to see if he gets both messages
using a non gmail account.
I confirm that I received only one copy of the above message, 
  that  was sent directly to my email address at operamail.com. I 
  did not  receive any copy from the mailing list manager.
Romildo (at opera.com)
 
  That was expected, as by default the Avoid duplicate copies of
  messages? option is set to Yes in the mailing list membership
  configuration. Now I have just set it to No, and I expect to receive
  both copies next time someone from the mailing list replies to all
  to one of my messages.
 
  Romildo at operamail.com
 
 Replying to all.
 
 Romildo at gmail.com

Well, romildo at operamail.com received both copies of the message. So the list 
manager worked as expected.

Romildo at operamail.com

-- 
___
Surf the Web in a faster, safer and easier way:
Download Opera 9 at http://www.opera.com

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


Re: [Haskell-cafe] List manager and duplicate copies of messsages

2010-07-21 Thread José Romildo Malaquias
On Wed, Jul 21, 2010 at 12:18:14PM -0300, José Romildo Malaquias wrote:
 On Wed, Jul 21, 2010 at 02:42:37PM +0200, Martijn van Steenbergen wrote:
  On 7/21/10 12:48, José Romildo Malaquias wrote:
   Hello.
  
   I have noticed that I do not receive duplicate copies of messages from
   haskell-cafe, although Avoid duplicate copies of messages? is set to
   No in the mailing list membership configuration.
  
   I want the copies because I archive all the mailing list messages with
   procmail based on the X-BeenThere header line.
  
   Has anybody else seen this behaviour, or am I missing anything?
  
   Is there any problems with the mailing list manager?
  
  You're using gmail. See:
  
  http://www.google.com/support/forum/p/gmail/thread?tid=2d5dbc1f28270634
 
 I am talking about answers to messages that I post to haskell-cafe. If
 somebody reply to my message sending it both to the mailing list and to
 me, I am receiving only the copy sent to me. The one sent to the mailing
 list (with the X-BeenThere in the header used for archiving) is not
 arriving to my inbox.
 
 It works with other mailing lists I subscribe with this same email
 address from gmail.
 
 Nontheless I will subscribe with another email address not from gmail
 and see if it works as expected.

After conducting the test with an email address from operamail.com, I
noticed that with replying to all, I receive two copies at operamail.com
and only one at gmail.com.

This is intriguing, because I am subscribed to several other mailing
lists with the gmail.com address, and I am seeing this behaviour only
with the haskell mailing lists.

I apologize for the Test thread.

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


[Haskell-cafe] Tiger compiler in Haskell: annotating abstract syntax tree

2010-07-19 Thread José Romildo Malaquias
Hello.

In his book Modern Compilder Implementation in ML, Appel presents a
compiler project for the Tiger programming language where type checking
and intermediate code generation are intrinsically coupled.

There is a function

  transExp :: Absyn.Exp - (Tree.Exp,Types.Type)

that do semantic analysis, translating an expression to the Tree
intermediate representation language and also do type checking,
calculating the type of the expression.

Maybe the compiler can be made more didatic if these phases are separate
phases of compilation.

The type checker would annotate the abstract syntax tree (ast) with type
annotations, that could be used later by the translater to intermediate
representation.

In an imperative language probably each relevant ast node would have a
field for the type annotation, and the type checker would assign the
type of the node to this field after computing it.

I am writing here to ask suggestions on how to annotate an ast with
types (or any other information that would be relevant in a compiler
phase) in Haskell.

As an example, consider the simplified ast types:

  data Exp
= IntExp Integer
| VarExp Symbol
| AssignExp Symbol Exp
| IfExp Exp Exp (Maybe Exp)
| CallExp Symbol [Exp]
| LetExp [Dec] Exp

  data Dec
 = TypeDec Symbol Ty
 | FunctionDec Symbol [(Symbol,Symbol)] (Mybe Symbol) Exp
 | VarDec Symbol (Maybe Symbol) Exp

Expressions can have type annotations, but declarations can not.

Comments?


Regards,

Romildo
--
Computer Science Department
Universidade Federal de Ouro Preto, Brasil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[romi...@malaquias.dhcp-geral: Re: [Haskell-cafe] Tiger compiler in Haskell: annotating abstract syntax tree]

2010-07-19 Thread José Romildo Malaquias
Forgot the attachment.

Romildo
---BeginMessage---
On Mon, Jul 19, 2010 at 01:51:57PM -0400, Job Vranish wrote:
 Martijn van Steenbergen has a good blog post that describes the method I
 generally use:
 http://martijn.van.steenbergen.nl/journal/2010/06/24/generically-adding-position-information-to-a-datatype/
 
 In his example he annotates the expression tree with position information,
 but you can use the same method to add type annotations, or whatever you
 want.

After a quick read at Martijn blog article I've written the attached
test program, which works.

But I am not succeeding in deriving Show for the data types. Any help?

Romildo

 2010/7/19 José Romildo Malaquias j.romi...@gmail.com
 
  Hello.
 
  In his book Modern Compilder Implementation in ML, Appel presents a
  compiler project for the Tiger programming language where type checking
  and intermediate code generation are intrinsically coupled.
 
  There is a function
 
   transExp :: Absyn.Exp - (Tree.Exp,Types.Type)
 
  that do semantic analysis, translating an expression to the Tree
  intermediate representation language and also do type checking,
  calculating the type of the expression.
 
  Maybe the compiler can be made more didatic if these phases are separate
  phases of compilation.
 
  The type checker would annotate the abstract syntax tree (ast) with type
  annotations, that could be used later by the translater to intermediate
  representation.
 
  In an imperative language probably each relevant ast node would have a
  field for the type annotation, and the type checker would assign the
  type of the node to this field after computing it.
 
  I am writing here to ask suggestions on how to annotate an ast with
  types (or any other information that would be relevant in a compiler
  phase) in Haskell.
 
  As an example, consider the simplified ast types:
 
   data Exp
 = IntExp Integer
 | VarExp Symbol
 | AssignExp Symbol Exp
 | IfExp Exp Exp (Maybe Exp)
 | CallExp Symbol [Exp]
 | LetExp [Dec] Exp
 
   data Dec
  = TypeDec Symbol Ty
  | FunctionDec Symbol [(Symbol,Symbol)] (Mybe Symbol) Exp
  | VarDec Symbol (Maybe Symbol) Exp
 
  Expressions can have type annotations, but declarations can not.
 
  Comments?
---End Message---
module Main where

newtype Fix f = In { out :: f (Fix f) }

newtype AnnFix x f = AnnFix { runAnnFix :: (x, f (AnnFix x f)) }

data ExpF r
  = Num Integer
  | Add r r
  | Mul r r
  | If r r r

type BareExp = Fix ExpF

eval :: BareExp - Integer
eval (In (Num i)) = i
eval (In (Add x y)) = eval x + eval y
eval (In (Mul x y)) = eval x * eval y
eval (In (If t x y)) | eval t == 0 = eval y
 | otherwise = eval x

e = In (Add (In (Num 7)) (In (Num 8)))

type Pos = Int

type PosExp = AnnFix Pos ExpF

aEval (AnnFix (_, e)) =
  case e of
Num i - i
Add x y - aEval x + aEval y
Mul x y - aEval x * aEval y
If t x y | aEval t == 0 - aEval y
 | otherwise - aEval x

ae = AnnFix (3, Add (AnnFix (1, Num 7)) (AnnFix (5, Num 8)))

main = do print (eval e)
  print (aEval ae)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell and Standard ML modules

2010-07-04 Thread José Romildo Malaquias
Hello.


I am writing a Haskell program based on some guidelines written for
Standard ML (The Tiger compiler from the Modern Compiler Implementation
in ML book). The author uses modules for abstracting things like
specifities of the taraget machine.

For intance, there is a general Frame signature that abstracts the frame
representation which depends on the target machine. For each target
machine there is a structure compliant to that signature. For instante
MipsFrame, PentiumFrame and SparcFrames would be structures implementing
the Frame signature.

Many parts of the program just see the Frame signature.

Is there any guidelines on how to achieve somethying similar to this in
Haskell?

Regards,

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


[Haskell-cafe] Physical equality

2010-06-28 Thread José Romildo Malaquias
Is there in Haskell a non monadic function of type a - a - Bool which
test for physical equality of two values? It would return True if only
if both values are the same object in memory.

For instance:

  value1 = good
  value2 = good

  eq value1 value2 = False

  value1 = good
  value2 = value1

  eq value1 value2 = True

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


Re: [Haskell-cafe] Tiger compiler: variable escaping analysis phase

2010-06-24 Thread José Romildo Malaquias
On Tue, Jun 22, 2010 at 04:44:09PM +0200, Vo Minh Thu wrote:
 2010/6/22 José Romildo Malaquias j.romi...@gmail.com:
  On Tue, Jun 22, 2010 at 02:54:08PM +0200, Vo Minh Thu wrote:
  2010/6/22 José Romildo Malaquias j.romi...@gmail.com:
   Hello.
  
   I have been teaching an introductory course on compiler construction to
   our undergraduates students using Appel's Modern Compiler
   Implementation in Java. There are also versions of the book in ML and
   C. The books explain how to write a compiler for the Tiger programming
   language.
  
   Now I want to implement a Tiger compiler in Haskell.
  
   The lexer and parser (built with the help of alex and happy) and the
   type checker are already working.
  
   Next step is implementing a variable escape analysis phase, needed for
   the intermediate code generator. The objective of this phase is to find
   out if each variable escapes or not. In general an escaping variable
   should be allocated in the stack frame (in memory). Non escaping
   variables may be allocated in the stack frame or in a register.
  
   Generally, a variable escapes if it is passed by reference, its address
   is taken (using C's  operator, for instance), or it is accessed from a
   nested function. Only the last is possible with Tiger.
  
   The approach adopted by Appel in his books is easy: a muttable field in
   the abstract syntax of variable declarations, of for expressions, and of
   function formal parameters, which introduce new variables, is used to
   collect the escaping information of the variable. In the ML version of
   the book this is a reference to boolean (bool ref). Initially, in a
   conservative approach, the reference is initialized to true.
  
   In the variable escaping analysis phase of the compiler, a function
   findEscape looks for escaping variables and record this information in
   the escape fields of the abstract syntax. To do this the entire abstract
   syntax tree is traversed looking for escaping uses of every variable,
   and, when found, the field is set to true.
  
   findEscape uses a symbol table to accomplish its work, binding variable
   names to a reference to boolean (the same reference used in the abstract
   syntax tree). When processing a variable declaraction, for instance, it
   inserts the variable name into the symbol table, binding it to its
   escaping field. When processing an expression which is a simple
   variable, if the variable occurs in a nested function, its binding in
   the symbol table is set to true. This reflects directly in the abstract
   syntax tree of the variable declaration, as the escape field in the
   variable declaration and the binding in the symbol table are the same
   reference to bool.
  
   I am look for good ways to implement the variable escaping analysis
   phase in Haskell, which is a pure language. I see two alternatives:
  
   1) adopt the same approach as Appel used in his ML version of the
     compiler: use a mutable reference in the IO monad (Data.IORef) to
     hold the variable escaping information, and write everything inside
     the IO monad
  
   2) build a new abstract syntax tree with updated information regarding
     variable escaping
  
   The second option is more elegant in my point of view, but would be much
   less efficient than the first one.
  
   So I want to know what advices Haskell programmers has to me about
   implementing this phase of the Tiger compiler in Haskell.
 
  Hi,
 
  I think there is a third way to do what you describe (if I understood
  everything). You can use a Writer monad (basically a state monad where
  the state is never read, only written to).
 
  Essentially you walk the tree and record the information you want (a
  mapping from variable name to a boolean 'does-escape'). That
  information is threaded through the tree-walking functions.
 
  The information you record is the underlying monoid of the Writer monad.
 
  The 'does-escape' information should be available for each variable at
  the point the variable is introduced (a variable declaration or a formal
  parameter in a function declaration, for instance). If this information
  is collected in another data structure that is not the abstract syntax
  tree, it may be difficult to access the 'does-escape' information when
  needed.
 
 I was thinking 'accessing when needed' was just a lookup into that
 other datastructure (i.e. a map). As someone said, and related to your
 second solution, this analysis and the resulting mapping can be put
 pack into the tree.
 
 I.e. instead of
 data Tree = ...
 
 you have
 data Tree a = ...
 
 and the 'a' can be whatever you want, including the 'does-escape'
 boolean value.
 
  In this line I thought about using a mapping from a pair consisting of
  the variable name and its position in the source code, to the
  'does-escape' boolean. The findEscape function would construct this
  mapping while traversing the abstract syntax tree.
 
 Yes, that was what I

[Haskell-cafe] Tiger compiler: variable escaping analysis phase

2010-06-22 Thread José Romildo Malaquias
Hello.

I have been teaching an introductory course on compiler construction to
our undergraduates students using Appel's Modern Compiler
Implementation in Java. There are also versions of the book in ML and
C. The books explain how to write a compiler for the Tiger programming
language.

Now I want to implement a Tiger compiler in Haskell.

The lexer and parser (built with the help of alex and happy) and the
type checker are already working.

Next step is implementing a variable escape analysis phase, needed for
the intermediate code generator. The objective of this phase is to find
out if each variable escapes or not. In general an escaping variable
should be allocated in the stack frame (in memory). Non escaping
variables may be allocated in the stack frame or in a register.

Generally, a variable escapes if it is passed by reference, its address
is taken (using C's  operator, for instance), or it is accessed from a
nested function. Only the last is possible with Tiger.

The approach adopted by Appel in his books is easy: a muttable field in
the abstract syntax of variable declarations, of for expressions, and of
function formal parameters, which introduce new variables, is used to
collect the escaping information of the variable. In the ML version of
the book this is a reference to boolean (bool ref). Initially, in a
conservative approach, the reference is initialized to true.

In the variable escaping analysis phase of the compiler, a function
findEscape looks for escaping variables and record this information in
the escape fields of the abstract syntax. To do this the entire abstract
syntax tree is traversed looking for escaping uses of every variable,
and, when found, the field is set to true.

findEscape uses a symbol table to accomplish its work, binding variable
names to a reference to boolean (the same reference used in the abstract
syntax tree). When processing a variable declaraction, for instance, it
inserts the variable name into the symbol table, binding it to its
escaping field. When processing an expression which is a simple
variable, if the variable occurs in a nested function, its binding in
the symbol table is set to true. This reflects directly in the abstract
syntax tree of the variable declaration, as the escape field in the
variable declaration and the binding in the symbol table are the same
reference to bool.

I am look for good ways to implement the variable escaping analysis
phase in Haskell, which is a pure language. I see two alternatives:

1) adopt the same approach as Appel used in his ML version of the
   compiler: use a mutable reference in the IO monad (Data.IORef) to
   hold the variable escaping information, and write everything inside
   the IO monad

2) build a new abstract syntax tree with updated information regarding
   variable escaping

The second option is more elegant in my point of view, but would be much
less efficient than the first one.

So I want to know what advices Haskell programmers has to me about
implementing this phase of the Tiger compiler in Haskell.


Regards,

Romildo
--
Computer Science Department
Universidade Federal de Ouro Preto, Brazil

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


Re: [Haskell-cafe] Tiger compiler: variable escaping analysis phase

2010-06-22 Thread José Romildo Malaquias
On Tue, Jun 22, 2010 at 02:30:04PM +0100, Stephen Tetley wrote:
 Hello
 
 Doaitse Swierstra has a Tiger compiler written in Haskell + UUAG as a
 demonstration for UUAG attribute grammar system.
 
 The package on Hackage only contains the derived source - i.e not the
 original attribute grammar code, but the generated Haskell source
 after running UUAG on the *.ag files.
 
 http://hackage.haskell.org/package/tiger
 
 You could try contacting Doaitse Swierstra for the original UUAG source.

I have found the sources at http://www.cs.uu.nl/wiki/HUT/WebHome.

What is provided is an implementation of a compiler front-end and type
checker for Andrew Appel's Tiger language.

The variable escaping phase (needed only to decide where variables would
be allocated in the back-end) is not implemented. At least I could not
find it in a quick view.

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


Re: [Haskell-cafe] Tiger compiler: variable escaping analysis phase

2010-06-22 Thread José Romildo Malaquias
On Tue, Jun 22, 2010 at 02:54:08PM +0200, Vo Minh Thu wrote:
 2010/6/22 José Romildo Malaquias j.romi...@gmail.com:
  Hello.
 
  I have been teaching an introductory course on compiler construction to
  our undergraduates students using Appel's Modern Compiler
  Implementation in Java. There are also versions of the book in ML and
  C. The books explain how to write a compiler for the Tiger programming
  language.
 
  Now I want to implement a Tiger compiler in Haskell.
 
  The lexer and parser (built with the help of alex and happy) and the
  type checker are already working.
 
  Next step is implementing a variable escape analysis phase, needed for
  the intermediate code generator. The objective of this phase is to find
  out if each variable escapes or not. In general an escaping variable
  should be allocated in the stack frame (in memory). Non escaping
  variables may be allocated in the stack frame or in a register.
 
  Generally, a variable escapes if it is passed by reference, its address
  is taken (using C's  operator, for instance), or it is accessed from a
  nested function. Only the last is possible with Tiger.
 
  The approach adopted by Appel in his books is easy: a muttable field in
  the abstract syntax of variable declarations, of for expressions, and of
  function formal parameters, which introduce new variables, is used to
  collect the escaping information of the variable. In the ML version of
  the book this is a reference to boolean (bool ref). Initially, in a
  conservative approach, the reference is initialized to true.
 
  In the variable escaping analysis phase of the compiler, a function
  findEscape looks for escaping variables and record this information in
  the escape fields of the abstract syntax. To do this the entire abstract
  syntax tree is traversed looking for escaping uses of every variable,
  and, when found, the field is set to true.
 
  findEscape uses a symbol table to accomplish its work, binding variable
  names to a reference to boolean (the same reference used in the abstract
  syntax tree). When processing a variable declaraction, for instance, it
  inserts the variable name into the symbol table, binding it to its
  escaping field. When processing an expression which is a simple
  variable, if the variable occurs in a nested function, its binding in
  the symbol table is set to true. This reflects directly in the abstract
  syntax tree of the variable declaration, as the escape field in the
  variable declaration and the binding in the symbol table are the same
  reference to bool.
 
  I am look for good ways to implement the variable escaping analysis
  phase in Haskell, which is a pure language. I see two alternatives:
 
  1) adopt the same approach as Appel used in his ML version of the
    compiler: use a mutable reference in the IO monad (Data.IORef) to
    hold the variable escaping information, and write everything inside
    the IO monad
 
  2) build a new abstract syntax tree with updated information regarding
    variable escaping
 
  The second option is more elegant in my point of view, but would be much
  less efficient than the first one.
 
  So I want to know what advices Haskell programmers has to me about
  implementing this phase of the Tiger compiler in Haskell.
 
 Hi,
 
 I think there is a third way to do what you describe (if I understood
 everything). You can use a Writer monad (basically a state monad where
 the state is never read, only written to).
 
 Essentially you walk the tree and record the information you want (a
 mapping from variable name to a boolean 'does-escape'). That
 information is threaded through the tree-walking functions.
 
 The information you record is the underlying monoid of the Writer monad.

The 'does-escape' information should be available for each variable at
the point the variable is introduced (a variable declaration or a formal
parameter in a function declaration, for instance). If this information
is collected in another data structure that is not the abstract syntax
tree, it may be difficult to access the 'does-escape' information when
needed.

In this line I thought about using a mapping from a pair consisting of
the variable name and its position in the source code, to the
'does-escape' boolean. The findEscape function would construct this
mapping while traversing the abstract syntax tree.

The function that generates the intermediate representation of the
program would be given the abstract syntax tree and the escaping mapping
as arguments. When traversing the abstract syntax tree to generate code,
it would consult the escaping mapping to determine if a varable escapes
or not, when allocating a variable. The variable name and its position
are available from the abstract syntax tree.

Are you suggesting that the Writer monad would be used to construct a
data structure like the escaping mapping I mentioned above?

 Anyway, the second option sounds better than the first one as you
 don't have to rely

Re: [Haskell-cafe] Tiger compiler: variable escaping analysis phase

2010-06-22 Thread José Romildo Malaquias
On Tue, Jun 22, 2010 at 10:01:37AM -0300, Felipe Lessa wrote:
 On Tue, Jun 22, 2010 at 09:33:22AM -0300, José Romildo Malaquias wrote:
  In the variable escaping analysis phase of the compiler, a function
  findEscape looks for escaping variables and record this information in
  the escape fields of the abstract syntax. To do this the entire abstract
  syntax tree is traversed looking for escaping uses of every variable,
  and, when found, the field is set to true.
 
  findEscape uses a symbol table to accomplish its work, binding variable
  names to a reference to boolean (the same reference used in the abstract
  syntax tree). When processing a variable declaraction, for instance, it
  inserts the variable name into the symbol table, binding it to its
  escaping field. When processing an expression which is a simple
  variable, if the variable occurs in a nested function, its binding in
  the symbol table is set to true. This reflects directly in the abstract
  syntax tree of the variable declaration, as the escape field in the
  variable declaration and the binding in the symbol table are the same
  reference to bool.
 
 Idea of pure algorithm:
 
  1) Update the symbol table itself, that is: instead of using
 
(a) Map Symbol (IORef Bool)
 
 use
 
(b) Map Symbol Bool.
 
 This doesn't change the complexity of the algorithm as
 searching and updating have the same complexity for many data
 structures (maps and hashtables, for example).
 
 In reality, you don't need to use a Map at all.  Just use
 
(c) Set Symbol
 
 and symbols not in the set do not escape.  Using (a) gives
 you O(n log k) for this step, where n is the size of the AST
 and k is the number of symbols.  On the other hand, (c) gives
 you O(n log e), where e is the number of escaping symbols.

These solutions would not work because they do not deal with scopes of
variables. In a Tiger program (as in most programming languges) a
variable name can be reused many times to refer to different variables,
and each variable can escape.

Maybe a set of pairs containing the variable name and its position in
the source code (available from the abstract syntax tree) would be a
good idea.

Then the code generator would traverse the abstract syntax tree and,
when needed, use this set to find out whether a variable escapes.

  2) After doing the whole analysis, use a function
 'addEscapeInfo' to process the whole pure AST again adding
 information about escaped symbols.  This is O(n log e) as
 well.

If the variable escaping analysis is done and its result is made
available in another data structure, there would be no need to add the
escaping information back to the abstract syntax tree.

  The second option is more elegant in my point of view, but would be much
  less efficient than the first one.
 
 While O(n log e) is better than O(n log k), probably the
 constants in the pure algorithm are higher than their impure
 counterparts.  I guess you could also try to write:
 
   1) Take an 'AST e' into 'AST (STRef s Bool, e)' in O(n).
 
   2) Use the impure algorithm inside ST monad in O(n log k).
 
   3) Take 'AST (STRef s Bool, e)' into 'AST (Bool, e)' in O(n).
 
   4) 'runST' on the above steps to get a pure function from
  'AST e' into 'AST (Bool, e)'.
 
 The ST monad has the same runtime overhead as IO.  Steps 1) and
 3) are used to hide the ST monad from the rest of the compiler.

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


[Haskell-cafe] Get data from HTML pages

2009-08-31 Thread José Romildo Malaquias
Hello.

I am porting to Haskell a Java application I have written to manage
collections of movies.

Currently the application has an option to indirectly import movie data
from web pages. For that first the user should access the page in a web
browser. Then the user should copy the rendered text in the web browser
into an import window in my application and click an import button. In
response the application parses the given text and collects any relevant
data it knows about, using regular expressions.

For instance, to get the director information from a movie in the
AllCenter web site I use the following regular expression:

   ^Direção:\s+(.+)$

I want to modify this scheme in order to eliminate the need to copy the
rendered text from a web browser. Instead my application should download
and parse the HTML page directly.

Which libraries are available in Haskell that would make it easy to get
content information from a HTML document, in the way described above?

Regards,

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


[Haskell-cafe] Pretty printing a tree

2009-05-14 Thread José Romildo Malaquias
Hello.

I would like to pretty print a tree in a way that its structure is
easily perceived.

For instance, consider the declarations:

   data Node a = Node a [Node a]

   type Tree a = [ Node a ]

   t = [ Node a [ Node b []
  , Node c [ Node c1 []
 , Node c2 [] ]
  , Node d [ Node d1 [ Node d1a [] ]
 , Node d2 [] ] ] ]

Then the resulting of pretty printing the given tree would be something
like the following:

   a
   |
+-+
|||
bcd
 ||
   +---++---+
   |   ||   |
   c1  c2   d1  d2
|
   d1a

There is the module Text.PrettyPrint.HughesPJ, but it lacks examples on
how to use the pretty print combinators, and it is not well docomented.

I would like to see solutions for this problem, or clues on how to solve
it.

Regards,

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