Re: Stylistic question about Haskell optional arguments

1999-08-18 Thread Marko Schuetz

Carl,

 "Carl" == Carl R Witty [EMAIL PROTECTED] writes:

Carl Paul Hudak [EMAIL PROTECTED] writes:
 One alternative is to use labelled fields.  In your example, if Html
 were an algebraic datatype such as:
 
  data Html = Type1 { align = Align, ... }
| Type2 { align = Align, ... }
| ...
 
  data Align = Left | Right | Center
 
 then instead of:
 
  h1 [align "right"] (stringToHtml "This is a Header")
 
 you could write:
 
  h1 (stringToHtml "This is a Header" { align = Right})
 
 or whatever, and you don't have the problem of dangling []'s, 
 since stringToHtml would preesumably provide a default allignment,
 and it is legal to have the same label in different constructors.

Carl I'm afraid this doesn't work.  There are two problems:

Carl 1) You need a constructor above:

 h1 (stringToHtml "This is a Header" (H1Args { align = Right}))

Carl or

 H1 { align = Right, html = stringToHtml "This is a Header" }

h1 (stringToHtml "This is a Header") { align = AlignRight}

works if h1 and stringToHtml are as follows

stringToHtml s = Text { text = s }

h1 h = H1 { inside = h }

Carl 2) Missing fields in a labeled field constructor are initialized to
Carl _|_ (bottom).  Thus, there's no safe way (in standard Haskell) to
Carl differentiate between

 H1 { align = Right, html = stringToHtml "This is a Header" }

Carl and

 H1 { html = stringToHtml "This is a Header" }

Carl Attempts to extract the "align" field and do something with it in the
Carl latter case will result in a run-time error.

But you could attach default alignment when converting any type to
Html

stringToHtml s = Text { align = defaultAlignment, text = s }

and propagate this as long as no other alignment is set, e.g

h1 h = H1 { align = align h, inside = h }

That way from 

h1 (stringToHtml "Test") { align = AlignRight }

you get

H1{align=AlignRight,inside=Text{align=AlignRight,text="Test"}}

and from 

(h1 (stringToHtml "Test")) { align = AlignRight }

you get

H1{align=AlignRight,inside=Text{align=AlignLeft,text="Test"}}

Marko

-- 
Marko Schütz[EMAIL PROTECTED]
http://www.ki.informatik.uni-frankfurt.de/~marko/





Re: Stylistic question about Haskell optional arguments

1999-08-18 Thread Paul Hudak

 Carl I'm afraid this doesn't work.  There are two problems:
 Carl 1) You need a constructor above:
  h1 (stringToHtml "This is a Header" (H1Args { align = Right}))
 Carl or
  H1 { align = Right, html = stringToHtml "This is a Header" }

and Marko replied:
 h1 (stringToHtml "This is a Header") { align = AlignRight}
 works if h1 and stringToHtml are as follows
 stringToHtml s = Text { text = s }
 h1 h = H1 { inside = h }

Actually, what I intended was this:

h1 ((stringToHtml "This is a Header") {align = Right})

but I left out the inner parens in my first message (sorry).  I think
that this is the simplest, and preserves Andy's original types.

 Carl 2) Missing fields in a labeled field constructor are initialized 
 Carl to _|_ (bottom).  Thus, there's no safe way (in standard
 Carl Haskell) to differentiate between

and Marko replied: 
 But you could attach default alignment when converting any type to
 Html
 stringToHtml s = Text { align = defaultAlignment, text = s }

Yes, this was my intention, as I remarked in my original message.

  -Paul





Re: Stylistic question about Haskell optional arguments

1999-08-18 Thread Carl R. Witty

Paul Hudak [EMAIL PROTECTED] writes:

  Carl I'm afraid this doesn't work.  There are two problems:
  Carl 1) You need a constructor above:
   h1 (stringToHtml "This is a Header" (H1Args { align = Right}))
  Carl or
   H1 { align = Right, html = stringToHtml "This is a Header" }
 
 and Marko replied:
  h1 (stringToHtml "This is a Header") { align = AlignRight}
  works if h1 and stringToHtml are as follows
  stringToHtml s = Text { text = s }
  h1 h = H1 { inside = h }
 
 Actually, what I intended was this:
 
 h1 ((stringToHtml "This is a Header") {align = Right})
 
 but I left out the inner parens in my first message (sorry).  I think
 that this is the simplest, and preserves Andy's original types.

Sorry about my message; I wasn't thinking straight.  (I forgot all
about the record update syntax, and only remembered the record
construction syntax.)

Carl Witty





Re: Stylistic question about Haskell optional arguments

1999-08-17 Thread Carl R. Witty

Paul Hudak [EMAIL PROTECTED] writes:

 One alternative is to use labelled fields.  In your example, if Html
 were an algebraic datatype such as:
 
  data Html = Type1 { align = Align, ... }
| Type2 { align = Align, ... }
| ...
 
  data Align = Left | Right | Center
 
 then instead of:
 
  h1 [align "right"] (stringToHtml "This is a Header")
 
 you could write:
 
  h1 (stringToHtml "This is a Header" { align = Right})
 
 or whatever, and you don't have the problem of dangling []'s, 
 since stringToHtml would preesumably provide a default allignment,
 and it is legal to have the same label in different constructors.

I'm afraid this doesn't work.  There are two problems:

1) You need a constructor above:

 h1 (stringToHtml "This is a Header" (H1Args { align = Right}))

or

 H1 { align = Right, html = stringToHtml "This is a Header" }

2) Missing fields in a labeled field constructor are initialized to
_|_ (bottom).  Thus, there's no safe way (in standard Haskell) to
differentiate between

 H1 { align = Right, html = stringToHtml "This is a Header" }

and

 H1 { html = stringToHtml "This is a Header" }

Attempts to extract the "align" field and do something with it in the
latter case will result in a run-time error.

Future versions of Haskell could address this using exception
handling, or by providing a default value for missing labels in
labeled field constructions.

Carl Witty





Re: Stylistic question about Haskell optional arguments

1999-08-17 Thread Keith Wansbrough

 I've got a stylistic question about Haskell.
 What's the best way to add optional arguments to a
 embedded DSL?
 
[..]
 --
 (1) Combinators takes a list of attributes.
Now we have
 
h1 :: [HtmlAttr] - Html - Html
 
and might write
 
 h1 [align "right"] (stringToHtml "This is a Header")
 
but now there are lots of [] scattered needlessly all over
the code.

 --

This is (as Tommy Thorn has already noted) what TkGofer and TclHaskell
use at present, and it seems quite convenient.  One clever thing is
done as well, to prevent illegal attributes being passed:

class Has_alt w where
  alt :: String - Conf w
  alt s = ...

class Has_align w where
  align :: Alignment - Conf w
  align a = ...

instance Has_alt IMG
instance Has_align IMG
instance Has_align H1

img :: URL- [Conf IMG] - HTML
h1  :: String - [Conf H1]  - HTML

img "purple.gif" [alt "purple picture", align Right]   -- OK
h1 "My heading" [align Left]   -- OK
h1 "My illegal heading" [align Left, alt "illegal"]-- type error


This is quite a cunning trick.

An override can be provided, too, as follows:

(%!) :: String - String - Conf w
tag %! val = ...

h1 "My illegal heading" [align Left, "alt" %! "illegal"]  -- OK


HTH.

--KW 8-)





Re: Stylistic question about Haskell optional arguments

1999-08-16 Thread Paul Hudak

One alternative is to use labelled fields.  In your example, if Html
were an algebraic datatype such as:

 data Html = Type1 { align = Align, ... }
   | Type2 { align = Align, ... }
   | ...

 data Align = Left | Right | Center

then instead of:

 h1 [align "right"] (stringToHtml "This is a Header")

you could write:

 h1 (stringToHtml "This is a Header" { align = Right})

or whatever, and you don't have the problem of dangling []'s, 
since stringToHtml would preesumably provide a default allignment,
and it is legal to have the same label in different constructors.

  -Paul





Re: Stylistic question about Haskell optional arguments

1999-08-16 Thread Andy Gill

Paul Hudak wrote:
 
 One alternative is to use labelled fields.  In your example, if Html
 were an algebraic datatype such as:
 
  data Html = Type1 { align = Align, ... }
| Type2 { align = Align, ... }
| ...
 
  data Align = Left | Right | Center
 
 then instead of:
 
  h1 [align "right"] (stringToHtml "This is a Header")
 
 you could write:
 
  h1 (stringToHtml "This is a Header" { align = Right})
 
 or whatever, and you don't have the problem of dangling []'s,
 since stringToHtml would preesumably provide a default allignment,
 and it is legal to have the same label in different constructors.

Interesting!

Consider:

   h1 { inside = stringToHtml "This is a header" }

for the normal case, and
  
  h1 { align = "right", inside = stringToHtml "This is a header" }

for the case with alignment.

Adding some combinators:

() :: Html - Html - Html
() h1 h2 = h1 { inside = h2 }

and we get
  h1  stringToHtml "This is a header"
  h1 { align = "right" }  stringToHtml "This is a header"

Now we've replaced [] with  :-)

However, this does seem more readable.

Andy