[Haskell-cafe] KiCS (Curry to Haskell interpreter) problem

2009-12-02 Thread Bernd Brassel
 I am playing around with KiCS and I have a strange problem, when I
 evaluate a goal the variable bindings are not displayed, I see only
 the value of the expression.

The idea is, that you decide yourself which bindings you want to see.
For example, you write (let x free in (not x,x)) to get

(True,False)
More?

(False,True)
More?

No more solutions

 I would have contacted the author but his email in not in the haskell
 cabal file.

Thanks for the hint. I have added my mail now and will do another update in a 
few weeks. Meanwhile, anyone interested in the system can contact me directly 
under  bbr at informatik.uni-kiel.de

Thanks for your interest in kics!
Bernd___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Gregg Reynolds
On Tue, Dec 1, 2009 at 7:01 PM, Michael P Mossey m...@alumni.caltech.edu 
wrote:
 Perhaps someone could either (1) help me do what I'm trying to do, or (2)
 show me a better way.

 In this one example, in a OO way of thinking, I have data called
 AssignedNumbers that assigns integers to unique strings and keeps track of
 the used integers and next available integer (the choice of available
 integer could follow a number of conventions so I wanted to hide that in an
 ADT.) So it has an associated function:


What do the numbers and strings mean?  Can you use an algebraic type
instead of strings?  Do particular numbers have meaning or are they
just serial numbers?  Can you compute some sort of checksum for the
strings rather than rely on an external list of numbers?  If you must
have a list of numbers, can you embed it in a specialized string type,
so that numbers get assigned as a side-effect of string construction?
In other words, would it help to think more in terms of specific types
rather than generic numbers and strings?

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Gregg Reynolds
On Tue, Dec 1, 2009 at 7:55 PM, Michael Mossey m...@alumni.caltech.edu
wrote:
 Thanks for the reply. Was there something specific you were referring to,
or

Maybe http://plucky.cs.yale.edu/cs431/reading.htm Chapter 9 An Algebra of
Music.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Stephen Tetley
Hi Mike

There used to be some slides available commenting on Haskore's CSound
interface. But they seem to have vanished (I have a copy rendered to
pdf when they were available). Like all slide presentations there's a
lot of reading between the lines to get a good picture after the fact:


http://www.nepls.org/Events/16/abstracts.html#hudak
http://plucky.cs.yale.edu/cs431/HasSoundNEPLS-10-05.ppt  -- vanished

Maybe you're doomed to frustration though trying to implement your
system in Haskell. For the argument I'm about to make, I'd say a
working programming language has two things - syntax, semantics and
libraries and a repertory of prior art. Stateful programming clearly
has some syntax burden in Haskell, stateful monadic programming has
some benefit of 'stratification' - you have precise control of 'what
state is where'. It's a matter of taste whether you like Python's
flexibility or Haskell's, erm, 'locality' (precision?).

As for the second half of what you get from a programming language,
your system description frames what you want to do with an emphasis on
dynamic aspects. This seems a good way off from the prior art in
Haskell. For instance there are Haskell synthesizers - George
Giorgidze's yampa-synth and Jerzy Karczmarczuk's Clarion (actually in
Clean, but near enough). Here you build signal processing modules -
unit generators, of course - Yampasynth uses arrows to do this Clarion
uses infinite streams. With both you would build a synthesizer
statically from unit generators and somehow run it to produce
sounds[1].

There is also the prior art of embedded hardware description
languages, Lava, Hydra, Wired, Gordon Pace's HeDLa, soon Kansas Lava.
One could view constructing synthesizers from unit generators as
usefully analogous to constructing circuits - and certainly if you are
'compiling' to another system to do do the real work (in your case
CSound) the papers on Wired, HeDLa, and Kansas Lava have useful
insights on 'offshoring' compilation. But again these systems have
strong bearing in the 'static description' of a circuit rather than
its dynamical operation.

If neither of those 'genres' is close to what you really want to do
then the Haskell prior art is running a bit thin. You could look at
dataflow - the dynamic PD / Max systems are often describe as a
dataflow systems. There are some outposts in Haskell of dataflow
programming - Gordon Pace has an embedding of Lustre available from
his homepage and there has been work on dataflow programming via
comonads. There is also reactive programming, but musical examples are
thin on the ground
(nonexistent?) so it might be a long haul to come up with something.

Best wishes

Stephen





[1] This seems a bit of a paraphrase of Yampasynth - which I think
allows you to
define a synthesizer statically in code, but then play it interactively.






2009/12/2 Michael Mossey m...@alumni.caltech.edu:
 Thanks for the reply. Was there something specific you were referring to, or
 just the idea that he wrote Haskore? Haskore is not very closely related to
 what I'm trying to do.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Building network package on Windows

2009-12-02 Thread Duncan Coutts
On Sat, 2009-06-06 at 21:43 -0700, Iavor Diatchki wrote:
 Hi,
 I have been trying to build the package network from hackage
 (version 2.2.1.3) on Windows Vista, and I could really use some help.

 Unfortunately, if I try to use my package to build an
 executable application I get a linker error, reporting a missing
 symbol during linking:
 C:\Users\diatchki\AppData\Roaming\cabal\network-2.2.1.3\ghc-6.10.3/libHSnetwork-2.2.1.3.a(Socket.o):fake:(.text+0xb014):
 undefined reference to `getnameinfo'
 collect2: ld returned 1 exit status

I saw some other people run into this today.

 Now, getnameinfo is present in the header files, and it is also
 defined in the library ws2_32.a which is being passed to GHC so I am
 not sure what is going on.  Any ideas?

 Searching the web suggests that the problem may be somehow related to
 the standard calling conventions but I don't really understand.

Right. The getnameinfo in ws2_32.a uses the stdcall calling convention.
The actual linker symbol for it is _getnamei...@28. If it used the
ccall convention then it's linker symbol name would be _getnameinfo. 

The FFI decl for getnameinfo uses ccall. So that's why we get the error.

The current version uses a C wrapper for this function (for unrelated
reasons) and this has the side effect that the C compiler picks up the
correct calling convention from the C header files.

We would be able to catch errors like this if we had a tool that would
check the Haskell FFI decls match the C headers. Of course c2hs already
does this, but only for generating correct FFI decls in the first place.
It cannot be used in a mode where it checks existing code. That might be
a useful extension though since very few projects seem to use c2hs to
generate correct imports in the first place. It also does not currently
check stdcall vs ccall calling convention but it could fairly easily be
extended to do so (since it parses those attributes).

-- 
Duncan Coutts, Haskell Consultant
Well-Typed LLP, http://www.well-typed.com/

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


[Haskell-cafe] Ord k = Data.Set.Set k - (k-v) - Data.Map.Map k v

2009-12-02 Thread Matthias Görgens
I feel that Data.Set and Data.Map should be working together more
closely.  For example you can already get the keyset of a Map, but the
`other way' is not built-in.  I mean a function with a signature like

Ord k = Data.Set.Set k - (k-v) - Data.Map.Map k v

You can implement it in O(n):

 assoc :: (a-b) - [a] - [(a,b)]
 assoc f = map (\x - (x, f x))

 mapToMap :: Ord k = (k - v) - Data.Set.Set k - Data.Map.Map k v
 mapToMap f = Data.Map.fromAscList . assoc f . Data.Set.toAscList

The name assoc alludes to the assoc-lists of Lisp.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] computing lists of pairs

2009-12-02 Thread Christian Maeder
Wizards,

I've the following small piece of code

\begin{code}
pairs :: [a] - [b] - [[(a, b)]]
pairs l1 = map (zip l1) . takeKFromN l1

takeKFromN :: [b] - [a] - [[a]]
takeKFromN s l = case s of
  [] - [[]]
  _ : r - [ a : b | a - l, b - takeKFromN r l]
\end{code}

I have a predicate:
  p :: (a, b) - Bool

and I want to keep only those results of pairs which fulfill
all p.

I do so currently by filter (all p) (pairs l1 l2), but I want to
generate the beginning of this pair lists more efficiently, because the
result list of pairs may become very large, soon:

  length (pairs l1 l2) == length l2 ^ length l1

Any ideas (or other hints) to improve the code?

pairs computes all different mappings from all elements of l1 to some
elements of l2. takeKFromN computes all possible sequences of length
l1 with elements from l2.

I somehow want to integrate the predicate into the generation.

Cheers Christian

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


RE: [Haskell-cafe] Type synonym family inside type class

2009-12-02 Thread Simon Peyton-Jones
I agree this is wrong. I've created a Trac bug report 
http://hackage.haskell.org/trac/ghc/ticket/3714

Thanks for pointing it out

Simon

| -Original Message-
| From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-
| boun...@haskell.org] On Behalf Of Martijn van Steenbergen
| Sent: 27 November 2009 10:35
| To: Haskell Cafe
| Subject: [Haskell-cafe] Type synonym family inside type class
| 
| Hello,
| 
| I have a type family and a type class:
| 
|  type family ErrorAlg (f :: (* - *) - * - *) e ix :: *
| 
|  class MkErrorAlg f where
|mkErrorAlg :: ErrorAlg f e a - f (K0 a) ix - Either e a
| 
| Instances for these two really go hand in hand, so I thought I would
| move the type family into the type class. However, this causes GHC to
| complain about the type variables that are bound on the LHS of the type
| synonym:
| 
|  Not in scope: type variable `e'
|  Not in scope: type variable `ix'
| 
| In function types, using new type variables (i.e. type variables not
| bound by the type class header) implicitly means universal
| quantification over these variables. Why is this disallowed in type
| families inside type classes?
| 
| Thanks,
| 
| Martijn.
| ___
| 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


[Haskell-cafe] Re: inversion lists

2009-12-02 Thread Ted Zlatanov
On Wed, 2 Dec 2009 01:12:23 +0100 Daniel Fischer daniel.is.fisc...@web.de 
wrote: 

DF No, quite the opposite. foldr is wonderful for lazy list processing.
DF I just need to make my function a wee bit lazier:
...
DF No, foldl cannot produce anything before the whole list has been traversed, 
so it can't 
DF deal with infinite lists at all.

Got it.  I simply had reversed the two functions mentally and thought
foldl was the lazy one.  I'll follow up on the rest separately.

Ted

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


Re: [Haskell-cafe] computing lists of pairs

2009-12-02 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 14:49:21 schrieb Christian Maeder:
 Wizards,

 I've the following small piece of code

 \begin{code}
 pairs :: [a] - [b] - [[(a, b)]]
 pairs l1 = map (zip l1) . takeKFromN l1

 takeKFromN :: [b] - [a] - [[a]]
 takeKFromN s l = case s of
   [] - [[]]
   _ : r - [ a : b | a - l, b - takeKFromN r l]
 \end{code}

 I have a predicate:
   p :: (a, b) - Bool

 and I want to keep only those results of pairs which fulfill
 all p.

takeKFromNWithP :: (a - b - Bool) - [a] - [b] - [[b]]
takeKFromNWithP p s l
= case s of
(h:t) - [x:ys | x - filter (p h) l, ys - takeKFromNWithP p t l]
[] - [[]]

filteredPairs :: (a - b - Bool) - [a] - [b] - [[(a,b)]]
filteredPairs p l1 = map (zip l1) . takeKFromNWithP l1

or, in one go:

funkyName :: (a - b - Bool) - [a] - [b] - [[(a,b)]]
funkyName p s l
= case s of
(h:t) - [(h,a):ys | a - filter (p h) l, ys - funkyName p t l]
[] - [[]]

 I do so currently by filter (all p) (pairs l1 l2), but I want to
 generate the beginning of this pair lists more efficiently, because the
 result list of pairs may become very large, soon:

   length (pairs l1 l2) == length l2 ^ length l1

 Any ideas (or other hints) to improve the code?

 pairs computes all different mappings from all elements of l1 to some
 elements of l2. takeKFromN computes all possible sequences of length
 l1 with elements from l2.

 I somehow want to integrate the predicate into the generation.

 Cheers Christian



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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Michael Mossey



Stephen Tetley wrote:

Hi Mike

There used to be some slides available commenting on Haskore's CSound
interface. But they seem to have vanished (I have a copy rendered to
pdf when they were available). Like all slide presentations there's a
lot of reading between the lines to get a good picture after the fact:


http://www.nepls.org/Events/16/abstracts.html#hudak
http://plucky.cs.yale.edu/cs431/HasSoundNEPLS-10-05.ppt  -- vanished



This looks like a great resource. Maybe Dr. Hudak can get me a copy. He 
clearly has the experience to implement a CSound compiler as gracefully 
as anyone could.




Maybe you're doomed to frustration though trying to implement your
system in Haskell. For the argument I'm about to make, I'd say a
working programming language has two things - syntax, semantics and
libraries and a repertory of prior art. Stateful programming clearly
has some syntax burden in Haskell, stateful monadic programming has
some benefit of 'stratification' - you have precise control of 'what
state is where'. It's a matter of taste whether you like Python's
flexibility or Haskell's, erm, 'locality' (precision?).

As for the second half of what you get from a programming language,
your system description frames what you want to do with an emphasis on
dynamic aspects. This seems a good way off from the prior art in
Haskell. For instance there are Haskell synthesizers - George
Giorgidze's yampa-synth and Jerzy Karczmarczuk's Clarion (actually in
Clean, but near enough). Here you build signal processing modules -
unit generators, of course - Yampasynth uses arrows to do this Clarion
uses infinite streams. With both you would build a synthesizer
statically from unit generators and somehow run it to produce
sounds[1].

There is also the prior art of embedded hardware description
languages, Lava, Hydra, Wired, Gordon Pace's HeDLa, soon Kansas Lava.
One could view constructing synthesizers from unit generators as
usefully analogous to constructing circuits - and certainly if you are
'compiling' to another system to do do the real work (in your case
CSound) the papers on Wired, HeDLa, and Kansas Lava have useful
insights on 'offshoring' compilation. But again these systems have
strong bearing in the 'static description' of a circuit rather than
its dynamical operation.



Thanks for this detailed review. I will investigate these things.

My system sits halfway between a low-level signal processor language like 
CSound and a high-level music description language like Hudak's Haskore. My 
work as a composer will be done at the highest level possible, which means 
thinking in terms of notes---things that go boo at a certain time, 
place, frequency, amplitude, timbre, etc. But I want to express things 
beyond, say, MIDI, like indicating that a group of notes should be played 
legato---which doesn't mean play them individually with no separation of 
notes but actually means modify the csound instrument's behavior at the 
time of note connections. So in one small breath I can say, Make this 
legato and at the low level the elves are scurrying around like mad, 
rearranging code, changing out instruments, merging notes, etc.


I also have a bad case of Not Invented Here Syndrome---seriously, I want 
to use this system to do experimental composition, by which I mean any 
crazy idea I dream up can be implemented by adding to or modifying my 
system, which gives me a preference to write it myself.



If neither of those 'genres' is close to what you really want to do
then the Haskell prior art is running a bit thin. You could look at
dataflow - the dynamic PD / Max systems are often describe as a
dataflow systems. There are some outposts in Haskell of dataflow
programming - Gordon Pace has an embedding of Lustre available from
his homepage and there has been work on dataflow programming via
comonads. There is also reactive programming, but musical examples are
thin on the ground
(nonexistent?) so it might be a long haul to come up with something.



But this all sounds great to study.

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Michael Mossey

Hi Gregg,

Yes, I've read his book School of Expression and I'll have to check up on 
this draft.


His ideas are very useful at the level of composing music, where an 
algebraic representation is natural and flies free and high. It's when that 
representation grinds against an old quaint system like CSound that things 
get ugly. However, I have a new idea. Stay tuned.


-Mike

Gregg Reynolds wrote:
On Tue, Dec 1, 2009 at 7:55 PM, Michael Mossey m...@alumni.caltech.edu 
mailto:m...@alumni.caltech.edu wrote:
  Thanks for the reply. Was there something specific you were referring 
to, or


Maybe http://plucky.cs.yale.edu/cs431/reading.htm Chapter 9 An Algebra 
of Music.



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


Re: [Haskell-cafe] computing lists of pairs

2009-12-02 Thread Daniel Fischer


Or:

fpairs p s l = sequence [[(a,b) | b - filter (p a) l] | a - s]



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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Michael Mossey



Michael P Mossey wrote:
Perhaps someone could either (1) help me do what I'm trying to do, or 
(2) show me a better way.


I have a problem that is very state-ful and I keep thinking of it as OO, 
which is driving me crazy. Haskell is several times harder to use than 
Python in this instance, probably because I'm doing it wrong.




Stop the presses! I had an idea to make this more functional in style. Do 
it through multiple passes.


The idea is that we've got a list of musical events as input (Node is a 
term some algorithmic composers use, so I will use type Node.)


In fact we could have other types of input data too, so I might need the 
algebraic type


data InputType = Node ...
   | CSoundSource ...

etc.

Then we make a pass through the nodes using map concat to produce a bunch 
of Output data.


data Output = OIStatement ...
| OInstrName InstrName  -- represents an instrument name
-- (ultimately we need a number, but
--  won't know that # during first
--  pass)
| OInstrNum Int -- when we compute an instrument
-- number, this will replace the above
| OMixer MixerName
 ...

we have a function processInput:

processInput :: InputType - [Output]

This expresses the idea that a single input may result in the generation of 
several pieces of output data.


The first pass is just a concat map

firstPass :: [InputType] - [Output]
firstPass = concatMap processInput

In translating an InputType datum, we look at it in isolation---here it 
sits in front of us in the stream, and we haven't maintained a lot of 
state---and we translate it to some intermediate Output form, making all 
specific calculations or substitutions possible at that given time and context.


Then further passes are needed, many of which are folds. For example, to 
assign the instrument number I have some kind of NumberDatabase, but now my 
dealings with it are limited to a single fold.

assignNumbers :: [Output] - NumberDatabase
assignNumbers outputList = foldl g newNumberDatabase outputList
  where g outputDatum numberDb =
   case outputDatum of
  OInstrName n - ... ah! unassigned name! update db
  _- numberDb  -- just return unchanged


All the rest of the processing can be done via filters, folds, and maps.

Does this seem more functional in style?

Thanks,
Mike



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


[Haskell-cafe] Re: computing lists of pairs

2009-12-02 Thread Christian Maeder
Thanks a lot, works as expected and is super short!

Cheers Christian

Daniel Fischer schrieb:
 
 Or:
 
 fpairs p s l = sequence [[(a,b) | b - filter (p a) l] | a - s]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: computing lists of pairs

2009-12-02 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 17:10:02 schrieb Christian Maeder:
 Thanks a lot, works as expected and is super short!

You're welcome.

However, according to a couple of tests, the funkyName version is somewhat 
faster and 
allocates less.

 Cheers Christian

 Daniel Fischer schrieb:
  Or:
 
  fpairs p s l = sequence [[(a,b) | b - filter (p a) l] | a - s]

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


Re: [Haskell-cafe] seems like I'm on the wrong track

2009-12-02 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 16:55:01 schrieb Michael Mossey:
 Does this seem more functional in style?

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


[Haskell-cafe] Re: computing lists of pairs

2009-12-02 Thread Christian Maeder
Daniel Fischer schrieb:
 However, according to a couple of tests, the funkyName version is somewhat 
 faster and 
 allocates less.

My timing tests showed that your fpairs version is fastest.
(first argument True selects filteredPairs, False funkyName)

My initial version myf is almost unusable.

C.

(code attached)

mae...@leibniz:~/haskell/examples ghc --make -O2 FilteredPairs.hs
[1 of 1] Compiling Main ( FilteredPairs.hs, FilteredPairs.o )
Linking FilteredPairs ...
mae...@leibniz:~/haskell/examples time ./FilteredPairs True EQ 5000
5000

real0m0.567s
user0m0.536s
sys 0m0.020s
mae...@leibniz:~/haskell/examples time ./FilteredPairs False EQ 5000
5000

real0m0.819s
user0m0.796s
sys 0m0.012s
import Data.Char
import System.Environment

filteredPairs :: (a - b - Bool) - [a] - [b] - [[(a, b)]]
filteredPairs p s l = sequence [[(a, b) | b - filter (p a) l] | a - s]

pairs :: [a] - [b] - [[(a, b)]]
pairs l1 = map (zip l1) . takeKFromN l1

takeKFromN :: [b] - [a] - [[a]]
takeKFromN s l = case s of
  [] - [[]]
  _ : r - [ a : b | a - l, b - takeKFromN r l]

myf :: (a - b - Bool) - [a] - [b] - [[(a, b)]]
myf p l = filter (all (uncurry p)) . pairs l

ordA = ord 'a'

prd :: Ordering - Int - Char - Bool
prd o i c = case o of
  LT - ord c - ordA  i
  _ - compare (ord c - ordA + 1) i == o

funkyName :: (a - b - Bool) - [a] - [b] - [[(a,b)]]
funkyName p s l
= case s of
(h:t) - [(h,a):ys | a - filter (p h) l, ys - funkyName p t l]
[] - [[]]

testCase :: Bool - Ordering - Int - [[(Int, Char)]]
testCase b o i =
  (if b then filteredPairs else funkyName) (prd o)
  [1 .. i] ['a' .. chr (ordA + i)]

main = do
  [arg1, arg2, arg3] - getArgs
  print . length . last . take 20 $ testCase (read arg1) (read arg2) (read arg3)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Existencial Types

2009-12-02 Thread Ryan Ingram
On Tue, Dec 1, 2009 at 4:44 PM, Luke Palmer lrpal...@gmail.com wrote:
 Existential types only buy you power when the quantified variable
 appears more than once on the right hand side, for example:  forall a.
 Num a = (a,a).  But even those can usually be factored out into more
 direct representations (I seem to recall Oleg has a proof that they
 always can, actually).

You are probably right that there is an encoding that doesn't use
existentials, but I've found they can be very useful in a few
situations, such as:

data Step s a = Done | Yield s a | Skip s
data Stream a = forall s. Stream s (s - Step s a)

Here the type of the stream state is encapsulated and not accessible
to the outside world, but it can still get some values of that type
via the result of the Step function.

data Expr a where
   ...
   App :: Expr (a - b) - Expr a - Expr b

Here we quantify over the type of the argument a; we just know that
we have an expression of that type and an expression of the function
type it wants.

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


[Haskell-cafe] Re: computing lists of pairs

2009-12-02 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 18:54:51 schrieb Christian Maeder:
 Daniel Fischer schrieb:
  However, according to a couple of tests, the funkyName version is
  somewhat faster and allocates less.

 My timing tests showed that your fpairs version is fastest.
 (first argument True selects filteredPairs, False funkyName)

I can confirm that for your test; still funkyName allocates less:

./FilteredPairs True EQ 5000 +RTS -sstderr  
   
5000
   
   1,810,136 bytes allocated in the heap
   
   1,160,412 bytes copied during GC 
   
 517,964 bytes maximum residency (1 sample(s))  
   
  16,932 bytes maximum slop 
   
   2 MB total memory in use (0 MB lost due to fragmentation)
   

  Generation 0: 2 collections, 0 parallel,  0.01s,  0.01s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.44s  (  0.44s elapsed)
  GCtime0.01s  (  0.01s elapsed)

./FilteredPairs False EQ 5000 +RTS -sstderr
5000
   1,432,328 bytes allocated in the heap
 974,252 bytes copied during GC
 441,064 bytes maximum residency (1 sample(s))
  27,608 bytes maximum slop
   2 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0: 2 collections, 0 parallel,  0.00s,  0.00s elapsed
  Generation 1: 1 collections, 0 parallel,  0.00s,  0.00s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.84s  (  0.84s elapsed)
  GCtime0.01s  (  0.01s elapsed)

./FilteredPairs True GT 5000 +RTS -sstderr  
   
5000
   
  10,961,984 bytes allocated in the heap
   
  12,164,420 bytes copied during GC 
   
   3,046,920 bytes maximum residency (4 sample(s))  
   
  25,836 bytes maximum slop 
   
   7 MB total memory in use (0 MB lost due to fragmentation)
   

  Generation 0:16 collections, 0 parallel,  0.04s,  0.04s elapsed
  Generation 1: 4 collections, 0 parallel,  0.03s,  0.04s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.23s  (  0.24s elapsed)
  GCtime0.08s  (  0.09s elapsed)

./FilteredPairs False GT 5000 +RTS -sstderr 
   
5000
   
   5,246,036 bytes allocated in the heap
   
   5,185,808 bytes copied during GC 
   
   1,699,744 bytes maximum residency (2 sample(s))  
   
  27,612 bytes maximum slop 
   
   4 MB total memory in use (0 MB lost due to fragmentation)
   

  Generation 0: 8 collections, 0 parallel,  0.02s,  0.02s elapsed
  Generation 1: 2 collections, 0 parallel,  0.02s,  0.01s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time0.44s  (  0.45s elapsed)
  GCtime0.04s  (  0.03s elapsed)

 My initial version myf is almost unusable.

 C.

 (code attached)

 mae...@leibniz:~/haskell/examples ghc --make -O2 FilteredPairs.hs
 [1 of 1] Compiling Main ( FilteredPairs.hs, FilteredPairs.o )
 Linking FilteredPairs ...
 mae...@leibniz:~/haskell/examples time ./FilteredPairs True EQ 5000
 5000

 real0m0.567s
 user0m0.536s
 sys 0m0.020s
 mae...@leibniz:~/haskell/examples time ./FilteredPairs False EQ 5000
 5000

 real0m0.819s
 user0m0.796s
 sys 0m0.012s

But with a different test, funkyName is considerably faster:

./pairs 1 8 20 +RTS -sstderr -A150M 
5529600 
 
 899,189,488 bytes allocated in the heap
 
  72,912,040 bytes copied during GC 
 
  28,074,964 bytes maximum residency (2 sample(s))  
 
 465,800 bytes maximum slop 
 
 200 MB total memory in use (2 MB lost due to fragmentation)
 

  Generation 0: 4 collections, 0 parallel,  0.17s,  0.21s elapsed
  Generation 1: 2 collections, 0 parallel,  0.36s,  0.39s elapsed

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time

[Haskell-cafe] Beginner's speed problem

2009-12-02 Thread Aditya M
Hi,

I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/
It is very simple. Given a and b, return the last digit of a^b. b
could be large, so I used logarithmic exponentiation and
wrote/submitted the code below for this problem:


--
lastdigit :: Int - Int - Int - Int
lastdigit 0 0 _ = 1
lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
| b == 1 = (a*c) `rem` 10
| otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)

doit :: [Char] - Int
doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1

main = do
  n - getLine
  inputs - sequence $ take (read n) $ repeat getLine
  let slist = map doit inputs
  mapM_ (putStrLn.show) slist
---

As n in main is at most 30, I thought this would easily run in 1
second, but I get a time limit exceeded error on the site. Can someone
tell me where my code is taking too much time?

Thanks in advance!
-- 
Aditya Manthramurthy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner's speed problem

2009-12-02 Thread Don Stewart
aditya87:
 Hi,
 
 I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/
 It is very simple. Given a and b, return the last digit of a^b. b
 could be large, so I used logarithmic exponentiation and
 wrote/submitted the code below for this problem:
 
 
 --
 lastdigit :: Int - Int - Int - Int
 lastdigit 0 0 _ = 1
 lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
 | b == 1 = (a*c) `rem` 10
 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)
 
 doit :: [Char] - Int
 doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 1
 
 main = do
   n - getLine
   inputs - sequence $ take (read n) $ repeat getLine
   let slist = map doit inputs
   mapM_ (putStrLn.show) slist
 ---

I notice an unnec. lazy 'c' argument to lastdigit,


{-# LANGUAGE BangPatterns #-}

lastdigit :: Int - Int - Int - Int
lastdigit 0 0 _  = 1
lastdigit a b !c | even b= lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
 | b == 1= (a*c) `rem` 10
 | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) 
(a*c)

doit :: [Char] - Int
doit line = lastdigit (read $ head $ words line) (read $ last $ words line) 
1

main = do
  n - getLine
  inputs - sequence $ take (read n) $ repeat getLine
  let slist = map doit inputs
  mapM_ (putStrLn.show) slist

Would generate better code for lastdigit.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-12-02 Thread Joachim Breitner
Hi,

Am Montag, den 30.11.2009, 00:30 + schrieb Duncan Coutts:
 I should also note that distros will not look kindly on solutions that
 require N * M separate packages.

with my Debian-Developer hat on I can very much support this statement.
Which is why I’m so interested in a proper solution to the
instance-Providing-problem. And which is why I’m trying to revive the
thread now :-)

Would it be techically possible and feasible to write instance that do
not actually cause a dependency on the package that defines the class
resp. the data type? From a distributor point of view, I could live
quite well with a setup like this:
 * When the package providing class Foo is compiled, instances for all
interesting data types in the distribution are defined. This means a lot
of build-dependencies, but they are not too bad (although annoying).
 * The generated package does (somehow) not depend on all these data
packages. Of course, any part of the code that uses these data types,
especially the class instances, are only usable when the corresponding
package is also installed. I guess this would need compiler support, to
not choke on code that uses unknown data types.
 * Packages needing an instance Foo Bar would just depend on the packges
providing foo and bar, and the instance will be available and
functional.

This idea works symmetric: The instances could also be defined in the
data type package, with no hard dependency on the package providing the
class definition.


Greetings,
Joachim

-- 
Joachim nomeata Breitner
  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nome...@debian.org


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner's speed problem

2009-12-02 Thread Daniel Fischer
Am Mittwoch 02 Dezember 2009 22:44:01 schrieb Don Stewart:
 aditya87:
  Hi,
 
  I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/
  It is very simple. Given a and b, return the last digit of a^b. b
  could be large, so I used logarithmic exponentiation and

Just to mention it, you can do something much much faster for this problem.
Something in the microsecond range (if IO is fast enough, millisecond 
otherwise).

  wrote/submitted the code below for this problem:
 
 
  --
  lastdigit :: Int - Int - Int - Int
  lastdigit 0 0 _ = 1
  lastdigit a b c | even b = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) c
 
  | b == 1 = (a*c) `rem` 10
  | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2)
  | (a*c)
 
  doit :: [Char] - Int
  doit line = lastdigit (read $ head $ words line) (read $ last $ words
  line) 1
 
  main = do
n - getLine
inputs - sequence $ take (read n) $ repeat getLine
let slist = map doit inputs
mapM_ (putStrLn.show) slist
  ---

 I notice an unnec. lazy 'c' argument to lastdigit,

Though for = 30 inputs and exponents  2^31, the laziness shouldn't do too 
much harm, I 
think. Shouldn't push it over one second, now they've at last replaced 6.6.1.



 {-# LANGUAGE BangPatterns #-}

 lastdigit :: Int - Int - Int - Int
 lastdigit 0 0 _  = 1
 lastdigit a b !c | even b= lastdigit ( (a*a) `rem` 10 ) (b `quot`
 2) c

  | b == 1= (a*c) `rem` 10

However,

   | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)

is problematic. The (a*c), to be exact. The exponent may be close to 2^31, so 
up to 30 
bits may be set. You then have a multiplication of up to 30 factors, the first 
is ( 20), 
the others ( 10), but it may easily overflow Int range, and then the last 
digit need not 
be correct.

You need ((a*c) `rem` 10) there.


 doit :: [Char] - Int
 doit line = lastdigit (read $ head $ words line) (read $ last $ words
 line) 1

 main = do
   n - getLine
   inputs - sequence $ take (read n) $ repeat getLine
   let slist = map doit inputs
   mapM_ (putStrLn.show) slist

I'd prefer

main = do
lns - fmap lines getContents
mapM_ (print . doit) $ tail lns

or

main = fmap lines getContents = mapM_ (print . doit) . tail


 Would generate better code for lastdigit.


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


[Haskell-cafe] Finding HP

2009-12-02 Thread Andrew Coppin
Today I was setting up a my new, and I wanted to put Haskell on it. 
Rather than download GHC itself, I decided to install the Haskell 
Platform instead, just to see what it's like.


Much to my surprise, I couldn't actually find any reference to its 
existence anywhere from the haskell.org home page, and I eventually had 
to run a search to find it.


Subsequently, I realise [as somebody will no doubt point out] that the 
link is actually there, on the front page, right next to GHC, Hugs, et al.


My suggestion is that if we really want people to grab the HP rather 
than download GHC directly, maybe we could make the link slightly more 
prominent? It also wouldn't hurt to mention it from the 
Implementations page, and maybe the GHC homepage? Just a suggestion...


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


Re: [Haskell-cafe] Finding HP

2009-12-02 Thread Don Stewart
andrewcoppin:
 Today I was setting up a my new, and I wanted to put Haskell on it.  
 Rather than download GHC itself, I decided to install the Haskell  
 Platform instead, just to see what it's like.

 Much to my surprise, I couldn't actually find any reference to its  
 existence anywhere from the haskell.org home page, and I eventually had  
 to run a search to find it.

It is listed right on the front page, twice. It is the first link on the
page:

[Download Haskell]

As well as:

[The Haskell Platform] has been released.

Are you sure  this isn't user error?

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


Re: [Haskell-cafe] Finding HP

2009-12-02 Thread Gregory Crosswhite
On Dec 2, 2009, at 2:26 PM, Andrew Coppin wrote:

 Subsequently, I realise [as somebody will no doubt point out] that the link 
 is actually there, on the front page, right next to GHC, Hugs, et al.

On Dec 2, 2009, at 2:29 PM, Don Stewart wrote:

 It is listed right on the front page, twice.

Whoa, Andrew, you really can predict the future!!!  Any stock market tips?

On a more serious note, Download Haskell /= Download Haskell Platform, so 
if I were glancing down the sidebar looking for a link to download the Haskell 
Platform then the first link wouldn't have registered for me.  And putting a 
X has been released link! in the news does not count as a prominent download 
link.

Furthermore, when someone offers feedback designed to improve a page, and does 
so in a very non-threatening way:

On Dec 2, 2009, at 2:26 PM, Andrew Coppin wrote:

 My suggestion is that if we really want people to grab the HP rather than 
 download GHC directly, maybe we could make the link slightly more prominent? 
 It also wouldn't hurt to mention it from the Implementations page, and 
 maybe the GHC homepage? Just a suggestion...

... then in my own humble opinion, snapping back with Are you sure this isn't 
user error? is not a particularly nice response.

- Greg

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


[Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Martijn van Steenbergen

So here's a totally wild idea Sjoerd and I came up with.

What if newtypes were unwrapped implicitly?

What advantages and disadvantages would it have?
In what cases would this lead to ambiguous code?

Thanks,

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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Tony Morris
Isn't that the point of type-classes?

Martijn van Steenbergen wrote:
 So here's a totally wild idea Sjoerd and I came up with.

 What if newtypes were unwrapped implicitly?

 What advantages and disadvantages would it have?
 In what cases would this lead to ambiguous code?

 Thanks,

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


-- 
Tony Morris
http://tmorris.net/


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


[Fwd: Re: [Haskell-cafe] Implicit newtype unwrapping]

2009-12-02 Thread Holger Siegel
Am Donnerstag, den 03.12.2009, 01:16 +0100 schrieb Martijn van
Steenbergen:
 So here's a totally wild idea Sjoerd and I came up with.
 
 What if newtypes were unwrapped implicitly?
 
 What advantages and disadvantages would it have?
 In what cases would this lead to ambiguous code?

1)
instance Monoid a = Monoid (Dual a)

2)
instance Monoid (Endo a)
instance Monoid b = Monoid (a - b)


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


Re: [Fwd: Re: [Haskell-cafe] Implicit newtype unwrapping]

2009-12-02 Thread Sjoerd Visscher
The idea is that there's just enough unwrapping such that you don't need to use 
getDual and appEndo.

On Dec 3, 2009, at 1:25 AM, Holger Siegel wrote:

 Am Donnerstag, den 03.12.2009, 01:16 +0100 schrieb Martijn van
 Steenbergen:
 So here's a totally wild idea Sjoerd and I came up with.
 
 What if newtypes were unwrapped implicitly?
 
 What advantages and disadvantages would it have?
 In what cases would this lead to ambiguous code?
 
 1)
 instance Monoid a = Monoid (Dual a)
 
 2)
 instance Monoid (Endo a)
 instance Monoid b = Monoid (a - b)
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

--
Sjoerd Visscher
sjo...@w3future.com



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


Re: [Haskell-cafe] Re: Are there standard idioms for lazy, pure error handling?

2009-12-02 Thread wren ng thornton

Nicolas Pouillard wrote:

Excerpts from Heinrich Apfelmus's message of Tue Dec 01 11:29:24 +0100 2009:

I propose to (trivially) generalize this type to list with an end

   data ListEnd a b = Cons a (ListEnd a b)
| End b

because it may have other uses than just lazy error handling. For
mnemonic value, we could call it a train:

   data Train a b = Wagon a (Train a b)
  | Loco  b

[...]


This proposition looks quite nice and gently subsume the ListThenError
type.

type ListThenError e a = Train a (Maybe e)

Anyone to put this on Hackage?


I rather like it too. The mnemonic version sounds a lot nicer than 
ListEnd, though I'd probably call the constructors Cabin and Caboose. 
The nice thing about the generalization is that even though (Train a b) 
is very similar to ([a],b) it's not exactly isomorphic. There are 
differences in the strictness of generating them and I've often wanted 
something like Train.


Wherever this ends up, it'd be pretty easy to do train-fusion in order 
to reduce the cost over using lists. If noone else wants to take it, I 
could probably find a few tuits to get it done. Though it looks like 
John Millikin already has failable-list up on Hackage, which differs 
only in also having a Nil to end with (which interferes with certain 
fusions, but not the major ones).


--
Live well,
~wren
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Gregory Crosswhite
Out of curiosity, why would one want a newtype that were unwrapped 
implicitly, rather than just using type?

Personally, whenever I use a newtype it is precisely because I *want* the 
compiler not to implicitly turn it into something else in order to protect 
myself.

Cheers,
Greg

On Dec 2, 2009, at 4:16 PM, Martijn van Steenbergen wrote:

 So here's a totally wild idea Sjoerd and I came up with.
 
 What if newtypes were unwrapped implicitly?
 
 What advantages and disadvantages would it have?
 In what cases would this lead to ambiguous code?
 
 Thanks,
 
 Martijn.
 ___
 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] Implicit newtype unwrapping

2009-12-02 Thread Greg Fitzgerald
Gregory Crosswhite gcr...@phys.washington.edu wrote:
 Out of curiosity, why would one want a newtype that were unwrapped 
 implicitly, rather than just using type?

One reason might be because you only switched from 'type' to 'newtype'
so that you could write more refined Arbitrary instances for your
QuickCheck tests.

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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Luke Palmer
On Wed, Dec 2, 2009 at 6:08 PM, Greg Fitzgerald gari...@gmail.com wrote:
 Gregory Crosswhite gcr...@phys.washington.edu wrote:
 Out of curiosity, why would one want a newtype that were unwrapped 
 implicitly, rather than just using type?

 One reason might be because you only switched from 'type' to 'newtype'
 so that you could write more refined Arbitrary instances for your
 QuickCheck tests.

Maybe that is an indication that we should use a checker combinator
library instead of typeclasses for automated testing.  Less
convenient, more adaptable.

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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Gregory Crosswhite
Ah, that's a really good point.  It seems then that there is a use for 
implicitly unwrapped newtypes, but perhaps only when you never really wanted to 
use a newtype to begin with but had to in order to use a different instance 
declaration for the same type.  That suggests that the feature we'd really like 
is a way to declare that we want a type in a context to act as if it had a 
different instance declaration for a given typeclass, without having to go 
through newtype.

Cheers,
Greg

On Dec 2, 2009, at 5:08 PM, Greg Fitzgerald wrote:

 Gregory Crosswhite gcr...@phys.washington.edu wrote:
 Out of curiosity, why would one want a newtype that were unwrapped 
 implicitly, rather than just using type?
 
 One reason might be because you only switched from 'type' to 'newtype'
 so that you could write more refined Arbitrary instances for your
 QuickCheck tests.
 
 -Greg

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


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-12-02 Thread Reid Barton
On Wed, Dec 02, 2009 at 11:03:52PM +0100, Joachim Breitner wrote:
 Hi,
 
 Am Montag, den 30.11.2009, 00:30 + schrieb Duncan Coutts:
  I should also note that distros will not look kindly on solutions that
  require N * M separate packages.
 
 with my Debian-Developer hat on I can very much support this statement.
 Which is why I’m so interested in a proper solution to the
 instance-Providing-problem. And which is why I’m trying to revive the
 thread now :-)
 
 Would it be techically possible and feasible to write instance that do
 not actually cause a dependency on the package that defines the class
 resp. the data type?

It is technically possible, using Template Haskell, by exporting a TH
value representing the instance, which can be constructed without
importing the module where the class is defined, and leaving it to the
importer (which has that module imported as well) to splice in the
class declaration.

- file A.hs

module A where

class Foo a where
  foo :: Int - a

- file B.hs

{-# LANGUAGE TemplateHaskell #-}

module B where

import Language.Haskell.TH

-- do not import A

newtype Bar = Bar Int deriving Show

-- the TH equivalent of instance Foo Bar where foo = Bar
instanceFooBar :: Q [Dec]
instanceFooBar = return [InstanceD [] (AppT (ConT $ mkName A.Foo) (ConT $ 
mkName B.Bar))
   [ValD (VarP $ mkName foo) (NormalB (ConE $ 
mkName B.Bar)) []]]

- file C.hs

{-# LANGUAGE TemplateHaskell #-}

import A
import B

$(instanceFooBar)

main = print (foo 3 :: Bar)

-

Needless to say it would be preferable not to write instances directly
as TH syntax trees!  Unfortunately (for our purposes) the definition
instanceFooBar = [d| instance A.Foo Bar where foo = Bar |] is
rejected by the compiler unless A is imported in B (it complains that
A.Foo and foo are not in scope).  I suppose one could create a class
B.Foo with the same definition as A.Foo, write a quoted instance
referring to A.Foo, and use some generic programming to replace all
occurrences of B.Foo with A.Foo.

Of course, module B still sort of depends on module A in the sense
that if the definition of A.Foo changes, importers of B will no longer
be able to use instanceFooBar until B is updated.  On the other hand B
could export TH descriptions of multiple instance corresponding to
different versions of A.Foo, relying on the importer to select the one
which matches its selected version of A.

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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Greg Fitzgerald
 That suggests that the feature we'd really like is a way
 to declare that we want a type in a context to act as if it
 had a different instance declaration for a given typeclass,
 without having to go through newtype.

I'd want implicit type coercion from subtypes, so that you wouldn't
need an infinite hierarchy of nested typeclasses to implement the
following for all integers:

   data One = One

   -- Somehow tell GHC that One is a subset of Integer (without
implementing Num)
   oneToInteger :: One - Integer
   oneToInteger One = 1

   One + One == (2 :: Integer)

Seems like something Agda could handle.

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


[Haskell-cafe] Second Call for Copy: Monad.Reader Issue 15

2009-12-02 Thread Brent Yorgey
It's not too late to write something for Issue 15 of the Monad.Reader!

Whether you're an established academic or have only just started
learning Haskell, if you have something to say, please consider
writing an article for The Monad.Reader! The submission deadline
for Issue 15 is

**Friday, January 8, 2010**

The Monad.Reader


The Monad.Reader is a electronic magazine about all things Haskell.
It is less formal than journal, but somehow more enduring than a
wiki-page. There have been a wide variety of articles: exciting
code fragments, intriguing puzzles, book reviews, tutorials, and
even half-baked research ideas.

Submission Details
~~

Get in touch with me if you intend to submit something -- the sooner
you let me know what you're up to, the better.  I am also happy to
provide feedback on draft versions before the submission deadline.

Please submit articles for the next issue to me by e-mail (byorgey
at cis.upenn.edu).

Articles should be written according to the guidelines available
from

http://themonadreader.wordpress.com/contributing/

Please submit your article in PDF, together with any source files
you used. The sources will be released together with the magazine
under a BSD license.

If you would like to submit an article, but have trouble with LaTeX
please let me know and we'll sort something out.


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


[Haskell-cafe] universal binary version of Haskell Platform?

2009-12-02 Thread Benjamin L . Russell
Recently, in changing my work schedule to work mainly from home, I
switched from mainly using a work Wintel machine running Windows XP
Professional, Service Pack 3, to mainly using my home PowerPC G4
PowerBook Macintosh, currently upgraded to Mac OS X 10.5.8 Leopard.

However, to my surprise, there does not seem to be a version of the
Haskell Platform that runs natively on my current OS.

Does anybody know where to find a universal binary version of the
Haskell Platform, or at least of GHC 6.10.4?  Otherwise, I'm stuck
without a native version.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
Furuike ya, kawazu tobikomu mizu no oto. 
-- Matsuo Basho^ 

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


[Haskell-cafe] Haddock Secrets?

2009-12-02 Thread Gregory Crosswhite
Hey everyone,

Is there some secret to getting Haddock to work with literate Haskell sources 
that I am missing?

For example, when I download Takusen and type

cabal configure
cabal haddock

It produces HTML files complete with a table of contents, but with all of the 
documentation stripped out.  Oddly, I know that it is *possible* to process the 
literate sources into documentation because it appears on Hackage!

I am doing this on OSX Snow Leopard with GHC 6.10.4 and Haddock 2.5.

Thanks,
Greg

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


Re: [Haskell-cafe] Beginner's speed problem

2009-12-02 Thread Aditya M
Hello

Thanks for all the help!

I only have a couple of questions.

On Thu, Dec 3, 2009 at 03:45, Daniel Fischer daniel.is.fisc...@web.de wrote:
 Am Mittwoch 02 Dezember 2009 22:44:01 schrieb Don Stewart:
 aditya87:
  Hi,
 
  I am trying to solve this problem: https://www.spoj.pl/problems/LASTDIG/
  It is very simple. Given a and b, return the last digit of a^b. b
  could be large, so I used logarithmic exponentiation and

 Just to mention it, you can do something much much faster for this problem.
 Something in the microsecond range (if IO is fast enough, millisecond 
 otherwise).


I guess you mean that we can find the cycle that the last digits
follow while multiplying repeatedly by a, and then use that.

I'll try that next in Haskell!

     {-# LANGUAGE BangPatterns #-}

     lastdigit :: Int - Int - Int - Int
     lastdigit 0 0 _  = 1
     lastdigit a b !c | even b    = lastdigit ( (a*a) `rem` 10 ) (b `quot`
 2) c

                      | b == 1    = (a*c) `rem` 10

 However,

   | otherwise = lastdigit ( (a*a) `rem` 10 ) (b `quot` 2) (a*c)

This bang pattern (!c) is giving me pattern match errors. Is its only
effect evaluating c instead of plain substitution?


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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Gregory Crosswhite
But it seems to me like the whole point of using newtype is because you 
*don't* want your new type to be used everywhere that the old type can be used; 
 otherwise you would just use type to create an alias.  The only convincing 
exception I have heard to this (as you helpfully explained to me) is that one 
might be forced to use newtype to make a piece of code use a different instance 
declaration for a type.

In particular, I am not sure what you are getting at with your example, since 

one :: Integer
one = 1

works just as well.  Why did you want to define a new type?

Cheers,
Greg

On Dec 2, 2009, at 6:40 PM, Greg Fitzgerald wrote:

 That suggests that the feature we'd really like is a way
 to declare that we want a type in a context to act as if it
 had a different instance declaration for a given typeclass,
 without having to go through newtype.
 
 I'd want implicit type coercion from subtypes, so that you wouldn't
 need an infinite hierarchy of nested typeclasses to implement the
 following for all integers:
 
  data One = One
 
  -- Somehow tell GHC that One is a subset of Integer (without
 implementing Num)
  oneToInteger :: One - Integer
  oneToInteger One = 1
 
  One + One == (2 :: Integer)
 
 Seems like something Agda could handle.
 
 -Greg

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


Re: [Haskell-cafe] Implicit newtype unwrapping

2009-12-02 Thread Max Bolingbroke
2009/12/3 Gregory Crosswhite gcr...@phys.washington.edu:
 But it seems to me like the whole point of using newtype is because you 
 *don't* want your new type to be used everywhere that the old type can be 
 used;  otherwise you would just use type to create an alias.  The only 
 convincing exception I have heard to this (as you helpfully explained to me) 
 is that one might be forced to use newtype to make a piece of code use a 
 different instance declaration for a type.

You might also be forced to use a newtype because you need to use it
recursively - i.e. you need an alternative to equirecursive types. I
hit this quite often when building datatype using
fixpoints-of-a-functor and regularly wish for the ability to write:

type Fix f = f (Fix f)

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