Re: [Haskell-cafe] operating on a hundred files at once

2007-04-10 Thread Chad Scherrer

Hi Jeff,


I have a series of NxM numeric tables I'm doing a quick
mean/variance/t-test etcetera on.  The cell t1 [i,j] corresponds exactly
to the cells t2..N [i,j], and so it's perfectly possible to read one
item at a time from each of the 100 files and compute the mean/variance
etcetera on all cells that way.


So after mapping openAndProcess, you have a 100xNxM array (really a
list-of-lists-of-lists), right? And then when you take means and
variances, which index are you doing this with respect to? As I read
it, you seem to be trying to eliminate the first axis, and end up with
an NxM array.

If this is the case, let's say we have
mean, variance :: [Double] - Double
openAndProcess :: String - IO (Matrix String)

Here, defining
type Matrix a = [[a]]
makes it easier to keep the types straight.

Then you have these building blocks:

(map . map . map) read :: [Matrix String] - [Matrix Double]

transpose2 :: [Matrix Double] - Matrix [Double]
(a couple of lines, maybe even a one-liner, if you use that [a] is a monad)

(map . map) mean :: Matrix [Double] - Matrix Double

Composing these gives a function [Matrix String] - Matrix Double, so
once we get to [Matrix String], we're effectively done.

you also use
map OpenAndProcess :: [String] - [IO (Matrix String)]

You can use sequence to get the IO outside the list, so now you have
IO [Matrix String]. All you have to do now is use liftM on your
function [Matrix String] - Matrix Double, which turns it into a
function IO [Matrix String] - IO (Matrix Double).

--

Chad Scherrer

Time flies like an arrow; fruit flies like a banana -- Groucho Marx
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] operating on a hundred files at once

2007-04-10 Thread Ketil Malde
On Tue, 2007-04-10 at 13:16 +1000, Duncan Coutts wrote:

 Note, that like in your original we read each file twice, once for the
 mean and once for the variance. 

As an aside, you can calculate both mean and variance in one pass (and
constant space) by calculating the sum of elements 'x', the sum of
squared elements 'x2', and keeping track of the number of elements 'n'.

  mean = x/n
  var  = (x2-mean*mean*n)/(n-1)

If you track the sum of cubed elements (x3) and the powers of four (x4),
you also get kurtosis and skew in a similar manner.

-k

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


Re: [Haskell-cafe] Compiling GHC

2007-04-10 Thread Chris Witte

HAVE_GETTIMEOFDAY is defined. I wrote a quick c program to check and I
can use gettimeofday fine. I can't work out why ghc can't find it. How
can I work out where ghc is searching to find it?

Chris.

On 3/30/07, Ian Lynagh [EMAIL PROTECTED] wrote:

On Fri, Mar 30, 2007 at 04:36:32PM +1000, Chris Witte wrote:
 I'm tying to compile GHC under mingw (winxp with mingw no cygwin),

 Loading package base ... linking ... ghc.exe: unable to load package `base'
 ghc.exe:
 C:/msys/1.0/local/HSbase.o: unknown symbol `_gettimeofday'


 any ideas on what could be causing this.

What does

grep -i gettimeofday mk/config.h

say?

If HAVE_GETTIMEOFDAY is defined then either comment it out (between
running configure and running make), or work out why the configure test
is succeeding but it doesn't work when GHC tries to use it.


Thanks
Ian



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


Re: [Haskell-cafe] Parsec: Help needed with simple parser

2007-04-10 Thread Joel Reymont


On Apr 10, 2007, at 3:42 AM, Albert Y. C. Lai wrote:


Does option help? Like:


It did, together with a couple of 'try's.

Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] Prettyprinting infix expressions with HughesPJ

2007-04-10 Thread Alfonso Acosta

Hi all,

I have to prettyprint infix expressions writing the least possible
parenthesis (taking in account precedence and associativity). A
simplified expression type could be:

data Expr = Val String |
 -- Binary operators (using infix constructors)
 Expr :+: Expr  | Expr  :-: Expr  |
 Expr :*: Expr  | Expr  :/: Expr  |
 Expr :^: Expr |
 -- Unary operators
 Negate Expr


I'm using HughesPJ for the rest of my AST (not just expressions) but
the library doesn't provide any mechanism to help coding this kind of
prettyprinter so I decided to simply use the standard showsPrec and
then feed HughesPJ with the obtained text .

showsPrec helps to take advantage of the precedence information.
However, I don't find a way to remove parenthesis according to
associativity.

I'm sure this kind of prettyprinting has been already done zillions of
times in Haskell. Any suggestions?

Thanks in advance,

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


[Haskell-cafe] Re: Type error

2007-04-10 Thread Alfonso Acosta

Hi oleg,

On 4/9/07, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote:


Alfonso Acosta wrote:

I have a type problem in my code which I dont know how to solve

 data HDSignal a = HDSignal
 class HDPrimType a where
 class PortIndex a where

 class SourcePort s where
  -- Plug an external signal to the port
  plugSig  :: (HDPrimType a, PortIndex ix) =ix - s  -(HDSignal a - b) - b

 class DestPort d where
  -- Supply a signal to the port
  supplySig  :: (PortIndex ix, HDPrimType a) = HDSignal a - ix - d - d


 -- Connect providing indexes
 connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) =
  six - s - dix - d - d
 connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d

I'm afraid the example may be a bit too simplified. The first
question: what is the role of the |HDPrimType a| constraint in plugSig
and supplySig? Do the implementations of those functions invoke some
methods of the class HDPrimType?


Yes, I added the |HDPrimType a| constraint beacuse I realized I'm
forced to call a function from that class withoin supplySig . Actually
all the code was working smothly before adding the constraint which
has been te cause of my problem.


Or the |HDPrimType a| constraint is
just to declare that the parameter |a| of HDSignal is a member of
HDPrimType?


Unfortunately not



If plugSig and supplySig do use the methods of HDPrimType, one could
use existentials:


I tried the existential approach when it was previously suggested by
Chris, but the problem is that, for some Source instances calling
methods from HDPrimType within supplySig is not enough. Thus, it
doesn't work with existentials due to their limitations.

I'm definitively stuck wit this problem :S

Cheers,

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


[Haskell-cafe] Re: What I learned from my first serious attempt low-level Haskell programming

2007-04-10 Thread Simon Marlow

Lennart Augustsson wrote:
It's not that hard to figure out an order to permute the arguments on 
the stack before a tail call that minimizes that number of moves and 
temporary locations.  Lmlc did this 20 years ago. :)


Right, and that's what GHC does too, with a strongly-connected-component 
analysis of the dependencies between assignments of the args for the tail call.


Cheers,
Simon

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


Re: [Haskell-cafe] Re: [web-devel] A light-weight web framework

2007-04-10 Thread Marc Weber
 Right now, you can largely do the same thing, but you have to write the XML 
 representations of your data structures manually.
 
 -Alex-

I'm not sure but doesn't use HAppS kind of stripped down HaXml ?
DrIft can derive HaXml instances automatically.
Where is the problem doing using DrIft?

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


[Haskell-cafe] Re: Profiling makes memory leak go away? Is Haskell a practical language?

2007-04-10 Thread apfelmus
Oren Ben-Kiki wrote:
 The code is in http://hpaste.org/1314#a1 if anyone at all is willing
 to take pity on me and explain what I'm doing wrong.

There is an important point to note about streaming, namely that it
conflicts with knowing whether the input is syntactically correct or
not. In other words, evaluating (rResult reply) parses the hole input to
the bitter end. For example, take your input data

  cycle a\n = a\na\na\na\n...

Can we determine whether (rResult reply) is Nothing or Just after
reading the first 'a'? No, we can't because the hole parse could fail
far to the end resulting in Nothing.

You've probably noticed this already and introduced rToken for that
reason but I'm not sure.

 Chasing down my memory leak I got into a weird situation where adding
 a magic manual SCC section and compiling with -prof makes the leak
 disappear.

That sounds fishy. Note that manual SCC annotations + optimization
currently is a bit buggy in GHC, in the sense that optimization disturbs
correct cost attribution.

Does the program eat the output of yes 'a' without memory explosion
showed by top? If so, it could perhaps be a problem of the
optimization phase which maybe expands

  D.append parsed (case result of ...)

to

  case result of {
  Nothing - D.append parsed D.empty
  Just .. - D.append parsed (D.singleton...) }

The latter won't stream because of the reason noted above. But it's
highly unlikely that GHC performs a transformation that changes
semantics this radically.

 I can achieve the results I want in very short elegant code...

In my opinion, your streaming parser is not as elegant as it could be
which makes it hard to read the code. With monad transformers, we almost
have

  Parser a ~= StateT State (WriterT (D.DList Token) Maybe) a
   ~= State - (D.DList Token, Maybe (a,State))

Your Parser is slightly different but I think that the monad instances
behave exactly the same way. The power functional programming is to
assemble big things from small things. Monad transformers supply tons of
small monads that you can reuse to build big monads. In a sense, the
many pattern matches on Maybe have already been written down in general
form by someone else.

Also, I'm really missing type signatures, especially for many. When
reading the code, I expected

  many :: Parser a - Parser [a]

but had to conclude

  many :: Parser a - Parser ()

by inspecting its code.


Regards,
apfelmus

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


[Haskell-cafe] Type level programming to eliminate array bound checking, a real world use

2007-04-10 Thread Vivian McPhail

Hi All,Inspired by Oleg's Eliminating Array Bound Checking through
Non-dependent types  http://okmij.org/ftp/Haskell/types.html#branding,I am
attempting to write code that will receive an array from C land and convert
it to a type safe representation.  The array could have n dimensions where n

2.  I receive the number of dimensions as a list of Ints [Int].  To do

type-safe programming I need to convert this to a type level
representation.  Using CPS (thanks to ski on #haskell) I can convert an Int
to the type level.  But I have found it impossible to insert this type-level
Digits representation into an HList.

In Oleg's examples with vectors he types in by hand the data whose type
represents the size of the vector:

sample_v = listVec (D2 Sz) [True,False]

where (D2 Sz) is the size of the vector and the type is:

ArbPrecDecT :t sample_v
Vec (D2 Sz) Bool

In a real program we can't expect the programmer to type in the size of the
data, it needs to be done programmatically, and this is where I am stuck.

Could someone please point me in the right direction, or explain why what
I'm trying to do won't work?  Basically I'm looking for a function
int2typelevel :: (HList l) :: [Int] - l

I thought that this would work because HLists can have elements of different
types and I can already (modulo CPS) convert an Int to it's Digits type
level representation.

One approach which won't work is existentially wrapping the result of
num2digits in a GADT, because this hides the type from the type-checker and
then can't be used for bounds checking.

Here is an example of what I want to be able to do:

add :: Equal size1 size2 = Array size1 idx - Array size2 idx - Array
size1 idx

for example:

data Array size idx = Array size (MArray idx Double)

add (Array (DCons (D1 (D2 Sz)) (DCons (D3 Sz) DNil)) (12,3)) (Array (DCons
(D1 (D2 Sz)) (DCons (D3 Sz) DNil)) (12,3))

the sizes are statically checked and I don't have to do runtime checking on
the idx.

This message is a literate source file.  The commented out function at the
end illustrates the problem.

Thanks,

Vivian


{-# OPTIONS -fglasgow-exts #-}

-- copied from http://okmij.org/ftp/Haskell/number-parameterized-types.html

module Digits where

data D0 a = D0 a deriving(Eq,Read,Show)
data D1 a = D1 a deriving(Eq,Read,Show)
data D2 a = D2 a deriving(Eq,Read,Show)
data D3 a = D3 a deriving(Eq,Read,Show)
data D4 a = D4 a deriving(Eq,Read,Show)
data D5 a = D5 a deriving(Eq,Read,Show)
data D6 a = D6 a deriving(Eq,Read,Show)
data D7 a = D7 a deriving(Eq,Read,Show)
data D8 a = D8 a deriving(Eq,Read,Show)
data D9 a = D9 a deriving(Eq,Read,Show)

class Digits ds where-- class of digit sequences
   ds2num:: (Num a) = ds - a - a -- CPS style

data Sz = Sz-- zero size (or the Nil of the sequence)
 deriving(Eq,Read,Show)

instance Digits Sz where
   ds2num _ acc = acc

instance (Digits ds) = Digits (D0 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc)
instance (Digits ds) = Digits (D1 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 1)
instance (Digits ds) = Digits (D2 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 2)
instance (Digits ds) = Digits (D3 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 3)
instance (Digits ds) = Digits (D4 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 4)
instance (Digits ds) = Digits (D5 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 5)
instance (Digits ds) = Digits (D6 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 6)
instance (Digits ds) = Digits (D7 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 7)
instance (Digits ds) = Digits (D8 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 8)
instance (Digits ds) = Digits (D9 ds) where
   ds2num dds acc = ds2num (t22 dds) (10*acc + 9)

t22::(f x)   - x; t22 = undefined

-- Class of non-negative numbers
-- This is a restriction on Digits. It is not possible to make
-- such a restriction in SML.
class {- (Digits c) = -} Card c where
   c2num:: (Num a) = c - a

instance Card Sz where c2num c = ds2num c 0
--instance (NonZeroDigit d,Digits (d ds)) = Card (Sz (d ds)) where
instance (Digits ds) = Card (D1 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D2 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D3 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D4 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D5 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D6 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D7 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D8 ds) where c2num c = ds2num c 0
instance (Digits ds) = Card (D9 ds) where c2num c = ds2num c 0

-- Support for generic cards
-- We introduce a data constructor CardC_unused merely for the sake of
-- Haskell98. With the GHC extension, we can simply omit the data
-- constructor and keep the type CardC purely abstract and phantom.
data CardC c1 c2 = CardC_unused

cardc:: 

[Haskell-cafe] Type checking and locating token with Parsec

2007-04-10 Thread Joel Reymont

Folks,

Imagine a language where Num + Num yields a Num and Str + Num yields  
a Str but Num + Str should not be allowed.


I implemented parsing for such a language in OCaml with a yacc-based  
parser without an additional type-checking pass, entirely within the  
yacc grammar. I tried to take such an approach with Parsec but hit  
the roadblock with buildExpressionParser since it returns the same  
type as the token parser given to it.


Rather than have numerical expressions, string expressions, etc., as  
separate types, I simplified things down to a single expression type  
that holds my booleans, strings and numbers. I now need to implement  
type checking of my parsed AST.


The main issue is error reporting. I'm not sure where to get token  
location with Parsec and how to elegantly embed it in my AST.


Has anyone implemented type checking on top of a Parsec-based parser?

How did you locate your tokens?

Thanks, Joel

--
http://wagerlabs.com/





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


[Haskell-cafe] A convenient way to deal with conditional function composition?

2007-04-10 Thread Maxime Henrion
Hello all,


I have found myself writing instances of Show for some types of
mine, and I did so by defining the showsPrec function, for performance
reasons.  I ended up with code that I find quite inelegant.  Here's
an example:

data Move = Move {
 movePiece :: PieceType,
 moveFile  :: Maybe File,
 moveTarget:: Square,
 moveIsCapture :: Bool
 --movePromotion :: Maybe PieceType
   }
  deriving (Eq)

instance Show Move where
  showsPrec _
Move {
  movePiece = p,
  moveFile  = f,
  moveTarget= s,
  moveIsCapture = c
} = (if p /= Pawn then shows p else id) .
(maybe id shows f) .
(if c then ('x':) else id) .
shows s

I considered writing a conditional composiion combinator to avoid all
the 'if foo then f else id' code.  Something looking like this:

f .? True  g = f . g
f .? False g = f

I'm not sure this is the best approach though, and I would be happy
to hear about your suggestions for improving the style of this code,
or any other comment that you think is appropriate.

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


Re: [Haskell-cafe] A convenient way to deal with conditional function composition?

2007-04-10 Thread Chris Kuklewicz
Maxime Henrion wrote:
   Hello all,
 
 
 I have found myself writing instances of Show for some types of
 mine, and I did so by defining the showsPrec function, for performance
 reasons.  I ended up with code that I find quite inelegant.  Here's
 an example:
 
 data Move = Move {
  movePiece :: PieceType,
  moveFile  :: Maybe File,
  moveTarget:: Square,
  moveIsCapture :: Bool
  --movePromotion :: Maybe PieceType
}
   deriving (Eq)
 
 instance Show Move where
   showsPrec _
 Move {
   movePiece = p,
   moveFile  = f,
   moveTarget= s,
   moveIsCapture = c
 } = (if p /= Pawn then shows p else id) .
 (maybe id shows f) .
 (if c then ('x':) else id) .
 shows s
 
 I considered writing a conditional composiion combinator to avoid all
 the 'if foo then f else id' code.  Something looking like this:
 
 f .? True  g = f . g
 f .? False g = f
 
 I'm not sure this is the best approach though, and I would be happy
 to hear about your suggestions for improving the style of this code,
 or any other comment that you think is appropriate.
 
 Thanks,
 Maxime

Well, since ((.) :: ShowS - ShowS - ShowS) is a Monoid, you can use Writer to
create the result:

 import Control.Monad
 import Control.Monad.Writer
 
 type Writes = Writer ShowS ()
 
 data PieceType = Pawn | Other deriving (Eq,Show)
 type File = Int
 type Square = Int
 
 data Move = Move {
  movePiece :: PieceType,
  moveFile  :: Maybe File,
  moveTarget:: Square,
  moveIsCapture :: Bool
  --movePromotion :: Maybe PieceType
}
   deriving (Eq)
 
 instance Show Move where showsPrec = showsPrec_Move
 
 showsPrec_Move :: Int - Move - ShowS
 showsPrec_Move _ Move { movePiece = p
   , moveFile  = f
   , moveTarget= s
   , moveIsCapture = c } = execWriter $ do
   when (p/=Pawn) (tell (shows p))
   maybe (return ()) (tell . shows) f
   when c (tell ('x':))
   tell (shows s)
 
 testMove = Move Other (Just 6) 10 True
 

which gives

 *Main testMove
 Other6x10
 *Main testMove { movePiece=Pawn }
 6x10
 *Main testMove { movePiece=Pawn, moveIsCapture=False }
 610

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


Re: [Haskell-cafe] A convenient way to deal with conditional function composition?

2007-04-10 Thread Stefan O'Rear
On Tue, Apr 10, 2007 at 02:33:41PM +0100, Chris Kuklewicz wrote:
 Well, since ((.) :: ShowS - ShowS - ShowS) is a Monoid, you can use Writer 
 to
 create the result:

Not portably.

[EMAIL PROTECTED]:~$ ghc-6.4.2 -e '(  (foo++) `Data.Monoid.mappend` (bar++) 
) END'
foobarEND
[EMAIL PROTECTED]:~$ ghc-6.6 -e '(  (foo++) `Data.Monoid.mappend` (bar++) ) 
END'
fooENDbarEND


-- 6.6 sources
instance Monoid b = Monoid (a - b) where
mempty _ = mempty
mappend f g x = f x `mappend` g x


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


[Haskell-cafe] Checking for correct invocation of a command line / shell haskell program

2007-04-10 Thread Thomas Hartman

New wiki page: Checking for correct invocation of a command line haskell program

at

http://haskell.org/haskellwiki/Checking_for_correct_invocation_of_a_command_line_haskell_program

This is a simple cookbook / boilerplate example I thought should go in
a haskell wiki somewhere.

I linked it from

http://haskell.org/haskellwiki/Simple_unix_tools

Perhaps it could be linked from other places as well.

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


[Haskell-cafe] Re: Checking for correct invocation of a command line / shell haskell program

2007-04-10 Thread Thomas Hartman

there was a minor mistake in the above, fixed on the wiki page.

2007/4/10, Thomas Hartman [EMAIL PROTECTED]:

New wiki page: Checking for correct invocation of a command line haskell program

at

http://haskell.org/haskellwiki/Checking_for_correct_invocation_of_a_command_line_haskell_program

This is a simple cookbook / boilerplate example I thought should go in
a haskell wiki somewhere.

I linked it from

http://haskell.org/haskellwiki/Simple_unix_tools

Perhaps it could be linked from other places as well.

Hope this helps!


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


Re: [Haskell-cafe] operating on a hundred files at once

2007-04-10 Thread Jefferson Heard
Thanks, Ketil.  I knew I could calcuate the mean in constant space, but
I didn't think about the variance.  Much appreciated.

On Tue, 2007-04-10 at 08:30 +0200, Ketil Malde wrote:
 On Tue, 2007-04-10 at 13:16 +1000, Duncan Coutts wrote:
 
  Note, that like in your original we read each file twice, once for the
  mean and once for the variance. 
 
 As an aside, you can calculate both mean and variance in one pass (and
 constant space) by calculating the sum of elements 'x', the sum of
 squared elements 'x2', and keeping track of the number of elements 'n'.
 
   mean = x/n
   var  = (x2-mean*mean*n)/(n-1)
 
 If you track the sum of cubed elements (x3) and the powers of four (x4),
 you also get kurtosis and skew in a similar manner.
 
 -k

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


Re: [Haskell-cafe] A convenient way to deal with conditional function composition?

2007-04-10 Thread Nicolas Frisby

Using the Endo newtype can avoid such ambiguities:
 http://darcs.haskell.org/packages/base/Data/Monoid.hs

newtype Endo a = Endo { appEndo :: a - a }

instance Monoid (Endo a) where
mempty = Endo id
Endo f `mappend` Endo g = Endo (f . g)

Endo allows you to explicitly select the monoid behavior of the
endomorphism String - String instead of using String - String as an
exponent. It seems 6.4.2 - 6.6 made a change from a default Monoid
instance for (a - a) to the more general Monoid instance for (a -
b).



On 4/10/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

On Tue, Apr 10, 2007 at 02:33:41PM +0100, Chris Kuklewicz wrote:
 Well, since ((.) :: ShowS - ShowS - ShowS) is a Monoid, you can use Writer 
to
 create the result:

Not portably.

[EMAIL PROTECTED]:~$ ghc-6.4.2 -e '(  (foo++) `Data.Monoid.mappend` (bar++) ) 
END'
foobarEND
[EMAIL PROTECTED]:~$ ghc-6.6 -e '(  (foo++) `Data.Monoid.mappend` (bar++) ) 
END'
fooENDbarEND


-- 6.6 sources
instance Monoid b = Monoid (a - b) where
mempty _ = mempty
mappend f g x = f x `mappend` g x


Stefan
___
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] A convenient way to deal with conditional function composition?

2007-04-10 Thread Chris Kuklewicz
Nicolas Frisby wrote:
 Not portably.

 [EMAIL PROTECTED]:~$ ghc-6.4.2 -e '(  (foo++) `Data.Monoid.mappend`
 (bar++) ) END'
 foobarEND
 [EMAIL PROTECTED]:~$ ghc-6.6 -e '(  (foo++) `Data.Monoid.mappend`
 (bar++) ) END'
 fooENDbarEND


 -- 6.6 sources
 instance Monoid b = Monoid (a - b) where
 mempty _ = mempty
 mappend f g x = f x `mappend` g x


 Stefan

Thanks for the reminder.  So the fixed 6.6 code is

 import Control.Monad(when)
 import Control.Monad.Writer(Writer,tell,execWriter)
 import Data.Monoid(Endo(..))
 
 type Writes = Writer (Endo String) ()
 
 data PieceType = Pawn | Other deriving (Eq,Show)
 type File = Int
 type Square = Int
 
 data Move = Move {
  movePiece :: PieceType,
  moveFile  :: Maybe File,
  moveTarget:: Square,
  moveIsCapture :: Bool
  --movePromotion :: Maybe PieceType
}
   deriving (Eq)
 
 instance Show Move where showsPrec = showsPrec_Move
 
 tShow :: Show a = a - Writes
 tShow = tell . Endo . shows
 
 tChar :: Char - Writes
 tChar = tell . Endo . (:)
 
 tString :: String - Writes
 tString = tell . Endo . (++)
 
 showsPrec_Move :: Int - Move - ShowS
 showsPrec_Move _ Move { movePiece = p
   , moveFile  = f
   , moveTarget= s
   , moveIsCapture = c } = appEndo . execWriter $ do
   when (p/=Pawn) (tShow p)
   maybe (return ()) tShow f
   when c (tChar 'x')
   tShow s
 
 testMove = Move Other (Just 6) 10 True
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] hackage.haskell.org

2007-04-10 Thread David Waern
Hi,

I'd like to set up a Trac for Haddock on hackage.haskell.org. Who should I
contact?

/David

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


Re: [Haskell-cafe] hackage.haskell.org

2007-04-10 Thread Neil Mitchell

Hi


I'd like to set up a Trac for Haddock on hackage.haskell.org. Who should I
contact?


Couldn't we use the bug tracker in Google Code? Its much better than
the Trac one, much more useable, and they host it for us even. Think
of it as Google giving us the gift of a perfectly formed bug tracker -
it would be rude to say no :-)

If someone wants to take a look at it, we use it for Yhc:
http://code.google.com/p/yhc/issues/list

Note the lack of spam :)

Thanks

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


[Haskell-cafe] Profiling makes memory leak go away? Is Haskell a practical language?

2007-04-10 Thread Oren Ben-Kiki

On Tue, 2007-04-10 at 12:14 +0200, apfelmus wrote:

Oren Ben-Kiki wrote:
 The code is in http://hpaste.org/1314#a1 if anyone at all is willing
 to take pity on me and explain what I'm doing wrong.

There is an important point to note about streaming, namely that it
conflicts with knowing whether the input is syntactically correct or
not.


True, this is  the core issue. Think of a turing machine processing an
infinite tape. It is writing output and producing a final result; it is
possible to examine the output tape before knowing the final result.
Haskell parsers insist on having the output tape live in memory until
the final result is known, and then give it to you as one huge object
when done (or discard it and just give you the error message). NOT a
good idea if your input tape is a 200 MB file!


You've probably noticed this already and introduced rToken for that
reason but I'm not sure.


The idea is that the parser generates a stream of tokens. If/when it
hits an error, you get an error token at the end and parsing stops.


 Chasing down my memory leak I got into a weird situation where adding
 a magic manual SCC section and compiling with -prof makes the leak
 disappear.

That sounds fishy. Note that manual SCC annotations + optimization
currently is a bit buggy in GHC, in the sense that optimization disturbs
correct cost attribution.


Er... I just added '-prof'. No '-O' flag at all so no optimizations,
right?


Does the program eat the output of yes 'a' without memory explosion
showed by top? If so, it could perhaps be a problem of the
optimization phase which maybe expands

  D.append parsed (case result of ...)

to

  case result of {
  Nothing - D.append parsed D.empty
  Just .. - D.append parsed (D.singleton...) }

The latter won't stream because of the reason noted above.


Ah, but it *does* stream! This is the beauty of lazy evaluation.
The free code is basically:

reply = parse ... -- Lazily evaluated
tokens = rTokens reply -- Has some values immediately
list = D.toList tokens -- Has some values immediately
mapM_ list print -- Start printing immediately!

Where what parse does is:

reply = Reply {
  rTokens = D.append concreteToken lazyTokens, -- Immediate
  rResult = lazyResult -- Only available at end of parsing
}

So every time the parser calls D.append into the tokens, the printing
D.toList is able to extract, print and GC the token immediately. And
this works perfectly, with constant memory consumption. The problem
occurs when I peek at the final rResult field. The leak code says:

reply = parse ... -- Lazily evaluated
result = rResult reply -- Lazy; has value when parsing is done
extra = case result ... -- Lazy; has value when parsing is done
parsed = rTokens reply -- Has some values immediately
tokens = D.append parsed extra -- Has some values immediately
list = D.toList tokens -- Has some values immediately
mapM_ list print -- Starts printing immediately!

This *still* starts printing tokens immediately. However, while in the
previous case the GC is smart enough to keep the program in constant
memory size, in the second case it for some reasons starts missing more
and more PAP objects so memory usage goes through the roof.


But it's
highly unlikely that GHC performs a transformation that changes
semantics this radically.


You'd think... but the fact of the matter is that while the first
version works fine, the second doesn't, UNLESS I add the magic SCC
section:

 extra = {-# SCC magic #-} case result ...

And compile with '-prof' (no '-O' flags). Then it somehow, finally, get
the idea and the program runs perfectly well with constant memory
consumption. Which, as you aptly put it, is very fishy indeed...


 I can achieve the results I want in very short elegant code...

In my opinion, your streaming parser is not as elegant as it could be
which makes it hard to read the code.


Well... one point is the above basically establishes two threads, one
printing tokens and one producing them. communicating through a sort of
message queue (rTokens). I think that's pretty elegant compared to the
hoops you need to jump through to do this in any other language :-)

Another point is that this is a dumbed-down toy example. In the real
program the parser does much more which justifies the awkwardness you
point out. Specifically there are nifty ways to handle decision points
(parsing isn't much good unless there are alternatives to be tested at
each point :-).


With monad transformers, we almost
have

  Parser a ~= StateT State (WriterT (D.DList Token) Maybe) a
   ~= State - (D.DList Token, Maybe (a,State))


Monad transformers are a bit beyond my grasp at this point, but from the
little I know about them I don't see how they would help me with the
GC/memory problem. They definitely might make the code even more
elegant...


Also, I'm really missing type signatures, especially for many. When
reading the code, I expected

  many :: Parser a - Parser [a]

but had to conclude

  

[Haskell-cafe] Re: What I learned from my first serious attempt low-level Haskell programming

2007-04-10 Thread Lennart Augustsson
So then tail calls should be very cheap when most of the arguments  
don't change.


On Apr 10, 2007, at 10:17 , Simon Marlow wrote:


Lennart Augustsson wrote:
It's not that hard to figure out an order to permute the arguments  
on the stack before a tail call that minimizes that number of  
moves and temporary locations.  Lmlc did this 20 years ago. :)


Right, and that's what GHC does too, with a strongly-connected- 
component analysis of the dependencies between assignments of the  
args for the tail call.


Cheers,
Simon


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


Re: [Haskell-cafe] Profiling makes memory leak go away? Is Haskell apractical language?

2007-04-10 Thread Claus Reinke

reply = parse ... -- Lazily evaluated
tokens = rTokens reply -- Has some values immediately
list = D.toList tokens -- Has some values immediately
mapM_ list print -- Start printing immediately!
.. 

reply = parse ... -- Lazily evaluated
result = rResult reply -- Lazy; has value when parsing is done
extra = case result ... -- Lazy; has value when parsing is done
parsed = rTokens reply -- Has some values immediately
tokens = D.append parsed extra -- Has some values immediately
list = D.toList tokens -- Has some values immediately
mapM_ list print -- Starts printing immediately!

This *still* starts printing tokens immediately. However, while in the
previous case the GC is smart enough to keep the program in constant
memory size, in the second case it for some reasons starts missing more
and more PAP objects so memory usage goes through the roof.


is that a nail for this hammer, perhaps?-)

   http://hackage.haskell.org/trac/ghc/ticket/917

if you don't use rResult reply, reply can be used and freed as it is used.
if you do use rResult reply, you are going to use it late, and that is going to hang 
on to reply, which is being expanded by the main thread of activities (rTokens).


i'm just guessing here, but if that is indeed the problem, you would need to 
exert
more control over what is evaluated when and shared where:

- evaluate rResult synchronously with rTokens, instead of rResult long after
   rTokens has unfolded the reply
- evaluate rResult independent of rTokens, on a separate copy of reply

since you want to use parts of the output before you can be sure whether the
whole input is correct, you might also want local errors instead of global ones
(i've seen a correct chunk of input, here is the corresponding chunk of output;
instead of here is a list of output chunks i've produced so far, i'll tell you later 
whether they are worth anything or whether they were based on invalid input).



You'd think... but the fact of the matter is that while the first
version works fine, the second doesn't, UNLESS I add the magic SCC
section:

 extra = {-# SCC magic #-} case result ...

And compile with '-prof' (no '-O' flags). Then it somehow, finally, get
the idea and the program runs perfectly well with constant memory
consumption. Which, as you aptly put it, is very fishy indeed...


adding profiling might (another wild guess here..) lose sharing, just as in the 
ticket,
i used \()-[..] to avoid sharing of the list. (although that guess wouldn't 
necessarily
suggest this particular SCC to be useful, so perhaps it is the wrong track..)

hth,
claus

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


[Haskell-cafe] Weaving fun

2007-04-10 Thread Bas van Dijk

Hello,

For my own exercise I'm writing a function 'weave' that weaves a
list of lists together. For example:

 weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
 weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]

Note that 'weave' stops when a list is empty. Right now I have:

 weave :: [[a]] - [a]
 weave ll = work ll [] []
 where
   work ll = foldr f (\rst acc - work (reverse rst) [] acc) ll
   f [] g = \_   acc - reverse acc
   f (x:xs) g = \rst acc - g (xs:rst) (x:acc)

However I find this definition hard to read and I'm questioning its
efficiency especially due to the 'reverse' parts (how do they impact
performance and can they be removed?)

So I'm wondering if 'weave' can be defined more elegantly (better
readable, shorter, more efficient, etc.)?

happy hacking,

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


[Haskell-cafe] Re: What I learned from my first serious attempt low-level Haskell programming

2007-04-10 Thread Stefan O'Rear
On Tue, Apr 10, 2007 at 07:59:04PM +0100, Lennart Augustsson wrote:
 So then tail calls should be very cheap when most of the arguments  
 don't change.
 
 On Apr 10, 2007, at 10:17 , Simon Marlow wrote:
 
 Lennart Augustsson wrote:
 It's not that hard to figure out an order to permute the arguments  
 on the stack before a tail call that minimizes that number of  
 moves and temporary locations.  Lmlc did this 20 years ago. :)
 
 Right, and that's what GHC does too, with a strongly-connected- 
 component analysis of the dependencies between assignments of the  
 args for the tail call.
 
 Cheers,
  Simon

The tailcall in question is NOT statically known (it is a variant of
CPS), so simpleminded tail recursion optimizations will not help much. 

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


Re: [Haskell-cafe] Profiling makes memory leak go away? Is Haskell a practical language?

2007-04-10 Thread Brandon Michael Moore
On Tue, Apr 10, 2007 at 11:03:32AM -0700, Oren Ben-Kiki wrote:
 On Tue, 2007-04-10 at 12:14 +0200, apfelmus wrote:
 Oren Ben-Kiki wrote:
  The code is in http://hpaste.org/1314#a1 if anyone at all is willing
  to take pity on me and explain what I'm doing wrong.
 
 There is an important point to note about streaming, namely that it
 conflicts with knowing whether the input is syntactically correct or
 not.
 
 True, this is  the core issue. Think of a turing machine processing an
 infinite tape. It is writing output and producing a final result; it is
 possible to examine the output tape before knowing the final result.
 Haskell parsers insist on having the output tape live in memory until
 the final result is known, and then give it to you as one huge object
 when done (or discard it and just give you the error message). NOT a
 good idea if your input tape is a 200 MB file!

It's nothing to do with Haskell or memory mangagement, you just can't decide
whether the whole input is well-formed until you're done parsing, just like
you can't in general decide if a Turing machine is going to terminate until
it has.

You have to accept not knowing whether the input is well-formed until you
get to the end. There are two ways to do this that make it easy to get
streaming right. One is to have a data structure that explicitly contains
the possiblity of errors, like

data ErrList a = Another a (ErrList a) | Done | Failed err

Another is to return an ordinary structure containing values that
will raise an error when examined, and wrap a catch around the code
processing the streaming results. You might return for example a result

[1,2,3,error parse error at 10:3 blah blah blah]

You chose the most difficult way, returning immediately a structure
that has a field that when examined blocks until the input is done
and tells you if everything is valid.

That's tricky becuase it's very easy to make that field be some
unevaluated code that hangs onto the complete list of tokens and so
on, something like (a thunk of)
first_line_valid  second_line_valid  ...

GHC doesn't just go out and evaluate thunks onces their dependencies
arrive, because sometimes that's a bad idea, most obviously it it's something
like an unevaluated infinite list, say [1..], which has no free parameters.

It's the same problem you see in

--argument to break sharing
input () = 'a' : input ()

main = let text = input() in putStr (text ++ [last text])

As the infinite list is unfolded the thunk for last text is still
hanging onto the beginning, so it can't be garbage collected.

It happens that you can incrementally compute length as the list is
unfolded, but it's somewhat beyond the compiler to figure that out
for itself. But, you can fix it by writing a function that does
both operations together:

list_followed_by_length l = rec l 0 where
  rec (x:xs) len = len `seq` (x:rec xs (len + 1))
  rec [] = show len

Another option, if you're determined to be fancy, is to use the one
case where GHC actually does decide to evaluate something a little
bit during garbage collection. It's called a selector thunk -
if a piece of unevaluated code is *exactly* (after optimization)
case x of (_, .. , projected, ... _) - projected, or an equivalent
pattern match on another data type with just a single constructor
it will be replaced by a direct reference to x as evaluation
proceeds.

If you want to go this way, add the -ddump-simpl flag to GHC and
inspect the output, and see what adding -O or -O2 does to it.

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


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Brandon Michael Moore
On Wed, Apr 11, 2007 at 12:13:10AM +0200, Bas van Dijk wrote:
 Hello,
 
 For my own exercise I'm writing a function 'weave' that weaves a
 list of lists together. For example:
 
  weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
  weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]
 
 Note that 'weave' stops when a list is empty. Right now I have:

If it wasn't for that, you could use

import Data.List(transpose)
weave :: [[a]] - [a]
weave = concat . transpose

e.g.
  weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1,3]

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


Re: [Haskell-cafe] Prettyprinting infix expressions with HughesPJ

2007-04-10 Thread Stefan O'Rear
On Tue, Apr 10, 2007 at 09:20:52AM +0200, Alfonso Acosta wrote:
 I have to prettyprint infix expressions writing the least possible
 parenthesis (taking in account precedence and associativity). A
 simplified expression type could be:

Your use of 'have' is slightly suspicious here.  That said, the rest
of your problem looks very un-homework-y, so I'll look at it. 

Associativity is ambiguous here.  Do you mean:

1 + 2 + 3   =  (1 + 2) + 3  (Associativity of parsing)
(1 + 2) + 3 == 6 == 1 + (2 + 3)  (Associativity of functions)

?

 data Expr = Val String |
  -- Binary operators (using infix constructors)
  Expr :+: Expr  | Expr  :-: Expr  |
  Expr :*: Expr  | Expr  :/: Expr  |
  Expr :^: Expr |
  -- Unary operators
  Negate Expr
 
 
 I'm using HughesPJ for the rest of my AST (not just expressions) but
 the library doesn't provide any mechanism to help coding this kind of
 prettyprinter so I decided to simply use the standard showsPrec and
 then feed HughesPJ with the obtained text.

That seems very counter-productive.  By using showsPrec, you lose all
the information that could be used to guide line breaks.  It would be
far better to do it yourself.  Note that the method I am about to show
is exactly the same as that used by the standard showsPrec:

-- let +, - have infixl 1
-- let *, / have infixl 2
-- let ^ have infixr 3
-- let uminus have (nofix) 4

pprExpr :: Int  -- ^ Precedence context - if you're like me no
--   explanation of this will make more sense than the
--   code
- Expr - Doc
pprExpr cx (Val str) = text str
pprExpr cx (a :+: b) = cparen (cx = 1) $ pprExpr 1 a + char '+' + pprExpr 
1 b
pprExpr cx (a :-: b) = cparen (cx = 1) $ pprExpr 1 a + char '+' + pprExpr 
1 b
pprExpr cx (a :*: b) = cparen (cx = 2) $ pprExpr 2 a + char '+' + pprExpr 
2 b
pprExpr cx (a :/: b) = cparen (cx = 2) $ pprExpr 2 a + char '+' + pprExpr 
2 b
pprExpr cx (a :^: b) = cparen (cx = 3) $ pprExpr 3 a + char '+' + pprExpr 
3 b
pprExpr cx (Negate a) = cparen (cx = 4) $ char '-' + pprExpr 4 a

-- this is provided for ShowS under the name showsParen, but
-- unfortunately does not exist for Doc standardly
cparen :: Bool - Doc - Doc
cparen False = id
cparen True = parens

 showsPrec helps to take advantage of the precedence information.
 However, I don't find a way to remove parenthesis according to
 associativity.

A simple modification of the above code will do it:

pprExpr cx (Val str) = text str
pprExpr cx (a :+: b) = cparen (cx = 1) $ pprExpr 0 a + char '+' + pprExpr 
1 b
pprExpr cx (a :-: b) = cparen (cx = 1) $ pprExpr 0 a + char '-' + pprExpr 
1 b
pprExpr cx (a :*: b) = cparen (cx = 2) $ pprExpr 1 a + char '*' + pprExpr 
2 b
pprExpr cx (a :/: b) = cparen (cx = 2) $ pprExpr 1 a + char '/' + pprExpr 
2 b
pprExpr cx (a :^: b) = cparen (cx = 3) $ pprExpr 3 a + char '^' + pprExpr 
2 b
pprExpr cx (Negate a) = cparen (cx = 4) $ char '+' + pprExpr 4 a

Handling line breaks is left as an excercise for the reader.

 I'm sure this kind of prettyprinting has been already done zillions of
 times in Haskell. Any suggestions?

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


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Matthew Brecknell
Bas van Dijk:
 For my own exercise I'm writing a function 'weave' that weaves a
 list of lists together. For example:
 
   weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
   weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]
 
 Note that 'weave' stops when a list is empty.

This *almost* does what you want:

 weave' = concat . transpose

Perhaps you could look at implementations of transpose for inspiration.
The following two sources show implementations which behave differently
when given ragged matrices. You seem to be looking for something between
these two extremes.

http://darcs.haskell.org/libraries/base/Data/List.hs
http://www.soi.city.ac.uk/~ross/papers/Applicative.html

Here's a modification of the latter to give the termination behaviour
you show above:

 weave = concat . foldr zipWeave [] where
   zipWeave (x:xs) (ys:yss) = (x:ys) : zipWeave xs yss
   zipWeave xs [] = map (:[]) xs
   zipWeave [] ys = []

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


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Dan Piponi

Here's a very different approach. I make no claim to increased
elegance or efficiency, though I find it fairly readable and its made
of reusable parts. (Of course that's how you always finds your own
code!)

import Prelude hiding (head,tail)

-- Some would say this is how head and tail should have been defined.
head (a:_) = Just a
head _ = Nothing
tail (_:a) = Just a
tail _ = Nothing

-- A bit like map but stops when f returns Nothing.
mapWhile f (a:b) = case f a of
   Just x - x : mapWhile f b
   Nothing - []
mapWhile f [] = []

weave [] = []
weave a = mapWhile head a ++ weave (mapWhile tail a)


On 4/10/07, Bas van Dijk [EMAIL PROTECTED] wrote:

Hello,

For my own exercise I'm writing a function 'weave' that weaves a
list of lists together. For example:

  weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
  weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]

Note that 'weave' stops when a list is empty. Right now I have:

  weave :: [[a]] - [a]
  weave ll = work ll [] []
  where
work ll = foldr f (\rst acc - work (reverse rst) [] acc) ll
f [] g = \_   acc - reverse acc
f (x:xs) g = \rst acc - g (xs:rst) (x:acc)

However I find this definition hard to read and I'm questioning its
efficiency especially due to the 'reverse' parts (how do they impact
performance and can they be removed?)

So I'm wondering if 'weave' can be defined more elegantly (better
readable, shorter, more efficient, etc.)?

happy hacking,

Bas van Dijk
___
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] Weaving fun

2007-04-10 Thread Dave Feustel
Talk about synchronicity! I was just wondering whether 'weaving' of
infinite lists is possible.
 
eg weave the infinite lists [2,4..], [3,6..], [5,10..] 
to get [2,3,4,5,6,8,9,10,..]

Is this kind of lazy evaluation possible?

Thanks,
Dave Feustel

-Original Message-
From: Bas van Dijk [EMAIL PROTECTED]
Sent: Apr 10, 2007 6:13 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Weaving fun

Hello,

For my own exercise I'm writing a function 'weave' that weaves a
list of lists together. For example:

  weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
  weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]

Note that 'weave' stops when a list is empty. Right now I have:

  weave :: [[a]] - [a]
  weave ll = work ll [] []
  where
work ll = foldr f (\rst acc - work (reverse rst) [] acc) ll
f [] g = \_   acc - reverse acc
f (x:xs) g = \rst acc - g (xs:rst) (x:acc)

However I find this definition hard to read and I'm questioning its
efficiency especially due to the 'reverse' parts (how do they impact
performance and can they be removed?)

So I'm wondering if 'weave' can be defined more elegantly (better
readable, shorter, more efficient, etc.)?

happy hacking,

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


http://RepublicBroadcasting.org - Because You CAN Handle The Truth!
http://iceagenow.com - Because Global Warming Is A Scam!


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


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Ricardo Herrmann

This reminded me of interleaving as in:

Backtracking, Interleaving, and Terminating Monad Transformers
http://www.cs.rutgers.edu/~ccshan/logicprog/LogicT-icfp2005.pdf

On 4/10/07, Dave Feustel [EMAIL PROTECTED] wrote:


Talk about synchronicity! I was just wondering whether 'weaving' of
infinite lists is possible.

eg weave the infinite lists [2,4..], [3,6..], [5,10..]
to get [2,3,4,5,6,8,9,10,..]

Is this kind of lazy evaluation possible?

Thanks,
Dave Feustel

-Original Message-
From: Bas van Dijk [EMAIL PROTECTED]
Sent: Apr 10, 2007 6:13 PM
To: haskell-cafe@haskell.org
Subject: [Haskell-cafe] Weaving fun

Hello,

For my own exercise I'm writing a function 'weave' that weaves a
list of lists together. For example:

  weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
  weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]

Note that 'weave' stops when a list is empty. Right now I have:

  weave :: [[a]] - [a]
  weave ll = work ll [] []
  where
work ll = foldr f (\rst acc - work (reverse rst) [] acc) ll
f [] g = \_   acc - reverse acc
f (x:xs) g = \rst acc - g (xs:rst) (x:acc)

However I find this definition hard to read and I'm questioning its
efficiency especially due to the 'reverse' parts (how do they impact
performance and can they be removed?)

So I'm wondering if 'weave' can be defined more elegantly (better
readable, shorter, more efficient, etc.)?

happy hacking,

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


http://RepublicBroadcasting.org - Because You CAN Handle The Truth!
http://iceagenow.com - Because Global Warming Is A Scam!


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





--
Ricardo GuimarĂ£es Herrmann
You never change things by fighting the existing reality. To change
something, build a new model that makes the existing model obsolete - R.
Buckminster Fuller
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Chris Mears
Bas van Dijk [EMAIL PROTECTED] writes:

 Hello,

 For my own exercise I'm writing a function 'weave' that weaves a
 list of lists together. For example:

  weave [[1,1,1], [2,2,2], [3,3]] == [1,2,3,1,2,3,1,2]
  weave [[1,1,1], [2,2], [3,3,3]] == [1,2,3,1,2,3,1]

[...]

 So I'm wondering if 'weave' can be defined more elegantly (better
 readable, shorter, more efficient, etc.)?

I don't know about your other criteria, but this is shorter:

weave [] = []
weave ([]:_) = []
weave ((x:xs):others) = x : weave (others ++ [xs])

It's also lazy:

 take 12 $ weave [[1..], [100..], [200..]]
[1,100,200,2,101,201,3,102,202,4,103,203]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Dave Feustel
I ask this question because I want to program a recently published
algorithm for directly enumerating all prime numbers. The algorithm
description uses infinite sets. The algorithm could possibly be
programmed using lazy evaluation.

-Original Message-
From: Ricardo Herrmann [EMAIL PROTECTED]
Sent: Apr 10, 2007 7:24 PM
To: Haskell-Cafe@haskell.org
Subject: Re: [Haskell-cafe] Weaving fun

This reminded me of interleaving as in:

Backtracking, Interleaving, and Terminating Monad Transformers
http://www.cs.rutgers.edu/~ccshan/logicprog/LogicT-icfp2005.pdf

On 4/10/07, Dave Feustel [EMAIL PROTECTED] wrote:

 Talk about synchronicity! I was just wondering whether 'weaving' of
 infinite lists is possible.

 eg weave the infinite lists [2,4..], [3,6..], [5,10..]
 to get [2,3,4,5,6,8,9,10,..]

 Is this kind of lazy evaluation possible?

 Thanks,
 Dave Feustel


http://RepublicBroadcasting.org - Because You CAN Handle The Truth!
http://iceagenow.com - Because Global Warming Is A Scam!


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


Re: [Haskell-cafe] Type checking and locating token with Parsec

2007-04-10 Thread Stefan O'Rear
On Tue, Apr 10, 2007 at 02:09:03PM +0100, Joel Reymont wrote:
 Folks,
 
 Imagine a language where Num + Num yields a Num and Str + Num yields  
 a Str but Num + Str should not be allowed.
 
 I implemented parsing for such a language in OCaml with a yacc-based  
 parser without an additional type-checking pass, entirely within the  
 yacc grammar. I tried to take such an approach with Parsec but hit  
 the roadblock with buildExpressionParser since it returns the same  
 type as the token parser given to it.

Just because you have a hammer doesn't mean you have a nail.  I've
gotten along all this time never learning buildExpressionParser,
instead hand-coding my precedence parsers.

 Rather than have numerical expressions, string expressions, etc., as  
 separate types, I simplified things down to a single expression type  
 that holds my booleans, strings and numbers. I now need to implement  
 type checking of my parsed AST.

Would something like this work for you:

data NumExpr = ...
data StrExpr = ...

data Expr = NumExpr NumExpr | StrExpr StrExpr

addExpr :: Expr - Expr - CharParser st Expr
addExpr (NumExpr n) (NumExpr m) = NumExpr (Add n m)
addExpr (StrExpr n) (NumExpr m) = StrExpr (Cat n (ToString m))

...

op3 ch fn a b = join $ liftM3 (\x _ y - fn x y) a (char ch) b

...

exp0 = op3 '+' addExpr exp1 exp0 ...

It might also be good to modify chainl1/chainr1, with support for
possibly failing operations. 

Remember - the provided abstractions have failed you, but you can
still define your own! 

 The main issue is error reporting. I'm not sure where to get token  
 location with Parsec and how to elegantly embed it in my AST.
 
 Has anyone implemented type checking on top of a Parsec-based parser?
 
 How did you locate your tokens?

There's haskell-src:

http://haskell.org/ghc/dist/current/docs/libraries/haskell-src/Language-Haskell-Syntax.html

And people wonder why I decided to abuse template haskell instead of
using the standard AST type.  You do NOT want to go there.  Not until
Oleg invents a way to make this stuff automatic, anyway. 

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


Re: [Haskell-cafe] Prettyprinting infix expressions with HughesPJ

2007-04-10 Thread Alfonso Acosta

On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:

Your use of 'have' is slightly suspicious here.  That said, the rest
of your problem looks very un-homework-y, so I'll look at it.


It's for my masters thesis (big piece of badly-specified homework  if
you want to think about it like that :)). I used have cause I'm
coding an embedded VHDL compiler and I really have to pretty print
VHDL in the backend :) (the more readable the code I get the better).



Associativity is ambiguous here.  Do you mean:
1 + 2 + 3   =  (1 + 2) + 3  (Associativity of parsing)


This is what I mean. Say - is right associative in the target
language, that allows to remove the parenthesis of the following
expression 1 - (1 - 2) and just write 1 - 1 - 2, but probably the
code would be less readable since a human doesn't normally take that
in account (I tend to forget those things and keep writing parenthesis
all the time anyway).


(1 + 2) + 3 == 6 == 1 + (2 + 3)  (Associativity of functions)


I don't see how taking this in account would make the output more readable.




 data Expr = Val String |
  -- Binary operators (using infix constructors)
  Expr :+: Expr  | Expr  :-: Expr  |
  Expr :*: Expr  | Expr  :/: Expr  |
  Expr :^: Expr |
  -- Unary operators
  Negate Expr


 I'm using HughesPJ for the rest of my AST (not just expressions) but
 the library doesn't provide any mechanism to help coding this kind of
 prettyprinter so I decided to simply use the standard showsPrec and
 then feed HughesPJ with the obtained text.

That seems very counter-productive.  By using showsPrec, you lose all
the information that could be used to guide line breaks.


Yes, you're totally right. Thanks a lot for your code :)


It would be
far better to do it yourself.  Note that the method I am about to show
is exactly the same as that used by the standard showsPrec:

-- let +, - have infixl 1
-- let *, / have infixl 2
-- let ^ have infixr 3
-- let uminus have (nofix) 4

pprExpr :: Int  -- ^ Precedence context - if you're like me no
--   explanation of this will make more sense than the
--   code
- Expr - Doc
pprExpr cx (Val str) = text str
pprExpr cx (a :+: b) = cparen (cx = 1) $ pprExpr 1 a + char '+' + pprExpr 
1 b
pprExpr cx (a :-: b) = cparen (cx = 1) $ pprExpr 1 a + char '+' + pprExpr 
1 b
pprExpr cx (a :*: b) = cparen (cx = 2) $ pprExpr 2 a + char '+' + pprExpr 
2 b
pprExpr cx (a :/: b) = cparen (cx = 2) $ pprExpr 2 a + char '+' + pprExpr 
2 b
pprExpr cx (a :^: b) = cparen (cx = 3) $ pprExpr 3 a + char '+' + pprExpr 
3 b
pprExpr cx (Negate a) = cparen (cx = 4) $ char '-' + pprExpr 4 a

-- this is provided for ShowS under the name showsParen, but
-- unfortunately does not exist for Doc standardly
cparen :: Bool - Doc - Doc
cparen False = id
cparen True = parens

 showsPrec helps to take advantage of the precedence information.
 However, I don't find a way to remove parenthesis according to
 associativity.

A simple modification of the above code will do it:

pprExpr cx (Val str) = text str
pprExpr cx (a :+: b) = cparen (cx = 1) $ pprExpr 0 a + char '+' + pprExpr 
1 b
pprExpr cx (a :-: b) = cparen (cx = 1) $ pprExpr 0 a + char '-' + pprExpr 
1 b
pprExpr cx (a :*: b) = cparen (cx = 2) $ pprExpr 1 a + char '*' + pprExpr 
2 b
pprExpr cx (a :/: b) = cparen (cx = 2) $ pprExpr 1 a + char '/' + pprExpr 
2 b
pprExpr cx (a :^: b) = cparen (cx = 3) $ pprExpr 3 a + char '^' + pprExpr 
2 b
pprExpr cx (Negate a) = cparen (cx = 4) $ char '+' + pprExpr 4 a

Handling line breaks is left as an excercise for the reader.

 I'm sure this kind of prettyprinting has been already done zillions of
 times in Haskell. Any suggestions?

Stefan


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


Re: [Haskell-cafe] Prettyprinting infix expressions with HughesPJ

2007-04-10 Thread Stefan O'Rear
On Wed, Apr 11, 2007 at 01:53:49AM +0200, Alfonso Acosta wrote:
 On 4/11/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 Your use of 'have' is slightly suspicious here.  That said, the rest
 of your problem looks very un-homework-y, so I'll look at it.
 
 It's for my masters thesis (big piece of badly-specified homework  if
 you want to think about it like that :)). I used have cause I'm
 coding an embedded VHDL compiler and I really have to pretty print
 VHDL in the backend :) (the more readable the code I get the better).

Hehe.  We're happy to solve subproblems.  It's the
copied-verbatim-from-the-book homework problems we mind. 

 
 Associativity is ambiguous here.  Do you mean:
 1 + 2 + 3   =  (1 + 2) + 3  (Associativity of parsing)
 
 This is what I mean. Say - is right associative in the target
 language, that allows to remove the parenthesis of the following
 expression 1 - (1 - 2) and just write 1 - 1 - 2, but probably the
 code would be less readable since a human doesn't normally take that
 in account (I tend to forget those things and keep writing parenthesis
 all the time anyway).

It's pretty easy to make this happen - just pretend (-) is
non-associative. 

 (1 + 2) + 3 == 6 == 1 + (2 + 3)  (Associativity of functions)
 
 I don't see how taking this in account would make the output more readable.

Suppose we receive Lit 1 :+: (Lit 2 :+: Lit 3).  Would you rather read
1 + 2 + 3 or 1 + (2 + 3)? 

NB: Beware of floating points!

  data Expr = Val String |
   -- Binary operators (using infix constructors)
   Expr :+: Expr  | Expr  :-: Expr  |
   Expr :*: Expr  | Expr  :/: Expr  |
   Expr :^: Expr |
   -- Unary operators
   Negate Expr
 
 
  I'm using HughesPJ for the rest of my AST (not just expressions) but
  the library doesn't provide any mechanism to help coding this kind of
  prettyprinter so I decided to simply use the standard showsPrec and
  then feed HughesPJ with the obtained text.
 
 That seems very counter-productive.  By using showsPrec, you lose all
 the information that could be used to guide line breaks.
 
 Yes, you're totally right. Thanks a lot for your code :)

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


Re: [Haskell-cafe] Weaving fun

2007-04-10 Thread Matthew Brecknell
Dave Feustel:
 Talk about synchronicity! I was just wondering whether 'weaving' of
 infinite lists is possible.
  
 eg weave the infinite lists [2,4..], [3,6..], [5,10..] 
 to get [2,3,4,5,6,8,9,10,..]
 
 Is this kind of lazy evaluation possible?

The base library version of (concat . transpose) can do that, since for
infinite lists, you don't have the termination requirements of the OP.

By the way, there is an error in my previous version of weave:

*Main weave [[1,1,1,1],[2,2],[3,3,3]]
[1,2,3,1,2,3,1,1]

Dan's version also has this behaviour.

So, a correct list-based solution that doesn't use reverse or quadratic
concatenation isn't immediately obvious. However, Chris Mears' solution
can easily be adapted to use the O(1) snoc from Data.Sequence:

 import Data.Sequence
 
 weave = weaveSeq . fromList where
   weaveSeq xs = case viewl xs of
 (x:xs) : xss - x : weaveSeq (xss | xs)
 _ - []

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


[Haskell-cafe] Re: Type error

2007-04-10 Thread oleg

Alfonso Acosta wrote:
 I tried the existential approach when it was previously suggested by
 Chris, but the problem is that, for some Source instances calling
 methods from HDPrimType within supplySig is not enough. Thus, it
 doesn't work with existentials due to their limitations.

I see. The typechecker is right then: one can't write 
   supplySig  :: (PortIndex ix, HDPrimType a) = HDSignal a - ix - d - d

because supplySig is not parametric in 'a': supplySig needs to know
more than just the membership of 'a' in HDPrimType. It needs a more
refined constraint. So, the class hierarchy has to change, for
example, as follows

 data HDSignal a = HDSignal
 data HDSignal' d = forall a. DestPort' d a = HDSignal' (HDSignal a)
 class HDPrimType a where
 class PortIndex a where

 class SourcePort s where
  -- Plug an external signal to the port
  plugSig  :: (PortIndex ix, DestPort d) =ix - s  - (HDSignal' d - b) - b

 class DestPort d where
  supplySig  :: (PortIndex ix) = HDSignal' d - ix - d - d
  supplySig (HDSignal' sig) = supplySig' sig

 class HDPrimType a = DestPort' d a where
  -- Supply a signal to the port
  supplySig'  :: (PortIndex ix) = HDSignal a - ix - d - d

 -- Connect providing indexes

 connectIx :: (SourcePort s, PortIndex six, DestPort d, PortIndex dix) =
  six - s - dix - d - d
 connectIx six s dix d = plugSig six s $ (push2 supplySig) dix d


 push2 :: (a - b - c - d) - b - c - a - d
 push2 f = (\b c a - f a b c)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe