On Monday 08 Nov 2004 6:00 am, Peter Simons wrote:
> Frankly, the idea that anyone would want to jump through
> hoops to add them to a purely functional language sounds
> bizarre to me.
The first step to solving a problem is to at least recognise
that it exists. What is "bizarre" is that so many
--- Ben Rudiak-Gould
<[EMAIL PROTECTED]> wrote:
> This is solved by merging the IO and ST monads,
> something that ought to
> be done anyway:
>
> type IO = ST RealWorld
> type IORef a = Ref RealWorld a
> type STRef s a = Ref s a
>
> newRef :: a -> ST s (Ref s a) -- replaces
> n
However, turning Haskell into O'Haskell seems like a far more radical
suggestion than the (IMO) conservative language extension under
discussion. So I don't expect it to happen anytime soon. Maybe if
Haskell ever gets a better records/modules system things might look
a bit different. But there doe
Adrian Hey wrote:
The first step to solving a problem is to at least recognise
that it exists. What is "bizarre" is that so many folk seem
to be in denial over this. Perhaps you would like to show
me your solution to the "oneShot" problem.
Why are you unable to give a concrete real world
example
Krasimir Angelov wrote:
Note that 2-rank type of runSTInit doesn't allow to
execute regular IO actions. Even that (ST s a) allows
actions like readRef and writeRef. This allows to
initialise local references but doesn't allow to
access other toplevel reverences since they are bound
to RealWorld sta
Note that 2-rank type of runSTInit doesn't allow to
execute regular IO actions. Even that (ST s a) allows
actions like readRef and writeRef. This allows to
initialise local references but doesn't allow to
access other toplevel reverences since they are bound
to RealWorld state.
Thinking about t
--- Keean Schupke <[EMAIL PROTECTED]> wrote:
>
> >> Note that 2-rank type of runSTInit doesn't allow
> to
> >> execute regular IO actions. Even that (ST s a)
> allows
> >> actions like readRef and writeRef. This allows to
> >> initialise local references but doesn't allow to
> >> access other to
Krasimir Angelov wrote:
ered on top of ST and the stToIO is
the lifting function. What does 'automatically be
lifted' mean?
Krasimir
For example with the state monad you can define:
instance (MonadState st m,MonadT t m) => MonadState st (t m) where
update = up . update
setState = up . setSt
Adrian Hey wrote:
Why are top level IORefs any worse than other IORefs (for
example)?
Because global variables are just BAD. They have been considered
bad a long time, it's not a Haskell thing.
If you really grok the functional way of doing things there should
be *very*, *very* few times you need
Adrian Hey wrote:
4- They already exist (stdin,stout,stderr) and I don't
recall anybody ever complaining about this.
stdin, stdout, and stderr are not global variables.
They are just handles. One possible implementation
of handles is as an Int. So stdin is no more a global
variable than 0. Of
Keean Schupke wrote:
Adrian Hey wrote:
The first step to solving a problem is to at least recognise
that it exists. What is "bizarre" is that so many folk seem
to be in denial over this. Perhaps you would like to show
me your solution to the "oneShot" problem.
Why are you unable to give a concre
On 8 Nov 2004, at 12:23, Lennart Augustsson wrote:
Adrian Hey wrote:
4- They already exist (stdin,stout,stderr) and I don't
recall anybody ever complaining about this.
stdin, stdout, and stderr are not global variables.
They are just handles. One possible implementation
of handles is as an Int.
As I know the ST monad doesn't provide
getState/setState functions. In order to get this kind
of overloading we need to put all functions that deal
with references in type class:
class MonadRef m r where
readRef :: r a -> m a
writeRef :: a -> r a -> m ()
I guess that this is an overkill s
Jules Bean wrote:
Yes... a lot of the example we have seen here are 'just' handles.
newIORef creates handles. Something many programmers would like is the
ability to create fresh handles at the toplevel...
Yes, I hear what they want. That doesn't mean I think it's
a good idea. Top level things
| Please, can we confine this discussion to just one mailing list:-)
|
| It started out on [EMAIL PROTECTED] so that's where I'd like
| to keep it (at least that's where I will be posting my responses
| from now on).
Actually, I'd like to suggest that it move to Haskell-café. It's certainly an
Krasimir Angelov <[EMAIL PROTECTED]> writes:
> I guess that this is an overkill since we can just
> define IO as
>
> type IO a = ST RealWorld a
'instance MonadIO IO' would start to need some type system extensions.
--
__("< Marcin Kowalczyk
\__/ [EMAIL PROTECTED]
^^
On Sunday 07 November 2004 23:19, Ben Rudiak-Gould wrote:
> Benjamin Franksen wrote:
> >data (?val::Bool) => Test = Test { name :: String }
> >
> >is rejected by the compiler:
> >
> >TestBug.hs:3:
> >Illegal constraint ?val :: Bool
> >In the context: (?val :: Bool)
> >While chec
Benjamin Franksen wrote:
>On Sunday 07 November 2004 23:19, Ben Rudiak-Gould wrote:
>
>>Does this do what you want?:
>>
>>data Test = Test { name :: (?val::Bool) => String }
>
>Thanks for the hint, but no:
>
>TestBug.hs:4:
>Illegal constraint ?val :: Bool
>In the type: ({?val :: Bool} =
On Monday 08 Nov 2004 10:52 am, Keean Schupke wrote:
> Krasimir Angelov wrote:
> >Note that 2-rank type of runSTInit doesn't allow to
> >execute regular IO actions. Even that (ST s a) allows
> >actions like readRef and writeRef. This allows to
> >initialise local references but doesn't allow to
> >
On Monday 08 Nov 2004 12:23 pm, Lennart Augustsson wrote:
> Adrian Hey wrote:
> > 4- They already exist (stdin,stout,stderr) and I don't
> >recall anybody ever complaining about this.
>
> stdin, stdout, and stderr are not global variables.
> They are just handles.
Isn't an IORef just a "handle
On Sunday 07 November 2004 19:36, Benjamin Franksen wrote:
>
> data (?val::Bool) => Test = Test { name :: String }
>
> is rejected by the compiler
> [...]
> which is unfortunate since it means that you cannot put a function that
> depends on an implicit parameter into a data structure. There are pr
Benjamin Franksen wrote:
>Functions with implicit parameters *are* first class values but only
if you
>use -fglasgow-exts and not only -fimplicit-params.
Careful, they're still not entirely first class. For example, you can't
pass types with implicit parameters as arguments to type constructors,
22 matches
Mail list logo