Re: [Haskell-cafe] Category theory monad <----> Haskell monad

2005-08-18 Thread Michael Vanier

The explanation given below might be a bit heavy for someone who didn't know 
much
about category theory.  For those individuals I'd recommend Phil Wadler's
papers:

http://homepages.inf.ed.ac.uk/wadler/topics/monads.html

I especially recommend "Monads for Functional Programming", "The Essence of
Functional Programming" and "Comprehending Monads".

Basically, though, the Haskell implementation _is_ the category theoretic
definition of monad, with bind/return used instead of (f)map/join/return as
described below.

Mike

> Date: Thu, 18 Aug 2005 20:39:37 -0400
> From: Cale Gibbard <[EMAIL PROTECTED]>
> Cc: haskell-cafe@haskell.org
> 
> On 14/08/05, Carl Marks <[EMAIL PROTECTED]> wrote:
> > Is there any text/article which makes precise/rigorous/explicit the 
> > connection
> > between the category theoretic definition of monad with the haskell
> > implementation?
> 
> Well, a monad over a category C is an endofunctor T on C, together
> with a pair of natural transformations eta: 1 -> T, and mu: T^2 -> T
> such that
> 1) mu . (mu . T) = mu . (T . mu)
> 2) mu . (T . eta) = mu . (eta . T) = id_C
> 
> In Haskell, a monad is an endofunctor on the category of all Haskell
> types and Haskell functions between them. Application of the
> endofunctor to an object is given by applying a type constructor (the
> one which is made an instance of the Monad class). Application of the
> endofunctor to a function is carried out by fmap or liftM. The natural
> transformation eta is called return, and mu is called join (found in
> the Monad library).
> 
> Haskell uses a somewhat different (but equivalent) basis for a monad,
> in that it is not map, return, and join which need defining to make a
> type an instance of the Monad class, but return and (>>=), called
> "bind" or "extend".
> 
> One can define bind in terms of fmap, and join as
> x >>= f = join (fmap f x)
> 
> and one can get back join and fmap from return and bind:
> join x = x >>= id
> fmap f x = x >>= (return . f)
> 
> hope this helps,
> - Cale
> ___
> 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] static typing and interactivity

2005-08-18 Thread Bernard Pope
On Thu, 2005-08-18 at 15:17 +0200, Ketil Malde wrote:
> Hi,
> 
> One slight annoyance using Haskell is the inability to load modules
> with type problems in the interactive environment (i.e. GHCi).  When I
> have a type error, it would be nice to have an interactive way to
> explore what the compiler thinks about the types involved -- as it is,
> I have to resort to adding type signatures more or less at random to
> narrow down the problem.
> 
> I'm not sure if it is technically feasible to (partially) load a
> module with definitions that fail type checking, but if it were, I
> thing it would make developing Haskell programs even nicer :-)

You might be interested in Chameleon:

   http://www.comp.nus.edu.sg/~sulzmann/chameleon/

especially the type debugger.

Bernie.

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


Re: [Haskell-cafe] Category theory monad <----> Haskell monad

2005-08-18 Thread Cale Gibbard
On 14/08/05, Carl Marks <[EMAIL PROTECTED]> wrote:
> Is there any text/article which makes precise/rigorous/explicit the connection
> between the category theoretic definition of monad with the haskell
> implementation?

Well, a monad over a category C is an endofunctor T on C, together
with a pair of natural transformations eta: 1 -> T, and mu: T^2 -> T
such that
1) mu . (mu . T) = mu . (T . mu)
2) mu . (T . eta) = mu . (eta . T) = id_C

In Haskell, a monad is an endofunctor on the category of all Haskell
types and Haskell functions between them. Application of the
endofunctor to an object is given by applying a type constructor (the
one which is made an instance of the Monad class). Application of the
endofunctor to a function is carried out by fmap or liftM. The natural
transformation eta is called return, and mu is called join (found in
the Monad library).

Haskell uses a somewhat different (but equivalent) basis for a monad,
in that it is not map, return, and join which need defining to make a
type an instance of the Monad class, but return and (>>=), called
"bind" or "extend".

One can define bind in terms of fmap, and join as
x >>= f = join (fmap f x)

and one can get back join and fmap from return and bind:
join x = x >>= id
fmap f x = x >>= (return . f)

hope this helps,
- Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Category theory monad <----> Haskell monad

2005-08-18 Thread Carl Marks
Is there any text/article which makes precise/rigorous/explicit the connection 
between the category theoretic definition of monad with the haskell 
implementation?





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


Re: [Haskell-cafe] Re: Oracle + Haskell advice?

2005-08-18 Thread Krasimir Angelov
2005/8/18, John Goerzen <[EMAIL PROTECTED]>:
> I would suspect that you could find Oracle drivers for either unixODBC,
> or some custom ODBC system that is nearly API-compatible.  Once you have
> that, you have HSQL.

I am planing to add support for Oracle in HSQL since now I am using it
at office, but I will do that when I have enough time to hack with it.
If there is any volunteer to do the job then I will be pretty happy to
incorporate its work.

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


[Haskell-cafe] Re: Oracle + Haskell advice?

2005-08-18 Thread John Goerzen
On 2005-08-18, Brian Strand <[EMAIL PROTECTED]> wrote:
> I'm thinking about (re)writing some perl code in Haskell (for performance and 
> correctness reasons).  Has anyone done much with Oracle and Haskell?  So far 

Not Oracle specifically, but other databases, both free and proprietary.

> Before I wade in too deep, I'm wondering if anyone has done much "business 
> app" programming with Haskell (where "business app" is rather fuzzily defined 
> as database access, web UIs, interfacing with various systems over ip, etc.). 
>   Does anyone have any advice?  eg "don't go there" or "works great!" or "try 
> OCaml" :) .

I'm doing a lot of it.  There's a good deal of web and database activity
going on here.  Haskell is also my language of choice for scripting
projects, especially data transfer (thanks in part to my FTP library in
MissingH )

I use HSQL for everything database-related.  HaskellDB did not work out
well.  It proved rather buggy, cumbersome, inflexible (it appeared to be
impossible to do a "SELECT" without "DISTINCT"), and poorly-scalable
(try having it scan a database with several thousand tables).

HSQL is more low-level, but I'm comfortable with that, having used
Perl's DBI and Python's DB-API before.

HSQL natively supports the common Free databases (MySQL, PostgreSQL,
SQLite, etc.)  We use PostgreSQL for everything that we can.  It's no
less speedy than MySQL when correctly tuned, and far more reliable.  It
also seems to be a heck of a lot easier to install and work with than
Oracle ;-)

One of our more important systems is in a Progress database.  They
provide their own ODBC system for Unix.  HSQL has an ODBC interface, and
it took only minor tweaking to port it from unixODBC to Progress's ODBC.
Configuration was trickier, but that was more because of poor docs from
Progress.  It is working highly reliably for us.

I would suspect that you could find Oracle drivers for either unixODBC,
or some custom ODBC system that is nearly API-compatible.  Once you have
that, you have HSQL.

You didn't mention what platform you're on, but if you're on Windows,
I'd imagine you'd have no problem making ODBC work.  Unix is slightly
more tricky, but again, I'd check out the unixODBC route.  It's included
in Debian by default, and I wouldn't be surprised if other OSs/distros
have it too.

-- John


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


Re: [Haskell-cafe] static typing and interactivity

2005-08-18 Thread Keean Schupke
I look at the source code and think about it... Generally I code in vi, 
then run ghci, or compile and run. I find from experience the type 
errors are normally easy to fix, you just look at the error, and study 
the structure of the function. If I still have problems I edit the code 
to return or output intermediate values. From years of doing this I can 
generally spot all my mistakes quickly... leaving only those situations 
where I don't fully understand the algorithm as requiring serious 
thought. Of course these are precisely those kind of problems for which 
a debugger is not much good either.


   Keean.




Jake Luck wrote:


One slight annoyance using Haskell is the inability to load modules
with type problems in the interactive environment (i.e. GHCi).  When I
have a type error, it would be nice to have an interactive way to
explore what the compiler thinks about the types involved -- as it is,
I have to resort to adding type signatures more or less at random to
narrow down the problem.

I'm not sure if it is technically feasible to (partially) load a
module with definitions that fail type checking, but if it were, I
thing it would make developing Haskell programs even nicer :-)



Along similiar lines, it would be quite nice if one can mark their 
haskell code(working or not) with "breakpoints" and drop the 
programmer into GHCi so they can poke around, especially inside a 
do-construct. e.g. something the evalutation engine can check during 
reduction maybe? I find myself writing a lot of testing frameworks, 
maybe this is a good thing!, when I program. How do most of the folks 
here debug their large code base?


jake
___
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] static typing and interactivity

2005-08-18 Thread Neil Mitchell
Hi Jake,

> program. How do most of the folks here debug their large code base?

You might have some success with Hat, http://www.haskell.org/hat/, for
debugging.

Unfortunately unless you are doing Monadic computations, breakpoints
don't really work as well as in strict imperative programs.

Thanks

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


Re: [Haskell-cafe] static typing and interactivity

2005-08-18 Thread Jake Luck

One slight annoyance using Haskell is the inability to load modules
with type problems in the interactive environment (i.e. GHCi).  When I
have a type error, it would be nice to have an interactive way to
explore what the compiler thinks about the types involved -- as it is,
I have to resort to adding type signatures more or less at random to
narrow down the problem.

I'm not sure if it is technically feasible to (partially) load a
module with definitions that fail type checking, but if it were, I
thing it would make developing Haskell programs even nicer :-)


Along similiar lines, it would be quite nice if one can mark their haskell 
code(working or not) with "breakpoints" and drop the programmer into GHCi 
so they can poke around, especially inside a do-construct. e.g. something 
the evalutation engine can check during reduction maybe? I find myself 
writing a lot of testing frameworks, maybe this is a good thing!, when I 
program. How do most of the folks here debug their large code base?


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


[Haskell-cafe] static typing and interactivity

2005-08-18 Thread Ketil Malde

Hi,

One slight annoyance using Haskell is the inability to load modules
with type problems in the interactive environment (i.e. GHCi).  When I
have a type error, it would be nice to have an interactive way to
explore what the compiler thinks about the types involved -- as it is,
I have to resort to adding type signatures more or less at random to
narrow down the problem.

I'm not sure if it is technically feasible to (partially) load a
module with definitions that fail type checking, but if it were, I
thing it would make developing Haskell programs even nicer :-)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] embedding prolog in haskell.

2005-08-18 Thread Keean Schupke

Christian Maeder wrote:


Keean Schupke wrote:
 


implementation of unify? For example can the algorithm be simplified
from my nieve attempt? Most importantly is it correct?
   



It will not be correct without occurs check. You may also get different
terms for the same variable in your substitution list.
 


Prolog does not use an occurs check... and this is embedding prolog.
However I accept this point, thats why there was the comment about
no occurs check in the code. I actually want to cope with recursive
definitions as Prolog does, so the solution to:

   X = f(X)

should be:

   f(f(f(f(...

which is an infinite recursion.


The simplest form of unification does not take a substitution as input
and uses functions to compose two substitutions and to apply a
substitution to a term.

 


  unify :: Subst -> (Term,Term) -> [Subst]
   


This signature came from the paper... The input subst is an accumulator
and it would normally be Id when calling - so there is effectively no input
substitution.



Do you ever get real lists? The result type "Maybe Subst" is more
appropriate.
 

No, I dont think the algorithm gives real lists, Maybe would be better, 
although I
think I will get it working before playing with changing the rest of the 
code.
Is it possible to ever have more than one meaningful answer from 
unification?


 


  unify' s [] [] = [s]
  unify' s (t0:ts) (u0:us) = case unify s (t0,u0) of
  s@(_:_) -> unify' (concat s) ts us
  _ -> []
   



input lists of different lengths should not cause a runtime error but
only a unification failure (indicated by "Nothing" or "[]" in your case.)

 


Aha, a genuine bug... thanks!


HTH Christian

Here's a part of my version:

unify' (t0:ts) (u0:us) = do
  s1 <- unify (t0,u0)
  s2 <- unify' (map (applySubst s1) ts)
   (map (applySubst s1) us)
  return (composeSubst s1 s2)
 


I am now using:
  
   unify' :: Subst -> [Term] -> [Term] -> [Subst]

   unify' s (t0:ts) (u0:us) = case unify s (t0,u0) of
   s@(_:_) -> unify' (concat s) ts us
   _ -> []   
   unify' s [] [] = [s]

   unify' _ _ _ = []



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


Re: [Haskell-cafe] embedding prolog in haskell.

2005-08-18 Thread Christian Maeder
Keean Schupke wrote:
> implementation of unify? For example can the algorithm be simplified
> from my nieve attempt? Most importantly is it correct?

It will not be correct without occurs check. You may also get different
terms for the same variable in your substitution list.

The simplest form of unification does not take a substitution as input
and uses functions to compose two substitutions and to apply a
substitution to a term.

>unify :: Subst -> (Term,Term) -> [Subst]

Do you ever get real lists? The result type "Maybe Subst" is more
appropriate.

>unify' s [] [] = [s]
>unify' s (t0:ts) (u0:us) = case unify s (t0,u0) of
>s@(_:_) -> unify' (concat s) ts us
>_ -> []

input lists of different lengths should not cause a runtime error but
only a unification failure (indicated by "Nothing" or "[]" in your case.)

HTH Christian

Here's a part of my version:

unify' (t0:ts) (u0:us) = do
   s1 <- unify (t0,u0)
   s2 <- unify' (map (applySubst s1) ts)
(map (applySubst s1) us)
   return (composeSubst s1 s2)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] embedding prolog in haskell.

2005-08-18 Thread Keean Schupke
Okay, I have found the missing definition (code was split by page 
break), and found the type error:


   type Subst = [(Var,Term)]

should be:

   type Subst = [(Vname,Term)]

And have written a simple implementation of unify from a description of 
the algorithm. I was wondering if anyone has any comments on my 
implementation of unify? For example can the algorithm be simplified 
from my nieve attempt? Most importantly is it correct?


   type Subst = [(Vname,Term)]
   data Term = Func Fname [Term] | Var Vname deriving (Eq,Show)
   type Fname = String
   data Vname = Name String | Auto Integer deriving (Eq,Show)

   unify :: Subst -> (Term,Term) -> [Subst]
   unify s (t,u) | t == u = [s]
   unify s (Var x,t) = [(x,t):s] -- no occurs check
   unify s (t,Var x) = [(x,t):s] -- no occurs check
   unify s (Func f ts,Func g us)
   | f == g = unify' s ts us
   | otherwise = []
  
   unify' :: Subst -> [Term] -> [Term] -> [Subst]

   unify' s [] [] = [s]
   unify' s (t0:ts) (u0:us) = case unify s (t0,u0) of
   s@(_:_) -> unify' (concat s) ts us
   _ -> []

Keean.

Keean Schupke wrote:

Does anyone know if the source code for the embedded prolog (by 
Silvija Seres & Michael Spivey) is available for download from 
anywhere? I have read the paper and found some of the types are wrong, 
some critical definitions are missing, and the definition of unify is 
missing.


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


RE: [Haskell-cafe] Oracle + Haskell advice?

2005-08-18 Thread Bayley, Alistair
> From: Brian Strand [mailto:[EMAIL PROTECTED] 
>
> I've gotten takusen 
> (http://cvs.sf.net/viewcvs.py/haskell-libs/libs/takusen/) 
> to compile and run on my Suse 9.3 x86-64 box against Oracle 
> 10.1.

Cool. I'm keen for feedback. I can also give general advice as far as
interfacing to Oracle is concerned.

To be fair, Takusen is usable, but far from feature-complete (no support for
BLOBs, CLOBs, invoking procedures). You might want to compare it to
HaskellDB over ODBC, if you can get HaskellDB running (I don't know how
usable ODBC-on-Unix is). HaskellDB is a higher-level approach to database
access, and might be better suited to "business apps".


> Before I wade in too deep, I'm wondering if anyone has done 
> much "business 
> app" programming with Haskell (where "business app" is rather 
> fuzzily defined 
> as database access, web UIs, interfacing with various systems 
> over ip, etc.). 

As for the other stuff, here are a few projects which might interest you. I
believe these represent the state-of-the-art in Haskell as far as this sort
of stuff is concerned:

  http://www.informatik.uni-freiburg.de/~thiemann/haskell/WASH/ : WASH, for
building browser-based apps
  http://www.haskell.org/haxr/ : HaXR, for XML-RPC (the "interfacing with
various systems over ip" requirement)
  http://www.repton-world.org.uk/mediawiki/index.php/HAIFA_Wiki : HAIFA.
Looks like it does SOAP. See also:
http://haskell.org/~shae/haifa_tmr.pdf

There are also a few XML libraries around; I can't comment on how well these
work.

It should be clear that there's not yet one clear bundle or approach that we
can point to and say "here, use this". Like, say, Ruby-on-rails, Zope,
Seaside, etc. Things are still a bit more DIY in Haskell land. I recommend
starting with WASH and adding what you need from there.

Alistair.

-
*
Confidentiality Note: The information contained in this   message, and any
attachments, may contain confidential   and/or privileged material. It is
intended solely for the   person(s) or entity to which it is addressed. Any
review,   retransmission, dissemination, or taking of any action in
reliance upon this information by persons or entities other   than the
intended recipient(s) is prohibited. If you received  this in error, please
contact the sender and delete the   material from any computer.
*

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