Re: [Haskell-cafe] Re: Control.Monad.Cont fun

2005-07-18 Thread Magnus Carlsson
Hi Thomas and Tomasz,

A late comment about a MonadFix instance for Cont/ContT:

Thomas Jäger wrote:
 Hello Tomasz,
 
 This stuff is very interesting! At first sight, your definition of
 getCC seems quite odd, but it can in fact be derived from its
 implementation in an untyped language.
 
 On 7/7/05, Tomasz Zielonka [EMAIL PROTECTED] wrote:
 

...

Besides sharing my happiness, I want to ask some questions:

- is it possible to define a MonadFix instance for Cont / ContT?
 
 It must be possible to define something that looks like a MonadFix
 instance, after all you can define generally recursive functions in
 languages like scheme and sml which live in a ContT r IO monad, but
 this has all kinds of nasty consequences, iirc.
 
 Levent Erkök's thesis suggests (pp. 66) that there's no implementation
 of mfix that satisfies the purity law.
 http://www.cse.ogi.edu/PacSoft/projects/rmb/erkok-thesis.pdf

A while ago, I attempted to marry value recursion a la Levent Erkök with
the continuation-monad transformer.  It seems possible if the underlying
monad has value recursion and references.  Interestingly, all mfix
properties except left shrinking appear to be valid.

There are slides about this (including implementation) at

  http://www.cse.ogi.edu/~magnus/mdo-callcc-slides.pdf

There is also a draft paper at

  http://www.cse.ogi.edu/~magnus/mdo-callcc.pdf

I should warn that the paper is still very unfinished.  If anyone is
interested in picking up the pieces together with me, please get in touch!

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


Re: [Haskell-cafe] Re: Control.Monad.Cont fun

2005-07-18 Thread Magnus Carlsson
Tomasz Zielonka wrote:
 On Fri, Jul 15, 2005 at 11:51:59PM +0200, Magnus Carlsson wrote:
 
A while ago, I attempted to marry value recursion a la Levent Erkök with
the continuation-monad transformer.  It seems possible if the underlying
monad has value recursion and references.  Interestingly, all mfix
properties except left shrinking appear to be valid.

There are slides about this (including implementation) at

  http://www.cse.ogi.edu/~magnus/mdo-callcc-slides.pdf

There is also a draft paper at

  http://www.cse.ogi.edu/~magnus/mdo-callcc.pdf
 
 
 I've already found your paper and played with the implementation :-)

:-)

 I was stupid to think that with MonadCont+MonadFix+getCC it would be
 possible to do forward jumps, but of course it doesn't work because of
 the strictness law.

I would expect forward jumps to work.  For example, consider

callcc (\k - mfix (\v - E))

where we assume that E is an expression in which k and v are free.

Then it would be OK for E to invoke k and thereby jump forward.  In
this case, the recursive value (bound to v) is simply bottom.

Moreover, suppose E in turn captures the current continuation and gives
it as an argument to k.  Then, it is possible to jump back inside E
again at a later point.  E might in this case return a non-bottom value,
which also would be the value of v.

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


RE: Syntax extensions (was: RE: The Future of Haskell discussion at the Haskell Workshop)

2003-09-11 Thread Magnus Carlsson
Mark P Jones writes an interesting suggestion:
 ...
  Hmm, ok, but perhaps you're worrying now about having to enumerate
  a verbose list of language features at the top of each module you
  write.  Isn't that going to detract from readability?  This is where
  the module system wins big!  Just define a new module that imports all
  the features you need, and then allows you to access them by a single
  name.  For example, you could capture the second feature set above
  in the following:
  
module HackersDelight where
import Extensions.Language.Mdo
import Extensions.Records.Structs
import Extensions.Types.RankN
import Extensions.Types.Multiparam
  
  Now the only thing you have to write at the top of a module that
  needs some or all of these features is:
  
import HackersDelight
 ...

Neat!  But maybe it is not always desirable to impose an extension on
the client of a module, just because the module itself needs it.  If
extensions were a kind of entity that can be mentioned in export and
import lists, we could write

  module HackersDelight(mdo,structs,rankN,multiparam) where
  import Extensions.Language(mdo)
  ...

Now, familiar mechanisms can be used from the module system.  In
particular, we can encode Hal's example (all extensions except
Template Haskell):

  import HackersDelight hiding (th)

/M
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: MonadCont, MonadFix

2002-03-09 Thread Magnus Carlsson

Ashley Yakeley writes:
  Are there any useful monads that are instances of both MonadCont and 
  MonadFix? I can't make the two meet. Perhaps this is because 
  continuations have no fixed point, or something. Very annoying.

If you have a recursive monad with first-class references (such as IO
or ST s), you can define a continuation monad on top of it with an
instance of MonadFix I enclose below.  The instance seems to make
sense operationally, but as Levent Erkök has pointed out, it doesn't
satisfy the left-shrinking axiom for recursive monads:

fixM (\x - a = f x)==a = \y - fixM (\x - f x y)

This axiom comes from Levent's and John Launchbury's ICFP'00
paper, see

  http://www.cse.ogi.edu/PacSoft/projects/rmb/

Moreover, I suspect that the instance breaks the axiom for callcc,
which shows how any evaluation context E can be pushed inside a
callcc:

   E[callcc e] = callcc (\k' - E[e (\z - k' (E[z]))]

This is for callcc without monadic types, see Sabry's and Friedman's
paper on Recursion is a Computational Effect, at

  http://www.cs.indiana.edu/hyplan/sabry/papers/

/M

--

class Monad m = FixMonad m where
  fixM :: (a - m a) - m a

class Monad m = Ref m r | m - r where
  newRef   :: a - m (r a)
  readRef  :: r a - m a
  writeRef :: r a - a - m ()

newtype C m a = C ((a - m ()) - m ())
deC (C m) = m

instance (FixMonad m, Ref m r) = FixMonad (C m) where
  fixM m = C $ \k - do
  x - newRef Nothing
  a - fixM $ \a - do
 deC (m a) $ \a - do
   ma - readRef x
   case ma of 
 Nothing - do writeRef x (Just a)
 Just _  - k a
 ma - readRef x
 case ma of
Just a - return a
Nothing - error fixM
  k a
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe



Re: O'Haskell OOP Polymorphic Functions

2001-01-16 Thread Magnus Carlsson

You can use overloading for the definition of theValue instead:

  class TheValue a where theValue :: a - Maybe Int

  instance TheValue Basewhere theValue _ = Nothing
  instance TheValue Derived where theValue x = Just (x.value)

/M

Ashley Yakeley writes:
  How do you do OOP-style polymorphic functions in O'Haskell? My first 
  attempt looked something like this:
  
  struct Base
  
  struct Derived  Base = 
   value :: Int
  
  theValue :: Base - Maybe Int
  theValue x = Just (x.value) -- problem line
  theValue _ = Nothing
  
  In the problem line, x is considered to be of type Base, so x.value gives 
  an error. I tried replacing it with
  
  theValue (x :: Derived) = Just (x.value)
  
  ...but that doesn't work either.
  
  -- 
  Ashley Yakeley, Seattle WA

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: O'Haskell OOP Polymorphic Functions

2001-01-16 Thread Magnus Carlsson

Ashley Yakeley writes:
  At 2001-01-16 10:23, Magnus Carlsson wrote:
  
  You can use overloading for the definition of theValue instead:
  
class TheValue a where theValue :: a - Maybe Int
  
instance TheValue Basewhere theValue _ = Nothing
instance TheValue Derived where theValue x = Just (x.value)
  
  Doesn't this imply that run-time type information is kept with the 
  structs?

The overloading is resolved statically, so no run-time type
information is needed. 

  
  Consider:
  
  d :: Derived
  d = struct
   value = 3
  
  b :: Base
  b = d
  
  idb :: Base - Base
  idb x = x
  
  f1 = theValue d
  f2 = theValue b
  f3 = theValue (idb d)
  f4 = theValue (idb b)
  
  What are the values of f1, f2, f3  f4?

f1 = Just 3
f2 = f3 = f4 = Nothing

  -- 
  Ashley Yakeley, Seattle WA

/M

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Language Feature Request: String Evaluation

1999-06-09 Thread Magnus Carlsson

S. Alexander Jacobson writes:
  In principle I can do this, but:
  1. how do I hide the import of show String to replace it w/ my own?
  2. If I do replce show String what else will break?

I'd rather let the preprocessor insert calls to eshow, and leave show
as it is.

  3. If instead I define an eshow function that strips "", how do I minimize
  the perforamnce hit of quote stripping?

Maybe you could make eshow a member in a class EShow, which defaults
to show, and make a special instance for Char (add a member eshowList).

  4. If I want to share my code, I have to share both the actual codebase as
  well as the preprocessor code.  This seems like sucha  basic language
  syntax issue that I shouldn't have to worry about which version of haskell
  your collaborators are running.  Everyone writing their own preprocessor
  will severely balkanize the language.

I think it's a good idea to use a preprocessor for experimenting with
your own language extensions. When (and if) the extensions settle and
turn out to be useful, you could consider proposing them as part of a
language definition.

  5. How does the use of this pre-processor interact w/ tools like Derive
  and PolyP which are also implemented as preprocessors?

I don't know. Buth the HacWrite preprocessor is simpleminded, it only
looks for the new text lexemes, and doesn't know about the Haskell
syntax. If you run such a preprocessor first, I think it would work.

  That being said, I would be happy to take a shot at HacWrite if it had a
  shot of becoming part of the language definition (or if it was a standard
  part of the various haskell distributions: ghc, hugs, hbc,etc.) and if
  Magnus would allow it.
  
  Is there a good lanugage reason to object to this feature?  It seems like
  a no brainer imprpovement.

I don't see any need to put something like this into the language
definition for the moment. But if you want to use HacWrite, I could
try to put it on some web page.

/M

  
  -Alex-
  
  
  ___
  S. Alexander JacobsonShop.Com
  1-212-697-0184 voice The Easiest Way To Shop
  
  On Tue, 8 Jun 1999, Lennart Augustsson wrote:
  
   "S. Alexander Jacobson" wrote:
   
HacWrite certainly seems like an improvement over Haskell.
However, it is just not as good as the scripting languages.
HacWrite still requires the author to differentiate between strings and
other types, still requires explicit use of show and still requires more
typing and curly balancing.  Isn't this nicer?
   
"insert into mytable values (NULL,'$var1','$(var2+var3)','$var3')
   
   
   So add your own little modification to HacWrite.  It would be easy enough
   to add $ interpolation.
   
   -- Lennart
   
   





Re: Language Feature Request: String Evaluation

1999-06-08 Thread Magnus Carlsson

I've been using a preprocessor to Haskell that I call HacWrite, which
adds a new kind of string appropriate for entering text.  Such strings
can span multiple lines and can be escaped using curly brackets:

  var1 = 2*2
  var2 = 4*var1
  var3 = «Foobar»
  sqlstring = «insert into mytable values
(NULL,'{show(var1)}','{show(var2)}','{var3}');»

Text is enclosed within «these characters» (which are hard to find on
my keyboard, so I let Emacs insert them when I press '"'). To support
markup, stuff that follows a space inside an escape is treated as
text:

   «This {bf sentence contains words in boldface}.»

Here, `bf' is a markup function from text to text.

I've found HacWrite quite useful for document writing (see
http://www.cs.chalmers.se/~hallgren/Thesis/ for a longer example :-),
but I'm sure it could be useful for CGI-scripting and the like as
well. 

/M

S. Alexander Jacobson writes:
  A popular thing to do with computer languages (especially scripting
  languages) is to  manipulate text and insert variables into strings.  
  It is extremely irritating to escape in and out of strings via ++ in
  Haskell or + in Java/Javascript.  
  e.g. 
   var1 = 2*2
   var2 = 4*var1
   var3 = "Foobar""
   sqlstring = "insert into mytable values "++
"(NULL,'"++(show var1)++"','"++(show var2)++"','"++var3"');"
  
  It would be much nicer if Haskell did what perl,php, and tcl do:
   sqlstring="insert into mytable values (NULL,'$var1','$var2','$var3')".
  Even nicer would be:
   sqlstring="insert into mytable values
(NULL,'$var1','$(var1+var2)','$var3')".
  
  (Notice both the embedded evaluation and the fact that the string runs
  accross multiple lines)
  
  Supporting this feature involves either:
  a. a syntactic transformation after you have type information (don't
  'show' strings)
  or 
  b. redefining show string not to return quotation marks
  
  To me the second makes more sense, but either way, this feature would make 
  haskell programming much less annoying.
  
  
  -Alex-
  
  PS Why does show string return quotation marks?  It seems inconsistent.
  
  ___
  S. Alexander JacobsonShop.Com
  1-212-697-0184 voice The Easiest Way To Shop





RE: Haskell-98 Quiz

1999-04-26 Thread Magnus Carlsson

Mark P Jones writes:
  | 2. Is there a way to modify the signatures to make it legal?
  
  Not that I can see!
  
  Personally, I think you've found a bug in the Haskell report!  But, as
  it stands, others can reasonably say this is a bug in Hugs 98 ... I guess
  we should modify the typechecker to reject this kind of program, at least
  when Hugs is running in Haskell 98 mode.  But it seems a shame to do all
  that work for a check that people might prefer to do without :-(

I think I prefer the Hugs 98 behaviour :-)

/M






Haskell-98 Quiz

1999-04-23 Thread Magnus Carlsson

Here are some questions for the Haskell-98 enthusiasts.

1. Why is the following declaration group illegal?

  f :: String
  f = g 1 ++ g True

  g :: Show a = a - String
  g x = fst (show x, show f)

2. Is there a way to modify the signatures to make it legal?

/M






2.01: Problem deriving instances for newtype data

1996-10-16 Thread Magnus Carlsson

When trying to derive an instance in a data declaration which depends
on a newtype ditto, I encountered:

  lips ghc-2.01 -c -v 
  Enter your Haskell program, end with ^D (on a line of its own):
newtype A = A Int deriving Show
data B = B A deriving Show
  ^D
  The Glorious Glasgow Haskell Compilation System, version 2.01 patchlevel 0

  Ineffective C pre-processor:
  echo '#line 1 "/tmp/ghc6530.hs"'  /tmp/ghc6530.cpp  cat /tmp/ghc6530.hs 
 /tmp/ghc6530.cpp

  real0.0
  user0.0
  sys 0.0

  Haskell compiler:
  
/usr/src/cs/pd/ghc/ghc-2.01-sparc-sun-solaris2/lib/ghc/2.01/sparc-sun-solaris2/hsc ,-W 
,/tmp/ghc6530.cpp  -fignore-interface-pragmas -fomit-interface-pragmas -fsimplify \(  
-ffloat-lets-exposing-whnf -ffloat-primops-ok -fcase-of-case -freuse-con 
-fpedantic-bottoms -fsimpl-uf-use-threshold0 -fessential-unfoldings-only 
-fmax-simplifier-iterations4 \)   -himap=/tmp/ghc6530.himap  -v 
-nohifile=/tmp/ghc6530.hi -S=/tmp/ghc6530.s +RTS -H600 -K100
  Glasgow Haskell Compiler, version 2.01, for Haskell 1.3


  "/tmp/ghc6530.hs", line 1: No instance for class `Show' at type `A' 

  "compiler-generated-code", line none: No instance for: Show A
  "compiler-generated-code", line none:
  at a use of an overloaded identifier: `Prelude.meth.Prelude.Show.showsPrec'


  Compilation had errors

  real3.9
  user2.9
  sys 0.7
  deleting... /tmp/ghc6530.hi /tmp/ghc6530.s

  rm -f /tmp/ghc6530*

/Magnus



Haskell 1.3 - what's it all about?

1996-05-16 Thread Magnus Carlsson

Maybe you have seen some mail lately on this list about something
called "Haskell 1.3", and wondered 

What is this "Haskell 1.3" anyway?,
Can I buy it?,
or
Do I have it?

By compiling and running the following two-module Haskell program, you
will at least get an answer to the last question.

-- Put in M.hs ---

module M where data M = M M | N ()

-- Put in Main.hs 

import M
main = interact (const (case (M.N) () of M (N ()) - "No\n"; N () - "Yes\n"))

---

Magnus  Thomas






Re: space leak in length[1..]

1996-02-17 Thread Magnus Carlsson


The problem is that the elements in the list [1..]  are not used by
the function lens, so they will not be evaluated. This is fatal, since
the unevaluated elements are becoming larger and larger function applications:

   [1..] = [1, 1+1, 1+1+1, ...]

For the same reasons, length [1..n] does not run in constant space.

By using a more strict definition of [1..], the space leak disappears:

 myFrom n = if n == n then t else t where t = n : myFrom (n+1)

 main = interact(("Enter stride: "++). unwords . map show .
 (flip lens)(myFrom 1) .
 fst . head . readDec)

Regards
/Magnus

Rex L. Page writes:
  
  length[1 .. n] seems to run in constant space (that is, space
  independent of n), as expected.
  
  However, length[1 ..] runs out of space.
  This doesn't seem reasonable to me.
   
  The following program, which computes length[1 ..]
  and reports its progress after every n-th element, also runs out of
  space, inexplicably to me.
  
   lens n = everyNth n . scanl (\n _ - n+1) 0
  
   everyNth n = map head . takeWhile(not.null) . iterate(drop n)
  
   main = interact(("Enter stride: "++). unwords . map show .
   (flip lens)[1 ..] .
   fst . head . readDec)
   
  With a stride of 1000, the program runs out of space 
  after 28,000 list elements with the default heap size in Hugs
  on my Unix (Sun) installation, and after 164,000 list elements under ghc.
  With larger strides, it runs out of space sooner on both Hugs and ghc.
   
  What's going on here? It appears to me that both length[1..] and the
  above definition of main should evaluate in constant space.
   
  Rex Page
[EMAIL PROTECTED]
School of Computer Science   405-325-4397
University of Oklahoma   fax 405-325-4044
Norman OK  73019-0631