Re: Closed type families, apartness, and occurs check

2014-07-02 Thread Brandon Moore
That was the only thing I worried about, but any examples I tried with families 
like that ended up with infinite type errors.
Infinite types are not meant to be supported, which perhaps gives a solution - 
the other sensible answer is bottom, i.e. a type checker error or perhaps an 
infinite loop in the compiler. For instantating with a type family to solve an 
equation that fails the occurs check, the type family has to be able to already 
reduce (even if there are some variables), so just adopting the policy that 
type families be fully expanded before the check would seem to prevent IsEq (G 
a) [G a] from ever evaulating to true.


Brandon



On Wednesday, July 2, 2014 7:11 AM, Richard Eisenberg  
wrote:
 

>
>
>Hi Brandon,
>
>
>Yes, this is a dark corner of GHC wherein a proper dragon lurks.
>
>
>In your second example, you're suggesting that, for all types `a`, `a` is 
>never equal to `[a]`. The problem is: that's not true! Consider:
>
>
>> type family G x where
>>   G x = [G x]
>
>
>This is a well-formed, although pathological, type family. What should the 
>behavior of `IsEq (G Int) [G Int]` be? The only possible consistent answer is 
>`True`. This is why `IsEq a [a]` correctly does not reduce.
>
>
>For further information, see section 6 of [1] and for a practical example of 
>how this can cause a program error (with open type families) see [2].
>
>
>[1]: http://www.cis.upenn.edu/~eir/papers/2014/axioms/axioms.pdf
>[2]: https://ghc.haskell.org/trac/ghc/ticket/8162
>
>
>It is conceivable that some restrictions around UndecidableInstances (short of 
>banning it in a whole program, including all importing modules) can mitigate 
>this problem, but no one I know has gotten to the bottom of it.
>
>
>Richard
>
>On Jul 2, 2014, at 4:19 AM, Brandon Moore  wrote:
>
>From the user manual, it sounds like a clause of a closed type family should 
>be rejected once no subsitution of the type could make it unify with the 
>clause. If so, it doesn't seem to do an occurs check:
>>
>>
>>type family IsEq a b :: Bool where
>>  IsEq a a = True
>>  IsEq a b = False
>>
>>
>>
>>> :kind! forall a . IsEq a a
>>forall a . IsEq a a :: Bool
>>= forall (a :: k). 'True
>>> :kind! forall a . IsEq a [a]
>>forall a . IsEq a [a] :: Bool
>>= forall a. IsEq a [a]
>>
>>
>>
>>I came across this while trying to using Generics to find the immediate 
>>children of a term - this sort of non-reduction happens while comparing a 
>>type like (Term var) with a constructor argument of type var.
>>
>>
>>
>>Brandon
>>___
>>Glasgow-haskell-users mailing list
>>Glasgow-haskell-users@haskell.org
>>http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>>
>
>
>___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Closed type families, apartness, and occurs check

2014-07-02 Thread Brandon Moore
>From the user manual, it sounds like a clause of a closed type family should 
>be rejected once no subsitution of the type could make it unify with the 
>clause. If so, it doesn't seem to do an occurs check:


type family IsEq a b :: Bool where
  IsEq a a = True
  IsEq a b = False


> :kind! forall a . IsEq a a
forall a . IsEq a a :: Bool
= forall (a :: k). 'True
> :kind! forall a . IsEq a [a]
forall a . IsEq a [a] :: Bool
= forall a. IsEq a [a]


I came across this while trying to using Generics to find the immediate 
children of a term - this sort of non-reduction happens while comparing a type 
like (Term var) with a constructor argument of type var.


Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Parallel --make (GHC build times on newer MacBook Pros?)

2011-08-26 Thread Brandon Moore
> From: Evan Laforge 

> Sent: Friday, August 26, 2011 6:35 PM
> Subject: Re: GHC build times on newer MacBook Pros?
> 
> On Tue, Aug 23, 2011 at 10:24 AM, David Terei  
> wrote:
>>  I have a 16 core machine at work (with 48GB of ram, a perk of the job
>>  :)). GHC can saturate them all. Can validate GHC in well under 10
>>  minutes on it.
> 
> To wander a bit from the topic, when I first saw this I thought "wow,
> ghc builds in parallel now, I want that" but then I realized it's
> because ghc itself uses make, not --make.  --make's automatic
> dependencies are convenient, but figuring out dependencies on every
> build and not being parallel means make should be a lot faster.  Also,
> --make doesn't understand the hsc->hs link, so in practice I have to
> do a fair amount of manual dependencies anyway.  So it inspired me to
> try to switch from --make to make for my own project.

I'm confused by this as well. Parallelizing --make was one of the
first case studies in the smp runtime paper, section 7 in
Haskell on a Shared-Memory Multiprocessor

There's also a trac ticket
http://hackage.haskell.org/trac/ghc/ticket/910with a vague comment that the 
patch from the paper
"almost certainly isn't ready for prime time",
but I haven't
seen any description of specific problems.


Brandon


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Package management

2011-04-27 Thread Brandon Moore
> From: Albert Y. C. Lai 

> To: glasgow-haskell-users@haskell.org
> Sent: Wed, April 27, 2011 9:53:38 PM
> Subject: Re: Package management
> 
> On 11-04-26 05:05 PM, Brandon Moore wrote:
> > There are already hashes to  keep incompatible builds of a package separate.
> > Would anything break  if
> > existing packages were left alone when a new version was installed?  
(perhaps
> > preferring the most
> > recent if a package flag specifies  version but not hash).
> 
> Whether we allow multiple builds of same package  same version, or allow 
>multiple versions of same package, we face the same  dilemmas:
> 
> First dilemma: If the package comes with C code, you get a name  clash at the 
> C 
>level. Because C function names in such packages are unlikely to  vary by 
>version. Well, the linker sees two extern C functions both called  
>get_current_timezone_seconds (real example from the time package),  great.
> 
> Second dilemma: If the package comes with instance code like  "instance Read 
>(IO a)", you get overlapping instances.
> 
> Third dilemma:  Data types and type classes defined by the package cannot be 
>safely exchanged  between two users because the two users depend on two 
>different builds. Perhaps  it is safe in most cases, but you can't be too  
>sure.

All of these problems only happen if you try to use multiple versions of the 
package in the same program.
Compilers and dependency solvers should continue to reject any attempt to use 
multiple versions of the same package.

I am only worried about the more basic situation, where each program needs just 
one version of
the library, but different programs might need it to be compiled against 
different versions of the dependencies.

What can happen now is that you build B-1.0 and build A-1.3 against B-1.0 for 
one program that
needs B-1.0, and then rebuild A-1.3 against B-2.0 to compile another program 
that needs B-2.0,
but this unregisters the first version of A-1.3, which has to be recompiled if 
you want to build P1 again.

Is there any reason not to leave both registered?

Brandon

Brandon


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Package management

2011-04-26 Thread Brandon Moore
Based on my own misadventures and Albert Y. C. Lai's SICP 
(http://www.vex.net/~trebla/haskell/sicp.xhtml)
it seems the that root of all install problems is that reinstalling a 
particular 
version of a particular package
deletes any other existing builds of that version, even if other packages 
already depend on them.

Deleting perfectly good versions seems to be the root of all package management 
problems.

There are already hashes to keep incompatible builds of a package separate. 
Would anything break if
existing packages were left alone when a new version was installed? (perhaps 
preferring the most
recent if a package flag specifies version but not hash).

For example, It seems the butterfly effect

http://cdsmith.wordpress.com/2011/01/17/the-butterfly-effect-in-cabal/

could be avoided if the package database was allowed to simultaneously
contain a "twittertags-1.0.0-hashA" and "twittertags-1.0.0-hashB" built against
different dependencies.

The obvious difficulty is a little more trouble to manually specify packages. 
Are there any other problems
with this idea?

Brandon


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Class constraints for associated type synonyms

2011-03-23 Thread Brandon Moore
> From: Jan-Willem Maessen 

> Sent: Wed, March 23, 2011 8:43:14 PM
> 
> Hi all -
> 
> I've been trying to construct a class declaration with an  associated
> type synonym, but I'd like to constrain that type to belong to  a
> particular class.
> 
> Consider the following class:
> 
> class Monoid  m => Constructs c m | c -> m where
>   construct :: m ->  c
> 
> This captures the idea that the collection c ought to be  constructed
> using the monoid m (say if we're doing the construction using  the
> Writer monad)--the functional dependency indicates the desire for  the
> type c to injectively determine the choice of monoid m.  For  example:
> 
> newtype ListBuilder a = Builder ([a] -> [a]) deriving  (Monoid)
> 
> instance Constructs [a] (ListBuilder a) where
>construct (Builder f) = f []
> 
> instance (Ord a) => Constructs (Set a)  (Set a) where
>   construct = id
> 
> Now I'd like to be able to do the  same thing using an associated type
> synonym, something like  this:
> 
>   type  GeneratorOf a :: * -> *
>   construct :: GeneratorOf a ->  a
> 
> Now, it seems I need FlexibleInstances to do this when I'm using  an
> associated type synonym, but I don't need the flexibility when using  a
> multiparameter type class.

The conditions in the report are quite restrictive - in particular, the context
must consist only of classes applied to type variables. When you used a
multiparameter type class and an FD, the type you wanted to mention was
just a type variable.

http://www.haskell.org/onlinereport/haskell2010/haskellch4.html#x10-750004.3

The GHC user's guide suggests FlexibleContexts should be enough to allow
you to declare that class:

http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/type-class-extensions.html


FlexibleInstances seems only to affect what is allowed in an instance head.
I don't see how it helps at all, unless it implies some other extensions.

You might still run into termination issues - as a an associated type synonym
rather than an associated data type, GeneratorOf a might very well be something
large, and the conditions (disabled by UndecidableInstances) don't take 
advantage
of the acyclic superclass relationship.

http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/type-class-extensions.html#instance-rules


> In both cases the instance  constraint
> involves types that can be injectively inferred (if I have  my
> terminology straight; work with me here) from a single type  mentioned
> in the class head.  In particular, I can imagine storing  the
> dictionary for Monoid (GeneratorOf a) in the dictionary for  Generable
> a, and thus allowing context reduction of (Monoid (GeneratorOf  tyvar))
> to (Generable tyvar).  Meanwhile, I think there are things that  are
> permitted by FlexibleInstances that I'd rather *not* have  creeping
> into my programs.

Do you have any examples? I've always found FlexibleInstances alone
unproblematic - it's only when you add OverlappingInstances or worse
that things can get messy.
 
Brandon



  

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: memory slop

2011-03-22 Thread Brandon Moore
> On Tue, March 22, 2011 21:00:29 Tim Docker  wrote:

> I'm a bit shocked at the amount of wasted memory here. The sample  data file 
>has ~61k key/value pair. Hence ~122k ByteStrings - as you point  out
> many of these are very small (1500 of them are empty). Assuming it's the  
>bytestring that are generating slop, I am seeing ~500 bytes on average per  
>bytestring!

It sounds like the space is allocated but unused pages. Unless you have messed 
with some kernel memory manager settings, unused virtual pages consume no 
physical RAM.
You could confirm this by using ps to check how much RSS is actually used, 
compared to VSZ allocated (VSZ - RSS shouldn't include any actual data unless 
your system is actively swapping stuff to disk). If it is just unsued pages 
it's 
not a problem.

Brandon



  

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Heap representation evil

2006-10-23 Thread Brandon Moore

John Meacham wrote:


I am not sure if you can't use them for some reason, but this sounds
like exactly the problem that stable pointers are meant to solve:

http://haskell.org/ghc/docs/latest/html/libraries/base/Foreign-StablePtr.html


Which problem? Mostly, I noticed that evaluated Haskell values greatly resemble
a header word plus a C struct, and was thinking this could be (ab)used for 
working
with C code, and might make it easier to manipulate values on the Haskell side.
Plus, it was fun figuring out how use unsafeCoerce# and Box to manufacture
a Ptr to an ordinary Haskell value.

Stable pointers might help with the GC relocating things, except I don't think
having a stable pointer guarantees that the object won't be moved around, just
that the stable pointer won't be invalidated by GC.


On Mon, Oct 23, 2006 at 06:43:26PM -0700, Brandon Moore wrote:
  
A different and in all likelihood saner approach is building up more 
tools for manipulating pointers to C data from Haskell, perhaps along 
the lines of cmucl's support for "Alien Objects".

http://www.math.sunysb.edu/~sorin/online-docs/cmucl/aliens.html



sorry to respond twice to the same mail, but have you seen hsc2hs? it
can let you access arbitrary components of structures defined in C, or
have haskell values that map to unknown c integral types in a portable
way. 


hsc2hs is nice. it is the minimum needed to write portable haskell ffi
using code.

Thanks, I've seen related things in c2hs, but I didn't realize
hsc2hs came with GHC.

Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Heap representation evil

2006-10-23 Thread Brandon Moore
Thinking to take advantage of fortuitous heap layout of some Haskell 
values for interfacing with C, I've written the following function:


addressOf :: a -> Ptr ()
addressOf x = x `seq` unsafeCoerce# (Box x)
data Box x = Box x

For example,

data A = A {-# UNPACK #-} !(Ptr Word8) {-# UNPACK #-} !CInt

main = let a = A nullPtr 12
  p = addressOf a `plusPtr` 4
in do x <- peek p :: IO Int
  y <- peek p :: IO Int
  print (x, y)
prints
(0, 12)

One thing I don't understand is that this fails if I use Just
rather than inventing my box type. I suppose the info table for
Just is set up to support a vectored return for pattern matching
on Maybe? (the commentary isn't very clear here. The section
http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/HaskellExecution#ReturnConvention
says, in full:
"Return Convention
Direct Returns
Vectored Returns"
)

The reason I'm messing about with this stuff is that I'm pretty sure 
passing p to C code would give a usable pointer to

struct a {char *; int;};

Obviously my plot will be spoiled if the GC comes along and relocates 
the value while C code is trying to use it.


Are there any other pitfalls with this approach?

A different and in all likelihood saner approach is building up more 
tools for manipulating pointers to C data from Haskell, perhaps along 
the lines of cmucl's support for "Alien Objects".

http://www.math.sunysb.edu/~sorin/online-docs/cmucl/aliens.html

The main reason to even think about touching the heap representation of 
Haskell objects is so that the values can be manipulated by pure code,

pattern matched, etc.

Brandon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users