Re: [Haskell-cafe] Newbie "Instance Of Floating Int" Error

2006-04-27 Thread Jared Updike
It looks like somewhere else in your program (or a type signature
somewhere) is trying to force the result of sqrt to be an Int which
won't work since square roots are irrational (represented by the
computer as a Float or Double).

You might try (1) making sure the place where distBetween is used
isn't trying to use only Ints or Integers and (2) taking off explicit
type signatures and seeing if that works (the compiler can usually get
things working for you as long as you don't give it misinformation in
type signatures). Also, a more useful type of Point if you are taking
distances would be

type Point = (Float,Float)

instead (or you can leave that out because the function type for
distBetween will be inferred to be the "right thing", i.e.
(Float,Float) is already a valid type without needing to be named).

Hope that helps,
  Jared.
--
http://www.updike.org/~jared/
reverse ")-:"

On 4/27/06, Aditya Siram <[EMAIL PROTECTED]> wrote:
> Hi all,
> I just started working with Haskell and am having some difficulties with its
> type system.
> Here is function that is supposed to calculate the distance between two
> coordinates:
> distBetween (x1,y1) (x2,y2) = sqrt((x2-x1)^2  + (y2-y1)^2)
>
> I am trying to explictly give it a type signature. Here is what I have tried
> and the errors generated by Hugs:
>
> type Point = (Int,Int)
> distBetween :: Point -> Point -> Float
> >>ERROR - Type error in explicitly typed binding
> *** Term   : distBetween
> *** Type   : Point -> Point -> Int
> *** Does not match : Point -> Point -> Float
>
> distBetween :: Point -> Point -> Int
> >>Instance of Floating Int required for definition of distBetween
>
> Any help is appreciated...
> Deech
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Newbie "Instance Of Floating Int" Error

2006-04-27 Thread Cale Gibbard
One thing to try:
type Point = (Float, Float)

The problem is that x1, y1, x2, and y2 are Ints, and so (x2-x1)^2  +
(y2-y1)^2 is also an Int, but then you try to take the square root,
which is an operation only available on floating point values (more
specifically, types in the class Floating, which also includes things
like Complex Double).

Another option is to leave the Point type as-is, but do a conversion
just before applying the sqrt, say, by applying the fromIntegral
function, which serves to convert from types in the class Integral,
like Int and Integer to any numeric type you need.
distBetween (x1,y1) (x2,y2) = sqrt . fromIntegral $ (x2-x1)^2 + (y2-y1)^2

hope this helps,
 - Cale

On 27/04/06, Aditya Siram <[EMAIL PROTECTED]> wrote:
> Hi all,
> I just started working with Haskell and am having some difficulties with its
> type system.
> Here is function that is supposed to calculate the distance between two
> coordinates:
> distBetween (x1,y1) (x2,y2) = sqrt((x2-x1)^2  + (y2-y1)^2)
>
> I am trying to explictly give it a type signature. Here is what I have tried
> and the errors generated by Hugs:
>
> type Point = (Int,Int)
> distBetween :: Point -> Point -> Float
> >>ERROR - Type error in explicitly typed binding
> *** Term   : distBetween
> *** Type   : Point -> Point -> Int
> *** Does not match : Point -> Point -> Float
>
> distBetween :: Point -> Point -> Int
> >>Instance of Floating Int required for definition of distBetween
>
> Any help is appreciated...
> Deech
>
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Newbie "Instance Of Floating Int" Error

2006-04-27 Thread Aditya Siram

Hi all,
I just started working with Haskell and am having some difficulties with its 
type system.
Here is function that is supposed to calculate the distance between two 
coordinates:

distBetween (x1,y1) (x2,y2) = sqrt((x2-x1)^2  + (y2-y1)^2)

I am trying to explictly give it a type signature. Here is what I have tried 
and the errors generated by Hugs:


type Point = (Int,Int)
distBetween :: Point -> Point -> Float

ERROR - Type error in explicitly typed binding

*** Term   : distBetween
*** Type   : Point -> Point -> Int
*** Does not match : Point -> Point -> Float

distBetween :: Point -> Point -> Int

Instance of Floating Int required for definition of distBetween


Any help is appreciated...
Deech


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


[Haskell-cafe] short yet featureful grep

2006-04-27 Thread John Meacham
my favorite example is the featureful yet short grep, supporting quite a
few non-trivial options as well as a detailed '--help' message. :)

this is a great example for anyone that says strong typing clutters code
:) Haskell can be much more concise as well as safer than perl given the
right libraries.


main = do
(fs,(verb,c,e,o,q)) <- getOptions (
"v|verbose" ?? "set verbose mode"
"c" ?? "count occurances",
"e" ==> "." ?? "the pattern to match",
"o" ?? "show just the match rather than the line"'
"q" ?? "just tell whether it matches"
)
when verb $ putStrLn ("reading " ++ show fs)
ls <- fmap (lines . concat) $ mapM readFiles fs
when q $ if any (=~ e) ls then exit 0 else exit 1
when c $ print $ sum (map (fromEnum . (=~ e)) ls)
flip mapM ls $ \l -> case (l =~ e) of
Nothing -> return ()
Just xs -> putStrLn $ if o then xs else l


John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread John Meacham
I wrote an option parser that infers everything about the options from
the types of what you pull out of it so there is no need to specify
redundant information and you can write very concise code (especially when 
combined with
the overloaded regex module!)

like for instance

main = do
 (args,(verb,output_name)) <- getOptions ("v|verbose", "o")
 putStrLn $ if verb then "verbose mode" else "not verbose"
 case output_name of
Nothing -> putStrLn "no output"
Just fn -> putStrLn $ "output file is: " ++ fn

will just work, infering from the type that '-v' and '-verbose' are
simple flags, while '-o' takes a string argument.


you can even set help messages with the (??) operator

"o" ?? "output file name"

and default values with the (==>) operator.

"o" ==> "out.txt"

it can be gotten here:
http://repetae.net/john/recent/out/GetOptions.html
and help is at:
http://repetae.net/john/recent/src/hsdocs//GetOptions.html

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-27 Thread John Meacham
On Thu, Apr 27, 2006 at 09:53:35PM +0100, Brian Hulley wrote:
> At the moment, there is a strange unnatural discrepancy between the fixed 
> set of built-in privileged operations such as newUnique which are "allowed" 
> to make use of global state and user defined operations which have to rely 
> on a shaky hack in order to preserve natural abstraction barriers between 
> components such as a user-defined Unique, Atom, and anything involving 
> memoisation or device management etc.

In fact, you reminded me of the so obvious it is easy to forget example
of global state that every haskell programer uses since day one.

CAFs.
as in

fibs = 0 : 1 : zipWith (+) fibs (tail fibs)

fibs is mutable global state that is updated with its value when it is
evaluated.

not sure how I missed the obvious example.

John




-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] GetOpt

2006-04-27 Thread Brian Hulley

Brian Hulley wrote:

moduleOptions = ComposedOption "My module" [ModOption1, ModOption2]

moduleOptions = Option $ ComposedOption "My module" [ModOption1, ModOption2]


allOptions = ComposedOption "Name of program" [Module1.moduleOptions,


allOptions = Option $ ComposedOption "Name of program" 
[Module1.moduleOptions,


Thinking more about it, it would be better to change the type of 
ComposedOption to:


   data ComposedOption = ComposedOption [(String, Option)]

since an option by itself can't tell what it's name should be because any 
name specified might conflict with other option names, but the parent can 
assign different names safely.
Also, many different schemes for composing options could be devised, so that 
some subsets of options would be indexed by a number instead of a letter 
etc.


Regards, Brian.

PS: this is definitely a good case for the use of augmented IO since the 
fact that a particular module needs to store option state should be 
completely invisible to the rest of the program... 


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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Anton Kulchitsky

Hi Bulat,

thank you very much for such a detailed reply!


I just started to study Haskell and it is my almost first big experience
with functional languages (except Emacs Lisp and Python). I enjoyed all
small exercises and started a bigger business writing a general utility.



you are my ideal client because we both speak Russian (but not here :) )
  

Da! :) Spasibo.


and both interested in large "real-world" applications :)  download
the http://freearc.narod.ru/FreeArc-sources.tar.gz and enjoy - it's a
full of Russian comments and it's a real-world program that solves
many problems that you yet foresee :)

in particular, i also started with vision of my program (it's a
RAR-like archiver) as a sequence of transformations:

1) first, a command line translated into the program "job" - it's
actually business of GetOpt and not very differ from other language's
implementations

2) second, this job plus information about files on disk is translated
into the record of structure of archive being created

3) third, archive structure translated into the sequence of I/O
operations

but when i started to do the actual implementation, i realized that
such pure functional approach is nor appropriate and at the last end
i wrote the straight imperative program, just using the power of
Haskell language. moreover, in this process i added to the language
many imperative constructs that make imperative programming easier

  
I really trying to avoid imperative approach. I do have a terribly big 
experience in imperative programming (by the way, you might know one 
application that I made about 3 years ago. It is Uni-K Sensei for 
windows). Now, I am breaking my previous habits just to think wider and 
more effective.

However, I have a problem from the beginning. The utility get some file
and convert it to another format. It is a kind of small compiler. It 
also accepts many parameters and behaves depending on them. The problem
is how to do this neat! How should I write my program to accept and 
neatly work with options



you can see my solution in Cmdline module - it's one of largest module
in my program. i don't like the GetOpt interface (it returns a list of
options what is unusable for high-speed application) so i implemented
  
Well, I do not care too much about high-speed. My main goal is to write 
a prototype of the language that I am creating. It is a kind of 
Domain-Specific language. I decided to start from a simple thing. A 
converter of pgn files with chess notation to javascript to visualize 
it. Just to have some practice.

my own option-processing routines, it's just about 50 lines long
(great demonstration of Haskell power!). all processed options are
record in one large record that is passed around all the program. if
you get accustomed to global variables, it's using in Haskell is
possible but that is not the best way. you can also use implicit
parameters (at least in hugs and ghc), but this again makes data
dependencies somewhat non-understandable

  
Thank you very much. I will see this approach as well. I am still pretty 
concern of using records instead of lists.



btw, i suggest you to use WinHugs for debugging program and ghc for
final compilation. this makes faster development time together with
faster final executable. moreover, making your program compatible with
both environments is almost ensure that it will be compatible with
coming Haskell standard, Haskell-prime
  
Thanks again. I do not use Windows any more. I use Mac or different 
Unices. I do use ghc everywhere I work with Haskell. For debugging I use 
ghci. Well, and everything within GNU Emacs.



returning back to options parsing - there is an interesting
alternative to GetOpt (which is just mimics corresponding C module) -
it's a PescoCmd:

http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.tgz
http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.pdf
http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-man-2.0.pdf

  

Thanks! Very interesting


i also recommend you to read several other real-world Haskell program
where you can steal more code and ideas:

http://postmaster.cryp.to/postmaster-2005-02-14.tar.gz
ftp://ftp.cse.unsw.edu.au/pub/users/dons/yi/yi-0.1.0.tar.gz
darcs (darcs get --partial http://www.abridgegame.org/repos/darcs/)
happs (darcs get --partial http://happs.org/HAppS)
  

Darcs was a little too complicated for me. Thank you for other links.


and one more interesting source of real-world approach to Haskell
programming:

http://www.haskell.org/haskellwiki/Hitchhikers_Guide_to_the_Haskell


  
Thank you very much, Bulat. Now I see why people say that haskell-cafe 
is the best mail-list! :)


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


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-27 Thread Brian Hulley

John Meacham wrote:

On Thu, Apr 27, 2006 at 11:09:58AM +0100, Adrian Hey wrote:

What really frustrates me about all this is that AFAIK there are no
significant technical or theoretical reasons why we can't get
this safety (without resort to the unsafePerformIO hack). The
only serious obstacle seems political, with this very strange but
apparently widespread dogma about so called "global variables"
being inherently evil, regardless of the circumstances or purpose
for which they are used.


indeed. perhaps we just need to come up with a more functional name
than 'global variables'. like 'universal monad' or 'world
transformer', maybe 'augmented IO'. :)


I like "augmented IO", because this makes it clear that there is absolutely 
no difference between the existing IO monad which keeps track of global 
RealWorld state, and an augmented IO monad which keeps track of RealWorld + 
state of IORefs needed internally by different components of a software 
system.


At the moment, there is a strange unnatural discrepancy between the fixed 
set of built-in privileged operations such as newUnique which are "allowed" 
to make use of global state and user defined operations which have to rely 
on a shaky hack in order to preserve natural abstraction barriers between 
components such as a user-defined Unique, Atom, and anything involving 
memoisation or device management etc.


Regards, Brian. 


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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Anton Kulchitsky



I find this approach very convenient, but I push it a bit further. Some
time ago I wrote a small article about this:

http://www.haskell.org/pipermail/haskell/2004-January/013412.html

I was not the first one to use the approach but I felt that it should be
made more popular. Perhaps I should make a wiki page from it, but I seem
to never do such things and can't promise to do it this time :-/

  

Thank you so much!!! That is great!

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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Einar Karttunen
On 27.04 12:32, Mirko Rahn wrote:
> So it would be much better to define the options in the library and to 
> provide this definitions to the user program somehow. I tought about 
> this topic several times and came up with a solution that works for me 
> but is far from being perfect. It uses existentials and a main 
> disadvantage is the need of explicit traversing. Moreover some new 
> boilerplate code is necessary.

HAppS has a typeclass for this kind of thing also:

http://test.happs.org/auto/apidoc/HAppS-Util-StdMain-Config.html
http://test.happs.org/HAppS/src/HAppS/Util/StdMain/Config.hs

and for an example instance see:

http://test.happs.org/HAppS/src/HAppS/Protocols/SimpleHTTP.hs

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


Re: Re[2]: [Haskell-cafe] GetOpt

2006-04-27 Thread Brian Hulley

Bulat Ziganshin wrote:

Hello Tomasz,
[snip]
ultimately, the main problem of all options-parsing stuff i ever seen,
is requirement to repeat option definition many times. if i have, say,
40 options, then i need to maintain 3 to 5 program fragments that deal
with each option. something like this:

data Options = Options { r :: Bool,
x :: Int

  }

options = { "r", "description"
   
 }

main = do list <- getOpts options cmdline
 let options = Options { r = findBoolOption list "r",
 x = findIntOption list "x",
 
   }



If it is not necessary to specify a specific command letter for each option, 
then perhaps options could be composed by something like (following code 
untested):


class OptionClass a where
 setOption :: a -> String -> IO ()
 getOptionDescription :: a -> String -> String

data Option = forall a. OptionClass a => Option a
instance OptionClass Option where
 setOption (Option a) = setOption a
 getOptionDescription (Option a ) opt = getOptionDescription a opt

data ComposedOption = ComposedOption _ [Option]
instance OptionClass ComposedOption where
 setOption (ComposedOption _ os) (c:cs) = setOption (os !! (fromEnum 
c - fromEnum 'a')) cs

 getOptionDescription (ComposedOption description os) (c:cs)=
 description ++ "." ++ getOptionDescription (os !! 
(fromEnum x - fromEnum 'a')) cs


Then each element in a module that needs an option makes its own instance of 
the existential eg


data ModOption1 = ModOption1
data ModOption2 = ModOption2

instance OptionClass ModOption1 where
setOption ModOption1 s = case s of
  [] -> do -- set default 
value
  s -> do -- parse s and 
set accordingly


getOptionDescription ModOption1 optvalue =
   -- description of this option, possibly clarified to the 
specific example of optvalue
   -- "would read from the file 'foo.txt'" if optvalue == " 
foo.txt"


moduleOptions = ComposedOption "My module" [ModOption1, ModOption2]

Then in main, do:

allOptions = ComposedOption "Name of program" [Module1.moduleOptions, 
Module2.moduleOptions, ...]


A disadvantage would be that the options would involve multiple letters in 
general eg -b -aba etc when there is a lot of nesting, but an advantage 
is that it allows libraries requiring options and code using such libraries 
to be written in a modular way.


Best regards, Brian. 


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


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-27 Thread John Meacham
On Thu, Apr 27, 2006 at 11:09:58AM +0100, Adrian Hey wrote:
> What really frustrates me about all this is that AFAIK there are no
> significant technical or theoretical reasons why we can't get
> this safety (without resort to the unsafePerformIO hack). The
> only serious obstacle seems political, with this very strange but
> apparently widespread dogma about so called "global variables"
> being inherently evil, regardless of the circumstances or purpose
> for which they are used.

indeed. perhaps we just need to come up with a more functional name than
'global variables'. like 'universal monad' or 'world transformer', maybe
'augmented IO'. :) 

I am tired of having to apologize for using them, they really are the
right solution to a number of practical problems when writing real-world
code. Every haskell programer depends on them whethre they know it or
not, they are just abstracted away in libraries, but the bottom line is
that someone needs to be able to write those libraries.

my ForeignData proposal (on the wiki) fills a hole in the haskell FFI
that can somewhat mitigate the problem, but only for Storable strict
values.

I have thought a safe 'StorableRef' would be a useful data type, that
uses peeks and pokes internally for very fast mutable state, but
provides a safe interface.


There is also the 'dependingOn' primitive which is in jhc and I think
will be in ghc (?) that lets you do global variables without having to
turn off cse.

dependingOn :: a -> b -> a
dependingOn = ...

where it has the same meaning as const, but introduces an artificial
dependence of its return value on its second argument. so you can do

data Var1 = Var1

{-# NOINLINE myVar #-}
myVar :: IORef Int
myVar = unsafePerformIO $ newIORef (0 `dependingOn` Var1)

and now myVar cannot be cse'd with anything else because Var1 will not
match anything of another type.

still not ideal though.

(I have been finding all sorts of uses for 'dependingOn' when it comes
to various tasks)

> >Let me just add one thing.  Sometimes you hear the argument
> >"I need a global IORef here because it's to track the use of my
> >single screen" (or keyboard, or elevator, or some some
> >other gizmo in th real world).

heh. the canonical strawman tactic. :)

> 
> No, this is not the justification for the creation of top level TWI's.
> This is the justification for not requiring that the API that mutates
> a particular top level TWI state takes that state as an explicit
> argument. There's no point if there is (and can be) only one of them.
> This is why you don't have to pass an OS state handle to every IO
> function that interacts with "the" OS (note singular).

it is not just about convinience, for instance my 'Atom' module in jhc
and ginsu depends on the fact you cannot pass in different states for
correctness. its API is purly funcitonal, but it needs to use global
state internally. Haskell has great tools for abstraction, global state
would be another one. What it boils down to is that it helps you write
more correct code in certain cases and there is no reasonable
work-around.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] GetOpt

2006-04-27 Thread Bulat Ziganshin
Hello Tomasz,

Thursday, April 27, 2006, 4:45:45 PM, you wrote:

> On Thu, Apr 27, 2006 at 03:10:32PM +0400, Bulat Ziganshin wrote:
>> i don't like the GetOpt interface (it returns a list of options what
>> is unusable for high-speed application)

> This got me interested. I assume that you measured performace and it
> wasn't fast enough.

no, i abandoned this without testing :)

you misunderstood me, though - i mean speed of using this list. if
some internal function need option "foo", it should scan the entire
list to find it's value. so i (like you, i think) save the result of
option parsing in the structure. and because i anyway need the way to
extract options from list and store them into structure - i
implemented my own set of functions to recognize options too.

ultimately, the main problem of all options-parsing stuff i ever seen,
is requirement to repeat option definition many times. if i have, say,
40 options, then i need to maintain 3 to 5 program fragments that deal
with each option. something like this:

data Options = Options { r :: Bool,
 x :: Int
 
   }

options = { "r", "description"

  }

main = do list <- getOpts options cmdline
  let options = Options { r = findBoolOption list "r",
  x = findIntOption list "x",
  
}

each change in options list mean that i should find all these places
and correct them. PescoCmd may be does something against this problem,
i don't remember why i was pleased by this library

as far as i see, solving of this problem is impossible in Haskell
itself, we need some form of preprocessing, probably with TH. this
should allow us to write something like this:

$(optionProcessor [("r", "description", `Bool, .)
  ,("x", .
  ...
  ]
)

what will generate all the stuff above

as i already said, you can find module Cmdline in my program, that
is not ultimate solution, but at least it somewhat simplified my work
  

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


RE: [Haskell-cafe] database access recommendation

2006-04-27 Thread Brock Peabody
> From: Duncan Coutts [mailto:[EMAIL PROTECTED]

> It's that too! And SQLite and you can write other backends
> independently.

Sounds cool!

Unfortunately I'm having problems installing it but I think it's
probably something simple this time.  I can configure, build, and
install hdbc.  When I try to build hdbc-postgresql it fails because it
can't include libpq-fe.h or pg_config.h, both of which are present in
/usr/local/include.

I noticed when I ran configure that it mentioned the absence of haddock,
happy, and alex, so I am installing them just in case that had anything
to do with it.

Thanks,
Brock

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


RE: [Haskell-cafe] database access recommendation

2006-04-27 Thread Duncan Coutts
On Thu, 2006-04-27 at 11:50 -0500, Brock Peabody wrote:
> > From: Duncan Coutts [mailto:[EMAIL PROTECTED]
> 
> > There is also HDBC which is nearing a 1.0 release and in my experience
> > is easier to install. (I package both HSQL & HDBC for Gentoo)
> 
> Thanks, I'll check that out.  For some reason I saw HDBC and just
> assumed it was an interface for ODBC.

It's that too! And SQLite and you can write other backends
independently.

Duncan

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


RE: [Haskell-cafe] database access recommendation

2006-04-27 Thread Brock Peabody
> From: Duncan Coutts [mailto:[EMAIL PROTECTED]

> There is also HDBC which is nearing a 1.0 release and in my experience
> is easier to install. (I package both HSQL & HDBC for Gentoo)

Thanks, I'll check that out.  For some reason I saw HDBC and just
assumed it was an interface for ODBC.

Brock


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


Re: [Haskell-cafe] database access recommendation

2006-04-27 Thread Duncan Coutts
On Thu, 2006-04-27 at 10:45 -0500, Brock Peabody wrote:
> I'm teaching myself Haskell, and was wondering if anyone could recommend
> a library for accessing databases, PostgreSQL in particular.
> 
> I looked at http://www.haskell.org/haskellwiki/Libraries_and_tools, and
> HSQL looked promising, but I can't get it to install on Windows or
> FreeBSD, with Hugs or GHC.  According to the FreeBSD ports system, it is
> marked as broken.

There is also HDBC which is nearing a 1.0 release and in my experience
is easier to install. (I package both HSQL & HDBC for Gentoo)

http://quux.org/devel/hdbc/

In particular you'll want:
http://quux.org/devel/hdbc/hdbc_0.99.2.tar.gz

and the PostgreSQL backend:
http://quux.org/devel/hdbc/hdbc-postgresql_0.99.2.1.tar.gz

API docs:
http://darcs.complete.org/hdbc/doc/Database-HDBC.html


Duncan

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


Re: [Haskell-cafe] database access recommendation

2006-04-27 Thread Neil Mitchell
Hi

> It fails with Hugs on both platforms on the "runhugs Setup.lhs
> configure" step in the base HSQL library with:
>
> Windows:
>
> ERROR "C:\Program
> Files\WinHugs\libraries\Text\ParserCombinators\ReadP.hs":156 -
>  Syntax error in type expression (unexpected `.')

That looks like it requires haskell extensions (forall in particular),
and Hugs is running without them. Try adding the -98 option to Hugs.
The other option is to start WinHugs, click on Options, and under
Haskell Extensions change it to Hugs/GHC extensions.

Thanks

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


[Haskell-cafe] database access recommendation

2006-04-27 Thread Brock Peabody
I'm teaching myself Haskell, and was wondering if anyone could recommend
a library for accessing databases, PostgreSQL in particular.

I looked at http://www.haskell.org/haskellwiki/Libraries_and_tools, and
HSQL looked promising, but I can't get it to install on Windows or
FreeBSD, with Hugs or GHC.  According to the FreeBSD ports system, it is
marked as broken.

It fails with Hugs on both platforms on the "runhugs Setup.lhs
configure" step in the base HSQL library with:

FreeBSD:

ERROR
"/usr/local/lib/hugs/libraries/Text/ParserCombinators/ReadP.hs":133 -
Syntax error in type expression (unexpected `.')

Windows:

ERROR "C:\Program
Files\WinHugs\libraries\Text\ParserCombinators\ReadP.hs":156 -
 Syntax error in type expression (unexpected `.')

GHC crashes with no error on the "runghc Setup.lhs build" step in the
base HSQL library in Windows.  In FreeBSD I can completely build and
install the base library, but in any of the database specific
directories, "runghc Setup.lhs configure" yields:

"Setup.lhs:17:71:
Couldn't match `PackageDescription' against `LocalBuildInfo'
  Expected type: Args -> ConfigFlags -> LocalBuildInfo -> IO
ExitCode
  Inferred type: [String]
 -> ConfigFlags
 -> PackageDescription
 -> LocalBuildInfo
 -> IO ExitCode
In the `postConf' field of a record
In the record update: defaultUserHooks {preConf = preConf, postConf
= postConf}

:1:87:
Failed to load interface for `Main':
Bad interface file: Setup.hi
Setup.hi: openBinaryFile: does not exist (No such file or
directory)"

Thanks,
Brock

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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Tomasz Zielonka
On Thu, Apr 27, 2006 at 03:10:32PM +0400, Bulat Ziganshin wrote:
> i don't like the GetOpt interface (it returns a list of options what
> is unusable for high-speed application)

This got me interested. I assume that you measured performace and it
wasn't fast enough.

How many command line args you had to handle? How many options? I don't
know how well System.GetOpt works with many possible options. It doesn't
seem to use any sophisticated algorithm for searching options, so the
cost of getOpt can be proportional to N*M, where N = numer of option
descriptions, M = number of program args.

If this was improved, it might become usable for you.

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


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-27 Thread Lennart Augustsson

Not to fuel the flame war, I will limit myself to two comments.

Adrian Hey wrote:

Or put another way, would it be possible to implement the socket
API, exactly as it currently is, entirely in Haskell, starting with
nothing but hardware? I don't believe it is possible, but perhaps
somebody can show me I'm wrong.

If I get to implement the IO monad, sure. :)



IME, the approach you take to these kinds of problems can vary
depending what you know or don't know for certain about the
system your working with. But you always end up using top level
mutable state somewhere along the way. I can only assume folk who
insist it's unnecessary (or worse) have never actually tried
implementing an IO sub-system from the ground up, starting with
nothing but bare hardware.

I've written about 5 lines of USB devices drivers for *BSD (in C).
They work from the bare metal and up.  They contain no global
mutable state (except for variables that define debugging levels,
because you need to access these from the in-kernel debugger).

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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Bulat Ziganshin
Hello Anton,

Wednesday, April 26, 2006, 11:29:16 PM, you wrote:

> I just started to study Haskell and it is my almost first big experience
> with functional languages (except Emacs Lisp and Python). I enjoyed all
> small exercises and started a bigger business writing a general utility.

you are my ideal client because we both speak Russian (but not here :) )
and both interested in large "real-world" applications :)  download
the http://freearc.narod.ru/FreeArc-sources.tar.gz and enjoy - it's a
full of Russian comments and it's a real-world program that solves
many problems that you yet foresee :)

in particular, i also started with vision of my program (it's a
RAR-like archiver) as a sequence of transformations:

1) first, a command line translated into the program "job" - it's
actually business of GetOpt and not very differ from other language's
implementations

2) second, this job plus information about files on disk is translated
into the record of structure of archive being created

3) third, archive structure translated into the sequence of I/O
operations

but when i started to do the actual implementation, i realized that
such pure functional approach is nor appropriate and at the last end
i wrote the straight imperative program, just using the power of
Haskell language. moreover, in this process i added to the language
many imperative constructs that make imperative programming easier

> However, I have a problem from the beginning. The utility get some file
> and convert it to another format. It is a kind of small compiler. It 
> also accepts many parameters and behaves depending on them. The problem
> is how to do this neat! How should I write my program to accept and 
> neatly work with options

you can see my solution in Cmdline module - it's one of largest module
in my program. i don't like the GetOpt interface (it returns a list of
options what is unusable for high-speed application) so i implemented
my own option-processing routines, it's just about 50 lines long
(great demonstration of Haskell power!). all processed options are
record in one large record that is passed around all the program. if
you get accustomed to global variables, it's using in Haskell is
possible but that is not the best way. you can also use implicit
parameters (at least in hugs and ghc), but this again makes data
dependencies somewhat non-understandable

btw, i suggest you to use WinHugs for debugging program and ghc for
final compilation. this makes faster development time together with
faster final executable. moreover, making your program compatible with
both environments is almost ensure that it will be compatible with
coming Haskell standard, Haskell-prime

returning back to options parsing - there is an interesting
alternative to GetOpt (which is just mimics corresponding C module) -
it's a PescoCmd:

http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.tgz
http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-2.0.pdf
http://scannedinavian.org/~pesco/distfiles/pesco-cmdline-man-2.0.pdf

i also recommend you to read several other real-world Haskell program
where you can steal more code and ideas:

http://postmaster.cryp.to/postmaster-2005-02-14.tar.gz
ftp://ftp.cse.unsw.edu.au/pub/users/dons/yi/yi-0.1.0.tar.gz
darcs (darcs get --partial http://www.abridgegame.org/repos/darcs/)
happs (darcs get --partial http://happs.org/HAppS)

and one more interesting source of real-world approach to Haskell
programming:

http://www.haskell.org/haskellwiki/Hitchhikers_Guide_to_the_Haskell


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Mirko Rahn

Tomasz Zielonka wrote:

On Thu, Apr 27, 2006 at 02:26:22AM +0300, Einar Karttunen wrote:



and handle options as functions from Config to Config:


Option ['i']   ["input"]   (ReqArg (\x c -> c { infile = Just x }) "file") "input 
file name"



I find this approach very convenient, but I push it a bit further. Some
time ago I wrote a small article about this:

http://www.haskell.org/pipermail/haskell/2004-January/013412.html

I was not the first one to use the approach but I felt that it should be
made more popular. Perhaps I should make a wiki page from it, but I seem
to never do such things and can't promise to do it this time :-/


You are dealing with more convenient option handling, validating and 
defaulting on top of Sven Pannes famous GetOpt module. Nice stuff but 
there is another important point: Your approach still needs a central 
definition of an option list (or record) in the main (user) program. But 
suppose you write some libraries that are used by a couple of user 
programs. It becomes tedious and error prone to define the same lists of 
options with descriptions and validating functions in all user programs 
just to give it to the library. Moreover the user program in general 
even don't know about the right validating function or option description.


So it would be much better to define the options in the library and to 
provide this definitions to the user program somehow. I tought about 
this topic several times and came up with a solution that works for me 
but is far from being perfect. It uses existentials and a main 
disadvantage is the need of explicit traversing. Moreover some new 
boilerplate code is necessary.


You can find the interface in

http://liinwww.ira.uka.de/~rahn/src/Util/Option.hs

Sample library definitions of options are in

http://liinwww.ira.uka.de/~rahn/src/PCP/Fast/Env.hs
http://liinwww.ira.uka.de/~rahn/src/PCP/Fast/Description.hs

These definitions are combined in

http://liinwww.ira.uka.de/~rahn/src/PCP/Fast/Auto.hs

and finally used for example in the user programs

http://liinwww.ira.uka.de/~rahn/src/Prog/Eval.hs
http://liinwww.ira.uka.de/~rahn/src/Prog/Interesting.hs

Note, that the user programs just define options that are specific for 
the program, e.g. both programs have options to define some search 
bounds without definition.


As stated: Far from being perfect. Looking forward to get some new ideas!

Best regards, Mirko Rahn

--
-- Mirko Rahn -- Tel +49-721 608 7504 --
--- http://liinwww.ira.uka.de/~rahn/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-27 Thread Adrian Hey

Lennart Augustsson wrote:

I was going to respond, but Cale very eloquently said most
of what I was thinking.


I don't think eloquent is the word I would use, but I'm certainly
glad you didn't feel the need to repeat all that. It'd be really nice
if just for once the "global mutable state is evil" folk could give
unsafePerformIO hack users the benefit of the doubt, not start
out from the presumption that we are a bunch of lazy incompetent
retards who are badly in need of education in the rudiments of
the IO monad and (allegedly) good programming practice in general.

These arguments about the language needing to protect users from
doing dangerous things (specifically creating top level mutable
state) are quite wrong headed. Concurrency can be dangerous too,
so should we lose it? Top level mutable state can be a way of
*gaining safety*, not losing it.

What really frustrates me about all this is that AFAIK there are no
significant technical or theoretical reasons why we can't get
this safety (without resort to the unsafePerformIO hack). The
only serious obstacle seems political, with this very strange but
apparently widespread dogma about so called "global variables"
being inherently evil, regardless of the circumstances or purpose
for which they are used.

With regard to Roberts post, I don't want too say much other than
Robert is the first person to provide an answer to my question.
I hope I'm not mis-representing his views, but I believe Robert
objects to the existence of IO libraries that could not be implemented
in Haskell (in principle). I.E. those that implicitly reference top
level mutable state. I might be missing something, but AFAICS just
about all the current IO libraries fall into this category.

To take a specific example, look at the socket API. None of the
functions there take any kind of OS or network sub-system state handle
as an explicit argument. So it seems to me that either the
implementation is entirely stateless, all the way down to peeking and
poking the registers of Ethernet MACs, DMA controllers and wotnot
(unlikely), or it's sneakily accessing top level mutable state in some
extremely devious and non-transparent manner (heaven forbid).

Or put another way, would it be possible to implement the socket
API, exactly as it currently is, entirely in Haskell, starting with
nothing but hardware? I don't believe it is possible, but perhaps
somebody can show me I'm wrong.


Let me just add one thing.  Sometimes you hear the argument
"I need a global IORef here because it's to track the use of my
single screen" (or keyboard, or elevator, or some some
other gizmo in th real world).


No, this is not the justification for the creation of top level TWI's.
This is the justification for not requiring that the API that mutates
a particular top level TWI state takes that state as an explicit
argument. There's no point if there is (and can be) only one of them.
This is why you don't have to pass an OS state handle to every IO
function that interacts with "the" OS (note singular).

But even if there are two or more, you still need some mechanism
to ensure that you have precisely 1:1 correspondance between
physical devices and device state TWI's and/or device driver
threads. This more or less prevents a robust API allowing unconstrained
creation of new device state TWI's. It's far safer and simpler
to provide top level TWIs (state handles) as *abstract data types*
(not IORefs!). This is no different from (or less safe than) having
stdout appear at the top level.

Even if there is an unknown (at compile time) number of such
devices and instead they are discovered somehow at boot time,
you still need to maintain a some kind of finite pool of these
device states, which is itself necessarily a unique TWI.

IME, the approach you take to these kinds of problems can vary
depending what you know or don't know for certain about the
system your working with. But you always end up using top level
mutable state somewhere along the way. I can only assume folk who
insist it's unnecessary (or worse) have never actually tried
implementing an IO sub-system from the ground up, starting with
nothing but bare hardware.


I think such decisions are just generally poor design, and
it should not be done in any language.  The number of physical
resources that a program can control should never be assumed
to be one; things change.


So is it reasonable to assume that there is only one OS?

Perhaps it would be best to let individual Haskell users decide
for themselves what assumptions are or are not reasonable in the
context of their work.

Regards
--
Adrian Hey






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


Re: [Haskell-cafe] GetOpt

2006-04-27 Thread Tomasz Zielonka
On Thu, Apr 27, 2006 at 02:26:22AM +0300, Einar Karttunen wrote:
> On 26.04 11:29, Anton Kulchitsky wrote:
> > I just started to study Haskell and it is my almost first big experience 
> > with functional languages (except Emacs Lisp and Python). I enjoyed all 
> > small exercises and started a bigger business writing a general utility. 
> > However, I have a problem from the beginning. The utility get some file 
> > and convert it to another format. It is a kind of small compiler. It 
> > also accepts many parameters and behaves depending on them. The problem 
> > is how to do this neat! How should I write my program to accept and 
> > neatly work with options
> 
> One solution is to have a datatype for configuration:
> 
> > data Config = Config { mode:: Mode,
> >infile  :: Maybe FilePath,
> >outfile :: Maybe FilePath
> >  }
> > nullConfig = Config Normal "-" "-"
> > data Mode   = Normal | Version | Help
> 
> and handle options as functions from Config to Config:
> 
> > Option ['i']   ["input"]   (ReqArg (\x c -> c { infile = Just x }) "file") 
> > "input file name"

I find this approach very convenient, but I push it a bit further. Some
time ago I wrote a small article about this:

http://www.haskell.org/pipermail/haskell/2004-January/013412.html

I was not the first one to use the approach but I felt that it should be
made more popular. Perhaps I should make a wiki page from it, but I seem
to never do such things and can't promise to do it this time :-/

> and then handle the parsed options like:
> 
> > case conf of
> >   Config Normal (Just i) (Just o) -> ...
> >   Config Normal __-> both input and output must be specified
> >   Config Help   __-> help message

You can eliminate this pattern matching by using functions and
IO-actions as fields of Config, for example:

> data Config = Config { input   :: IO String, -- or (Handle -> IO a) -> IO a
>output  :: String -> IO ()
>  }

This way it is easy to read from stdin and write to stdout by default.

We eliminate Version and Help modes by using IO functions as option
handlers, which enables us to finish the execution in the middle of
option processing.

> Option ['h'] ["help"]   (NoArg (\_ -> printHelp >> exitWith ExitSuccess)) 
> "show help"

Your main function could look like this:

> main = do
> args <- getArgs
> let (optsActions, rest, errors) = getOpt RequireOrder options args
> mapM_ (hPutStrLn stderr) errors
> config <- foldl (>>=) (return initialConfig) optsActions
> cs <- input config
> ...
> output config result

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