Re: [Haskell-cafe] Yet another Conduit question

2013-02-04 Thread Kevin Quick
While on the subject of conduits and timing, I'm using the following  
conduit to add elapsed timing information:


timedConduit :: MonadResource m = forall l o u . Pipe l o o u m (u,  
NominalDiffTime)

timedConduit = bracketP getCurrentTime (\_ - return ()) inner
where inner st = do r - awaitE
case r of
  Right x - yield x  inner st
  Left  r - deltaTime st = \t - return (r,t)
  deltaTime st = liftIO $ flip diffUTCTime st $ getCurrentTime

I'm aware that this is primarily timing the downstream (and ultimately the  
Sink) more than the upstream, and I'm using the bracketP to attempt to  
delay the acquisition of the initial time (st) until the first downstream  
request for data.


I would appreciate any other insights regarding concerns, issues, or  
oddities that I might encounter with the above.


Thanks,
  Kevin

On Mon, 04 Feb 2013 02:25:11 -0700, Michael Snoyman mich...@snoyman.com  
wrote:



I think this is probably the right approach. However, there's something
important to point out: flushing based on timing issues must be handled
*outside* of the conduit functionality, since by design conduit will not
allow you to (for example) run `await` for up to a certain amount of  
time.

You'll probably need to do this outside of your conduit chain, in the
initial Source. It might look something like this:

yourSource = do
mx - timeout somePeriod myAction
yield $ maybe Flush Chunk mx
yourSource


On Sun, Feb 3, 2013 at 5:06 PM, Felipe Almeida Lessa  
felipe.le...@gmail.com

wrote:



I guess you could use the Flush datatype [1] depending on how your
data is generated.

Cheers,

[1]
http://hackage.haskell.org/packages/archive/conduit/0.5.4.1/doc/html/Data-Conduit.html#t:Flush

On Fri, Feb 1, 2013 at 6:28 AM, Simon Marechal si...@banquise.net  
wrote:

 On 01/02/2013 08:21, Michael Snoyman wrote:
 So you're saying you want to keep the same grouping that you had
 originally? Or do you want to batch up a certain number of results?
 There are lots of ways of approaching this problem, and the types  
don't

 imply nearly enough to determine what you're hoping to achieve here.

 Sorry for not being clear. I would like to group them as much as
 possible, that is up to a certain limit, and also within a time
 threshold. I believe that the conduit code will be called only when
 something happens in the conduit, so an actual timer would be useless
 (unless I handle this at the source perhaps, and propagate ticks).

 That is why in my first message I talked about stacking things into  
the
 list until the conduit has no more input available, or a maximum size  
is

 reached, but was not sure this even made sense.

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



--
Felipe.




--
-KQ

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


Re: [Haskell-cafe] Ticking time bomb

2013-01-31 Thread Kevin Quick

Git has the ability to solve all of this.

...
2. Uploads to hackage either happen through commits to the git  
repository,

or an old-style upload to hackage automatically creates a new anonymous
branch in the git repository.
3. The git repository is authorative.  Signing releases, code reviews  
etc.

all happens through the git repositories.  This gives us all the
flexibility of a git-style trust model.

...

5. Who owns which package names can be held in a separate meta-tree git
repository, and can have consensus requirements on commits.
6. This special meta-tree can also contain suggested verification keys  
for

commits to the other hackage git trees.  It can even contain keys that
protect Haskell namespaces in general, so that no hackage package can
overwrite a protected Haskell namespace.
7. As backward compatibility, the meta-tree can sign simple hashes of
already existing packages on hackage.

...

1. There could be some git magic script that downloads the signed git tag
objects only (small data set).  Then another script would generate a
git-compatible SHA1 of the extracted tarball, given that the tarball was
fetched from hackage.
2. Or cabal-install could fetch directly from git repositories and use
standard git verification.
3. Or a trusted machine creates tarballs from the git repositories, signs
them and uploads them to hackage.


Without details of git's trust/verification model, it's difficult to see  
how this particular SCM tool provides the trust capabilities being  
discussed any better than a more focused solution.  Additionally, the use  
of git is also difficult for many Windows users (80MB installed footprint,  
last I tried).  git has a much broader solution space than simply ensuring  
the integrity of package downloads, especially when there could be some  
git magic script that is still not identified and appears to have the  
same insecurities as the package download/upload itself.


Instead of using the git solution and looking for problems to solve with  
it, IMHO we should work from clearly defined problem to solution in  
general terms as our class, and then determine what specific tools  
represent an instance of that  solution class.


--
-KQ

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


Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-02-01 Thread Kevin Quick


On Wed, 01 Feb 2012 19:42:19 -0700, AntC anthony_clay...@clear.net.nz  
wrote:


A piece of background which has perhaps been implicit in the discussions  
up to

now. Currently under H98:
   f.g-- (both lower case, no space around the dot)
Is taken as function composition -- same as (f . g).
   f.  g  -- is taken as func composition (f . g)
   f  .g  -- is taken as func composition (f . g)


And so it is.  Could have sworn these weren't accepted, but clearly I'm  
wrong.  Thanks for pointing this out.


All proposals are saying that if you want to use dot as function  
composition
you must always put the spaces round the dot (or at least between the  
dot and

any name) -- even if you're part-applying. So:
  (f .)   -- part-apply function composition on f
  (. g)   -- part-apply function composition


+1

SOPR? SPJ's current proposal is abbreviated as SORF (Simple  
Overloaded

Record Fields).


Yes, I caught this 5 minutes *after* hitting send (of course).


In these examples you're giving, I assume recs is a list of records(?).


Yes.  I err'd on the side of brevity.



...


In the RHCT examples, I assume r is a record, f is a field (selector
function) -- or is it 'just some function'?


It should be a field selector.


RHCT:  map (\r - f r) recs

is the same as:  map f recs-- by eta reduction
so map f takes a list of records, returns a list of the f field from each
This also works under H98 record fields, with type enforcement that the
records must be of the single type f comes from.


RHCT:  map (\r - r.$rev_ f) recs

Beware that (.$) is an operator, so it binds less tightly than function
application, so it's a poor 'fake' syntactically. Did you mean .$ to  
simulate

dot-notation to extract field rev_ from r?


Sort of.  I didn't fully grasp your implemenation and based on your  
clarification I think I should have written:


map (\r - r.$f) recs

to extract field f from a single record r (from the recs collection).




RHCT:  map ((.$)f) recs

If you mean this to return a list of the f fields from recs, put:
 map f recs
I don't know what else you could be trying to do.


I was trying to eta-reduce my previous (corrected) situation *but* also  
indicate that I specifically want the field selector rather than some  
arbitrary f.  I wanted to extract the field f of every record in recs but  
clearly indicate that f was a field selector and not a free function.


If partial application is allowed (against SPJ's inclination and  
explicitly

disallowed in your scheme), I could have:

map .f recs


If you mean this to return a list of the f fields from recs, put:
DORF:  map f recs-- are you beginning to see how easy  
this is?


I'm saying the .f should be rejected as too confusing.
(That is, under DORF aka RHCT. Under SORF or TDNR I'm not sure, which is  
why I
don't like their proposals for dot notation, which is why I  
re-engineered it

so that dot notation is tight-binding reverse function application **and
nothing more**.)


And this is finally our difference.  I had wanted the no-space preceeding  
dot syntax (.f) to specifically indicate I was selecting a field.  This  
desire was based on expectations of partial application and being unaware  
of the H98 valid interpretation of this as partial function application. I  
think perhaps I was overly concerned on this point though.  The issue can  
be resolved by explicit module namespace notation (ala. Prelude.map v.s.  
Data.List.map).


In addition, under SORF, SPJ indicated that Dot notation must work in  
cascades (left-associatively), and with an expression to the left:

  r.x
  r.x.y
  (foo v).y

I assume DORF would also support this as well and that r.x.y.z would  
desugar to z (y (x r)).


With regards to module namespace notation, neither SORF nor DORF mentions  
anything that I found, but I'm assuming that the assertion is that it's  
not needed because of the type-directed resolution.  To wit:


Rlib/Recdef.hs:

module Rlib.Recdef (R(..)) where

data Rec = R { foo :: String } deriving Show


Rlib/Rong.hs:

module Rong (T(..)) where
import Rlib.Recdef
data Rstuff = T { baz :: R }

foo :: Rec - String
foo = show


main.hs:

import Rlib.Recdef
import Rlib.Rong
main = let r = R hi
   t = T r
   bar, bar_pf :: Rstuff - String
   bar_pf = Rlib.Recdef.foo . Rlib.Rong.baz
   bar x = x.baz.foo
   in assert $ bar_pf t == bar t
  assert $ Rlib.Rong.foo r /= Rlib.Recdef.foo r


The assumptions are that the syntax of bar and bar_pf would be the same  
for both SORF and DORF, and that no namespace qualifiers are needed (or  
allowed) for bar  (i.e. you wouldn't write something like bar x =  
x.Rlib.Rong.baz.Rlib.Recdef.foo).


Apologies for putting you through the syntax grinder, and especially when  
I'm not really qualified to be operating said grinder.  

Re: [Haskell-cafe] Some thoughts on Type-Directed Name Resolution

2012-01-31 Thread Kevin Quick



On Tue, 31 Jan 2012 23:10:34 -0700, Anthony Clayden  
anthony_clay...@clear.net.nz wrote:

I'm proposing x.f is _exactly_ f x. That is, the x.f gets
desugared at an early phase in compilation.


Anthony,

I think part of the concern people are expressing here is that the above  
would imply the ability to use point-free style.  But this orthogonality  
is disavowed by your exception:



A 'one-sided dot doesn't mean anything.


I haven't read the underlying proposals, so I apologize if the following  
is covered, but my understanding of the discussion is that the x.f  
notation is intended to disambiguate f to be a field name of the type of x  
and therefore be advantageous over f x notation where f is presently in  
the global namespace.


With your exception, I still cannot disambiguate the following:

data Rec = { foo :: String }

foo :: Rec - String
foo = show

rs :: [Rec]
rs = [ ... ]

bar = map foo rs

If the exception doesn't exist, then I could write one of the following to  
clarify my intent:


bar = map foo rs
baz = map .foo rs


--
-KQ

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


Re: [Haskell-cafe] Avoiding parametric function binding

2012-01-02 Thread Kevin Quick
On Sun, 01 Jan 2012 05:29:42 -0700, Sebastian Fischer fisc...@nii.ac.jp  
wrote:

On Sat, Dec 31, 2011 at 4:09 PM, Kevin Quick qu...@sparq.org wrote:
 onVarElem :: forall a . (Show a) = (Maybe a - String) - Var -  
String


The problem is the scope of the quantification of the type variable 'a'.
You can use higher-rank types (via the Rank2Types or RankNTypes language
extension) to achieve what you want. Change the type of 'onVarElem' to

onVarElem :: (forall a . (Show a) = Maybe a - String) - Var -  
String


Thanks to both Sebastian and Sean for the solution (abbreviated from  
Sebastian's reponse above).


-Kevin

P.S.  Sorry for the late followup: some minor system issues prevented  
checking email for a little while.  The delay notwithstanding, *all* of  
the responses were much appreciated.


--
-KQ

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


[Haskell-cafe] Avoiding parametric function binding

2011-12-31 Thread Kevin Quick
I'm having some difficulty avoiding a tight parametric binding of function  
parameters, which is limiting the (de)composability of my expressions.   
I'm curious as to whether there is an option or method I haven't tried to  
achieve this.


Here's an example test case:


data Var = V1 (Maybe Int)
 | V2 (Maybe String)

test = V1 (Just 1)


Given this structure, I can do something like this:


elemStr :: (Show a) = Maybe a - String
elemStr = show

varStr (V1 x) = elemStr $ id x
varStr (V2 x) = elemStr $ id x

main = putStrLn . varStr $ test


This operation extracted the internal value from the Var container, and  
then passes it to a parametric function (id) and that result to another  
parametric function with a class restriction on the input.  This is fine  
so-far.


However, what I'd like to do is decompose this to allow more flexibility  
(using id is pretty boring) without having to repeat the extraction  
boilerplate each time.  My first attempt:



varElem :: forall x . (Show x) = Var - x
varElem (V1 x) = x
varElem (V2 x) = x

main = putStrLn . elemStr . varElem $ test


This fails because even though I've specified the same class constraint  
for the output type of varElem that elemStr requires on its input element,  
the compiler binds the parametric type of x when it processes the first  
(V1) definition and fails with an error on the second definition because  
it asserts that x must be an Int and it found a String.


I realized that the parametric output type was awkward, so I tried  
inverting the design (somewhat similar to fmap):



onVarElem :: forall a . (Show a) = (Maybe a - String) - Var - String
onVarElem f (V1 x) = f x
onVarElem f (V2 x) = f x

main = putStrLn . onVarElem elemStr $ test


This is probably a better design, but still fails for the same reason:

Couldn't match expected type `Int' with actual type `[Char]'
Expected type: Maybe Int
  Actual type: Maybe String
In the first argument of `f', namely `x'
In the expression: f x

Even changing onVarElem so the second parameter was a simple variable and  
performing the pattern match in an internal where or let binding failed  
because the first application of f bind its parametric values.


Is there a way to delay this parametric binding to allow composable  
function specifications?


Thanks,
  Kevin

--
-KQ

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


Re: [Haskell-cafe] Avoiding parametric function binding

2011-12-31 Thread Kevin Quick
On Sat, 31 Dec 2011 08:50:05 -0700, Stephen Tetley  
stephen.tet...@gmail.com wrote:



Maybe you want a deconstructor (sometime called an eliminator)?

deconsVar :: (Maybe Int - a) - (Maybe String - a) - Var - a
deconsVar f g (V1 a) = f a
deconsVar f g (V2 b) = g b


That works and has the advantage of allowing a single deconstructor  
definition that can be reused in multiple places, but it requires me to  
add an argument for each wrapped type, which causes some ripple effect if  
the type changes.


Also, if that argument is parametric over the possible inputs (as asserted  
by a class restriction) then it starts to get a bit tedious:


main = putStrLn . deconsVar elemStr elemStr $ test

If I find myself adding a V3 and a V4 to my datatype in the future then  
that would change to:


main = putStrLn . deconsVar elemStr elemStr elemStr elemStr $ test

I was hoping to find a way that would let the functor argument retain its  
parametricity and therefore not need such repetition.


-Kevin

--
-KQ

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


Re: [Haskell-cafe] QuickCheck Questions

2011-07-24 Thread Kevin Quick
On Sun, 24 Jul 2011 07:30:56 -0700, Mark Spezzano  
mark.spezz...@chariot.net.au wrote:



Hi all,

I would appreciate it if someone can point me in the right direction  
with the following problem.


I'm deliberately implementing a naive Queues packages that uses finite  
lists as the underlying representation. I've already read through  
Hughes' paper and the article in The Fun of Programming, but I'm still  
having some difficulties. Specifically:


1. I have a newtype Queue a = Queue [a] and I want to generate Queues of  
random Integers that are also of random size. How do I do this in  
QuickCheck? I guess that  I need to write a generator and then make my  
Queue a concrete type an instance of Arbitrary? How?


Mark,

One of the great things about QuickCheck is that it is automatically  
compositional.
What I mean by this is that all you need in your instance is how to form a  
Queue [a] given [a], because there are already QuickCheck instances  
for forming lists, and as long as a is pretty standard (Integers is fine)  
then there's likely an Arbitrary instance for that as well.


So (from my head, not actually tested in GHC):

import Control.Applicative
import Test.QuickCheck

instance Arbitrary Queue where
   arbitrary = Queue $ arbitrary

Then you can use this as:

testProperty length is something propQInts

propQInts t = length t == 
where types = (t :: Queue Integers)

The where clause is a fancy way of specifying what the type of t should be  
without having to express the overall type of propQInts.  You could use a  
more conventional type specification as well.




2. If I wanted to specify/constrain the ranges of random Integers  
generated, how would I do this?


Probably something like this:

instance Arbitrary Queue where
arbitrary = do li - listOf $ arbitrary
   lr - liftM $ map rangelimit li
   return $ Queue lr
where rangelimit n = case (n  LOW, n  HIGH) of
(True,_) - LOW
(_,True) - HIGH
_ - n




3. If I wanted to specify/constrain the Queue sizes how would I do this?


Similar to #2.  Perhaps:

   arbitrary = arbitrary = (return . Queue . take CNT . listOf)


--
-KQ

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


Re: [Haskell-cafe] Oracle Sessions in Takusen

2011-06-02 Thread Kevin Quick

Dmitry,

I'm not directly familiar with Takusen or its use with OracleDB, but I  
would hazard a guess that the withSession is doing FFI resource management  
and that resources obtained inside the withSession environment are no  
longer valid outside of the withSession.


If this is the case then I would expect the following to work:

   replicateM 2 (do
withSession (connect x x x) (do
  res - doQuery ...
  liftIO $ print res
)
)

If this really is the case then it seems that withSession shouldn't be  
exporting FFI-based resources.


-KQ

On Wed, 01 Jun 2011 07:44:10 -0700, Dmitry Olshansky  
olshansk...@gmail.com wrote:



Hello,

Could anyone explain strange behavior of Takusen with OracleDB (OraClient
11.x)? Several sequential sessions give Seqmentation Fault error. In  
case

of nested sessions it works well.

{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Database.Oracle.Enumerator
import Control.Monad(replicateM)
import Control.Monad.Trans(liftIO)
main = do
{-
-- This gives an Segmentation Fault for the second session

replicateM 2 (do
res - withSession (connect x x x)  (do
doQuery (sql SELECT dummy FROM dual) (\(d::String)
(_::Maybe String) - result' $ Just d) Nothing
)
print res
)
-}

-- This is works well

withSession (connect x x x)  (do
r1 - doQuery (sql SELECT dummy FROM dual) (\(d::String)
(_::Maybe String) - result' $ Just d) Nothing
liftIO $ print r1
liftIO $ withSession (connect x x x)  (do
r2 - doQuery (sql SELECT dummy FROM dual)
(\(d::String) (_::Maybe String) - result' $ Just d) Nothing
liftIO $ print r2
)
)
Best regards,
Dmitry



--
-KQ

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


[Haskell-cafe] impoosible dependencies

2011-04-20 Thread Kevin Quick

Hmmm...

$ cabal update
$ cabal install hakyll
Resolving dependencies...
cabal: dependencies conflict: ghc-6.12.3 requires unix ==2.4.0.2 however
unix-2.4.0.2 was excluded because ghc-6.12.3 requires unix ==2.4.1.0
$

Any advice (other than upgrading to 7.0.3, which is not an option at the 
moment)?

--
-KQ

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


Re: [Haskell-cafe] impoosible dependencies

2011-04-20 Thread Kevin Quick

On Wed, 20 Apr 2011 15:18:21 -0700, Rogan Creswick cresw...@gmail.com wrote:


On Wed, Apr 20, 2011 at 2:51 PM, Kevin Quick qu...@sparq.org wrote:

$ cabal update
$ cabal install hakyll
Resolving dependencies...
cabal: dependencies conflict: ghc-6.12.3 requires unix ==2.4.0.2 however
unix-2.4.0.2 was excluded because ghc-6.12.3 requires unix ==2.4.1.0
$

Any advice (other than upgrading to 7.0.3, which is not an option at the
moment)?


You can run the build with verbose output (--verbose=3) and get more
details about why the impossible dependencies were required,


No joy: hakyll itself requires unix 2.4, so the following are discarded:  
unix-2.0, 2.2.0.0, 2.3.0.0, 2.3.1.0, 2.3.2.0,

However, that's the only unix discard before the error occurs somewhat later 
on, only now the error is not with unix but with array (which is not discarded 
by anything):

...

selecting text-0.11.0.5 (installed or hackage) and discarding text-0.11.0.0,
0.11.0.1, 0.11.0.2, 0.11.0.3, 0.11.0.4, 0.11.0.6 and 0.11.0.7
selecting deepseq-1.1.0.2 (installed or hackage) and discarding
deepseq-1.1.0.0 and 1.1.0.1
selecting QuickCheck-2.4.0.1 (installed or hackage) and discarding
QuickCheck-2.1, 2.1.0.1, 2.1.0.2, 2.1.0.3, 2.1.1, 2.1.1.1, 2.1.2, 2.2, 2.3,
2.3.0.1, 2.3.0.2 and 2.4
selecting
cabal: dependencies conflict: ghc-6.12.3 requires array ==0.3.0.2 however
array-0.3.0.2 was excluded because ghc-6.12.3 requires array ==0.3.0.1
$

Its starting to look like there's something very wrong with cabal databases.  
My first thought is to remove my local version, but I'm hesitant because I do 
have other haskell work I'm in progress on that isn't broken and I don't want 
to break it.  :-)


or you
can build your application (whatever relies on hakyll) with cabal-dev
-- I've been able to build hakyll that way on my machine with
ghc-6.12.3, so I suspect there is some unexpected dependency in your
local package db that is causing cabal to make a series of undesirable
version selections.

--Rogan


No joy there either.  There were some preliminary package version complaints 
that I tried to resolve, but the end result is:

$ cabal install cabal-dev
Resolving dependencies...
[1 of 1] Compiling Main ( 
/tmp/cabal-dev-0.7.4.113115/cabal-dev-0.7.4.1/Setup.hs, 
/tmp/cabal-dev-0.7.4.113115/cabal-dev-0.7.4.1/dist/setup/Main.o )

/tmp/cabal-dev-0.7.4.113115/cabal-dev-0.7.4.1/Setup.hs:7:47:
Warning: In the use of `buildVerbose'
 (imported from Distribution.Simple.Setup):
 Deprecated: Use buildVerbosity instead
Linking /tmp/cabal-dev-0.7.4.113115/cabal-dev-0.7.4.1/dist/setup/setup ...
cabal: Error: some packages failed to install:
cabal-dev-0.7.4.1 failed during the configure step. The exception was:
ExitFailure 11
$

With --verbose=3 this appears to be post-link running cabal-dev itself:

$ cabal install cabal-dev --verbose=3
...

*** Deleting temp files:
Deleting:
link: linkables are ...
LinkableM (Wed Apr 20 16:14:58 MST 2011) main:Main
   [DotO /tmp/cabal-dev-0.7.4.113193/cabal-dev-0.7.4.1/dist/setup/Main.o]
Linking /tmp/cabal-dev-0.7.4.113193/cabal-dev-0.7.4.1/dist/setup/setup ...
*** Linker:
...[verbose GCC output elided]...
rtend.o /nix/store/l8x3fdy1r6zf441vnqa87lzsvxrjbdz9-glibc-2.11.1/lib/crtn.o
link: done
*** Deleting temp files:
Deleting:
*** Deleting temp dirs:
Deleting: /tmp/ghc13224_0
/tmp/cabal-dev-0.7.4.113193/cabal-dev-0.7.4.1/dist/setup/setup configure
--verbose=3 --ghc --prefix=/home/kquick/.cabal --user --flags=-build-tests
--flags=-no-cabal-dev --extra-include-dirs=/home/kquick/.nix-profile/include
--extra-lib-dirs=/home/kquick/.nix-profile/lib --constraint=Cabal ==1.10.1.0
--constraint=HTTP ==4000.1.1 --constraint=base ==4.2.0.2
--constraint=bytestring ==0.9.1.9 --constraint=directory ==1.0.1.1
--constraint=filepath ==1.1.0.4 --constraint=mtl ==2.0.1.0
--constraint=network ==2.3.0.2 --constraint=pretty ==1.0.1.1
--constraint=process ==1.0.1.3 --constraint=tar ==0.3.1.0 --constraint=zlib
==0.5.3.1
cabal: Error: some packages failed to install:
cabal-dev-0.7.4.1 failed during the configure step. The exception was:
ExitFailure 11
$


--
-KQ

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


Re: [Haskell-cafe] Fun with the ST monad

2011-02-26 Thread Kevin Quick
 $ B.hPut h r
work m
  op a b = (shiftR b 4, if b  32 then b else a+b)


That's not so bad!  The learning curve of Iteratees is non-trivial,
but the results are pretty readable, IMHO.

And here's verification that the output is reasonable:

$ ls -1sh *.example*
4.9M input.example
4.9M output.example1
4.9M output.example2
4.9M output.example3
4.9M output.example4
4.9M output.example5
4.9M output.example6


Hopefully this has been a useful comparison of using Iteratee
techniques in relation to more conventional monads, and the
performance results are good support of the usefulness of Iteratee's.

As always, the greatest benefit was probably for myself in actually
implementing and writing this up, but if you read through this far I
hope you found it readable and useful.

-Kevin Quick


--
-KQ

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


Re: [Haskell-cafe] Fun with the ST monad

2011-02-25 Thread Kevin Quick

On Thu, 24 Feb 2011 13:45:59 -0700, Andrew Coppin andrewcop...@btinternet.com 
wrote:


The input list is being read from disk by lazy I/O. With the original 
implementation, the input file gets read at the same time as the output file is 
written. But runST returns nothing until the *entire* input has been 
compressed. So writing to disk doesn't start until the entire file has been 
slurped up into memory.
Anybody have any hints on how to get around this?



I'd recommend using an enumerator/iterator package to read and process the file 
as a stream of chunks.  The assumption here is that you don't need the entire 
input to provide enough state to begin generating output.

--
-KQ

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


Re: [Haskell-cafe] Cmdargs and common flags

2011-01-24 Thread Kevin Quick

Magnus,

I used the following technique, but it was a couple of iterations of CmdArgs 
ago:


data UIMode = Normal | Batch | Query deriving (Data,Typeable,Show,Eq)

uimode_arg :: forall t. t - UIMode
uimode_arg _ = enum Normal
   [ Batch = flag B  text batch mode (no interaction)  group 
grp
   , Query = flag Q
text query mode (user verification solicited)
group grp
   ]
where grp = Operating Mode


data Globalargs = CMD1 { ... , uimode :: UIMode , ... }
| CMD2 { ... , uimode :: UIMode , ... }


cmd1mode :: Mode Globalargs
cmd1mode = mode $ CMD1 { ... , uimode = uimode_arg cmd1 }
  = text (usage ...)


cmd2mode :: Mode Globalargs
cmd2mode = mode $ CMD1 { ... , uimode = uimode_arg cmd2 }
  = text (usage ...)

modes :: [ Mode Globalargs ]
modes = [ cmd1mode, cmd2mode ]

main  = do cmdArgs progSummary modes
   ...


I've cut and pasted from my usage and perhaps pasted too little, so let me know 
if the above is unuseably brief.  And again, cmdargs has changed somewhat since 
this code was written and I haven't tried a recent compilation.

-KQ

P.S.  This often required {-# OPTIONS_GHC -fno-full-laziness -fno-strictness 
#-} because GHC (6.12? 6.10?) would complain about my uimode_arg type otherwise.


On Thu, 20 Jan 2011 01:48:35 -0700, Magnus Therning mag...@therning.org wrote:


I'm looking for a good way of dealing with common flags in cmdargs.
Currently what I do requires a bit of repetition that I'd really like
to get rid of:

1. Data types

data Modes = Cmd1 { foo :: String, ... } | Cmd2 { foo :: String, ... }

2. Mode specifications

cmd1 = Cmd1 { foo = def = help .., ...}
cmd2 = Cmd2 { foo = def = help .., ...}

I have no idea how to deal with the repetition in the data types, so
all suggestions are welcome.

For the repetition in the mode specifications I attempted to factor
the common bits into a variable:

flagFoo =  = help ..

but that resulted in only the first command getting the proper
specification.  I suppose this comes down to the impurity, but how do
I work around that?  (Especially, are there any good examples of using
the pure part of the API?)

/M




--
-KQ

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


Re: [Haskell-cafe] possible bug in default module lookup scheme / or invalid haskell?

2010-07-19 Thread Kevin Quick

On Sun, 18 Jul 2010 12:02:39 -0700, Carter Schonwald 
carter.schonw...@gmail.com wrote:


nope, I was suggesting rather:
./A.hs has module A which has an import A.B line
./A/ has  B.hs with module A.B  which imports A.B.C
 /C which has module A.B.C in file C.hs

I think this scenario  should work 
-carter


It's an interesting proposal, but unfortunately there's the possibility of an n:1 mapping 
between parent directory and child.  This would make using .. against the 
current working directory potentially non-deterministic, and removing lower elements from 
an absolute path wouldn't necessarily get you back to the directory where A.hs lived 
either.

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


Re: [Haskell-cafe] possible bug in default module lookup scheme / or invalid haskell?

2010-07-18 Thread Kevin Quick

On Sat, 17 Jul 2010 22:45:57 -0700, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:


Carter Schonwald carter.schonw...@gmail.com writes:


Hello All, I'm not sure if this either a bug in how ghc does path/module
lookup or  it simply is invalid haskell:


consider modules A, A.B and A.B.C
where  A imports A.B, and A.B imports A.B.C
with the following file system layout

A.hs
A/B.hs
A/B/C.hs

minimal file examples:
module A where
import A.B
 testA = will it really really work?

module A.B where
import A.B.C
 testB = will it work
-
module A.B.C where
testC = will this work?
--
if i run ghci A.hs everything's fine
but if in directory B i rune ghci B.hs,  i get
A/B.hs:2:8:
Could not find module `A.B.C':
  Use -v to see a list of the files searched for.

---
it seems to me that if the default search path for ghc(i) includes the
current directory (which according to docs it does), this shouldn't be
happening.  (or is there some why this is good Behavior?)


I think ghci is just not smart enough to know that it should change to
the parent directory and run it from there.  As such, it's trying to
find A.B.C from the context of the current directory, and the file is
not in A/A/B/C.hs so it can't find it.

So it's just a limitation of ghci (I think).


I'm afraid I disagree and would view this as expected behavior.

import A.B.C translates internally to something like 
load_file_using_paths(A/B/C.hs).

When you are running this from the top level directory (e.g. top), ghci includes the current path 
top so the lookup is for top/A/B/C.hs, which clearly exists.

When you are in directory B, ghci includes the current path top/A/B so the lookup is 
for top/A/B/A/B/C.hs... which does not exist, thus your error.

Your example would require ghci to try load_file_using_paths(B/C.hs) (and then 
load_file_using_paths(C.hs) to be complete), which discards the directory heirarchy specified by the module 
nomenclature.  This is not adviseable because it introduces ambiguities.  For example, if you also had a C.hs in A and 
another C.hs in A/B, which C.hs should it load when you say import A.B.C?  Or import C? If 
ghc/ghci discarded paths, then the results would be either (1) a different C.hs depending on your current directory, 
(2) the bottom-most C.hs, (3) the C.hs in the current directory, (4) random?.  Worse, any of the above results in a 
trojan-horse style security hole.  Also, what if there was a C.hs in the directory above you (top/..)?  A 1:1 mapping 
between module heirarchy specification and directory paths is the only dependable mechanism.

The better solution is to specifically set the paths you expect to form the roots of the 
(non-default) module heirarchy if you plan to work from within subdirectories of your 
source tree.  If you invoked ghci as $ ghci -i /path/to/top then it would 
work regardless of your current directory.  I believe that this is the proper solution to 
http://hackage.haskell.org/trac/ghc/ticket/3140 as well.

-KQ

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Kevin Quick

On Thu, 08 Jul 2010 09:48:34 -0700, Daniel Fischer daniel.is.fisc...@web.de 
wrote:


On Thursday 08 July 2010 18:24:05, Ben Millwood wrote:

On Thu, Jul 8, 2010 at 3:45 PM, Daniel Fischer daniel.is.fisc...@web.de

wrote:

 Well, I made the suggestion of emitting a warning on instance
 declarations without method definitions. That would be comparatively
 easy to implement (even with an additional check to only emit the
 warning if the class defines any methods) and catch many (if not most)
 cases.

Unfortunately, it would catch some perfectly valid cases, see the list
of instances for flat datatypes here:

http://hackage.haskell.org/packages/archive/deepseq/1.1.0.0/doc/html/src
/Control-DeepSeq.html

This demonstrates that there is at least one (admittedly probably not
much more than one) case where a class with methods would have a
default implementation that was total and valid in some cases.


Good point.
So one should check for more than one class-method [then defining no
methods in the instance declaration is likely to lead to a default-method
loop if there are default methods for all, otherwise GHC will warn
already].
That can of course still give rise to spurious warnings, but is less likely
to.


I would think that only mutually recursive default methods would require 
respecification and that there could be any number of default methods that were 
reasonable as is.  Since it's probably quite difficult for the Haskell compiler 
to analytically detect non-terminating v.s. terminating mutual recursion it may 
be useful to define an explicit comment flag for this case.

For example:

   class Show a where
  shows = showsPrec 5
  showsPrec _ = shows
  {-# REDEFINE_ONE: shows showsPrec #-}

This would fairly simply allow a warning to be generated for an instance which 
did not redefine one of the identified methods; it would capture that 
requirement in the same place the recursive definition was defined, it would 
avoid false warnings, and it would be backward compatible (and it might be 
Haddock-able as well).

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Kevin Quick

On Fri, 09 Jul 2010 16:26:13 -0700, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:


Kevin Quick qu...@sparq.org writes:


I would think that only mutually recursive default methods would
require respecification and that there could be any number of default
methods that were reasonable as is.  Since it's probably quite
difficult for the Haskell compiler to analytically detect
non-terminating v.s. terminating mutual recursion it may be useful to
define an explicit comment flag for this case.

For example:

   class Show a where
  shows = showsPrec 5
  showsPrec _ = shows
  {-# REDEFINE_ONE: shows showsPrec #-}

This would fairly simply allow a warning to be generated for an
instance which did not redefine one of the identified methods; it
would capture that requirement in the same place the recursive
definition was defined, it would avoid false warnings, and it would be
backward compatible (and it might be Haddock-able as well).


This should be generalised IMO, since there might be cases where you
have to redefine either (foo  bar) || baz; of course, that makes the
syntax specification, etc. of the pragma more difficult...


I'm having trouble envisioning a restriction case such as you describe.  Can 
you provide an example?

The comment can't dictate that the resulting redefined method isn't still 
mutually recursive, but the warning for the lack of any override should provide 
enough of a trigger for the developer to read the docs/code and write an 
appropriate method.  If foo, bar, and baz are all interrelated it seems to me 
that an appropriate override of any of them could provide the necessary exit 
from recursion.

That's probably an interesting assertion that one of the category theorists 
around here could prove or disprove.  ;-)

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


Re: [Haskell-cafe] bug in ghci ?

2010-07-09 Thread Kevin Quick

On Fri, 09 Jul 2010 18:57:34 -0700, Edward Kmett ekm...@gmail.com wrote:

I hope the above demonstrate that there are at least some fairly reasonable
(and, given your request, appropriately category theoretic!) examples where
one would want the ability to specify that there is more than one member of
a minimal mutual definition. =)


It does, thanks!  (And thanks as well to Alexander for the description of 
proofs).

This confirms Ivan's proposal a more general form allowing grouping () and 
exclusion (|) would be needed.  The question now is: is that enough and is this a 
useful approach to the problem that should be moved forward as a more formal 
suggestion?

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


Re: [Haskell-cafe] Canonical Graphviz code

2010-07-06 Thread Kevin Quick

On Mon, 05 Jul 2010 19:26:34 -0700, Ivan Miljenovic ivan.miljeno...@gmail.com 
wrote:


Graphviz (http://graphviz.org/) has the option to convert provided Dot
code for visualising a graph into a canonical form.  For example, take
the sample Dot code:

[snip]

I've recently thought up a way that I can duplicate this functionality
(in terms of what it does, not necessarily the actual output) in my
graphviz library (http://hackage.haskell.org/package/graphviz),
however I'm not sure how closely to follow what Graphviz does.


There doesn't seem to be a clear definition of canon output is, and the implication in the 
documentation is that this mode might better have been named pprint (thus my hesitance to refer 
to it as canonical form).  Based on this, I'd suggest that you don't need strict adherence to 
graphviz.

It generally appears that canon output follows the two guidelines of Atomic and 
Minimal:

* Atomic meaning specify all attributes that apply to an element instead of 
relying on inheritance
* Minimal meaning don't specify too much
   - No default attributes
   - Each element (edge or node) on its own, no combining (see also Atomic)
   - Elements only in necessary scope (thus move edges/nodes that only appear 
in a subgraph context into that subgraph)

Based on this I would anticipate your options (1), (2), and (4) below.  The advantages of 
canon form would seem to be that removing, or adding elements to the graph is as 
safe as possible because the impact to the graph is only as explicitly stated.  For 
example, removal of a node requires only removing that node statement and any edge statement 
specifying that node---no concern about removing it from multi-node or multi-edge elements---and 
that the locality of the removal is fairly evident (i.e. which subgraph the element is part of).  
Likewise adding an element means that the element will appear pretty much as-specified without 
inheriting attributes.

Interestingly you could envision providing a dual of this mode named compact.  The 
compact mode would attempt to specify the graph as compactly as possible, using inheritance for 
attributes and multi-element statements (interestingly it's an attribute-oriented approach to the 
graph as opposed to the element-oriented approach of canon form).

-KQ


 What
would the community prefer out of the following (including a mixture,
such as options 2 and 3):

1) Match Graphviz's output as much as possible (note that the ordering
of the attributes won't happen this way, since I'll be sorting them
alphabetically rather than working out Graphviz's arcane rules).

1a) As with 1), but don't worry about defining extra attributes such
as node [label=\N].

2) Explicitly define nodes that are only mentioned in edges (e.g.
actually define a `c' node, even if it doesn't have any extra
attributes).  Note that this already happens if such an edge is
specified inside a different cluster than the already known node is
in; in that case then the stand-alone node is defined in the cluster
its edge is defined in, and the actual edge is moved into the outer
context that combines the two clusters.

2a) As with 2), but define all edges in the overall graph rather than
grouping them internally inside clusters, etc.

3) Group common attributes together as much as possible (e.g. inside
the bar cluster, define another subgroup which has a top-level
attribute node [color=blue] and define the `a' and `b' nodes in
there).  Not sure how well this will work with edges though, and is
probably not possible in conjunction with option 2a).  This is a bit
tricky and subtle: if `a' and `b' are already in such a subgraph, but
an edge specifying one of them is defined _before_ the subgraph is
defined, then that node will have an explicit color attribute defined
of  (i.e. empty string), though I would classify this as a bug.

4) As an alternate to option 3), remove all explicit top-level node
and edge attributes and move them all to the affected node and edge
definitions themselves; this may require option 2).

I'm also willing to hear and consider other possible variants;
however, I'm only going to code (at most) one.



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


[Haskell-cafe] GHC AT inference bug?

2010-07-04 Thread Kevin Quick

I started with the following:


{-# LANGUAGE TypeFamilies  #-}

class DoC a where
type A2 a
op :: a - A2 a

data Con x = InCon (x (Con x))
type FCon x = x (Con x)

foldDoC :: Functor f = (f a - a) - Con f - a
foldDoC f (InCon t) = f (fmap (foldDoC f) t)

doCon :: (DoC (FCon x)) = Con x - A2 (FCon x)
doCon (InCon x) = op x

fCon :: (Functor x, DoC (FCon x)) = Con x - A2 (FCon x)
fCon = foldDoC op


I then changed the rank of op, but forgot to update the foldDoC 
accordingly---see below.  Attempting to compile this causes GHC to run forever 
using 100% cpu.  The corrected definition of foldDoC works fine.  Should the 
GHC (6.12.1) behavior in the face of my foolishness be reported as a bug or is 
this a legitimate infinite recursion of type deduction?


{-# LANGUAGE TypeFamilies  #-}

class DoC a where
type A2 a
type A3 a
op :: a - A2 a - A3 a

data Con x = InCon (x (Con x))
type FCon x = x (Con x)

-- should have been changed to this, which works
-- foldDoC :: Functor f = (f a - a) - A2 (FCon f) - Con f - a
-- foldDoC f i (InCon t) = f (fmap (foldDoC f i) t)

-- this original version causes GHC to hang
foldDoC :: Functor f = (f a - a) - Con f - a
foldDoC f (InCon t) = f (fmap (foldDoC f) t)

doCon :: (DoC (FCon x)) = Con x - A2 (FCon x) - A3 (FCon x)
doCon (InCon x) = op x

-- note that if this is commented out then there's no hang: presumably because 
GHC doesn't have to perform type deduction for foldDoC.
fCon :: (Functor x, DoC (FCon x)) = Con x - A2 (FCon x) - A3 (FCon x)
fCon = foldDoC op


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


Re: [Haskell-cafe] checking types with type families

2010-07-03 Thread Kevin Quick

On Wed, 23 Jun 2010 00:14:03 -0700, Simon Peyton-Jones simo...@microsoft.com 
wrote:


I'm interested in situations where you think fundeps work and type families 
don't.  Reason: no one knows how to make fundeps work cleanly with local type 
constraints (such as GADTs).


Simon,

I have run into a case where fundeps+MPTC seems to allow a more generalized 
instance declaration than type families.

The fundep+MPTC case:

{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}

class C a b c | a - b, a - c where
op :: a - b - c

instance C Bool a a where op _ = id

main = putStrLn $ op True done


In this case, I've (arbitrarily) chosen the Bool instance to be a no-op and 
pass through the types.  Because the dependent types are part of the 
declaration header I can use type variables for them.  I don't seem to have the 
same ability with type families:


{-# LANGUAGE RankNTypes, TypeFamilies, UndecidableInstances #-}

class C a where
type A2 a
type A3 a
op :: a - A2 a - A3 a

instance {-forall a.-} C Bool where
type A2 Bool = {-forall a.-} a
type A3 Bool = A2 Bool
op _ = id

main = putStrLn $ op True done


I cannot get this to compile as above or with either of the existential 
quantifications of a.  The first example may be the more erroneous one because 
the use of type variables would seem to violate the functional dependency 
assertions, but GHC accepts it nonetheless.

Regards,

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


Re: [Haskell-cafe] checking types with type families

2010-07-03 Thread Kevin Quick

On Sat, 03 Jul 2010 12:48:56 -0700, Dan Doel dan.d...@gmail.com wrote:


Then the instance declares infinitely many instances C Bool a a. This is a
violation of the fundep. Based on your error message, it looks like it ends up
treating the instance as the first concrete 'a' it comes across, but who
knows?


Hmmm.. it doesn't look like a first concrete lockdown.  The following works 
fine:

opres1 :: Int - Int
opres1 = op True

opres2 :: String - String
opres2 = op True

main = do putStrLn $ op True start
  putStrLn $ show $ opres1 5
  putStrLn $ opres2 $ opres2 $ show $ opres1 6
  putStrLn $ opres2 done

As a side note, although I agree it abuses the fundeps intent, it was handy for the 
specific purpose I was implementing to have a no-op/passthrough instance of 
op.  In general I like the typedef approach better, but it looks like I must sacrifice 
the no-op to make that switch.

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


Re: [Haskell-cafe] checking types with type families

2010-07-03 Thread Kevin Quick

On Sat, 03 Jul 2010 13:28:44 -0700, Dan Doel dan.d...@gmail.com wrote:


As a side note, although I agree it abuses the fundeps intent, it was handy
for the specific purpose I was implementing to have a no-op/passthrough
instance of op.  In general I like the typedef approach better, but it


  ^^^ should have been type family, not 
typedef


looks like I must sacrifice the no-op to make that switch.

It's potentially not just a violation of intent, but of soundness.


I agree when examining this from the perspective of the compiler.  It's an 
interesting little wormhole in the safety net usually provided by Haskell (or 
more properly GHC in this case) to stop people like me from doing foolish 
things.

From the domain of the original problem, having a no-op instance is still 
desireable, and I achieved this by making the noop instance type polymorphic 
and use the target concrete type to guide the resolution of the interior family 
types.

class C a where
type A2 a
type A3 a
op :: a - A2 a - A3 a

data NoOp x = NoOp

instance C  (NoOp b) where
type A2 (NoOp x) = x
type A3 (NoOp x) = x
op _ = id

This is straightforward and less ambiguous and should therefore be safer as 
well.

Thanks and regards,

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


Re: [Haskell-cafe] FGL instance constraint

2010-05-01 Thread Kevin Quick

On Fri, 30 Apr 2010 23:30:21 -0700, Jason Dagit da...@codersbase.com wrote:


On Fri, Apr 30, 2010 at 11:08 PM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:


You're putting the constraint in the wrong places: put the (Cls a) = 
in the actual functions where you need it.


I need to use Cls methods in the Graph methods: see below.  More specifically, 
the Node decorators (type 'a') need to be of class Cls as well, but I can't 
figure out how to do this.


That's solid advice in general, but it's still not going to work here if any
of the functions needed for the instance of Graph require the type class
constraint.


Yes.


A solution to the monad problem I just mentioned is outlined here as
'restricted monads':
http://okmij.org/ftp/Haskell/types.html#restricted-datatypes


I'll read this, but my brain has low Oleg-ability, so it may take me some time 
to begin to understand.  Thanks for the reference though.


Perhaps you can try either associated types or the restricted monad
approach?  Unfortunately, I think both of them require you to change FGL
instead of just your code, although maybe not with the restricted monad
stuff.  I don't recall how invasive that approach is.


Yes, I was hoping to use FGL directly (or it's replacement as I've scanned some 
of the recent Cafe discussions and seen that Ivan in particular is undertaking 
this).

The key here is that the decorators for the Node are of type a, and I need that 
type a to be of (Cls a) because I use the methods in Cls a to implement the 
Graph functionality.  I've attached a simple example below that attempts to 
demonstrate this need (and my numerous failures).


{-# LANGUAGE RankNTypes #-}

module Main where

import Data.Graph.Inductive.Graph

class Cls a where
int :: a - Int   -- just to have something

data (Cls a) = B a = B [a]

-- The intent is that B is a collection of objects fulfilling the Cls
-- class interface.  It is also the intent to represent B as a Graph
-- object.  However, in order to create the Graph, the Cls operations
-- are needed.

-- To make a Graph representation of B, I need to convert my
-- univariant B datatype into a bivariant type.  This is odd because:
-- (1) I ignore/drop b because it's not needed, and (2) I have a
-- constraint on a imposed by B.

data GrB a b = GrB (B a)
-- data (Cls a) = GrB a b = GrB (B a)  -- no difference in compilation errors

instance Graph GrB where
-- instance (Cls a) = Graph GrB where -- error: ambiguous 
constraint, must mention type a
-- instance (Cls a) = forall a. Graph GrB where   -- error: malformed instance 
header
-- instance (Cls a) Graph GrB | GrB - a where -- error: parse error on |
-- empty :: (Cls a) = GrB a b -- error: Misplaced type 
signature (can't redefine the type)
empty = GrB (B []) -- error: could not deduce 
(Cls a) from context () for B

isEmpty (GrB (B l)) = null l

match _ g = (Nothing, g)   -- Actually need Cls methods on 'a' type to 
generate the non-trivial case

mkGraph n e = GrB (B [])  -- TBD
labNodes g = []  -- TBD

main = putStrLn ok


Perhaps I need some alternative method here, or perhaps as has been suggested 
I'm trying to use something that's older/Haskell-98 specific that can't support 
this.

Thanks again for the advice and help.  Sorry I was rude in not answering for so 
long: shortly after my original post I realized sleep was needed.

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


Re: [Haskell-cafe] FGL instance constraint

2010-05-01 Thread Kevin Quick

On Sat, 01 May 2010 01:01:47 -0700, Sebastian Fischer 
s...@informatik.uni-kiel.de wrote:



On May 1, 2010, at 8:08 AM, Ivan Lazar Miljenovic wrote:


* I can't redefine the Graph methods to introduce the (Cls a)
constraint [reasonable]


Not sure if you can.


I think Kevin means that he cannot change the signature of the methods
in the Graph class because those are defined in the FGL package.


Mostly.

If I was able to redefine the method to add the class constraint in *my* code, that would 
be what I wanted but clearly wrong from the general type perspective: once 
defined it should not be possible to redefine.  I was more trying to indicate that I'd 
been flailing around and trying everything, even things that make me look stupid.  :-)




You're putting the constraint in the wrong places: put the (Cls a)
= 
in the actual functions where you need it.


Those seem to be the methods of the Graph class, where he can't place
the constraints. Kevin may have a version of  makeGraph  with
additional constraints but cannot use it to to define a  Graph
instance.


Exactly.  I posted a separate response with more details, but this is my problem.  
Actually, I'm even struggling defining the empty method of Graph.

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


Re: [Haskell-cafe] FGL instance constraint

2010-05-01 Thread Kevin Quick

On Sat, 01 May 2010 15:42:09 -0700, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:


instance Graph GrB where
-- instance (Cls a) = Graph GrB where -- error: ambiguous constraint, must 
mention type a
-- instance (Cls a) = forall a. Graph GrB where -- error: malformed instance 
header
-- instance (Cls a) Graph GrB | GrB - a where -- error: parse error on |
-- empty :: (Cls a) = GrB a b -- error: Misplaced type signature (can't 
redefine the type)
empty = GrB (B []) -- error: could not deduce (Cls a) from context () for B

isEmpty (GrB (B l)) = null l

match _ g = (Nothing, g) -- Actually need Cls methods on 'a' type to 
generate the non-trivial case

mkGraph n e = GrB (B [])  -- TBD
labNodes g = []  -- TBD


Unless you have something else you haven't put here, I don't see any
reason why you have to have the constraint on the datatype rather than
on the actual functions (outside of the class instance) you need them
for later on.


I was trying to put them on the inside.  Essentially I was trying to use the 'a' portion 
of the LNode as a type that would provide methods from which I could reconstruct the 
shape of the Graph.  Or to put it another way, I had a collection of data and I wanted to 
be able to say this container of data is also useable as a graph by using 
class operations on the data.

I've discovered an alternative, workable approach to the issue.  After coming to terms that the instance of Graph could 
impose no restrictions on the node (or edge) labels and that they were (as you previously mentioned) simply 
decorators for the node, I determined that I could achieve my goal by writing a converter from Cls 
- a Graph instance for a and I simply used Data.Graph.Inductive.Tree as the a Graph instance 
portion.

import Data.Graph.Inductive.Tree

clsToGraph :: (Cls a) = B a - Gr a ()
clsToGraph b = mkGraph (nodes b) (edges b)
  where nodes x = ...
edges x = ...

The downside of this, to my procedurally-trained brain is that (1) I've now 
duplicated each 'a' in two different datastructures, and (2) I've had to 
pay--albeit lazily--for the conversion from B to the tree container represented 
by Gr.  The nascent functionaly-trained portion of my brain would like to think 
that GHC (or other) is smart enough to not create duplicate copies... I'm not 
sure that's true though.  I think I was probably fooling myself about (2) 
though: it was always there, just more explicitly now.

It's one of the joys of Haskell: it saves your from your own stupid ideas.  :-)

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


[Haskell-cafe] FGL instance constraint

2010-04-30 Thread Kevin Quick


I need help understanding how to express the following:



 data (Cls a) = B a = B [a]



 data GrB a b = GrB (B a)



 instance Graph GrB where ...


In the methods for the instance specification, I need to perform Cls a 
operations on a.

 * As shown, the compiler complains that it cannot deduce (Cls a) from the 
context () on those methods.
 * I can't redefine the Graph methods to introduce the (Cls a) constraint 
[reasonable]
 * If I try to express the constraint as part of the Graph instance: instance (Cls a) 
= Graph GrB where ... then it says it's an ambiguous constraint because 'a' isn't 
mentioned.
 * I've tried specifying a functional constraint: instance (Cls a) = Graph GrB | GrB 
- a where ... but that's not valid for an instance declaration.
 * I can't include a in the GrB instance: instance (Cls a) = Graph (GrB a b) where 
... because that's a kind conflict.

Suggestions/solutions are appreciated.

Thanks!

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