Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-20 Thread Bas van Dijk
On Wed, Jan 14, 2009 at 3:59 PM, Manlio Perillo
manlio_peri...@libero.it wrote:
 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

I just like to point out the dependently typed, Haskell-like,
programming language Agda[1] which has a very nice module system with
the following features:

 * Modules can contain other modules

 * Modules can be locally opened. For example:
   mapMaybe f m = let open Maybe in maybe nothing (just . f) m

 * Renaming of important names: For example:
   open Maybe renaming (Maybe to option; nothing to none; just to some)

 * Parameterized modules: For example:

   module Sort (A : Set) (__ : A - A - Bool) where
 insert : A - List A - List A
 insert y [] = y :: []
 insert y (x :: xs) with x  y
 ... | true  = x :: insert y xs
 ... | false = y :: x :: xs

See section 2.7 of the following Agda tutorial (an open minded Haskell
hacker should be able to read that section on its own):

http://www.cs.chalmers.se/~ulfn/darcs/AFP08/LectureNotes/AgdaIntro.pdf

Hopefully Haskell can borrow some of these ideas sometime.

regards,

Bas

[1] http://wiki.portal.chalmers.se/agda/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-20 Thread Lennart Augustsson
Yes, the Agda modules remind me of Cayenne. :)

On Tue, Jan 20, 2009 at 12:54 PM, Bas van Dijk v.dijk@gmail.com wrote:
 On Wed, Jan 14, 2009 at 3:59 PM, Manlio Perillo
 manlio_peri...@libero.it wrote:
 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

 I just like to point out the dependently typed, Haskell-like,
 programming language Agda[1] which has a very nice module system with
 the following features:

  * Modules can contain other modules

  * Modules can be locally opened. For example:
   mapMaybe f m = let open Maybe in maybe nothing (just . f) m

  * Renaming of important names: For example:
   open Maybe renaming (Maybe to option; nothing to none; just to some)

  * Parameterized modules: For example:

   module Sort (A : Set) (__ : A - A - Bool) where
 insert : A - List A - List A
 insert y [] = y :: []
 insert y (x :: xs) with x  y
 ... | true  = x :: insert y xs
 ... | false = y :: x :: xs

 See section 2.7 of the following Agda tutorial (an open minded Haskell
 hacker should be able to read that section on its own):

 http://www.cs.chalmers.se/~ulfn/darcs/AFP08/LectureNotes/AgdaIntro.pdf

 Hopefully Haskell can borrow some of these ideas sometime.

 regards,

 Bas

 [1] http://wiki.portal.chalmers.se/agda/
 ___
 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] some ideas for Haskell', from Python

2009-01-20 Thread George Pollard
On Wed, 2009-01-14 at 15:59 +0100, Manlio Perillo wrote:
 1) In a Python string it is available the \U{name} escape, where name is
 a character name in the Unicode database.
 
 As an example:
 foo = uabc\N{VULGAR FRACTION ONE HALF}

This is possible via QuasiQuotation, you can write a parser that will
let you do it like this:

foo = [$s|abc\N{VULGAR FRACTION ONE HALF}|]

I started to write one but got stuck :P By working from the wiki page
[1] I ended up with some code that will let you do:

let e = 3 in [$s|h\V{e}llo\U{32}world|] == h3llo world

I got stuck on a few things:
- how best to allow arbitrary expressions (requires additional parsing
to allow braces inside strings and so on, e.g. [$s|hello \E{}}
world|])
- can't figure out how to write the quoting function for the patterns...
this would be awesome if it worked:

everythingAfterFirstK [$s|\V{before}k\V{after}|] = after

- there's no library for looking up characters by name. 'unicode-names'
has getCharacterName but not the inverse.

Code follows:

StringSplicer.hs
 {-# LANGUAGE DeriveDataTypeable #-}
 
 module StringSplicer 
 where
 
 import Data.Generics
 import Text.ParserCombinators.Parsec
 import Control.Monad
 
 data Exp = StringLit String
   | Unicode Int
   | Variable String
   | Backslash
   deriving (Show, Typeable, Data)
 
 interp = do
   char '\\'
   c - choice [char 'U', char 'V', char '\\']
   case c of
   'U' - do
   char '{'
   n - many1 digit
   char '}'
   return $ Unicode (read n)
   'V' - do
   char '{'
   s - manyTill anyChar (try $ char '}')
   return $ Variable s
   '\\' - return Backslash
 
 str = do
   s - many1 $ noneOf ['\\']
   return $ StringLit s
 
 expr = many $ interp | str
 
 parseString :: Monad m = (String, Int, Int) - String - m [Exp]
 parseString (file, line, col) s =
   case runParser p ()  s of
   Left err - fail $ show err
   Right e - return e
   where
   p = do
   pos - getPosition
   setPosition $
   (flip setSourceName) file $
   (flip setSourceLine) line $
   (flip setSourceColumn) col $
   pos
   e - expr
   eof
   return e

StringSplicer.Quote.hs
 module StringSplicer.Quote
 where
 
 import Data.Generics
 import qualified Language.Haskell.TH as TH
 import Language.Haskell.TH.Quote
 import Data.Char (chr)
 import StringSplicer
 
 quoteExprExp :: String - TH.ExpQ
 quoteExprPat :: String - TH.PatQ
 
 s :: QuasiQuoter
 s = QuasiQuoter quoteExprExp quoteExprPat
 
 parseIt x = do
   loc - TH.location
   let pos =
   (TH.loc_filename loc,
   fst (TH.loc_start loc),
   snd (TH.loc_start loc))
   parseString pos x
 
 quoteExprExp x = do
   expr - parseIt x
   it - dataToExpQ (const Nothing `extQ` antiExprExp) expr
   return $ TH.AppE (TH.VarE (TH.mkName concat)) it
 
 quoteExprPat x = do
   expr - parseIt x
   it - dataToPatQ (const Nothing `extQ` antiExprPat) expr
   error help!
 
 antiExprExp :: Exp - Maybe (TH.Q TH.Exp)
 antiExprExp (StringLit s) = Just $ TH.litE (TH.stringL s)
 antiExprExp (Backslash) = Just $ TH.litE (TH.stringL \\)
 antiExprExp (Unicode n) = Just $ TH.litE (TH.stringL [chr n])
 antiExprExp (Variable v) = Just $ TH.appE
   (TH.varE (TH.mkName show))
   (TH.varE (TH.mkName v))
 
 antiExprPat :: Exp - Maybe (TH.Q TH.Pat)
 antiExprPat (Unicode n) = Just $ TH.litP (TH.stringL [chr n])
 antiExprPat (Backslash) = Just $ TH.litP (TH.stringL \\)
 antiExprPat (StringLit s) = Just $ TH.litP (TH.stringL s)
 antiExprPat (Variable v) = Just $ TH.varP (TH.mkName v)

[1]: http://haskell.org/haskellwiki/Quasiquotation



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-17 Thread Artyom Shalkhakov
Hello,

2009/1/16 Immanuel Litzroth immanuel...@gmail.com:
 I don't understand your comment.
 1) If XMonad already uses it the problem is solved, without giving Haskell
 import new semantics?

Right, but there are some restrictions.

 2) These guys refer to a method to do plugin work in Haskell
 http://www.cse.unsw.edu.au/~dons/hs-plugins/
 So the problem of dynamically loading plugins should already be solved?

Well, mostly yes, but I think that it should be added to the language.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-16 Thread Manlio Perillo

Artyom Shalkhakov ha scritto:

[...]

Prelude :l foo.hs
[1 of 1] Compiling Main ( foo.hs, interpreted )
Ok, modules loaded: Main.
*Main isDirectory /var

interactive:1:0:
   Ambiguous occurrence `isDirectory'
   It could refer to either `Main.isDirectory', defined at foo.hs:6:0
 or `PF.isDirectory', imported from
System.Posix.Files at foo.hs:2:0-30



That's exactly the problem of function call hi-jacking. [1] In Haskell
it's solved using qualified imports.



What a surprise to see there are others that know both Haskell and D ;-).


I find D a very interesting language.
I also have support for pure functions.



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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Manlio Perillo

Artyom Shalkhakov ha scritto:

Hi Manlio,



Hi Artyom.
Note that it seems you have sent this message only to me;
I'm sending the reply to both you and the mailing list.



2009/1/14 Manlio Perillo manlio_peri...@libero.it:

2) In Python it is possible to import modules inside a function.

  In Haskell something like:

  joinPath' root name =
  joinPath [root, name]
  importing System.FilePath (joinPath)


I guess you're talking about first-class modules, the ones that
might be passed to functions as arguments, returned from functions
as a result, loaded at run-time, etc.


No, I was not going that far :).

I simply was proposing a method to keep imported definitions local to a 
function.



By the way, here is a strange (for me) problem I hit, and made me think 
about this extension.


Suppose a file foo.hs defines:

import Control.Monad
import System.Posix.Files as PF


isDirectory :: FilePath - IO Bool
isDirectory path =
PF.isDirectory `liftM` PF.getFileStatus path


If I try to load the file from ghci I get:

Prelude :l foo.hs
[1 of 1] Compiling Main ( foo.hs, interpreted )
Ok, modules loaded: Main.
*Main isDirectory /var

interactive:1:0:
Ambiguous occurrence `isDirectory'
It could refer to either `Main.isDirectory', defined at foo.hs:6:0
  or `PF.isDirectory', imported from 
System.Posix.Files at foo.hs:2:0-30


 [...]


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Manlio Perillo

Brandon S. Allbery KF8NH ha scritto:

 [... about Python import local to functions ...]


Sometime they are necessary, to avoid circular import problems (but 
this not a problem with Haskell).


...in theory. In practice GHC needs help with circular imports, and some 
cycles might be impossible to resolve.




This is interesting.
Where can I find some examples?

Is this explained in the Real World Haskell book?



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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Marc Weber
  1) In a Python string it is available the \U{name} escape, where name is
 a character name in the Unicode database.
 
 As an example:
 foo = uabc\N{VULGAR FRACTION ONE HALF}
 
I think you can use quasi quotation of ghc to achieve this ?
Your code would look like this then:
  let foo = [$mystr|abc\N{VULGAR FRACTION ONE HALF}]

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Immanuel Litzroth
 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)


In Python importing a module has totally different semantics from importing
in Haskell.
I runs the initialization code for the module  makes the names in that
module
available to you code. In Haskell modules are just namespace control, and
you can always
refer to names imported through import X through the syntax X.name.
This means that the local import in Python solves two problems
1) making a name available locally.
2) running initialization code only when a specific function is called.
Neither of those makes any sense for Haskell as far as I can tell.
Immanuel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Brandon S. Allbery KF8NH

On 2009 Jan 15, at 5:55, Manlio Perillo wrote:

Brandon S. Allbery KF8NH ha scritto:

 [... about Python import local to functions ...]
Sometime they are necessary, to avoid circular import problems  
(but this not a problem with Haskell).
...in theory. In practice GHC needs help with circular imports, and  
some cycles might be impossible to resolve.


This is interesting.
Where can I find some examples?


http://www.haskell.org/ghc/docs/latest/html/users_guide/separate-compilation.html#mutual-recursion
The impossible to resolve is my interpretation of a discussion on  
the lists several months ago.


I don't see any mention in RWH offhand.

--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Artyom Shalkhakov
Hi Immanuel,

2009/1/15 Immanuel Litzroth immanuel...@gmail.com:
 In Python importing a module has totally different semantics from importing
 in Haskell.
 I runs the initialization code for the module  makes the names in that
 module
 available to you code. In Haskell modules are just namespace control, and
 you can always
 refer to names imported through import X through the syntax X.name.
 This means that the local import in Python solves two problems
 1) making a name available locally.
 2) running initialization code only when a specific function is called.
 Neither of those makes any sense for Haskell as far as I can tell.

Well, how about extensible programs? XMonad uses run-time module
loading to remain configurable. I think this approach is much better than
the ill-defined, partially-specified configuration files used by e.g. Apache,
wpa_supplicant, and other widely used programs.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-15 Thread Artyom Shalkhakov
Hi Manlio

2009/1/15 Manlio Perillo manlio_peri...@libero.it:
 Note that it seems you have sent this message only to me;
 I'm sending the reply to both you and the mailing list.

Yes, sorry, I always forget forwading to the mailing list. :(

 By the way, here is a strange (for me) problem I hit, and made me think
 about this extension.

 Suppose a file foo.hs defines:

 import Control.Monad
 import System.Posix.Files as PF


 isDirectory :: FilePath - IO Bool
 isDirectory path =
PF.isDirectory `liftM` PF.getFileStatus path


 If I try to load the file from ghci I get:

 Prelude :l foo.hs
 [1 of 1] Compiling Main ( foo.hs, interpreted )
 Ok, modules loaded: Main.
 *Main isDirectory /var

 interactive:1:0:
Ambiguous occurrence `isDirectory'
It could refer to either `Main.isDirectory', defined at foo.hs:6:0
  or `PF.isDirectory', imported from
 System.Posix.Files at foo.hs:2:0-30


That's exactly the problem of function call hi-jacking. [1] In Haskell
it's solved using qualified imports.

Cheers,
Artyom Shalkhakov.

[1] http://digitalmars.com/d/2.0/hijack.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Manlio Perillo

Hi.

There are two features found in Python language, that I would like to 
see in Haskell.


1) In a Python string it is available the \U{name} escape, where name is
   a character name in the Unicode database.

   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}

2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)



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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Neil Mitchell
Hi

 1) In a Python string it is available the \U{name} escape, where name is
   a character name in the Unicode database.

   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}

Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax I want:

foo\E{show i}bar

i.e. embed expressions in strings. I think this would be fantastic.

 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

Looks a bit ugly, but kind of useful. I'd make the syntax:

joinPath' root name = joinPath [root,name]
  where import System.FilePath(joinPath)

It does mean you need to read an entire file to see what functions it
imports, but perhaps that is the way it should be. I could also
imagine a syntax:

joinPath' root name = import.System.FilePath.joinPath [root,name]

i.e. doing an import and use at the same time.

Nice ideas, but they probably want implemented in a Haskell compiler
and using in real life before they are ready for Haskell' like
thoughts.

Thanks

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread minh thu
2009/1/14 Neil Mitchell ndmitch...@gmail.com:
 Hi

 1) In a Python string it is available the \U{name} escape, where name is
   a character name in the Unicode database.

   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}

 Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax I 
 want:

 foo\E{show i}bar

 i.e. embed expressions in strings. I think this would be fantastic.

Hi,

why not simpy foo\E{i}bar ?

 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

 Looks a bit ugly, but kind of useful. I'd make the syntax:

 joinPath' root name = joinPath [root,name]
  where import System.FilePath(joinPath)

 It does mean you need to read an entire file to see what functions it
 imports, but perhaps that is the way it should be. I could also
 imagine a syntax:

 joinPath' root name = import.System.FilePath.joinPath [root,name]

 i.e. doing an import and use at the same time.

and why not simply System.FilePath.joinPath (without the import.) ?

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Neil Mitchell
   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}

 Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax I 
 want:

 foo\E{show i}bar

 i.e. embed expressions in strings. I think this would be fantastic.

 why not simpy foo\E{i}bar ?

What if i is a string? You'd get: fooibar

Having different behaviour for string vs everything else would be equally bad.

 joinPath' root name = import.System.FilePath.joinPath [root,name]

 i.e. doing an import and use at the same time.

 and why not simply System.FilePath.joinPath (without the import.) ?

That is the same as saying everything is always in scope but fully
qualified. I'd rather have to explicitly say which modules were being
used - I'm not sure my enhanced import idea is a good idea at all.

Thanks

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Dougal Stanton
On Wed, Jan 14, 2009 at 3:12 PM, Neil Mitchell ndmitch...@gmail.com wrote:

 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

 Looks a bit ugly, but kind of useful. I'd make the syntax:

 joinPath' root name = joinPath [root,name]
  where import System.FilePath(joinPath)

 It does mean you need to read an entire file to see what functions it
 imports, but perhaps that is the way it should be. I could also
 imagine a syntax:

 joinPath' root name = import.System.FilePath.joinPath [root,name]

 i.e. doing an import and use at the same time.


This can be done with a fully-qualified name (or two). Not quite as
succinct, but I assume the scope of these imports is only local
anyway.

 joinPath root path = jp [root,filename path]
  where jp = System.FilePath.joinPath
filename = System.FilePath.takeFileName

or

 joinPath root path = System.FilePath.joinPath 
 [root,System.FilePath.takeFileName path]


Cheers,

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Manlio Perillo

Neil Mitchell ha scritto:

Hi


1) In a Python string it is available the \U{name} escape, where name is
  a character name in the Unicode database.

  As an example:
  foo = uabc\N{VULGAR FRACTION ONE HALF}


Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax I want:

foo\E{show i}bar



How this should/can work?
There is Text.Printf for this.


i.e. embed expressions in strings. I think this would be fantastic.


2) In Python it is possible to import modules inside a function.

  In Haskell something like:

  joinPath' root name =
  joinPath [root, name]
  importing System.FilePath (joinPath)


Looks a bit ugly, but kind of useful. I'd make the syntax:

joinPath' root name = joinPath [root,name]
  where import System.FilePath(joinPath)



It seems a good solution.


It does mean you need to read an entire file to see what functions it
imports, 


Yes.
That's the same with Python.

I use imports inside a function only with care.
Sometime they are necessary, to avoid circular import problems (but this 
not a problem with Haskell).


 [...]

Nice ideas, but they probably want implemented in a Haskell compiler
and using in real life before they are ready for Haskell' like
thoughts.



The first feature requires some works.
As far as I know GHC does not support the Unicode database at all.

It would be nice to have an Haskell interface for the CLDR (Common 
Locale Data Repository), like done in

babel: http://babel.edgewall.org/
http://unicode.org/cldr/


Thanks

Neil




Regards  Manlio Perillo

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Lennart Augustsson
When Haskell was designed there was a bried discussion (if my memory
serves me) to have import be a decl, so it could occur anywhere a
normal declaration can occur.
I kinda like the idea, but some people didn't and it never happened.

  -- Lennart

On Wed, Jan 14, 2009 at 3:12 PM, Neil Mitchell ndmitch...@gmail.com wrote:
 Hi

 1) In a Python string it is available the \U{name} escape, where name is
   a character name in the Unicode database.

   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}

 Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax I 
 want:

 foo\E{show i}bar

 i.e. embed expressions in strings. I think this would be fantastic.

 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

 Looks a bit ugly, but kind of useful. I'd make the syntax:

 joinPath' root name = joinPath [root,name]
  where import System.FilePath(joinPath)

 It does mean you need to read an entire file to see what functions it
 imports, but perhaps that is the way it should be. I could also
 imagine a syntax:

 joinPath' root name = import.System.FilePath.joinPath [root,name]

 i.e. doing an import and use at the same time.

 Nice ideas, but they probably want implemented in a Haskell compiler
 and using in real life before they are ready for Haskell' like
 thoughts.

 Thanks

 Neil
 ___
 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] some ideas for Haskell', from Python

2009-01-14 Thread Ketil Malde
Neil Mitchell ndmitch...@gmail.com writes:

 1) In a Python string it is available the \U{name} escape, where name is
   a character name in the Unicode database.

   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}

Why not:

import Unicode.Entities as U

foo = abc++U.vulgar_fraction_one_half

 Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax I 
 want:

 foo\E{show i}bar

  foo++show i++bar

Change the language - save two characters.

 2) In Python it is possible to import modules inside a function.

   In Haskell something like:

   joinPath' root name =
   joinPath [root, name]
   importing System.FilePath (joinPath)

 It does mean you need to read an entire file to see

Well, then you might as well allow multiple modules per file as per
the recent discussion.  And multi-module files will possibly let you
achieve the desired encapsulation without actually changing the
language. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Job Vranish
What I would really like to see is locally scoped imports but with
parameterized modules. (so modules could take types and values as
parameters)
The places where I most want a feature like this is when I have a group of
helper functions that need a value that is outside the modules scope, but
that in general doesn't change. Usually we just curry the functions, but
that generates a lot of wasted code.
A good example might be the token
parsershttp://legacy.cs.uu.nl/daan/download/parsec/parsec.html#Lexical%20analysisin
parsec. Rather than have something like this:

whiteSpace= P.whiteSpace
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#whiteSpace
lexer
lexeme= P.lexeme lexer
symbol= P.symbol
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#symbol lexer
natural   = P.natural
http://legacy.cs.uu.nl/daan/download/parsec/parsec.html#natural
lexer
...

We could do something like:

import ParsecToken lexer

Having an import/module feature like this would replace almost all cases
where someone might wish for a macro system for Haskell.

 Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax
I want:

 foo\E{show i}bar

 foo++show i++bar

Change the language - save two characters.

For simple cases, doing foo ++ show i ++ bar isn't bad at all, but when
you have five or six or ten (show i)s that you want to mix in, it can get
pretty hard to read.


On Wed, Jan 14, 2009 at 11:43 AM, Ketil Malde ke...@malde.org wrote:

 Neil Mitchell ndmitch...@gmail.com writes:

  1) In a Python string it is available the \U{name} escape, where name is
a character name in the Unicode database.

As an example:
foo = uabc\N{VULGAR FRACTION ONE HALF}

 Why not:

import Unicode.Entities as U

foo = abc++U.vulgar_fraction_one_half

  Hmm, looks nice, and sensible. But as soon as you've got \N{} syntax
 I want:
 
  foo\E{show i}bar

   foo++show i++bar

 Change the language - save two characters.

  2) In Python it is possible to import modules inside a function.
 
In Haskell something like:
 
joinPath' root name =
joinPath [root, name]
importing System.FilePath (joinPath)

  It does mean you need to read an entire file to see

 Well, then you might as well allow multiple modules per file as per
 the recent discussion.  And multi-module files will possibly let you
 achieve the desired encapsulation without actually changing the
 language.

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants
 ___
 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] some ideas for Haskell', from Python

2009-01-14 Thread Tim Wawrzynczak
Having an import/module feature like this would replace almost all cases
 where someone might wish for a macro system for Haskell.


Don't say that until you've tried Lisp macros... read some of Paul Graham's
essays or try some Common Lisp for yourself... macros can be an incredibly
powerful tool, but macros from C, etc. aren't really macros, they're more
like find-and-replace expressions :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread David Leimbach


 joinPath' root name = import.System.FilePath.joinPath [root,name]


How is this different from

joinPath' root name = System.FilePath.joinPath [root,name]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread David Leimbach
On Wed, Jan 14, 2009 at 10:13 AM, David Leimbach leim...@gmail.com wrote:


 joinPath' root name = import.System.FilePath.joinPath [root,name]


 How is this different from

 joinPath' root name = System.FilePath.joinPath [root,name]


 I'm sorry I didn't mean different, I meant better than?  I don't get
the advantage.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Job Vranish
On Wed, Jan 14, 2009 at 12:48 PM, Tim Wawrzynczak
inforichl...@gmail.com wrote:


 Having an import/module feature like this would replace almost all cases 
 where someone might wish for a macro system for Haskell.

 Don't say that until you've tried Lisp macros... read some of Paul Graham's 
 essays or try some Common Lisp for yourself... macros can be an incredibly 
 powerful tool, but macros from C, etc. aren't really macros, they're more 
 like find-and-replace expressions :)

You're probably right.
I've played around with LISP macros a little, but it seems that most
of the cases where you would use a macro in LISP you don't need one in
haskell due to lazy evaluation.  Although I haven't played around with
them enough to say much one way or another.

Do you know of a particular example where a macro would be a big help
in haskell?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Tim Wawrzynczak

 You're probably right.
 I've played around with LISP macros a little, but it seems that most
 of the cases where you would use a macro in LISP you don't need one in
 haskell due to lazy evaluation.  Although I haven't played around with
 them enough to say much one way or another.

 Do you know of a particular example where a macro would be a big help
 in haskell?


Well, like many good programming tools, Lisp macros are another abstraction,
but instead of dealing with data, they deal with code.  They are a syntactic
abstraction.  They're often described as programs that write programs.  We
all know how much Haskell likes abstractions ;)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Miguel Mitrofanov
Well, like many good programming tools, Lisp macros are another  
abstraction, but instead of dealing with data, they deal with code.


I didn't know Lisp puts such an emphasis on the difference between  
code and data.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Martijn van Steenbergen

Jonathan Cast wrote:

Haskell already has a couple of abstraction tools for dealing with code.
One is called `first-class functions'; another is called `lazy
evaluation'.


And for all the rest there is TH?

M.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Tim Wawrzynczak
On Wed, Jan 14, 2009 at 12:56 PM, Martijn van Steenbergen 
mart...@van.steenbergen.nl wrote:

 Jonathan Cast wrote:

 Haskell already has a couple of abstraction tools for dealing with code.
 One is called `first-class functions'; another is called `lazy
 evaluation'.


 And for all the rest there is TH?

 M.


Woah fellas, I wasn't trying to start a flame war, I was merely commenting
that those who have not used Lisp don't really understand the power that
macros can have in a language (such as Lisp) that supports them, and where
code and data can be used interchangeably.  And I've never used TH so I
can't comment on that.  Don't worry, I'm on your side :)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Martijn van Steenbergen

Tim Wawrzynczak wrote:
Woah fellas, I wasn't trying to start a flame war, I was merely 
commenting that those who have not used Lisp don't really understand the 
power that macros can have in a language (such as Lisp) that supports 
them, and where code and data can be used interchangeably.  And I've 
never used TH so I can't comment on that.  Don't worry, I'm on your side :)


Oh, I didn't mean that in a bad way. :-)

I was just thinking that if something turns out hard to express in pure 
functions, you can always resort to Template Haskell.


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Max Rabkin
On Wed, Jan 14, 2009 at 10:48 AM, Jonathan Cast
jonathancc...@fastmail.fm wrote:
 Do you have an example of
 a macro that can't be replaced by higher-order functions and laziness?

I believe I do: one macro I found useful when writing a web app in
Lisp was something I called hash-bind, which binds variables to the
values in a hashtable, with the variable names as keys. For example:

(hash-bind (a b) hashtable body)
==
(let
((a (lookup hashtable a))
 (b (lookup hashtable b))
body)

I found this very useful in places where I was given URL request
parameters in a hashtable and wanted to extract some variables from
it. I don't believe it can be replaced by a higher order function
(though I may be wrong).

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Alex Queiroz
Hallo,

On Wed, Jan 14, 2009 at 5:06 PM, Max Rabkin max.rab...@gmail.com wrote:
 On Wed, Jan 14, 2009 at 10:48 AM, Jonathan Cast
 jonathancc...@fastmail.fm wrote:
 Do you have an example of
 a macro that can't be replaced by higher-order functions and laziness?

 I believe I do: one macro I found useful when writing a web app in
 Lisp was something I called hash-bind, which binds variables to the
 values in a hashtable, with the variable names as keys. For example:


 I have one for binding GET/POST variables to regular variables
transparently and with error checking, just inside the body of the
macro.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Jonathan Cast
On Wed, 2009-01-14 at 11:06 -0800, Max Rabkin wrote:
 On Wed, Jan 14, 2009 at 10:48 AM, Jonathan Cast
 jonathancc...@fastmail.fm wrote:
  Do you have an example of
  a macro that can't be replaced by higher-order functions and laziness?
 
 I believe I do: one macro I found useful when writing a web app in
 Lisp was something I called hash-bind, which binds variables to the
 values in a hashtable, with the variable names as keys. For example:
 
 (hash-bind (a b) hashtable body)
 ==
 (let
 ((a (lookup hashtable a))
  (b (lookup hashtable b))
 body)
 
 I found this very useful in places where I was given URL request
 parameters in a hashtable and wanted to extract some variables from
 it. I don't believe it can be replaced by a higher order function
 (though I may be wrong).

Thanks!  When you *know* there's a good reason people say something, and
can't find a good example of *why*, it's a tremendous relief when when
you find one.  Sort of restores your faith in humanity :)

jcc


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Max Rabkin
On Wed, Jan 14, 2009 at 11:11 AM, Alex Queiroz asand...@gmail.com wrote:
 I have one for binding GET/POST variables to regular variables
 transparently and with error checking, just inside the body of the
 macro.

N! You reinvented PHP. What happens if a request variable shadows
the name of another variable used in the body?

 --
 -alex
 http://www.ventonegro.org/

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Alex Queiroz
Hallo,

On Wed, Jan 14, 2009 at 5:16 PM, Max Rabkin max.rab...@gmail.com wrote:
 On Wed, Jan 14, 2009 at 11:11 AM, Alex Queiroz asand...@gmail.com wrote:
 I have one for binding GET/POST variables to regular variables
 transparently and with error checking, just inside the body of the
 macro.

 N! You reinvented PHP. What happens if a request variable shadows
 the name of another variable used in the body?


 I list the variables I want to bind in the form. I do not ask to
automatically bind all of them. :)

(query-let (id name job salary)
   (if ( salary 1000) ...))

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Tim Wawrzynczak
On Wed, Jan 14, 2009 at 1:14 PM, Jonathan Cast jonathancc...@fastmail.fmwrote:

 On Wed, 2009-01-14 at 11:06 -0800, Max Rabkin wrote:
  On Wed, Jan 14, 2009 at 10:48 AM, Jonathan Cast
  jonathancc...@fastmail.fm wrote:
   Do you have an example of
   a macro that can't be replaced by higher-order functions and laziness?
 
  I believe I do: one macro I found useful when writing a web app in
  Lisp was something I called hash-bind, which binds variables to the
  values in a hashtable, with the variable names as keys. For example:
 
  (hash-bind (a b) hashtable body)
  ==
  (let
  ((a (lookup hashtable a))
   (b (lookup hashtable b))
  body)
 
  I found this very useful in places where I was given URL request
  parameters in a hashtable and wanted to extract some variables from
  it. I don't believe it can be replaced by a higher order function
  (though I may be wrong).

 Thanks!  When you *know* there's a good reason people say something, and
 can't find a good example of *why*, it's a tremendous relief when when
 you find one.  Sort of restores your faith in humanity :)

 jcc



I thought of another good case (Shamelessly stolen from Paul Graham's 'On
Lisp').  When defining a function to average the results of the list, you
could define avg like this:

(defun avg (rest args)
  (/ (apply #'+ args) (length args)))

Or as a macro like this:

(defmacro avg (rest args)
  `(/ (+ ,@args) ,(length args)))

The reason the macro is better is that the length of the list is known at
compile time, so you don't need to traverse the list to calculate the length
of the list.

Food for thought, anyway.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Max Rabkin
2009/1/14 Tim Wawrzynczak inforichl...@gmail.com:
 The reason the macro is better is that the length of the list is known at
 compile time, so you don't need to traverse the list to calculate the length
 of the list.

Or you could use a real compiler (perhaps even a glorious one) that
does constant folding when the list length is constant, but have your
function still work when it isn't constant.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Dougal Stanton
 (defun avg (rest args)
   (/ (apply #'+ args) (length args)))

 Or as a macro like this:

 (defmacro avg (rest args)
   `(/ (+ ,@args) ,(length args)))

 The reason the macro is better is that the length of the list is known at
 compile time, so you don't need to traverse the list to calculate the length
 of the list.



I'm trying to work out how awesome the (+) operator is that you can
add the values together without needing to traverse the list ;-)


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Alex Queiroz
Hallo,

On Wed, Jan 14, 2009 at 8:47 PM, Dougal Stanton ith...@gmail.com wrote:
 (defun avg (rest args)
   (/ (apply #'+ args) (length args)))

 Or as a macro like this:

 (defmacro avg (rest args)
   `(/ (+ ,@args) ,(length args)))

 The reason the macro is better is that the length of the list is known at
 compile time, so you don't need to traverse the list to calculate the length
 of the list.



 I'm trying to work out how awesome the (+) operator is that you can
 add the values together without needing to traverse the list ;-)


 Don't need to traverse the list at run time, not compile
(actually macro-expansion) time.

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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Lennart Augustsson
With macros you can define new variable binding constructs.
That's something I occasionally miss in Haskell.

  -- Lennart

On Wed, Jan 14, 2009 at 6:48 PM, Jonathan Cast
jonathancc...@fastmail.fm wrote:
 On Wed, 2009-01-14 at 12:39 -0600, Tim Wawrzynczak wrote:
 You're probably right.
 I've played around with LISP macros a little, but it seems
 that most
 of the cases where you would use a macro in LISP you don't
 need one in
 haskell due to lazy evaluation.  Although I haven't played
 around with
 them enough to say much one way or another.

 Do you know of a particular example where a macro would be a
 big help
 in haskell?

 Well, like many good programming tools, Lisp macros are another
 abstraction, but instead of dealing with data, they deal with code.

 Haskell already has a couple of abstraction tools for dealing with code.
 One is called `first-class functions'; another is called `lazy
 evaluation'.

 They are a syntactic abstraction.

 What is this good for?  I suspect most Lisp macros are parametric in
 form, rather than really syntactic; I know that every example of a Lisp
 macro I've seen is parametric in form.  Parametric macros --- macros
 that don't deconstruct their arguments --- don't usually need to be
 macros at all in modern functional languages.  Do you have an example of
 a macro that can't be replaced by higher-order functions and laziness?

 They're often described as programs that write programs.

 So are code generators.  The most common example of a code generator is
 probably YACC --- but Parsec replaces it, with better readability even,
 with first-class parsers (built atop first-class functions).

 jcc


 ___
 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] some ideas for Haskell', from Python

2009-01-14 Thread Brandon S. Allbery KF8NH

On 2009 Jan 14, at 10:26, Neil Mitchell wrote:

 As an example:
 foo = uabc\N{VULGAR FRACTION ONE HALF}


Hmm, looks nice, and sensible. But as soon as you've got \N{}  
syntax I want:


foo\E{show i}bar

i.e. embed expressions in strings. I think this would be fantastic.


why not simpy foo\E{i}bar ?


What if i is a string? You'd get: fooibar

Having different behaviour for string vs everything else would be  
equally bad.


...except that show already *has* different behavior for String vs.  
everything else.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Brandon S. Allbery KF8NH


On 2009 Jan 14, at 10:39, Manlio Perillo wrote:

Neil Mitchell ha scritto:

Hi
1) In a Python string it is available the \U{name} escape, where  
name is

 a character name in the Unicode database.

 As an example:
 foo = uabc\N{VULGAR FRACTION ONE HALF}
Hmm, looks nice, and sensible. But as soon as you've got \N{}  
syntax I want:

foo\E{show i}bar


How this should/can work?
There is Text.Printf for this.


I vaguely recall seeing some TH go by that did this (albeit with $()  
TH foo).


Sometime they are necessary, to avoid circular import problems (but  
this not a problem with Haskell).


...in theory. In practice GHC needs help with circular imports, and  
some cycles might be impossible to resolve.


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] some ideas for Haskell', from Python

2009-01-14 Thread Jonathan Cast
On Wed, 2009-01-14 at 18:59 -0500, Brandon S. Allbery KF8NH wrote:
 On 2009 Jan 14, at 10:26, Neil Mitchell wrote:
   As an example:
   foo = uabc\N{VULGAR FRACTION ONE HALF}
 
  Hmm, looks nice, and sensible. But as soon as you've got \N{}  
  syntax I want:
 
  foo\E{show i}bar
 
  i.e. embed expressions in strings. I think this would be fantastic.
 
  why not simpy foo\E{i}bar ?
 
  What if i is a string? You'd get: fooibar
 
  Having different behaviour for string vs everything else would be  
  equally bad.
 
 ...except that show already *has* different behavior for String vs.  
 everything else.

Technically, showList has different behavior for Char vs. everything
else.

And not necessarily for *everything* else.

And that's very well *not* what he meant.

jcc


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