Re: Mutually-recursive/cyclic module imports

2008-08-17 Thread Isaac Dupree

Isaac Dupree wrote:

Duncan Coutts wrote:

[...]

I'm not saying it's a problem with your proposal, I'd just like it to be
taken into account. For example do dependency chasers need to grok just
import lines and {-# SOURCE -#} pragmas or do they need to calculate
fixpoints.


Actually, good point, Duncan, that got me thinking about 
what we need in order to obviously not to lose much/any of 
the .hs-boot efficiency.  (warning: another long post ahead, 
although the latter half of it is just an example from GHC's 
source) [and I re-read my post and wasn't sure about a few 
things, but maybe better to get feedback first -- please 
tell me if I'm being too verbose somewhere, too]


Let's look at the total imports of a .hs and its .hs-boot, 
as they currently are for GHC.  Either can be non-SOURCE 
imports (let's call them NOSOURCE), SOURCE imports, or not 
importing that.

.hs:NOSOURCE, .hs-boot:NOSOURCE : okay
.hs:NOSOURCE, .hs-boot:SOURCE : okay
.hs:NOSOURCE, .hs-boot:not-imported : okay
.hs:SOURCE, .hs-boot:NOSOURCE : bad, if the .hs needs 
SOURCE, then probably so does the .hs-boot

.hs:SOURCE, .hs-boot:SOURCE : okay
.hs:SOURCE, .hs-boot:not-imported : okay
- the .hs-boot importing a module that the .hs doesn't is 
invalid, or at least useless [actually, see later example -- 
there may be reasons for this, but in that case, it doesn't 
hurt to also import the module in the .hs (assuming there's 
no syntactic/maintenance burden), and it provides better 
automatic error-checking to do so]


Given the limited amount of information a .hs-boot file (or 
SOURCE-imported file, in my scheme) needs for being a 
boot-file, there is no advantage to import the modules it 
depends on as NOSOURCE.  The compiler just has to be clever 
enough to ignore imports of functions that it can't find out 
the type of.  Also, currently using SOURCE requires the 
imported module to have a .hs-boot.  But it should work fine 
to look for a .hi and use that in the absence of .hi-boot, 
because it has strictly a superset of the information (so 
that my statement that "SOURCE is superior to NOSOURCE when 
it works" can be truer, for the sake of demonstration). 
[oops! I was wrong, it may need to NOSOURCE-import on 
occasion to find out a function's type - more on that in a 
later post?]


Now, since the .hs-boot SOURCE vs NOSOURCE has been 
collapsed, I think we can move mostly-all .hs-boot info into 
the .hs file.  If the .hs-boot file had imported something, 
the corresponding import in the .hs is imported with 
{-#SOURCE_FOLLOW#-} (in addition to {-#SOURCE#-} or 
{-#NOSOURCE#-}); otherwise it's imported with 
{-#SOURCE_NOFOLLOW#-} (ditto).  For demonstration, I'll 
assume that all imports are annotated this way, with two 
bits of information.  Presumably all imports that aren't 
part of an import loop are NOSOURCE (which includes all 
cross-package imports).


Now let's look at the dependency chaser.
NOSOURCE imports must not form a loop.  They form dependency 
chains as normal.
SOURCE imports depend on either a .hi or a .hi-boot for the 
imported module.

When a X.hi-boot is demanded:
only SOURCE_FOLLOW imports are dependency-chased from X.hs, 
through any .hs modules that don't already have a .hi or 
.hi-boot.
In the case where .hs-boots worked, this *can* avoid cycles. 
 If this SOURCE_FOLLOW dependency DAG doesn't have any 
cycles, then it should be as simple as calling (the 
fictional) `ghc -source X.hs` to produce X.hi.  If there are 
cycles, and it is sometimes necessary*, GHC needs to be 
slightly smarter and be able to produce all the .hi-boot 
files at once from any graph SCCs (loops) that prevent it 
from being a DAG (e.g., `ghc -source X.hs Y.hs` to produce 
X.hi-boot and Y.hi-boot).  Note that it doesn't need to be 
particularly smart here -- e.g., no type inference is done.


*necessary loops:
example 1, the data/declarations literally loop:
module X1 where
{ import Y1(Y); data X a = End a | Both Y Y; }
module Y1 where
{ import X1(X); data Y = Only (X (Maybe Y)); }
(or kind annotations could be required for these loops in 
general, e.g. data X (a :: *) = ...)
[hmm, in this case actually all we need is the data 
left-hand-side, so we could do this in two stages.  But that 
wouldn't work out so well if their RHSs contained 
{-#UNPACK#-}!SomeNewtypeForInt where SomeNewtypeForInt was 
from the other module.  But that's an optimization that it 
might be okay not to do, as long as it was consistently not 
done both for .hi-boot and .hi/.o; and it could perhaps be 
doable]


example 2, there are just too many back-and-forths:
module X2 where
{ import Y2(Yb); data Xa = Xa; data Xc = Xc Yb; }
module Y2 where
{ import X2(Xa,Xc); data Yb = Yb Xa; data Yd = Yd Xc; }
This second one "could" also be accomplished if multiple 
different .hs-boots were allowed per .hs,
although it doesn't seem worth the annotation!! such as 
using SOURCE_FOLLOW[0] or [1], [2]...
I'm not even going to try to write that! [oh wait, 
SOURCE[0->1] = SOURCE,

Re: New language feature: array-types

2008-08-17 Thread Lennart Augustsson
You can code array types with static bounds with the existing Haskell
type system.

On Sun, Aug 17, 2008 at 3:45 PM, Ramin <[EMAIL PROTECTED]> wrote:
> I am new to both the Haskell language, and to this group, but I have
> recently become obsessed with the mathematical precision of Haskell, and I
> want to help improve it, if members of the group could bear with me.
>
> The one thing I dislike about the Haskell language is it's treatment of
> arrays. I don't understand how things work internally to the system, and
> perhaps array-manipulating code can be efficiently optimized, but I would
> prefer to have a language feature for explicitly creating and modifying
> arrays in a way that does not require the entire array be copied on every
> update.
>
> My idea is this: a fixed-width mutable array can be declared as a type, much
> like a list, but can be evaluated more like a bitwise-integer operation.
>
>  -- in an array of A's set the 5th item in the array with an "initial-A"
> value
>  changeArrayFunc :: a^10 -> a^10
>  changeArrayFunc  ar = (ar:5 <- initA) -- returns an array which is that
> same as the old array, except the value at index 5 is different.
>
>  -- select the 5th item of an array
>  getArrayItemFunc :: a^10 -> a
>  getArrayItemFunc  ar = (ar:5)
>
> Here, I use the caret (^) operator to indicate an "array-10" type. I used
> caret because it is typically used for exponents -- as in, if your data type
> has N possible values, an array with 10 units would have N^10 possible
> values. Then, I use the colon (:) operator to do indexing. I've seen the
> various proposals for indexing operators and honestly I don't care which
> operator is chosen; I just use the colon operator because that is how lists
> are treated in pattern matching.
>
> The important thing is that an array-type exists, that way all
> bounds-checking can be done at compile-time by the typing system. Using
> arrays of different lengths would result in a compile-time error: Obviously,
> this will increase the complexity of the typing system.
>
>  data  Something = Array Int^10
>
>  change5Array :: Int^5 -> Int^5
>  change5Array  ar = ((ar:4) <- 0)
>
>  -- Something has an array of type Int^10, but calls "change5Array" which
> expects an Int^5
>  badFunc :: Something -> Int
>  badFunc  (Array x) = (change5Array  x)
>
> -- COMPILE-TIME ERROR
> -- Arrays.hs:8:16:
> -- Couldn't match expected type `Int^5' against inferred type `Int^10'
> -- In the first argument of `change5array', namely `x'
> -- In the expression: (change5array x)
> -- In the definition of `badFunc':
> -- badFunc (Array x) = (change5Array  x)
>
> ...or something like that.
>
> An efficient implementation of array access would make Haskell very useful
> for a much wider variety of computationally intensive applications. Haskel
> could be used to efficiently model memory access, provided that the
> interpreter knew not to "copy" arrays upon update, but simply to update a
> value within an array. If arrays were a language feature of Haskell, then
> this optimization could be guaranteed.
>
> If anyone takes the time to consider this idea, or to tell my why this isn't
> necessary, I would be most greatful.
>
> -- Ramin Honary
>
> ___
> Haskell-prime mailing list
> Haskell-prime@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-prime
>
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


New language feature: array-types

2008-08-17 Thread Ramin
I am new to both the Haskell language, and to this group, but I have 
recently become obsessed with the mathematical precision of Haskell, and 
I want to help improve it, if members of the group could bear with me.


The one thing I dislike about the Haskell language is it's treatment of 
arrays. I don't understand how things work internally to the system, and 
perhaps array-manipulating code can be efficiently optimized, but I 
would prefer to have a language feature for explicitly creating and 
modifying arrays in a way that does not require the entire array be 
copied on every update.


My idea is this: a fixed-width mutable array can be declared as a type, 
much like a list, but can be evaluated more like a bitwise-integer 
operation.


  -- in an array of A's set the 5th item in the array with an 
"initial-A" value

  changeArrayFunc :: a^10 -> a^10
  changeArrayFunc  ar = (ar:5 <- initA) -- returns an array which is 
that same as the old array, except the value at index 5 is different.


  -- select the 5th item of an array
  getArrayItemFunc :: a^10 -> a
  getArrayItemFunc  ar = (ar:5)

Here, I use the caret (^) operator to indicate an "array-10" type. I 
used caret because it is typically used for exponents -- as in, if your 
data type has N possible values, an array with 10 units would have N^10 
possible values. Then, I use the colon (:) operator to do indexing. I've 
seen the various proposals for indexing operators and honestly I don't 
care which operator is chosen; I just use the colon operator because 
that is how lists are treated in pattern matching.


The important thing is that an array-type exists, that way all 
bounds-checking can be done at compile-time by the typing system. Using 
arrays of different lengths would result in a compile-time error: 
Obviously, this will increase the complexity of the typing system.


  data  Something = Array Int^10

  change5Array :: Int^5 -> Int^5
  change5Array  ar = ((ar:4) <- 0)

  -- Something has an array of type Int^10, but calls "change5Array" 
which expects an Int^5

  badFunc :: Something -> Int
  badFunc  (Array x) = (change5Array  x)

-- COMPILE-TIME ERROR
-- Arrays.hs:8:16:
-- Couldn't match expected type `Int^5' against inferred type `Int^10'
-- In the first argument of `change5array', namely `x'
-- In the expression: (change5array x)
-- In the definition of `badFunc':
-- badFunc (Array x) = (change5Array  x)

...or something like that.

An efficient implementation of array access would make Haskell very 
useful for a much wider variety of computationally intensive 
applications. Haskel could be used to efficiently model memory access, 
provided that the interpreter knew not to "copy" arrays upon update, but 
simply to update a value within an array. If arrays were a language 
feature of Haskell, then this optimization could be guaranteed.


If anyone takes the time to consider this idea, or to tell my why this 
isn't necessary, I would be most greatful.


-- Ramin Honary

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


Re: Mutually-recursive/cyclic module imports

2008-08-17 Thread Duncan Coutts
On Sat, 2008-08-16 at 13:51 -0400, Isaac Dupree wrote:
> Duncan Coutts wrote:
> > [...]
> > 
> > I'm not saying it's a problem with your proposal, I'd just like it to be
> > taken into account. For example do dependency chasers need to grok just
> > import lines and {-# SOURCE -#} pragmas or do they need to calculate
> > fixpoints.
> 
> Good point.  What does the dependency chaser need to figure out?
> - exactly what dependency order files must be compiled 
> (e.g., ghc -c) ?
> - what files (e.g., .hi) are needed to be findable by the 
> e.g. (ghc -c) ?
> - recompilation avoidance?

It needs to work out which files the compiler will read when it compiles
that module.

So currently, I think we just have to read a single .hs file and
discover what modules it imports. We then can map those to .hi
or .hs-boot files in one of various search dirs or packages.

We also need to look at {#- SOURCE #-} import pragmas since that means
we look for a different file to ordinary imports.

Calculating dependency order and recompilation avoidance are things the
dep program has to do itself anyway. The basics is just working out what
things compiling a .hs file depends on. Obviously it's somewhat
dependent on the Haskell implementation.

Duncan

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