[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
On Tue, 22 Mar 2005 [EMAIL PROTECTED] wrote:

> On Tue, Mar 22, 2005 at 09:52:04AM -0700, Kevin Atkinson wrote:
> > I must admit that I am baffled by what this is doing.  But I don't think
> > it has the semantics I want.  When I try substituting your
> > code in I get "Exception: <>".
>
> I could have made it a bit simpler:
>
> instance ArrowLoop FG' where
> loop (FG' f) = FG' $ \ c x -> do
> (c', ~(x', _)) <- mfix $ \ ~(_, ~(_, y)) -> f c (x, y)
> return (c', x')
>
> This executes f once only, with y bound to the third component of the
> output of f.  This isn't available until f finishes, so any attempt
> to examine it while f is running will lead to <>, but f can pass
> it around, and store it in data structures; it can even create cyclic
> structures.  (Under the hood, the IO instance of mfix starts with y bound
> to an exception, and updates it when f finishes, a bit like what you're
> trying to do with IORef's, except that existing references to y then
> point at the updated thing.)  Your definition runs f once with undefined
> as the last argument to get a value for y to supply to a second run.
> Presumably the things you're doing with Control need to change too,
> and I don't understand all that, but I expect that the mfix version
> could be made to work, and would do less work.

I think I understand it more, but I am not sure it will do what I want.
For one thing f still needs to know when it can examine its input thus,
still needing an initializing pass.

Please have a look at the new code.  I have reworked how loops are handled
and no longer use Control.  Also the state variable is now needed in
separate functions.  Thus I am not sure I can use the mfix trick to hide
the state.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread ross
On Tue, Mar 22, 2005 at 09:52:04AM -0700, Kevin Atkinson wrote:
> I must admit that I am baffled by what this is doing.  But I don't think 
> it has the semantics I want.  When I try substituting your 
> code in I get "Exception: <>".

I could have made it a bit simpler:

instance ArrowLoop FG' where
loop (FG' f) = FG' $ \ c x -> do
(c', ~(x', _)) <- mfix $ \ ~(_, ~(_, y)) -> f c (x, y)
return (c', x')

This executes f once only, with y bound to the third component of the
output of f.  This isn't available until f finishes, so any attempt 
to examine it while f is running will lead to <>, but f can pass
it around, and store it in data structures; it can even create cyclic
structures.  (Under the hood, the IO instance of mfix starts with y bound
to an exception, and updates it when f finishes, a bit like what you're
trying to do with IORef's, except that existing references to y then
point at the updated thing.)  Your definition runs f once with undefined
as the last argument to get a value for y to supply to a second run.
Presumably the things you're doing with Control need to change too,
and I don't understand all that, but I expect that the mfix version
could be made to work, and would do less work.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread S. Alexander Jacobson
Would it be harder/easier better/worse to use Linux device drivers 
from hOp/House as opposed to writing new disk I/O stuff in Haskell?

-Alex-
__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
On Tue, 22 Mar 2005, Keean Schupke wrote:
I don't think I said anything controversial. I guess I was just 
over-simplifying things by only considering PC IDE hardware - but then again 
that must get you running on 90% of the systems people are likely to have 
lying around to play with a developmental OS on.

On the other hand the average network driver seems to be about 2,000 lines of 
code, whereas if you add all the parts of the generic ide driver together you 
get about 20,000 lines of code. I guess that answers my question - storage is 
an order of magnitude harder than networking, even before including SCSI.

  Regards,
  Keean.

Simon Marlow wrote:
Keean, you should be aware that Lennart is something of a device driver
guru.  He knows what he's talking about :-)  Go grep for Augustsson in
the NetBSD kernel sometime.
Cheers,
Simon
___
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] Linux device drivers

2005-03-22 Thread Keean Schupke
I don't think I said anything controversial. I guess I was just 
over-simplifying things by only considering PC IDE hardware - but then 
again that must get you running on 90% of the systems people are likely 
to have lying around to play with a developmental OS on.

On the other hand the average network driver seems to be about 2,000 
lines of code, whereas if you add all the parts of the generic ide 
driver together you get about 20,000 lines of code. I guess that answers 
my question - storage is an order of magnitude harder than networking, 
even before including SCSI.

   Regards,
   Keean.

Simon Marlow wrote:
Keean, you should be aware that Lennart is something of a device driver
guru.  He knows what he's talking about :-)  Go grep for Augustsson in
the NetBSD kernel sometime.
Cheers,
	Simon
 

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


[Haskell-cafe] Re: Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
[From haskell@ to [EMAIL PROTECTED]

On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:

> Some more minor suggestions:
> - I'd suggest making Container a newtype, so it could have an Arrow
>   instance (it would be a reader arrow).  Then hbox and vbox could be
>   used as arrow operators/combinators.

What will that give me?  Could you give me an example of how I would use 
it in such a manner?

-- 
http://kevin.atkinson.dhs.org

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


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
On Tue, 22 Mar 2005, Kevin Atkinson wrote:

> On Sun, 20 Mar 2005 [EMAIL PROTECTED] wrote:
> 
> > On Sat, Mar 19, 2005 at 12:17:46PM -0700, Kevin Atkinson wrote:
> > > On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:
> > > > I would also have expected loopFG to have been defined using fixIO.
> > > 
> > > Could you be more specific.  Ie How?
> > 
> > For the type definitions
> > 
> > newtype FG' a b = FG' (Control -> a -> IO (Control, b))
> > newtype FG a b = FG (FGState -> IO (FG' a b, FGState))
> > newtype Container a b = Container (FG ([WidgetP], a) b)
> > 
> > the usual instances would be (give or take a ~):
> > 
> > instance ArrowLoop FG' where
> > loop (FG' f) = FG' $ \ c x -> do
> > (c', x', _) <- mfix $ \ ~(_, _, y) -> do
> > ~(c', ~(x', y')) <- f c (x, y)
> > return (c', x', y')
> > return (c', x')
> 
> I must admit that I am baffled by what this is doing.  But I don't think 
> it has the semantics I want.  When I try substituting your 
> code in I get "Exception: <>".  I have reworked the way loops are 
> handled.  Please have a look at the new code at 
> http://www.haskell.org/arrows/.

Make that http://kevin.atkinson.dhs.org/fg/.  Sorry need to pay attention 
when I paste URL's :(

-- 
http://kevin.atkinson.dhs.org

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


[Haskell-cafe] Re: [Haskell] Arrows GUI Library Based on GTK+

2005-03-22 Thread Kevin Atkinson
On Sun, 20 Mar 2005 [EMAIL PROTECTED] wrote:

> On Sat, Mar 19, 2005 at 12:17:46PM -0700, Kevin Atkinson wrote:
> > On Sat, 19 Mar 2005 [EMAIL PROTECTED] wrote:
> > > I would also have expected loopFG to have been defined using fixIO.
> > 
> > Could you be more specific.  Ie How?
> 
> For the type definitions
> 
>   newtype FG' a b = FG' (Control -> a -> IO (Control, b))
>   newtype FG a b = FG (FGState -> IO (FG' a b, FGState))
>   newtype Container a b = Container (FG ([WidgetP], a) b)
> 
> the usual instances would be (give or take a ~):
> 
>   instance ArrowLoop FG' where
>   loop (FG' f) = FG' $ \ c x -> do
>   (c', x', _) <- mfix $ \ ~(_, _, y) -> do
>   ~(c', ~(x', y')) <- f c (x, y)
>   return (c', x', y')
>   return (c', x')

I must admit that I am baffled by what this is doing.  But I don't think 
it has the semantics I want.  When I try substituting your 
code in I get "Exception: <>".  I have reworked the way loops are 
handled.  Please have a look at the new code at 
http://www.haskell.org/arrows/.

-- 
http://kevin.atkinson.dhs.org

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


RE: [Haskell-cafe] Symbolic differentation using GHC's simplificationrules

2005-03-22 Thread Jacques Carette
> I tried to implement symbolic differentation using GHC's simplification 
> rules. I assume that someone has already thought about this, right? 

You are trying to do 'intensional programming' via GHC's simplification
rules, ouch!  You are likely to hit limits very very quickly.

However, if you want to do this *in* GHC, then Oleg showed how to do it in
the post
http://www.haskell.org/pipermail/haskell/2004-November/014939.html

> I have 
> also heard that the rules system is not strong enough for implementing a 
> full computer algebra system.

That might be because CASes cannot be done as (unconditional) rewrite
systems!  With 'conditional' TRS you can get much further, but the
condition-checking may involve arbitrary theorem proving.

I also attach a minor variation of Oleg's code in which all the Num
dependencies are removed(!) and replaced by the much weaker Show dependence.

Jacques


SymbolicDifferentiator.lhs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Keean Schupke
The generic busmaster diver should go all the way to UDMA mode 4 (133Mb)
   Keean.
Lennart Augustsson wrote:
Keean Schupke wrote:
Have a look at the linux kernel IDE drivers, look for
Generic IDE Chipset support
That's the part I missed, you were talking about IDE
chips.  Yes, they have many similarities.  You can
probably run many of them in one of the slower modes
with a common driver.  But even these chips differ
in the details.
-- Lennart

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


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Lennart Augustsson
Keean Schupke wrote:
Have a look at the linux kernel IDE drivers, look for
Generic IDE Chipset support
That's the part I missed, you were talking about IDE
chips.  Yes, they have many similarities.  You can
probably run many of them in one of the slower modes
with a common driver.  But even these chips differ
in the details.
-- Lennart
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Keean Schupke
Have a look at the linux kernel IDE drivers, look for
Generic IDE Chipset support
Generic PCI bus-master DMA support
   Keean.
Lennart Augustsson wrote:
What is this standard BusMaster interface you talk about?
I must have missed something.  I've yet to see two PCI chips
that do DMA the same way.
-- Lennart
Keean Schupke wrote:
I thought the BusMaster interface was pretty uniform, unlike the 
earlier DMA interfaces which varied from chipset to chipset.

   Keean.
Lennart Augustsson wrote:
But there are plenty of minor variations on how to program
and initiate DMA for different devices.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] tuple and HList

2005-03-22 Thread Keean Schupke
Oleg has just pointed out that the 'Show' constraint bellow does not 
work if you try and use a function from the show class (say 'show'), as 
the function:

test2 l = show l
has the type:
test2 :: forall a. (Show a) => a -> String
The technique below works to constrain for membership of a class, So we 
know all
elements in the list are instances of show, but we cannot call functions.

The best thing here is to let the compiler infer any remaining 
constraints using:

showList :: ConstrainedList SHOW l => l -> String
showList = undefined
test l
   | False = showList l
   | otherwise = show (hHead l)
Here the 'False' guard is never executed, but its type is unified with 
the inferred type for 'show l'... ghci shows us:

*Main> :type test
test :: forall b a.
   (Show a, ConstrainedList SHOW (HCons a b)) =>
   HCons a b -> String
In other words use constraints only to enforce explicit requirements, 
the compiler can safely infer all required constraints from the code (IE 
just don't give signatures for the functions).

Keean.

Keean Schupke wrote:
You can avoid the need to declare a new class for each constrained list
by using the following:
>class Constraint c a
>
>data SHOW
>instance Show a => Constraint SHOW a
>
>class HListConstraint c l
>instance HListConstraint c HNil
>instance (Constraint c a,HListConstraint c l) => HListConstraint c 
(HCons a l)

You can now constrain a list as follows:
>assertShow :: HListConstraint SHOW l => l -> l
>assertShow = id
The type parameter can be made first class using:
>showConstraint :: SHOW
>showConstraint = undefined
So we can now pass this as a parameter:
>assertConstraintOnHList :: HListConstraint c l => c -> l -> l
>assertConstraintOnHList _ = id
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Lennart Augustsson
What is this standard BusMaster interface you talk about?
I must have missed something.  I've yet to see two PCI chips
that do DMA the same way.
-- Lennart
Keean Schupke wrote:
I thought the BusMaster interface was pretty uniform, unlike the earlier 
DMA interfaces which varied from chipset to chipset.

   Keean.
Lennart Augustsson wrote:
But there are plenty of minor variations on how to program
and initiate DMA for different devices.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] implicit parameters THANK YOU!

2005-03-22 Thread Thomas Jäger
Hello again,

Sorry, I made a little mistake.

> > a :: Int
> > a = let ?foo = 0 in b where
> >   b :: (?foo :: Int) => Int
> >   b = let ?foo = 1 in c where
> > c = ?foo
> The meaning of this code depends on the flag
> -f(no)-monomorphism-restriction since with the monomorphism turned on,
> `c' gets the monomorphic type `Int', and the `?foo' in the definition
> of `c' refers to the implicit parameter of `b', so `a' evaluates to
> `0'. On the other hand, without the monomorphism restriction, the type
> of `c' becomes `(?foo :: Int) => Int', and it is easy to see that `a'
> evaluates to `0'.
In this case, `a' of course evaluates to `1'.

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


Re: [Haskell-cafe] implicit parameters THANK YOU!

2005-03-22 Thread Thomas Jäger
On Mon, 21 Mar 2005 20:29:35 -0500 (Eastern Standard Time), S.
Alexander Jacobson <[EMAIL PROTECTED]> wrote:
> I just discovered implicit parameters.  To everyone involved with
> making them, THANK YOU.  They are blazingly useful/powerful for server
> handler style libraries where you want to make a veriety of local
> environment information available to the handlers without burdening
> the handlers with a big dictionary object to carry around.  FANTASTIC.
I like to think of implicit parameters as a direct-style reader monad.
Therefore, they can be used interchangably with reader monads (or with
explicit passing of the parameter, for that matter). Which one you
choose is of course a matter of taste, but personally, I prefer the
monadic approach, since it is easier to extend (maybe you later
discover that you really needed state) and it is the usual (and
portable) Haskell solution. Furthermore, because `(->) r' already is a
reader monad, the code can often be kept very consice.

The situation is different if you've already written some code and
realize you need an additional parameter in a couple of functions.
Monadifying all that code (or explicitely threading the parameter) is
usually a lot of trouble and the change might be only experimental
anyway, so with implicit parameters, you can just change a few
signatures and be done.

> That being said, they so powerful they are proabably easy to abuse.
> Could those experienced with this feature provide warnings about
> possible problems with overuse?
I've only used them sparsely and I think that's the way to go. Also,
you should be aware of a few common problems:

1. Recursive functions
http://www.haskell.org/pipermail/haskell-cafe/2005-January/008571.html
This is not surprising if you consider how type inference for
recursive functions works, but it is obviously the wrong thing to do.
Personally, I'd be happy if (mutually) recursive functions using
implicit parameters without a type signature were rejected, because to
do it correctly, some sort of polymorphic recursion is necessary.

2. The monomorphism restriction
Consider
> a :: Int
> a = let ?foo = 0 in b where
>   b :: (?foo :: Int) => Int
>   b = let ?foo = 1 in c where 
> c = ?foo  
The meaning of this code depends on the flag
-f(no)-monomorphism-restriction since with the monomorphism turned on,
`c' gets the monomorphic type `Int', and the `?foo' in the definition
of `c' refers to the implicit parameter of `b', so `a' evaluates to
`0'. On the other hand, without the monomorphism restriction, the type
of `c' becomes `(?foo :: Int) => Int', and it is easy to see that `a'
evaluates to `0'.
The fact that the meaning depends on the type signature actually isn't
that bad; after all, in explicit monadic code, you would have to make
the same choice. The interaction with the monomorphism restriction,
however, seems very unfortunate.

Btw, to explicitely type a declaration in a let binding, the style
"let x :: a = b" isn't enough, it needs to be "let x :: a; x = b".

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


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Keean Schupke
I thought the BusMaster interface was pretty uniform, unlike the earlier 
DMA interfaces which varied from chipset to chipset.

   Keean.
Lennart Augustsson wrote:
But there are plenty of minor variations on how to program
and initiate DMA for different devices.
-- Lennart
Keean Schupke wrote:
Actually with PCI chipsets, implementing a generic BusMaster DMA driver
is not too hard, assuming you already have interrupts handled (and 
you don't want 64bit DMA support)... You just load the parameters for 
the disk read into the PCI registers, and wait for the completed 
interrupt. I wrote a diver in assembly language for my own OS project 
a few years ago.

   Keean.

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


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Lennart Augustsson
But there are plenty of minor variations on how to program
and initiate DMA for different devices.
-- Lennart
Keean Schupke wrote:
Actually with PCI chipsets, implementing a generic BusMaster DMA driver
is not too hard, assuming you already have interrupts handled (and you 
don't want 64bit DMA support)... You just load the parameters for the 
disk read into the PCI registers, and wait for the completed interrupt. 
I wrote a diver in assembly language for my own OS project a few years ago.

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


Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Keean Schupke
Actually with PCI chipsets, implementing a generic BusMaster DMA driver
is not too hard, assuming you already have interrupts handled (and you 
don't want 64bit DMA support)... You just load the parameters for the 
disk read into the PCI registers, and wait for the completed interrupt. 
I wrote a diver in assembly language for my own OS project a few years ago.

   Keean.
Iavor Diatchki wrote:
Hello,
There are no storage drivers at the moment.  Actually part of the
motivation for implementing the networking stuff was so that we can
avoid doing that at least for the time being.
-Iavor
On Mon, 21 Mar 2005 01:32:19 -0500 (Eastern Standard Time), S.
Alexander Jacobson <[EMAIL PROTECTED]> wrote:
 

Very very cool.
Has anyone written any storage drivers?
If there is already TCP, has someone written an iscsi (RFC3720)
driver?
-Alex-
On Mon, 21 Mar 2005, Donald Bruce Stewart wrote:
   

dons:
 

alex:
   

Wow!  Did you also implement tcp in Haskell?
 

On this topic, the following House code looks relevant:
  http://cvs.haskell.org/cgi-bin/cvsweb.cgi/programatica/hOp/kernel/Net/
There's something satsifying about seeing 'instance Functor Packet' in
IPv4.hs ;)
 

Does hOp or House also have the ability to write to disk?
(With HAppS, I've gotten rid of the AMP part of LAMP, it would be
really cool to get rid of the L as well!)
 

Sorry! By "We've got a few drivers written in Haskell", I meant
"the Haskell community", not me personally :} You have the hOp and House
developers to thank for this stuff.
   

On Mon, 21 Mar 2005, Donald Bruce Stewart wrote:
 

mark:
   

I was wondering about the possibility of using Haskell for developing
device drivers that would be kernel modules for Linux. If nothing else,
it would be quite an educational experience for me, as I've not yet
experimented with either the Linux kernel or Haskell FFI, nor have I
had to learn how to squeeze much performance out of my Haskell code.
Clearly, this application demands special things from the compiler and
the runtime. But, I'm not exactly sure what, nor how to achieve such
given current compilers. Does anyone have any thoughts?
 

Well, it would be tricky, but fun!
We've got a few drivers written in Haskell already (but not for Linux,
as far as I know). For example check out the House network stack and
drivers:
 http://cvs.haskell.org/cgi-bin/cvsweb.cgi/programatica/hOp/
and
 
http://cvs.haskell.org/cgi-bin/cvsweb.cgi/programatica/hOp/kernel/Kernel/Driver/NE2000/
So there's heavy use of Data.Bits and Word# types - but nothing that
isn't fairly well established in GHC Haskell, anyway.
Then (for GHC, anyway) you'd have to link the kernel against libHSrts.a,
much
as we do when calling Haskell from other kinds of C apps, which involves
compiling the C app with all the magic flags ghc normally sets up (ghc -v9
main.c is helpful).  Something like: ;)
egcc -v -o a.out -DDONT_WANT_WIN32_DLL_SUPPORT main.o
-L/home/dons/lib/ghc-6.4 -lHStemplate-haskell -lHSCabal -lHSposix
-lHSposix_cbits -lHSlang -lHSmtl -lHShaskell-src -lHSunix -lHSunix_cbits
-lHShi -lHShaskell98 -lHSaltdata -lHSbase -lHSbase_cbits -lHSrts -lm -lgmp
-u GHCziBase_Izh_static_info -u GHCziBase_Czh_static_info -u
GHCziFloat_Fzh_static_info ...
Then, having the kernel start up the Haskell rts (at boot would be
good):
   hs_init(&argc, &argv);
 .. do something in Haskell or C land ...
   hs_exit();
Then you'd could dyn load (via GHC's rts) your Haskell driver into the C
app, and use it, as long as you've got a nice ffi interface to pass
values back and forward.
I'm sure the fun part is in the details ;)
Cheers,
Don
___
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
   

__
S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
___
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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Symbolic differentation using GHC's simplification rules

2005-03-22 Thread Henning Thielemann
I tried to implement symbolic differentation using GHC's simplification 
rules. I assume that someone has already thought about this, right? I have 
also heard that the rules system is not strong enough for implementing a 
full computer algebra system.

But here is a simple trial and some questions and problems which arise:
 1. How to specify a type class context to which the rules have to be 
restricted? (see the first comment)
 2. How to handle lambdas?
 3. The module can only be used for compiled programs, since in GHCi 
optimisation is not available.

{-# OPTIONS -O -fglasgow-exts #-}
module SymbolicDifferentation where
{- These rules need Num context. -- How to write that?
 "derive/const"  forall y.   derive (const y) = const 0 ;
 "derive/id" derive id= const 1 ;
 "derive/compos" forall f g. derive (f .  g) = derive f . g .* derive 
g ;
-}

{-# RULES
 "derive/plus"   forall f g. derive (f .+ g) = derive f .+ derive g ;
 "derive/minus"  forall f g. derive (f .- g) = derive f .- derive g ;
 "derive/times"  forall f g. derive (f .* g) = derive f .* g .+ f .* derive 
g ;
 "derive/divide" forall f g. derive (f ./ g) = derive f .* g .- f .* derive 
g ./ ((^2).g) ;
 "derive/power"  forall n.   derive ((^) n) = (n*) . (^(n-1)) ;
 "derive/sin"derive sin  = cos ;
 "derive/cos"derive cos  = negate . sin ;
 "derive/exp"derive exp  = exp ;
 "derive/log"derive log  = recip ;
  #-}
-- lift a binary operation to the function values
fop2 :: (c -> d -> e) -> (a -> c) -> (a -> d) -> (a -> e)
fop2 op f g x = op (f x) (g x)
infixl 6 .+, .-
infixl 7 .*, ./
(.+), (.-), (.*) :: Num a=> (t -> a) -> (t -> a) -> (t -> a)
(./) :: Fractional a => (t -> a) -> (t -> a) -> (t -> a)
(.+) = fop2 (+)
(.-) = fop2 (-)
(.*) = fop2 (*)
(./) = fop2 (/)
derive :: (t -> a) -> (t -> a)
derive = error "Could not derive expression symbolically."
test :: IO ()
test =
   do print (derive log 2)
  print (derive sin 0)
  print (derive cos 0.1)
  print (derive (cos .+ sin) (pi/4))
  print (derive (\x -> exp x) 0)
  print (derive (\x -> x^2 + x) 0)
  print (derive (exp . sin) 0)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] State, StateT and lifting

2005-03-22 Thread Juan Carlos Arevalo Baeza
Andrew Pimlott wrote:
On Sat, Mar 19, 2005 at 03:25:32AM -0800, Juan Carlos Arevalo Baeza wrote:
 

Andrew Pimlott wrote:
   

You might solve this by changing the type of matchRuleST:
 matchRuleST :: MonadState RuleSet m => String -> m (Maybe Rule)
 

 I don't know... The original using IO somehow offended me because it 
was not an operation that required IO. This one leaves the inner monad 
unspecified, but still looks like baggage to me.
   

Look again:  There is no inner monad there, only the constraint that m
is a state monad.  State and StateT are both instances of MonadState, so
you can use this matchRuleST both with plain State, or StateT with any
inner monad.
 

  Oh, I see now. It does work, too. Even after using this, it still 
looks quite strange to me. I dunno... it's odds like this one that make 
Haskell into a naturally obfuscated language, IMHO. You can only see 
this by "thinking mathematically", if you know what I mean. The way I 
was doing it before, I was thinking... relatively little in comparison. 
It's what came naturally (and still does).

  I can prove I'm not a hopeless case :). So... same thing for the 
other functions. Following your example, I switched them to:

makeListST :: (MonadState RuleSet m, MonadIO m) => [String] -> m ()
makeST :: (MonadState RuleSet m, MonadIO m) => String -> m ()
  and that works, too. No more StateT either. Just like with STate, the 
question is... would I ever use it directly? Now, I still need 
execStateT to implement the main entry point into the engine, right?

-- Main entry point into the make engine.
make :: RuleSet -> String -> IO RuleSet
make ruleSet ruleName = execStateT (makeST ruleName) ruleSet
you don't need liftState at all.
 

  No I don't. I don't need State either. Are there any situations where 
it makes sense to use State directly?

Aside:  It bugs me that this is not defined by Control.Monad.State
(alongside modify and gets):
 state :: MonadState s m => (s -> (a, s)) -> m a
 

 Cute, thanx! It's good to know I wasn't just missing something 
obvious. So, this is my final implementation (works!):

state :: MonadState s m => (s -> (a, s)) -> m a
state sm = do
  s <- get
  let (result, newState) = sm s
  put newState
  return result
liftState :: Monad m => State s a -> StateT s m a
liftState (State f) = state f
   

Nice!  Note that the inferred signature for liftState is
   liftState :: (MonadState s m) => State s a -> m a
 

  Ah, yes! Even more general-purpose. so... liftState and state are 
both gone. You say you end up having to define "state" anyway. What 
situations are there which require it?

  So... about liftIO... I implemented the main function of my make 
engine like this:

makeST ruleName = do
   rule <- matchRuleST ruleName -- (thanx!)
   case rule of
   Just (File dst srcList action) -> do
   makeListST srcList
   older <- liftIO $ isOlderFile dst srcList
   if older then do
   liftIO $ do
   print $ "Running file " ++ dst ++ "\n"
   action dst srcList
   return ()
   else
   return ()
   Just (DoneRule _) -> return ()
   Nothing -> liftIO $ do
   exists <- doesFileExist ruleName
   if existsthen return ()
   else ioError $ userError $ "Rule not found: " ++ 
ruleName

  As you can see, I'm using liftIO quite a lot. I guess that's 
necessary. I just wanted to double-check that it really is, and that I'm 
doing it correctly.

  Thanx a lot for your patience!
JCAB
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe