Re: [Haskell-cafe] Code Review: Sudoku solver

2006-03-23 Thread Michael Hanus
Jared Updike wrote:
 On 3/22/06, David F. Place [EMAIL PROTECTED] wrote:
 ...
  It solves
  sudoku puzzles.  (What pleasure do people get by doing these in their
  heads?!?)
 
 
 They are probably asking the same question: why take hours to write a
 program to do it when with my mad sudoku solving skills I can solve it
 in X seconds? My roommate is like this.

I would say because they have chosen the wrong language for this
problem :-) Solving Sudoku is a typical finite domain constraint
problem. Thus, a language with constraint solving facilities
like Curry (a combination of Haskell and constraint logic programming)
is much better suited. Actually, I wrote a Sudoku solver in Curry
and the actual code for the solver is 10 lines of code which is
compact and well readable (if you are familiar with Haskell), see

http://www.informatik.uni-kiel.de/~curry/examples/CLP/sudoku.curry

Regards,

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


[Haskell-cafe] Re: how would this be done? type classes?existential types?

2006-03-23 Thread Ben Rudiak-Gould

Brian Hulley wrote:

Is there a reason for using  instead of

  [exists a. Resource a=a]

?


Only that = looks like a function arrow,  looks like a tuple. I stole 
this notation from an unpublished paper by SimonPJ et al on adding 
existential quantification to Haskell. I'm not especially attached to it. 
Actually I rather like


forall a | Resource a. a
exists a | Resource a. a

a) A value 'v' of type 'exists a. Resource a=a 'would have to be 
internally represented as something like (dictResource_t, value_t)


Yes.

b) Given such a value, there is no syntactic way to distinguish the pair 
from the value_t stored inside it, unlike the use of 'forall' where the 
syntax for the constructor conveniently represents any dictionaries 
that have been glued onto the value (ie pattern matching against R x 
gives us back the dictionaries R and the plain value x)?


Yes, but that doesn't necessarily mean you can't work out when to construct 
and deconstruct these implicit tuples. That's exactly what the type 
inference process does with implicit type arguments, and implicit type 
returns are dual to that, so the process should be similar.


It is tricky, though. E.g. given (f (g z)) where

   f :: forall a. [a] - Int
   g :: String - (exists b. [b])

in principle you should be able to call g first, getting a type b and a list 
[b], then instantiate f with the type b, then pass the list to it, 
ultimately getting an Int. But I don't know how to design a type inference 
algorithm that will find this typing. If on the other hand


   f :: (exists a. [a]) - Int

then it's easy to do the right thing---which is a little odd since these two 
types for f are otherwise indistinguishable.


Hope I'm not making this more confusing but I'm still trying to get my 
head around all these invisible happenings regarding dictionaries so I 
can visualise what's happening in terms of bytes and pointers in the 
runtime


Once you understand where the types go in System F, the dictionaries are 
easy: they always follow the types around. Any time you have


forall a b c. (C1 a b, C2 b c) = ...

in the source, you have five corresponding parameters/arguments in GHC Core, 
one for each type variable and constraint. These are always passed around as 
a unit (at least prior to optimization). In principle you could box them in 
a 5-tuple. The dictionary values are nothing more or less than proofs that 
the corresponding constraints hold.


-- Ben

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


Re: [Haskell-cafe] Code Review: Sudoku solver

2006-03-23 Thread David F. Place


Thanks for your helpful suggestions.  I took them to heart and  
incorporated many of them in a new version.




sudoku.hs
Description: Binary data



David F. Place
mailto:[EMAIL PROTECTED]

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


[Haskell-cafe] Question about Arrows and Computation by Paterson

2006-03-23 Thread Reilly Hayes

I've been taking a close look at the paper Arrows and Computation by
Ross Paterson.  It's not relevant to my question, but I'm doing this
because I think that Arrows may be a useful abstraction for a problem I
have (I need to both construct a computational pipeline AND perform a
computation over the pipeline itself).

The paper is published as Chapter 10 in The fun of Programming and is
also available here: http://www.soi.city.ac.uk/~ross/papers/fop.html

My question originates with the statement at the bottom of page 205 (the
5th page of the paper) regarding the behavior of the function 'first':
 ... while 'first' routes the state through f:.  My problem is that
this statement appears to be erroneous.  My reading of the code would
indicate that 'first' does not do this at all.  The state portion of the
Arrow remains unaltered.  Nor does it even seem desirable for 'first' to
have an impact on the state portion of the Arrow, as I would think that
this would preclude using 'first' and 'second' to lift binary operators
into the Arrow.  So what is it that am I missing?

The relevant code is as follows.  Paterson used Greek letters where I
have used Latin.  I represented his product operator with the letter x,
requiring surrounding backquotes.  If there are other changes to his
code I am unaware of them and they are an error on my part. 

class Arrow a where
  pure :: (b - c) - a b c
  () :: a b c - a c d - a b d
  first :: a b c - a (b,d) (c,d)

x :: (a - a') - (b - b') - (a,b) - (a',b')
(f `x` g) ~(a,b) = (f a, g b)

assoc :: ((a,b),c) - (a,(b,c))
assoc ~(~(a,b),c) = (a,(b,c))

unassoc :: (a,(b,c)) - ((a,b),c)
unassoc ~(a,~(b,c)) = ((a,b),c)

newtype State s i o = ST ((s,i) - (s,o))

instance Arrow (State s) where
  pure f  = ST (id `x` f)
  (ST f)  (ST g) = ST (g . f) 
  first (ST f) = ST (assoc . (f `x` id) . unassoc)


-Reilly Hayes



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


Re: [Haskell-cafe] Question about Arrows and Computation by Paterson

2006-03-23 Thread Ross Paterson
On Thu, Mar 23, 2006 at 09:20:10AM -0800, Reilly Hayes wrote:
 My question originates with the statement at the bottom of page 205 (the
 5th page of the paper) regarding the behavior of the function 'first':
  ... while 'first' routes the state through f:.  My problem is that
 this statement appears to be erroneous.  My reading of the code would
 indicate that 'first' does not do this at all.  The state portion of the
 Arrow remains unaltered.

Try this picture:

  (s,(b,d))
  |
  | unassoc
  v
((s,b),  d)
   | |
 f |  x  | id
   v v
((s',c), d)
  |
  | assoc
  v
  (s',(c,d))

The state type is not changed, but its value can be.  It is the second
part of the input (d) that is passed through.

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


Re: [Haskell-cafe] planet.haskell.org? for Haskell blogs

2006-03-23 Thread Antti-Juhani Kaijanaho

Isaac Jones wrote:

There's already software out there for this, so nothing new needs to
be written.  I think we need a volunteer to set this up somewhere?
Preferably someone with their own server, and we'll worry about
setting up the DNS later :)


Since nobody else seems to have volunteered, I'll try to set this up (if 
I can get the software working).


If you want your blog listed, email me. I will not add people without 
their consent.  Just tell me your RSS/Atom feed URI (try to pick one 
that will not contain non-English posts; but there is no need to 
restrict to just Haskell-related posts - half of the beauty is seeing 
what else people are doing and thinking).



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


Re: [Haskell-cafe] Re: how would this be done? type classes?existentialtypes?

2006-03-23 Thread Brian Hulley

Ben Rudiak-Gould wrote:

Brian Hulley wrote:

Is there a reason for using  instead of

  [exists a. Resource a=a]

?


Only that = looks like a function arrow,  looks like a tuple. I
stole this notation from an unpublished paper by SimonPJ et al on
adding existential quantification to Haskell. I'm not especially
attached to it. Actually I rather like

forall a | Resource a. a
exists a | Resource a. a




The bar is certainly consistent with the use in guards etc, but would lead 
to:


 exists a | (Show a, Eq a) . a

which looks a bit clunky because of the need for () as well because of the 
comma (to limit the scope of the comma). Also, it might be confusing to have 
to use a different notation to qualify type variables just because these 
type variables are being existentially qualified, when = is used everywhere 
else.

Personally I'd get rid of = altogether, and enclose constraints in {} eg

 foo :: forall a {Resource a} a  -- dot is optional after }
 bar :: {Show a, Eq a} a-Bool
 [exists a {Resource a} a]
 class {Monad m} MonadIO m where ...

This would fit into the rest of the syntax for Haskell as it stands at the 
moment.


[snip]


It is tricky, though. E.g. given (f (g z)) where

   f :: forall a. [a] - Int
   g :: String - (exists b. [b])

in principle you should be able to call g first, getting a type b and
a list [b], then instantiate f with the type b, then pass the list to
it, ultimately getting an Int. But I don't know how to design a type
inference algorithm that will find this typing. If on the other hand

   f :: (exists a. [a]) - Int

then it's easy to do the right thing---which is a little odd since
these two types for f are otherwise indistinguishable.


If the two types for f are indistinguishable, perhaps the forall in f's type 
could be converted into an existential as a kind of normal form before doing 
type inference?





Hope I'm not making this more confusing but I'm still trying to get
my head around all these invisible happenings regarding dictionaries
so I can visualise what's happening in terms of bytes and pointers
in the runtime


Once you understand where the types go in System F, the dictionaries
are easy: they always follow the types around. Any time you have

forall a b c. (C1 a b, C2 b c) = ...

in the source, you have five corresponding parameters/arguments in
GHC Core, one for each type variable and constraint. These are always
passed around as a unit (at least prior to optimization). In
principle you could box them in a 5-tuple. The dictionary values are
nothing more or less than proofs that the corresponding constraints
hold.


Thanks, this helps a lot,

Brian. 


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


Re: [Haskell-cafe] planet.haskell.org? for Haskell blogs

2006-03-23 Thread Antti-Juhani Kaijanaho

Antti-Juhani Kaijanaho wrote:
Since nobody else seems to have volunteered, I'll try to set this up (if 
I can get the software working).


If you want your blog listed, email me. I will not add people without 
their consent.  Just tell me your RSS/Atom feed URI (try to pick one 
that will not contain non-English posts; but there is no need to 
restrict to just Haskell-related posts - half of the beauty is seeing 
what else people are doing and thinking).


Now at http://antti-juhani.kaijanaho.fi/planet-haskell/ . This is 
obviously a temporary address (somebody set up a proper Haskell DNS for 
this; I can configure this to answer a particular domain name).


Also, submit your feeds!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] planet.haskell.org? for Haskell blogs

2006-03-23 Thread Isaac Jones
Antti-Juhani Kaijanaho [EMAIL PROTECTED] writes:

 Antti-Juhani Kaijanaho wrote:
 Since nobody else seems to have volunteered, I'll try to set this up
 (if I can get the software working).
 If you want your blog listed, email me. I will not add people
 without their consent.  Just tell me your RSS/Atom feed URI (try to
 pick one that will not contain non-English posts; but there is no
 need to restrict to just Haskell-related posts - half of the beauty
 is seeing what else people are doing and thinking).

 Now at http://antti-juhani.kaijanaho.fi/planet-haskell/ . This is
 obviously a temporary address (somebody set up a proper Haskell DNS
 for this; I can configure this to answer a particular domain name).

Cool, if you think you want to manage this, we can probably host it on
the hackage.haskell.org machine.  What would you think of that?

peace,

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


Re: [Haskell-cafe] planet.haskell.org? for Haskell blogs

2006-03-23 Thread Antti-Juhani Kaijanaho

Cool, if you think you want to manage this, we can probably host it on
the hackage.haskell.org machine.  What would you think of that?


I can host this just fine, I just want a better URI for it :)


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


Re: [Haskell-cafe] planet.haskell.org? for Haskell blogs

2006-03-23 Thread Antti-Juhani Kaijanaho

Isaac Jones wrote:

Cool, if you think you want to manage this, we can probably host it on
the hackage.haskell.org machine.  What would you think of that?


On the other hand, if it's easier for others, I'm not going to insist on 
hosting it myself. The host requires Python 2.3, GNU Arch and crontab 
access.



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


[Haskell-cafe] Building Monads from Monads

2006-03-23 Thread Daniel McAllansmith
Hi, I've got a few (9) random questions, mainly about monads and building 
monads from existing monads, partly trying to confirm conclusions I've come 
to through experimentation.

Any, and all, attempts to enlighten me will be much appreciated.

Thanks
Daniel

First, terminology.  In
StateT s (ReaderT r IO) ()
Q. 1) StateT is referred to as the outermost monad, and IO as the innermost 
monad, correct?



Using a monadic function, eg MonadReader.ask, in a monadic expression will 
access the outermost monad of the appropriate class.
Q. 2) Does this work for all monad classes in all expressions?



How does Control.Monad.Trans.lift work?  It seems that a single application of 
lift will find the next outermost monad of the appropriate class, but if you 
want to dig deeper into the nest you need to apply lift according to the 
monads actual depth in the nest.
Q. 3) Why the different behaviour?

Q. 4) Is it possible to give a type to the lifted function so that the monad 
of the correct class _and_ type is used?  E.g. dig into a String Reader 
rather than an Int Reader.

Defining an instance of MonadTrans for a monad instance seems universally 
useful.
Q. 5) Are there obvious situations where it's not useful or possible?



Carrying out IO in a nested monadic expression requires liftIO.  Apart from 
having to type an extra 7-9 characters it seems good to use liftIO even in 
plain IO monad expressions so they can become nested expressions with no 
trouble later on.
Q. 6) Is it safe to always use liftIO, even in plain IO monad?
Q. 7) If it's safe to do, why aren't functions in the IO monad just typed in 
the MonadIO class instead?



It looks to me like types with class constraints are better than types 
specifying nests of monad instances.  So
g :: (MonadReader String m, MonadState Int m, Monad m) = m ()
is better than
g :: StateT Int (Reader String) ()
because you can change the instance of the monadic class at will.  Also you 
can change the nesting order of the monads, though maybe that's not useful in 
practice.
The disadvantage seems to be that you can't use lift to access nested monads.
Q. 8) Is it possible to get access to nested monads when using class 
constraint types?



In the following code, the test2 function is not valid because there is no 
instance for (MonadCounter (ReaderT [Char] (StateT Word IO))), which is a 
fair enough complaint.
Q. 9) What allows ReaderT and StateT to be nested in arbitrary order but not 
ReaderT and CounterT?  Especially given CounterT is actually a StateT.


class (Monad m) = MonadCounter m where
increment :: m Word
decrement :: Word - m ()

type Counter = State Word

instance MonadCounter Counter where
increment = increment_
decrement = decrement_

runCounter :: Counter a - a
runCounter c = evalState c 0

type CounterT m = StateT Word m

instance (Monad m) = MonadCounter (CounterT m) where
increment = increment_
decrement = decrement_

runCounterT :: (Monad m) = CounterT m a - m a
runCounterT c = evalStateT c 0

increment_ :: (MonadState Word m) = m Word
increment_ = do
w - get
put (w + 5)
return w

decrement_ :: (MonadState Word m) = Word - m ()
decrement_ w = do
curW - get
if w  curW
then put 0
else put (curW - w)
return ()

test1 :: IO ()
test1 = runReaderT (runCounterT bar) blah

--test2 :: IO ()
--test2 = runCounterT (runReaderT bar blah)

bar :: (MonadReader String m, MonadCounter m, MonadIO m) = m ()
bar = do
w - increment
s - ask
liftIO $ putStrLn $ (show w) ++ s
return ()
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Positive integers

2006-03-23 Thread Daniel McAllansmith
Unless I've missed it, there is no typeclass for positive integers in GHC.
Is there any particular reason it doesn't exist?

Also, it seems Word would be a far better type in the likes of (!!), length, 
etc.  Is it just tradition that resulted in the use of Int?


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


[Haskell-cafe] Re: Positive integers

2006-03-23 Thread Aaron Denney
On 2006-03-24, Daniel McAllansmith [EMAIL PROTECTED] wrote:
 Unless I've missed it, there is no typeclass for positive integers in GHC.
 Is there any particular reason it doesn't exist?

The number of useable operations is small, and checks for leaving the
domain would have to be done all the time.  It basically doesn't buy
anything.

 Also, it seems Word would be a far better type in the likes of (!!), length, 
 etc.  Is it just tradition that resulted in the use of Int?

No.  I'd like to be able to get the differences in length both positive
and negative, for example.  (This could be fixed by making (+) and (-)
instance of an MPTC, though, as additive torsors.)

-- 
Aaron Denney
--

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


[Haskell-cafe] Define combination of type classes?

2006-03-23 Thread Fritz Ruehr
What is the easiest way to name a combination of type classes, i.e., to 
abbreviate the fact that a certain type is an instance of several 
classes simultaneously? I have a vague sense that this is do-able, but 
that I am messing up by trying to use an empty class body as below.


So in the code below, I try to use FooBar to abbreviate the conjunction 
of Foo and Bar. But while f (which uses a FooBar constraint) has a 
valid definition, it can't be used. On the other hand, g (which uses 
the long-winded constraint), is both a valid defined and useable.


(In a real example, imagine that FooBar names a conjunction of a half 
dozen things, so that the g-like form really is onerous, whereas the 
f-like form would be sweet and tidy :) .)


  --  Fritz

---

class Foo a where
  foo :: a - Int

class Bar a where
  bar :: a - a

class (Foo a, Bar a) = FooBar a

f :: FooBar a = a - Int
f a = foo (bar a)

g :: (Foo a, Bar a) = a - Int
g a = foo (bar a)

instance Foo Char where
  foo = ord

instance Bar Char where
  bar = id

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


Re: [Haskell-cafe] Re: Positive integers

2006-03-23 Thread Daniel McAllansmith
On Friday 24 March 2006 13:14, Aaron Denney wrote:
 On 2006-03-24, Daniel McAllansmith [EMAIL PROTECTED] wrote:
  Unless I've missed it, there is no typeclass for positive integers in
  GHC. Is there any particular reason it doesn't exist?

 The number of useable operations is small, and checks for leaving the
 domain would have to be done all the time.  It basically doesn't buy
 anything.

I can see the domain bounds check would be a problem in theory, but in 
practice doesn't the type enforce that?  Keeping Word positive costs nothing 
because it just overflows.  Wouldn't it be much the same?
Not that I'm really concerned about the absence, probably because of your 
other point.


  Also, it seems Word would be a far better type in the likes of (!!),
  length, etc.  Is it just tradition that resulted in the use of Int?

 No.  I'd like to be able to get the differences in length both positive
 and negative, for example.  (This could be fixed by making (+) and (-)
 instance of an MPTC, though, as additive torsors.)

An additive torsor is?

I'd maintain that the difference between two lengths is an entirely different 
quantity from the length of a list.  Though I'll admit the extra work 
converting to Integrals to get that quantity would be a pain, and probably 
not worth it.

I was more concerned about functions with Int as input, such as (!!), that can 
result in errors.
If practically feasible I would have preferred (!!) to take a Word rather than 
Int, even though you'd sometimes need bounds checks at fromInteger calls to 
be safe.


I suppose the 'correct' type for the index in (!!) would be
(Integral n, LowBounded n) = n
if such a low bound type class existed.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Define combination of type classes?

2006-03-23 Thread Sean Seefried


On 24/03/2006, at 12:45 PM, Fritz Ruehr wrote:

What is the easiest way to name a combination of type classes,  
i.e., to abbreviate the fact that a certain type is an instance of  
several classes simultaneously? I have a vague sense that this is  
do-able, but that I am messing up by trying to use an empty class  
body as below.


So in the code below, I try to use FooBar to abbreviate the  
conjunction of Foo and Bar. But while f (which uses a FooBar  
constraint) has a valid definition, it can't be used. On the other  
hand, g (which uses the long-winded constraint), is both a valid  
defined and useable.


(In a real example, imagine that FooBar names a conjunction of a  
half dozen things, so that the g-like form really is onerous,  
whereas the f-like form would be sweet and tidy :) .)




Hi Fritz!

You only need to do a couple of things to get this working. Add an  
instance declaration:


instance (Foo a, Bar a) = FooBar a

But for this to work you need to allow undecidable instances (and - 
fglasgow-exts).


To have this type class synonym trick work you need both the class  
and instance declaration:


class(Foo a, Bar a) = FooBar a
instance (Foo a, Bar a) = FooBar a

The first ensures that members of class FooBar will inherit the  
methods of classes Foo and Bar. The second ensures that if there is a  
Foo and a Bar instance then there will be a FooBar instance. You were  
lacking this in your code hence the error message:


 f 'a'

No instance for (FooBar Char)
  arising from use of `f' at interactive:1:0
Probable fix: add an instance declaration for (FooBar Char)
In the definition of `it': it = f 'a'

This is a neat trick. I've also used it to reduce onerous contexts.

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


Re: [Haskell-cafe] Re: Positive integers

2006-03-23 Thread Jared Updike
 An additive torsor is?

Surprisingly, there is a page on MathWorld about Torsors but it is
empty. Google turned up the following page with a good explanation.

http://math.ucr.edu/home/baez/torsors.html

 I'd maintain that the difference between two lengths is an entirely different
 quantity from the length of a list.

(Maybe this is a good example of what the term torsor captures.)

Thanks to Aaron for expanding our vocabulary.

  Jared.
--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Positive integers

2006-03-23 Thread Ben Rudiak-Gould

Daniel McAllansmith wrote:
I can see the domain bounds check would be a problem in theory, but in 
practice doesn't the type enforce that?  Keeping Word positive costs nothing 
because it just overflows.  Wouldn't it be much the same?


If you're planning wraparound semantics then you're better off with Int 
indexes. Passing an index congruent to -1 mod 2^32 is certainly an error, 
and (!!) may as well fail immediately rather than try to traverse 2^32-1 
list nodes. I think both Int and Word are equally correct here, since both 
are proper supersets of the valid set of indexes. (If you're working with 
lists so long that Int may not be big enough, you shouldn't trust Word either.)


Haskell 98's List module supplies generic versions of the list functions, 
like genericIndex :: Integral a = [b] - a - b, which will work with Word.


-- Ben

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


Re: [Haskell-cafe] Building Monads from Monads

2006-03-23 Thread Cale Gibbard
On 23/03/06, Daniel McAllansmith [EMAIL PROTECTED] wrote:
 Hi, I've got a few (9) random questions, mainly about monads and building
 monads from existing monads, partly trying to confirm conclusions I've come
 to through experimentation.

 Any, and all, attempts to enlighten me will be much appreciated.

 Thanks
 Daniel

 First, terminology.  In
 StateT s (ReaderT r IO) ()
 Q. 1) StateT is referred to as the outermost monad, and IO as the innermost
 monad, correct?

Yeah, that's the somewhat informal terminology. Probably better would
be that StateT is the outermost monad transformer, and IO is the
transformed monad, or base monad.

 Using a monadic function, eg MonadReader.ask, in a monadic expression will
 access the outermost monad of the appropriate class.
 Q. 2) Does this work for all monad classes in all expressions?

No, basically, applying ask will use the version of ask for your
particular monad. (Including all transformers.) Various instances of
MonadReader are used to automatically get reader instances on
transformed monads in various cases involving the MTL transformers,
but not in all cases. (Read the list of instances for MonadReader to
find out exactly which monad transformers preserve it.) If there's no
instance, you have to write one yourself. Also, when you're newtyping
a monad which is an instance of MonadReader, you can use newtype
deriving to get an instance for the newtype automatically.

 How does Control.Monad.Trans.lift work?  It seems that a single application of
 lift will find the next outermost monad of the appropriate class, but if you
 want to dig deeper into the nest you need to apply lift according to the
 monads actual depth in the nest.
 Q. 3) Why the different behaviour?

Lift is best understood via its type:

lift :: (MonadTrans t, Monad m) = m a - t m a

it simply takes a value in the base monad, and lifts it into the
transformed monad. When you have a stack of transformers, you may have
to apply it multiple times if you want to lift something up from one
monad, through a stack of transformations of that monad. For example,
I might be working in the
StateT Integer (ReaderT String IO)
monad, and want to get an analogue of (print Hello) which is of type
IO () in my monad. First I apply lift to it, to get a value in
(ReaderT String IO ()), then again to get something of type StateT
Integer (ReaderT String IO) ().

That's all it does - there's no magic with locating applications of
transformers or anything like that, it just goes one level each time.
However, there's also liftIO, which is a special case for when the
base monad is IO -- this lifts an IO action into any monad which is an
instance of MonadIO. This class is preserved by most monad
transformers, and is satisfied by IO, so the end result is like
applying lift enough times to bring an IO action up through as many
transformers as necessary, but without having to know how many
beforehand.


 Q. 4) Is it possible to give a type to the lifted function so that the monad
 of the correct class _and_ type is used?  E.g. dig into a String Reader
 rather than an Int Reader.

I'm not completely sure what you're after here -- basically, you just
lift things into whichever monad you're using. If you want to be
polymorphic, but insist on a particular instance of MonadReader,
that's easy enough, just put a constraint like (MonadReader String m)
or something similar on your type.


 Defining an instance of MonadTrans for a monad instance seems universally
 useful.
 Q. 5) Are there obvious situations where it's not useful or possible?


MonadTrans is only for monad transformers. Actual monads can't be
turned into transformers into any automatic way. However, in a lot of
cases, it's quite natural and obvious how to write a monad
transformer, such that applying that transformer to the identity monad
gives the monad you were thinking of (for example, writing code for
StateT instead of State), and when this is the case, you usually
should, since it's usually not much extra trouble, and it buys you a
lot of extra flexibility later.

 Carrying out IO in a nested monadic expression requires liftIO.  Apart from
 having to type an extra 7-9 characters it seems good to use liftIO even in
 plain IO monad expressions so they can become nested expressions with no
 trouble later on.
 Q. 6) Is it safe to always use liftIO, even in plain IO monad?

It's safe, sure, though a little awkward. It's easy enough to lift
whole IO computations later on anyway. The only benefit would be if
you wanted to later intersperse actions into the code which came from
a transformed version.

 Q. 7) If it's safe to do, why aren't functions in the IO monad just typed in
 the MonadIO class instead?

First of all, historical reasons -- the MTL is newer than the IO monad
by a good bit, and it doesn't exist in Haskell 98. While it would be
nice to have automatically lifted IO actions, it's actually fairly
rare that this actually gets in your way. The biggest problem