You are expected to use my code fragments for *ideas*,
not to incorporate them *literally* in your code.  As
I explained, *without seeing the specification*, I have
no way to tell whether the specification uses a left-handed
or right-handed coordinate system.

For what it's worth, here's a complete program in my
Smalltalk dialect.  It doesn't plug into the exercism
testing framework because I can do not know what it
looks like.  But if it makes the code more complicated
that this, it's doing it wrong.

require: 'geometry.st'  "Point"
require: 'print.st'     "OutputStream>>print:"

Object subclass: #Robot
  instanceVariableNames: 'position direction'
  poolDirectionaries:    'FileStream'

  methods for: 'initialising'
    pvtPostNew
      position  := 0@0.
      direction := 1@0.

  methods for: 'accessing'
    direction
      ^direction copy

    location
      ^location copy

    obey: commands
      commands do: [:each |
        each caseOf: {
          [$A] -> [position  := position  + direction].
          [$L] -> [direction := direction leftRotated].
          [$R] -> [direction := direction rightRotated]
        }].

  class methods for: 'main'
    start
      [StdIn atEnd] whileFalse: [
         |robot|
         robot := Robot new.
         Robot obey: StdIn nextLine.
         StdOut print: Robot location; cr].

On Tue, 9 Apr 2019 at 02:58, Roelof Wobben <r.wob...@home.nl> wrote:

> yes,  this is a real  tests from the pharo track on exercism.io
>
> I understand what you mean but maybe I overthinking things.
> But if we have a robot facing north and the robot turns to the left  , im
> my oponion it faces now to the east.
>
> like this test is saying :
>
>
> test04_RotatesTheRobotsDirection90DegreesClockwiseChangesTheDirectionFromEastToSouth
>     | result |
>     result := robotSimulatorCalculator
>         moveDirection: 'east'
>         position:
>             (Dictionary new
>                 add: 'x' -> 0;
>                 add: 'y' -> 0;
>                 yourself)
>         instructions: 'R'.
>     self
>         assert: result
>         equals:
>             (Dictionary new
>                 add: 'direction' -> 'south';
>                 add:
>                     'position'
>                         ->
>                             (Dictionary new
>                                 add: 'x' -> 0;
>                                 add: 'y' -> 0;
>                                 yourself);
>                 yourself)
>
>
> but I cannot come to the same outcome with this code :
>
>
> pointToName: aPoint
>   ^aPoint x isZero
>      ifTrue:  [aPoint y > 0 ifTrue: [#north] ifFalse: [#south]]
>      ifFalse: [aPoint x > 0 ifTrue: [#west ] ifFalse: [#east ]]
>
>
> maybe exercism.io is not a good way to practice and learn smalltalk but I
> found not a better one. or smalltalk is not for me.
>
> Roelof
>
>
>
>
>
>
>
>
>
>
>
> Op 8-4-2019 om 16:44 schreef Richard O'Keefe:
>
> The basic issue here is abstraction.
> An instance of "Robot" in your program is not a
> physical object.  How could it possibly point North,
> South, or Nor-nor-west?  It cannot.
> Its location and direction are abstract values
> *metaphorically* related to real world notions
> like position vectors and velocity vectors.
> "North" in this program is not a real thing,
> it is an *idea* which could be represented by
> 'North', 'north', #North, #north, $N, $n,
> 'Raki',  'raki',  #Raki,  #raki,  $R, $r,
> 137, (0@ -1), a picture of the star Polaris,
> the colour red (the conventional colour for
> that end of a compass needle which points north),
> a sound recording of a lecture by Alfred North
> Whitehead, or anything you please, as long as,
> inside the program, it *acts* the way *you* want
> "north" to act (which is not necessarily the way
> the physical direction North acts, and in fact in
> this case it most certainly is not).
>
> Locations and movements in a 2D space are, in Smalltalk,
> commonly represented by Points.  "Represented by."
>
> As for this method:
>
>
> test11_MovesTheRobotForward1SpaceInTheDirectionItIsPointingIncreasesTheYCoordinateOneWhenFacingNorth
>     | result |
>     result := robotSimulatorCalculator
>         moveDirection: 'north'
>         position:
>             (Dictionary new
>                 add: 'x' -> 0;
>                 add: 'y' -> 0;
>                 yourself)
>         instructions: 'A'.
>     self
>         assert: result
>         equals:
>             (Dictionary new
>                 add: 'direction' -> 'north';
>                 add:
>                     'position'
>                         ->
>                             (Dictionary new
>                                 add: 'x' -> 0;
>                                 add: 'y' -> 1;
>                                 yourself);
>                 yourself)
>
> PLEASE tell me that is not what they are actually using.
> Let's start with
>   (Dictionary new)
>      add: k1 -> v1;
>      ...
>      add: kn -> vn;
>      yourself
> Did you know that sending #add: to a dictionary is not
> portable?  Storing actual Association objects inside
> Dictionaries was originally an encapsulation error and
> remains a performance error, so there are Smalltalks
> that do not make that mistake.  The *portable* way to
> make a Dictionary is
>     (Dictionary new)
>        at: k1 put: v1;
>        ...
>        at: kn put: vn;
>        yourself.
>
> And why in the name of sanity are the keys *strings*
> instead of *symbols*?  This is not Smalltalk.  It is
> Javascript in drag.
>
> Now exercism.io has a habit of insisting on particular
> implementations.  For example, I completed the SML track,
> and found that the test code ONLY worked with Poly and
> not with any of the three SML implementations I already
> had on my machine.  Since you are doing this in Pharo,
> I take it that exercism.io will insist on the Smalltalk
> track being done in Pharo, and in that case it is
> *nauseating* to use a Dictionary when you could use a
> Point.  Old-fashioned Smalltalk style would have been
> to return something like
>    #(<direction> <x> <y>)
> e.g. #(north 1 0), and I still prefer that.
>
> In fact *good* Smalltalk style for something like this
> would be
>
> test11_MovesTheRobotForward1SpaceInTheDirectionItIsPointingIncreasesTheYCoordinateOneWhenFacingNorth
>   robotSimulatorCalculator
>     moveTo: 0@0;
>     head: #north;
>     obey: 'A'.
>   self assert: robotSimulatorCalculator heading equals: #north.
>   self assert: robotSimulatorCalculator location equals: 0@1.
>
> -- We're starting to get the idea that identifiers like
> robotSimulatorCalculator are not a very good idea when
> simulatedRobot would do the job as well or better.
>
> (This is also pointing us towards Betrand Meyer's
> Command/Query Separation principle, but we shan't
> go there today.)
>
> This is important feedback to give to the exercism.io
> people.  The test code should use a SMALLTALK interface,
> not a warmed-over JAVASCRIPT interface.
>
> Now, how do we map between direction *names* and
> direction *points*?  Well, we have to start by
> laying down clearly what we *mean* by the directions.
>
> To move North one step is to add 1 to y and 0 to x.
> (We know that from the appalling test case above.)
> To move South one step is to add -1 to y and 0 to x.
> (South is the opposite of North.)
> To move East one step, oh we have a problem.
> THIS NEEDS SPELLING OUT.  And one of the things the
> exercism.io exercises are HORRIBLY BAD AT is specifying
> the problem.  Nearly every single exercise I have tried,
> I have been unable to tell what the problem is without
> examining the test cases, and that is not the way
> exercises are supposed to work.  (Yeah, that's why I'm
> screaming about it.  I've taught a class using exercises
> like this that were not of my writing and vague specifications
> really upset the students.  People who had taken the class
> under someone else several years before were still angry
> about it.)
>
> The geometric classes in Smalltalk were written to support
> graphic user interfaces.  And in user interfaces, the y
> coordinate increases DOWN.  So if we take the compass rose
> and rotate it so that North is DOWN, it follows that
> West is right and East is left.  So
>
> To move East one step is to add -1 to x and 0 to y.
> To move West one step is to add 1 to x and 0 to y.
>
> The chances are excellent that the problem specification
> is inconsistent with this.  Sigh.  Let's proceed, though.
>
> North  0@1
> South  0@ -1
> East   -1@0
> West   1@0
>
>
> pointToName: aPoint
>   ^aPoint x isZero
>      ifTrue:  [aPoint y > 0 ifTrue: [#north] ifFalse: [#south]]
>      ifFalse: [aPoint x > 0 ifTrue: [#west ] ifFalse: [#east ]]
>
> nameToPoint: aSymbol
>   aSymbol = #north ifTrue: [^0 @ 1].
>   aSymbol = #south ifTrue: [^0 @ -1].
>   aSymbol = #west  ifTrue: [^1 @ 0].
>   aSymbol = #east  ifTrue: [^-1 @ 0].
>   aSymbol error: 'not a compass direction in lower case'.
>
> Another problem I had with exercism was a "Space-Age"
> exercise where the README.md capitalised the planet names
> but test_Space-Age.<whatever> insisted on lower case.
> That might well happen here.
>
> Just for grins,
> Dictionary>>
> asPoint
>   ^(self at: 'x') @ (self at: 'y')
>
> Point>>
> asDictionary
>   ^(Dictionary new)
>      at: 'x' put: self x;
>      at: 'y' put: self y;
>      yourself
>
>
>
>
> On Mon, 8 Apr 2019 at 22:15, Roelof Wobben <r.wob...@home.nl> wrote:
>
>> Richard thanks.
>>
>> One thing I do not see direct.
>>
>> you said :
>>
>>
>> A direction could be represented by a pair of integers
>> dx, dy such that |dx|+|dy| = 1.  It could also be
>> represented by a Point with integer components.
>>
>> for me a direction is the direction the robot is facing so something like
>> north or east.
>>
>> the challenge also wants a output like this :
>>
>>
>> test11_MovesTheRobotForward1SpaceInTheDirectionItIsPointingIncreasesTheYCoordinateOneWhenFacingNorth
>>     | result |
>>     result := robotSimulatorCalculator
>>         moveDirection: 'north'
>>         position:
>>             (Dictionary new
>>                 add: 'x' -> 0;
>>                 add: 'y' -> 0;
>>                 yourself)
>>         instructions: 'A'.
>>     self
>>         assert: result
>>         equals:
>>             (Dictionary new
>>                 add: 'direction' -> 'north';
>>                 add:
>>                     'position'
>>                         ->
>>                             (Dictionary new
>>                                 add: 'x' -> 0;
>>                                 add: 'y' -> 1;
>>                                 yourself);
>>                 yourself)
>>
>> so how do I "convert" the point you are using to the text.
>>
>> Or do I misunderstood you somewhere wrong.
>>
>> Roelof
>>
>>
>>
>>
>> Op 8-4-2019 om 10:57 schreef Richard O'Keefe:
>>
>> One thing I have often seen and lamented is students
>> writing excessively complicated code with way too many
>> classes.  There is a huge difference between
>>   "A Robot knows its position and direction."
>> and
>>   "A Robot has-a Position and has-a Direction."
>> The first is the important one.  The second is
>> an over-commitment to too many classses.  For a
>> problem like this, you really really do not want
>> a Direction class, and you certainly have no use
>> for double dispatch.
>>
>> A position can be represented by a pair of integers
>> x, y.  It could also be represented by a Point with
>> integer components.
>>
>> A direction could be represented by a pair of integers
>> dx, dy such that |dx|+|dy| = 1.  It could also be
>> represented by a Point with integer components.
>>
>> For movement, you need to be able to add the direction
>> to the location, which could be simply
>> x := x + dx.  y := y + dy.
>> or it could be
>> position := position + direction.
>> For turning, you need to be able to rotate a direction
>> vector by ninety degrees.  Now it so happens that
>> Point has methods #leftRotated and #rightRotated.
>>
>> So we can do the following:
>>    a Robot has position (a Point) and direction (aPoint)
>>    position := 0 @ 0.
>>    direction := 0 @ 1.
>> To move forward without turning:
>>    position := position + direction.
>> To turn left without moving:
>>    direction := direction leftRotated.
>> To turn right without moving:
>>    direction := direction rightRotated.
>> To obey a sequence of characters, commands:
>>    commands do: [:each |
>>       each caseOf: {
>>          [$A] -> [--move forward--].
>>          [$L] -> [--turn left--].
>>          [$R] -> [--turn right--]
>>       }].
>>
>>
>> One of the key ideas in extreme programming is
>> "You Ain't Gonna Need It", abbreviated to YAGNI!
>> The idea is *DON'T* generalise beyond your immediate
>> needs.  In this case, for example, the likelihood of
>> *this* program needing to deal with more general
>> kinds of movement is ZERO.  And the only reason for
>> using Point here instead of just using a few simple
>> assignment statements is that Point already exists,
>> so costs nothing to write, and as a familiar class,
>> code using it should be easy to read.
>>
>> If someone challenges you to do something counter-productive,
>> refuse the challenge.
>>
>> On Mon, 8 Apr 2019 at 17:21, Roelof Wobben <r.wob...@home.nl> wrote:
>>
>>> I can try to explain what I trying to solve.
>>>
>>> I have a Robot which can turn left,  turn right or moveForward.
>>>
>>> now I have a string like 'LAR'
>>>
>>> that means the robot needs to turn left (l) , move forward one place (A)
>>> and turn left.
>>> and I have to keep track to which direction the robot is facing and on
>>> which coordinate it stands.
>>>
>>> so to summarize with the above string
>>>
>>> lets say the robot is facing north on coordinate (0,0)
>>> then it has to turn left , so its facing east and still on coordinate
>>> (0,0)
>>> then it has to move forward, so its still  facing east but are on
>>> coordinate(0,1)
>>> then it has to turn right, so its facing north and on coordinate (0,1)
>>>
>>> and TimMacKinnon has challenged me to do this with double dispatch.
>>>
>>> So I think now I need a object Direction, a sub object North and a sub -
>>> sub object TurnLeft, turnRight and moveForward.
>>>
>>> So I can use double dispath first the direction North, East, South, West
>>> and then use double dispatch to find the right move.
>>>
>>> Roelof
>>>
>>>
>>>
>>>
>>>
>>> Op 8-4-2019 om 06:50 schreef Richard O'Keefe:
>>>
>>> It would really REALLY **REALLY** help if we knew what
>>> the heck you were trying to do.  There is an excellent
>>> chance that it is MUCH simpler than you think.  If you
>>> cannot show us the Smalltalk version of the problem,
>>> can you show us the version for some other language?
>>>
>>>
>>> On Sun, 7 Apr 2019 at 20:15, Roelof Wobben <r.wob...@home.nl> wrote:
>>>
>>>> Op 6-4-2019 om 15:15 schreef K K Subbu:
>>>> > On 06/04/19 4:49 PM, Roelof Wobben wrote:
>>>> >> Hello,
>>>> >>
>>>> >> I just learned double dispatch.
>>>> >> And now for the Robot challenge of exercism Tim has pointed me to
>>>> >> this
>>>> >> article(
>>>> https://blog.metaobject.com/2019/04/accessors-have-message-obsession.html)
>>>>
>>>> >>
>>>> >> but I fail to see how the move method looks like in that article.
>>>> >> I had a conversation with Tim in the exercism channel and the way he
>>>> >> explains it, it looks like double dispatch for me.
>>>> >>
>>>> >> Am I on the right track or do I oversee something here.
>>>> > unary methods like moveRight perform specific ops and are not
>>>> > parametric, so only a single dispatch, depending on the receiver, is
>>>> > needed.
>>>> >
>>>> > If you change it to move: aDistanceOrAngle, then performing requests
>>>> > like "move: 3 cms" or "move: 30 degrees" will depend not only on the
>>>> > receiver but also on the class of the argument. This would need
>>>> double
>>>> > dispatch (aka multiple polymorphism). The first dispatch would be
>>>> > based on the receiver and the receiver's method would then dispatch
>>>> it
>>>> > based on the class of the argument (i.e. Distance>>move or
>>>> Angle>>move )
>>>> >
>>>> > HTH .. Subbu
>>>> >
>>>> >
>>>>
>>>>
>>>> hmm, still stuck
>>>>
>>>> I have now a class Direction with as instance variables north, south,
>>>> east, west
>>>> and made the accessors.
>>>>
>>>> then I thought I need a initialize like this :
>>>>
>>>> initialize
>>>>     north = Direction( 0, -1).
>>>>     east  = Direction( 1,  0).
>>>>     south = Direction( 0,  1).
>>>>     west  = Direction(-1,  0).
>>>>
>>>> but the Direction (0,-1)  is a problem . the compiler does not like the
>>>> (0,-1) part
>>>>
>>>> to give you the big picture. I have a Robot which can turnRight ,
>>>> turnLeft and moveForward and I try to understand how the page would
>>>> work
>>>> in my case.
>>>>
>>>> So I have a object Direction as described above and a Object
>>>> MoveForward
>>>> which is a subobject of Direction.
>>>> MoveForward has only 1 method :
>>>>
>>>> IsMove
>>>>     ^  'A'
>>>>
>>>> Roelof
>>>>
>>>>
>>>>
>>>
>>
>

Reply via email to