[Haskell-cafe] bizarre syntax error

2009-06-27 Thread Geoffrey Irving
I ran into a unfortunate syntax error just now.  I figured I'd share
it because it's the weirdest message I've ever gotten out of ghc.  The
broken code is

case t of
  TyApply tv types -> do
(tvl, cases) <- lookupDatatype prog tv
let tenv = Map.fromList (zip tvl types)  -- GHC POINTS HERE
caseType (c,vl,e')
  | Just tl <- List.lookup c cases =
  if length vl == a then
expr prog global (foldl (\e (v,t) -> Map.insert v
t e) env (zip vl (map (subst tenv) tl))) e'
  else
typeError ("arity mismatch in pattern: "++show
(pretty c)++" expected "++show a++" argument"++(if a == 1 then "" else
"s")
  ++" but got ["++concat (intersperse ", " (map
(show . pretty) vl))++"]")
  where a = length tl -- THIS IS THE PROBLEM
  | otherwise = typeError ("datatype "++show (pretty
tv)++" has no constructor "++show (pretty c))
defaultType Nothing = return []
defaultType (Just (v,e')) = expr prog global (Map.insert v
t env) e' >>=. \t -> [t]
join t1 t2 | Just t <- unifyS t1 t2 = return t
   | otherwise = typeError ("failed to unify types
"++show (pretty t1)++" and "++show (pretty t2)++" from different case
branches")
caseResults <- mapM caseType pl
defaultResults <- defaultType def
foldM1 join (caseResults ++ defaultResults)
  _ -> typeError ("expected datatype, got "++show (pretty t))

ghc complains that

"The last statement in a 'do' construct must be an expression"

and points to the line declaring "tenv".  The actual problem is that
you can't put a "where" block in between two pattern guards. :)

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


Re: [Haskell-cafe] unique identity and name shadowing during type inference

2009-06-25 Thread Geoffrey Irving
Thanks.  I'll go with the monad for now.

Geoffrey

On Sat, Jun 20, 2009 at 4:40 PM, Lennart
Augustsson wrote:
> Use 1.  You'll probably need a monad in the type checker soon or later
> anyway, e.g., for handling errors.

On Sun, Jun 21, 2009 at 5:13 AM, Zsolt Dollenstein wrote:
> I think you should also take a look at the value-supply package. At least
> that was my solution for scope analysis issues.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] unique identity and name shadowing during type inference

2009-06-20 Thread Geoffrey Irving
Hello,

I am designing a type inference algorithm for a language with
arbitrary function overloading.  For various reasons (beyond the scope
of this email), it's impossible to know the full type of an overloaded
function, so each function is assigned a unique primitive type and the
inference algorithm gradually learns more information about the
primitive.  For example, if we declare an identity function

f x = x

the algorithm will create a primitive type F, and record f :: F.  If
we use the function a few times,

f 1
f "blah"

the algorithm will infer

F Int = Int
F String = String

My question is: what's the best way to represent these unique
primitive types in Haskell?  A new type primitive needs to be created
whenever we process a function declaration.  Nested function
declarations produce a different primitive each time the parent is
invoked with different argument types.  These separate primitives can
escape if local functions are returned, so the inference algorithm
must be able to keep them separate and learn more about them after
their parent function is forgotten.

Here are a few ways I know of:

1. Thread a uniqueness generator monad through the whole algorithm.
I'd prefer to avoid this extra plumbing if possible.
2. Label primitives with the full context of how they were created.
If function f declares a nested function g, and f is called with Int
and Char, the primitives for g would be labeled with "f Int" and "f
Char" to keep them separate.  This is similar to lambda lifting.
3. Scary hacks involving makeStableName and unsafePerformIO.  Some
sort of context would have to be thrown around here to make sure GHC
doesn't merge the different makeStableName calls.

Unfortunately, method (2) is complicated by the fact that variable
names are not unique even in the internal representation (I'm using
the trick from [1]), so I'm not sure what the minimal unique "context"
would be.

Does anyone know other methods outside of (1), (2), or (3), or clean
ways of structuring (2) or (3)?

Thanks!
Geoffrey

[1]: http://www.haskell.org/~simonmar/bib/ghcinliner02_abstract.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: [Announce] primes

2009-04-16 Thread Geoffrey Irving
On Thu, Apr 16, 2009 at 12:39 PM, Daniel Fischer
 wrote:
> Am Donnerstag 16 April 2009 16:45:59 schrieb Niemeijer, R.A.:
>> Sebastian Fischer wrote:
>> > I am pleased to announce the package 'primes' that implements lazy
>> > wheel sieves for efficient, purely functional generation of prime
>> > numbers in Haskell.
>> >
>> > The implementation is reasonably efficient. The query
>> >
>> >  > primes !! 100
>> >
>> > 15485867
>> >
>> > answers after a few seconds.
>> >
>> > Feel free to contribute more functionality to this package. The
>> > sources are on Github:
>> >
>> >      http://github.com/sebfisch/primes
>> >
>> > If you fork my project, I'll be happy to merge your changes.
>>
>> I have just finished benchmarking all the implementations provided in
>> http://www.cs.hmc.edu/~oneill/code/haskell-primes.zip (the zip file linked
>> to from the Haskell wiki article on primes).
>>
>> NaurPrimes.hs is by far the fastest version, and at least 2 or 3 times
>> faster than your current implementation. I'm pretty sure it also uses less
>> memory. I want to find efficient algorithms for the other proposed
>> functions before forking, but I figured I'd let you know in the meantime.
>
> Nevertheless, a bitsieve is much faster:
>
> Prelude NaurPrimes> length $ primesToLimit (10^8)
> 5761455
> (26.50 secs, 5734921092 bytes)
> Prelude NaurPrimes> :l
> Ok, modules loaded: none.
> (0.00 secs, 0 bytes)
> Prelude> :m +Euler.Primes
> Prelude Euler.Primes> length $ primesUpTo (10^8)
> Loading package base-3.0.3.0 ... linking ... done.
> Loading package euler-0.1 ... linking ... done.
> 5761455
> (2.14 secs, 573050276 bytes)
>
> The problems for a bitsieve are
> a) you don't easily get the small primes before sieving is complete
> b) how to proceed after the sieving bound

You can solve both of these by always sieving up to powers of 2.  If
you've sieved up to 2^n you can extend it to 2^(n+1) by restarting the
sieve and using the fact that you don't need to recheck the first half
of the range.  The result shouldn't be much slower than a full sieve,
and can probably be written entirely with unboxed array monads (no
unsafePerformIO)  if desired.

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