Send Beginners mailing list submissions to
        beginners@haskell.org

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
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

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


Today's Topics:

   1.  First code review (Emanuel Koczwara)
   2. Re:  Beginners Digest, Vol 56, Issue 33 (Kim-Ee Yeoh)
   3.  GHC warnings (Emanuel Koczwara)
   4. Re:  GHC warnings (Patrick Mylund Nielsen)
   5. Re:  First code review (Brent Yorgey)
   6. Re:  First code review (Emanuel Koczwara)
   7. Re:  First code review (Brent Yorgey)


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

Message: 1
Date: Sat, 23 Feb 2013 16:39:53 +0100
From: Emanuel Koczwara <poc...@emanuelkoczwara.pl>
Subject: [Haskell-beginners] First code review
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID: <1361633993.3205.15.camel@emanuel-Dell-System-Vostro-3750>
Content-Type: text/plain; charset="UTF-8"

Hi,

Note: Following code is a solution for a problem from hackerrank.com
(Category: Artifical Intelligence / Single Player Games / Bot saves
princess).

Here is my first Haskell code! Short explanation of the problem: it's
standard path finding problem, we have a matrix where 'm' denotes the
bot, 'p' denotes the princess and '-' is for empty space.

Sample input (grid size followed by the grid itself, where each row is
separated by new line):

3
---
-m-
p--

Sample output:

DOWN
LEFT

Here is the code:

module Main where

import Data.List
import Data.Maybe

type Size = Int

type Grid = [String]

type Path = [Move]

type Heuristic = [[Int]]

type Position = (Int,Int)

data Move = LEFT | RIGHT | UP | DOWN deriving Show

getSize :: IO Size
getSize = readLn

getGrid :: Size -> IO Grid
getGrid s = sequence $ replicate s getLine

getHeuristic :: Size -> Position -> Heuristic
getHeuristic s p = map (getHeuristic' s p) [0..s-1]

getHeuristic' :: Size -> Position -> Int -> [Int]
getHeuristic' s p y = map (getHeuristic'' p y) [0..s-1]

getHeuristic'' :: Position -> Int -> Int -> Int
getHeuristic'' (x2, y2) y1 x1 = abs (x1 - x2) + (abs (y1 - y2))

getPos :: Char -> Size -> Grid -> Position
getPos c s g = (i `mod` s, i `div` s)
  where g' = concat g
        i = fromJust $ elemIndex c g'

getSteps :: Size -> Heuristic -> Position -> Position -> Path
getSteps s h b p | b == p = []
                 | otherwise = let (m,b') = getStep s h b 
                               in m : (getSteps s h b' p)

getStep :: Size -> Heuristic -> Position -> (Move,Position)
getStep s h b = head $ sortBy compareCost (getAvailableSteps s h b)
  where compareCost (_,(x1,y1)) (_,(x2,y2)) = 
          compare (h !! y1 !! x1) (h !! y2 !! x2)

getAvailableSteps :: Size -> Heuristic -> Position -> [(Move,Position)]
getAvailableSteps s h (x,y) = up ++ down ++ left ++ right
  where up = if y > 0 then [(UP, (x, y - 1))] else []
        down = if y < (s - 1) then [(DOWN, (x, y + 1))] else []
        left = if x > 0 then [(LEFT, (x - 1, y))] else []
        right = if x < (s - 1) then [(RIGHT, (x + 1, y))] else []

main :: IO ()
main = do
  size <- getSize
  grid <- getGrid size
  let botPos = getPos 'm' size grid
      princessPos = getPos 'p' size grid
      heuristic = getHeuristic size princessPos
      result = getSteps size heuristic botPos princessPos
  mapM_ print result

Please point out all my mistakes.

Emanuel





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

Message: 2
Date: Sat, 23 Feb 2013 22:58:55 +0700
From: Kim-Ee Yeoh <k...@atamo.com>
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 56, Issue 33
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <CAPY+ZdRcxk7pX4V9O8a2H=gxpe-r5efx9hmpm2tafngxywf...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Sat, Feb 23, 2013 at 7:27 AM, xiao Ling <lingx...@seas.upenn.edu> wrote:

>  How do you define a function of signature h :: M Int -> M Int -> M Int
>  so that h ( M x ) ( M y ) = M ( x + y ), but without unwrapping the  value
> from the monad?
>
>  In addition to the fine points that Brent and Brandon have already made,
I observe that there seems to be a reservation about "unwrapping the value
from the monad", which I don't get.

Your code is equivalent to h = \mx my -> do { x <- mx; y <- my; return $
x+y; }, which, I suspect, doesn't go well with you because of the
"unwrapping".

Or are you aiming at syntactic compositionality, i.e. point-free style?

Once you've hacked Haskell enough, you just reach for the liftM2 combinator
and write h = liftM2 (+).

-- Kim-Ee
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130223/01298f51/attachment-0001.htm>

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

Message: 3
Date: Sat, 23 Feb 2013 22:25:35 +0100
From: Emanuel Koczwara <poc...@emanuelkoczwara.pl>
Subject: [Haskell-beginners] GHC warnings
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID: <1361654735.3205.19.camel@emanuel-Dell-System-Vostro-3750>
Content-Type: text/plain; charset="UTF-8"

Hi,

  Why GHC doesn't tell me such things like hpaste? (example here:
http://hpaste.org/82917)
  
27:12: Error: Use replicateM
Found:
  sequence $ replicate gridSize getLine
Why not:
  Control.Monad.replicateM gridSize getLine


50:14: Warning: Use list comprehension
Found:
  if y > 0 then [(UP, (x, y - 1))] else []
Why not:
  [(UP, (x, y - 1)) | y > 0]


81:1: Error: Eta reduce
Found:
  sortByPathCost p ps = sortBy compareHeuristic ps
Why not:
  sortByPathCost p = sortBy compareHeuristic


  Can I enable this kind of verbosity in GHC somehow?

Emanuel





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

Message: 4
Date: Sat, 23 Feb 2013 22:29:58 +0100
From: Patrick Mylund Nielsen <hask...@patrickmylund.com>
Subject: Re: [Haskell-beginners] GHC warnings
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID:
        <caew2jfx-pb3g+-nmgjndyvsdfoiskupdpbkvutrndlsylxe...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

It's hlint: http://community.haskell.org/~ndm/hlint/

e.g.:

# sudo apt-get install hlint
# hlint src

(where src is the folder containing Haskell files)

or

# hlint src --report

to generate an HTML report.


On Sat, Feb 23, 2013 at 10:25 PM, Emanuel Koczwara <
poc...@emanuelkoczwara.pl> wrote:

> Hi,
>
>   Why GHC doesn't tell me such things like hpaste? (example here:
> http://hpaste.org/82917)
>
> 27:12: Error: Use replicateM
> Found:
>   sequence $ replicate gridSize getLine
> Why not:
>   Control.Monad.replicateM gridSize getLine
>
>
> 50:14: Warning: Use list comprehension
> Found:
>   if y > 0 then [(UP, (x, y - 1))] else []
> Why not:
>   [(UP, (x, y - 1)) | y > 0]
>
>
> 81:1: Error: Eta reduce
> Found:
>   sortByPathCost p ps = sortBy compareHeuristic ps
> Why not:
>   sortByPathCost p = sortBy compareHeuristic
>
>
>   Can I enable this kind of verbosity in GHC somehow?
>
> Emanuel
>
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20130223/2bd05cb9/attachment-0001.htm>

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

Message: 5
Date: Sat, 23 Feb 2013 17:35:26 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] First code review
To: beginners@haskell.org
Message-ID: <20130223223526.ga32...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sat, Feb 23, 2013 at 04:39:53PM +0100, Emanuel Koczwara wrote:
> Hi,
> 
> Note: Following code is a solution for a problem from hackerrank.com
> (Category: Artifical Intelligence / Single Player Games / Bot saves
> princess).

Looks pretty good overall.  One note is that using lists of lists for
Grid and Heuristic will be slow, especially Heuristic since you do
lots of repeated lookups.  For small grids it really doesn't make much
difference, but if you wanted to run it on larger grids you might
notice.  Since both the Grid and Heuristic values are created once and
then used in a read-only fasion, this is a perfect opportunity to use
arrays: see 

  
http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array.html

Using read-only arrays is really quite simple (as opposed to
read/write arrays which require a monad of some sort).

-Brent

> 
> Here is my first Haskell code! Short explanation of the problem: it's
> standard path finding problem, we have a matrix where 'm' denotes the
> bot, 'p' denotes the princess and '-' is for empty space.
> 
> Sample input (grid size followed by the grid itself, where each row is
> separated by new line):
> 
> 3
> ---
> -m-
> p--
> 
> Sample output:
> 
> DOWN
> LEFT
> 
> Here is the code:
> 
> module Main where
> 
> import Data.List
> import Data.Maybe
> 
> type Size = Int
> 
> type Grid = [String]
> 
> type Path = [Move]
> 
> type Heuristic = [[Int]]
> 
> type Position = (Int,Int)
> 
> data Move = LEFT | RIGHT | UP | DOWN deriving Show
> 
> getSize :: IO Size
> getSize = readLn
> 
> getGrid :: Size -> IO Grid
> getGrid s = sequence $ replicate s getLine
> 
> getHeuristic :: Size -> Position -> Heuristic
> getHeuristic s p = map (getHeuristic' s p) [0..s-1]
> 
> getHeuristic' :: Size -> Position -> Int -> [Int]
> getHeuristic' s p y = map (getHeuristic'' p y) [0..s-1]
> 
> getHeuristic'' :: Position -> Int -> Int -> Int
> getHeuristic'' (x2, y2) y1 x1 = abs (x1 - x2) + (abs (y1 - y2))
> 
> getPos :: Char -> Size -> Grid -> Position
> getPos c s g = (i `mod` s, i `div` s)
>   where g' = concat g
>         i = fromJust $ elemIndex c g'
> 
> getSteps :: Size -> Heuristic -> Position -> Position -> Path
> getSteps s h b p | b == p = []
>                  | otherwise = let (m,b') = getStep s h b 
>                                in m : (getSteps s h b' p)
> 
> getStep :: Size -> Heuristic -> Position -> (Move,Position)
> getStep s h b = head $ sortBy compareCost (getAvailableSteps s h b)
>   where compareCost (_,(x1,y1)) (_,(x2,y2)) = 
>           compare (h !! y1 !! x1) (h !! y2 !! x2)
> 
> getAvailableSteps :: Size -> Heuristic -> Position -> [(Move,Position)]
> getAvailableSteps s h (x,y) = up ++ down ++ left ++ right
>   where up = if y > 0 then [(UP, (x, y - 1))] else []
>         down = if y < (s - 1) then [(DOWN, (x, y + 1))] else []
>         left = if x > 0 then [(LEFT, (x - 1, y))] else []
>         right = if x < (s - 1) then [(RIGHT, (x + 1, y))] else []
> 
> main :: IO ()
> main = do
>   size <- getSize
>   grid <- getGrid size
>   let botPos = getPos 'm' size grid
>       princessPos = getPos 'p' size grid
>       heuristic = getHeuristic size princessPos
>       result = getSteps size heuristic botPos princessPos
>   mapM_ print result
> 
> Please point out all my mistakes.
> 
> Emanuel
> 
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 6
Date: Sun, 24 Feb 2013 00:15:05 +0100
From: Emanuel Koczwara <poc...@emanuelkoczwara.pl>
Subject: Re: [Haskell-beginners] First code review
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Message-ID: <1361661305.3205.24.camel@emanuel-Dell-System-Vostro-3750>
Content-Type: text/plain; charset="UTF-8"

Hi,

Dnia 2013-02-23, sob o godzinie 17:35 -0500, Brent Yorgey pisze:
> On Sat, Feb 23, 2013 at 04:39:53PM +0100, Emanuel Koczwara wrote:
> > Hi,
> > 
> > Note: Following code is a solution for a problem from hackerrank.com
> > (Category: Artifical Intelligence / Single Player Games / Bot saves
> > princess).
> 
> Looks pretty good overall.  One note is that using lists of lists for
> Grid and Heuristic will be slow, especially Heuristic since you do
> lots of repeated lookups.  For small grids it really doesn't make much
> difference, but if you wanted to run it on larger grids you might
> notice.  Since both the Grid and Heuristic values are created once and
> then used in a read-only fasion, this is a perfect opportunity to use
> arrays: see 
> 
>   
> http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array.html
> 
> Using read-only arrays is really quite simple (as opposed to
> read/write arrays which require a monad of some sort).
> 

  Thank you, I will try Arrays. Handling list of lists is very hard for
me. Please look at this code: http://hpaste.org/82925 (indexedGrid and
getDirty). In C/C++ it's very natural for me, here it looks like i'm
missing something.

Emanuel





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

Message: 7
Date: Sat, 23 Feb 2013 19:27:13 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] First code review
To: beginners@haskell.org
Message-ID: <20130224002713.ga16...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Sun, Feb 24, 2013 at 12:15:05AM +0100, Emanuel Koczwara wrote:
> Hi,
> 
> Dnia 2013-02-23, sob o godzinie 17:35 -0500, Brent Yorgey pisze:
> > On Sat, Feb 23, 2013 at 04:39:53PM +0100, Emanuel Koczwara wrote:
> > > Hi,
> > > 
> > > Note: Following code is a solution for a problem from hackerrank.com
> > > (Category: Artifical Intelligence / Single Player Games / Bot saves
> > > princess).
> > 
> > Looks pretty good overall.  One note is that using lists of lists for
> > Grid and Heuristic will be slow, especially Heuristic since you do
> > lots of repeated lookups.  For small grids it really doesn't make much
> > difference, but if you wanted to run it on larger grids you might
> > notice.  Since both the Grid and Heuristic values are created once and
> > then used in a read-only fasion, this is a perfect opportunity to use
> > arrays: see 
> > 
> >   
> > http://hackage.haskell.org/packages/archive/array/latest/doc/html/Data-Array.html
> > 
> > Using read-only arrays is really quite simple (as opposed to
> > read/write arrays which require a monad of some sort).
> > 
> 
>   Thank you, I will try Arrays. Handling list of lists is very hard for
> me. Please look at this code: http://hpaste.org/82925 (indexedGrid and
> getDirty). In C/C++ it's very natural for me, here it looks like i'm
> missing something.

In C/C++ you get to use arrays with indexing.  Lists are entirely
different, so it's no surprise that something natural in C/C++ should
feel foreign here.  Indeed, I don't think lists are the right data
structure for you to be using.  If you use arrays I think this code
will become much simpler too.

A good rule of thumb is that lists should be primarily used as a
*control structure* (i.e. to describe something that would be done
with a loop in an imperative language).  If you find yourself using
lists as a *data structure*, especially a random-access one, you
probably ought to be using something else instead (Data.Sequence,
arrays, ...)

-Brent



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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 56, Issue 39
*****************************************

Reply via email to