[Haskell-cafe] Why does the class called "Real" support only rationals, and not all reals?

2007-06-03 Thread bretm

I just got started learning Haskell a few days ago. I've implemented a
numeric data type that can represent some irrational numbers exactly, and
I'd like to instantiate the RealFrac class so I can do truncate, round,
etc., in the most natural way in the language.

Implementing properFraction (which is in RealFrac) would not a problem at
all, but implementing RealFrac requires implementing Real, which has the
function toRational, which Haskell 98 says "returns the rational equivalent
of its real argument with full precision" which isn't possible for this
number type (which includes irrationals).

I'd also like to implement approxRational since this can be done in a
straightforward manner with my data type, but this appears to be just a
library function in the Ratio library and not a function defined in a class,
and is dependent on the toRational function which doesn't make sense for a
data type that can represent irrational values exactly.

So my questions are: 1) Am I understanding the Haskell numeric classes
correctly by thinking that to define properFraction I also have to define
(incorrectly in this case) the toRational function?  2) Is a literal reading
of Haskell 98 necessary for toRational or can it just be approximate? (Seems
like not, since there's approxRational, and no other way to indicate the
desired accuracy for toRational.)  3) If I'm right about toRational
requiring "full precision", why was implementing this made a requirement for
implementing properFraction? 4) Why on earth is there a class called "Real"
that requires the ability to convert to Rational with full precision, which
can't be done with all real numbers?

As an example, consider a data type that can represent a quadratic surd,
e.g. (1, 5, 2) might mean (1 + (sqrt 5)) / 2.  With this data type it's
straightforward to implement the Num and Fractional classes and get full
arithmetic operations +, -, *, /, etc. The properFraction function also
makes sense: there's an integer portion equal to 1 in this case, and a
fractional portion equal to (-1, 5, 2), exactly. So truncate, round,
ceiling, and floor make sense (in RealFrac). But toRational can't be
implemented with "full precision". 

With this example you can also see how approxRational is a perfectly good
idea, and would be something likely to be needed, but this function isn't a
class function designed to be implemented by custom data types.

It seems to me (with my meager few days of Haskell experience) that
approxRational should have been part of the Real class, and that toRational
should be relegated the Ratio library instead. Or else, that the functions
that are in RealFrac should be in the Fractional class instead. So I'm
guessing there are some good reasons for having RealFrac in addition to
Fractional that I'm not yet aware of.

-- 
View this message in context: 
http://www.nabble.com/Why-does-the-class-called-%22Real%22-support-only-rationals%2C-and-not-all-reals--tf3862820.html#a10943139
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-03 Thread Donald Bruce Stewart
almeidaraf:
> On 6/3/07, Rafael Almeida <[EMAIL PROTECTED]> wrote:
> >The site seems to be asking for the internal floating point
> >representation.  So it doesn't matter if it's IEEE 754, if the ints are
> >2-complements, or whatever. I used this code as a quick hack for one of
> >my programs, but I think it would work in this case. It should work for
> >any Storable type.
> >
> >import qualified Data.ByteString as BS
> >import Data.ByteString.Base
> >import Foreign.ForeignPtr
> >import Foreign.Storable
> >binPut num =
> >do
> >fptr <- mallocForeignPtrBytes (sizeOf num)
> >withForeignPtr (castForeignPtr fptr) (\x -> poke x num)
> >BS.writeFile "/tmp/foo" (BS.reverse $ fromForeignPtr fptr (sizeOf 
> >num))
> >
> Ops, that reverse was needed for what I was doing, but not needed for
> this particular problem, so the code should actually be:
> 
> import qualified Data.ByteString as BS
> import Data.ByteString.Base
> import Foreign.ForeignPtr
> import Foreign.Storable
> binPut num =
>do
>fptr <- mallocForeignPtrBytes (sizeOf num)
>withForeignPtr (castForeignPtr fptr) (\x -> poke x num)
>BS.writeFile "/tmp/foo" (fromForeignPtr fptr (sizeOf num))
 ^^^
Interesting use of ByteStrings to print foreigin ptr arrays there. 

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


Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-03 Thread Rafael Almeida

On 6/3/07, Rafael Almeida <[EMAIL PROTECTED]> wrote:

The site seems to be asking for the internal floating point
representation.  So it doesn't matter if it's IEEE 754, if the ints are
2-complements, or whatever. I used this code as a quick hack for one of
my programs, but I think it would work in this case. It should work for
any Storable type.

import qualified Data.ByteString as BS
import Data.ByteString.Base
import Foreign.ForeignPtr
import Foreign.Storable
binPut num =
do
fptr <- mallocForeignPtrBytes (sizeOf num)
withForeignPtr (castForeignPtr fptr) (\x -> poke x num)
BS.writeFile "/tmp/foo" (BS.reverse $ fromForeignPtr fptr (sizeOf num))


Ops, that reverse was needed for what I was doing, but not needed for
this particular problem, so the code should actually be:

import qualified Data.ByteString as BS
import Data.ByteString.Base
import Foreign.ForeignPtr
import Foreign.Storable
binPut num =
   do
   fptr <- mallocForeignPtrBytes (sizeOf num)
   withForeignPtr (castForeignPtr fptr) (\x -> poke x num)
   BS.writeFile "/tmp/foo" (fromForeignPtr fptr (sizeOf num))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Just for a laugh...

2007-06-03 Thread Rafael Almeida

The site seems to be asking for the internal floating point
representation.  So it doesn't matter if it's IEEE 754, if the ints are
2-complements, or whatever. I used this code as a quick hack for one of
my programs, but I think it would work in this case. It should work for
any Storable type.

import qualified Data.ByteString as BS
import Data.ByteString.Base
import Foreign.ForeignPtr
import Foreign.Storable
binPut num =
   do
   fptr <- mallocForeignPtrBytes (sizeOf num)
   withForeignPtr (castForeignPtr fptr) (\x -> poke x num)
   BS.writeFile "/tmp/foo" (BS.reverse $ fromForeignPtr fptr (sizeOf num))
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Template Haskell, information about data constructor types

2007-06-03 Thread Neil Mitchell

Hi

I'm trying to write a function:

reaches :: Type -> Q [Type]

The intention is that reaches (Either Bool [Int]) would return [Either
Bool [Int], Bool, [Int], Int] - i.e. all types which are contained by
the initial type at any level.

I took a shot at this:

getTypes :: Type -> Q [Type]
getTypes t = do
   let (ConT c, cs) = typeApp t
   TyConI dat <- reify c
   return $ concatMap ctorTypes $ dataCtors dat


reaches :: Type -> Q [Type]
reaches t = f [] [t]
   where
   f done [] = return done
   f done (t:odo)
   | t `elem` done = f done odo
   | otherwise = do
   ts <- getTypes t
   f (t:done) (odo ++ ts)

Where typeApp splits a type to find its constructor, ctorTypes gets
the types of the fields, and dataCtors gets the constructors in a data
type. Unfortunately reify doesn't seem to work on types. Is it
possible to do what I am after?

Thanks

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


Re: [Haskell-cafe] Ref and Derive

2007-06-03 Thread Neil Mitchell

Hi


Speaking of Derive: I tried to install it just a few days ago, and failed.
'Derive' needed 'filepath-any', which needed 'directory-any', which I
couldn't find (in Hackage or on Neil's website).


Either:

1) Use GHC 6.6.1, which comes with filepath
2) Use the hackage version:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/filepath-1.0

I wouldn't recommend using the darcs version, since it will only work
with the very latest copy of base which is in the process of being
split up.

Thanks

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Ketil Malde
On Sun, 2007-06-03 at 09:02 -0300, Felipe Almeida Lessa wrote:
> On 6/3/07, Tillmann Rendel <[EMAIL PROTECTED]> wrote:
> > In functional programming, problems of the kind "and the same code for
> > all functions doing something related" are most often solved by
> > introducing higher order functions. Let's try to decompose the problem
> > as follows:

> Now I've got one question ;).  Is it *efficient* to go down this way?

Only one way to find out!

> Maybe using a Map instead of
> a list would at least let the complexity go down a little bit? Or am I
> missing something?

I was going to suggest that.  The difference - well, one of them -
between OOP and FP is that FP deals with values, OOP with data ojects.
The objects have identity, so you can change the name of a planet, and
maintain that it is still the same planet.  A value is just defined as
itself, and if you insist you can change a value, at least you must
admit it then becomes a different one.

Identity can be emulated by relatively straightforward means: store all
planets in a Map indexed by something that is useful as an identifier
(i.e. stays constant and is unique), and have a Galaxy keep a list of
identifiers.

You may even find that the dissociation of galaxies from planets etc is
an advantage, perhaps you want to deal with planets irrespectively of
their galaxies, or perhaps some planets don't even belong to a galaxy?

-k


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


[Haskell-cafe] Ref and Derive

2007-06-03 Thread Arie Peterson
Hello,


Stefan O'Rear wrote:

> I've implemented this in Derive[1] in 12 minutes, counting the time
> required to re-familiarize with the code.  The patch is at [2] and has
> also been darcs sent.

Neil Mitchell wrote:

> It's been applied, and is now in the main repo.

Wow, that was fast. I didn't really consider that this code might be
consolidated, so the naming could be off. Not that I'm complaining :-).

Would anyone care to see the Ref type itself in some publicly available
place?


Speaking of Derive: I tried to install it just a few days ago, and failed.
'Derive' needed 'filepath-any', which needed 'directory-any', which I
couldn't find (in Hackage or on Neil's website).


Greetings,

Arie

-- 

Just follow the magic footprints.

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


Re: [Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Neil Mitchell

Hi


> You could also use 'compositional functional references'. These are
> introduced in the paper "A Functional Programming Technique for Forms in
> Graphical User Interfaces" by Sander Evers, Peter Achten and Jan Kuper.
>
> I've written a template haskell function to derive Refs from a data  
  
   > structure definition (with record 
syntax): given

I've implemented this in Derive[1] in 12 minutes, counting the time
required to re-familiarize with the code.  The patch is at [2] and has
also been darcs sent.

[1] http://www-users.cs.york.ac.uk/~ndm/derive


It's been applied, and is now in the main repo.

Thanks

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


[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Stefan O'Rear
(Sorry to break the thread, but mutt somehow managed to eat the message
I'm replying to...)

Arie Peterson:
> You could also use 'compositional functional references'. These are
> introduced in the paper "A Functional Programming Technique for Forms in
> Graphical User Interfaces" by Sander Evers, Peter Achten and Jan Kuper.
>
> === Introduction ===
>
> There are two things one typically wants to do when working with a
> substructure of some larger data structure: (1) extract the substructure;
> and (2) change the larger structure by acting on the substructure. A 'Ref
> cx t' encodes both of these functions (for a substructure of type 't' and
> larger structure (context) of type 'cx').
>
> > data Ref cx t
> >  = Ref
> >{
> >  select :: cx -> t
> >, update :: (t -> t) -> cx -> cx
> >}
...
> I've written a template haskell function to derive Refs from a data   
>   
>   > structure definition 
> (with record syntax): given

I've implemented this in Derive[1] in 12 minutes, counting the time
required to re-familiarize with the code.  The patch is at [2] and has
also been darcs sent.

[1] http://www-users.cs.york.ac.uk/~ndm/derive
[2] http://members.cox.net/stefanor/derive-Ref-patch

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


[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Arie Peterson
You could also use 'compositional functional references'. These are
introduced in the paper "A Functional Programming Technique for Forms in
Graphical User Interfaces" by Sander Evers, Peter Achten and Jan Kuper.

=== Introduction ===

There are two things one typically wants to do when working with a
substructure of some larger data structure: (1) extract the substructure;
and (2) change the larger structure by acting on the substructure. A 'Ref
cx t' encodes both of these functions (for a substructure of type 't' and
larger structure (context) of type 'cx').

> data Ref cx t
>  = Ref
>{
>  select :: cx -> t
>, update :: (t -> t) -> cx -> cx
>}

A Ref is a bit like a typed and composable incarnation of apfelmus's
indices, or a wrapper around Tillmann's change* functions, containing not
only a setter but also the accompanying getter.

=== Use ===

These Refs are compositional: given 'x :: Ref a b' and 'y :: Ref b c', we
can form

> z :: Ref a c
> z = Ref
> {
>   select = select b . select a
> , update = update a . update b
> }

. In fact we can almost make 'Ref' into an arrow. (Only 'pure :: (a -> b)
-> Ref a b' does not make sense, because a pure function 'f : a -> b'
doesn't give information about how to transform a change in 'b' into a
change in 'a'.)

I've written a template haskell function to derive Refs from a data
structure definition (with record syntax): given

> data Universe
>   = Universe
> {
>   galaxies :: [Galaxy]
> }

, it creates

> galaxiesRef :: Ref Universe [Galaxy]

. Together with some Ref functions for container types (List, Map, etc.)
this eliminates most (all?) necessary boilerplate code.


Greetings,

Arie

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Vincent Kraeutler
Phlex wrote:
> This is very informative, and easier to grasp for such a newbie as me.
> So the idea is to take the "changing function" down the chain, i knew
> this couldn't be that hard !
> Still this requires indeed to think different, I guess i'm up for
> quite a few exercises in order to wrap my mind around this.
>
> That's the kind of information that's missing from all these tutorials
> i found around the web.
>
> Thank you,
> Sacha
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>

for what it's worth, i find it easiest to think about it this way:

assume you want to update a planet, i.e. you want to apply
changeP :: Planet -> Planet
to one planet in your system.

the important step is then to invoke wishful thinking (viz. SICP), and
assume you can partition your data structure into two parts, the one
that stays constant, and the one that is changed, i.e.

partition :: Universe -> (Rest, Planet)

with a corresponding inverse operation

recombine :: (Rest, Planet) -> Universe

So after the partitioning, updating the planet of interest is very easy
to accomplish:

changeP' (rest, planet) = (rest, changeP planet)

rolling the partitioning, updating and recombination into one, we get

update u = recombine (changeP' (partition u))

The second step is then to find out how to do the partitioning and
recombination easily and efficiently. For one very generic way to do
this, i would recommend that you read up on the Zipper data structure [1-3].

kind regards,
v.

[1] http://en.wikibooks.org/wiki/Haskell/Zippers
[2]
http://www.st.cs.uni-sb.de/edu/seminare/2005/advanced-fp/docs/huet-zipper.pdf
[3] http://cgi.cse.unsw.edu.au/~dons/blog/2007/05/17#xmonad_part1b_zipper





signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Christopher Lane Hinson



Let's say i have a deep nested data structure.
Universe containing galaxies, containing solar systems, containing
planets, containing countries, containing inhabitants, containing
...whatever.


Oh.  I had /exactly/ this problem.  If you use separate types (i.e. a 
newtyped integer, acting kindof like a pointer) to represent (1) the 
identity and (2) the state of the object, you can use a separate data 
structure that remembers which object is inside which other object.


http://www.downstairspeople.org/darcs/unstable/roguestar-engine/src/InsidenessMap.hs

Where "InsidenessMap a b c" represents a relationship where b's are inside 
a's, and b's have a state of c.  Then, you need to declare a separate 
InsidenessMap for each possible relationship, but this ensures that you'll 
never put a galaxy inside a solar system.  Or you can make 'a' be a 
reference to any type of object; there are options.


But, you just update this structure once, with no thought of recursively 
updating a heterogenous tree of data.


It may not be the best solution, but if I knew of something better I
would be using the better thing instead.

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Felipe Almeida Lessa

On 6/3/07, Tillmann Rendel <[EMAIL PROTECTED]> wrote:

In functional programming, problems of the kind "and the same code for
all functions doing something related" are most often solved by
introducing higher order functions. Let's try to decompose the problem
as follows:

[snip]

Now I've got one question ;).  Is it *efficient* to go down this way?
You are recreating (parts of) two lists and checking every planet,
every time you need to change something. Maybe using a Map instead of
a list would at least let the complexity go down a little bit? Or am I
missing something?

Cheers, =)

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Claus Reinke

hi there,


Let's say i have a deep nested data structure.
Universe containing galaxies, containing solar systems, containing 
planets, containing countries, containing inhabitants, containing 
...whatever.


Using the OO paradigm, once i get a reference to an inhabitant, i can 
update it quite easily (say by changing it's age), and that's the end of it.


but that approach limits you to about one choice for modelling your 
problem: a big ball of interlinked updateable references. every time

you update anything, you update everything, because that is all there is.
so you've reached "the end of it" for your modelling process before
you've even started to think about how best to model your problem.

haskell does have updateable references, so you could replicate that
approach, though i'd suspect there'd be very few cases where this
could actually be recommended. so here are two alternative, related
approaches, to give you an idea of what is possible:

data Universe = U [Galaxy] deriving Show
data Galaxy = G [SolarSystem] deriving Show
data SolarSystem = S [Planet] deriving Show
type Planet = String

u = U [G [S ["mercury","venus","earth","mars"]]] -- it's a small world

a) work inside the outer structures, by moving the work inwards, 
   to the target


traverseU g traverse (U gs) = U (here++(traverse this:there))
   where (here,this:there) = splitAt g gs
traverseG s traverse (G ss) = G (here++(traverse this:there))
   where (here,this:there) = splitAt s ss
traverseS p traverse (S ps) = S (here++(traverse this:there))
   where (here,this:there) = splitAt p ps

so, to work on a planet, you'd visit its solar system, then do the
work there:

workOnPlanet [g,s,p] work = traverseU g (traverseG s (traverseS p work))

b) work through the outer structures, by lifting target accessors 
outwards


liftUget g get (U gs) = get (gs!!g)
liftGget s get (G ss) = get (ss!!s)
liftSget p get (S ps) = get (ps!!p)

liftUset g set (U gs) =  U (here++(set this:there))
   where (here,this:there) = splitAt g gs
liftGset s set (G ss) =  G (here++(set this:there))
   where (here,this:there) = splitAt s ss
liftSset p set (S ps) =  S (here++(set this:there))
   where (here,this:there) = splitAt p ps

getPlanet get [g,s,p] = liftUget g (liftGget s (liftSget p get))
setPlanet set [g,s,p] = liftUset g (liftGset s (liftSset p set))

now, if 'get'/'set' work on a planet, then 'getPlanet get [g,s,p]'/
'setPlanet set [g,s,p]' work on a specific planet in a universe.

main = do
 print $ workOnPlanet [0,0,2] ("HERE: "++) u
 print $ getPlanet id [0,0,2] u
 print $ setPlanet (const "EARTH") [0,0,2] u

while (b) may be closer to the 'reference into everything' you're used
to, (a) is usually nicer and more efficient, because it nests larger chunks
of work instead of nesting each and every small step. both styles are in 
common use in haskell, though get&set are often merged into one.


there are more interesting aspects to this, eg, how exactly to model
the data structures (lists are a useable default, but not always the best
choice), or how to share substructures not affected by updates, or 
how to make traversal more flexible, so that we can change traversal
directions on the fly, or how to extract the commonalities in the data 
structure interfaces, so that we only have to write that traverse or 
lifting code once, and perhaps generically over the different types
addressed by different paths, etc. but since all of those will no 
doubt be addressed in other replies, i thought a simple start might 
be best;-)


hth,
claus

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex



Tillmann Rendel wrote:

Hello,

Phlex wrote:
changePlanetAge universe galaxy planet age = ...lots of code, 
returning a new universe
And the same code for all functions updating any of the properties of 
my planet ...
And the same code for all functions updating properties of a country 
on this planet...


In functional programming, problems of the kind "and the same code for 
all functions doing something related" are most often solved by 
introducing higher order functions. Let's try to decompose the problem 
as follows:


(1) change an attribute
(2) change a planet by changing one of it's attributes
(3) change a galaxy by changing one of it's planets
(4) change an universe by changing one of it's galaxies.

(1) is done by functions of type (Attribute -> Attribute). We will 
construct them on the fly.


For (2), we need functions for each attribute of a planet.

  type Name = String
  type Age = Integer
  data Planet = Planet Name Age

  -- lift name changer to planet changer
  changeName :: (Name -> Name) -> Planet -> Planet
  changeName f (Planet n a) = Planet (f n) a

  -- lift age changer to planet changer
  changeAge :: (Age -> Age) -> Planet -> Planet
  changeAge f (Planet n a) = Planet n (f a)

we need one of these functions for each attribute of each object. they 
correspond to setter-Methods in oop.


For (3), we have to select one of the planets in a galaxy to be 
changed. Let's assume integer indices for all planets.


  type Galaxy = [Planet]

  -- lift planet changer to galaxy changer
  changePlanet :: Integer -> (Planet -> Planet) -> Galaxy -> Galaxy
  changePlanet 0 f (p:ps) = f p : ps
  changePlanet n f (p:ps) = p : changePlanet (pred n) f ps

For (4), we have to select one of the galaxies in a universe to be 
changed. Let's assume integer indices again.


  type Universe = [Galaxy]

  -- lift galaxy changer to universe changer
  changeGalaxy :: Integer -> (Galaxy -> Galaxy) -> Universe -> Universe
  changeGalaxy 0 f (g:gs) = f g : gs
  changeGalaxy n f (g:gs) = g : changeGalaxy (pred n) f gs

Oups, that's the same as (3), up to renaming of types and variables. 
Let's refactor it to


  -- lift element changer to list changer
  changeElement :: Integer -> (a -> a) -> [a] -> [a]
  changeElement f 0 (x:xs) = f x : xs
  changeElement f n (x:xs) = x : changeListElement f (pred n) xs

  -- provide nicer names
  changePlanet = changeElement
  changeGalaxy = changeElement

Let's see how we can use this:

To set the name of the second planet of the third galaxy to "earth":

  (changeGalaxy 2 $ changePlanet 1 $ changeName $ const "earth") univ

To increase the age of the same planet by 1:

  (changeGalaxy 2 $ changePlanet 1 $ changeAge $ succ) univ

Using map instead of changeElement, we can change all galaxies or 
planets at once:


  --  provide nicer names
  changeGalaxies = map
  changePlanets = map

To set the name of the first planet in all galaxies to "first":

  (changeGalaxies $ changePlanet 0 $ changeName $ const "first") univ

To increase the age of all planets by one:

  (changeGalaxies $ changePlanets $ changeAge $ succ) univ

A possible next step is to use typeclasses as supposed by apfelmus to 
access elements of different structures in a uniform way.


  Tillmann



This is very informative, and easier to grasp for such a newbie as me.
So the idea is to take the "changing function" down the chain, i knew 
this couldn't be that hard !
Still this requires indeed to think different, I guess i'm up for quite 
a few exercises in order to wrap my mind around this.


That's the kind of information that's missing from all these tutorials i 
found around the web.


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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Tillmann Rendel

Hello,

Phlex wrote:
changePlanetAge universe galaxy planet age = ...lots of code, returning 
a new universe
And the same code for all functions updating any of the properties of my 
planet ...
And the same code for all functions updating properties of a country on 
this planet...


In functional programming, problems of the kind "and the same code for 
all functions doing something related" are most often solved by 
introducing higher order functions. Let's try to decompose the problem 
as follows:


(1) change an attribute
(2) change a planet by changing one of it's attributes
(3) change a galaxy by changing one of it's planets
(4) change an universe by changing one of it's galaxies.

(1) is done by functions of type (Attribute -> Attribute). We will 
construct them on the fly.


For (2), we need functions for each attribute of a planet.

  type Name = String
  type Age = Integer
  data Planet = Planet Name Age

  -- lift name changer to planet changer
  changeName :: (Name -> Name) -> Planet -> Planet
  changeName f (Planet n a) = Planet (f n) a

  -- lift age changer to planet changer
  changeAge :: (Age -> Age) -> Planet -> Planet
  changeAge f (Planet n a) = Planet n (f a)

we need one of these functions for each attribute of each object. they 
correspond to setter-Methods in oop.


For (3), we have to select one of the planets in a galaxy to be changed. 
Let's assume integer indices for all planets.


  type Galaxy = [Planet]

  -- lift planet changer to galaxy changer
  changePlanet :: Integer -> (Planet -> Planet) -> Galaxy -> Galaxy
  changePlanet 0 f (p:ps) = f p : ps
  changePlanet n f (p:ps) = p : changePlanet (pred n) f ps

For (4), we have to select one of the galaxies in a universe to be 
changed. Let's assume integer indices again.


  type Universe = [Galaxy]

  -- lift galaxy changer to universe changer
  changeGalaxy :: Integer -> (Galaxy -> Galaxy) -> Universe -> Universe
  changeGalaxy 0 f (g:gs) = f g : gs
  changeGalaxy n f (g:gs) = g : changeGalaxy (pred n) f gs

Oups, that's the same as (3), up to renaming of types and variables. 
Let's refactor it to


  -- lift element changer to list changer
  changeElement :: Integer -> (a -> a) -> [a] -> [a]
  changeElement f 0 (x:xs) = f x : xs
  changeElement f n (x:xs) = x : changeListElement f (pred n) xs

  -- provide nicer names
  changePlanet = changeElement
  changeGalaxy = changeElement

Let's see how we can use this:

To set the name of the second planet of the third galaxy to "earth":

  (changeGalaxy 2 $ changePlanet 1 $ changeName $ const "earth") univ

To increase the age of the same planet by 1:

  (changeGalaxy 2 $ changePlanet 1 $ changeAge $ succ) univ

Using map instead of changeElement, we can change all galaxies or 
planets at once:


  --  provide nicer names
  changeGalaxies = map
  changePlanets = map

To set the name of the first planet in all galaxies to "first":

  (changeGalaxies $ changePlanet 0 $ changeName $ const "first") univ

To increase the age of all planets by one:

  (changeGalaxies $ changePlanets $ changeAge $ succ) univ

A possible next step is to use typeclasses as supposed by apfelmus to 
access elements of different structures in a uniform way.


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


Re: [Haskell-cafe] Haskell on a PDA (was "Implementing Mathematica")

2007-06-03 Thread Philippa Cowderoy
On Sat, 2 Jun 2007, Fritz Ruehr wrote:

> I seem to recall that Aarne Ranta ran Hugs on a (Sharp) Zaurus PDA at one of
> the ICFPs a few years back. Aha, here in fact is a picture of his GF
> (Grammatical Framework), written in Haskell, running on a Zaurus:
> 

I've got Hugs and GHC both running under a debian image on my Zaurus (a 
C3200), for what it's worth. GHC's painfully slow though, sometime I 
should get round to cooperating some with everyone else looking at doing a 
registerised build on ARM to try producing a registerised GHC that runs 
natively on Sharp-derived ROMs. Not that that necessarily means I'll do 
it!

-- 
[EMAIL PROTECTED]

Ivanova is always right.
I will listen to Ivanova.
I will not ignore Ivanova's recomendations.
Ivanova is God.
And, if this ever happens again, Ivanova will personally rip your lungs out!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread apfelmus
apfelmus wrote:
>   {-# OPTIONS_GHC -fglasgow-exts -#}
>   import Prelude hiding (lookup)
> 
>   class Map map key a | map key -> a where
>   lookup :: key -> map -> Maybe a
>   adjust :: (a -> a) -> key -> map -> map
> 
>   instance (Map m k m', Map m' k' a) => Map m (k,k') a where
>   lookup (k,k') m   = lookup k m >>= lookup k'
>   adjust f (k,k') m = adjust (adjust f k') k m

Uh, that actually needs -fundecidable-instances or something similar.
Using explicit functor composition doesn't resolve the problem

  class Map map key | map -> key where
 lookup :: key -> map a -> Maybe a
 adjust :: (a -> a) -> key -> map a -> map a

  data O f g a = O (f (g a))

  instance (Map m k, Map m' k') => Map (m `O` m') (k,k') a where
...

  -- but how to make ((m `O` m') a) a map for (m' a)?

With associated type synonyms, this program can't even be formulated.
Any ideas?


For the time being, you can specialize the key-pairing for concrete maps
in question.

  newtype UniverseF a = UniverseF [a]
  newtype GalaxyF   a = GalaxyF [a]

  type Universe   = UniverseF Galaxy
  type Galaxy = GalaxyF Planet
  data Planet = ...

  instance Map (UniverseF a) k a where ...
  instance Map m k a => Map (UniverseF m) (Int,k) a where ...

Oh, and you need a dummy instance for Planets as "singleton"-maps.

  instance Map Planet () Planet where ...

Regards,
apfelmus

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


Re[2]: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Bulat Ziganshin
Hello Malcolm,

Sunday, June 3, 2007, 1:13:06 PM, you wrote:
>> The thing is, now that i have my planet p... i want to change it's age
>> ... and get back the new state of the universe...

> There has been lots of research into easing the pain of creating this
> outer traversal code - search for "Scrap your boilerplate", "compos",
> "Play", "generic traversal" (in conjunction with "Haskell").

yes, one more gentle haskell introduction LOL

i think that this is one more example of pattern where we suggest to
beginner advanced solution of problem. of course, problem still
exists and from time to time we need to solve it. but ABSOLUTELY MOST
of cases where beginners try to do something like this is when they
don't groked FP programming style and try to use Haskell in the
imperative way

so, Phlex, don't listen to my opponents :)  solution they suggest is
not what you need nor that you can understand now


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Phlex

apfelmus wrote:

Phlex wrote:
  

Donald Bruce Stewart wrote:


Yes and no. The point is that if you can't automate it, you have to code
it by hand anyway which constitutes most of the hairiness. But I know
what you mean and there's a nice way to do that with multi-parameter
type classes.

Let's assume a data structure

  data Universe = Universe [Galaxy]
  data Galaxy   = Galaxy   [Planet]
  data Planet   = Planet   { name :: String, size :: Double }

The insight is that in order to reference a planet inside the universe
structure, you have to know the path from the top. In other words, you
have to know that's it's the 2nd planet from the 4th galaxy before you
look up its name. If you don't throw that information away, you can use
it to update it as well. In effect, the Universe behaves like a finite
map with composite keys.

  {-# OPTIONS_GHC -fglasgow-exts -#}
  import Prelude hiding (lookup)

  class Map map key a | map key -> a where
  lookup :: key -> map -> Maybe a
  adjust :: (a -> a) -> key -> map -> map

  instance Map [a] Int a where
  lookup 0 [x]= Just x
  lookup 0 _  = Nothing
  lookup k (x:xs) = lookup (k-1) xs
  lookup _ _  = Nothing

  adjust f 0 [x]= [f x]
  adjust _ 0 xs = error "Index out of range"
  adjust f k (x:xs) = x : adjust f (k-1) xs
  adjust f _ xs = error "Index out of range"

  instance Map Universe Int Galaxy where
  lookup k (Universe gs)   = lookup k gs
  adjust f k (Universe gs) = Universe (adjust f k gs)

  instance Map Galaxy Int Planet where
  lookup k (Galaxy ps)   = lookup k ps
  adjust f k (Galaxy ps) = Galaxy (adjust f k ps)

  instance (Map m k m', Map m' k' a) => Map m (k,k') a where
  lookup (k,k') m   = lookup k m >>= lookup k'
  adjust f (k,k') m = adjust (adjust f k') k m


You can lookup the 2nd planet in the 4th galaxy with

  lookup (4,2) universe :: Maybe Planet

and you can update it via

  adjust (\planet -> planet {name = "Earth"}) (4,2) universe

Thanks to type-classes and overloading, you can still access single
galaxies with

  lookup 4 universe :: Maybe Galaxy

Regards,
apfelmus


This answers precisely my question.
Hiding the access/update methods behind a common interface, that's the 
key ...


Thanks a lot,
Sacha


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


Re[2]: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Bulat Ziganshin
Hello Phlex,

Sunday, June 3, 2007, 12:34:26 PM, you wrote:
> So i need to do something like this :

> changePlanetAge universe galaxy planet age = ...lots of code, returning
> a new universe
> And the same code for all functions updating any of the properties of my
> planet ...
> And the same code for all functions updating properties of a country on
> this planet...

> while in the OO paradigm, i only need to do

> changlePlanetAge planet age = ...just what you wrote


i think that problem is that you think in imperative paradigm. you
want to update the whole universe structure each time when one
children is born. the solution is to work on lower levels and change
your algorithms to group changes in substructures together

just one example: i parse config file in my program, i.e. i need
function that returns setting given section and entry name:

configData configFileContents sectionName entryName

in imperative paradigm i will probably scan whole file each time i
need an entry. in Haskell, i just split the whole config file into
sections and extract entries from appropriate sections. imagine the
opposite task, i will probably group entries together and concat them
into sections and then concat sections into the whole config file
while in imperative programming each new update will change the global
structure

change your mind, Neo! ;)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Malcolm Wallace
Phlex <[EMAIL PROTECTED]> writes:

> The thing is, now that i have my planet p... i want to change it's age 
> ... and get back the new state of the universe...

It is true, there is often a significant amount of "boilerplate" code
needed to wrap a simple planet-change nested deep within a universe
structure.

There has been lots of research into easing the pain of creating this
outer traversal code - search for "Scrap your boilerplate", "compos",
"Play", "generic traversal" (in conjunction with "Haskell").

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


Re: [Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread Donald Bruce Stewart
apfelmus:
> Phlex wrote:
> > Donald Bruce Stewart wrote:
> >>
> >> Imagine updating a node in a tree by just detaching and reattaching a
> >> pointer.
> >>
> >> [1] [1]
> >> / \ / \
> >>   [2] [3] update node 5   [2] [3]
> >>   / \ with value  7   / \
> >> [4] [5] [4]  *
> >>
> >> and share the rest of the structure. Since the rest isn't mutable
> >> anyway, you can share all over.
> > 
> > That's precisely the thing i don't understand.
> > In order to update node 3 with a new pointer, i need to mutate it, so i
> > need to recreate it, and so on up to node 1.
> 
> Yes, that's correct, I think Dons shared a bit too much here :)

Spent too much time with zippers lately ;)

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


[Haskell-cafe] Re: I just don't get it (data structures and OO)

2007-06-03 Thread apfelmus
Phlex wrote:
> Donald Bruce Stewart wrote:
>>
>> Imagine updating a node in a tree by just detaching and reattaching a
>> pointer.
>>
>> [1] [1]
>> / \ / \
>>   [2] [3] update node 5   [2] [3]
>>   / \ with value  7   / \
>> [4] [5] [4]  *
>>
>> and share the rest of the structure. Since the rest isn't mutable
>> anyway, you can share all over.
> 
> That's precisely the thing i don't understand.
> In order to update node 3 with a new pointer, i need to mutate it, so i
> need to recreate it, and so on up to node 1.

Yes, that's correct, I think Dons shared a bit too much here :)

[1]   [1']
/ \   /  \
  [2] [3]  update node 5[2]  [3']
  / \/  \
[4] [5][4]  [5']

You have to recreate all nodes that point directly or indirectly to 5,
but you can share all the other nodes like 2 and 4 that have no forward
pointers to 5.

Note that creating new nodes is dead simple, there's no effort involved
on the programmer's part. Here's an example that rotates the top of a
binary tree:

  data Tree a = Leaf a | Node (Tree a) (Tree a)

  rotateRight :: Tree a -> Tree a
  rotateRight (Node (Node a b) c) = Node a (Node b c)

The top two nodes are recreated with the constructor Node but a,b and c
are shared.

> Now in this example, it's ok since that's a regular tree and the process
> can be automated, but when each node has a different type, it can become
> quite hairy.

Yes and no. The point is that if you can't automate it, you have to code
it by hand anyway which constitutes most of the hairiness. But I know
what you mean and there's a nice way to do that with multi-parameter
type classes.

Let's assume a data structure

  data Universe = Universe [Galaxy]
  data Galaxy   = Galaxy   [Planet]
  data Planet   = Planet   { name :: String, size :: Double }

The insight is that in order to reference a planet inside the universe
structure, you have to know the path from the top. In other words, you
have to know that's it's the 2nd planet from the 4th galaxy before you
look up its name. If you don't throw that information away, you can use
it to update it as well. In effect, the Universe behaves like a finite
map with composite keys.

  {-# OPTIONS_GHC -fglasgow-exts -#}
  import Prelude hiding (lookup)

  class Map map key a | map key -> a where
  lookup :: key -> map -> Maybe a
  adjust :: (a -> a) -> key -> map -> map

  instance Map [a] Int a where
  lookup 0 [x]= Just x
  lookup 0 _  = Nothing
  lookup k (x:xs) = lookup (k-1) xs
  lookup _ _  = Nothing

  adjust f 0 [x]= [f x]
  adjust _ 0 xs = error "Index out of range"
  adjust f k (x:xs) = x : adjust f (k-1) xs
  adjust f _ xs = error "Index out of range"

  instance Map Universe Int Galaxy where
  lookup k (Universe gs)   = lookup k gs
  adjust f k (Universe gs) = Universe (adjust f k gs)

  instance Map Galaxy Int Planet where
  lookup k (Galaxy ps)   = lookup k ps
  adjust f k (Galaxy ps) = Galaxy (adjust f k ps)

  instance (Map m k m', Map m' k' a) => Map m (k,k') a where
  lookup (k,k') m   = lookup k m >>= lookup k'
  adjust f (k,k') m = adjust (adjust f k') k m


You can lookup the 2nd planet in the 4th galaxy with

  lookup (4,2) universe :: Maybe Planet

and you can update it via

  adjust (\planet -> planet {name = "Earth"}) (4,2) universe

Thanks to type-classes and overloading, you can still access single
galaxies with

  lookup 4 universe :: Maybe Galaxy



Regards,
apfelmus

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex



Bulat Ziganshin wrote:

Hello Phlex,

Sunday, June 3, 2007, 11:41:29 AM, you wrote:
  

That's precisely the thing i don't understand.
In order to update node 3 with a new pointer, i need to mutate it, so i
need to recreate it, and so on up to node 1.



yes, that's true

  

Now in this exemple, it's ok since that's a regular tree and the process
can be automated, but when each node has a different type, it can become
quite hairy.



may be all that you need is structure update syntax?

data Planet = Planet { age :: Double
 , weight :: Double
 .
 }

updatePlanet p = p {age=(age p)*2}


  


The thing is, now that i have my planet p... i want to change it's age 
... and get back the new state of the universe...


So i need to do something like this :

changePlanetAge universe galaxy planet age = ...lots of code, returning 
a new universe
And the same code for all functions updating any of the properties of my 
planet ...
And the same code for all functions updating properties of a country on 
this planet...


while in the OO paradigm, i only need to do

changlePlanetAge planet age = ...just what you wrote

I understand that the advantages of functional programming do come at a 
cost ... And i'm pretty sure you guys came up with some way to avoid 
expressing all that upward copying, although it must happen somehow.


I'm not sure i'm being clear here.

Carkos


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


Re[2]: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Bulat Ziganshin
Hello Phlex,

Sunday, June 3, 2007, 11:41:29 AM, you wrote:
> That's precisely the thing i don't understand.
> In order to update node 3 with a new pointer, i need to mutate it, so i
> need to recreate it, and so on up to node 1.

yes, that's true

> Now in this exemple, it's ok since that's a regular tree and the process
> can be automated, but when each node has a different type, it can become
> quite hairy.

may be all that you need is structure update syntax?

data Planet = Planet { age :: Double
 , weight :: Double
 .
 }

updatePlanet p = p {age=(age p)*2}

the same applies to updating nested structures. you just return
updated structure on each level of processing

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex



Donald Bruce Stewart wrote:

Phlex:
  
On the other side, using the functional paradigm, it seems to me that 
the function i use in order to create a _new_ inhabitant with a 
different age will need to have knowledge of the country over it, the 
planet ..and so on up to the universe...as i need to update all these 
structures to reflect the change. This is pretty bad and most probably 
doesn't need to be like this.


Nope, its not done like that. You share as much of the original
structure as you can, as a general principle.

Imagine updating a node in a tree by just detaching and reattaching a
pointer.

[1] [1]
/ \ / \
  [2] [3] update node 5   [2] [3] 
   / \ with value 7   / \

 [4] [5] [4] *

and share the rest of the structure. Since the rest isn't mutable
anyway, you can share all over.

-- Don


That's precisely the thing i don't understand.
In order to update node 3 with a new pointer, i need to mutate it, so i 
need to recreate it, and so on up to node 1.


Now in this exemple, it's ok since that's a regular tree and the process 
can be automated, but when each node has a different type, it can become 
quite hairy.


Sacha

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


Re: [Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Donald Bruce Stewart
Phlex:
> Hello all,
> 
> I'm coming from the OO world, and there's something i don't quite 
> understand in the way haskellers manipulate data (as all functional 
> programmers i guess).
> 
> Let's say i have a deep nested data structure.
> Universe containing galaxies, containing solar systems, containing 
> planets, containing countries, containing inhabitants, containing 
> ...whatever.
> 
> Using the OO paradigm, once i get a reference to an inhabitant, i can 
> update it quite easily (say by changing it's age), and that's the end of it.
> 
> On the other side, using the functional paradigm, it seems to me that 
> the function i use in order to create a _new_ inhabitant with a 
> different age will need to have knowledge of the country over it, the 
> planet ..and so on up to the universe...as i need to update all these 
> structures to reflect the change. This is pretty bad and most probably 
> doesn't need to be like this.
> 
> So here I am hoping for you all to give me some pointers on how this is 
> done "the functional way".
> 

Nope, its not done like that. You share as much of the original
structure as you can, as a general principle.

Imagine updating a node in a tree by just detaching and reattaching a
pointer.

[1] [1]
/ \ / \
  [2] [3] update node 5   [2] [3] 
   / \ with value 7   / \
 [4] [5] [4] *

and share the rest of the structure. Since the rest isn't mutable
anyway, you can share all over.

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


[Haskell-cafe] I just don't get it (data structures and OO)

2007-06-03 Thread Phlex

Hello all,

I'm coming from the OO world, and there's something i don't quite 
understand in the way haskellers manipulate data (as all functional 
programmers i guess).


Let's say i have a deep nested data structure.
Universe containing galaxies, containing solar systems, containing 
planets, containing countries, containing inhabitants, containing 
...whatever.


Using the OO paradigm, once i get a reference to an inhabitant, i can 
update it quite easily (say by changing it's age), and that's the end of it.


On the other side, using the functional paradigm, it seems to me that 
the function i use in order to create a _new_ inhabitant with a 
different age will need to have knowledge of the country over it, the 
planet ..and so on up to the universe...as i need to update all these 
structures to reflect the change. This is pretty bad and most probably 
doesn't need to be like this.


So here I am hoping for you all to give me some pointers on how this is 
done "the functional way".


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