[Haskell-cafe] Fw: [darcs-devel] Inferred type is less polymorphic than expected and type witnesses

2009-01-12 Thread Rob Hoelz
Forwarding to Haskell Cafe per Eric's suggestion.

Begin forwarded message:

Date: Sun, 11 Jan 2009 23:01:31 -0600
From: Rob Hoelz r...@hoelzro.net
To: darcs-de...@darcs.net
Subject: [darcs-devel] Inferred type is less polymorphic than
expected and type witnesses


Hello again, Darcs users and developers,

As I mentioned in my last e-mail, I'm working on
http://bugs.darcs.net/issue291.  It's actually gone pretty well, and I
feel I'm just about finished (I've done all but sorting out the
changes after leaving the editor), only I've encountered the compiler
error you see in the subject of this message. This error only appears
when compiling with witnesses. Here's the source for the function
that it's complaining about:

compare_changes_with_old (x :: xs) (y :: ys) =
  case compare_changes_with_old xs ys of
nx : ny - if unsafeCompare x y
  then ((x :: nx) : ny)
  else (NilFL : (y :: ys))
compare_changes_with_old NilFL NilFL = (NilFL : NilFL)
compare_changes_with_old NilFL ys@(_ :: _) = (NilFL : ys)
compare_changes_with_old x@(_ :: _) NilFL = (NilFL : NilFL)

Now, I have two questions:

1) What exactly does this error mean, and how do I get around it?
2) What are witness types, and what are they used for?

I will gladly accept links to fine manuals as answers to either
question, but simple explanations would be nice. =D  I thought I
understood Haskell pretty well, but existentially qualified types have
thrown me for a loop.

Thanks much,
Rob Hoelz
___
darcs-devel mailing list (AUTOMATIC POSTINGS ONLY PLEASE!)
darcs-de...@darcs.net
http://lists.osuosl.org/mailman/listinfo/darcs-devel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fw: [darcs-devel] Inferred type is less polymorphic than expected and type witnesses

2009-01-12 Thread Rob Hoelz
I should've included these when I forwarded it, but that was pre-coffee
today. =P

class MyEq p where
  unsafeCompare :: p C(a b) - p C(c d) - Bool
  -- more stuff

data FL a C(x z) where
  (::) :: a C(x y) - FL a C(y z) - FL a C(x z)
  NilFL :: FL a C(x x)

data (a1 : a2) C(x y) = FORALL(z) (a1 C(x z)) : (a2 C(z y))
infixr 1 :

-- I'm not entirely sure on this one, because type witnesses confuse me.
compare_changes_with_old :: (Patchy p) = 
  FL p C(x y)
   - FL p C(x y)
   - (FL p : FL p) C(x y)

C(args...) is a preprocessor macro that expands to args if Darcs is
building with GADT type witnesses.  FORALL(args...) expands to forall
args. under the same condition.

All of the definitions are available at
http://darcs.net/api-doc/doc-index.html as well.

Thanks,
Rob

Ryan Ingram ryani.s...@gmail.com wrote:

 Some questions first:
 What's the type of this function supposed to be?
 What's the type of unsafeCompare?
 How is the data type with NilFL and :: defined?
 
   -- ryan
 
 On Mon, Jan 12, 2009 at 5:43 AM, Rob Hoelz r...@hoelzro.net wrote:
  Forwarding to Haskell Cafe per Eric's suggestion.
 
  Begin forwarded message:
 
  Date: Sun, 11 Jan 2009 23:01:31 -0600
  From: Rob Hoelz r...@hoelzro.net
  To: darcs-de...@darcs.net
  Subject: [darcs-devel] Inferred type is less polymorphic than
  expected and type witnesses
 
 
  Hello again, Darcs users and developers,
 
  As I mentioned in my last e-mail, I'm working on
  http://bugs.darcs.net/issue291.  It's actually gone pretty well,
  and I feel I'm just about finished (I've done all but sorting out
  the changes after leaving the editor), only I've encountered the
  compiler error you see in the subject of this message. This error
  only appears when compiling with witnesses. Here's the source for
  the function that it's complaining about:
 
  compare_changes_with_old (x :: xs) (y :: ys) =
   case compare_changes_with_old xs ys of
 nx : ny - if unsafeCompare x y
   then ((x :: nx) : ny)
   else (NilFL : (y :: ys))
  compare_changes_with_old NilFL NilFL = (NilFL : NilFL)
  compare_changes_with_old NilFL ys@(_ :: _) = (NilFL : ys)
  compare_changes_with_old x@(_ :: _) NilFL = (NilFL : NilFL)
 
  Now, I have two questions:
 
  1) What exactly does this error mean, and how do I get around it?
  2) What are witness types, and what are they used for?
 
  I will gladly accept links to fine manuals as answers to either
  question, but simple explanations would be nice. =D  I thought I
  understood Haskell pretty well, but existentially qualified types
  have thrown me for a loop.
 
  Thanks much,
  Rob Hoelz
  ___
  darcs-devel mailing list (AUTOMATIC POSTINGS ONLY PLEASE!)
  darcs-de...@darcs.net
  http://lists.osuosl.org/mailman/listinfo/darcs-devel
  ___
  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] Damnit, we need a CPAN.

2008-05-29 Thread Rob Hoelz
Neil Mitchell [EMAIL PROTECTED] wrote:

 Hi
 
  Rationale: We need a CPAN
 
 We choose to spell CPAN as Hackage
 
 , a cabal that is smart enough to know what to
  to, even if building depends on make
 
 Why should building depend on make? Shouldn't cabal build stuff for
 us? We need a cabal that is clever enough that we don't need a make.
 
 , grapefruit authors that commit
  to hackage
 
 Or someone to help show the grapefruit authors the light. I helped put
 smallcheck on hackage, others have done other packages. Perhaps you
 could do grapefruit?
 
 , a cabal-inst that can install from darcs (or at least from
  a local directory)
 
 Yes, that would be lovely!
 
 , or maybe just a make-replacement for haskell, like
  java has with ant (which is really cool if you successfully do not
  notice the xml-syntax).
 
 We have replaced a lot of make with just --make in GHC. Cabal replaces
 more. What more bits of make do you need? If you can say why make is
 still necessary, people may be able to eliminate it.
 
 Thanks
 
 Neil
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

Hackage and Cabal are nice, but a command line tool for automatically
searching Hackage and installing Hackage packages (like the cpan
program, or easy_install) would be nice.  Unless I haven't done my
homework and this tool exists...

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


[Haskell-cafe] Haskell interface file (.hi) format?

2007-11-29 Thread Rob Hoelz
Hello fellow Haskellers,

Does anyone know if/where I can find a specification for the .hi files
generated by GHC?  I ask because I want to write an omni-completion
plugin for Vim to make Haskell hacking a bit nicer.

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


Re: [Haskell-cafe] Haskell interface file (.hi) format?

2007-11-29 Thread Rob Hoelz
Claus Reinke [EMAIL PROTECTED] wrote:

  Does anyone know if/where I can find a specification for the .hi
  files generated by GHC?  I ask because I want to write an
  omni-completion plugin for Vim to make Haskell hacking a bit nicer.
 
 you might find it easier to use GHCi's :browse command
 
 $ ghc -e ':browse Control.Concurrent.MVar'
 modifyMVar :: MVar a - (a - IO (a, b)) - IO b
 modifyMVar_ :: MVar a - (a - IO a) - IO ()
 readMVar :: MVar a - IO a
 swapMVar :: MVar a - a - IO a
 withMVar :: MVar a - (a - IO b) - IO b
 data MVar a = GHC.IOBase.MVar (GHC.Prim.MVar# GHC.Prim.RealWorld
 a) addMVarFinalizer :: MVar a - IO () - IO ()
 isEmptyMVar :: MVar a - IO Bool
 newEmptyMVar :: IO (MVar a)
 newMVar :: a - IO (MVar a)
 putMVar :: MVar a - a - IO ()
 takeMVar :: MVar a - IO a
 tryPutMVar :: MVar a - a - IO Bool
 tryTakeMVar :: MVar a - IO (Maybe a)
 
 that is what the haskell mode plugins for vim use, for one
 of their completion modes, anyway;-)
 
 http://www.cs.kent.ac.uk/~cr3/toolbox/haskell/Vim/
 
 (actually, that completion is wrt to imported identifiers,
 so we simply do a ':browse *current_module'; another 
 completion mode is based on haddock indices, and then 
 there are the standard occurs-in-imported-source-files 
 and occurs-in-tags-file completions)
 
 claus
 

Wow!  Thanks for saving me a ton of work, everyone!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] IO Monad operation madness

2007-05-17 Thread Rob Hoelz
Hello again,

I'm still working on that binding, and I've come to a problem that I
just can't figure out.  I'm sure it's staring me right in the face, so
I think another pair of eyes to take a look.

So if you look at my previous message, I defined a linked list data
type in C.  I'm trying to convert it to a Haskell list of strings, so
here's my function:

linkedListToHaskellStringList :: LinkedList - IO [String]
linkedListToHaskellStringList listPtr =
let convertList' ptr =
if listIsNull ptr
then
[]
else
let str = peekCString = (linked_list_getdata ptr)
next - linked_list_next ptr
str : (convertList' next)
in
sequence $ convertList' listPtr

listIsNull :: LinkedList - Bool
listIsNull (LinkedList ptr) = ptr == nullPtr

So here's the compile error:

Option.hsc:63:14:
Couldn't match expected type `[t]'
   against inferred type `IO LinkedList'
In a 'do' expression: next - linked_list_next ptr
In the expression:
if listIsNull ptr then
[]
else
do let str = peekCString = linked_list_getdata ptr
   next - linked_list_next ptr
 str : (convertList' next)
In the definition of `convertList'':
convertList' ptr
   = if listIsNull ptr then
 []
 else
 do let str = ...
next - linked_list_next ptr
  str : (convertList' next)

Could anyone tell me what I'm doing wrong?  Thanks a lot!

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


Re: [Haskell-cafe] IO Monad operation madness

2007-05-17 Thread Rob Hoelz
Isaac Dupree [EMAIL PROTECTED] wrote:

  linkedListToHaskellStringList :: LinkedList - IO [String]
  linkedListToHaskellStringList listPtr =
  let convertList' ptr =
 convertList' :: LinkedList - [IO String], I infer?

Correct.
  if listIsNull ptr
  then
  []
  else
 are you doing IO here or not? You need a 'do' if you are (else this
 is a syntax error), but IO /= [], so what is the function returning?
My mistake; I left off the 'do.'  My original code does have it, though.

I figure since the null case returns [] (which should be a valid [IO
String], and str is an IO String, it should work.  In fact, if I take
out the next - ... line and substitute ptr for next, it compiles.  But
that's not exactly desirable behavior...=P

  let str = peekCString = (linked_list_getdata ptr)
  next - linked_list_next ptr
  str : (convertList' next)
  in
  sequence $ convertList' listPtr
  
  listIsNull :: LinkedList - Bool
  listIsNull (LinkedList ptr) = ptr == nullPtr
 
 I'd recommend recursion without the 'sequence', I think, so you can do
 IO along the way - traversing the LinkedList - and then 'return' the
 list made from (:).  (and throw in unsafeInterleaveIO if you're
 feeling sadistical and want parts of the traversal to be performed at
 unspecified later dates)

The problem I have with that is that I'd have to do something like this:

str - peekCString = (linked_list_getdata ptr)
next - linked_list_next ptr
rest - linkedListToHaskellStringList next
return (str : rest)

I don't like this because it's not really tail recursive.  I've been
told tail recursion is overrated, but since I don't really know how
long the C linked lists are going to be (could be 10 elements, could be
100), I don't think avoiding a stack overflow is overrated.

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


Re: [Haskell-cafe] IO Monad operation madness

2007-05-17 Thread Rob Hoelz
Isaac Dupree [EMAIL PROTECTED] wrote:

 
 Isaac Dupree wrote:
  liftM2 (:)
(peekCString = (linked_list_getdata ptr))
(linkedListToHaskellStringList = linked_list_next ptr)
 
 formerly missing parenthesis fixed in the above before it bites you :(
 
 Isaac

Thanks for the help, Isaac.  I didn't know how good of a job GHC did
when optimizing code like that.  I don't have a problem with that code
I wrote as a rule (it doesn't look ugly to me), but I just wanted to
make sure my binding didn't cause crashes.  I like the liftM2 thing,
though; I think I'll go with that.

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


[Haskell-cafe] Safe/Unsafe calls with the GHC Foreign Function Interface

2007-05-17 Thread Rob Hoelz
More questions from Rob regarding his mysterious bindings...

So I've been reading the docs for the FFI, and it's my understanding
that foreign functions imported as unsafe are faster, but they've got
a problem with callbacks.  From what I read, I believe that I should
just make a foreign function safe if it sets up a callback; is this
correct?  Normally I wouldn't bother people with questions like this,
but I'd rather be absolutely certain and avoid tracking down a strange
bug later.

Many thanks as always,
Rob
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Safe/Unsafe calls with the GHC Foreign Function Interface

2007-05-17 Thread Rob Hoelz
Stefan O'Rear [EMAIL PROTECTED] wrote:

 On Thu, May 17, 2007 at 10:32:11PM -0500, Rob Hoelz wrote:
  More questions from Rob regarding his mysterious bindings...
  
  So I've been reading the docs for the FFI, and it's my understanding
  that foreign functions imported as unsafe are faster, but they've
  got a problem with callbacks.  From what I read, I believe that I
  should just make a foreign function safe if it sets up a callback;
  is this correct?  Normally I wouldn't bother people with questions
  like this, but I'd rather be absolutely certain and avoid tracking
  down a strange bug later.
  
  Many thanks as always,
  Rob
 
 If it *calls* a callback into haskell.
 
 Also, for unfathomable reasons, safety has been overloaded to include
 forking OS threads.  If it could block (like getchar), you must make
 it safe. 
 
 Stefan

Ouch...how bad is the overhead for a safe function?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Rob Hoelz
Hello everyone,

You may have seen my message about how I'm writing a binding to a C
library.  This is another question related to that.

So, let's say I have a linked list implemented in C.  Here's what its
definition looks like:

struct __linked_list {
void *data;
struct __linked_list *next;
};

typedef struct __linked_list linked_list_t;

void *linked_list_getdata(linked_list_t *);
linked_list_t *linked_list_next(linked_list_t *);

Keep in mind, this is just a segment.

So using the Haskell FFI, I import these into my .hsc file:

data LinkedList = LL (Ptr linked_list_t)

foreign import ccall unsafe linked_list.h 
linked_list_getdata :: Ptr LinkedList - IO Ptr a

foreign import ccall unsafe linked_list.h
linked_list_next :: Ptr LinkedList - IO Ptr LinkedList

So now that that's done, I attempt to write a Ptr LinkedList -
[String] function (assuming the given LinkedList is holding c strings):

linkedListToStringList :: Ptr LinkedList - IO [String]
linkedListToStringList listPtr =
if listPtr == nullPtr
then 
return []   
else do
item - linked_list_getdata listPtr
next - linked_list_next listPtr
cStr - peek item
hStr - peekCString cStr
t - linkedListToStringList next
return (hStr : t)

This is just ugly...making the recursive call first, THEN consing the
value on?  However, this is the only way I could think of doing it.  I
figure there are three possibilities from here:

1) Leave this code alone, as GHC will optimize it because it's smart.
2) There's a way to more effectively write this code!  Change it!
3) Roll my own optimization.

I know how to do 3, but I'd rather avoid it.  I guess I'm looking for
an answer to 2, but if 1 is true, that'd be ok too.  Could anyone give
me a hand?

And as long as I'm asking, is there some kind of monadic function
composition operator?  I'd like to clean up the above with something
like peekCString . peek . linked_list_getdata...

Many thanks,
Rob Hoelz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tail Recursion within the IO Monad

2007-05-16 Thread Rob Hoelz
Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote:

 
 On May 16, 2007, at 12:23 , Rob Hoelz wrote:
 
  And as long as I'm asking, is there some kind of monadic function
  composition operator?  I'd like to clean up the above with something
  like peekCString . peek . linked_list_getdata...
 
 (=)?
 

Thanks for the reply;  I can't believe I missed that one!  But while
looking over the documentation, completely humbled, I discovered
sequence, which allows me to write my code cleanly!  Thanks for the
help!

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


[Haskell-cafe] Converting CTime - Int

2007-05-15 Thread Rob Hoelz
Hello everyone,

I'm writing an interface to C code, and one of the functions I'm
wrapping returns time_t.  I see that this maps to CTime in
Foreign.C.Types, but I can't figure out how to convert it to an Int (or
any other useful Haskell type, for that matter) for the life of me.
I've poured over the standard library docs, but to no avail.  Could
someone give me a hint?

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


Re: [Haskell-cafe] Any Haskellers anywhere? (was Re: Any Haskellers in St Louis, MO?)

2007-05-05 Thread Rob Hoelz
Sounds like a good idea to me.  I'd like to see if any Haskellers are
in Madison.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Any Haskellers anywhere?

2007-05-05 Thread Rob Hoelz
Gabor Greif [EMAIL PROTECTED] wrote:

 Am 06.05.2007 um 03:52 schrieb Rob Hoelz:
 
  Sounds like a good idea to me.  I'd like to see if any Haskellers
  are in Madison.
 
 Doesn't Google have a service for visualizing locations on a map?
 The wiki could point there, for example...
 
   Gabor

I bet Google does have one, but first thing that came to my mind is
Frappr: http://www.frappr.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe