Problem when compiling with -prof -fasm

2003-06-12 Thread Zdenek Dvorak
Hello,

when compiling anything with -prof -fasm, I get the following response:

ghc-6.0: panic! (the `impossible' happened, GHC version 6.0):
AbsCStixGen.gencode
CC_DECLARE(CGI_CAFs_cc,CAF,CGI,CC_IS_CAF,);

Please report it as a compiler bug to [EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.

(without -fasm I get

Prologue junk?: .globl __stginit_CGI
.type   __stginit_CGI,@function
__stginit_CGI:
pushl   %ebp
movl%esp, %ebp

instead, which is probably caused by non-supported version of gas or gcc?)

Zdenek Dvorak
___
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: int to float problem

2003-03-01 Thread Zdenek Dvorak
Hello,

[snip]
Try

intToFloat :: Int - Float
intToFloat n = fromInteger (toInteger n)
[snip]

Use the Prelude function realToFrac.
it sometimes happens to me that I must spend some time browsing
prelude to devise somethink like this; it might be useful to have
a library for this, that would define
class Coerce a b where
 coerce :: a-b
of course this cannot work without multiparametric type classes.

Zdenek

_
Help STOP SPAM with the new MSN 8 and get 2 months FREE*  
http://join.msn.com/?page=features/junkmail

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: FiniteMap performance WITHOUT any copying?

2003-02-08 Thread Zdenek Dvorak
Hello,


Now, Haskell has a garbage collector, so Haskell must know how many
pointers there are to all objects in the heap (or?). Then, if a finite map
for example only has one single pointer to it, then it ought to be all
right to modify the finite map (or whatever datastructure we are
considering), I mean really modify the map without making any copies, just
like in imperative languages. Perhaps there might be pointers to nodes
inside the tree and I guess that could complicate the matter somewhat. But
for Haskell arrays it ought to be possible to really modify the array if
it is used by only one pointer ?

Are such optimizations possible, and if they are, are they already
implemented in for example GHC ? Or am I wrong somewhere ?


You are more or less right; except that
-- the Haskell implementations I have seen do not keep number of pointers to
objects (gc in principle works by traversing the graph made by pointers,
marking reachable nodes and finally removing the unreachable ones; just
keeping the number of references is not sufficient due to cyclic structures)
-- due to lazy evaluation, the situation where there would be just one
pointer to array is rare

Zdenek

_
Add photos to your messages with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: default class methods in sub-classes

2003-02-06 Thread Zdenek Dvorak
Hello,


Apparently I can't do this (in ghc or hugs -- haven't tried others):

class Space a where
  distance :: a - a - Int
  subtract :: a - a - a

class (Space a) = NormSpace a where
  norm :: a - Int
  distance a b = norm (subtract a b)

That is, I can't make (or redefine) a default for the superclass method
'distance' in a subclass.  I agree that the Haskell'98 definition doesn't
claim that this should be allowed, but it seems like something that would 
be
useful.  Are there reasons not to allow this (or that I shouldn't want to 
do
this at all)?

Apologies if this is well-covered.  I couldn't find any mention of it.

the problem is, that to make something instance of NormSpace, you must first
have it as instance of Space, i.e. with distance already defined. Then for 
this
to work, the default definition in NormSpace would have to override what 
user
defined, which looks strange.

Your problem can be solved in ghc by this (but unfortunately only with
-fallow-overlapping-instances -fallow-undecidable-instances (or some 
simmilar
flags)):

class HavingSubtract a where  -- not sure why generic space should have 
subtract,
 subtract :: a - a - a -- but why not

class (HavingSubtract a) = Space a where
 distance :: a - a - Int

class (HavingSubtract a) = NormSpace a where
 norm :: a - Int

instance (NormSpace a) = Space a where
 distance a b = norm (subtract a b)

(and there is several more examples in that I would find something like this
very useful, but AFAIK there is no clean and elegant way how to do it --
you may do something simmilar using newtypes, but that is totally clumsy).

Zdenek

_
The new MSN 8: smart spam protection and 2 months FREE*  
http://join.msn.com/?page=features/junkmail

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: avoiding cost of (++)

2003-01-16 Thread Zdenek Dvorak
Hello,


I have a function which behaves like map, except instead of applying the
given function to, say, the element at position 5, it applies it to the
entire list *without* the element at position 5.  An implementation looks
like:

 mapWithout :: ([a] - b) - [a] - [b]
 mapWithout f = mapWith' []
 where mapWith' pre [] = []
   mapWith' pre (x:xs) = f (pre ++ xs) : mapWith' (x:pre) xs

Unfortunately, this is very slow, due to the overhead of (++).

Any way I could speed this up would be great.  Note that order doesn't
matter to 'f', but I do need that the order in which the elements of the
list are processed be the same as in map.


two remarks:
1) as long as f works on single list, there is no way how to make things
  faster (IMHO)
2) this solution is up to constant factor optimal due to laziness (at most 
one
  step of ++ will be evaluated for each element f needs)

Zdenek Dvorak

_
Protect your PC - get McAfee.com VirusScan Online 
http://clinic.mcafee.com/clinic/ibuy/campaign.asp?cid=3963

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Question About Random Module

2002-12-24 Thread Zdenek Dvorak
Hello,


Hello! I just Wanna Know, What should I do, to build a List of random 
Numbers,
without IO type, just Float or Int

the answer for this is either you can't, read something about IO and monads
(good starting places are http://haskell.org/wiki/wiki?UsingIo and
http://haskell.org/wiki/wiki?UsingMonads, and reading other FAQs there is a
good idea, too) or you should not, but if you really have to, browse this
mailing list archives, where you'll find the answer 1000x, depending on 
what
you are asking for.

Zdenek

_
MSN 8 helps eliminate e-mail viruses. Get 3 months FREE*. 
http://join.msn.com/?page=features/virusxAPID=42PS=47575PI=7324DI=7474SU= 
http://www.hotmail.msn.com/cgi-bin/getmsgHL=1216hotmailtaglines_virusprotection_3mf

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Running out of memory in a simple monad

2002-11-29 Thread Zdenek Dvorak
Hello,

I hope I understand what's going on; if not please someone correct me.


I have problems with monads and memory. I have a monad through which
I thread output. If I do the concatenation of the output-strings in
one way Hugs runs out of memory, but if I do it in another way
everything works. I can't see why the first way doesn't work but the
second is OK. I woudl appreciate if someone could tell me what I am
doing wrong.
  Here is the non-working monad:   -}


The problem is not directly connected to monads; what is the problem:

[] ++ x = x
(h:t) ++ x = h : (t++x),

i.e. time complexity of ++ is proportional to the length of first list.

first way:


putCharM c  = M $ \o  - ((), o ++ [c]) -- Is this stupid in some way?


this takes list (looong) of everything produced before this putCharM and
concatenates c as last member; this takes time linear in the length of
the list, summing over all putCharMs it is quadratic (and of course,
due to laziness a lot of memory is consumed; seq does not help, as it only
evaluates first cell of the list so that it sees it is not empty; deepSeq
would solve this, but the time consumption would still stay long).

the second way:


  M f = k  = M $
let (x, o)   = f
M f2 = k x
(x', o') = f2
in (x', o ++ o')


this is done reverse way (because = is bracketed to the right); we
concatenate output of f (short) with output of f2 (the rest of computation,
i.e. looong); but the time is proportional to the length of first list,
so it is constant in our case; summing it over all putCharMs, we get linear
time and we are happy :-)

If you want to do it the first way, define

putCharM c  = M $ \o  - ((), c : o)

and then reverse the list in runM.

Zdenek Dvorak

_
Add photos to your messages with MSN 8. Get 2 months FREE*. 
http://join.msn.com/?page=features/featuredemail

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: need help optimizing a function

2002-10-08 Thread Zdenek Dvorak

Hello,

  p.s., I sense your next question is going to be something like why
  can't the compiler detect that the array can be updated in place
  instead of copied and the answer, from what i can tell, is simply
  that it doesn't try.

And one might argue that it should not try
[snip]

and the other answer is that the result would not be worth the effort
usually. The idea seems nice, but the laziness is where I see the problem;
see the following code:

do_something::Array Int Int-(Array Int Int, Result)
do_something a = (a'',res)
where
  a' = a // [(summon_index, summon_int)]
  w = a' ! 4
  res = do_some_work w
  a'' = a' // [(summon_other_index, summon_other_int)]

Seems like nice candidate for update-in-place? But the problem is, that
in general you cannot say when w will be evaluated -- so you simply cannot
destroy a' before then.

This is also reason why DiffArray (from hslibs) does not have to be very 
useful,
unless you have a good control on when things are evaluated -- it may (and 
it
also happened to me) have quadratic behavior in cases like this.

To solve this, '!' would have to produce a new array too; but then you must
pass it everywhere and effectively you are doing the work monads would do
for you.

So in general you must choose -- either your programs will be nice and 
functional,
but you will have to use structures with (some kind of) logarithmic slowdown
(FiniteMap, Trie), or some of their parts will be embedded in monads.

Zdenek Dvorak

_
MSN Photos is the easiest way to share and print your photos: 
http://photos.msn.com/support/worldwide.aspx

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: how to debug?

2002-10-06 Thread Zdenek Dvorak

Hello,

How does one debug in haskell? I have a function that I could swear should
behave differently than it does, and after tracking down bugs for many
hours, I'm wondering if there's any way to step through the evaluation of a
haskell function?

The other way I would be debugging in an imperative language would be to
sprinkle printfs around.  Is there any way to do something like that
cleanly in haskell?  The only thing I can think of would be to modify every
function to accept an additional parameter, which seems like it's more
likely to introduce bugs than remove them...

For what it's worth I'm using ghc, and the only debugging options it seems
to have are for debugging the compiler itself.  I would be happy to install
and use hugs for debugging if it has some nicer debugging mode.

I have already isolated my bug within one function, but that function has
somewhat funky recursion, and uses an array (which I'm none too familiar
with in haskell), and there aren't any smaller parts that I can see to
test.  :(

aside from (useful) general advices already given, just few tips that I
found useful when I needed to debug:

-- to print debug dumps, you may use 'trace' function from IOExts (but 
beware,
   it may affect behavior of your program if used incorrectly)
-- other way (safer, but slower to learn and use) is to use Hood library
-- if your program fails with some really informative error message of type
   '*** Exception: Maybe.fromJust: Nothing', compiling it with profiling
   (-prof -auto-all) and running with +RTS -xc will give you a stack dump
   (pretty useful, well hidden feature :-)

Zdenek Dvorak

_
Chat with friends online, try MSN Messenger: http://messenger.msn.com

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Pretty printing (was: Standard Library for text formatting?)

2002-08-26 Thread Zdenek Dvorak

Hello,

  After doing some searching, it seems that pretty printing is
  a prominant Haskell way of doing text output.  I still am
  interested in finding a library of standard text formatting
  (String formatting) functions, but it seems like it might
  be worth my while investigating pretty printing.

Pretty printing is not very suited for printf like formatting,

I have looked for something simmilar some time ago, but unsuccesfully. 
Pretty printing libraries are not very useful for breaking paragraphs into 
lines, distributing spaces evenly, etc. (at least I was not able to persuade 
them to work like that). I have written following module that implements 
stupid first-fit algorithm for these purposes; the interface is simmilar to 
the pretty printing libraries.

Zdenek Dvorak

module ReportPrinter (
LowDoc,HighDoc,
(),(+),($$),($),
int, lowText, text, empty,
colon, comma, space, semi, period,
brackets, parens,
vcat, sep,
punctuate,
high, nest, par,
render
) where

data LowDoc=Text String |
Join LowDoc LowDoc |
Append LowDoc LowDoc |
Empty deriving (Show)

data HighDoc=HLowDoc LowDoc |
 Paragraph Int HighDoc |
 Nest Int HighDoc |
 Above HighDoc HighDoc |
 Beside HighDoc HighDoc deriving (Show)

()::LowDoc-LowDoc-LowDoc
x  Empty = x
Empty  x = x
x  y = Join x y

(+)::LowDoc-LowDoc-LowDoc
x + Empty = x
Empty + x = x
x + y = Append x y

($)::HighDoc-HighDoc-HighDoc
x $ HLowDoc Empty=x
HLowDoc Empty $ x=x
x $ y=Beside x y

($$)::HighDoc-HighDoc-HighDoc
x $$ HLowDoc Empty=x
HLowDoc Empty $$ x=x
x $$ y=Above x y

lowText::String-LowDoc
lowText=Text

text::String-LowDoc
text str=sep $ map lowText $ words str

int::Int-LowDoc
int=text . show

empty::LowDoc
empty=Empty

colon::LowDoc
colon=lowText :

comma::LowDoc
comma=lowText ,

space::LowDoc
space=lowText  

semi::LowDoc
semi=lowText ;

period::LowDoc
period=lowText .

brackets::LowDoc-LowDoc
brackets doc=lowText [  doc  lowText ]

parens::LowDoc-LowDoc
parens doc=lowText (  doc  lowText )

sep::[LowDoc]-LowDoc
sep=foldl (+) empty

high::LowDoc-HighDoc
high=HLowDoc

vcat::[HighDoc]-HighDoc
vcat=foldl ($$) (high empty)

punctuate::LowDoc-[LowDoc]-[LowDoc]
punctuate _ [] = []
punctuate _ [x] = [x]
punctuate pun (h:t) = (h  pun) : punctuate pun t

nest::Int-HighDoc-HighDoc
nest=Nest

par::Int-HighDoc-HighDoc
par=Paragraph

render::Int-HighDoc-String
render width doc=highRender width 0 0 doc 

highRender::Int-Int-Int-HighDoc-String-String
highRender width indFirst indRest doc rest=
case doc of
  HLowDoc lowDoc - lowRender width indFirst indRest lowDoc rest
  Paragraph ind pDoc - highRender width indFirst (indRest+ind) pDoc rest
  Nest ind pDoc  - highRender width (indFirst+ind) (indRest+ind) pDoc 
rest
  Above doc1 doc2- highRender width indFirst indRest doc1 $
highRender width indRest indRest doc2 rest
  Beside doc1 doc2   - error Rendering two HighDocs beside not supported.

lowRender::Int-Int-Int-LowDoc-String-String
lowRender width indFirst indRest doc rest=
  stringRender width indFirst indRest strs rest
  where
   (strs,_) = stringify False doc []
   stringify False (Text txt) rest =
   ((txt,length txt):rest,False)
   stringify True (Text txt) [] =
   ([(txt,length txt)],False)
   stringify True (Text txt) ((txt',len'):rest) =
   ((txt++txt',length txt+len'):rest,False)
   stringify join Empty rest = (rest,join)
   stringify join (Append doc1 doc2) rest =
 let (rest',join')=stringify join doc2 rest
  in stringify join' doc1 rest'
   stringify join (Join doc1 doc2) rest =
 let (rest',_)=stringify join doc2 rest
  in stringify True doc1 rest'

stringRender::Int-Int-Int-[(String,Int)]-String-String
stringRender width indFirst indRest [] rest=rest
stringRender width indFirst indRest strs rest=
let (lne,rst)=cutLine (width-indFirst) strs
 rest'=stringRender width indRest indRest rst rest
  in lineRender (rst==[]) width indFirst lne rest'


cutLine tot ((txt,len):t)=(txt:lne',rst)
where
  (lne',rst)=cutLine' (tot-len) t
  cutLine' ml []=([],[])
  cutLine' ml r@((tx,ln):t')
   | mlln = let (lne'',rst')=cutLine' (ml-ln-1) t'
  in (tx:lne'',rst')
   | otherwise = ([],r)

lineRender::Bool-Int-Int-[String]-String-String
lineRender last width ind lne rest=indent ind rslt
where
  totlen   = sum $ map length lne
  words= length lne
  reqlen   = totlen + words - 1
  havelen  = width - ind
  distsp   = if havelen  reqlen  not last then havelen - reqlen else 0
  count= words `div` 2
  rslt = distribSpaces count distsp words lne rest
  indent n = (take n (cycle  ) ++)

distribSpaces::Int-Int-Int-[String]-String-String
distribSpaces _ _ _ [h] rest = h ++ '\n' : rest
distribSpaces count minus plus (h:t) rest = h ++ ' ' : spaced
where
  (spaced,count') = recount count
  rest' = distribSpaces (count'-minus) minus plus t rest
  recount cnt
   | cnt  0   = let

RE: comparison of execution speed of array types

2002-07-23 Thread Zdenek Dvorak

Hello,

DiffArray seems to be broken :).  Either that or I'm using it
incorrectly.  I've attached the relevant code, but when I don't reverse
the array everything works fine; when I reverse it the program doesn't
(seem to) halt.

I've tried to use DiffArray recently and it is terribly slow. I was forced
to write my own version (it is a bit faster, but still nothing great). My
suspicion about the result of your measuring is that it does the updates
in reversing the array one by one, thus leading to quadratic behavior.

Zdenek Dvorak

_
Chat with friends online, try MSN Messenger: http://messenger.msn.com

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Defining instances of superclasses

2002-06-30 Thread Zdenek Dvorak

Hello.

I've got the following problem:

I have class Structure, that says that its members have some internal parts
that can be read from/written to Strings:

data StrItem a=forall b c.(Show b,Parse c)=StrItem String (a-b) (a-c-a)

class Structure a where
  strName::a-String
  strEmpty::a
  strItems::[StrItem a]

Now I would like to use it to create instances of Show and Parse (and 
perhaps
others (for input/output from various formats, ...)).

The approaches I have tried:

1)

instance Structure a = Show a where
  showsPrec _ w =
   showsStruct (strName w) (map showsPair strItems)
  where
   showsPair (StrItem fName fGet _)=(fName,shows $ fGet w)

This is nice, but it only works in ghc with allowed overlapping and 
undecidable
instances. It may not seem too important, when I use existential types 
anyway,
but existential types are supported by at least one more implementation 
(hugs)
and they seem to me to be a well defined extension that has good chances to
become part of standard Haskell later; handling of overlapping and 
undecidable
instances in ghc seems quite too much ad-hoc and experimental for me.

2)

newtype Str a=Str a
instance Structure a = Show (Str a) where
  showsPrec _ (Str w) =
   showsStruct (strName w) (map showsPair strItems)
  where
   showsPair (StrItem fName fGet _)=(fName,shows $ fGet w)

This seems to be a standard way how to do it. The problem is, that
I don't get Show instance for a, but for isomorphic type Str a; this is
a bit annoying when I want to use it; also I may no longer use deriving Show
on types containing such structure.

Is there some better way how to do this?

Zdenek Dvorak

_
Send and receive Hotmail on your mobile device: http://mobile.msn.com

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: Haskell digest, Vol 1 #656 - 3 msgs

2002-06-29 Thread Zdenek Dvorak

Hello.

Can I write dependencies like this:

  class C x y z | x - (y, z)
  class D x y z | (x, y) - z

in hugs? in ghc? The ghc doc refers to
Mark Jones: Type Classes with Functional Dependencies,
http://www.cse.ogi.edu/~mpj/pubs/fundeps.html
where this seems to be allowed (section 4, page 9)

Especially, I would need class D above.

class C can be rewritten to

class C x y z | x - y, x - z

concerning class D, I used (in GHC)

class D x y z | x y - z

and it seemed to do what I wanted. I guess

class C x y z | x - y z

would work too.

Zdenek Dvorak

_
MSN Photos is the easiest way to share and print your photos: 
http://photos.msn.com/support/worldwide.aspx

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Haskell puzzles!

2002-03-20 Thread Zdenek Dvorak

Hello.

- All the answers are at the end of this mail.

-
1) Are e1 and e2 equal?

  f (x:xs) y  = x
  g (x:xs)= \y - x
 
  e1 = seq (f []) 1
  e2 = seq (g []) 1

Should not these be

f (x:xs) y  = y
g (x:xs)= \y - y
?
Otherwise, both e1 and e2 are obviously undefined.

Zdenek Dvorak


_
Chat with friends online, try MSN Messenger: http://messenger.msn.com

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell