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.  randomize the order of a list (Gaius Hammond)
   2. Re:  randomize the order of a list (Felipe Lessa)
   3. Re:  randomize the order of a list (Gaius Hammond)
   4. Re:  randomize the order of a list (Daniel Fischer)
   5. Re:  typeclass confusion (Greg Best)
   6. Re:  instances of different kinds (Greg)


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

Message: 1
Date: Fri, 27 Aug 2010 21:02:59 +0100
From: Gaius Hammond <ga...@gaius.org.uk>
Subject: [Haskell-beginners] randomize the order of a list
To: Haskell Beginners List <beginners@haskell.org>
Message-ID: <0fdac119-ed13-4b58-8fb3-48a32b6dc...@gaius.org.uk>
Content-Type: text/plain; charset=UTF-8; format=flowed; delsp=yes

Hi all,



I am trying to randomly reorder a list (e.g. shuffle a deck of  
cards) . My initial approach is to treat it as an array, generate a  
list of unique random numbers between 0 and n - 1, then use those  
numbers as new indexes. I am using a function to generate random  
numbers in the State monad as follows:



randInt∷  Int →  State StdGen Int
randInt x = do g ←  get
                (v,g') ←  return $ randomR (0, x) g
                put g'
                return v



This is pretty much straight from the documentation. My function for  
the new indexes is:



-- return a list of numbers 0 to x-1 in random  
order                                        
randIndex∷ Int → StdGen → ([Int], StdGen)
randIndex x = runState $ do
     let randIndex' acc r
             | (length acc ≡ x) = acc
             | (r `elem` acc) ∨ (r ≡  (−1)) = do
                 r' ← randInt (x − 1)
                 randIndex' acc r'
             | otherwise = do
                 r' ← randInt (x − 1)
                 randIndex' r:acc r'
         in
         randIndex' [] (−1)



This fails to compile on




    Couldn't match expected type `[a]'
            against inferred type `State StdGen b'
     In a stmt of a 'do' expression: r' <- randInt (x - 1)
     In the expression:
         do { r' <- randInt (x - 1);
              randIndex' acc r' }




I can see what's happening here - it's treating randIndex' as the  
second argument to randInt instead of invisibly putting the State in  
there. Or am I going about this completely the wrong way?


Thanks,



G






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

Message: 2
Date: Fri, 27 Aug 2010 17:16:55 -0300
From: Felipe Lessa <felipe.le...@gmail.com>
Subject: Re: [Haskell-beginners] randomize the order of a list
To: Gaius Hammond <ga...@gaius.org.uk>
Cc: Haskell Beginners List <beginners@haskell.org>
Message-ID:
        <aanlktimxnir1vqx2fgm1hlcvz0xvam6ek5d7q2zuv...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Fri, Aug 27, 2010 at 5:02 PM, Gaius Hammond <ga...@gaius.org.uk> wrote:
> I am trying to randomly reorder a list (e.g. shuffle a deck of cards) .

Note: you could use random-shuffle package [1].

[1] http://hackage.haskell.org/package/random-shuffle

Cheers!

-- 
Felipe.


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

Message: 3
Date: Fri, 27 Aug 2010 21:21:11 +0100
From: Gaius Hammond <ga...@gaius.org.uk>
Subject: Re: [Haskell-beginners] randomize the order of a list
To: Felipe Lessa <felipe.le...@gmail.com>
Cc: Haskell Beginners List <beginners@haskell.org>
Message-ID: <fa709d55-732f-4de9-8dc4-d5cb9e425...@gaius.org.uk>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

Amazing! Thanks :-)



G





On 27 Aug 2010, at 21:16, Felipe Lessa wrote:

> On Fri, Aug 27, 2010 at 5:02 PM, Gaius Hammond <ga...@gaius.org.uk>  
> wrote:
>> I am trying to randomly reorder a list (e.g. shuffle a deck of  
>> cards) .
>
> Note: you could use random-shuffle package [1].
>
> [1] http://hackage.haskell.org/package/random-shuffle
>
> Cheers!
>
> -- 
> Felipe.



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

Message: 4
Date: Fri, 27 Aug 2010 22:36:32 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] randomize the order of a list
To: beginners@haskell.org
Message-ID: <201008272236.33734.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="utf-8"

On Friday 27 August 2010 22:02:59, Gaius Hammond wrote:
> Hi all,
>
>
>
> I am trying to randomly reorder a list (e.g. shuffle a deck of
> cards) . My initial approach is to treat it as an array, generate a
> list of unique random numbers between 0 and n - 1, then use those
> numbers as new indexes. I am using a function to generate random
> numbers in the State monad as follows:
>
>
>
> randInt∷  Int →  State StdGen Int
> randInt x = do g ←  get
>                 (v,g') ←  return $ randomR (0, x) g

value <- return $ expression

is always awkward. Bind it with a let:

let value = expression

>                 put g'
>                 return v

Here, it would be simpler to just write

randInt x = State $ randomR (0,x)

>
>
>
> This is pretty much straight from the documentation. My function for
> the new indexes is:
>
>
>
> -- return a list of numbers 0 to x-1 in random
> order
> randIndex∷ Int → StdGen → ([Int], StdGen)
> randIndex x = runState $ do
>      let randIndex' acc r
>
>              | (length acc ≡ x) = acc

If you need many random values, it would be faster to pass the number of 
values you still require as a parameter, that avoids traversing the list to 
get its length in each step.

>              | (r `elem` acc) ∨ (r ≡  (−1)) = do

You will get a skewed distribution of shuffles that way, that may or may 
not be a problem.

>
>                  r' ← randInt (x − 1)
>                  randIndex' acc r'
>
>              | otherwise = do
>
>                  r' ← randInt (x − 1)
>                  randIndex' r:acc r'

This is parsed as

            (randIndex' r) : (acc r')

, remember, function application binds tightest.

So the compiler sees a list and infers the type [a] for this do-block. Thus 
it would require (randInt x) to be a list too, of type [b]. However, it is 
of type (State StdGen Int).

You need parentheses around the list pattern:

        randIndex' (r:acc) r'


>          in
>          randIndex' [] (−1)
>
>
>
> This fails to compile on
>
>
>
>
>     Couldn't match expected type `[a]'
>             against inferred type `State StdGen b'
>      In a stmt of a 'do' expression: r' <- randInt (x - 1)
>      In the expression:
>          do { r' <- randInt (x - 1);
>               randIndex' acc r' }
>
>
>
>
> I can see what's happening here - it's treating randIndex' as the
> second argument to randInt instead of invisibly putting the State in
> there. Or am I going about this completely the wrong way?
>
>
> Thanks,
>
>
>
> G



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

Message: 5
Date: Mon, 23 Aug 2010 22:37:07 -0700
From: Greg Best <gb...@mac.com>
Subject: Re: [Haskell-beginners] typeclass confusion
To: beginners@haskell.org
Message-ID: <80c6dbc2-a63d-44b5-9379-a3cc7cf9f...@mac.com>
Content-Type: text/plain; charset=us-ascii

Thanks.  I wasn't trying to do anything terribly practical-- just looking for 
toy problems to get my head around the type system.

The part I figured was impractical was the "Angular" class, but this is the 
second feedback that suggested making both Degrees and Radians type 
constructors rather than alternate value constructors.  Is that the right 
approach?  I know the trig functions are already available and they all just 
traffic in floats, but if this weren't the case, I'd imagine a structure along 
the lines of

data Angle a = Radians a
             | Degrees a
             deriving (Eq, Show)

sin :: Angle a -> a

I think the approach you were suggesting is to make Degrees and Radians as 
types, and put sin as a function of the class.  I suppose that is better in 
that it makes it much easier to implement additional angular measurements 
(without reimplementing sin).

My reservations were with needing to define sin for each angle type (which I 
now think my method would force me to do anyway), which could be a potentially 
expensive operation.  With Degree and Radian as types, I think I can get away 
without reimplementing by using default functions such as:

sin x = radianSin $ rad x

or some such which would only require that I define a radian conversion for 
each angle type.

(where Degree and Radian are stand ins for useful types and classes)

Cheers--
 Greg

On Aug 23, 2010, at 10:01 PM, Isaac Dupree wrote:

> On 08/23/10 22:33, Greg wrote:
>> ...it would be nice to force
>> the type system to check whether I'm using degrees or radians:
>> 
>> data Angle a = Radians a
>> | Degrees a
>> deriving (Eq, Show)
> 
> You did it wrong... the difference between Radians and Degrees here is only 
> visible at runtime, as they are both of the same type, Angle. Don't feel bad, 
> this confused me for a while as a Haskell-beginner too.  An example to "force 
> the type system to check" would be
> 
> data Radians a = Radians a  deriving (Eq, Show)
> data Degrees a = Degrees a  deriving (Eq, Show)
> 
> Then you could make conversion functions, say,
> radToDeg :: (Floating a) => Radians a -> Degrees a
> degToRad :: (Floating a) => Degrees a -> Radians a
> 
> and implement them;
> 
> you *could* have a 'class Angle' or such, if you wanted... perhaps trig 
> functions or such would be sensible to put in there.  And/or you could try to 
> make each data-type be a member of Num and related classes (being able to add 
> angles, etc)
> 
> For a real program, I think I would try to stick to just one unit (e.g. 
> radians) for internal program use (and convert any outside data to that unit 
> promptly), unless there was a reason that didn't work very well; but the 
> typeclass-stuff is an excellent thing to play with!
> 
> -Isaac
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



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

Message: 6
Date: Sat, 28 Aug 2010 02:58:44 +0000 (GMT)
From: Greg <gregli...@me.com>
Subject: Re: [Haskell-beginners] instances of different kinds
To: beginners@haskell.org
Message-ID: <0d110c48-eeef-6106-901f-e0706b846...@me.com>
Content-Type: text/plain; charset="iso-8859-1"


I'm still having a hard time finding a way to make this work, even given the 
fine suggestions from Tobias and Jürgen.  I suspect there's some piece of 
information that the compiler can't make sense of that I'm just not seeing-- a 
case of it insisting on doing what I say instead of what I mean...  =)

I guess the problem I'm having is finding a way to treat parametric and 
non-parametric types interchangeably.  The syntax doesn't seem to exist that 
will allow me to say:

div2pi :: (Floating a) => a -> a   -- for non parametric types (ie. Float)
and
div2pi :: (Floating b) => a b -> b  -- for parametric types (ie. Foo Float)


In addition, I'm having a hard time understanding the errors I'm getting from 
constructs like this:

data Foo a = Foo a 

class TwoPi a where
  div2pi :: (Floating b) => a -> b

instance (Floating a) => TwoPi (Foo a)  where
  div2pi (Foo x) = x / (2*pi)

{- only this code, no other instances in the file -}

It complains that I can't match expected b against inferred a where

      `b' is a rigid type variable bound by
          the type signature for `div2pi' at gcbTest.hs:6:22

which points immediately before the 'b' in (Floating b) of the div2pi type 
statement, and

      `a' is a rigid type variable bound by
          the instance declaration at gcbTest.hs:8:19

which points immediately before the 'a' in the (Floating a) of the instance 
definition.  It sounds like it's saying there's an explicit conflict between 
two type variables, both constrained identically.  Is the problem instead that 
they aren't well enough constrained?  It wants to know what instance of the 
Floating class to expect?  I would hope that it wouldn't care whether I 
provided Foo Float or Foo Double, and would return whatever type it received.

Here's the full error:

    Couldn't match expected type `b' against inferred type `a'
      `b' is a rigid type variable bound by
          the type signature for `div2pi' at gcbTest.hs:6:22
      `a' is a rigid type variable bound by
          the instance declaration at gcbTest.hs:8:19
    In the expression: x / (2 * pi)
    In the definition of `div2pi': div2pi (Foo x) = x / (2 * pi)
    In the instance declaration for `TwoPi (Foo a)'

Thanks--
  Greg


On Aug 27, 2010, at 02:31 AM, Jürgen Doser <jurgen.do...@gmail.com> wrote:

El vie, 27-08-2010 a las 01:58 -0700, Greg escribió:
> Hi--
> 
> 
> More silly typeclass questions. I'm not sure the right way to ask it,
> so I'll start with a failed code snippet:
> 
> 
> data Foo a = Foo a 
> 
> class TwoPi a where
> div2pi :: (Floating b) => a -> b
> 
> instance (Floating a) => TwoPi (Foo a) where
> div2pi (Foo a) = a / (2*pi)
> 
a/(2*pi) has type Floating a => a, where a is the type of a in Foo a.
the class declaration however requires to be able to return a value of
type Floating b => b for any type b, no relation to a whatsoever.

> instance TwoPi Float where
> div2pi a = a / (2*pi)
> 
a/(2*pi) has type Float (because a has type Float), so this again can
not work.
> 
You would need a function f::(Floating b) => Float -> b for this to
work. In the former, you would need a function f::(Floating a, Floating
b) => a -> b.

> This code is obviously meaningless, but I'm trying to figure out how
> you can create instances of a typeclass for data types of different
> kinds.
> 
> 
> I have a similar piece of code that works:
> 
> 
> data Foo a = Foo a 
> 
> 
> class Testable a where
> isPos :: a -> Bool
> 
> instance (Ord b, Num b) => Testable (Foo b) where
> isPos (Foo b) = b > 0
> 
b > 0 has type Bool, no matter what type of number b is. so this is ok. 

> instance Testable Float where
> isPos a = a > 0
> 
same here
> 
> 
> 
> One obvious difference is that the type of isPos is a -> Bool, with a
> defined type as the return. I'd rather not commit to a specific
> Floating type up front (I'd prefer sometimes Float sometimes Double,
> depending on the 'a' in Foo a, but trying to declare it as Float
> doesn't help me. This fails:
> 
> 
> data Foo a = Foo a 
> 
> class TwoPi a where
> div2pi :: a -> Float
> 
> instance (Floating b) => TwoPi (Foo b) where
> div2pi (Foo b) = b / (2*pi)
> 
b/(2*pi) has type Floating b => b, not Float. You would need a function
of type Floating b => b -> Float.

> instance TwoPi Float where
> div2pi a = a / (2*pi)
> 
This is ok

> 
> What is the difference between these last two cases ("a -> Bool" and
> "a -> Float"),

The difference is not between these type, but between (>), and (/).
(>) returns Bool, no matter the type of its arguments. (/) returns sth
of the same type as its arguments.

> and is there anyway to make "a -> b" work? 
> 
The closest is probably using a function like:
realToFrac::(Real a, Fractional b) => a -> b
> 
then you can write sth like

data Foo a = Foo a 

class TwoPi a where
div2pi :: (Floating b) => a -> b

instance (Real a, Floating a) => TwoPi (Foo a) where
div2pi (Foo a) = a / (2*pi)


Jürgen


_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners
-------------- next part --------------
Skipped content of type multipart/related

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

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


End of Beginners Digest, Vol 26, Issue 53
*****************************************

Reply via email to