
In article <41ECD49F.9020601@imperial.ac.uk>,
Keean Schupke
Surely both requirements can be satisfied if the programs arguments are made parameters of main:
main :: [String] -> IO ()
Keean.
Better yet, it should be an implicit parameter so as not to break existing programs. main :: (?args :: [String]) => IO () You could do the same with standard input and output. -- Ashley Yakeley, Seattle WA

Of course both suggestions don't really change anything as: _main = do args <- getArgs main args (or the equivalent for implicit parameters) is all that is required... In a way the implicit parameter approach makes it seem like a normal function... Do you think implicit parameters could replace top-level-things-with-identity? I hadn't really thought of it before (and I don't use implicit parameters much). Keean. Ashley Yakeley wrote:
In article <41ECD49F.9020601@imperial.ac.uk>, Keean Schupke
wrote: Surely both requirements can be satisfied if the programs arguments are made parameters of main:
main :: [String] -> IO ()
Keean.
Better yet, it should be an implicit parameter so as not to break existing programs.
main :: (?args :: [String]) => IO ()
You could do the same with standard input and output.

In article <41EE22BE.80302@imperial.ac.uk>,
Keean Schupke
Do you think implicit parameters could replace top-level-things-with-identity?
I hadn't really thought of it before (and I don't use implicit parameters much).
Yes, but I think people are clamouring for top-level-things-with-identity because they don't like implicit parameters. Not me, though. I have been musing on the connection between data-types, modules, classes, and implicit parameters, and wondering if there might be some grand scheme to tie it all together. For instance, a module is very similar to class with no type parameters and all members defined. You'll notice that class members have different declared types inside and outside the class: class C a where foo :: a -> a -- inside foo :: (C a) => a -> a -- outside Perhaps one could have top-level implicit parameters (or top-level contexts in general): module (?myvar :: IORef Int) => Random where random :: IO Int -- inside random = do i <- readIORef ?myvar ... writeIORef i' return i' module (?myvar :: IORef Int) => MyMain where import Random -- random :: IO Int -- also inside mymain :: IO () mymain = do ... i <- random ... module Main where import MyMain -- mymain :: (?myvar :: IORef Int) => IO () -- outside main = do var <- newIORef 1 -- initialisers in the order you want let ?myvar = var in mymain -- Ashley Yakeley, Seattle WA

On Wednesday 19 January 2005 12:52, Ashley Yakeley wrote:
I have been musing on the connection between data-types, modules, classes, and implicit parameters, and wondering if there might be some grand scheme to tie it all together. For instance, a module is very similar to class with no type parameters and all members defined. [...]
You will probably find this paper interesting: Wolfram Kahl and Jan Scheffczyk: "Named Instances for Haskell Type Classes", http://www.informatik.uni-bonn.de/~ralf/hw2001/4.pdf I wonder if their (conservative) extensions have ever been contemplated for inclusion in one of the standard Haskell implementations. Ben

I may have got this wrong, but I think you can do named instances without any extensions, by using datatypes and fundeps: data Instance0 data Instance1 instance0 :: Instance0 instance0 = undefined instance1 :: Instance1 instance1 = undefined class Named a b | a -> b test :: a -> b -> b instance Named Instance0 Int test _ a = a + a instance Named Instance1 Float test _ a = a * a test instance0 1 test instance1 1.5 Keean. Benjamin Franksen wrote:
You will probably find this paper interesting: Wolfram Kahl and Jan Scheffczyk: "Named Instances for Haskell Type Classes", http://www.informatik.uni-bonn.de/~ralf/hw2001/4.pdf

On Wednesday 19 January 2005 14:31, Keean Schupke wrote:
I may have got this wrong, but I think you can do named instances without any extensions, by using datatypes and fundeps:
data Instance0 data Instance1
instance0 :: Instance0 instance0 = undefined
instance1 :: Instance1 instance1 = undefined
class Named a b | a -> b test :: a -> b -> b instance Named Instance0 Int test _ a = a + a instance Named Instance1 Float test _ a = a * a
test instance0 1 test instance1 1.5
Sure you can. However, the extension presented in the paper goes way beyond this (while still being conservative). For instance, named instances can be defined for standard Haskell98 classes, they don't need special class definitions as in your example. For a given class, standard unnamed instances may be used together with additional named instances. Another benefit of the proposal is that it slves a number of problems regarding multi-parameter classes quite elegantly. But the reason why I mentioned the paper was that it offers a lot of insight into exactly what Ashley Yakeley was thinking about. Citing again:
I have been musing on the connection between data-types, modules, classes, and implicit parameters, and wondering if there might be some grand scheme to tie it all together.
Neither I nor the authors claim that their proposal is the ultimate "grand scheme", yet. Still I think there are very interesting ideas in there that should be considered for experimental implementation or further research. Ben

Benjamin Franksen wrote:
Neither I nor the authors claim that their proposal is the ultimate "grand scheme", yet. Still I think there are very interesting ideas in there that should be considered for experimental implementation or further research.
But thats interesting isn't it. If one extension can be defined in terms of the other, then only one of the extensions is necessary. There is obviously some connection between functional dependancies and named instances. Maybe there is a better mechanism that both can be defined in terms of?

On Wednesday 19 January 2005 21:48, Keean Schupke wrote:
Benjamin Franksen wrote:
Neither I nor the authors claim that their proposal is the ultimate "grand scheme", yet. Still I think there are very interesting ideas in there that should be considered for experimental implementation or further research.
But thats interesting isn't it. If one extension can be defined in terms of the other, then only one of the extensions is necessary. There is obviously some connection between functional dependancies and named instances. Maybe there is a better mechanism that both can be defined in terms of?
Any idea? I'll propose you for the next Nobelprize in Programming Language Design ;--) Ben

Perhaps one could have top-level implicit parameters (or top-level contexts in general):
module (?myvar :: IORef Int) => Random where
Hi! I suggested something very similar to this some months ago, syntax and all. Nice to see I'm not the only one thinking along this lines. http://www.mail-archive.com/haskell%40haskell.org/msg14884.html
module Main where import MyMain
-- mymain :: (?myvar :: IORef Int) => IO () -- outside
main = do var <- newIORef 1 -- initialisers in the order you want let ?myvar = var in mymain
By then I also suggest that maybe we could also bind the implicit on import, something like:
module (?par :: Parameter) => A where ...
module B where import A -- simple, ?par unbound import qualified A as Ak where ?par = k -- ?par bound to k import qualified A as Am where ?par = m -- ?par bound to m
Seemed fine as long as the parameters didn't depend on the imported modules. But on hindsight, making an import depend on valued defined in the body of the module is probably quite clumsy, unfortunately (right?). Still,
import qualified A as Ak where ?par = 1 or import qualified A as Ak where ?par = newIORef or even import C(k) import qualified A as Ak where ?par = k
Doesn't sound that bad though. J.A.

On Wednesday 19 January 2005 21:20, Jorge Adriano Aires wrote:
Perhaps one could have top-level implicit parameters (or top-level contexts in general):
module (?myvar :: IORef Int) => Random where
I suggested something very similar to this some months ago, syntax and all. Nice to see I'm not the only one thinking along this lines.
Please note that implicit parameters -- at least as currently implemented in GHC -- have a number of severe problems. A good summary was given by Ben Rudiak-Gould in http://www.mail-archive.com/haskell%40haskell.org/msg15595.html (although in a different context):
[...] In a program with implicit parameters:
* Beta conversion no longer preserves semantics.
* The monomorphism restriction is no longer a restriction: it sometimes silently changes the meaning of a program.
* Adding type signatures for documentation is no longer safe, since they may silently change the behavior of the program.
* It's not even safe in general to add a signature giving the same type that the compiler would infer anyway: there are (common) cases in which this too changes the program's meaning. I ran into this quite by accident the first time I tried to use implicit parameters, and it was enough to scare me away from ever trusting them again.
Ben

In article <200501192149.11831.benjamin.franksen@bessy.de>,
Benjamin Franksen
Please note that implicit parameters -- at least as currently implemented in GHC -- have a number of severe problems. A good summary was given by Ben Rudiak-Gould in http://www.mail-archive.com/haskell%40haskell.org/msg15595.html (although in a different context):
This is mostly ambiguity due to missing type-signatures, isn't it? That's not so severe in my view. But maybe the compiler can issue a warning in such cases. -- Ashley Yakeley, Seattle WA

Benjamin Franksen wrote:
Please note that implicit parameters -- at least as currently implemented in GHC -- have a number of severe problems.
Does anyone have examples of these? This one scares the foo out of me:
* It's not even safe in general to add a signature giving the same type that the compiler would infer anyway
Jim

Jim Apple wrote:
Does anyone have examples of these? This one scares the foo out of me:
* It's not even safe in general to add a signature giving the same type that the compiler would infer anyway
Here's an example: > len :: [a] -> Int > > len xs = let ?accum = 0 in len' xs > > len' [] = ?accum > len' (x:xs) = let ?accum = ?accum + (1::Int) in len' xs *Main> :t len' len' :: forall a. (?accum :: Int) => [a] -> Int *Main> len "hello" 0 > len :: [a] -> Int > > len xs = let ?accum = 0 in len' xs > > len' :: forall a. (?accum :: Int) => [a] -> Int > > len' [] = ?accum > len' (x:xs) = let ?accum = ?accum + (1::Int) in len' xs *Main> :t len' len' :: forall a. (?accum :: Int) => [a] -> Int *Main> len "hello" 5 This happens as a side effect of the way that type inference currently works on recursive binding groups. It happens with typeclass dictionaries too, but it isn't observable because they can't be rebound in a local scope. -- Ben

Ben Rudiak-Gould wrote:
len :: [a] -> Int
len xs = let ?accum = 0 in len' xs
len' :: forall a. (?accum :: Int) => [a] -> Int
len' [] = ?accum len' (x:xs) = let ?accum = ?accum + (1::Int) in len' xs
*Main> :t len' len' :: forall a. (?accum :: Int) => [a] -> Int *Main> len "hello" 5
I don't get this. The second answer (the one quoted above) must be wrong... len' gets a value only in the empty '[]' case. The recursion is such that the value of '?accum' is incremented on the return of the recursively called function, therefore the value of '?accum' in the case '[]' is always zero! How on earth does this get the answer five? Keean,
participants (6)
-
Ashley Yakeley
-
Ben Rudiak-Gould
-
Benjamin Franksen
-
Jim Apple
-
Jorge Adriano Aires
-
Keean Schupke