Monads in plain engllish (Was: Re: Licenses and Libraries)

1999-08-23 Thread felix


-Original Message-
From: Keith Wansbrough <[EMAIL PROTECTED]>
To: Ted Carroll <[EMAIL PROTECTED]>
Cc: Mark P Jones <[EMAIL PROTECTED]>; [EMAIL PROTECTED]
<[EMAIL PROTECTED]>; [EMAIL PROTECTED] <[EMAIL PROTECTED]>
Date: 23 August 1999 14:38
Subject: Re: Licenses and Libraries


>[..]
>> Ted C.
>>
>> P.S.  If somebody could explain Monads in plain english it might not
>> hurt either.
>
>Someone already has:
>
>http://www.dcs.gla.ac.uk/~nww/Monad.html
>
>--KW 8-)

Yes, that text is not bad, but I think it still has a problem (one I found
in two or
three other introductory texts of monads): it stops right before getting
really interesting!
The examples are probably well thought out, but they are either just toy
stuff or they
are to special. There are so many questions still open: how to declare an
instance of
the 'Monad' class (for using 'do'-constructs) combined with a plain
state-monad, for example.
The standard-prelude doesn't really contain any good examples. 'IO' is too
abstract
to be of any use. Yes, I can figure all that out (and I do, with some work)
but most certainly
someone else already did that.

Don't get me wrong here: I think Haskell is the culmination of decades of
Programming-
Language reasearch, but, coming from the LISP direction, I really have
trouble to adapt to
the totally different terminology found in functional programming.
Everything just looks
so darn complicated - even if you are basically just doing the same thing:
CONS, APPLY,
and LAMBDA.

felix

P.S.: Can someone point me to a good book on functional programming ? One
which
doesn't bore you with trivialities, but comes right to the point and
explains everything
with real-world examples ? Just the one book specially written for a stupid
LISPer
with bad grades in mathematics, like me ? :-)







Re: Still confused (was: Re: Type casting??)

1999-03-13 Thread Felix Schroeter

Hello again!

On Thu, Mar 11, 1999 at 08:09:54PM -0500, Steve Frampton wrote:
> [...]

> 1. Can I perform multiple statements on one line?  Eg.
>foo :: Int -> [Char]
>foo 0 = []
>foo x = b = x - 5 * 3; c = b * 5; foo(x - b * c)

>(The above is just a silly example...but you catch my meaning)

There are no statements in a functional language (except that
which is called statement as a component of the do-notation).

But the answer to what you obviously mean (judging from your
example) has already been given. (let or where)

> 2. I tried playing around with the foo function I was working with
>last time, and am getting a different error now:
>foo :: Int -> [Char]
>foo 0 = []
>foo x = ['1'] ++ foo(x div 10)

> [...]

That's a small syntactic mistake. Normal identifiers like foo, div, ...
are *never* infix operators. But you can turn every function of (at
least) two curried arguments into an infix operator by either giving
it an operator name (like ==), or enclosing the identifier in
backticks (like `div`). In fact, the latter would make your function
definition correct in my eyes.

Regards, Felix.





Re: TypeCasting??

1999-03-13 Thread Felix Schroeter

Hello!

On Thu, Mar 11, 1999 at 02:34:44PM -0800, Fritz K Ruehr wrote:
> [...]

> I highly recommend browsing the prelude for ideas on how to use
> Haskell. A few of the definitions are written in a more subtle
> fashion than you might want for this purpose (usually for generality
> or or efficiency), but many of them are very direct and readable.

And it's recommendable to browse the prelude to see what's already
available. There's no need to reinvent the wheels. And by using
prelude functions, the program gets shorter, more understandable.
And if the language implementor improves the prelude implementation,
all those programs profit from that which really *use* the
prelude.

> [...]

Regards, Felix.





Re: Type casting??

1999-03-13 Thread Felix Schroeter

Hello!

On Thu, Mar 11, 1999 at 12:13:21PM -0800, Craig Dickson wrote:
> [...]

> Absolutely not. It sounds like you're thinking you can call foo, have it
> generate a list of unknown type but known length, and then assign a type
> afterwards. You can't do that.

Yes you can, as there IS a value that is member of all types: bottom.

i.e.
foo n :: (Num a) => a -> [b]
foo n = take n (repeat bottom)
  where
bottom = bottom -- or undefined or error "bottom" or any other
-- concrete way to express bottom

Regards, Felix.





Re: Type casting??

1999-03-13 Thread Felix Schroeter

Hello!

Just a small nitpick:

On Thu, Mar 11, 1999 at 08:02:57PM +, [EMAIL PROTECTED] wrote:
> [...]

> the only thing you can do is to restrict something to have fewer types
> than it otherwise would have.

Or avoid restriction, in the case when the MR hits.

Such as:

fact = product . enumFromTo 1

Without an explicit type signature, this gets typed Integer -> Integer
(or Int -> Int pre H'98). But in fact, the principal type is
fact :: (Num a, Enum a) => a -> a

Regards, Felix.





Re: Semantics of generators

1999-01-31 Thread Felix Schroeter

Hello!

On Fri, Jan 22, 1999 at 01:14:43AM +1100, Jason Stokes wrote:
> Hi, this is kind of a novice question, but I hope it's OK to ask it here: what 
> precisely is the semantics of a generator?  The Haskell report mentions them, 
> but doesn't explain their semantics.

See section 3.11, "Translation".

> I understand how to use them in list 
> comprehensions, but I don't understand how generators can be applied to 
> arbitrary monads.  What does a generator applied to an arbitrary monad in a 
> monad comprehension do?  How can they be used?

It seems that in most cases except lists, the do notation seems
to be more natural than comprehensions, as comprehensions got
(re)restricted to lists (instead of monads in general) in the
Haskell 98 standard.

Perhaps with the Maybe monad or the parser monad (from the monadic
parser combinator library), one could imagine good uses of comprehensions.

Regards, Felix.






Re: PS

1999-01-30 Thread Felix Schroeter

Hello!

On Thu, Jan 28, 1999 at 06:36:57AM -0800, Simon Peyton-Jones wrote:
> I propose to remove Show (IO a) as well as Show (a->b),
> for the same reason

Looks good. But then, IMHO, interpreters should have special handling
for those types instead (run anything of type IO a, not only IO (),
as in H98, main is allowed to be of type IO a instead of IO (), anyway.
"magically" print something, if the interpreter doesn't know a Show
instance for some instance of a -> b).

Regards, Felix.






Re: Haskell 98 final stuff

1999-01-30 Thread Felix Schroeter

Hello!

On Thu, Jan 28, 1999 at 06:34:26AM -0800, Simon Peyton-Jones wrote:
> [...]

>  Fix defn of range for Int, Integer,
> Char.
> With Haskell 98 dot-dot notation, we must write:
> 
>   range (m,n)
>   | m < n = [m..n]
>   | otherwise = []
> 

Shouldn't the condition of the first guard be "m <= n"?

> [...]

Regards, Felix.





Re: Haskell 98 draft report

1998-12-02 Thread Felix Schroeter

Hello!

On Mon, Nov 23, 1998 at 08:42:39AM -0800, Simon Peyton-Jones wrote:

> I have now completed the draft report on Haskell 98, both language and
> libraries.  I have dated them both 'Draft: 1 Dec 1998'.

> [...]

You wrote "comments welcome", so I'll write some, based on the
list of changes.

3.11 (restricting monad comprehensions to list comprehensions)
Generally I don't like to lose generality without a strong
necessity. Can someone refer me to the rationale for that change?
I've found only a reference that there can be confusing (for people
in the process of learning Haskell) error messages. But then the
question arises if that should not perhaps be better remedied in
the compiler/interpreter systems.

Prelude:

filter is unoverloaded without a replacement, it seems.
How about mfilter in the Monad library module, defined as

mfilter   :: MonadPlus m => (a -> Bool) -> m a -> m a
mfilter p =  applyM (\x -> if p x then return x else mzero)

The rest looks fine to me.

Kind regards, Felix.





Re: Calling Java From Haskell

1998-11-14 Thread Felix Schroeter

Hello!

Only a few comments to your mappings.

On Fri, Nov 13, 1998 at 10:02:02AM -0500, S. Alexander Jacobson wrote:
> [...]
> Java  Haskell
> ---   ---
> Class Module
> Static method function

And IO tagged result, as the method may be impure.

> Instance  Module.Instance (Haskell data type)
> Instance Method   (Module.Instance ->) (function w/ instance arg)

And IO tagged result, as the method may be impure.

> get static variable   function w/ no args

In fact: get_varName :: IO , as the value can change

> set static variable set_varName::value->IO ()
> get instance variable varName::Instance->value

varName :: Instance -> IO value, as the value can change, again.

> set instance variable set_varName::Instance->value->IO()

Regards, Felix.





Re: topdelcs / decls

1998-10-24 Thread Felix Schroeter

Hello!

On Fri, Oct 23, 1998 at 01:44:58PM +0200, Johannes Waldmann wrote:
> > Your thought would destroy equational reasoning! For example you
> > would be able to define different equalties on the same data
> > structure. So Red==Black could be False in one place and True 
> > in another place. Does that make any sense? 

> well, yes and no, of course :-) 

> for instance, i could want to sort a list,
> according to two different criteria,
> using two different instances of Ord.

newtype IntFunnilyOrdered = IFO Int
instance Ord IntFunnilyOrdered where
  compare (IFO x) (IFO y) | even x && even y = compare x y
  | even x && odd y  = LT
  | odd x && even y  = GT
  | otherwise= compare x y
int_from_ifo (IFO x) = x

newtype IntReverse = IR Int
instance Ord IntReverse where
  compare (IR x) (IR y) = compare y x
int_from_ir (IR x) = x

Now, you can do
  map int_from_ir $ sort $ map IR l
or
  map int_from_ifo $ sort $ map IFO l

Ideally, the compiler should figure out that map IFO and map
int_from_ifo are essentially noops, except changing the class
instances to use.

Or use a function sortWith :: (a -> a -> Ordering) -> [a] -> [a]
and give it the ordering to use as parameter.

> moreover, i would need these instances only while sorting,
> so i would like to keep them local.

If you use the instances once, I think using something like sortWith
instead will be more elegant.

> [...]

> i fear there are more problems hidden. let's take this:

> data T = ...

> xx = let instance Ord T where ...
>x :: T = ...
>  in  x

> yy = let instance Ord T where ...
>   y :: T = ...
>  in y

> do xx and yy have the same type? yes and no, again,
> it looks like they belong to different (incomparable) subtypes of T.

> what about the expression (xx < yy)? which instance to use?
> none - on the outside it's not visible that T is any Ord instance, 
> so you cannot compare them at all.

Hmmm. So in your sorting example:

sort :: Ord a => [a] -> [a]
sort ... = ... < ...,

foo = let instance Ord T where compare ... = ... in sort (something::[T])

There's no Ord instance visible in the definition of sort.

And if you dynamically assign those instances and transport them to
sort, this becomes a real mind twist:

sort :: ... (as above)

somelist :: [T]
somelist = let instance Ord T where ... in (generate some list of values in T)

sortedlist :: [T]
sortedlist = let instance Ord T where [different from the above instance] in
  sort somelist

Now, which instance to usw? That bound to the values when they were
generated, i.e. that local to somelist? Or is that instance replaced by
that in sortedlist by that let instance binding?

That somehow twists my mind :-)

Regards, Felix.





Re: defined result

1998-09-16 Thread Felix Schroeter

Hello!

On Tue, Sep 15, 1998 at 01:16:49PM +0400, S.D.Mechveliani wrote:
> [...]

> At least, i think, this will be a good idea to consider the values 
> like [1..] as the defined results.

It *is* defined, when you consider "you can compute the WHNF in
finite time" as defined.

The WHNF of [1..] is 1:[2..].

> Also does  `let  f = f  in  f  :: Char'yield a defined result? 

This is not defined in the sense above, because it doesn't terminate
(when demanded).  Thus, denotationally, the value of that expression
is bottom.

Regards, Felix.





Re: Int vs Integer

1998-09-14 Thread Felix Schroeter

Hello!

On Sun, Sep 13, 1998 at 11:13:35PM +0100, Simon Marlow wrote:
> [...]

> The plan is to use something like

>   data Integer = Small Int# | Big { ... }

> where '...' is the GMP representation.  You then need a full set of
> [...]

Sounds fine. Just a question, will there remain an Int type (machine Ints,
boxed, w/o overflow checks) in addition to the new Integer implementation,
for those who explicitly declare something as Int to squeeze out the last
few cycles?

If yes, I think switching the default for Integral from Int to Integer
is a good thing :-)

Regards, Felix.





Re: Rambling on numbers in Haskell

1998-08-04 Thread Felix Schroeter

Hello!

On Mon, Aug 03, 1998 at 04:18:49PM +0200, Hans Aberg wrote:
> [...]

> with a complex unit $i$. More explicitly, the complexification $R_\C$ will
> consist of pairs $r + i s$, where $r, s \in R$, $i$ is a formal symbol, and
> addition, multiplication and so on uses the rules for the usual complex
> numbers.

>   So, why not add a type "Complexify(R)" of a ring R to Haskell?

Note that you can't divide in a ring. A type class *roughly* corresponding
to a ring is probably Num.

newtype Complexify t = Complexify (t,t)

instance Eq t => Eq (Complexify t) where
  (Complexify (r1,i1)) == (Complexify (r2,i2)) = (r1 == r2) && (i1 == i2)
  (Complexify (r1,i1)) /= (Complexify (r2,i2)) = (r1 /= r2) && (i1 /= i2)

instance Show t => Show (Complexify t) where
  showsPrec p (Complexify (r,i)) = showChar '(' . shows r . showChar ',' .
   shows i . showChar ')'

instance Num t => Num (Complexify t) where
  (Complexify (r1,i1)) + (Complexify (r2,i2)) = Complexify (r1+r2, i1+i2)
  (Complexify (r1,i1)) - (Complexify (r2,i2)) = Complexify (r1-r2, i1-i2)
  (Complexify (r1,i1)) * (Complexify (r2,i2)) =
Complexify (r1*r2-i1*i2, r1*i2+r2*i1)
  negate (Complexify (r,i)) = Complexify (-r,-i)
  -- abs and signum are a bit more difficult
  fromInteger a = Complexify (fromInteger a, 0)

That compiles with warnings that no methods for abs or signum are
defined.

Regards, Felix.