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.  Combining the Rand and State monads (Amy de Buitl?ir)
   2. Re:  Combining the Rand and State monads (Amy de Buitl?ir)
   3.  Overloading resolution with numbers (j.romi...@gmail.com)
   4. Re:  Overloading resolution with numbers (Amy de Buitl?ir)
   5. Re:  Overloading resolution with numbers (Marius Ghita)
   6. Re:  Overloading resolution with numbers (j.romi...@gmail.com)
   7. Re:  Overloading resolution with numbers (damodar kulkarni)
   8. Re:  Overloading resolution with numbers (Jason Dusek)


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

Message: 1
Date: Thu, 5 Apr 2012 10:42:20 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: [Haskell-beginners] Combining the Rand and State monads
To: beginners@haskell.org
Message-ID: <loom.20120405t12153...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

I'm trying to develop a very simple simulation framework. A simulation consists
of a list of models. Models generate output events based on an input event. Here
is what I have currently (it works fine).

-----8<-----
import Data.List (foldl')
import Control.Monad.State ( get, gets, modify, put, runState, State )

type Event = Char

type Environment = String

-- | Given an event, a model generates zero or more new events
type Model = Event -> State Environment [Event]

modelA :: Model
modelA a = do
  s <- get
  put $ s ++ a:"A "
  return $ a:"hip "

modelT :: Model
modelT a = do
  s <- get
  put $ s ++ a:"T "
  return $ a:"hop "

-- | Process a sequence of events using one model
runModel :: Model -> [Event] -> State Environment [Event]
runModel m [] = return []
runModel m (e:es) = do
  s <- get
  let (es', s') = runState (m e) s
  let (es'', s'') = runState (runModel m es) s'
  put s''
  return $ es' ++ es''

-- | Process a sequence of events using multiple models
runModels :: [Model] -> [Event] -> State Environment [Event]
runModels [] es = return []
runModels (m:ms) es = do
  s <- get
  let (es', s') = runState (runModel m es) s
  let (es'', s'') = runState (runModels ms es) s'
  put s''
  return $ es' ++ es''
----->8-----

Now what I want to do is to give models the ability to generate random numbers.
So I thought I might change the definition of Model to:

type Model g = Event -> StateT Environment (Rand g) [Event]

And then I could alter one of the models to use random numbers like so:

modelT :: Model g
modelT _ = do
  s <- get
  put $ s ++ " R"
  n <- HOW DO I GET A RANDOM NUMBER????
  return [n]

I can't figure out how to get a random number from the inner monad. I assume I
use lift, but I can't get it to work. Would it be better to use RandT instead of
StateT? (And if so, how would I do the state operations?)

Thank you in advance for any help!




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

Message: 2
Date: Thu, 5 Apr 2012 11:36:49 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Combining the Rand and State monads
To: beginners@haskell.org
Message-ID: <loom.20120405t133551-...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

Sorry, instead of /2random number", I meant "random character"




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

Message: 3
Date: Thu, 5 Apr 2012 10:16:34 -0300
From: j.romi...@gmail.com
Subject: [Haskell-beginners] Overloading resolution with numbers
To: beginners@haskell.org
Message-ID: <20120405131634.ga21...@malaquias.dhcp-GERAL>
Content-Type: text/plain; charset=us-ascii

Hello.

Consider the following ghci session:

   Prelude> :t read "2" + 1
   read "2" + 1 :: (Num a, Read a) => a

   Prelude> :t read "2.3" + 1
   read "2.3" + 1 :: (Num a, Read a) => a

   Prelude> read "2" + 1
   3

   Prelude> read "2.3" + 1
   *** Exception: Prelude.read: no parse

Why does (read "2" + 1) works, but (read "2.3" + 1) fail at runtime?

Romildo



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

Message: 4
Date: Thu, 5 Apr 2012 13:18:39 +0000 (UTC)
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: Re: [Haskell-beginners] Overloading resolution with numbers
To: beginners@haskell.org
Message-ID: <loom.20120405t151647...@post.gmane.org>
Content-Type: text/plain; charset=us-ascii

 <j.romildo <at> gmail.com> writes:
> Why does (read "2" + 1) works, but (read "2.3" + 1) fail at runtime?

Try this:

read "2.3" + 1 :: Float

Or this:

read "2.3" + 1.0

The reason that your version didn't work is because GHCi is guessing that you
want the read operation to parse an Integer, since you're adding it to 1.




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

Message: 5
Date: Thu, 5 Apr 2012 16:19:11 +0300
From: Marius Ghita <mhi...@gmail.com>
Subject: Re: [Haskell-beginners] Overloading resolution with numbers
To: j.romi...@gmail.com
Cc: beginners@haskell.org
Message-ID:
        <CAB7aqhjLYatWkKgbucXuPOYgfiCwTKZq-J-UT=x50gkwrko...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Because this works

Prelude> read "2.3" + 1.0
3.3

Seriously I can only assume that via the inference it decides based on the
one that the string must be of type Int and uses the Read instance of Int
to parse it; whereas that string is obviously a float.

That is what* I think* it does.

On Thu, Apr 5, 2012 at 4:16 PM, <j.romi...@gmail.com> wrote:

> Hello.
>
> Consider the following ghci session:
>
>   Prelude> :t read "2" + 1
>   read "2" + 1 :: (Num a, Read a) => a
>
>   Prelude> :t read "2.3" + 1
>   read "2.3" + 1 :: (Num a, Read a) => a
>
>   Prelude> read "2" + 1
>   3
>
>   Prelude> read "2.3" + 1
>   *** Exception: Prelude.read: no parse
>
> Why does (read "2" + 1) works, but (read "2.3" + 1) fail at runtime?
>
> Romildo
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
Google+: https://plus.google.com/111881868112036203454
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120405/1350a43e/attachment-0001.htm>

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

Message: 6
Date: Thu, 5 Apr 2012 10:54:55 -0300
From: j.romi...@gmail.com
Subject: Re: [Haskell-beginners] Overloading resolution with numbers
To: Amy de Buitl?ir <a...@nualeargais.ie>
Message-ID: <20120405135455.ga21...@malaquias.dhcp-GERAL>
Content-Type: text/plain; charset=iso-8859-1

On Thu, Apr 05, 2012 at 01:18:39PM +0000, Amy de Buitl?ir wrote:
>  <j.romildo <at> gmail.com> writes:
> > Why does (read "2" + 1) works, but (read "2.3" + 1) fail at runtime?
> 
> Try this:
> 
> read "2.3" + 1 :: Float
> 
> Or this:
> 
> read "2.3" + 1.0
> 
> The reason that your version didn't work is because GHCi is guessing that you
> want the read operation to parse an Integer, since you're adding it to 1.

This is explanation does not seem to be enough once we consider the type
of the literal 1:

   Prelude> :t 1
   1 :: Num a => a

That is, the literal 1 is overloaded to any numeric type. It is not
necessarily an Integer.

Romildo



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

Message: 7
Date: Thu, 5 Apr 2012 20:30:40 +0530
From: damodar kulkarni <kdamodar2...@gmail.com>
Subject: Re: [Haskell-beginners] Overloading resolution with numbers
To: j.romi...@gmail.com
Cc: Amy de Buitl?ir <a...@nualeargais.ie>,      beginners@haskell.org
Message-ID:
        <cad5hsyqaiu-ft5ajs7ihzo0wc1elcla--1ffcaqt7o1npxy...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Thu, Apr 5, 2012 at 8:29 PM, damodar kulkarni <kdamodar2...@gmail.com>wrote:

> See this:
> Prelude> :t 2.3
> 2.3 :: Fractional a => a
>
> Hope this helps.
>
>
>
> On Thu, Apr 5, 2012 at 7:24 PM, <j.romi...@gmail.com> wrote:
>
>> On Thu, Apr 05, 2012 at 01:18:39PM +0000, Amy de Buitl?ir wrote:
>> >  <j.romildo <at> gmail.com> writes:
>> > > Why does (read "2" + 1) works, but (read "2.3" + 1) fail at runtime?
>> >
>> > Try this:
>> >
>> > read "2.3" + 1 :: Float
>> >
>> > Or this:
>> >
>> > read "2.3" + 1.0
>> >
>> > The reason that your version didn't work is because GHCi is guessing
>> that you
>> > want the read operation to parse an Integer, since you're adding it to
>> 1.
>>
>> This is explanation does not seem to be enough once we consider the type
>> of the literal 1:
>>
>>   Prelude> :t 1
>>   1 :: Num a => a
>>
>> That is, the literal 1 is overloaded to any numeric type. It is not
>> necessarily an Integer.
>>
>> Romildo
>>
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>
>
>
>
> --
> Thanks and regards,
> -Damodar Kulkarni
>
>


-- 
Thanks and regards,
-Damodar Kulkarni
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120405/2e14bdd4/attachment-0001.htm>

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

Message: 8
Date: Thu, 5 Apr 2012 14:53:39 +0000
From: Jason Dusek <jason.du...@gmail.com>
Subject: Re: [Haskell-beginners] Overloading resolution with numbers
To: j.romi...@gmail.com
Cc: Amy de Buitl?ir <a...@nualeargais.ie>
Message-ID:
        <CAO3NbwNz+MXBuS66rEb-Y3Q=_7u2vzm027rzy2suu5_fvwr...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

The 1 is not necessarily an Integer nor is it necessarily a Float, Double
or Rational. GHC applies so called type-defaulting rules to make a
best guess in this scenario. Informally, if it could be an Integer (due
to lack of static evidence to the contrary), then you can expect the
defaulting rules to assign it that type.

--
Jason Dusek
 On Apr 5, 2012 7:45 AM, <j.romi...@gmail.com> wrote:

> On Thu, Apr 05, 2012 at 01:18:39PM +0000, Amy de Buitl?ir wrote:
> >  <j.romildo <at> gmail.com> writes:
> > > Why does (read "2" + 1) works, but (read "2.3" + 1) fail at runtime?
> >
> > Try this:
> >
> > read "2.3" + 1 :: Float
> >
> > Or this:
> >
> > read "2.3" + 1.0
> >
> > The reason that your version didn't work is because GHCi is guessing
> that you
> > want the read operation to parse an Integer, since you're adding it to 1.
>
> This is explanation does not seem to be enough once we consider the type
> of the literal 1:
>
>   Prelude> :t 1
>   1 :: Num a => a
>
> That is, the literal 1 is overloaded to any numeric type. It is not
> necessarily an Integer.
>
> Romildo
>
> _______________________________________________
> 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/20120405/90ba6402/attachment.htm>

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

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


End of Beginners Digest, Vol 46, Issue 6
****************************************

Reply via email to