Re: int to float problem

2003-03-03 Thread Ketil Z. Malde
"Mike T. Machenry" <[EMAIL PROTECTED]> writes:

>   I am having a problem. I recently desided I wanted a bunch function to return
> float instead of Int. I changed their type and wrote a new function that
> returned a float. I figured it'd be okay if all the others still returned
> Int since it's trivial to convert Int to Float.

Perhaps the other functions could be written with a more general type?
(E.g. :: Num a => ... -> a)

Try to remove the type declaration, and see what Hugs or GHCi :t has
to say about it!

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: fundeps for extended Monad definition

2003-03-03 Thread Simon Peyton-Jones

| > The reason, which is thoroughly explained in Simon Peyton-Jones'
| > message, is that the given type signature is wrong: it should read
| > f1 :: (exists b. (C Int b) => Int -> b)
| 
| Right.  Simon pointed out that this is a pretty useless function, but
not
| entirely so, since the result of it is not of type 'forall b. b', but
| rather of 'forall b. C Int b => b'.  Thus, if the C class has a
function
| which takes a 'b' as an argument, then this value does have use.

I disagree.   Can you give an example of its use?   

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


Re: How to force UNIX text files as output instead of DOS text files??

2003-03-03 Thread Alexandre Weffort Thenorio
Thanks a lot m8 but ghc says it can't the module IOExts when I try to
compile, any suggestion??? Do I just use normal writeFile method to create
the text file then??

Best Regards

Alex

- Original Message -
From: "Glynn Clements" <[EMAIL PROTECTED]>
To: "Alexandre Weffort Thenorio" <[EMAIL PROTECTED]>
Cc: <[EMAIL PROTECTED]>
Sent: Monday, March 03, 2003 2:02 AM
Subject: Re: How to force UNIX text files as output instead of DOS text
files??


>
> Alexandre Weffort Thenorio wrote:
>
> > I am working on a small program which writes a text file but I need this
> > file to be in UNIX format and as it is a Windows program I am compiling
> > it, the output file tends to be in DSO format. Is there anyway that I
> > can force it to create the file in UNIX format???
>
> Use openFileEx, e.g.:
>
> import IOExts
> ...
> handle <- openFileEx filename (BinaryMode WriteMode)
>
> --
> Glynn Clements <[EMAIL PROTECTED]>
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
>

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


Re: How to make Parser explicitly "fail"?

2003-03-03 Thread Leonid Bouriakovsky
If you are using the ParseLib from the Hugs distribution,
the function you are looking for is mzero:

C:\Hugs98\lib\hugs\ParseLib.hs:

instance MonadPlus Parser where
   -- mzero:: Parser a
   mzero= P (\inp -> [])

   -- mplus:: Parser a -> Parser a -> Parser a
   (P p) `mplus` (P q)  = P (\inp -> (p inp ++ q inp))

For the explanations on how this function works and
why it has such a name you can take a look at the
following paper:

Monadic parser combinators
Graham Hutton and Erik Meijer. Technical Report NOTTCS-TR-96-4,
Department of Computer Science, University of Nottingham, 1996.

http://www.cs.nott.ac.uk/Department/Staff/gmh/bib.html#monparsing

Regards,

Leonid Bouriakovsky


> Hi, there. I am glad to join Haskell community. :)
> 
> Here I have a question about Parser: how to make a
> parser explicitly "fail"?
> 
> My question arises from the syntax below:
> 
> ::=
> ::="define"
> ::=':'
> ::=identifier other than 
> ::=()+
> ::=a..z|A..Z
> 
> Now I am thinking of writing a Parser for variable. My
> thought is:
> 
> variable::Parser String
> variable = do s<-identifier
>   if not (s=="define") then return s else
> --let parser fail
> 
> I will be very happy if there is some mechanism to
> implement the "else" branch, for I have thought of it
> for long. :)
> 
> __
> Do you Yahoo!?
> Yahoo! Tax Center - forms, calculators, tips, more
> http://taxes.yahoo.com/
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell


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


Re: How to make Parser explicitly "fail"?

2003-03-03 Thread Daan Leijen

Now I am thinking of writing a Parser for variable. My
thought is:
variable::Parser String
variable = do s<-identifier
if not (s=="define") then return s else
--let parser fail
You forgot to tell which parser library you use. If you
use ParseLib (or Parsec) you can use the monadic zero
function "mzero".
Now, if you are using Parsec, you can also use
"fail :: String -> Parser a" to add some error message.
variable = do s<-identifier
when (s=="define") (fail "define is a keyword")
return s
Or better:

variable = do s<-identifier when (s=="define") (unexpected "keyword")
return s
 "variable"
Or even better, use the standard "identifier" parser from the "ParsecToken" module 
to handle this for you automatically. The
user guide describes this in detail: http://www.cs.uu.nl/~daan/parsec.html
All the best,
Daan.




I will be very happy if there is some mechanism to
implement the "else" branch, for I have thought of it
for long. :)
__
Do you Yahoo!?
Yahoo! Tax Center - forms, calculators, tips, more
http://taxes.yahoo.com/
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell





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


Re: How to force UNIX text files as output instead of DOS text files??

2003-03-03 Thread Alexandre Weffort Thenorio
OK I fixed the IOExts not found problem (-package lang) but my problem now
is that I never worked with handles. How can I write the string to the file
and so on?? Where can I find more info on handle data types??

Best Regards

NooK

- Original Message -
From: "Glynn Clements" <[EMAIL PROTECTED]>
To: "Alexandre Weffort Thenorio" <[EMAIL PROTECTED]>
Cc: <[EMAIL PROTECTED]>
Sent: Monday, March 03, 2003 2:02 AM
Subject: Re: How to force UNIX text files as output instead of DOS text
files??


>
> Alexandre Weffort Thenorio wrote:
>
> > I am working on a small program which writes a text file but I need this
> > file to be in UNIX format and as it is a Windows program I am compiling
> > it, the output file tends to be in DSO format. Is there anyway that I
> > can force it to create the file in UNIX format???
>
> Use openFileEx, e.g.:
>
> import IOExts
> ...
> handle <- openFileEx filename (BinaryMode WriteMode)
>
> --
> Glynn Clements <[EMAIL PROTECTED]>
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
>

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


How to force UNIX text files as output instead of DOS text files??

2003-03-03 Thread Alexandre Weffort Thenorio



I am working on a small program which writes a text 
file but I need this file to be in UNIX format and as it is a Windows program I 
am compiling it, the output file tends to be in DSO format. Is there anyway that 
I can force it to create the file in UNIX format???
 
Best Regards
 
NooK


Re: How to force UNIX text files as output instead of DOS text files??

2003-03-03 Thread Nick Name
On Mon, 3 Mar 2003 11:03:48 +0100
"Alexandre Weffort Thenorio" <[EMAIL PROTECTED]> wrote:

> 
>  OK I fixed the IOExts not found problem (-package lang) but my
>  problem now is that I never worked with handles. How can I write the
>  string to the file and so on?? Where can I find more info on handle
>  data types??

In the "IO" section of the prelude,

http://www.zvon.org/other/haskell/Outputio/index.html

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


looking for Database Interface in Haskell

2003-03-03 Thread Johannes Waldmann
Dear all, we want to access a (MySQL) data base,
running on a linux server, from a Haskell program.
We planned to use http://www.volker-wysk.de/mysql-hs/ 
but it depends on earlier versions of hdirect (0.17?) and ghc(-4?).
I built hdirect-0.19 (?) (from the ghc CVS) but the Foreign interfaces
seem to have changed a bit since mysql-hs-0.10.1 was written.
Any hints on what direction to take? Thanks,
-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/207 --

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


The Revised Haskell 98 Report

2003-03-03 Thread Simon Peyton-Jones
Folks

I am holding in my hands the first copy of the Haskell 98 Report to roll off the 
presses at Cambridge University Press.  It looks great.   And it has a copyright 
notice that says "It is intended that this Report belong to the entire Haskell 
community...", just as the online version does.

It's in CUP's catalogue here:
http://titles.cambridge.org/catalogue.asp?isbn=0521826144

Order your copy now (£35)!   Not only is a physical copy useful, but CUP's agreement 
to the rather unique copyright terms deserves our support.

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


Re: looking for Database Interface in Haskell

2003-03-03 Thread Steffen Mazanek
Have a look here:
http://haskell.cs.yale.edu/haskellDB/

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


Re: looking for Database Interface in Haskell

2003-03-03 Thread Shae Matijs Erisson
Johannes Waldmann <[EMAIL PROTECTED]> writes:

> Dear all, we want to access a (MySQL) data base,
> running on a linux server, from a Haskell program.
> We planned to use http://www.volker-wysk.de/mysql-hs/ 
> but it depends on earlier versions of hdirect (0.17?) and ghc(-4?).
> I built hdirect-0.19 (?) (from the ghc CVS) but the Foreign interfaces
> seem to have changed a bit since mysql-hs-0.10.1 was written.
> Any hints on what direction to take? Thanks,

Also, HToolkit has working but not yet stable support for both postgresql and
mysql. I haven't tried the mysql interface myself, but I have tried the
postgresql code. It works, but it does explode if you do something unexpected.
http://sourceforge.net/projects/htoolkit/
-- 
Shae Matijs Erisson - 2 days older than RFC0226
#haskell on irc.freenode.net - We Put the Funk in Funktion

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


Re: looking for Database Interface in Haskell

2003-03-03 Thread Daan Leijen
On 03 Mar 2003 13:57:06 +, Steffen Mazanek <[EMAIL PROTECTED]> wrote:

Dear all, we want to access a (MySQL) data base,
running on a linux server, from a Haskell program.

Have a look here:
http://haskell.cs.yale.edu/haskellDB/
A word of warning though from the author :-),
HaskellDB is somewhat outdated at the moment and only works with
TREX supported systems on windows ODBC databases. It is not so hard
to give it a different backend (ie. mySQL) but it is harder to
give it a non-TREX type system -- I have ideas about that though
and I am planning an update after my thesis is finished, but untill that moment, I 
don't think it would fit your particular target very well.
All the best,
 Daan.


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


GUI for Windows

2003-03-03 Thread Markus . Schnell
What User Interface Library would you recommend for use under Windows?
I tried FranTk but it crashes as soon as I run the display function (under
hugs)
and with ghc it won't even compile (I already tinkered with the makefiles,
so
finally I could make the package, but then the demos won't compile).

Any ideas, suggestions?

Markus


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


Re: GUI for Windows

2003-03-03 Thread Daan Leijen
On Mon, 3 Mar 2003 16:21:22 +0100, <[EMAIL PROTECTED]> wrote:

What User Interface Library would you recommend for use under Windows?
Unfortunately, there is no official GUI library for Haskell yet (but many
people are working toward this goal at the haskell gui mailing list).
At the moment, the best solution on windows (in my opionion) is to use the ObjectIO 
library that ships with GHC 5.04.2. You need to look at some examples to get started 
but it is pretty stable and useable. Unfortunately, it seems though that no one 
actively maintains it...
Another solution could be the HTk library but I have no experience with it.
Fortunately though, people are working on a good portable GUI solution for Haskell so I expect that over a few months the situation will be better.

All the best,
Daan.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: GUI for Windows

2003-03-03 Thread Axel Simon
On Mon, Mar 03, 2003 at 04:21:22PM +0100, [EMAIL PROTECTED] wrote:
> What User Interface Library would you recommend for use under Windows?
> I tried FranTk but it crashes as soon as I run the display function (under
> hugs)
> and with ghc it won't even compile (I already tinkered with the makefiles,
> so
> finally I could make the package, but then the demos won't compile).
> 
> Any ideas, suggestions?
 There has been a lot of discussions about defining a common API for GUIs,
you get an impression when you read the archives for [EMAIL PROTECTED]  
HToolkit+Ports+GIO tries to provide functionality that works with Gtk and
Win32 as backend. In contrast, there is the more complete gtk2hs binding
which uses Gtk 2.0 on Unix, Windows and Mac (more info from me).  There is
Object I/O wich is specific to Windows and comes with GHC. There are more
options like HGL which is more for graphics AFAIK and higher-level
approaches like Fudgets (not for Windows). There is no best way right now
so it would be wrong to give a definite answer here.

Hope this helps,
Axel.

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


Re: int to float problem

2003-03-03 Thread Mike T. Machenry
Thank does sound like a pain, but it's better than putting fromIntegral
all over my code. Why can't Haskell unify a an expected float with an
infered int? It seems that this would make life alot easier.

-mike

On Sun, Mar 02, 2003 at 11:28:00AM +, Jorge Adriano wrote:
> 
> > "Mike T. Machenry" <[EMAIL PROTECTED]> writes:
> > > I recently desided I wanted a bunch function to return
> > > float instead of Int. [...] I found fromInteger but it
> > > didn't seem to work on the return value of the cardinality
> > > function for instance.
> >
> > Try fromIntegral, which works for Int and Integer, too.
> 
> 
> Casting an Integral value to a Fractional value to perform arithmetic 
> operations, is a very common need and I don't like adding fromIntegral 
> everywhere, so ended up writing a (very simple) module with generalized 
> arithmetic operators (see attachment). The » next to the operations indicate 
> a cast from an Integral to a Fractional value. 
> 
> J.A.
> 
> 

> module CrossTypeOps where
> 
> 
> -- Addition
> (+«) :: (Fractional a, Integral b)=> a -> b -> a
> (+«) x n = x+fromIntegral n
> 
> (»+) :: (Integral a, Fractional b)=> a -> b -> b
> (»+) n x = fromIntegral n + x
> 
> (»+«) :: (Integral a, Fractional b)=> a -> a -> b
> (»+«) m n = fromIntegral m+fromIntegral n
> 
> 
> -- Difference
> (-«) :: (Fractional a, Integral b)=> a -> b -> a
> (-«) x n = x-fromIntegral n
> 
> (»-) :: (Integral a, Fractional b)=> a -> b -> b
> (»-) n x = fromIntegral n - x
> 
> (»-«) :: (Integral a, Fractional b)=> a -> a -> b
> (»-«) m n = fromIntegral m-fromIntegral n
> 
> 
> -- Multiplication
> (*«) :: (Fractional a, Integral b)=> a -> b -> a
> (*«) x n = x*fromIntegral n
> 
> (»*) :: (Integral a, Fractional b)=> a -> b -> b
> (»*) n x = fromIntegral n * x
> 
> (»*«) :: (Integral a, Fractional b)=> a -> a -> b
> (»*«) m n = fromIntegral m*fromIntegral n
> 
> 
> -- Division 
> (/«) :: (Fractional a, Integral b)=> a -> b -> a
> (/«) x n = x / fromIntegral n
> 
> (»/) :: (Integral a, Fractional b)=> a -> b -> b
> (»/) n x = fromIntegral n / x
> 
> (»/«) :: (Integral a, Fractional b)=> a -> a -> b
> (»/«) m n = fromIntegral m / fromIntegral n
> 
> 
> -- Priorities
> infixl 6  +«, »+, »+«, -«, »-, »-«
> infixl 7  *«, »*, »*«, /«, »/, »/«
> 
> 
> 

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


Tutorial for literate Haskell

2003-03-03 Thread Daniel Luna
I am planning to write a small project in Haskell and stumbled upon some
text that mentioned literate Haskell. Is there any good tutorial on how to
write literate Haskell?

I know that I could take any tutorial on latex and use that, but that's
not what I am after. What I want is more like a base document with header
and footer done, and perhaps a couple of example files. With that as a
base I could get a hint on what the correct idioms for literate Haskell
are.

If there is no such tutorial a few hints on how other persons write would
be very welcome. (with that I mean: how to comment (what info is
relevant), how much/little one should describe a function/module, and such
stuff)

#Luna
-- 
Daniel Luna   | Top reasons that I have a beard:
[EMAIL PROTECTED] |  a) Laziness.
http://www.update.uu.se/~luna/|  b) I can.
Don't look at my homepage (it stinks).|  c) I can get away with it.

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


Re: Tutorial for literate Haskell

2003-03-03 Thread Steffen Mazanek
Hello.

I do Literate Programming this way:
At first I define a Latex environment "code" as "verbatim"
e.g. so: \newenvironment{code}{\footnotesize\verbatim}{\endverbatim\normalsize}
This environment is understood by the Haskell compilers.
All my modules are own documents concluded in the main tex-file with
\input{...}.
Alternatively I sometimes use lambdaTeX which typesets the code
really nice (problem: latex2html doesn't understand it).

Hope that will help.
Ciao,
Steffen
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


AW: GUI for Windows

2003-03-03 Thread Markus . Schnell
Thanks, Axel, Daan,

I will have a try with ObjectIO. (At least the examples
work ;-))

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


Re: int to float problem

2003-03-03 Thread Matthew Donadio
>Thank does sound like a pain, but it's better than putting fromIntegral
>all over my code. Why can't Haskell unify a an expected float with an
>infered int? It seems that this would make life alot easier.

This is my biggest gripe with Haskell, at least for what I do.  The numeric class 
system is good, but it assumes that the sub-classes are distict, where in fact 
integers are a proper subset of reals, which are a proper subset of complex numbers.

Personally, I would like to see module level explicit coersion, similar to the way the 
default numeric type is handled.  Something like:

> module Blah where

> coerce Int to Double
> in mean with fromInt

> mean :: [Double] -> Double
> mean x = sum x / length x

So, if the typesystem infers a Double, but finds an Int, the function would be 
rewritten as if it had been specified as

> mean x = sum x / (fromInt.length) x

If you want a global declaration then you could specify

> coerce Int to Double
> with fromInt

--Matthew Donadio ([EMAIL PROTECTED])

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


Re: How to force UNIX text files as output instead of DOS text files??

2003-03-03 Thread Alexandre Weffort Thenorio
Hi Great I got it working. Thanks a lot guys. My only problem now is when
compiling. I am getting:

hextodat.0(.text+0x34):fake: undefined reference to '_stginit_IOExts'

Anybody can tell me what could be wrong?? I can run --make but when trying
to compile with -o flag I get this error.

Best Regards

Alex

- Original Message -
From: "Nick Name" <[EMAIL PROTECTED]>
To: <[EMAIL PROTECTED]>
Sent: Monday, March 03, 2003 1:34 PM
Subject: Re: How to force UNIX text files as output instead of DOS text
files??


> On Mon, 3 Mar 2003 11:03:48 +0100
> "Alexandre Weffort Thenorio" <[EMAIL PROTECTED]> wrote:
>
> >
> >  OK I fixed the IOExts not found problem (-package lang) but my
> >  problem now is that I never worked with handles. How can I write the
> >  string to the file and so on?? Where can I find more info on handle
> >  data types??
>
> In the "IO" section of the prelude,
>
> http://www.zvon.org/other/haskell/Outputio/index.html
>
> Vincenzo
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell
>

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


RE: fundeps for extended Monad definition

2003-03-03 Thread Hal Daume III
> | entirely so, since the result of it is not of type 'forall b. b', but
> | rather of 'forall b. C Int b => b'.  Thus, if the C class has a
> function
> | which takes a 'b' as an argument, then this value does have use.
> 
> I disagree.   Can you give an example of its use?   

I believe something along the lines of the following would work:

> class C a b | a -> b where { foo :: b -> String }
> instance C Int Int   where { foo x = show (x+1) }
> x :: forall b. C Int b => b
> x = 5

(Supposing that the above definition were valid; i.e., we didn't get the
type signature error, this reads that x has type "b" for all types
"b" such that C Int b -- the fact that there is only one such type (due to
the fun dep) is for us to know.)

Then, we should be able to say:

> foo x

and get "6".

>From a "translation to untyped core" perpective (*grin*), we essentially
replace class constraints with dictionaries.  The definition of C
introduces a dictionary like the following (I'm not 100% familiar with
MPTC dictionaries, but I assume they're just like normal dictionaries):

> data CDict a b = CDict (b -> String)

Then the instance will give us:

> cIntIntDict :: CDict Int Int
> cIntIntDict = CDict (\x -> show (x+1))

foo will become:

> foo (CDict foo_f) x = foo_f x

and if we apply this properly, we get:

|  foo cIntIntDict x
| ==>  (\ (CDict foo_f) x -> foo_f x) cIntIntDict x
| ==>  (\ (CDict foo_f) -> foo_f x) cIntIntDict
| ==>  (\x -> show (x+1)) x
| ==>  show (5+1)
| ==>  "6"

or something like that?

In fact, except for the type definition on x, this is actually a valid
translation into typed core, I believe.  The weird type on x is the only
stumbling block, afaics.

...it is well known that I could be wrong though...

 - Hal

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


RE: fundeps for extended Monad definition

2003-03-03 Thread oleg

| > The reason, which is thoroughly explained in Simon Peyton-Jones'
| > message, is that the given type signature is wrong: it should read
| > f1 :: (exists b. (C Int b) => Int -> b)

> Can you give an example of its use?

Yes, I can.

> class (Show a, Show b) => C a b | a -> b where
> doit:: a -> b -> String
   
> instance C Int Int where
>doit a b = (show a)

> instance C Bool Bool where
>doit a b = if a then "everything" else "nothing"

> newtype M a = M (forall b.(C a b) => b)
> f :: Int -> M Int
> f x = M undefined

> g :: Bool -> M Bool
> g x = M undefined

> test1 a = case (f a) of
> M b -> doit a b

> test2 a = case (g a) of
> M b -> doit a b

I wonder if the Obfuscated Haskell contest has an entry for the most
useless type (with no uses). However, if a type can be used for the
contest, it is no longer the most useless. This makes one wonder if
the rules of the contest implicitly contain the Russel paradox.


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


Re: How to force UNIX text files as output instead of DOS text files??

2003-03-03 Thread Alexandre Weffort Thenorio
Thanks a lot m8. I got it. I was supplying it with --make but not with -o.
Thanks again. I guess everything is fine now thanks to you guys.I wanna
learn more about catching errors but that comes later when I finish this
program.

Best Regards

Alex

- Original Message -
From: "Nils Decker" <[EMAIL PROTECTED]>
To: "Alexandre Weffort Thenorio" <[EMAIL PROTECTED]>
Sent: Monday, March 03, 2003 7:19 PM
Subject: Re: How to force UNIX text files as output instead of DOS text
files??


> "Alexandre Weffort Thenorio" <[EMAIL PROTECTED]> wrote:
> > Hi Great I got it working. Thanks a lot guys. My only problem now is
> > when compiling. I am getting:
> >
> > hextodat.0(.text+0x34):fake: undefined reference to '_stginit_IOExts'
> >
> > Anybody can tell me what could be wrong?? I can run --make but when
> > trying to compile with -o flag I get this error.
>
> AFAIK, you have to supply -package lang to the linker too when using
seperate
> compilation.
>
>
> e.g:
> ghc -package lang -o foo.o foo.hs
> ghc -package lang -o foo foo.o ...
>
> Regards
>   Nils
>
> --
> Unix is user friendly - it's just picky about it's friends.
>
> Nils Decker <[EMAIL PROTECTED]>
>

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


Re: Tutorial for literate Haskell

2003-03-03 Thread b . i . mills
Yo,

Steffen Mazanek wrote:

> I do Literate Programming this way:
> At first I define a Latex environment "code" as "verbatim"
> e.g. so: \newenvironment{code}{\footnotesize\verbatim}{\endverbatim\normalsize}

When I ran into the same question some time ago I tried that,
but found that the \verbatim was interpreted to0 literally, so
that the \end{code} does not terminate it. Could you give a 
complete short example that works for you?

My own solution was to copy the definition of verbatim from the 
base files, and define code the same way in a separate style file.

Regards,

Bruce.


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


Re: looking for Database Interface in Haskell

2003-03-03 Thread Krasimir Angelov
   Hi, Shae

> Also, HToolkit has working but not yet stable
> support for both postgresql and
> mysql. I haven't tried the mysql interface myself,
> but I have tried the
> postgresql code. It works, but it does explode if
> you do something unexpected.
> http://sourceforge.net/projects/htoolkit/

Can you send me examples where the MySQL binding
explode? I am interested of improving of the library.

Best wishes,
Krasimir

__
Do you Yahoo!?
Yahoo! Tax Center - forms, calculators, tips, more
http://taxes.yahoo.com/
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


First-class types

2003-03-03 Thread oleg

The following is a more flexible alternative to overloading. We
essentially define a function on types and invoke it, seemingly at run
time. No Dynamics or unsafe computations are employed. We only need
existential types, multi-parameter classes and functional
dependencies. The code also shows how to manipulate values which
cannot be manipulated.

As an example, we define a _function_ (not a method!) 'add' such that:

Main> add True False 
1
Main> add () (5::Int)
5
Main> add () (5::Float)
5.0
Main> add (4::Int) True
5
Main> add (10::Int) (5::Float)
15.0

The example works both in GHC and Hugs. The signature of add is quite
revealing:
forall b a2 a1.
(Num b, Coerce a2 b, Coerce a1 b, D a1 a2 b) =>
a1 -> a2 -> b

That is, 'add' is capable of adding any two _things_, provided they both can
be "generalized" and "coerced" into a number. The "type function" D
computes the generalization of two types -- in a manner we specify.

The function add is actually quite simple:

> add x y = let general_type = typeof x y
>   x' = coerce x general_type
>   y' = coerce y general_type
> in x' + y'

The function 'typeof' is also interesting. It has a type
forall b a2 a1. (D a1 a2 b) => a1 -> a2 -> b
Note that it returns 'b' forall b! In a sense, the function performs a
type computation at run time.

The code follows. We should note that we could have achieved the same
effect by defining an appropriate class with the method 'add'. In our
solution however, the acts of generalizing, coercion, and addition are
all separated. If we later decide to subtract things rather than add
them, we do not need to alter the class and all the instances. We
merely need to introduce the subtraction function. This makes the
maintenance of the code easier.

The distinct characteristic of the following code is an indirect
manipulation of an untouchable, existential value. We were able to
force a value to be of a specific type without any means of accessing
the value directly.

> class Type a where
> name :: a -> String

> instance Type Bool where
> name a = "Bool"

> instance Type Int where
> name a = "Int"

> --instance Type Char where
> --name a = "Char"

> instance Type () where
> name a = "()"

> instance Type Float where
> name a = "Float"

> -- Type generalization function: type -> type -> type
> class (Type b) => D a1 a2 b | a1 a2-> b
   
> instance D Bool Bool Int
> instance D Int Bool Int
> instance D Bool Int Int
> instance D Int Int Int
> instance D () Int Int
> instance D Int () Int
> instance D () () Int
> instance D Int Float Float
> instance D () Float Float
> instance D Float Int Float
> instance D Float Float Float

> -- The coercion function

> class Coerce a b where
> coerce :: a -> b -> b

> instance Coerce () Int where
> coerce _ _ = 0

> instance Coerce () Float where
> coerce _ _ = 0

> instance Coerce Int Int where
> coerce = const

> instance Coerce Float Float where
> coerce = const

> instance Coerce Int Float where
> coerce x _ = fromInteger $ toInteger x
   
> instance Coerce Bool Int where
> coerce True _ = 1
> coerce False _ = 0

> newtype M a1 a2 = M (forall b.(D a1 a2 b) => b)
> data M1 a1 a2 = M1 a1 a2 (M a1 a2)
> typeof v1 v2 = case (M1 v1 v2 (M undefined)) of M1 _ _ (M y) -> y
> typeof1 v1 v2 = case (M1 v1 v2 (M undefined)) of M1 _ _ y -> y

> add x y = let general_type = typeof x y
>   x' = coerce x general_type
>   y' = coerce y general_type
> in x' + y'
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: Tutorial for literate Haskell

2003-03-03 Thread b . i . mills
Hi,

Since I sent this to the haskell list in the first place,
I'd better let everyone know that it all worked out.

> Hmm, there were no problems in simply doing so.

Ok, I've cut your example down a bit (just from a
minimalist tendency). The complete modified code is ...

   \documentclass{report}
   \usepackage{verbatim}% vital
   \begin{document}
   \newenvironment{code}{\footnotesize\verbatim}{\endverbatim\normalsize}
   
   HaskellModule.lhs:
   
   Maybe some text...
   We call our module Foo, 
   because this name is very meaningful.
   
   \begin{code}
   module Foo where
   \end{code}
   
   \end{document}

Works just fine and seems robust.

My original problem ... an over-developed tendency to go it alone?
I was not using package verbatim, which does help, doesn't it.

> I hope this will help.

Yup, thanks.

Bruce.

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


Persistent data

2003-03-03 Thread Sengan . Baring-Gould
Is there some way to reduce the cost of garbage collection over large persistent
datastructures without resorting to escaping to C to malloc memory outside the
heap?

The program I'm working is part database, which cannot discard information.
The net result is that I see figures like 82.9% of the time taken by garbage
collection. The heap profile looks like a charging capacitor: a linear increase
(as expected) which is slowly dilated as time increases by the garbage collector
thrashing memory.

When I worked on the LOLITA natural language processor we solved the problem
by moving a lot of the data out to C++, so that the heap only contains things
soon to be freed. I know generational garbage collection is supposed to help,
but it doesn't seem to. Is there a pure Haskell solution to this problem?

Sengan

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


Re: int to float problem

2003-03-03 Thread Ketil Z. Malde
"Matthew Donadio" <[EMAIL PROTECTED]> writes:

>> Thank does sound like a pain, but it's better than putting fromIntegral
>> all over my code. Why can't Haskell unify a an expected float with an
>> infered int? It seems that this would make life alot easier.

Personally, I think that one of the things that made my life easier
with Haskell compared to C++, is the lack of implicit type
cast/conversions/coercions.   Now, obviously C++ does this in a quite
byzantine way, it's possible that a simpler and better system exists. 

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell