Re: [Haskell-cafe] More documentation: how to create a Haskell project

2006-10-31 Thread Henning Thielemann

On Mon, 30 Oct 2006, David House wrote:

> On 30/10/06, Tony Morris <[EMAIL PROTECTED]> wrote:
> > 4) If you want links to base libraries in your haddock output, do "such
> > and such" (how do you do that anyway?)
> 
> I believe you need a local copy of the library sources, whose path you
> give to haddock with some flag.

No, haddock needs only .haddock files of the base libraries. I added some
support to Cabal. It currently fails if old style file names like
Data.List.html are installed, but a new haddock version links to new style
Data-List.html.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple GADT parser for the eval example

2006-10-31 Thread Ulf Norell


On Nov 1, 2006, at 1:32 AM, Greg Buchholz wrote:

Thanks to everyone who replied (especially Dimitrios Vytiniotis  
and

Joost Visser).  I now know the standard way to write the GADT parser.
But I'm still curious if anyone has comments pertaining to the version
using type classes.  It seems so close to doing what we want, and  
it is

pretty straightforward to implement.  The best way I can think to
describe it would be to say it uses the type system to find what it
should parse next, and dies of a pattern match failure if something
unexpected shows up, instead of checking to see if we can assemble a
type safe tree from pre-parsed parts (does that make any sense?).

I'm curious if there could be a small change to the type system to
make the fully general "my_read" possible, or if it suffers from an
incurable defect.


I'm not sure what you're asking, but it's possible to get

  my_read :: .. => Expr -> Term a

Previously given code:


-- Give a GADT for representation types
data R a where
  Rint :: R Int
  Rbool :: R Bool
  Rpair :: R a -> R b -> R (a,b)

-- Give an existential type with a type representation
data TermEx where
  MkTerm :: R a -> Term a -> TermEx

my_readEx :: Expr -> TermEx
getTerm   :: TermEx -> R a -> Term a


Given this you can define

> classRep awhere rep :: R a
> instance Rep Int  where rep = Rint
> instance Rep Bool where rep = Rbool
> instance (Rep a, Rep b) => Rep (a,b) where
>   rep = Rpair rep rep
>
> my_read :: Rep a => Expr -> Term a
> my_read e = getTerm (my_readEx e) rep

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


[Haskell-cafe] there's a monster in my Haskell!

2006-10-31 Thread Andrew Pimlott
To boost the popularity of Scheme, Felleisen has argued for renaming
"lambda" to "something cool, such as Funster".[1]  Likewise, Haskell
intimidates newcomers with the arcane term "monad".  Peyton Jones's
hopeful campaign to replace it with "warm fuzzy thing"[2] has so far
produced few results.  Inspired by Felleisen, and in the spirit of
Halloween, I offer a new alternative:  Meet "monsters", your
computational companions in the land of lazy functional programming.  To
illustrate this proposal, I present here a gentle introduction to
monsters.

Monsters come in great variety, each type having its own special powers.
But, as noted by Elmo[3], they are alike in an essential way.

All monsters are capable of devouring values:

devour :: Monster m => a -> m a

The result of "devour x" is simply a monster that has ingested the value
"x".

Most monsters have a weakness and can be slain, liberating some ingested
values or producing some other result.  The instrument of demise varies,
as do the possible outcomes, so this function is particular to a
monster.  If SomeMonster always yields a single value upon its demise,
we would have

slay :: SomeMonster a -> a

The compassionate (and fastidious) programmer defers the gruesome (and
messy) slaying while making use of the monster's special powers.  But
how to get at the monster's values short of that macabre act?
Fortunately, monsters gladly contribute their values towards the
creation of more monsters:

(>>=) :: Monster m => m a -> (a -> m b) -> m b

(>>=) should be read as the monster on the left expelling values through
its rows of teeth and over its tongue at the function on the right.
(Its pronunciation is a sort of bestial hissing that is difficult to
describe; when you say it correctly, the terminal may become slightly
moist.)

Monsters range from the tame to the tumultuous, but we cannot let them
run entirely amok.  All therefore must obey the "monster laws".  For
instance, the regurgitation law states that immediately after devouring
a value, a monster expels the same value:

devour x >>= k   ===   k x

We have still seen none of the promised special powers.  For that, we
must look at a particular monster.  The Either monster is defined as

data Either a b = Trick a | Treat b

This monster devours Treats, but if it doesn't get a Treat, it can play
a Trick:

playTrick :: t -> Trick t a
playTrick t = Trick t

This monster is commonly used as follows:

takeFood :: Food -> Either Mischief Food
takeFood Apple = playTrick eggHouse
takeFood Raisins   = playTrick tpTree
takeFood CandyCorn = devour CandyCorn

The divine among monsters is the mysterious and awesome IO.  Its powers
are vast, perhaps limitless, and beginners are taught that it cannot be
slain.  Like poisoned candy and release dates, this is of course a myth.
The pure of spirit may, after meditation at the altar of referential
transparency, cast the spell

:: IO a -> a

(When you are prepared to call this function, its name will be
revealed.)

The ST monster can be slain without esoteric ritual:

slay :: (forall s. ST s a) -> a

Yet philosophers whisper that there is something otherworldly about it,
a kinship with IO.  Eavesdropping on their debates, I hear the words
"phantom type", but that gives me the chills so I leave them.


[1] http://permalink.gmane.org/gmane.comp.lang.lightweight/3427
[2] http://research.microsoft.com/~simonpj/papers/haskell-retrospective/
[3] http://muppet.wikia.com/wiki/We%27re_All_Monsters
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Simple GADT parser for the eval example

2006-10-31 Thread Greg Buchholz
Thanks to everyone who replied (especially Dimitrios Vytiniotis and
Joost Visser).  I now know the standard way to write the GADT parser.
But I'm still curious if anyone has comments pertaining to the version
using type classes.  It seems so close to doing what we want, and it is
pretty straightforward to implement.  The best way I can think to
describe it would be to say it uses the type system to find what it
should parse next, and dies of a pattern match failure if something
unexpected shows up, instead of checking to see if we can assemble a
type safe tree from pre-parsed parts (does that make any sense?).

I'm curious if there could be a small change to the type system to
make the fully general "my_read" possible, or if it suffers from an
incurable defect. 

Thanks, 
Greg Buchholz 

> {-# OPTIONS -fglasgow-exts #-}  
> 
> main = print test
> 
> test :: Int 
> test = eval.my_read.read $
> "(EIf (EIsZ (ELit 0))  " ++
> " (EInc (ELit 1))  " ++
> " (EFst (EPair (ELit 42)   " ++
> "  (ELit 43"
> 
> class MyRead a where
> my_read :: Expr -> Term a 
> 
> instance MyRead Int where
> my_read (ELit a)= Lit a
> my_read (EInc a)= Inc (my_read a)
> my_read (EIf p t e) = If  (my_read p) (my_read t) (my_read e)
> my_read (EFst a)= Fst (my_read a :: Term (Int,Int))
> my_read (ESnd a)= Snd (my_read a :: Term (Int,Int))
> 
> instance MyRead Bool where
> my_read (EIsZ a)= IsZ (my_read a)
> my_read (EIf p t e) = If  (my_read p) (my_read t) (my_read e)
> my_read (EFst a)= Fst (my_read a :: Term (Bool,Bool))
> my_read (ESnd a)= Snd (my_read a :: Term (Bool,Bool))
> 
> instance (MyRead a, MyRead x) => MyRead (a,x) where
> my_read (EPair a b) = Pair (my_read a) (my_read b)
> my_read (EIf p t e) = If   (my_read p) (my_read t) (my_read e)
> 
> data Expr = ELit Int
>   | EInc Expr
>   | EIsZ Expr 
>   | EPair Expr Expr
>   | EIf Expr Expr Expr
>   | EFst Expr
>   | ESnd Expr
> deriving (Read,Show)
> 
> data Term a where
> Lit  :: Int -> Term Int
> Inc  :: Term Int -> Term Int
> IsZ  :: Term Int -> Term Bool
> If   :: Term Bool -> Term a -> Term a -> Term a
> Pair :: Term a -> Term b -> Term (a,b)
> Fst  :: Term (a,b) -> Term a
> Snd  :: Term (a,b) -> Term b 
>   
> eval :: Term a -> a
> eval (Lit i)= i
> eval (Inc t)= eval t + 1
> eval (IsZ t)= eval t == 0
> eval (If b t e) = if eval b then eval t else eval e
> eval (Pair a b) = (eval a, eval b)
> eval (Fst t)= fst (eval t)
> eval (Snd t)= snd (eval t)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: A type class puzzle

2006-10-31 Thread Arie Peterson

Greg Buchholz wrote:

> I guess it just looks really strange to my eyes.  For example, "foo"
> and "bar" are legal, but "baz" isn't.  That's what I was thinking of the
> situation, but I guess the type classes iron out the differences.

Ah, but here 'baz' is illegal because of the (somewhat arbitrary)
restriction that different lines of a function binding must have the same
number of "argument patterns". The different instances of 'BuildList' have
unrelated definitions of 'build\'' - at least as far as this restriction
is concerned.

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


Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Jacques Carette

Greg Buchholz wrote:

I guess it just looks really strange to my eyes.  For example, "foo"
and "bar" are legal, but "baz" isn't.  That's what I was thinking of the
situation, but I guess the type classes iron out the differences. 
  

foo :: Int -> Int -> Int -> Int
foo 0 = (+)

bar :: Int -> Int -> Int -> Int
bar 1 x = succ

baz :: Int -> Int -> Int -> Int
baz 0 = (+)
baz 1 x = succ




This could be understood as a weakness in the de-sugaring of 
pattern-matching, because


bong :: Int -> Int -> Int -> Int
bong 0 = (+)
bong 1 = \x -> succ

is just fine.

Jacques

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


Re: [Haskell-cafe] Accumulating related XML nodes using HXT

2006-10-31 Thread Albert Lai
Daniel McAllansmith <[EMAIL PROTECTED]> writes:

> Hello.
> 
> I have some html from which I want to extract records.  
> Each record is represented within a number of  nodes, and all records 
>  
> nodes are contained by the same parent node.

This is very poorly written HTML.  The original structure of the data
is destroyed - the parse tree no longer reflects the data structure.
(If a record is to be displayed in several rows, there are proper
ways.)  It is syntactically incorrect: nested , and color in .
(Just ask http://validator.w3.org/ .)  I trust that you are parsing
this because you realize it is all wrong and you want to
programmatically convert it to proper markup.

Since the file is unstructured, I choose not to sweat over restoring
the structure in an HXT arrow.  The HXT arrow will return a flat list,
just as the file is a flat ensemble.  The list looks like:

["/prod17", "Television", " (code: 17)", "A very nice telly.",
 "/prod24", "Cyclotron", " (code: 24)", "Mind your fillings."]

I then use a pure function to decompose this list four items at a time
to emit the desired records.  This is trivial outside HXT arrows.  I
use tuples, and every field is a string; you can easily change the
code to produce Prod's, turn " (code: 17)" into the number 17, etc.

Here is a complete, validated HTML 4 file containing the table, just
so that my program below actually has valid input.

http://www.w3.org/TR/html4/strict.dtd";>



Products




  
Product:
Television (code: 17)
  
  
Description:
A very nice telly.
  

  

  

  
Product:
Cyclotron (code: 24)
  
  
Description:
Mind your fillings.
  

  

  




Here is my program:

import Text.XML.HXT.Arrow

main =
do { unstructured <- runX (p "table.html")
   ; let structured = s unstructured
   ; print structured
   }

p filename =
readDocument [(a_parse_html,"1")] filename >>>
deep (isElem >>> hasName "table") >>>
getChildren >>> isElem >>> hasName "tr" >>>
getChildren >>> isElem >>> hasName "td" >>>
getChildren >>>
p1 <+> p2

p1 =
isElem >>> hasName "strong" >>>
getChildren >>> isElem >>> hasName "a" >>>
getAttrValue "href" <+> (getChildren >>> getText)

p2 =
getText

s (a:b:c:d: rest) = (a,b,c,d) : s rest
s _ = []
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Greg Buchholz
Arie Peterson wrote:
] I'm not sure I'm getting your point, but this is just because in the
] second instance, the second parameter of BuildList is 'a -> r', so the
] specific type of 'build\'' is '[a] -> a -> (a -> r)' which is just '[a] ->
] a -> a -> r' (currying at work).

I guess it just looks really strange to my eyes.  For example, "foo"
and "bar" are legal, but "baz" isn't.  That's what I was thinking of the
situation, but I guess the type classes iron out the differences. 

> foo :: Int -> Int -> Int -> Int
> foo 0 = (+)
> 
> bar :: Int -> Int -> Int -> Int
> bar 1 x = succ
> 
> baz :: Int -> Int -> Int -> Int
> baz 0 = (+)
> baz 1 x = succ

Greg Buchholz

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


Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Tomasz Zielonka
On Tue, Oct 31, 2006 at 03:12:53PM +0200, Yitzchak Gale wrote:
> But I would rather not be forced to write things like
> 
> >replace (I 0 $ I 2 $ I 3 $ ())
> 
> in my code. My first attempt was very similar to yours,
> except I used
> 
> >replace (0, (2, (3, (
> 
> instead of your Index type.

I started with it too, but I had to disambiguate the numeric type, eg.
by saying: (0 :: Int, (2 :: Int, (3 :: Int, (. Hmmm... I could solve
it without creating a new type.

> I don't like my solution, either.
> 
> So I guess I would define a full solution as something
> nice enough to be used in practice. Let's be more
> concrete - it has to be nice enough that most people
> who need, say, replace2 or replace3, in real life, would
> actually use your function instead of writing it out by hand.

I think that in pracice I would still prefer the version with
indices gathered in a single argument - it is a bit more uniform,
more first-class, etc. Hmmm... Haskell's Arrays are a good example.

> Maybe others would disagree, but so far, I personally
> do not use either your solution or my solution. I write it
> out by hand.

Well, I didn't yet have a need for such a function...

> >If you insist that each index should be given as a separate
> >function argument, it may be possible to achieve it using the tricks
> >that allow to write the variadic composition operator.
> 
> I am not familiar with that. Do you have a reference?

I think it's in one of Oleg's articles mentioned in other replies.

> Is that the best way to do it? (Is that a way to do it at all?)

I am not sure.

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


Re: [Haskell-cafe] hdbc linking errors

2006-10-31 Thread Jeff Polakow

Hello,

  I think my problem is a faulty
ghc installation and not HDBC. 

sorry for the noise,
  Jeff

 

[EMAIL PROTECTED] wrote on 10/31/2006
02:31:27 PM:

> 
> Hello, 
> 
> When trying to compile a standalone program using hdbc in cygwin,
I 
> get many linker errors. 
> I have no problems using my code interactively with ghci. 
> 
> I am using the command line: 
> 
>     ghc --make -package HDBC -package HDBC-odbc -O -o testExecute

> testExecute.hs 
> 
> Am I missing something? 
> 
> thanks 
>   Jeff 
> 
> --
> This e-mail may contain confidential and/or privileged information.

> If you are not the intended recipient (or have received this e-mail

> in error) please notify the sender immediately and destroy this e-
> mail. Any unauthorized copying, disclosure or distribution of the

> material in this e-mail is strictly forbidden. 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


--
This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden. ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Nicolas Frisby

Does that explain how, why, or when you can use more arguments than
you are allowed to use?  Or is it just another example of "using more
arguments than you are allowed to use"?  Is this a Haskell 98 thing, or
is it related to MPTCs, or fun deps, or something else?



I don't understand "you can use more arguments than you are allowed to use".

I doubt the work in Faking It is Haskell 98 because I'm pretty sure it
uses MPTCs, fundeps and undecidable instances. I think it does a bit
to introduce these concepts too if you're unfamiliar with them.

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


Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Arie Peterson

Greg Buchholz wrote:

> ...That first article is the strangest.  I couldn't reconcile the fact
> that if our type signature specifies two arguments, we can pattern
> match on three arguments in the function definition.  Compare the number
> of arguments in the first and second instances...
>
>> class BuildList a r  | r-> a where
>> build' :: [a] -> a -> r
>>
>> instance BuildList a [a] where
>> build' l x = reverse$ x:l
>>
>> instance BuildList a r => BuildList a (a->r) where
>> build' l x y = build'(x:l) y

I'm not sure I'm getting your point, but this is just because in the
second instance, the second parameter of BuildList is 'a -> r', so the
specific type of 'build\'' is '[a] -> a -> (a -> r)' which is just '[a] ->
a -> a -> r' (currying at work).


Regards,

Arie

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


Re: Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Greg Buchholz
Rearranging...

Nicolas Frisby wrote:
> On 10/31/06, Greg Buchholz <[EMAIL PROTECTED]> wrote:
> >...That first article is the strangest.  I couldn't reconcile the fact
> >that if our type signature specifies two arguments, we can pattern
> >match on three arguments in the function definition.  Compare the number
> >of arguments in the first and second instances...
>
> See
>  Connor McBride's "Faking It: Simulating Dependent Types in Haskell"
>  http://citeseer.ist.psu.edu/mcbride01faking.html
> 
> It might help; your example makes me think of the "nthFirst" function.
> If it's different, I'md wager the polyvariadic stuff and nthFirst can
> be reconciled on some level.

Does that explain how, why, or when you can use more arguments than
you are allowed to use?  Or is it just another example of "using more
arguments than you are allowed to use"?  Is this a Haskell 98 thing, or
is it related to MPTCs, or fun deps, or something else?

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


[Haskell-cafe] hdbc linking errors

2006-10-31 Thread Jeff Polakow

Hello,

When trying to compile a standalone
program using hdbc in cygwin, I get many linker errors. 
I have no problems using my code interactively
with ghci.

I am using the command line: 

    ghc --make -package HDBC
-package HDBC-odbc -O -o testExecute testExecute.hs

Am I missing something?

thanks
  Jeff


--
This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden. ___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Nicolas Frisby

See
 Connor McBride's "Faking It: Simulating Dependent Types in Haskell"
 http://citeseer.ist.psu.edu/mcbride01faking.html

It might help; your example makes me think of the "nthFirst" function.
If it's different, I'md wager the polyvariadic stuff and nthFirst can
be reconciled on some level.

Nick

On 10/31/06, Greg Buchholz <[EMAIL PROTECTED]> wrote:

Yitzchak Gale wrote:
> Tomasz Zielonka wrote:
> >If you insist that each index should be given as a separate
> >function argument, it may be possible to achieve it using the tricks
> >that allow to write the variadic composition operator.
>
> I am not familiar with that. Do you have a reference?
> Is that the best way to do it? (Is that a way to do it at all?)

  You might find these articles somewhat related...

Functions with the variable number of (variously typed) arguments
http://okmij.org/ftp/Haskell/types.html#polyvar-fn

Deepest functor [was: fmap for lists of lists of lists of ...]
http://okmij.org/ftp/Haskell/deepest-functor.lhs

...That first article is the strangest.  I couldn't reconcile the fact
that if our type signature specifies two arguments, we can pattern
match on three arguments in the function definition.  Compare the number
of arguments in the first and second instances...

> class BuildList a r  | r-> a where
> build' :: [a] -> a -> r
>
> instance BuildList a [a] where
> build' l x = reverse$ x:l
>
> instance BuildList a r => BuildList a (a->r) where
> build' l x y = build'(x:l) y

...if you try something like...

foo :: [a] -> a -> r
foo l x y = undefined

...you'll get an error message like...

The equation(s) for `foo' have three arguments,
but its type `[a] -> a -> r' has only two


YMMV,

Greg Buchholz

___
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] A type class puzzle

2006-10-31 Thread Greg Buchholz
Yitzchak Gale wrote:
> Tomasz Zielonka wrote:
> >If you insist that each index should be given as a separate
> >function argument, it may be possible to achieve it using the tricks
> >that allow to write the variadic composition operator.
> 
> I am not familiar with that. Do you have a reference?
> Is that the best way to do it? (Is that a way to do it at all?)

  You might find these articles somewhat related...

Functions with the variable number of (variously typed) arguments
http://okmij.org/ftp/Haskell/types.html#polyvar-fn

Deepest functor [was: fmap for lists of lists of lists of ...]
http://okmij.org/ftp/Haskell/deepest-functor.lhs

...That first article is the strangest.  I couldn't reconcile the fact
that if our type signature specifies two arguments, we can pattern
match on three arguments in the function definition.  Compare the number
of arguments in the first and second instances...

> class BuildList a r  | r-> a where
> build' :: [a] -> a -> r
>
> instance BuildList a [a] where
> build' l x = reverse$ x:l
>
> instance BuildList a r => BuildList a (a->r) where
> build' l x y = build'(x:l) y

...if you try something like...

foo :: [a] -> a -> r
foo l x y = undefined

...you'll get an error message like...

The equation(s) for `foo' have three arguments,
but its type `[a] -> a -> r' has only two


YMMV,

Greg Buchholz

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


[Haskell-cafe] Why is Haskell not homoiconic?

2006-10-31 Thread Henning Sato von Rosen

Hi all!

I am curious as to why Haskell not is homoiconic?
I am interested in the reasons behind that design descision.


I ask using this defintion og homiconicity:
Homiconic means that "the primary representation of programs is also a
data structure in a primitive type of the language itself" --
http://en.wikipedia.org/wiki/Homoiconic
Examples: LISP, Rebol, Natural Languages...

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


[Haskell-cafe] Re: Why is Haskell not homoiconic?

2006-10-31 Thread Stefan Monnier
>> Homiconic means that "the primary representation of programs is also a
>> data structure in a primitive type of the language itself"

> The main reason is that Haskell is designed as a compiled
> language, so the source of the programme can safely
> disappear at runtime.  So there's no need to have a
> representation of it beyond the source code.

I'm not sure it's relevant.  In syntactically scoped Lisps, the code is
mostly manipulated at compile-time by macros, rather than at run-time.

And indeed, Template Haskell makes Haskell pretty much "homoiconic".


Stefan

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


[Haskell-cafe] Re: Why is Haskell not homoiconic?

2006-10-31 Thread Jón Fairbairn
"Henning Sato von Rosen" <[EMAIL PROTECTED]> writes:

> Hi all!
> 
> I am curious as to why Haskell not is homoiconic?

It very nearly is. The icon for Haskell is a lower-case
lambda, but the logo for these folk
http://www.ualberta.ca/~cbidwell/cmb/lambda.htm is an
upper-case lambda.

> Homiconic means that "the primary representation of programs is also a
> data structure in a primitive type of the language itself"

Oh, dear, that renders my remark above irrelevant ;-0

The main reason is that Haskell is designed as a compiled
language, so the source of the programme can safely
disappear at runtime.  So there's no need to have a
representation of it beyond the source code. 

-- 
Jón Fairbairn [EMAIL PROTECTED]

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


Re: [Haskell-cafe] Why is Haskell not homoiconic?

2006-10-31 Thread Jerzy Karczmarczuk

Henning Sato von Rosen wrote:


I am curious as to why Haskell not is homoiconic?
I am interested in the reasons behind that design descision.


I ask using this defintion og homiconicity:
Homiconic means that "the primary representation of programs is also a
data structure in a primitive type of the language itself" --
http://en.wikipedia.org/wiki/Homoiconic
Examples: LISP, Rebol, Natural Languages...


Could you say why do you think Haskell SHOULD belong to this class?

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


[Haskell-cafe] Monad.Reader Licensing (Re: [Haskell] The Monad.Reader - Call for Copy)

2006-10-31 Thread Conrad Parker
Hi,

On Tue, Oct 31, 2006 at 12:10:21PM +, Wouter Swierstra wrote:
> 
>   * License: The entire magazine should be published under a  
> Creative Commons Attribution 2.5 License. This makes it much easier  
> to publish, distribute, teach, and share the Reader. This license  
> allows anyone to use the work in any way they seem fit as long as  
> credit is given to the original author.

Given that articles written in LaTeX are likely to be written in literate
Haskell (yay!), it's quite likely that their contents will be incorporated
into software.

Others have expressed misgivings about the use of the CC Attribution
license for software. Usually the issue is that the method of attribution
is unclear: the license leaves it up to the original author of each
article to specify how they should be attributed (or not), and has some
vague terms regarding "comparable authorship credit".

A more detailed summary is at http://people.debian.org/~evan/ccsummary which
suggests that such works would not be distributable by the Debian project.

I suggest that articles in the Monad.Reader be BSD3 licensed, which
has similar intent but clearer rules for incorporation in software.

Besides, CC-BY-2.5 is not a member of Distribution.License in Cabal ;-)

cheers,

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


Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Yitzchak Gale

Tomasz Zielonka wrote:

It's quite easy if you allow the indices to be put in a
single compound value.


Hmm. Well, I guess I don't need to insist on the exact
type that I gave in the statement of the puzzle - although
something like that would be the nicest.

This is actually a function that is useful quite often in
practice. But I would rather not be forced to write things
like


replace (I 0 $ I 2 $ I 3 $ ())


in my code. My first attempt was very similar to yours,
except I used


replace (0, (2, (3, (


instead of your Index type. I don't like my solution, either.

So I guess I would define a full solution as something
nice enough to be used in practice. Let's be more
concrete - it has to be nice enough that most people
who need, say, replace2 or replace3, in real life, would
actually use your function instead of writing it out by hand.

Maybe others would disagree, but so far, I personally
do not use either your solution or my solution. I write it
out by hand.


If you insist that each index should be given as a separate
function argument, it may be possible to achieve it using the tricks
that allow to write the variadic composition operator.


I am not familiar with that. Do you have a reference?
Is that the best way to do it? (Is that a way to do it at all?)

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


[Haskell-cafe] Re : Tutorial: Writing a Lisp Interpreter In Haskell

2006-10-31 Thread minh thu

Thanks for pointing it !

(There's also this one:
http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/overview.html
which is featured on the Tools and Libraries/Compilers and
Interpreters page of the haskell wiki)

bye,
minh thu

2006/10/31, Donald Bruce Stewart <[EMAIL PROTECTED]>:

People might be interested in a new tutorial that's just appeared in
blogspace, by coffeemug (of #haskell):

http://www.defmacro.org/ramblings/lisp-in-haskell.html

Also, its on reddit, http://programming.reddit.com/info/oj1w/details

An enthusiastic view of the language from a newcomer's perspective.

-- Don
___
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


[Haskell-cafe] Tutorial: Writing a Lisp Interpreter In Haskell

2006-10-31 Thread Donald Bruce Stewart
People might be interested in a new tutorial that's just appeared in
blogspace, by coffeemug (of #haskell):

http://www.defmacro.org/ramblings/lisp-in-haskell.html

Also, its on reddit, http://programming.reddit.com/info/oj1w/details 

An enthusiastic view of the language from a newcomer's perspective.

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


Re: [Haskell-cafe] Simple GADT parser for the eval example

2006-10-31 Thread Ulf Norell


On Oct 31, 2006, at 2:19 AM, Dimitrios Vytiniotis wrote:


-- Give a GADT for representation types
data R a where
  Rint :: R Int
  Rbool :: R Bool
  Rpair :: R a -> R b -> R (a,b)

-- Give an existential type with a type representation
data TermEx where
  MkTerm :: R a -> Term a -> TermEx

-- we use Weirich's higher-order type-safe cast to avoid deep  
traversals

-- one can replace the type_cast with a more simple traversal-based
-- version.


...complicated higher order stuff...

For instance:

> data a :==: b where
>   Refl :: a :==: a
>
> (===) :: Monad m => R a -> R b -> m (a :==: b)
> Rint  === Rint  = return Refl
> Rbool  === Rbool = return Refl
> Rpair a b === Rpair c d = do
> Refl <- a === c
> Refl <- b === d
> return Refl
> a === b = fail $ show a ++ " =/= " ++ show b
>
> cast :: a :==: b -> c a -> c b
> cast Refl x = x

In particular one wants to extract the Term part of a TermEx:

> getTerm :: Monad m => TermEx -> R a -> m (Term a)
> getTerm (MkTerm r' t) r = do
>   Refl <- r === r'
>   return t

/ Ulf

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


Re: [Haskell-cafe] A type class puzzle

2006-10-31 Thread Tomasz Zielonka
On Tue, Oct 31, 2006 at 11:02:03AM +0200, Yitzchak Gale wrote:
> Consider the following sequence of functions
> that replace a single element in an n-dimensional
> list:
> 
> replace0 :: a -> a -> a
> replace1 :: Int -> a -> [a] -> [a]
> replace2 :: Int -> Int -> a -> [[a]] -> [[a]]

> Generalize this using type classes.

It's quite easy if you allow the indices to be put in a single compound
value. If you insist that each index should be given as a separate
function argument, it may be possible to achieve it using the tricks
that allow to write the variadic composition operator.

Here's my version using MPTCs and fundeps:

data Index t = I Int t

class Replace i l a | i a -> l where
replace :: i -> a -> l -> l

instance Replace () a a where
replace _ = const

instance Replace i l a => Replace (Index i) [l] a where
replace (I i0 is) x xs
| null t= h
| otherwise = h ++ (replace is x (head t) : tail t)
  where (h, t) = splitAt i0 xs

Example use:

*Nested> :t replace (I 0 $ I 2 $ I 3 $ ()) "qweqwe"
replace (I 0 $ I 2 $ I 3 $ ()) "qweqwe" :: Char -> Char


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


[Haskell-cafe] A type class puzzle

2006-10-31 Thread Yitzchak Gale

Consider the following sequence of functions
that replace a single element in an n-dimensional
list:

replace0 :: a -> a -> a
replace0 = const

replace1 :: Int -> a -> [a] -> [a]
replace1 i0 x xs
| null t= h
| otherwise = h ++ (replace0 x (head t) : tail t)
where (h, t) = splitAt i0 xs

replace2 :: Int -> Int -> a -> [[a]] -> [[a]]
replace2 i0 i1 x xs
| null t= h
| otherwise = h ++ (replace1 i1 x (head t) : tail t)
where (h, t) = splitAt i0 xs

etc.

Generalize this using type classes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Guidelines for proposing library changes

2006-10-31 Thread Ross Paterson
On Wed, Oct 25, 2006 at 11:58:59AM +1000, Donald Bruce Stewart wrote:
> After some discussion on the libraries list, I've put up the suggested
> 'best practice' for proposing library changes, here:
> 
> http://haskell.org/haskellwiki/Library_submissions 
> 
> The idea is to reduce the number of 'bikeshed' discussions we're having, 
> ensure that submissions are not dropped, and generally improve
> productivity.
> 
> People should refer to this when proposing new functions for the core
> libraries, at risk of not having the suggestion adopted or considered ;)

Perhaps it would be kinder to the mail system to suggest attaching the
patch to the ticket instead of mailing it.  These patches to base are
quite big, and are causing trouble.  And if we could get the ticket mail
sent to libraries instead of ghc-users, that would make the procedure
simpler, too.

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


[Haskell-cafe] Re: Simple GADT parser for the eval example

2006-10-31 Thread Stefan Monnier
> ...No surprise there, since there is no way to fail in the event of a
> maltyped "Expr".  The next thing to try is a type class solution... 

Think about it: you need to do type checking.
For our little language we used Template Haskell to do your "Expr -> Term a"
translation, thus the type-checking of our input programs is actually done
by Haskell's type checker ;-)

See our PLPV paper http://www.iro.umontreal.ca/~monnier/tct.pdf


Stefan

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