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. Re:  IO ( stuff ) (Paul Monday)
   2. Re:  Fwd: Averaging a string of numbers (Brent Yorgey)
   3. Re:  Fwd: Averaging a string of numbers (goodman....@gmail.com)
   4.  In Search Of a clue... (Defining and making use  of a type)
      (Allen S. Rout)
   5. Re:  In Search Of a clue... (Defining and making use of a
      type) (David McBride)
   6. Re:  In Search Of a clue... (Defining and making use of a
      type) (Thomas)
   7. Re:  In Search Of a clue... (Defining and making use of a
      type) (Brent Yorgey)


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

Message: 1
Date: Mon, 12 Dec 2011 10:16:37 -0700
From: Paul Monday <paul.mon...@parsci.com>
Subject: Re: [Haskell-beginners] IO ( stuff )
To: beginners@haskell.org
Cc: dmcbr...@neondsl.com
Message-ID: <de5fe573-c21b-4d87-9cae-540c837dd...@parsci.com>
Content-Type: text/plain; charset=windows-1252

Thank you SO much for the discussion.  I've learned quite a bit over the course 
of it.  As one would expect, lifting wasn't my only issue ? I had some rather 
annoying Unbox / Boxed / [] problems with the recursion.

I stepped way back finally this morning to think about the problem and the 
discussion points.  

I was able to make use of laziness with the randomRs function.  randomRs is 
nice since there are no side-effects, I get an "infinite" list of random 
numbers that can easily be broken into rows and matrices lazily.

So, here is how I generated two square matrices with rows and columns = n (some 
other artifacts are included here as well, like the Matrix type I'm using)

data Matrix a = Matrix (V.Vector (U.Vector a))
    deriving (Show, Eq)

makematrix :: [Float] -> Int -> Int -> [U.Vector Float]
makematrix xs n 0 = []
makematrix xs n r = (U.fromList $ ys) : makematrix zs n (r - 1)
    where (ys, zs) = splitAt n xs

main :: IO ()
main = do
    args <- getArgs
    let n = read (args !! 0) :: Int
    let minrange = read (args !! 1) :: Float
    let maxrange = read (args !! 2) :: Float
    let s = read (args !! 3) :: Int
    let g = mkStdGen s
    let range = (minrange, maxrange)
    let all = randomRs range g
    
    let ma = Matrix $ (V.fromList (makematrix all n n))
    let mb = Matrix $ (V.fromList (makematrix (drop (n*n) all)  n n))

    ...

As with all Haskell I'm learning, I'm 100% sure there are quite a few better 
ways to write this ;-)

Still, again, I can't thank you enough for the thoughtful discussion on IO and 
randomness.  I have avoided running back to Java with my tail between my legs 
for another day.

Paul Monday
Parallel Scientific, LLC.
paul.mon...@parsci.com




On Dec 9, 2011, at 3:05 PM, David McBride wrote:

> I wish I'd known this when I was first beginning, but it is possible
> to do randomness outside of IO, surprisingly easily.  I like to use
> the monadRandom library, which provides some monads and monad
> transformers for this task.  I too became frustrated when I wrote a
> roguelike but could not figure out how to inject randomness into it
> when I wanted.  A program you would write might be like this:
> 
> data Obstacle = Mon (Int, Int) Monster | Door (Int, Int) | Trap (Int,
> Int) deriving (Show, Enum)
> data Monster = Orc | Wolf | Dragon deriving (Show, Enum)
> 
> main = do
>  print =<< evalRandIO randomObstacle
> 
> randomObstacle :: RandomGen g => Rand g Obstacle
> randomObstacle = do
>  x <- getRandomR (0,2::Int)
>  case x of
>    0 -> Mon <$> randomLocation <*> randomMonster
>    1 -> Door <$> randomLocation
>    2 -> Trap <$> randomLocation
> 
> randomLocation :: RandomGen g => Rand g (Int,Int)
> randomLocation = do
>  x <- getRandomR (0,10)
>  y <- getRandomR (0,10)
>  return (x,y)
> 
> randomMonster :: RandomGen g => Rand g Monster
> randomMonster = do
>  x <- getRandomR (0,2::Int)
>  return $ case x of
>    0 -> Orc
>    1 -> Dragon
>    2 -> Wolf
> 
> This way, even though my randomBlah functions do not have IO in them,
> nor do they pass around a stdGen around, but they can be combined
> willy nilly as needed, and only computed when you want them to.  I
> also could have made Random instances for Obstacle and Monster so that
> I did not have to do the cases in the code, making things easier to
> understand.
> 
> On Fri, Dec 9, 2011 at 3:27 PM, Brent Yorgey <byor...@seas.upenn.edu> wrote:
>>> Does "impurity" from something
>>> like a random number generator or file I/O have to move it's way all
>>> the way through my code?
>> 
>> No, only through the parts that actually have to do file I/O or
>> generate random numbers or whatever.  However, cleanly separating the
>> IO code from the non-IO/"pure" code takes some experience.  It does
>> seem to be a common experience of people learning Haskell that IO ends
>> up "infecting" everything, even stuff that shouldn't have to do any
>> IO, but with good design this is not necessary.
>> 
>> In your particular case, your matrix generation function does depend
>> on random number generation so it makes sense that its type must
>> involve IO. However, if you go on to write other functions which do
>> deterministic operations on matrices, their types should *not* involve
>> IO, even if you pass randomly generated matrices to them as
>> arguments.
>> 
>> -Brent
>> 
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 2
Date: Mon, 12 Dec 2011 13:53:11 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Fwd: Averaging a string of numbers
To: beginners@haskell.org
Message-ID: <20111212185311.ga...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Dec 12, 2011 at 10:00:35AM -0500, Dean Herington wrote:
> At 9:04 PM +1000 12/12/11, Ben Kolera wrote:
> >There is some magic here that I'm not quite groking. Sorry for my
> >slowness; but I seem to be missing a step:
> 
> Oops, my bad!  The magic is an inadequate test ;-).  Thanks for
> spotting the bug!
> 
> The magic I was trying to leverage is this instance from Data.Monoid:
> 
> instance Monoid a => Monoid (Maybe a) where
>   mempty = Nothing
>   Nothing `mappend` m = m
>   m `mappend` Nothing = m
>   Just m1 `mappend` Just m2 = Just (m1 `mappend` m2)

Just to provide a bit of perspective at this point: the reason this
Monoid instance for (Maybe a) can't be used is because it requires a
to be an instance of Monoid... but numbers under min/max DON'T form a
Monoid since there is no identity element.  In fact, that's the very
reason why we wanted to use Maybe in the first place!

I therefore consider this Monoid instance for Maybe "broken".  What we
really want is

  instance Semigroup a => Monoid (Maybe a) where ...

A semigroup is a set with an associative binary operation (but not
necessarily an identity element).  Maybe turns any semigroup into a
monoid by adding a "synthetic" identity element (namely, Nothing).  In
fact, such an instance is provided in the 'semigroups' package on
Hackage (except for a type called Option instead of Maybe).

Maybe someday we will get semigroups defined in 'base'.  That would be
nice.

-Brent



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

Message: 3
Date: Mon, 12 Dec 2011 12:07:19 -0800
From: "goodman....@gmail.com" <goodman....@gmail.com>
Subject: Re: [Haskell-beginners] Fwd: Averaging a string of numbers
To: Brent Yorgey <byor...@seas.upenn.edu>
Cc: beginners@haskell.org
Message-ID:
        <CAGXBFAr=6MLVE3R-TEBRLb=ydalj_qdhr+lmaqkku+odfu-...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

I'll just chime in at this point to say thanks everyone for the
discussion. It's a little above my level of comprehension, so I'll
continue digesting what's been offered here. I don't have anything
else to add but if you all want to continue refining the solution I'm
sure many of us would benefit :)

Thanks again

-- 
-Michael Wayne Goodman



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

Message: 4
Date: Mon, 12 Dec 2011 16:31:02 -0500
From: "Allen S. Rout" <a...@ufl.edu>
Subject: [Haskell-beginners] In Search Of a clue... (Defining and
        making use      of a type)
To: beginners@haskell.org
Message-ID: <jc5rqm$g80$1...@dough.gmane.org>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed



So, I'm approaching a problem which I think I understand pretty well.
I'm a novice to Haskell, though, and I'm having difficulty even
getting started with e.g. data types and building more complex
structures.

Here's what I'm trying to do; this is an xmonad
customization/extension.

My end goal is thus:

Innermost: a 'Screen Tuple' , which I'm calling a 'ScrUple'.  This
represents a statement like 'screen 0 is displaying workspace "mail"'.

Next: A variable-length list of these, I'm calling 'ScrConfig'.  It
means something like 'display this workspace on screen 0, that one on
1, etc'.

Next: [ haven't gotten here ] a hash, or something: pairs of 'label :
ScrConfig'.  I don't know if the most haskelly way to do that is to
build another type, and then another aggregate of that type..


In PERL, it'd be something vaguely like:

$configs =
         {
         'initial'  => {
                        \(0,"mail"),
                        \(1,"web"),
                        \(2,"jabber")
                        }

         'project'  => {
                        \(4,"editor"),
                        \(1,"compile"),
                        \(2,"jabber")
                        }

         };


Here's what I'm doing so far,

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

data ScrUple = ScrUple { xineramascreen :: Integer
                          , workspace :: String
                        } deriving (Show)

data  ScrConfig = ScrConfig [ ScrUple ]  deriving (Show)



s1 = ScrUple 0 "mail"
s2 = ScrUple 1 "web"


ScrConfig sc1 =ScrConfig( [s2 s1] ) ;

main = putStrLn $  show sc1[1]

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

and I get errors like:

play.hs:17:27:
     Couldn't match expected type `ScrUple -> ScrUple'
            against inferred type `ScrUple'
     In the expression: s2 s1
     In the first argument of `ScrConfig', namely `([s2 s1])'
     In the expression: ScrConfig ([s2 s1])

play.hs:21:19:
     Couldn't match expected type `[t] -> String'
            against inferred type `String'
     In the second argument of `($)', namely `show sc1 [1]'
     In the expression: putStrLn $ show sc1 [1]
     In the definition of `main': main = putStrLn $ show sc1 [1]

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


... I feel like I'm thinking about the problem wrong, because this
kind of "Here's how you build up a data structure" doesn't seem to be
in the tutorials.  I've been working through LYAH and Gentle
Introduction, but so far haven't found things that feel related.


I'd be delighted with pointers to the right parts of the Fine Manual,
and similarly pleased with discursion on how to think about this data
storage problem from a haskelly point of view.

- Allen S. Rout




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

Message: 5
Date: Mon, 12 Dec 2011 17:02:05 -0500
From: David McBride <toa...@gmail.com>
Subject: Re: [Haskell-beginners] In Search Of a clue... (Defining and
        making use of a type)
To: "Allen S. Rout" <a...@ufl.edu>
Cc: beginners@haskell.org
Message-ID:
        <can+tr42ns1ajw5s0ywuekbsbjen8hly_gkcasmo68qmjpte...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Your main problem and the only reason I can see why what you have
wouldn't work is that you have created a list of ScrUple's, but then
you tried to access it with [1] notation, which works in like every
other language, but not haskell.  That notation is for creating a
list, so when you type [1] that is basically of type Integral n =>
[n], so ghc has no clue what you are trying to do and blows up.  The
way to access by index is to use the !! operator.  You will have to
import Data.List to get that.

main = putStrLn $  show $ sc1 !! 1

should work.  Just keep in mind that it is unsafe in that

On Mon, Dec 12, 2011 at 4:31 PM, Allen S. Rout <a...@ufl.edu> wrote:
>
>
> So, I'm approaching a problem which I think I understand pretty well.
> I'm a novice to Haskell, though, and I'm having difficulty even
> getting started with e.g. data types and building more complex
> structures.
>
> Here's what I'm trying to do; this is an xmonad
> customization/extension.
>
> My end goal is thus:
>
> Innermost: a 'Screen Tuple' , which I'm calling a 'ScrUple'. ?This
> represents a statement like 'screen 0 is displaying workspace "mail"'.
>
> Next: A variable-length list of these, I'm calling 'ScrConfig'. ?It
> means something like 'display this workspace on screen 0, that one on
> 1, etc'.
>
> Next: [ haven't gotten here ] a hash, or something: pairs of 'label :
> ScrConfig'. ?I don't know if the most haskelly way to do that is to
> build another type, and then another aggregate of that type..
>
>
> In PERL, it'd be something vaguely like:
>
> $configs =
> ? ? ? ? {
> ? ? ? ? 'initial' ?=> {
> ? ? ? ? ? ? ? ? ? ? ? ?\(0,"mail"),
> ? ? ? ? ? ? ? ? ? ? ? ?\(1,"web"),
> ? ? ? ? ? ? ? ? ? ? ? ?\(2,"jabber")
> ? ? ? ? ? ? ? ? ? ? ? ?}
>
> ? ? ? ? 'project' ?=> {
> ? ? ? ? ? ? ? ? ? ? ? ?\(4,"editor"),
> ? ? ? ? ? ? ? ? ? ? ? ?\(1,"compile"),
> ? ? ? ? ? ? ? ? ? ? ? ?\(2,"jabber")
> ? ? ? ? ? ? ? ? ? ? ? ?}
>
> ? ? ? ? };
>
>
> Here's what I'm doing so far,
>
> ----------------
>
> data ScrUple = ScrUple { xineramascreen :: Integer
> ? ? ? ? ? ? ? ? ? ? ? ? , workspace :: String
> ? ? ? ? ? ? ? ? ? ? ? } deriving (Show)
>
> data ?ScrConfig = ScrConfig [ ScrUple ] ?deriving (Show)
>
>
>
> s1 = ScrUple 0 "mail"
> s2 = ScrUple 1 "web"
>
>
> ScrConfig sc1 =ScrConfig( [s2 s1] ) ;
>
> main = putStrLn $ ?show sc1[1]
>
> ------------------
>
> and I get errors like:
>
> play.hs:17:27:
> ? ?Couldn't match expected type `ScrUple -> ScrUple'
> ? ? ? ? ? against inferred type `ScrUple'
> ? ?In the expression: s2 s1
> ? ?In the first argument of `ScrConfig', namely `([s2 s1])'
> ? ?In the expression: ScrConfig ([s2 s1])
>
> play.hs:21:19:
> ? ?Couldn't match expected type `[t] -> String'
> ? ? ? ? ? against inferred type `String'
> ? ?In the second argument of `($)', namely `show sc1 [1]'
> ? ?In the expression: putStrLn $ show sc1 [1]
> ? ?In the definition of `main': main = putStrLn $ show sc1 [1]
>
> -------------------
>
>
> ... I feel like I'm thinking about the problem wrong, because this
> kind of "Here's how you build up a data structure" doesn't seem to be
> in the tutorials. ?I've been working through LYAH and Gentle
> Introduction, but so far haven't found things that feel related.
>
>
> I'd be delighted with pointers to the right parts of the Fine Manual,
> and similarly pleased with discursion on how to think about this data
> storage problem from a haskelly point of view.
>
> - Allen S. Rout
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 6
Date: Mon, 12 Dec 2011 23:22:32 +0100
From: Thomas <hask...@phirho.com>
Subject: Re: [Haskell-beginners] In Search Of a clue... (Defining and
        making use of a type)
To: beginners@haskell.org
Message-ID: <4ee67ea8.6090...@phirho.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi Allen,

 > Here's what I'm doing so far,
 >
 > ----------------
 >
 > data ScrUple = ScrUple { xineramascreen :: Integer
 > , workspace :: String
 > } deriving (Show)
 >
 > data ScrConfig = ScrConfig [ ScrUple ] deriving (Show)
 >
 >
 >
 > s1 = ScrUple 0 "mail"
 > s2 = ScrUple 1 "web"
 >
 >
 > ScrConfig sc1 =ScrConfig( [s2 s1] ) ;

   sc1 = ScrConfig [s2, s1]

 > main = putStrLn $ show sc1[1]

   main = putStrLn $ show sc1

To print just parts of a ScrConfig you'll probably want a helper 
function. Maybe something like:

   scPrint (ScrConfig sus) nth = show (sus !! nth)

(it will make problems on out-of-bounds-indexes!)

HTH,
Thomas







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

Message: 7
Date: Mon, 12 Dec 2011 20:03:53 -0500
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] In Search Of a clue... (Defining and
        making use of a type)
To: beginners@haskell.org
Message-ID: <20111213010352.ga14...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Dec 12, 2011 at 04:31:02PM -0500, Allen S. Rout wrote:
>
>
> ----------------
>
> data ScrUple = ScrUple { xineramascreen :: Integer
>                          , workspace :: String
>                        } deriving (Show)
>
> data  ScrConfig = ScrConfig [ ScrUple ]  deriving (Show)
>
>
>
> s1 = ScrUple 0 "mail"
> s2 = ScrUple 1 "web"
>
>
> ScrConfig sc1 =ScrConfig( [s2 s1] ) ;
>
> main = putStrLn $  show sc1[1]

Looks OK so far except for the problems of syntax already pointed out
by others.

Proceeding from this point, to build an association between labels and
ScrConfigs, you would use Data.Map. Something like this:

  import qualified Data.Map as M

  type ScrConfigs = M.Map String ScrConfig

  myScrConfigs :: ScrConfigs
  myScrConfigs = M.fromList [ ("initial",
                                [ ScrUple 0 "mail"
                                , ScrUple 1 "web"
                                , ScrUple 2 "jabber"
                                ]
                              )
                            , ("project",
                                [ ScrUple 0 "editor"
                                , ScrUple 1 "compile"
                                , ScrUple 2 "jabber
                                ]
                              )
                            ]

However, I should point out that this is essentially already
implemented in XMonad.Actions.DynamicWorkspaceGroups.  It may not
currently do exactly what you want -- for example, there's currently
no function provided to initialize the list of workspace configs.  But
it should not be too hard to add.  I'd be happy to help walk you
through the code or help you figure out how to add the features you
want.

-Brent



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

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


End of Beginners Digest, Vol 42, Issue 17
*****************************************

Reply via email to