Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-07 Thread Kim-Ee Yeoh
On Sun, Apr 7, 2013 at 5:03 AM, Ömer Sinan Ağacan  wrote:
> That's interesting, thanks! Do you have any recommendations about
> which file to start reading? AFAIK, GHC is _huge_.

Without a discussion of your interests, it's hard to say. Certainly,
I'd set up the reading environment, namely an editor that can traverse
from usage to point of definition and back.

An interesting idea that occurred to me is to start with the file with
the largest comments to code ratio.

-- Kim-Ee

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread kudah
On Sun, 7 Apr 2013 01:02:12 +0300 Ömer Sinan Ağacan
 wrote:

> I'm not happy with this design because to me it was like I'm missing
> the point of using a 'functional' language.

You kind of do, e.g. you might not be able to test parts of your
program independently.

> For instance, in most parts of my code I can actually do IO.

You can disable IO in parts of your code by making it polymorphic over
monad.

{-# LANGUAGE RankNTypes #-}
type MonadStack = ErrorT Err (StateT St IO)
type MonadStackNoIO = forall m. Monad m => ErrorT Err (StateT St m)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Tillmann Rendel

Hi,

Ömer Sinan Ağacan wrote:

One thing I'm not happy about my Haskell programs is, almost all of my
programs have a monad transformer stack consisting MonadError, MonadIO
and MonadState.


You can try to write most of your program in pure functions that are 
called from a few "main" functions in the monad. Or, if you need some 
but not all monadic actions in each function, you can use the following 
pattern:


  -- This helper function cannot cause monadic effects other than
  -- throwing errors. But it can be used in arbitrary monads that
  -- support throwing errors.
  helper :: MonadError MyError m => ... -> m ...
  helper = do ...

  -- Same but with only allowing IO, but other monadic actions
  other :: MonadIO m => ... -> m ...
  other = do ...

  -- we can use both functions in the same monad
  main = runMyStack $ do
helper
other

This way, you have some control over what effects are allowed where.

  Tillmann

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Ömer Sinan Ağacan
> Not as well-known as it should be is the fact that GHC doesn't make
> much use of monad transformers. Have you taken a look at the sources?
> That might provide ideas on future ways of structuring your
> experiments.

That's interesting, thanks! Do you have any recommendations about
which file to start reading? AFAIK, GHC is _huge_.

Ömer

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Ömer Sinan Ağacan
> You forgot to mention what your problem is. :)
>
> What you describe sounds reasonable. Why do you want to "escape"?

It's not really a problem,

I'm not happy with this design because to me it was like I'm missing
the point of using a 'functional' language. For instance, in most
parts of my code I can actually do IO. On the other hand, I know it's
mostly because of my application area and nothing to do with Haskell.
Let's say I just wanted to know ideas of experienced Haskell
programmers :-)

Ömer


---
Ömer Sinan Ağacan
http://osa1.net/


2013/4/7 Roman Cheplyaka :
> Hi Ömer,
>
> You forgot to mention what your problem is. :)
>
> What you describe sounds reasonable. Why do you want to "escape"?
>
> Roman
>
> * Ömer Sinan Ağacan  [2013-04-07 00:22:58+0300]
>> Hi,
>>
>> I'm a hobbyist Haskell programmer and my use of Haskell is mostly
>> consists of writing interpreters, simple virtual machines, and type
>> checkers.
>>
>> One thing I'm not happy about my Haskell programs is, almost all of my
>> programs have a monad transformer stack consisting MonadError, MonadIO
>> and MonadState.
>>
>> Let's say I'm writing an interpreter, I certainly need MonadIO to
>> interpret object language's IO functions: printing, reading from file
>> etc. I also need MonadState for, well, states(dynamic environment
>> etc.). MonadError is also required because most computations can
>> fail(unbound variable error, type mismatch etc. it can be also used
>> for implementing exceptions in object language)
>>
>> Same applies for my other applications as well. Type checkers require
>> MonadError(unification error etc.), MonadState(to keep substitutions).
>> MonadIO is not required in this case. But it also required for virtual
>> machines(IOVector for memory -- ST vectors also work, but IO is still
>> required for other stuff - printing, display etc.)
>>
>> I know these are mostly related with my application area, but I still
>> wanted to write this because I may be missing something, or simply
>> doing things wrong.
>>
>> Advices from experienced Haskell programmers would be appreciated,
>>
>> Cheers,
>> Ömer
>>
>> ___
>> Haskell-Cafe mailing list
>> Haskell-Cafe@haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Roman Cheplyaka
Hi Ömer,

You forgot to mention what your problem is. :)

What you describe sounds reasonable. Why do you want to "escape"?

Roman

* Ömer Sinan Ağacan  [2013-04-07 00:22:58+0300]
> Hi,
> 
> I'm a hobbyist Haskell programmer and my use of Haskell is mostly
> consists of writing interpreters, simple virtual machines, and type
> checkers.
> 
> One thing I'm not happy about my Haskell programs is, almost all of my
> programs have a monad transformer stack consisting MonadError, MonadIO
> and MonadState.
> 
> Let's say I'm writing an interpreter, I certainly need MonadIO to
> interpret object language's IO functions: printing, reading from file
> etc. I also need MonadState for, well, states(dynamic environment
> etc.). MonadError is also required because most computations can
> fail(unbound variable error, type mismatch etc. it can be also used
> for implementing exceptions in object language)
> 
> Same applies for my other applications as well. Type checkers require
> MonadError(unification error etc.), MonadState(to keep substitutions).
> MonadIO is not required in this case. But it also required for virtual
> machines(IOVector for memory -- ST vectors also work, but IO is still
> required for other stuff - printing, display etc.)
> 
> I know these are mostly related with my application area, but I still
> wanted to write this because I may be missing something, or simply
> doing things wrong.
> 
> Advices from experienced Haskell programmers would be appreciated,
> 
> Cheers,
> Ömer
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Kim-Ee Yeoh
On Sun, Apr 7, 2013 at 4:22 AM, Ömer Sinan Ağacan  wrote:
> I'm a hobbyist Haskell programmer and my use of Haskell is mostly
> consists of writing interpreters, simple virtual machines, and type
> checkers.
>
> One thing I'm not happy about my Haskell programs is, almost all of my
> programs have a monad transformer stack consisting MonadError, MonadIO
> and MonadState.

Welcome! Hobbyist Haskellers writing VMs and type checkers are a
critical part of the community and what sets us apart.

Not as well-known as it should be is the fact that GHC doesn't make
much use of monad transformers. Have you taken a look at the sources?
That might provide ideas on future ways of structuring your
experiments.

Also, what precisely are the infelicities with monad transformers in
your code? Depth of stack? Forced type annotation? Syntax inflation
due to extra lift* functions?

Monad transformers provide an abstraction which may not be necessary
for some apps. But it's easy to write something and then suddenly, the
need for generalization kicks in.

-- Kim-Ee

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Is there an escape from MonadState+MonadIO+MonadError monad stack?

2013-04-06 Thread Ömer Sinan Ağacan
Hi,

I'm a hobbyist Haskell programmer and my use of Haskell is mostly
consists of writing interpreters, simple virtual machines, and type
checkers.

One thing I'm not happy about my Haskell programs is, almost all of my
programs have a monad transformer stack consisting MonadError, MonadIO
and MonadState.

Let's say I'm writing an interpreter, I certainly need MonadIO to
interpret object language's IO functions: printing, reading from file
etc. I also need MonadState for, well, states(dynamic environment
etc.). MonadError is also required because most computations can
fail(unbound variable error, type mismatch etc. it can be also used
for implementing exceptions in object language)

Same applies for my other applications as well. Type checkers require
MonadError(unification error etc.), MonadState(to keep substitutions).
MonadIO is not required in this case. But it also required for virtual
machines(IOVector for memory -- ST vectors also work, but IO is still
required for other stuff - printing, display etc.)

I know these are mostly related with my application area, but I still
wanted to write this because I may be missing something, or simply
doing things wrong.

Advices from experienced Haskell programmers would be appreciated,

Cheers,
Ömer

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe