[Haskell-cafe] RE: No warning in GHC

2010-03-22 Thread Simon Peyton-Jones
[Redirecting to haskell-cafe]

Try

http://www.haskell.org/ghc/docs/latest/html/users_guide/flag-reference.html#id2959068

With -Wall I get

bash-3.2$ ghc -c -Wall Foo.hs

Foo.hs:3:0:
Warning: Definition but no type signature for `func'
 Inferred type: func :: forall t t1. (Num t1) = t - t1

Foo.hs:3:5: Warning: Defined but not used: `x'

Foo.hs:4:10:
Warning: This binding for `x' shadows the existing binding
   bound at Foo.hs:3:5

| -Original Message-
| From: cvs-ghc-boun...@haskell.org [mailto:cvs-ghc-boun...@haskell.org] On 
Behalf Of
| Grigory Sarnitskiy
| Sent: 21 March 2010 19:37
| To: cvs-...@haskell.org
| Subject: No warning in GHC
| 
| Hello! I wonder, why GHC shows no warning in situations like
| 
| func x = x
| where x = 5
| 
| Sometimes I forget about argument names used, and use the same names in let 
or where.
| And it can take me quite a lot time to understand what is wrong. I think it 
would be
| nice to warn users if the argument is redefined in let/where clause. Shall 
I report
| a bug/feature request? I'm using ghc 6.10.4.
| 
| btw, I couldn't post to IRC: #ghc :Cannot send to channel
| 
| ___
| Cvs-ghc mailing list
| cvs-...@haskell.org
| http://www.haskell.org/mailman/listinfo/cvs-ghc

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


Re: [Haskell-cafe] Re: Occurs check error, help!

2010-03-22 Thread Daniel Fischer
-Ursprüngliche Nachricht-
Von: adamtheturtle kill2thr...@hotmail.com
Gesendet: 22.03.2010 04:52:19
An: haskell-cafe@haskell.org
Betreff: [Haskell-cafe] Re: Occurs check error, help!

Ivan Miljenovic ivan.miljenovic [ gmail.com writes:

 
 Since my answer before to your question obviously wasn't clear enough,
 let me highlight the lines of the error message that summarise what
 you have to do:
 
 On 22 March 2010 14:31, adamtheturtle kill2thrill [ hotmail.com
wrote:
     Possible fix:
       add (Eq a) to the context of the type signature for `shuffle'
 
 Alternatively, use the random-shuffle package rather than coding your own.
 


So sorry to keep on going on about this but I have been set to start with
shuffle :: Int - [a] - [a] so I have to do that and can't use the given 
code
and I 
really don't know where to put (Eq a)


shuffle :: Eq a = Int - [a] - [a]

Another option is to remove the call to delete, after all, what you want isn't 
to remove the first occurrence of an element equal to (cards !! i) from cards, 
but you want to remove element No. i from cards. You can simply achieve that 
without any type-class constraint. Take a look at take, drop and splitAt. Those 
should help you.


Thank you so much for replying :)



___
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: Strange typing?

2010-03-22 Thread Gleb Alexeyev

Ozgur Akgun wrote:
Is there any way to limit a functions type, not by a data type but by a 
group of constructors of a data type? If not, what would be the *right* 
thing to do to achieve this level of type safety?


data DT1 = X | Y | Z
data DT2 = A | B | C | D


func1 :: DT1 - DT2 -- instead of this
func1' :: (X|Y) - (B|C) -- i want sth. like this. (| means or)

OCaml has a feature called 'polymorphic variants' that allows exactly 
this. You may want to google 'polymorphic variants in haskell'.


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


[Haskell-cafe] breadth first search one-liner?

2010-03-22 Thread Johannes Waldmann
Dear all, there is this neat one-line BFS implementation

bfs :: Eq a
= ( a - [a] ) - a - [a]
bfs next start =
let xs = nub $ start : ( xs = next )
in  xs

but it has a problem: it only works for infinite graphs. This is fine:

take 20 $  bfs ( \ x - [2*x, x+1] ) 1

but this is not:

take 20 $  bfs ( \ x - filter (0) [ div x 2, x - 1 ] ) 10


Is there a nice way to repair this?
(I know how to code a BFS but here I'm asking for a one-liner.)


J. W.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] breadth first search one-liner?

2010-03-22 Thread Ross Paterson
On Mon, Mar 22, 2010 at 11:02:32AM +0100, Johannes Waldmann wrote:
 Dear all, there is this neat one-line BFS implementation
 
 bfs :: Eq a
 = ( a - [a] ) - a - [a]
 bfs next start =
 let xs = nub $ start : ( xs = next )
 in  xs
 
 but it has a problem: it only works for infinite graphs. This is fine:
 
 take 20 $  bfs ( \ x - [2*x, x+1] ) 1
 
 but this is not:
 
 take 20 $  bfs ( \ x - filter (0) [ div x 2, x - 1 ] ) 10
 
 Is there a nice way to repair this?

bfs :: (a - [a]) - a - [a]
bfs f s = concat $ takeWhile (not . null) $ iterate (= f) [s]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: breadth first search one-liner?

2010-03-22 Thread Johannes Waldmann
Nice! - Where's the 'nub'?



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


[Haskell-cafe] ANNOUNCE: AusHac2010

2010-03-22 Thread Ivan Lazar Miljenovic

Dreading the end of ZuriHac?  Wish the Haskellian camaraderie could
continue?

Well, if you're able to make your way to Sydney, Australia between the
16th and 18th of July, then AusHac2010 is for _you_!  It will be held
at the School of Computer Science and Engineering at the University of
New South Wales (thanks to Manuel Chakravarty and Ben Lippmeier for
offering to organise the rooms!).

If you are wanting to attend the inaugural Australian Hackathon, please
register at http://axman6.wufoo.com/forms/aushac-2010-sign-up/ .

For more information, see http://www.haskell.org/haskellwiki/AusHac2010
We will shortly be adding an extended version of the Who table; please
also add your details there as well as which projects you would be
interested in hacking in.

Hoping to see you there!

--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: breadth first search one-liner?

2010-03-22 Thread Ross Paterson
On Mon, Mar 22, 2010 at 10:30:32AM +, Johannes Waldmann wrote:
 Nice! - Where's the 'nub'?

A bit longer:

bfs :: Eq a = (a - [a]) - a - [a]
bfs f s = concat $ takeWhile (not . null) $ map snd $ iterate step ([], [s])
  where step (seen, xs) = let seen' = xs++seen in (seen', nub $ [y | x - xs, y 
- f x, notElem y seen'])
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: breadth first search one-liner?

2010-03-22 Thread Ross Paterson
A bit closer to the original:

bfs :: Eq a = (a - [a]) - a - [a]
bfs f s = concat $ takeWhile (not . null) levels
  where levels = foldr trim [] $ [s] : map (nub . (= f)) levels
trim xs xss = xs : map (\\ xs) xss
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: breadth first search one-liner?

2010-03-22 Thread Bertram Felgenhauer
Ross Paterson wrote:
 On Mon, Mar 22, 2010 at 10:30:32AM +, Johannes Waldmann wrote:
  Nice! - Where's the 'nub'?
 
 A bit longer:
 
 bfs :: Eq a = (a - [a]) - a - [a]
 bfs f s = concat $ takeWhile (not . null) $ map snd $ iterate step ([], [s])
   where step (seen, xs) = let seen' = xs++seen in (seen', nub $ [y | x - xs, 
 y - f x, notElem y seen'])

Basically the same idea:

bfs next start =
let go _  [] = []
go xs ys = let zs = nub (ys = next) \\ xs
   in  ys ++ go (zs ++ xs) zs
in  go [start] [start]

A slightly different approach is to add stage markers to the produced
streams, say

bfs next start =
let xs = nub $ Left 0 : Right s : (xs = next')
next' (Left n) = [Left (n + 1)]
next' (Right s) = map Right (next s)
stop (Left _ : Left _ : _) = []
stop (Left x : xs) = stop xs
stop (Right x : xs) = x : stop xs
in  stop xs

or
bfs next start = lefts . takeWhile (not . null)
. unfoldr (Just . span (either (const False) (const True)) . tail)
$ fix (nub . (Left 0 :) . (Right start :)
  . (= either ((:[]) . Left . succ) (map Right . next)))

This has the advantage that nub can be used directly. But it's far from
beautiful.

regards,

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


[Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Johann Höchtl
Hello, I was recentyl playing with Haskell (GHC that is) IO and text
processing.

Bytestrings and Lazy Bytestrings allow for fast and memory eficient
string (well, bytestring) handling, yet a lot of libraries do not
support them (yet)

Given the incredibly inneficient memory representation of [Char] (16
bytes? per cell) I wonder wheather String should default to lazy
batestring altogether instead of [Char].

The levenshtein distance as is on hackage uses e.g. String ([Char])
and as such is unneccessarily slow.

My question or discussion point: Why not depreciate [Char] altogether
and favour of lazy Bytestrings?

Regards,

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


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Ivan Lazar Miljenovic
Johann Höchtl johann.hoec...@gmail.com writes:
 Bytestrings and Lazy Bytestrings allow for fast and memory eficient
 string (well, bytestring) handling, yet a lot of libraries do not
 support them (yet)

WHat do you mean?  A lot of libraries need to use String because it's
easier to deal with and doesn't rely on knowing which encoding is being
used.  Bytestring is often nicer for IO, but for internal library stuff
(e.g. parsing) it may still be easier to use String.

 Given the incredibly inneficient memory representation of [Char] (16
 bytes? per cell) I wonder wheather String should default to lazy
 batestring altogether instead of [Char].

Well, then all pattern matching, etc. fails.  String and ByteStrings
have their own separate places and uses.

 The levenshtein distance as is on hackage uses e.g. String ([Char])
 and as such is unneccessarily slow.

Have you ported a version to ByteString and demonstrated that it is
noticeably faster?  Are you sure that it isn't the fault of the
algorithm being used?  Do you know that people only care about the
levenshtein distance of ByteStrings and not of normal Strings?
(Disclaimer: I've never even looked at the package.)  Providing a
ByteString version as well might be a viable option; replacing the
current one is quite likely not.

 My question or discussion point: Why not depreciate [Char] altogether
 and favour of lazy Bytestrings?

I believe I've answered this above.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Johan Tibell
On Mon, Mar 22, 2010 at 1:16 PM, Johann Höchtl johann.hoec...@gmail.com wrote:
 My question or discussion point: Why not depreciate [Char] altogether
 and favour of lazy Bytestrings?

A sequence of bytes is not the same thing as a sequence of Unicode
code points. If you want to replace String by something more efficient
have a look at Data.Text.

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


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Ivan Miljenovic
On 23 March 2010 00:10, Johan Tibell johan.tib...@gmail.com wrote:
 A sequence of bytes is not the same thing as a sequence of Unicode
 code points. If you want to replace String by something more efficient
 have a look at Data.Text.

Though Data.Text still has the disadvantage of not being as nice to
deal with as String, since you can't pattern match on it, etc.

Whilst it may degrade performance, treating String as a list of
characters rather than an array provides you with greater flexibility
of how to deal with it.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] which version is in the platform

2010-03-22 Thread S. Doaitse Swierstra
On the page:

http://hackage.haskell.org/platform/

I am told that the platform includes ghc-6.10.4, but if I click there on the 
Haskell:batteries included link to get to the page:

http://hackage.haskell.org/platform/contents.html

its states there that I get 6.12.1?

 Doaitse


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


Re: [Haskell-cafe] which version is in the platform

2010-03-22 Thread Don Stewart
doaitse:
 On the page:
 
 http://hackage.haskell.org/platform/
 
 I am told that the platform includes ghc-6.10.4, but if I click there
 on the Haskell:batteries included link to get to the page:
 
 http://hackage.haskell.org/platform/contents.html
 
 its states there that I get 6.12.1?
 

The beta of the 2010.2.0.0 release is now up, which is based on GHC 6.12.

The last stable Haskell Platform release is 2009.2.0.0, which used GHC
6.10.4. (And the windows installer currently up provides this version).

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


Re: [Haskell-cafe] which version is in the platform

2010-03-22 Thread S. Doaitse Swierstra
It seems that I am being served old pages by my web browser from the cache on 
my machine. By reloading the platform page, I suddenly am asked what system I 
do have, from weher I am referred to the 6.12 version of the platform,

 Doaitse

On 22 mrt 2010, at 14:25, Don Stewart wrote:

 doaitse:
 On the page:
 
 http://hackage.haskell.org/platform/
 
 I am told that the platform includes ghc-6.10.4, but if I click there
 on the Haskell:batteries included link to get to the page:
 
 http://hackage.haskell.org/platform/contents.html
 
 its states there that I get 6.12.1?
 
 
 The beta of the 2010.2.0.0 release is now up, which is based on GHC 6.12.
 
 The last stable Haskell Platform release is 2009.2.0.0, which used GHC
 6.10.4. (And the windows installer currently up provides this version).
 
 -- Don

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


Re: [Haskell-cafe] which version is in the platform

2010-03-22 Thread Don Stewart
doaitse:
 It seems that I am being served old pages by my web browser from the
 cache on my machine. By reloading the platform page, I suddenly am
 asked what system I do have, from weher I am referred to the 6.12
 version of the platform,

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


[Haskell-cafe] ANN: Three package announcements

2010-03-22 Thread Mario Blažević

There are three new packages on Hackage:
  - monad-parallel 0.5
(http://hackage.haskell.org/package/monad-parallel)
  - monad-coroutine 0.5
(http://hackage.haskell.org/package/monad-coroutine)
  - Streaming Component Combinators 0.5
(http://hackage.haskell.org/package/scc)

   The first two packages are completely new. Their functionality has
been present in SCC 0.4, but I thought they might be useful on their
own. I'm keeping all the version numbers in sync for now, and the source
code for all three packages is in a single Darcs repository at
http://code.haskell.org/SCC/.

   The monad-parallel library defines two Monad subclasses, 
MonadParallel and MonadFork, that enable monadic computations to be

executed in parallel and their results combined. The library also
exports a subset of the Control.Monad interface (ap, sequence, and
related functions), adjusted to exploit the parallelism. The only 
currently defined MonadParallel instances are IO, Maybe, [], and 
Identity. More  instances could be added, but I didn't want the package 
to depend on MTL or transformers. The library design was heavily 
influenced by the discussion in this Cafe thread:


http://www.mail-archive.com/haskell-cafe@haskell.org/msg68581.html

   The monad-coroutine package exports a generic monad transformer
Coroutine: Functor s = MonadTrans (Coroutine s). A 
Coroutine-transformed monad can suspend at any point, returning its

resumption wrapped in the functor s. There are also some functions for
manipulating and running coroutines, as well as a couple of useful
suspension functors such as Yield and Await.

   Finally, version 0.5 of Streaming Component Combinators (a.k.a. SCC)
comes with some significant code refactoring (as the two aforementioned
packages prove), simplifications, and performance enhancements. No new
features have been added since the 0.4 release.

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


[Haskell-cafe] CUFP mailing list

2010-03-22 Thread Günther Schmidt

Hi everyone,

is there a mailing list for CUFP-lers?

I have some questions that are related to commercial software 
development (in Haskell) which I don't think fit well on this list.


Günther


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


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread David Leimbach
On Mon, Mar 22, 2010 at 6:10 AM, Johan Tibell johan.tib...@gmail.comwrote:

 On Mon, Mar 22, 2010 at 1:16 PM, Johann Höchtl johann.hoec...@gmail.com
 wrote:
  My question or discussion point: Why not depreciate [Char] altogether
  and favour of lazy Bytestrings?

 A sequence of bytes is not the same thing as a sequence of Unicode
 code points. If you want to replace String by something more efficient
 have a look at Data.Text.


Slight correction.

A sequence of bytes is exactly the same thing as a sequence of Unicode bytes
when you use UTF8.




 -- Johan
 ___
 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] Syntax programming with lexemes rather than trees?

2010-03-22 Thread Stephen Tetley
Hello All

Modern functional programming languages give you algebraic data types
that are mighty convenient for programming with syntax trees. However,
I'm working in a domain (music typesetting) where modelling syntax
with trees can be problematic and I'm wondering whether I should work
at a lower level - essentially a list / stream of lexemes and some
notion of a context stack for processing, tracking when I'm inside a
tuplet and the metrical calculation is scaled, for example.

Does anyone know of any previous work that takes a lexical view of
syntax rather than an abstract syntax tree view? Any domain is good -
I can't imagine there's any prior work on music typesetting.

Pointers to papers would be more digestible than code but either is
fine. Similarly, implementation in any functional language is fine.

Thanks

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


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Jochem Berndsen

David Leimbach wrote:



On Mon, Mar 22, 2010 at 6:10 AM, Johan Tibell johan.tib...@gmail.com 
mailto:johan.tib...@gmail.com wrote:


On Mon, Mar 22, 2010 at 1:16 PM, Johann Höchtl
johann.hoec...@gmail.com mailto:johann.hoec...@gmail.com wrote:
  My question or discussion point: Why not depreciate [Char] altogether
  and favour of lazy Bytestrings?

A sequence of bytes is not the same thing as a sequence of Unicode
code points. If you want to replace String by something more efficient
have a look at Data.Text.


Slight correction.

A sequence of bytes is exactly the same thing as a sequence of Unicode 
bytes when you use UTF8.  



What is a Unicode byte?

Cheers, Jochem

--
Jochem Berndsen | joc...@functor.nl
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell platform questions

2010-03-22 Thread Gregory Collins
wren ng thornton w...@freegeek.org writes:

 I'm still on 10.5.8. I don't have cabal-install installed yet, but I just
 installed GHC-6.12.1/HP-2010.1.0.0. I can verify that ghci works fine so
 far. I'll check out cabal-install in the next couple days.

If there is an issue here it'd be with the binaries that ship with the
platform, not GHC; can you check /usr/local/bin/cabal to see if yours
has the same issue?

I'm betting I probably have to re-link the binaries with some magic don't
break on Leopard linker flag.

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: breadth first search one-liner?

2010-03-22 Thread Bertram Felgenhauer
Bertram Felgenhauer wrote:
 or
 bfs next start = lefts . takeWhile (not . null)

I copied the wrong version. This should be

bfs next start = rights . concat . takeWhile (not . null) 
-- rest unchanged
 . unfoldr (Just . span (either (const False) (const True)) . tail)
 $ fix (nub . (Left 0 :) . (Right start :)
   . (= either ((:[]) . Left . succ) (map Right . next)))

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


[Haskell-cafe] Announce: Haskell Platform 2010.1.0.0 (beta) release

2010-03-22 Thread Don Stewart
Live from (post-) Zurihac, I'm pleased to announce the 2010.1.0.0 (beta branch)
release of the Haskell Platform, supporting GHC 6.12.

http://hackage.haskell.org/platform/

The Haskell Platform is a comprehensive, robust development environment for
programming in Haskell. For new users the platform makes it trivial to get up
and running with a full Haskell development environment. For experienced
developers, the platform provides a comprehensive, standard base for commercial
and open source Haskell development that maximises interoperability and
stability of your code.

The 2010.1.0.0 release is a beta release for the GHC 6.12 series of compilers. 
It currently doesn't provide a Windows installer (which defaults to GHC 6.10.4
for now). We expect to make the stable branch with GHC 6.12.2 in soon.

This release includes a binary installer for Mac OS X Snow Leopard, as well as
source bundles for an Unix system, and a new design.

The Haskell Platform would not have been possible without the hard work
of the Cabal development team, the Hackage developers and maintainers,
the individual compiler, tool and library authors who contributed to the
suite, and the distro maintainers who build and distribute the Haskell
Platform.

Thanks!

-- Don  (for The Platform Infrastructure Team)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RFC: only-read-or-write-vars

2010-03-22 Thread vlado


  I wonder if this would be a place to add a function returning the pair
  of the read and write capabilities (for the lack of a better word) of a
  value.
 
  something like:
 
  rwPair:: v α - (ReadOnly v α , WriteOnly v α)
  rwPair a = (readOnly a, writeOnly a)
 
  sorry for the lame name, but my name game is off today.
 
  This particular function comes handy when playing with passing channels
  or pointers around. It might be worth it to have a dedicated type for
  that as well.
 
 What would this dedicated type look like?

Something along the lines of
* a type alias:
   type ReadWrite v α = (ReadOnly v α , WriteOnly v α)

* or a data type:
   data ReadWrite v α = ReadWrite {reader:: ReadOnly v α, writer::
WriteOnly v α }

The intent is to be able to recognise the available capabilities.

Then we could write a Link type, which is the sum of all four
possibilities and allowing pattern matching on capabilities. This is
similar to links in pi-calculus. I'm not sure if a link type should be
in your library though. My gut feeling is it should be in a separate
library, which implements a trusted kernel, which guarantees linearity -
i.e ReadOnly and WriteOnly to be used only once - either shallow,
guaranteeing that the projection can be taken only once, or deep
providing guarantees for 'proper' linearity. Sorry, I digress, that is a
pet subject I've been playing with on and off. 

 BTW thanks for pointing me to pointers! Of course a Ptr is also a
 mutable variable so I've added instances for them.
Pleasure to be of help, even if it was by accident


Cheers,
Vlado

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


Re: [Haskell-cafe] Syntax programming with lexemes rather than trees?

2010-03-22 Thread Malcolm Wallace
I'm working in a domain (music typesetting) where modelling syntax  
with trees can be problematic and I'm wondering whether I should  
work at a lower level - essentially a list / stream of lexemes and  
some notion of a context stack for processing, tracking when I'm  
inside a tuplet and the metrical calculation is scaled, for example.


It sounds like your domain is generation of syntax, rather than  
parsing.  It also sounds rather similar to the difference between the  
high-level language accepted by a compiler (represented by an AST) and  
the target language produced by a compiler (generally a flat list of  
almost-atomic instructions and labels).  So maybe techniques for  
dealing with low-level assembly-like languages would be worth  
investigating.


Regards,
Malcolm




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


Re: [Haskell-cafe] Syntax programming with lexemes rather than trees?

2010-03-22 Thread Stephen Tetley
Hi Malcolm

Thanks - particularly I don't want to go to an AST because its I'm
finding it too convoluted 'shape wise' - processing beam groups inside
tuplets etc. is a nightmare - music representations have had at least
eight centuries of ad hoc extension.

I know Norman Ramsey and colleagues papers on low-level
representations - I'll give them a re-reading.

Thanks again

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


Re: [Haskell-cafe] Re: Strange typing?

2010-03-22 Thread Ozgur Akgun
Thank you all very much for the pointers.

Best,

On 22 March 2010 09:32, Gleb Alexeyev gleb.alex...@gmail.com wrote:

 Ozgur Akgun wrote:

 Is there any way to limit a functions type, not by a data type but by a
 group of constructors of a data type? If not, what would be the *right*
 thing to do to achieve this level of type safety?

 data DT1 = X | Y | Z
 data DT2 = A | B | C | D


 func1 :: DT1 - DT2 -- instead of this
 func1' :: (X|Y) - (B|C) -- i want sth. like this. (| means or)

  OCaml has a feature called 'polymorphic variants' that allows exactly
 this. You may want to google 'polymorphic variants in haskell'.


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




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


[Haskell-cafe] Hackape package lackage

2010-03-22 Thread Dougal Stanton
Hackage seems to be down again.

$ cabal update
Downloading package list from server
'http://hackage.haskell.org/packages/archive'
^Ccabal: interrupted

$ ping -c3 hackage.haskell.org
PING abbot.galois.com (69.30.63.204) 56(84) bytes of data.

--- abbot.galois.com ping statistics ---
3 packets transmitted, 0 received, 100% packet loss, time 2012ms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Lennart Augustsson
Turn on OverloadedStrings and you can pattern match on any type you
like that is in the IsString class.
Which means that Data.Text can use string literals just like regular
strings (but you can't use Char literals in the match).

On Mon, Mar 22, 2010 at 1:15 PM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 23 March 2010 00:10, Johan Tibell johan.tib...@gmail.com wrote:
 A sequence of bytes is not the same thing as a sequence of Unicode
 code points. If you want to replace String by something more efficient
 have a look at Data.Text.

 Though Data.Text still has the disadvantage of not being as nice to
 deal with as String, since you can't pattern match on it, etc.

 Whilst it may degrade performance, treating String as a list of
 characters rather than an array provides you with greater flexibility
 of how to deal with it.

 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 ___
 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] Hackape package lackage

2010-03-22 Thread Don Stewart
We're watching *massive* traffic right now due to HP release.
It's not down, just very very busy.

For fun, here's a map of who's downloading Haskell:

http://imgur.com/flwPF.png

74 countries in 12 hours, and counting.

- Don

dougal:
 Hackage seems to be down again.
 
 $ cabal update
 Downloading package list from server
 'http://hackage.haskell.org/packages/archive'
 ^Ccabal: interrupted
 
 $ ping -c3 hackage.haskell.org
 PING abbot.galois.com (69.30.63.204) 56(84) bytes of data.
 
 --- abbot.galois.com ping statistics ---
 3 packets transmitted, 0 received, 100% packet loss, time 2012ms
 ___
 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] Hackape package lackage

2010-03-22 Thread Thomas Davie
I'd love to see that map normalised by the population of the country – would be 
interesting to see where Haskell is popular.

Bob

On 22 Mar 2010, at 16:22, Don Stewart wrote:

 We're watching *massive* traffic right now due to HP release.
 It's not down, just very very busy.
 
 For fun, here's a map of who's downloading Haskell:
 
http://imgur.com/flwPF.png
 
 74 countries in 12 hours, and counting.
 
 - Don
 
 dougal:
 Hackage seems to be down again.
 
 $ cabal update
 Downloading package list from server
 'http://hackage.haskell.org/packages/archive'
 ^Ccabal: interrupted
 
 $ ping -c3 hackage.haskell.org
 PING abbot.galois.com (69.30.63.204) 56(84) bytes of data.
 
 --- abbot.galois.com ping statistics ---
 3 packets transmitted, 0 received, 100% packet loss, time 2012ms
 ___
 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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: data-category, restricted categories

2010-03-22 Thread Sjoerd Visscher
Hi everybody,

At ZuriHac I released data-category. It is an implementation of several 
category-theoretical constructions.

I started this library to learn about both category theory and type level 
programming, so I wanted to implement the CT concepts as directly as possible. 
This in contrast to the excellent category-extras library, which (I think) also 
tries to be as useful as possible.

CT is about studying categories, so for data-category I wanted to implement all 
kinds of categories. The Control.Category module unfortunately requires you to 
implement id :: cat a a (for all a), which means it only supports categories 
that have exactly the same objects as Hask. So Data.Category contains an 
implementation of restricted categories, using inspiration from Oleg's 
restricted monads.

It is well known that the Functor class also is a bit limited, as it only 
supports endofunctors in Hask. But there's another problem, if you want to 
define the identity functor, or the composition of 2 functors, then you have to 
use newtype wrappers, which can get in the way. Data.Category has an 
implementation of functors which solves this by using type families. Functors 
are represented by labels, and the type family F turns the label into the 
actual functor. F.e. type instance F List a = [a], type instance F Id a = a.

The current version contains:
- categories
  - Void, Unit, Pair (discrete categories with 0, 1 and 2 objects respectively)
  - Boolean
  - Omega, the natural numbers as an ordered set (ω)
  - Monoid
  - Functor, the category of functors from one category to another
  - Hask
  - Kleisli
  - Alg, the category of F-Algebras
- functors
  - the identity functor
  - functor composition
  - the constant functor
  - the co- and contravariant Hom-functors
  - the diagonal functor
- natural transformations
- universal arrows
- limits and colimits (as universal arrows from/to the diagonal functor)
  - using Void as index category this gives initial and terminal objects
- f.e. in Alg the arrows from the initial object are catamorphisms
  - using Pair as index category this gives products and coproducts
- f.e. in Omega they are the minimum and maximum and in Boolean and and or.
- adjunctions

Of course the are still a lot of things missing, especially in the details. And 
I'm a category theory beginner, so there will probably be some mistakes in 
there as well. F.e. Edward Kmett doesn't like () being the terminal object in 
Hask, which I thought I understood, but after thinking about it a bit more I 
don't.

You can find data-category on hackage and on github:
http://hackage.haskell.org/package/data-category
http://github.com/sjoerdvisscher/data-category

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


[Haskell-cafe] Zarathustra

2010-03-22 Thread Günther Schmidt

Hi Cliff,

here is a link which might interest you

http://en.wikipedia.org/wiki/Zoroastrianism

Love

Günther


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


[Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-22 Thread Maciej Piechotka
Hmm. What are benefits of data-category over category-extras?

Regards



signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: ANN: data-category, restricted categories

2010-03-22 Thread Sjoerd Visscher
Mainly that category-extras doesn't have restricted categories, so most of the 
categories in data-category cannot be defined with category-extras. This also 
means that in category-extras many constructions are built from the ground up, 
instead of being built with a few basic building blocks, because that often 
requires a restricted category.

But data-category certainly isn't meant as a replacement of category-extras. It 
is a totally different way of working with CT.

On Mar 22, 2010, at 6:10 PM, Maciej Piechotka wrote:

 Hmm. What are benefits of data-category over category-extras?
 
 Regards
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

--
Sjoerd Visscher
http://w3future.com




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


Re: [Haskell-cafe] haskell platform questions

2010-03-22 Thread Warren Harris
BTW, I started to try the macports method (thinking that maybe  
building on my machine would resolve the linker problem), but the  
package up there seems to be the old one:


$ port info haskell-platform
haskell-platform @2009.2.0.2 (devel, haskell)

Description:  This is the the Haskell Platform: a single,  
standard Haskell distribution for every system. The Haskell Platform  
is a blessed library and tool suite for Haskell distilled from

  Hackage.
Homepage: http://hackage.haskell.org/platform/

Runtime Dependencies: ghc, hs-platform-cgi, hs-platform-fgl, hs- 
platform-editline, hs-platform-GLUT, hs-platform-haskell-src, hs- 
platform-html, hs-platform-HUnit, hs-platform-mtl, hs-platform-network,
  hs-platform-OpenGL, hs-platform-parallel, hs- 
platform-parsec, hs-platform-QuickCheck, hs-platform-regex-base, hs- 
platform-regex-compat, hs-platform-regex-posix, hs-platform-stm,
  hs-platform-time, hs-platform-xhtml, hs- 
platform-zlib, hs-platform-HTTP, hs-platform-alex, hs-platform-happy,  
hs-platform-cabal

Platforms:darwin
License:  unknown
Maintainers:  gwri...@macports.org


Maybe the dependencies haven't changed?

Also, not a big deal, but the instructions for the dmg version here http://hackage.haskell.org/platform/new/mac.html 
 page say to follow the instructions, but there aren't any packaged  
with it. I mistakenly ran the Haskell Platform 2010.1.0.0 installer  
first thinking that maybe it would install ghc as a dependency, but  
this crashed. Then I uninstalled everything, installed GHC-6.12.1- 
i386.pkg, then Haskell Platform 2010.1.0.0, and rebooted... and then  
experienced the cabal problem.


BTW, there's some description of linker flags here: http://discussions.apple.com/thread.jspa?threadID=2151112 
 but the developer claims 10.5.8 solved his problems (that's what I'm  
on).


Warren


On Mar 22, 2010, at 7:45 AM, Gregory Collins wrote:


wren ng thornton w...@freegeek.org writes:

I'm still on 10.5.8. I don't have cabal-install installed yet, but  
I just
installed GHC-6.12.1/HP-2010.1.0.0. I can verify that ghci works  
fine so

far. I'll check out cabal-install in the next couple days.


If there is an issue here it'd be with the binaries that ship with the
platform, not GHC; can you check /usr/local/bin/cabal to see if yours
has the same issue?

I'm betting I probably have to re-link the binaries with some magic  
don't

break on Leopard linker flag.

G
--
Gregory Collins g...@gregorycollins.net
___
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] haskell platform questions

2010-03-22 Thread Gregory Collins
Warren Harris warrensomeb...@gmail.com writes:

 Then I uninstalled everything, installed GHC-6.12.1- i386.pkg, then
 Haskell Platform 2010.1.0.0, and rebooted... and then experienced
 the cabal problem.

 BTW, there's some description of linker flags here:
 http://discussions.apple.com/thread.jspa?threadID=2151112 but the
 developer claims 10.5.8 solved his problems (that's what I'm on).

Thanks, that's helpful. I'll cut a new release shortly.

G
-- 
Gregory Collins g...@gregorycollins.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] which version is in the platform

2010-03-22 Thread Ivan Lazar Miljenovic
Don Stewart d...@galois.com writes:
 The beta of the 2010.2.0.0 release is now up, which is based on GHC
 6.12.

Hang on, you just announced 2010.1.0.0... have you suddenly released
_another_ major version? :p

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CUFP mailing list

2010-03-22 Thread Erik de Castro Lopo
Günther Schmidt wrote:

 I have some questions that are related to commercial software 
 development (in Haskell) which I don't think fit well on this list.

Really? This is haskell-cafe. If its even tangentially haskell
related I'm sure this this list would be fine.

According to http://www.haskell.org/haskellwiki/Mailing_Lists

  haskell-cafe@haskell.org (archives)
General Haskell questions; extended discussions.
In Simon Peyton Jones' words: forum in which it's acceptable to ask
anything, no matter how naive, and get polite replies. 

Cheers,
Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bytestrings and [Char]

2010-03-22 Thread Mads Lindstrøm
Hi

David Leimbach wrote:
 
 
 On Mon, Mar 22, 2010 at 6:10 AM, Johan Tibell johan.tib...@gmail.com
 wrote:
 On Mon, Mar 22, 2010 at 1:16 PM, Johann Höchtl
 johann.hoec...@gmail.com wrote:
  My question or discussion point: Why not depreciate [Char]
 altogether
  and favour of lazy Bytestrings?
 
 
 A sequence of bytes is not the same thing as a sequence of
 Unicode
 code points. If you want to replace String by something more
 efficient
 have a look at Data.Text.
 
 
 Slight correction.
 
 
 A sequence of bytes is exactly the same thing as a sequence of Unicode
 bytes when you use UTF8.  

And a sequence of bytes is exactly the same thing as a UTF-32 string,
when the sequence is encoded as UTF-32.

But that is not the point. The point is that when some function is
handed a ByteString, the ByteString can be encoded in many ways. It do
not even have to be text.

So you need a UTF-8 String type.

/Mads

 
 
  
 
 -- Johan
 
 ___
 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


signature.asc
Description: This is a digitally signed message part
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Software Deployment and Distribution - WAS Re: CUFP mailing list

2010-03-22 Thread Günther Schmidt

Hello Erik,

all right then.
I've written a commercial Desktop application in Haskell for the Win32 
platform.


The one thing missing is Software Copy Protection, ie. a software 
licensing mechanism. When I google for Software Copy Protection I get 
a lot of results, commercial products themselves, which is fine, but I 
can't tell which ones are any good or worth their money.


I've never seriously done C#, VB or whatever people mainly write Win32 
apps in, so I don't know any mailing lista or forums where I could ask 
this question. This list has pretty much been the only list I used for 
more than 2 years now.


I've never seen a similar issued raised here before so I thought the 
CUFP mailing list is a better place for this.



Can anybody here recommend a good software for this then? I do not want 
to code it myself and would prefer a ready to use solution, it it's not 
free that fine too.


Best regards

Günther



Am 22.03.10 22:23, schrieb Erik de Castro Lopo:

Günther Schmidt wrote:


I have some questions that are related to commercial software
development (in Haskell) which I don't think fit well on this list.


Really? This is haskell-cafe. If its even tangentially haskell
related I'm sure this this list would be fine.

According to http://www.haskell.org/haskellwiki/Mailing_Lists

   haskell-cafe@haskell.org (archives)
 General Haskell questions; extended discussions.
 In Simon Peyton Jones' words: forum in which it's acceptable to ask
 anything, no matter how naive, and get polite replies.

Cheers,
Erik




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


Re: [Haskell-cafe] Software Deployment and Distribution - WAS Re: CUFP mailing list

2010-03-22 Thread Erik de Castro Lopo
Günther Schmidt wrote:

 I've written a commercial Desktop application in Haskell for the Win32 
 platform.
 
 The one thing missing is Software Copy Protection, ie. a software 
 licensing mechanism. When I google for Software Copy Protection I get 
 a lot of results, commercial products themselves, which is fine, but I 
 can't tell which ones are any good or worth their money.
 
 I've never seriously done C#, VB or whatever people mainly write Win32 
 apps in, so I don't know any mailing lista or forums where I could ask 
 this question. This list has pretty much been the only list I used for 
 more than 2 years now.
 
 I've never seen a similar issued raised here before so I thought the 
 CUFP mailing list is a better place for this.
 
 
 Can anybody here recommend a good software for this then? I do not want 
 to code it myself and would prefer a ready to use solution, it it's not 
 free that fine too.

Well that certainly is an unusual question.

There are large companies like Apple, the RIAA and the MPAA who have put
large amounts of time, money and effort into copy protection schemes only
to have them broken, sometimes in as little as a day or two.

In addition, by the time you have a copy control mechanism that is
partially effective your users may find the experience so painful that
using cracked copies is easier. There is a common theme here:

http://i.imgur.com/GxzeV.jpg
http://www.bradcolbow.com/archive.php/?p=205
http://xkcd.com/488/

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Software Deployment and Distribution - WAS Re: CUFP mailing list

2010-03-22 Thread MightyByte
Fundamentally, Software Copy Protection (as well as DRM) is an
unsolvable problem.  It's basically like saying that you want to give
someone something and not give it to them at the same time.  With
physical products there are physical properties that you can use to
accomplish some aspects of this.  But with information products and
the possibility of essentially zero-cost copying you don't have these
physical constraints to help you.

Copy Protection (CP) and DRM advocates have tried to use cryptography
to solve this problem.  The idea being that cryptography lets you hide
information from people, so it should be able to help with this
problem.  Encryption allows Alice and Bob to communicate secretly
without Eve, Mallet, etc from being able to read their communication.
This is all predicated on the idea that Alice and Bob trust each
other.  (I'm only going to reveal my secrets to you if I trust that
you're not going to publish them for others to read.)  The problem
that CP (Alice) is up against is that Bob and Eve are the same person!

If you can't trust the person to whom you're sending something, then
the only secure solution is not to send it to them.  This can be done
by delivering software that simply doesn't have certain capabilities.
You typically can't just disable the capabilities in your software.
You have to ensure that the code implementing those capabilities is
not present.

Software as a service is another solution to this problem.


On Mon, Mar 22, 2010 at 6:09 PM, Erik de Castro Lopo
mle...@mega-nerd.com wrote:
 Günther Schmidt wrote:

 I've written a commercial Desktop application in Haskell for the Win32
 platform.

 The one thing missing is Software Copy Protection, ie. a software
 licensing mechanism. When I google for Software Copy Protection I get
 a lot of results, commercial products themselves, which is fine, but I
 can't tell which ones are any good or worth their money.

 I've never seriously done C#, VB or whatever people mainly write Win32
 apps in, so I don't know any mailing lista or forums where I could ask
 this question. This list has pretty much been the only list I used for
 more than 2 years now.

 I've never seen a similar issued raised here before so I thought the
 CUFP mailing list is a better place for this.


 Can anybody here recommend a good software for this then? I do not want
 to code it myself and would prefer a ready to use solution, it it's not
 free that fine too.

 Well that certainly is an unusual question.

 There are large companies like Apple, the RIAA and the MPAA who have put
 large amounts of time, money and effort into copy protection schemes only
 to have them broken, sometimes in as little as a day or two.

 In addition, by the time you have a copy control mechanism that is
 partially effective your users may find the experience so painful that
 using cracked copies is easier. There is a common theme here:

    http://i.imgur.com/GxzeV.jpg
    http://www.bradcolbow.com/archive.php/?p=205
    http://xkcd.com/488/

 Erik
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/
 ___
 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] Software Deployment and Distribution - WAS Re: CUFP mailing list

2010-03-22 Thread Stephen Tetley
Hi Günther

Congratulations!

You might find this article useful. Though it only mentions one
particular system Armadillo, there are a number of good tips like
releasing updates frequently so the binaries change, and the author is
well regarded in micro software circles.

http://www.kalzumeus.com/2006/09/05/everything-you-need-to-know-about-registration-systems/

GHC binaries do contain quite a lot of textual information. Where
functions work with registration codes you ought to cloak their names
and maybe add a dummy API to throw crackers off the scent.

Best wishes

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


[Haskell-cafe] Graphical representation of Haskell code

2010-03-22 Thread Dupont Corentin
Hello,

I’m relatively new to Haskell.

 I’m wondering if it exist a tool to graphically represent Haskell code.


 Look at the little graphics at: http://www.haskell.org/arrows/index.html (and
following pages) from Ross Paterson.
http://www.haskell.org/arrows/index.htm

If found these very useful to understand the Arrow monad.


 Why not automatise this in a tool? Such a tool could draw a graphic from
the code of a program.

This could be done entirely automatically from the types of the functions.


 Let’s try to do it on a simple example, as an exercise:

 f = Map (+1)


 How does this function could be represented?


 It contains the (+) function.

This function has the type (+) :: Num a = a - a - a.

From this type we could deduce the graphic:

[image: Haskell schematic_html_m20060f13.gif]

Or a curried version:

[image: Haskell schematic_html_5155f0eb.gif]

The function (+1) then is:

[image: Haskell schematic_html_m68795eb7.gif]


 The function map could be drawn like this :

[image: Haskell schematic_html_m28c92a58.gif]

 Or like this:


[image: Haskell schematic_html_m6ae433ea.gif]


And the entire function map (+1) could be represented as:

[image: Haskell schematic_html_macb1643.gif]



Thanks to the advanced type system of Haskell, everything could be deduced
from the type signatures.


 Such a tool would be recreational and educational.

One could zoom in and out in a program, to display more or less details.

This could help understand a program, globally or locally.


 We could even imagine a constructive version of the tool, where the
programmer would draw functions from a toolbox, and stick them into the
graphic!


 Does a tool approaching this already exist? If not, would it be a good
project?


 Cheers,

Corentin
Haskell schematic_html_m28c92a58.gifHaskell schematic_html_m6ae433ea.gifHaskell schematic_html_m68795eb7.gifHaskell schematic_html_macb1643.gifHaskell schematic_html_m20060f13.gifHaskell schematic_html_5155f0eb.gif___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-22 Thread Ivan Miljenovic
On 23 March 2010 10:02, Dupont Corentin corentin.dup...@gmail.com wrote:
 I’m relatively new to Haskell.

Welcome!

 I’m wondering if it exist a tool to graphically represent Haskell code.

 Look at the little graphics at: http://www.haskell.org/arrows/index.html (and 
 following pages) from Ross Paterson.

 If found these very useful to understand the Arrow monad.

 Why not automatise this in a tool? Such a tool could draw a graphic from the 
 code of a program.

1) Because no-one has written such a tool yet (though someone has
suggested doing one as a GSoC project).
2) I'm of the opinion that unless you just use it on small snippets,
the generated images will be too large and unweildy.

 This could be done entirely automatically from the types of the functions.

Except not everyone provides type signatures for their functions;
whilst it may be possible to use the GHC API to infer these type
signatures, my understanding is that it's preferable to use other
parsers such as haskell-src-exts as the GHC API is unstable.

[shameless plug]
My SourceGraph (http://hackage.haskell.org/package/SourceGraph) tool
does function call visualisation as part of its analyses.
[/shameless plug]


--
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Software Deployment and Distribution - WAS Re: CUFP mailing list

2010-03-22 Thread Günther Schmidt

Hello Erik,

the software I wrote and am about to sell was developed for use by 
German Hospitals only. It's being used to calculate a departments share 
of the revenues paid by the insurance companies for a case and needed 
every 6 months by the hospitals when it enters budget negotiations with 
the insurance companies. It could for instance not be used by Hospitals 
outside of Germany.


I think it is unlikely that the Hospitals would try to hack my 
application but thanks for the concern.


But I do need something in place, something that will check if the 
hospital is using a licensed version. It is also expected on the 
customers side otherwise the customer would not even consider using the 
software but reject it outright.


Best regards

Günther


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


Re: [Haskell-cafe] Re: Software Deployment and Distribution - WAS Re: CUFP mailing list

2010-03-22 Thread Erik de Castro Lopo
Günther Schmidt wrote:

 Hello Erik,
 
 the software I wrote and am about to sell was developed for use by 
 German Hospitals only. It's being used to calculate a departments share 
 of the revenues paid by the insurance companies for a case and needed 
 every 6 months by the hospitals when it enters budget negotiations with 
 the insurance companies. It could for instance not be used by Hospitals 
 outside of Germany.
 
 I think it is unlikely that the Hospitals would try to hack my 
 application but thanks for the concern.

Since the number of people wanting to use your application is small,
even the most primitve copy protection mechanisms would probably
suffice.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-22 Thread Lyndon Maydwell
Reminds me of To Dissect a Mockingbird [http://dkeenan.com/Lambda/].

On Tue, Mar 23, 2010 at 7:12 AM, Ivan Miljenovic
ivan.miljeno...@gmail.com wrote:
 On 23 March 2010 10:02, Dupont Corentin corentin.dup...@gmail.com wrote:
 I’m relatively new to Haskell.

 Welcome!

 I’m wondering if it exist a tool to graphically represent Haskell code.

 Look at the little graphics at: http://www.haskell.org/arrows/index.html 
 (and following pages) from Ross Paterson.

 If found these very useful to understand the Arrow monad.

 Why not automatise this in a tool? Such a tool could draw a graphic from the 
 code of a program.

 1) Because no-one has written such a tool yet (though someone has
 suggested doing one as a GSoC project).
 2) I'm of the opinion that unless you just use it on small snippets,
 the generated images will be too large and unweildy.

 This could be done entirely automatically from the types of the functions.

 Except not everyone provides type signatures for their functions;
 whilst it may be possible to use the GHC API to infer these type
 signatures, my understanding is that it's preferable to use other
 parsers such as haskell-src-exts as the GHC API is unstable.

 [shameless plug]
 My SourceGraph (http://hackage.haskell.org/package/SourceGraph) tool
 does function call visualisation as part of its analyses.
 [/shameless plug]


 --
 Ivan Lazar Miljenovic
 ivan.miljeno...@gmail.com
 IvanMiljenovic.wordpress.com
 ___
 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] haskell platform questions

2010-03-22 Thread wren ng thornton

Gregory Collins wrote:

wren ng thornton w...@freegeek.org writes:


I'm still on 10.5.8. I don't have cabal-install installed yet, but I just
installed GHC-6.12.1/HP-2010.1.0.0. I can verify that ghci works fine so
far. I'll check out cabal-install in the next couple days.


If there is an issue here it'd be with the binaries that ship with the
platform, not GHC; can you check /usr/local/bin/cabal to see if yours
has the same issue?


w...@semiramis:~ $ ls /usr/local
ls: /usr/local: No such file or directory
w...@semiramis:~ $ ls /usr/bin/cabal
ls: /usr/bin/cabal: No such file or directory


But http://hackage.haskell.org/platform/new/contents.html tells me 
cabal-install is supposed to ship with the platform...


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


Re: [Haskell-cafe] haskell platform questions

2010-03-22 Thread Ivan Miljenovic
On 23 March 2010 14:25, wren ng thornton w...@freegeek.org wrote:
 w...@semiramis:~ $ ls /usr/local
 ls: /usr/local: No such file or directory
 w...@semiramis:~ $ ls /usr/bin/cabal
 ls: /usr/bin/cabal: No such file or directory


 But http://hackage.haskell.org/platform/new/contents.html tells me
 cabal-install is supposed to ship with the platform...

It is; where did you install it to though?  Does whereis cabal say anything?

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-22 Thread Mihai Maruseac
I've proposed to do it at this GSOC. More exactly, it is still in the
feedback phase, I'll integrate all feedback in another blog post and in an
application for GSOC tomorrow. If you want to read about it in this stage,
you can visit my blog [0]. Feedback on reddit can be seen here[1].

The pictures from Ross Paterson were one of the reasons for my idea.

[0]: http://pgraycode.wordpress.com/2010/03/20/haskell-project-idea/
[1]:
http://www.reddit.com/r/haskell/comments/bg3bx/i_need_feedback_on_a_haskell_project_idea_maybe/

-- 
Mihai Maruseac

On Tue, Mar 23, 2010 at 1:02 AM, Dupont Corentin
corentin.dup...@gmail.comwrote:

 Hello,

 I’m relatively new to Haskell.

  I’m wondering if it exist a tool to graphically represent Haskell code.


  Look at the little graphics at: http://www.haskell.org/arrows/index.html (and
 following pages) from Ross Paterson.
 http://www.haskell.org/arrows/index.htm

 If found these very useful to understand the Arrow monad.


  Why not automatise this in a tool? Such a tool could draw a graphic from
 the code of a program.

 This could be done entirely automatically from the types of the functions.


  Let’s try to do it on a simple example, as an exercise:

  f = Map (+1)


  How does this function could be represented?


  It contains the (+) function.

 This function has the type (+) :: Num a = a - a - a.

 From this type we could deduce the graphic:

 [image: Haskell schematic_html_m20060f13.gif]

 Or a curried version:

 [image: Haskell schematic_html_5155f0eb.gif]

 The function (+1) then is:

 [image: Haskell schematic_html_m68795eb7.gif]


  The function map could be drawn like this :

 [image: Haskell schematic_html_m28c92a58.gif]

  Or like this:


 [image: Haskell schematic_html_m6ae433ea.gif]


 And the entire function map (+1) could be represented as:

 [image: Haskell schematic_html_macb1643.gif]



 Thanks to the advanced type system of Haskell, everything could be deduced
 from the type signatures.


  Such a tool would be recreational and educational.

 One could zoom in and out in a program, to display more or less details.

 This could help understand a program, globally or locally.


  We could even imagine a constructive version of the tool, where the
 programmer would draw functions from a toolbox, and stick them into the
 graphic!


  Does a tool approaching this already exist? If not, would it be a good
 project?


  Cheers,

 Corentin



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


Haskell schematic_html_m6ae433ea.gifHaskell schematic_html_5155f0eb.gifHaskell schematic_html_m68795eb7.gifHaskell schematic_html_macb1643.gifHaskell schematic_html_m28c92a58.gifHaskell schematic_html_m20060f13.gif___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Graphical representation of Haskell code

2010-03-22 Thread Ronald Guida
On Mon, Mar 22, 2010 at 7:02 PM, Dupont Corentin
corentin.dup...@gmail.com wrote:
 Hello, I’m relatively new to Haskell.
 I’m wondering if it exist a tool to graphically represent Haskell code.
...
 Let’s try to do it on a simple example, as an exercise:
 f = Map (+1)

Your graphic for f = map (+1) seems much more complex than the
corresponding code.  I would agree with Ivan Miljenovic:
 I'm of the opinion that unless you just use it on small snippets,
 the generated images will be too large and unwieldy.

The first question I would ask is /why/ would you like to visualize
some Haskell code?  If you want to see the high-level structure of
a complex program, try SourceGraph. (I have never used it though.)

On the other hand, if you are trying to visualize Haskell as part of
your efforts to learn the language, then I believe it would be best to
draw diagrams by hand, rather than relying on an automated tool.
The kinds of things that you'll want to depict are probably going to
vary considerably, depending on what you're trying to understand.

Consider a few different implementations of the map function:

  -- version 1: recursion
  map1 :: (a - b) - [a] - [b]
  map1 f [] = []
  map1 f (x:xs) = (f x) : map1 f xs

  -- version 2: fold
  map2 :: (a - b) - [a] - [b]
  map2 f = foldr ((:) . f) []

  -- version 3: continuation passing style
  map3 :: (a - b) - [a] - [b]
  map3 f xs = map' (\x y - f x : y) xs
where
  map' k [] = []
  map' k (y:ys) = k y  (map' k ys)

  -- version 4: list comprehension
  map4 :: (a - b) - [a] - [b]
  map4 f xs = [f x | x - xs]

  -- version 5: list monad
  map5 :: (a - b) - [a] - [b]
  map5 f xs = xs = (return . f)

These all do exactly the same thing, but each one uses different
techniques.  If I'm trying to learn (or teach) Haskell, I would
probably need a slightly different visual language for each one
in order to capture the most relevant concepts in a useful way.
How would you visualize them?

@Mihai Maruseac:
I think a visual debugger would be a wonderful idea.  You may want
to consider how a visual debugger would work with each of these
versions of map.

:-) You might also consider several versions of factorial :-)
http://www.willamette.edu/~fruehr/haskell/evolution.html

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


Re: [Haskell-cafe] which version is in the platform

2010-03-22 Thread Don Stewart
ivan.miljenovic:
 Don Stewart d...@galois.com writes:
  The beta of the 2010.2.0.0 release is now up, which is based on GHC
  6.12.
 
 Hang on, you just announced 2010.1.0.0... have you suddenly released
 _another_ major version? :p
 

2010.1.0.0 is definited as a 'beta' for 2010.2

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