[Haskell-cafe] Re: [Haskell] thread-local variables

2006-08-08 Thread Frederik Eaton
 Furthermore, can we move this thread from the Haskell mailing list
 (which should not have heavy traffic) to either Haskell-Café, or
 the libraries list?

Sure, moving to haskell-cafe.

Frederik

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


Re: [Haskell-cafe] Haskell performance in heavy numerical computations

2006-07-16 Thread Frederik Eaton
Alberto Ruiz has developed a linear algebra library which could be
seen as an alternative to Matlab/Octave, using the GSL, ATLAS, LAPACK,
etc. IIRC.

http://dis.um.es/~alberto/GSLHaskell/

I've optimized it in some places, and added an interface which
guarantees operand conformability through the type system at compile
time.

http://ofb.net/~frederik/stla/

It is almost twice as fast as Octave on an example program, and
probably comparable to Matlab. However, it is currently very difficult
to debug some of the type errors which are emitted by GHC when using
it, and there are some outstanding heap-related bugs. Also, we don't
have as wide a variety of built-in functions as Matlab and Octave do.

Frederik

On Thu, Jul 06, 2006 at 11:03:11PM +0100, Joel Reymont wrote:
 Is anyone using Haskell for heavy numerical computations? Could you share 
 your experience?
 
 My app will be mostly about running computations over huge amounts of stock 
 data (time series)  so I'm thinking 
 I might be better of with OCaml.
 
   Thanks, Joel

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


[Haskell-cafe] Re: [Haskell] ANNOUNCE: An index-aware linear algebra library in Haskell

2006-04-16 Thread Frederik Eaton
Hi Alberto,

Those are good questions, I've added some examples which hopefully
clarify the situation. Input and output of vectors is not a strong
point of the library, but I don't think there is a good alternative to
the way I do it.

  http://ofb.net/~frederik/futility/src/Vector/read-example.hs

(also, your example exposed some missing functionality. I've added
three new functions; in addition to listMat, now there are listMatCol,
listMatRow, and listMatSquare. Hopefully these should cover almost all
use cases.

  http://ofb.net/~frederik/futility/src/Vector/Base.hs
)

By the way, here is how I would download and run the thing, although
you seem to have figured it out:

$ wget http://ofb.net/~frederik/futility/futility-devel.tar.gz
$ tar -xvzf futility-devel.tar.gz
$ cd futility-devel/
$ ghc -fth --make Vector/read-example.hs -o read-example
$ ./read-example
# 11.0, 23.0; 14.0, 30.0; 15.0, 33.0; 18.0, 40.0 #
1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0, 10.0
1.0, 2.0, 3.0, 4.0, 5.0, 6.0, 7.0, 8.0, 9.0, 10.0
# 1.0, 5.0; 2.0, 6.0; 3.0, 6.0; 4.0, 7.0 #
# 11.0, 23.0; 14.0, 30.0; 15.0, 33.0; 18.0, 40.0 #
# -3.0, -5.0; -5.0, -7.0 #
# 7.0, 10.0; 15.0, 22.0 #

As for your questions:

 Vector/examples.hs:35:11:
 GHC stage restriction: `x'
   is used in a top-level splice, and must be imported, not defined locally
 In the first argument of `dAM', namely `x'
 In the definition of `m1': m1 = $[splice](dAM x)

This is a shortcoming of Template Haskell - it will not let you call a
function from a splice if that function is defined in the same file as
the splice. It should be possible to remove this shortcoming, but I
don't know what is planned.

 m2 = listMat x

This is not how listMat is used, see the example file above.

listMat takes a list of lists and a function, and passes the matrix
version of the list of lists to the function.

 I would also like to create a matrix from a data file:

See 'v3' in the example.

Cheers,

Frederik

On Sun, Apr 16, 2006 at 05:06:55PM +0200, Alberto Ruiz wrote:
 It is really counterintuitive! I will study carefully your library and the 
 Implicit Configurations paper. Using static dimension checking we can write 
 very solid code for matrix computations...
 
 However, I don't know how to write some definitions. For instance, this is ok:
 
 m = $(dAM [[1,2,3]])
 
 but with:
 
 x = [[1,2,3]] :: [[Double]]
 m1 = $(dAM x)
 m2 = listMat x
 
 main = do
 print m1
 print m2
 
 I get:
 
 Vector/examples.hs:35:11:
 GHC stage restriction: `x'
   is used in a top-level splice, and must be imported, not defined locally
 In the first argument of `dAM', namely `x'
 In the definition of `m1': m1 = $[splice](dAM x)
 
 Vector/examples.hs:40:10:
 Inferred type is less polymorphic than expected
   Quantified type variable `m' escapes
   Quantified type variable `n' escapes
   Expected type: (v (L m, L n) - w) - t
   Inferred type: (forall n1 m1.
   (ReflectNum n1, ReflectNum m1) =
   v (L m1, L n1) - w)
  - w
 In the first argument of `print', namely `m2'
 In the result of a 'do' expression: print m2
 
 
 I would also like to create a matrix from a data file:
 
 main = do
 let m1 = $(dAM [[1,2],[3,4::Double]])
 s - readFile data.txt
 let list = read s :: [[Double]]
 --let m2 = $(dAM list)
 let m2 = listMat list
 print $ m2 * trans m1
 
 But I get a similar error. Perhaps I must provide information about the 
 expected dimensions, but I don't know how to do it.
 
 --
 Alberto
 
 On Saturday 15 April 2006 22:09, Frederik Eaton wrote:
  Yes, certainly... Otherwise the library would not be much use! If it
  seems counterintuitive, as it did to me at first, you should check out
  the Implicit Configurations paper, which uses modular arithmetic as
  an example. My version of their code is in
 
  http://ofb.net/~frederik/futility/src/Prepose.hs
 
  The function I mainly use is:
 
  reifyIntegral :: Integral a = a - (forall s. ReflectNum s = s - w) - w
 
  which turns an integral value into a type of the ReflectNum class
  which represents that value, and calls the provided polymorphic
  function with a dummy value (actually 'undefined') of that type; then
  returning the function's result.
 
  Frederik
 
  On Sat, Apr 15, 2006 at 06:14:44PM +0200, Alberto Ruiz wrote:
   On Friday 14 April 2006 17:02, Frederik Eaton wrote:
An index-aware linear algebra library in Haskell
  
   Excellent work!
  
   Is it possible to create a vector or matrix whose size is not known at
   compile time?
  
 

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


[Haskell-cafe] Re: [Haskell] ANNOUNCE: An index-aware linear algebra library in Haskell

2006-04-15 Thread Frederik Eaton
Yes, certainly... Otherwise the library would not be much use! If it
seems counterintuitive, as it did to me at first, you should check out
the Implicit Configurations paper, which uses modular arithmetic as
an example. My version of their code is in

http://ofb.net/~frederik/futility/src/Prepose.hs

The function I mainly use is:

reifyIntegral :: Integral a = a - (forall s. ReflectNum s = s - w) - w

which turns an integral value into a type of the ReflectNum class
which represents that value, and calls the provided polymorphic
function with a dummy value (actually 'undefined') of that type; then
returning the function's result.

Frederik

On Sat, Apr 15, 2006 at 06:14:44PM +0200, Alberto Ruiz wrote:
 On Friday 14 April 2006 17:02, Frederik Eaton wrote:
  An index-aware linear algebra library in Haskell
 
 Excellent work!
 
 Is it possible to create a vector or matrix whose size is not known at 
 compile 
 time? 
 
  - Due to the need to specify index types at some point, input of
  vectors is difficult. I have provided two functions in Fu.Vector.Base
  which should cover most of the cases:
 
  listVec :: Vector v e = [e] - (forall n . (ReflectNum n) = v (L n) - w)
  - w 
  listMat :: Vector v e = [[e]] - 
  (forall n m . (ReflectNum n, ReflectNum m) = v (L m, L n) - w) - w
 
  However, these aren't useful in interactive situations. So I have also
  provided some template-haskell routines
 
http://ofb.net/~frederik/futility/src/Vector/Template.hs
 
  which can be used to instantiate vectors directly. For example:
 
 (In examples.hs):
 
 -- matrix with elements of type Double
 v6 = trans $(dAM [[1,2,3,4]])
 
 v7 = $(dAM [[1,0,0],[0,1,0],[0,0,1],[1,1,1]])
 
 --
 Alberto
 

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


[Haskell-cafe] Re: generics question 2

2006-04-04 Thread Frederik Eaton
Hi Ralf,

Thanks. I'm sorry, now I think that wasn't the source of my problem. 
What I want to do is specialise not to a specific type like Bool but
to the class of all pairs (a,b). But this causes the compiler to
complain, even for simpler examples:

cast True :: (Typeable a, Typeable b) = Maybe (a,b)

interactive:1:0:
Ambiguous type variable `a' in the constraints:
  `Typeable a' arising from instantiating a type signature at 
interactive:1:0-51
  `Show a' arising from use of `print' at Top level
Probable fix: add a type signature that fixes these type variable(s)

interactive:1:0:
Ambiguous type variable `b' in the constraints:
  `Typeable b' arising from instantiating a type signature at 
interactive:1:0-51
  `Show b' arising from use of `print' at Top level
Probable fix: add a type signature that fixes these type variable(s)

Is there a way to solve this, or do I have to avoid polymorphism? I
can use 'toConstr' to find out dynamically if a particular type is a
pair, and then use unsafeCoerce, but I hear that unsafeCoerce is
unsafe.

Frederik

On Mon, Apr 03, 2006 at 05:41:55PM -0700, Ralf Lammel wrote:
  Hi Ralf,
  
  I'm looking for a function like extT but with more general type:
  
  (t a - s a) - (t b - s b) - (t a - s a)
  
  Is there such a thing in the generics library?
 
 Hi Frederik,
 
 Not sure how you are exactly going to use such an operation ...
 But here is its implementation anyhow.
 Thanks for the riddle.
 
 Ralf
 
 import Data.Generics
 
 -- Frederik's weird ext operation :-)
 ext' :: (Data (t a), Data (s a), Data (t b), Data (s b))
  = (t a - s a) - (t b - s b) - (t a - s a)
 ext' f g ta = case cast g of
Just g' - g' ta
Nothing - f ta
 
 -- A generic default
 f (Just x) = [x]
 f Nothing  = []
 
 -- A type-specific case
 g (Just True)  = [True]
 g (Just False) = []
 g Nothing  = []
 
 -- A composition using our new type-extension operator
 test :: Data a = Maybe a - [a]
 test = ext' f g
 
 -- Let's see whether it works ...
 main = do 
   print $ test (Just (1::Int))
   print $ test (Just False)
 
 

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


[Haskell-cafe] generics question 2

2006-04-03 Thread Frederik Eaton
Hi Ralf,

I'm looking for a function like extT but with more general type:

(t a - s a) - (t b - s b) - (t a - s a)

Is there such a thing in the generics library?

Thanks,

Frederik

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


Re: [Haskell-cafe] matrix computations based on the GSL

2006-03-16 Thread Frederik Eaton
Hi Alberto,

I'm sorry if this has been discussed before...

I'm reading your paper, at one point it says (re. the PCA example):
Octave achieves the same result, slightly faster. (In this experiment
we have not used optimized BLAS libraries which can improve efficiency
of the GSL)

That seems to imply that there is a way to use optimized BLAS
libraries? How can I do that?

Also, in my experiments (with matrix inversion) it seems,
subjectively, that Octave is about 5 or so times faster for operations
on large matrices. Presumably you've tested this as well, do you have
any comparison results?

Thanks,

Frederik

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


Re: [Haskell-cafe] STUArray

2006-03-11 Thread Frederik Eaton
I see. The solutions on that thread, i.e.: 

http://www.mail-archive.com/haskell%40haskell.org/msg17085.html

would seem to require me to at least declare an instance of some
class, for every type that I want to support. So the short answer to
I'm trying to figure out how to use STUArray. Is it possible to let
it be polymorphic? appears to be No.

Perhaps some sort of warning in the documentation for STUArray is in
order, until Bulat's code can be incorporated?

By the way, why make the distinction between unboxable types and
other types in the first place? E.g., just because I want something
to work quickly on Int, doesn't mean that I don't want it to work at
all on String. It seems that there could be a default IArray UArray
e instance which just implements a regular Array behind the scenes.

Frederik

On Fri, Mar 10, 2006 at 11:49:10PM +0100, Benjamin Franksen wrote:
 On Friday 10 March 2006 23:01, Frederik Eaton wrote:
  I'm trying to figure out how to use STUArray. Is it possible to let
  it be polymorphic?
 
 Hi Frederik
 
 I think this thread (and the one it referres to) provide a solution:
 
 http://www.mail-archive.com/haskell%40haskell.org/msg17081.html
 
 Ben
 -- 
 There are three kinds of programmers: those who make off by one errors, 
 and those who don't.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


[Haskell-cafe] STUArray

2006-03-10 Thread Frederik Eaton
Hi all,

I'm trying to figure out how to use STUArray. Is it possible to let it
be polymorphic?

Here is an excerpt from my program:

class (IArray UArray k, Ord k, Fractional k) = Elt k

class (Bounded a, Enum a, Ix a, Eq a, Show a) = IxB a 

-- |like Array but uses IxB instead of Ix 
newtype Vector k i = Vector (UArray.UArray i k) deriving (Eq) 

margin :: (IxB a, IxB b, Elt k, (MArray (STUArray s) k (ST s))) = Vector k 
a - (a - b) - Vector k b
margin (Vector v) f = Vector (runSTUArray (do
ax - newArray (minBound, maxBound) 0
mapM_ (\ (i,x) - updateArray ax (f i) (+x)) (assocs v)
return ax
  )) where
updateArray ax i f = do
  e - readArray ax i
  writeArray ax i (f e)

When I try to run it, I get the following error. I think I understand
what the error means, but not how to fix the problem:

Vector2.hs:166:22:
No instance for (MArray (STUArray s) k (ST s))
  arising from use of `updateArray' at Vector2.hs:166:22-32
Probable fix:
  add (MArray (STUArray s) k (ST s)) to the expected type of an 
expression
  or add an instance declaration for (MArray (STUArray s) k (ST s))
In a lambda abstraction: \ (i, x) - updateArray ax (f i) ((+ x))
In the first argument of `mapM_', namely
`(\ (i, x) - updateArray ax (f i) ((+ x)))'
In a 'do' expression:
mapM_ (\ (i, x) - updateArray ax (f i) ((+ x))) (assocs v)

Thanks in advance,

Frederik

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


Re: [Haskell-cafe] matrix computations based on the GSL

2005-12-09 Thread Frederik Eaton
Hi,

I've just looked through this discussion, since I'm working on my own
library, I wanted to see what people are doing.

It's something like this, using the Prepose (Implicit Configurations)
paper:

data L n = L Int deriving (Show, Eq, Ord)

-- singleton domain
type S = L Zero

class (Bounded a, Ix a) = IxB a

instance ReflectNum n = Bounded (L n) where
minBound = L 0
maxBound = L $ reflectNum (__ :: n) - 1

mul :: (Num k, IxB a, IxB b, IxB c) = Matrix k a b - Matrix k b c - Matrix k 
a c
add :: (Num k, IxB a, IxB b) = Matrix k a b - Matrix k a b - Matrix k a b
vec :: (Num k, IxB a, IxB b) = Matrix k a b - Matrix k (a,b) S

This way one can form a type L n which represents integers between 0
inclusive and n (rather, 'reflectNum (__ :: n)') exclusive, which can
serve to index the matrices and vectors... Of course, other index
types are allowed, such as Either a b - if we want to, say, take the
sum of two vector spaces, one indexed by a and the other by b,
then the result should be indexed by Either a b, etc. - we never
have to do anything with the type-level numerals other than assert
equality, i.e. we don't have to be able to add or multiply them in our
type-signatures, since structural operations will suffice.

I think having the ability to guarantee through the type system that
column and row dimensions are correct is of paramount importance to
those who would use a matrix library, but so far in this thread I
haven't seen any suggestions which would accomplish that. I'm sorry if
I didn't read carefully. Does my approach not work? I haven't filled
in the implementation yet, but it type-checks.

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


Re: [Haskell-cafe] How to debug GHC

2005-09-19 Thread Frederik Eaton
On Mon, Sep 19, 2005 at 02:22:10PM +0100, Glynn Clements wrote:
 
 Frederik Eaton wrote:
 
  In addition to the stack trace problems, I found: (1) a problem where
  output freezes when it is being piped through 'tee' and the user
  presses ^S and then ^Q
 
 That's the terminal driver; use stty -ixon to disable that.

That will sure prevent ^S and ^Q having any effect, but it won't make
the bug go away. With other programs, e.g. if I run

seq 10 | tee foo

and press ^S and then ^Q, then suspend and resume work as expected,
there is no freezing shortly after resume as I am observing with my
ghc-compiled program. The program should resume its output when ^Q is
pressed, rather than freezing.

Frederik

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


Re: [Haskell-cafe] generics question, logical variables

2005-09-18 Thread Frederik Eaton
Hi Ralf,

I'm revisiting this project and just have another question. The story
seems to be that GHC cannot derive Typeable1, or Typeable when
Typeable1 is available - so anyone who wants to use ext1Q must define
special instances for all of the datatypes they use, is this correct? 
Will this change soon?

Aside from that, your 'idify' in PseudoFmap2 certainly seems to have
the correct type for this application. However, the absence of
automatic derivation is somewhat of an impediment.

Thanks for your help.

Frederik

On Tue, Aug 30, 2005 at 02:25:08PM -0700, Ralf Lammel wrote:
 Frederik,
 
  As for your code example, it looks very interesting, but are you
  saying that this could turn into an extension of the Data.Generics
  library, or that this is something I could be implementing in terms of
  what's already there?
 
 The posted code works with GHC 6.4 (SYB2) intentionally and actually. I
 have attached another attempt (again GHC 6.4, based on SYB2) which might
 be more useful for your purposes, and it may be useful in general, in
 fact.
 
 What I defined this time is a certainty-improving function:
 
 idify :: (Typeable1 f, Monad m, Data (a f), Data (a Id))
   = (forall a. f a - m a) - a f - m (a Id)
 
 That is, the function idify get takes a value whose type is
 parameterized in a type constructor f (such as Maybe or IORef), and the
 function attempts to establish Id instead of f on the basis of the
 function argument get.
 
  What is the 'a' parameter for in force?
  
  force :: ( Data (t Maybe a)
   , Data (t Id a)
   , Term t Maybe a
   , Term t Id a
   ) = t Maybe a - t Id a
 
 The previous attempt was a more parameterized blow than required in your
 case. (I was guessing about what typed logical variables could mean.
 I was assuming that you would need some extra layer of embedding types
 on top of the Haskell term types. Looking at your code, this was not the
 case.)
  
  For the part which I asked for help with, to get around my trouble
  with generics, I defined a class GenFunctor and an example instance.
  The intent is that generics should be able to provide this
  functionality automatically later on, but you can see what the
  functionality is.
 
 Let's look at the type of your GenFunctor:
 
 class GenFunctor f where
 gfmapM :: (Monad m, FunctorM b) = (forall x . a x - m (b x)) - f
 a - m (f b)
 
 This type can be seen as a more relaxed version of the idify operation
 above. That is, idify fixes GenFunctor's b to Id. The particular
 encoding of idify (attached) takes advantage of this restriction. I
 wonder whether I should bother. (Exercise for reader :-))
 
  However, I am stuck on something else, the program doesn't typecheck
  because of use of another function I defined, 'cast1'. Maybe you can
  take a look. I had thought that I would be able to write a generic
  'unify' but I get the error:
  
  GenLogVar.hs:82:19:
  Ambiguous type variable `a' in the constraint:
`Data a' arising from use of `cast1' at GenLogVar.hs:82:19-23
  Probable fix: add a type signature that fixes these type
 variable(s)
  
  This is because I need to do something special when I encounter a
  Var variable in unification, but the compiler seems to not like the
  fact that the type argument of the Var data type is not known.
 
 Please try to avoid new cast operations at all costs. :-)
 Your code can be arranged as follows:
 
 (i) Use extQ1 to dispatch to a special case for Var x for the first
 argument. (ii) In this special case, use again ext1Q to dispatch to a
 special case for Var y for the second argument. (iii) At this point,
 *cast* the variable value of *one* variable to the type of the other.
 
 So the problem with your code, as it stands, is that the target type of
 cast is ambiguous because you cast *both* arguments. The insight is to
 make the cast asymmetric. Then, not even polymorphism is in our way.
 
 Interesting stuff!
 
 Ralf
 



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


Re: [Haskell-cafe] How to debug GHC

2005-09-18 Thread Frederik Eaton
  It could be a bug - can you reduce the example and report it?
  
  GHC's profiler tries to overlay a lexical call graph on to the dynamic
  execution of the program.  It does this more or less in the way you
  described before: every function gets an extra argument describing the
  call context.  However, there are some tricky areas: notably CAFs.  We
  don't as yet have a principled description of the mechanism, and I know
  of various cases where odd results are obtained with the current system.
  Also, the optimiser has to be careful not to change the shape of the
  call graph, and I suspect there are cases where it goes wrong.
 
 I see. Well, I'm afraid I've lost the example, but I'll keep my eyes
 open in case it happens again. It's good to know what the correct
 behavior is supposed to be.

While I was finishing a project for somebody I ran into this problem
again, as well as some other bugs, and made several copies of the code
so that the problems could be reproduced.

In addition to the stack trace problems, I found: (1) a problem where
output freezes when it is being piped through 'tee' and the user
presses ^S and then ^Q and (2) an issue where a trace statement is
not being printed correctly by ghc (but is being printed correctly by
runghc).

However, I don't have time to reduce these to minimal test cases. Do
you want to look at them anyway?

Frederik

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


Re: [Haskell-cafe] How to debug GHC

2005-09-14 Thread Frederik Eaton
On Wed, Sep 14, 2005 at 02:44:11PM +0100, Simon Marlow wrote:
 On 10 September 2005 21:15, Frederik Eaton wrote:
 
  On Fri, Sep 02, 2005 at 04:40:05PM +0400, Bulat Ziganshin wrote:
  Hello Nils,
  
  Friday, September 02, 2005, 10:47:05 AM, you wrote:
  
  Compile your program with -prof -auto-all (make sure you have
  the 
  
  I tried this out under GHC 6.4/Linux and got a segmentation fault
  instead of a stack trace. Under GHC 6.2.2 it seemed to work, though.
  
  this error is already fixed in current pre-6.4.1 version
  
  I'm using a 2005/9/3 version of 6.4.1 and running into situations
  where the stack trace has function A calling function B, where when
  I look at the code, A never calls B. Is this normal? Is it some
  side-effect of laziness? It sure makes the traces a lot less useful.
 
 It could be a bug - can you reduce the example and report it?
 
 GHC's profiler tries to overlay a lexical call graph on to the dynamic
 execution of the program.  It does this more or less in the way you
 described before: every function gets an extra argument describing the
 call context.  However, there are some tricky areas: notably CAFs.  We
 don't as yet have a principled description of the mechanism, and I know
 of various cases where odd results are obtained with the current system.
 Also, the optimiser has to be careful not to change the shape of the
 call graph, and I suspect there are cases where it goes wrong.

I see. Well, I'm afraid I've lost the example, but I'll keep my eyes
open in case it happens again. It's good to know what the correct
behavior is supposed to be.

Frederik

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


Re: [Haskell-cafe] How to debug GHC

2005-09-02 Thread Frederik Eaton
 Just more or less as an aside, at its origin in April (!) this thread
 didn't mention any debugger - the question was just how to build ghc
 so that a stack trace would come out.  A real debugger is no replacement
 for that (because you have to be on hand and know how to repeat the problem
 to get anywhere with a debugger), but that's just my opinion.
 
   Donn Cave, [EMAIL PROTECTED]

I agree. Some could argue that stack traces are no replacement for a
debugger but it is also true that a debugger is no replacement for
stack traces. :)

I will try the +RTS -xc -RTS method, many thanks to everybody for
the advice.

Frederik

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


Re: [Haskell-cafe] How to debug GHC

2005-09-01 Thread Frederik Eaton
On Wed, Apr 27, 2005 at 05:15:30PM +1000, Bernard Pope wrote:
 On Wed, 2005-04-27 at 07:45 +0200, Ketil Malde wrote:
   [I want to know] who called who all the way from main to head,
   because the key function is going to be one somewhere in the middle.
  
  Perhaps.  I am told stack backtraces are difficult with non-strict
  semantics.
 
 This is true, at least for _lazy_ implementations of non-strict
 semantics.

 The reason is that the (graph) context in which a function application
 is constructed can be very different to the context in which it is
 reduced. 

Is it that backtraces are difficult, or just require a lot of
overhead? It doesn't seem very hard to me, at least in principle. Add
a stack trace argument to every function. Every time a function is
called, the source location of the call is prepended to the stack
trace. I'm not familiar with the implementation of functional
programming languages, though.

(It seems like if the operation of GHC or GHCI could be parametrized
by an arbitrary monad, here a Reader, then transformations like the
above wouldn't be so difficult, and compiler compatibility for
debuggers wouldn't be so much of an issue.)

 Partial application of functions introduces a similar problem.

 This is not a problem in first-order eager languages because the
 construction of a (saturated) function application is followed
 immediately by its reduction. Thus the contexts of construction and
 reduction are the same.
 
 Debugging tools like Hat, Freya and Buddha, remember the
 construction context of an application, so you can get call graphs that
 reflect the dependencies between symbols in the source code. Thus you
 can construct a meaningful backtrace etc. Actually, Hat remembers quite
 a bit more context than Freya and Buddha, but that's another story.

Are the following correct?

1. Hat requires users to restrict themselves to a certain small subset
of the standard libraries, and to use hmake

2. Buddha doesn't work with GHC 6.4

3. I can't find Freya

4. I can't find HsDebug. Maybe it's part of the fptools cvs
repository? But solander.dcs.gla.ac.uk seems to be down :(

But getting a stack backtrace when there is an error should be a
pretty basic feature. It's very hard to debug a large program when you
can randomly get messages like *** Exception: Prelude.head: empty
list and have no idea where they came from. So GHC's many features
become much less useful when there is no debugger which supports a
program that has been written with them.

Furthermore, in my opinion, this sort of error location information is
much more valuable to debugging a program, than being able to step
through its execution, which is the more difficult problem that a lot
of the debuggers seem to be aimed at solving. So maybe it would be
good if GHC had basic stack trace support built in? It could be a
compiler option, which would produce slower but more debuggable
code...

Frederik

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


Re: [Haskell-cafe] generics question, logical variables

2005-08-29 Thread Frederik Eaton
 strong typing.
 - We make the assumption that all occurrences of Spot are to be
 converted.
 - That is, we don't quite track the type parameter for Maybe vs. Id.
 - This is a bit inefficient because of going through Tree Constr.
 
 So I am willing to summarize that this is potentially a sort of a (cool)
 hack.
 
 Code attached.
 
 Ralf 
 
 P.S.: The extension you propose seems to be a major one. Perhaps you
 could look into the TH code for SYB3 (ICFP 2005) to see whether this can
 be automated. This sort of discussion calls for kind polymorphism once
 again.
 
 
  -Original Message-
  From: [EMAIL PROTECTED] [mailto:haskell-cafe-
  [EMAIL PROTECTED] On Behalf Of Frederik Eaton
  Sent: Sunday, August 28, 2005 9:36 PM
  To: haskell-cafe@haskell.org
  Subject: [Haskell-cafe] generics question, logical variables
  
  Hi all,
  
  I'm trying to write something like a generic fmap, or a generic
  natural transformation. The application is this. I have a typed
  logical variable library which produces arbitrary terms with values of
  type Var a, which are references to a value of type Maybe a, and I
  want to write a solve function which replaces these values with
  instantiated versions of type Id a where
  
  newtype Id a = Id a
  
  . Furthermore I want this to be reflected in the type of the generic
  term:
  
  solve :: Pred (t Var) - [t Id]
  
  so if I have a type like
  
  data Entry k = Entry (k String) (k Int)
  
  then I can write some constraint equation with values of type Entry
  Var, and get back values of type Entry Id - in other words, objects
  where the unknowns are statically guaranteed to have been filled in.
  
  I looked at the generics library. I may be mistaken, but it seems that
  it doesn't have what I need to do this. The problem isn't the mapping,
  it's creating a new type which is parameterized by another type. The
  only options for creating new types are variations on
  
  fromConstr :: Data a = Constr - a
  
  but what is needed is something like
  
  fromConstr1 :: Data1 a = Constr1 - a b
  
  With something like that it should be possible to define:
  
  gmapT1 :: (forall b . Data1 b = b l - b m) - a l - a m
  
  Does this make sense? Here I would be treating all instances of Data
  as possibly degenerate instances of Data1 (which just might not depend
  on the type variable).
  
  If it seems like a good idea, I would be interested in helping out
  with the implementation.
  
  Frederik
  
  --
  http://ofb.net/~frederik/
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 



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


[Haskell-cafe] generics question, logical variables

2005-08-28 Thread Frederik Eaton
Hi all,

I'm trying to write something like a generic fmap, or a generic
natural transformation. The application is this. I have a typed
logical variable library which produces arbitrary terms with values of
type Var a, which are references to a value of type Maybe a, and I
want to write a solve function which replaces these values with
instantiated versions of type Id a where

newtype Id a = Id a

. Furthermore I want this to be reflected in the type of the generic
term:

solve :: Pred (t Var) - [t Id]

so if I have a type like

data Entry k = Entry (k String) (k Int)

then I can write some constraint equation with values of type Entry
Var, and get back values of type Entry Id - in other words, objects
where the unknowns are statically guaranteed to have been filled in.

I looked at the generics library. I may be mistaken, but it seems that
it doesn't have what I need to do this. The problem isn't the mapping,
it's creating a new type which is parameterized by another type. The
only options for creating new types are variations on

fromConstr :: Data a = Constr - a

but what is needed is something like

fromConstr1 :: Data1 a = Constr1 - a b

With something like that it should be possible to define:

gmapT1 :: (forall b . Data1 b = b l - b m) - a l - a m

Does this make sense? Here I would be treating all instances of Data
as possibly degenerate instances of Data1 (which just might not depend
on the type variable).

If it seems like a good idea, I would be interested in helping out
with the implementation.

Frederik

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


Re: [Haskell-cafe] cabal --user question

2005-07-11 Thread Frederik Eaton
Hi Isaac,

Is there a way to specify a particular package.conf for use when
installing and registering packages with Cabal? I'm trying to
Cabal-ize WASH which has a number of packages which depend on each
other. The problem is that in order to build the next package, the
previous one has to be installed, yet users typically want to do a
full build *before* installing anything. I was thinking that for the
'make' step it could just install each package locally and register it
in a local package.conf (i.e. somewhere in the project tree), and then
'make install' would rerun the install commands with the final install
location and final package database as arguments. But I can't figure
out how to specify the local package.conf to 'configure' or 'install',
there are just the '--user' and '--global' commands which aren't quite
enough.

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


[Haskell-cafe] cabal --user question

2005-07-10 Thread Frederik Eaton
Hi,

How do I install a package in the user package.conf with cabal? It is
not clear to me how to do this, looking at the output of 'configure
--help'. There is an option --user to get dependencies from the user
cabal file but this still, somewhat counterintuitively, tries to
install the package in the global location (why would one want such
behavior?). Specifying '--with-hc-pkg=ghc-pkg --user' doesn't seem
to work either, when I do this then 'install' and 'unregister'
complete without error but apparently have no effect.

Thanks in advance,

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


Re: [Haskell-cafe] cabal --user question

2005-07-10 Thread Frederik Eaton
Thanks for the quick reply!

  How do I install a package in the user package.conf with cabal? It is
  not clear to me how to do this, looking at the output of 'configure
  --help'. There is an option --user to get dependencies from the user
  cabal file but this still, somewhat counterintuitively, tries to
  install the package in the global location (why would one want such
  behavior?). Specifying '--with-hc-pkg=ghc-pkg --user' doesn't seem
  to work either, when I do this then 'install' and 'unregister'
  complete without error but apparently have no effect.
 
 ./setup configure --user #if it depends on user-local packages
 ./setup build
 ./setup install --user

Ah, I see.

 Perhaps install --user should be the default if you configure --user.

Yeah, it seems somewhat inconsistent - everything about the
installation of a package is usually controlled by 'configure' options
(e.g. in autoconf), even in cabal the prefix is still part of
'configure' but the other relevant installation parameter is specified
as an option to 'install'...

For one, it means that I can't just call ./setup unregister to
unregister my package, I have to remember which arguments I passed to
'register' or 'install'. It seems like a bad design to me. At the very
least, I should be able to specify the default behavior (user or
global) at configure time so that if I run these commands without
arguments they behave in a way that is consistent with each other and
with the package configuration.

Is there a reason why there is no 'uninstall' command, by the way? It
might be useful.

Also, I would shorten the '--copy-prefix' argument to 'copy' to just
'--prefix' unless there is a good reason for having it that way. The
copy- part seems reduntant to me. That's my opinion.

 The user's guide is here:
 
 http://www.haskell.org/ghc/docs/latest/html/Cabal/

Thanks,

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


Re: [Haskell-cafe] cabal --user question

2005-07-10 Thread Frederik Eaton
I forgot to say, when I run configure like

runghc Setup.hs configure --with-hc-pkg=ghc-pkg --user --prefix=$HOME

and then run 'install', it exits with code 127 but displays no error
message. Maybe something to look into...

Frederik

On Sun, Jul 10, 2005 at 05:00:13PM -0700, Frederik Eaton wrote:
 Thanks for the quick reply!
 
   How do I install a package in the user package.conf with cabal? It is
   not clear to me how to do this, looking at the output of 'configure
   --help'. There is an option --user to get dependencies from the user
   cabal file but this still, somewhat counterintuitively, tries to
   install the package in the global location (why would one want such
   behavior?). Specifying '--with-hc-pkg=ghc-pkg --user' doesn't seem
   to work either, when I do this then 'install' and 'unregister'
   complete without error but apparently have no effect.
  
  ./setup configure --user #if it depends on user-local packages
  ./setup build
  ./setup install --user
 
 Ah, I see.
 
  Perhaps install --user should be the default if you configure --user.
 
 Yeah, it seems somewhat inconsistent - everything about the
 installation of a package is usually controlled by 'configure' options
 (e.g. in autoconf), even in cabal the prefix is still part of
 'configure' but the other relevant installation parameter is specified
 as an option to 'install'...
 
 For one, it means that I can't just call ./setup unregister to
 unregister my package, I have to remember which arguments I passed to
 'register' or 'install'. It seems like a bad design to me. At the very
 least, I should be able to specify the default behavior (user or
 global) at configure time so that if I run these commands without
 arguments they behave in a way that is consistent with each other and
 with the package configuration.
 
 Is there a reason why there is no 'uninstall' command, by the way? It
 might be useful.
 
 Also, I would shorten the '--copy-prefix' argument to 'copy' to just
 '--prefix' unless there is a good reason for having it that way. The
 copy- part seems reduntant to me. That's my opinion.
 
  The user's guide is here:
  
  http://www.haskell.org/ghc/docs/latest/html/Cabal/
 
 Thanks,
 
 Frederik
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tuple and HList

2005-03-21 Thread Frederik Eaton
 You need to swap the arguments to TCons...
 
 data TCons l a = TCons !l a
 
 Then:
 
 instance Functor (TCons (TCons HNil a)) where
fmap f (TCons (TCons HNil x) y) = TCons (TCons HNil (f x)) y)

How does one solve this problem in general, i.e. when the arguments to
a type are in the wrong order for an instance that one wants to
declare? Someone on the haskell IRC channel mentioned that if you
could derive instances for partially applied type synonyms then one
could just make a dummy synonym with the arguments in the right order,
but that doesn't appear to be premitted. The other question is why
isn't it permitted.

Frederik

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


Re: [Haskell-cafe] tuple and HList

2005-03-20 Thread Frederik Eaton
  This was brought up in passing in a recent conversation on
  haskell-cafe

Sorry, mairix was malfunctioning...

  It certainly seems like an interesting idea, Would type inference
  still work okay?

I don't understand all of the issues. One is that in the HList paper,
rather than constructing HLists with data constructors, they use
special functions which guarantee through class constraints that the
tail of an HList is a valid HList, and not some other random type.
(There was some reason that they didn't want to put the constraints on
the data type itself.) But this prevents us from using the same syntax
in construction and pattern matching. And if tuples were syntactic
sugar for something that constructs a valid HList then it seems the
constraints wouldn't be necessary.

  The other problem mentioned is that they are not quite isomorphic,
  since HLists are equivalant to (a,(b,c)) rather than (a,b,c), but
  changing HCons so that it is strict in its second argument makes them
  behave the same I think..

And it's important to be able to costruct a HList with one element.
Perhaps the syntax (a,) could be used for a tuple with one element?

 Since most of the HList functionality is defined using type classes, we
 could probably declare a new type, TCons, make it strict in the second
 argument, and use it alongside HCons.
 
 data TCons a b = TCons a !b
 
 One way t make tuples into sugar for HLists would be to effectively have
 a series of declarations like these:
 
 type (a,b)   = TCons a (TCons b HNil)
 type (a,b,c) = TCons a (TCons b (TCons c HNil))
 
 But then we can't use tuples in instance declarations. That is, there
 isn't any way to desugar 'instance Functor ((,) a)' without using a type
 lambda.

I'm not sure I understand this, but the intent was that you'd use e.g.
TCons instead of the tuple syntax in instance declarations.

 On the other hand, using HLists for tuples means we can have projection
 functions that work on any tuple arity, which would be nice.

Another thing which I don't think is mentioned in the paper, which is
convenient, is that you can define HLists all of whose elements are
members of a given class:

class HListShow l
instance HListShow HNil
instance (Show a, HListShow l) = HListShow (a :* l)

It's not as clean as if you could parameterize over classes, but it's
better than this...

(Show a, Show b) = Show (a, b)
(Show a, Show b, Show c) = Show (a, b, c)
(Show a, Show b, Show c, Show d) = Show (a, b, c, d)
(Show a, Show b, Show c, Show d, Show e) = Show (a, b, c, d, e)

Frederik

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


Re: [Haskell-cafe] tuple and HList

2005-03-20 Thread Frederik Eaton
That's a neat technique. Since it's so general it would be nice if
there were a way to make it more automatic, could one use template
haskell? It seems one should be able to write

HListConstraint $(mkConstraint Show) l

to generate the declarations automatically.

Frederik

On Sun, Mar 20, 2005 at 11:05:06PM +, Keean Schupke wrote:
 Frederik Eaton wrote:
 
 Another thing which I don't think is mentioned in the paper, which is
 convenient, is that you can define HLists all of whose elements are
 members of a given class:
 
 class HListShow l
 instance HListShow HNil
 instance (Show a, HListShow l) = HListShow (a :* l)
  
 
 You can avoid the need to declare a new class for each constrained list
 by using the following:
 
 class Constraint c a
 
 data SHOW
 instance Show a = Constraint SHOW a
 
 class HListConstraint c l
 instance HListConstraint c HNil
 instance (Constraint c a,HListConstraint c l) = HListConstraint c 
 (HCons a l)
 
 You can now constrain a list as follows:
 
 assertShow :: HListConstraint SHOW l = l - l
 assertShow = id
 
 The type parameter can be made first class using:
 
 showConstraint :: SHOW
 showConstraint = undefined
 
 So we can now pass this as a parameter:
 
 assertConstraintOnHList :: HListConstraint c l = c - l - l
 assertConstraintOnHList _ = id
 
Keean.
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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


[Haskell-cafe] tuple and HList

2005-03-19 Thread Frederik Eaton
HList seems just like a tuple, but more powerful because one can
access the type structure directly, and more cumbersome because one
has to use lengthier constructors a 'nil' terminator. So why not just
make tuples synonyms for HLists, so one can use HLists with the
shorter notation, and have the added benefit of being able to access
the internals of a tuple (e.g. make instances which concatenate
generic tuples, project elements, etc.)...?

Frederik

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