Send Beginners mailing list submissions to
        [email protected]

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        [email protected]

You can reach the person managing the list at
        [email protected]

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  List combination function? (Alexander Dunlap)
   2. Re:  Circular programming (Maciej Piechotka)
   3.  A rigid type and a better pattern (Javier M Mora)
   4. Re:  A rigid type and a better pattern (Daniel Fischer)
   5.  Re: Closure (Heinrich Apfelmus)
   6.  Re: Closure (Daniel Bastos)
   7.  Ambigous Types with Haskell Functional Graph     Library
      (Joe Schafer)


----------------------------------------------------------------------

Message: 1
Date: Sat, 15 Aug 2009 17:16:45 -0700
From: Alexander Dunlap <[email protected]>
Subject: Re: [Haskell-beginners] List combination function?
To: Ian Duncan <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset=UTF-8

On Sat, Aug 15, 2009 at 5:12 PM, Ian Duncan<[email protected]> wrote:
> Hello all,
>
> I'm trying to build a function that takes a string such as "123" and gives
> me permutations including permutations with lesser list lengths. I'm not
> sure how to phrase it, but here is what the output could look like:
>
> foo "123" => ["123","213","321","231","312","132", "12", "13", "21", "23",
> "31", "32", "1", "2", "3", ""]
>
> The ordering doesn't matter, and that null list at the end doesn't
> particularly matter, but I don't really know the mathematical phrasing of
> what I'm asking for. I'm trying to build a scrabble helper that can find the
> optimal score given a set of letters to work with.
>
> Thanks for your help,
>
> Ian Duncan
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>

Import Data.List, then the function you want is

concatMap permutations . subsequences

subsequences returns a list of all subsequences of the original list in order.

permutations returns a list of all possible orderings of the list.

concatMap applies permutations to every member of the subsequence list
and then flattens the list down to a single list again.

Hope that helps,
Alex


------------------------------

Message: 2
Date: Sun, 16 Aug 2009 12:14:35 +0200
From: Maciej Piechotka <[email protected]>
Subject: Re: [Haskell-beginners] Circular programming
To: Peter Verswyvelen <[email protected]>
Cc: [email protected]
Message-ID: <1250417675.8044.58.ca...@notebook>
Content-Type: text/plain; charset="us-ascii"

On Sat, 2009-08-15 at 14:27 +0200, Peter Verswyvelen wrote:
> oh and reading first about fix should help too:
> 
> 
> http://en.wikibooks.org/wiki/Haskell/Fix_and_recursion
> 

Thanks. That helped a lot - so it is 'wired'[1] recursion.


[1] for imperative programmers

-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
Url : 
http://www.haskell.org/pipermail/beginners/attachments/20090816/379a2977/attachment-0001.bin

------------------------------

Message: 3
Date: Sun, 16 Aug 2009 14:04:10 +0200
From: Javier M Mora <[email protected]>
Subject: [Haskell-beginners] A rigid type and a better pattern
To: [email protected]
Message-ID:
        <[email protected]>
Content-Type: text/plain; charset=ISO-8859-1

(I had problems sending this email and I don't know if earlier arrived
to  mail list. I'm going to send again. Sorry if you get it duplicate)



Hi All, this is my first email to beginners list. I'm ending my Master
Degree in Robotics (in Spain). One of my assignment is about Motion
Planning and I thought solve with Haskell. This is my problem:

* Every robot has a local state. I can get the position of the robot
from the state. The state can be rect coords or polar coords or distance
moved on a fixed path or whatever.

* I have a global state witch keep the local state of each robot.

* Every state has a different system to action over it. So, in distance
over fixed path we can "stop" or "go". In polar coords we can increase
and decrease the radius and phi. And in rect coords we can move in x and
y direction

* I have several robots at same time. But every robot has the same state
and the same action. So, all robots in the run of my program has same
local state and action.

So, I split the algorithm in a common part (used in all states and
actions) and other for each specific state-action.

This is the structure (abstract):
     class Robot a where
     ...

     class State a where
       getpos a -> [Position]
     ...

     class Action a where
     ...

later I have instances for concrete cases. In phase 1, local state is a
Int for each robot and action is a Bool (stop or run).

     data State1 = State1 [Int]
     instance State State1 where
       getpos (State1 a) = ...
     ...

     data Action1 = Action1 [Bool]
     instance Action Action1 where
     ...


I have a function "newstate" to calculate the new state from an old
state and the action. This is the type signature:

     newstate:: (State a,Action b) => a -> b -> a

and my instantiation in phase 1 is

     newstate (State1 s) (Action1 u) = State1 $
          zipWith (\x y -> if y then succ x else x) s u

I want to use polymorphism in newstation because I need use
    newstate (State2 s) (Action2 u)
in the future (phase 2) so I tried include newstate in a typeclass.

But if I write:

  class State a where
    newstate:: (Action b)=> a -> b -> a
    ...

or

  class Action a where
    newstate:: (State b) => b -> a -> b
    ...

(and move newstate definition to correct instance block)

I get similar errors in both cases: (this is the first case):

    Couldn't match expected type `b' against inferred type `Action1'
      `b' is a rigid type variable bound by
          the type signature for `newstate' at Tipos.hs:17:24
    In the pattern: Action1 u
    In the definition of `newstate':
        newstate (State1 s) (Action1 u)
                      = State1 $ zipWith (\ x y -> if y then succ x
else x) s u
    In the instance declaration for `State State1'


My questions:

* How can I fix this error?

* the point is associate every instance of Robot with one instance of
State and with one instance of Action. So when I select the Robot I'm
goint to use I get "automagically" the correct instances of newstate and
others.

Is there a pattern to this behaviour?

My ideal is associate every function related with a Robot with a general
typeclass "Robot" (I don't tested this) :

  class Robot a where
    initstate:: (State a) => a
    newstate:: (State a,Action b) => a-> b-> a

And the instance:

  instance Robot Robot1 where
    initstate = State1 [0,0,0]
    newstate (State1 a) (Action1 b) = ...

and

  instance Robot Robot2 where
    initstate = State2 [(0,0),(1,1),(2,2)] -- i.e.
    newstate (State2 a) (Action2 b) = ...

and so on.

But I think It can't work because neither initstate or newstate use Robot1.

Any tips?





Javier M Mora.


------------------------------

Message: 4
Date: Sun, 16 Aug 2009 15:42:44 +0200
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] A rigid type and a better pattern
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain;  charset="iso-8859-1"

Am Sonntag 16 August 2009 14:04:10 schrieb Javier M Mora:
> (I had problems sending this email and I don't know if earlier arrived
> to  mail list. I'm going to send again. Sorry if you get it duplicate)
>
>
>
> Hi All, this is my first email to beginners list. I'm ending my Master
> Degree in Robotics (in Spain). One of my assignment is about Motion
> Planning and I thought solve with Haskell. This is my problem:
>
> * Every robot has a local state. I can get the position of the robot
> from the state. The state can be rect coords or polar coords or distance
> moved on a fixed path or whatever.
>
> * I have a global state witch keep the local state of each robot.
>
> * Every state has a different system to action over it. So, in distance
> over fixed path we can "stop" or "go". In polar coords we can increase
> and decrease the radius and phi. And in rect coords we can move in x and
> y direction
>
> * I have several robots at same time. But every robot has the same state
> and the same action. So, all robots in the run of my program has same
> local state and action.
>
> So, I split the algorithm in a common part (used in all states and
> actions) and other for each specific state-action.
>
> This is the structure (abstract):
>      class Robot a where
>      ...
>
>      class State a where
>        getpos a -> [Position]
>      ...
>
>      class Action a where
>      ...
>
> later I have instances for concrete cases. In phase 1, local state is a
> Int for each robot and action is a Bool (stop or run).
>
>      data State1 = State1 [Int]
>      instance State State1 where
>        getpos (State1 a) = ...
>      ...
>
>      data Action1 = Action1 [Bool]
>      instance Action Action1 where
>      ...
>
>
> I have a function "newstate" to calculate the new state from an old
> state and the action. This is the type signature:
>
>      newstate:: (State a,Action b) => a -> b -> a
>
> and my instantiation in phase 1 is
>
>      newstate (State1 s) (Action1 u) = State1 $
>           zipWith (\x y -> if y then succ x else x) s u
>
> I want to use polymorphism in newstation because I need use
>     newstate (State2 s) (Action2 u)
> in the future (phase 2) so I tried include newstate in a typeclass.
>
> But if I write:
>
>   class State a where
>     newstate:: (Action b)=> a -> b -> a
>     ...
>
> or
>
>   class Action a where
>     newstate:: (State b) => b -> a -> b
>     ...
>
> (and move newstate definition to correct instance block)
>
> I get similar errors in both cases: (this is the first case):
>
>     Couldn't match expected type `b' against inferred type `Action1'
>       `b' is a rigid type variable bound by
>           the type signature for `newstate' at Tipos.hs:17:24
>     In the pattern: Action1 u
>     In the definition of `newstate':
>         newstate (State1 s) (Action1 u)
>                       = State1 $ zipWith (\ x y -> if y then succ x
> else x) s u
>     In the instance declaration for `State State1'
>

Yes. The above signatures promise that newstate will work given any pair of 
arguments 
whose types belong to classes State and action respectively, so in the 
definition you 
can't pattern match on constructors since you have to be polymorphic.

You can make it one multi-parameter type class

{-# LANGUAGE MultiParamTypeClasses #-}

class ActState a s where
    newstate :: s -> a -> s

instance ActState Action1 State1 where
    newstate (State1 s) (Action1 u) = ...

>From the above I have the impression that each action type only works on one 
>state type 
and each state type has only one action type that works for it, thus you could 
use 
functional dependencies or data families to aid resolution of instances. Since 
Robots are 
associated with States and Actions (presumably again in a 1-1 correspondence), 
it makes 
sense to tie them into it.

With functional dependencies:

{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}

class ActState a s | a -> s, s -> a where
    newstate :: s -> a -> s

instance ActState Action1 State1 where
    newstate (State1 s) (Action1 u) = ...

class (ActState a s) => Robot r s a | r -> s, r -> a, s -> r, s-> a, a -> r, a 
-> s where
    ...

instance Robot Robot1 State1 Action1 where
    ...

(or leave out the ActState class and have it all in class Robot)

With type Families:
{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}

class Rob2 r where
    data St r
    data Ac r
    initstate :: St r
    newstate :: St r -> Ac r -> St r


instance Rob2 Robot1 where
    data St Robot1 = State2 [Int] deriving Show
    data Ac Robot1 = Action2 [Bool] deriving Show
    initstate2 = State2 [0,0,0]
    newstate2 (State2 xs) (Action2 gs) = 
                State2 $ zipWith (\x g -> if g then succ x else x) xs gs

or, moving the families outside the class:

data family St3 r
data family Ac3 r

data instance St3 Robot1 = State3 [Int] deriving Show
data instance Ac3 Robot1 = Action3 [Bool] deriving Show

class Rob3 r where
    initstate3 :: St3 r
    newstate3 :: St3 r -> Ac3 r -> St3 r

instance Rob3 Robot1 where
    initstate3 = State3 [0,0,0]
    newstate3 (State3 xs) (Action3 gs) = 
                State3 $ zipWith (\x g -> if g then succ x else x) xs gs

>
> My questions:
>
> * How can I fix this error?
>
> * the point is associate every instance of Robot with one instance of
> State and with one instance of Action. So when I select the Robot I'm
> goint to use I get "automagically" the correct instances of newstate and
> others.
>
> Is there a pattern to this behaviour?

Functional dependencies/Type families.
Or you could use parameterized types.

data Distance = Distance Double
data Polar = Polar Double Double
data Cartesian = Cartesian Int Int

data Action a = Action [a -> a]
data State a = State [a]
data Robot a = Robot ???

class Robot a where
    initstate :: State a
    newstate :: State a -> Action a -> State a

instance Robot Distance where ...
instance Robot Polar where ...
instance Robot Cartesian where ...

>
> My ideal is associate every function related with a Robot with a general
> typeclass "Robot" (I don't tested this) :
>
>   class Robot a where
>     initstate:: (State a) => a
>     newstate:: (State a,Action b) => a-> b-> a
>
> And the instance:
>
>   instance Robot Robot1 where
>     initstate = State1 [0,0,0]
>     newstate (State1 a) (Action1 b) = ...
>
> and
>
>   instance Robot Robot2 where
>     initstate = State2 [(0,0),(1,1),(2,2)] -- i.e.
>     newstate (State2 a) (Action2 b) = ...
>
> and so on.
>
> But I think It can't work because neither initstate or newstate use Robot1.
>
> Any tips?
>
>
>
>
>
> Javier M Mora.



------------------------------

Message: 5
Date: Sun, 16 Aug 2009 15:58:33 +0200
From: Heinrich Apfelmus <[email protected]>
Subject: [Haskell-beginners] Re: Closure
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=ISO-8859-15

Daniel Bastos wrote:
> Heinrich Apfelmus wrote:
> 
>> The simplest example of a closure is indeed
>>
>>    foo = add 3
>>
>> where
>>
>>    add = \x y -> x + y
> 
> Question. This is actually equal to 
> 
> add x y = x + y
> 
> But you wrote in terms of \. Why such preference?

I wanted to emphasize that  add  is a value just like  4  or  "baz" ,
i.e. that it's not very different from writing say

    add = "baz"

>> Note that closures are an implementation detail. From a semantic point
>> of view,  add 3  can readily be understood as an ordinary function.
> 
> This makes sense. Because, even in a language like C, a similar effect
> can be achieved, no? For example
> 
> int plus(int x, int y) { return x + y; }
> 
> int plus3(int y) { plus(3, y); }
> 
> So, what I can't do in C, besides almost everything I can't do, is to
> do this nicely like I do in Haskell. But we don't call this a
> closure. In fact, we say C does not allow for closures. So what am I
> missing?

A litmus test for being a functional language is the ability to define
function composition

   f . g = \x -> f (g x)

This is not possible in C; mainly because functions cannot be defined
locally, they have to be declared at the top-level.

(I think this test is due to Lennart Augustsson, but I can't find a
reference on the web right now.)


Hm... this means that Brent's example

   foo x = add
       where
       add y = x + y

is actually a much better demonstration of a closure than the one I
gave. Yes, I think this one is impossible to write in C.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



------------------------------

Message: 6
Date: Sun, 16 Aug 2009 16:12:38 +0000 (UTC)
From: Daniel Bastos <[email protected]>
Subject: [Haskell-beginners] Re: Closure
To: [email protected]
Message-ID: <[email protected]>

In article <[email protected]>,
Daniel Fischer wrote:

>> [Does] Haskell allow me to define a function at run time? I know
>> Lisp can, since a function is just a data structure which we can
>> put together at run time. But how about Haskell?

[...]

> If you write a good parser, you can also
>
> do  putStrLn "Please enter function code:"
>     code <- getLine
>     let fun = parseFunction code
>     use fun   -- may segfault if the entered code isn't good
>
> In which (other) ways can you construct functions at run time in Lisp?

None. I guess the only difference, if so considered, is that since
Lisp is so much syntactically simpler, it's easy to write a parser for
it, and I guess most implementations already bring one for ya. And
that's nice. It allows for the code that write code, which sounds
great. But anyway, my interest here was understanding Haskell better,
which I now do. Thanks for all inputs in this subthread.



------------------------------

Message: 7
Date: Sun, 16 Aug 2009 21:16:54 -0400
From: Joe Schafer <[email protected]>
Subject: [Haskell-beginners] Ambigous Types with Haskell Functional
        Graph   Library
To: [email protected]
Message-ID: <[email protected]>
Content-Type: text/plain; charset=us-ascii

Hey all,

New to Haskell and I'm trying to use the FGL but I keep running into the
same error.

If I load Data.Graph.Inductive.Example and use one of the example
functions such as ucycle I get:

    Ambiguous type variable `gr' in the constraint:
      `Graph gr' arising from a use of `ucycle' at <interactive>:1:0-7
    Probable fix: add a type signature that fixes these type variable(s)

Here's the type of ucycle for reference.

ucycle :: Graph gr => Int -> gr () ()

I'm using GHC 6.10.1 and FGL 5.4.2.2

Thanks,
Joe



------------------------------

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 14, Issue 10
*****************************************

Reply via email to