Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Ryan Ingram
Sure, but it's easy to roll your own from those primitives:

{-# LANGUAGE MagicHash, UnboxedTuples #-}
import GHC.Exts

addCarry :: Int - Int - (Int, Bool)
addCarry (I# x) (I# y) = case addIntC# x y of
 (# s, c #) - case c of
 0# - (I# s, False)
 _ - (I# s, True)

or something along those lines.

  -- ryan

On Mon, Jul 30, 2012 at 1:43 PM, Евгений Пермяков permea...@gmail.comwrote:

 On 07/31/2012 12:04 AM, Artyom Kazak wrote:

 Евгений Пермяков permea...@gmail.com писал в своём письме Mon, 30 Jul
 2012 09:47:48 +0300:

  Can someone tell me if there are any primitives, that used to detect
 machine type overflows, in ghc haskell ? I perfectly understand, that I can
 build something based on preconditioning of variables, but this will kill
 any performance, if needed.


 In GHC.Prim -- primitives addIntC# and subIntC#:

  addIntC# :: Int# - Int# - (#Int#, Int##)
 Add with carry. First member of result is (wrapped) sum; second member
 is 0 iff no overflow occured.


  subIntC# :: Int# - Int# - (#Int#, Int##)
 Subtract with carry. First member of result is (wrapped) difference;
 second member is 0 iff no overflow occured.


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

 Still no way to detect overflow in *.

 Strangely enough, I found some relevant descriptions in *.pp in dev
 branch, so I expect them in 7.6.1. They applies to native-size Word and Int
 only.


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] Detecting numeric overflows

2012-07-31 Thread Ryan Ingram
Actually, looking at the docs, I'm not sure if case expressions work on
unboxed ints; you may need

addCarry (I# x) (I# y) = case addIntC# x y of (# s, c #) - (I# s, c /=# 0#)

which is somewhat simpler anyways.

  -- ryan

On Tue, Jul 31, 2012 at 1:56 AM, Ryan Ingram ryani.s...@gmail.com wrote:

 Sure, but it's easy to roll your own from those primitives:

 {-# LANGUAGE MagicHash, UnboxedTuples #-}
 import GHC.Exts

 addCarry :: Int - Int - (Int, Bool)
 addCarry (I# x) (I# y) = case addIntC# x y of
  (# s, c #) - case c of
  0# - (I# s, False)
  _ - (I# s, True)

 or something along those lines.

   -- ryan


 On Mon, Jul 30, 2012 at 1:43 PM, Евгений Пермяков permea...@gmail.comwrote:

 On 07/31/2012 12:04 AM, Artyom Kazak wrote:

 Евгений Пермяков permea...@gmail.com писал в своём письме Mon, 30 Jul
 2012 09:47:48 +0300:

  Can someone tell me if there are any primitives, that used to detect
 machine type overflows, in ghc haskell ? I perfectly understand, that I can
 build something based on preconditioning of variables, but this will kill
 any performance, if needed.


 In GHC.Prim -- primitives addIntC# and subIntC#:

  addIntC# :: Int# - Int# - (#Int#, Int##)
 Add with carry. First member of result is (wrapped) sum; second member
 is 0 iff no overflow occured.


  subIntC# :: Int# - Int# - (#Int#, Int##)
 Subtract with carry. First member of result is (wrapped) difference;
 second member is 0 iff no overflow occured.


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

 Still no way to detect overflow in *.

 Strangely enough, I found some relevant descriptions in *.pp in dev
 branch, so I expect them in 7.6.1. They applies to native-size Word and Int
 only.


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://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] CRIP: the Curiously Reoccuring Instance Pattern

2012-07-31 Thread oleg

Ryan Ingram wrote:
 I've been seeing this pattern in a surprising number of instance
 definitions lately:

 instance (a ~ ar, b ~ br) = Mcomp a ar b br [1]
 instance (b ~ c, CanFilterFunc b a) = CanFilter (b - c) a [2]

And here are a few more earlier instances of the same occurrence:

http://okmij.org/ftp/Haskell/typecast.html

 What I'm wondering is--are there many cases where you really want the
 non-constraint-generating behavior?  It seems like (aside from contrived,
 ahem, instances) whenever you have instance CLASS A B where A and B share
 some type variables, that there aren't any valid instances of the same
 class where they don't share the types in that way.

Instances of the form
class C a b
class C a a
class C a b
are very characteristic of (emulation) of disequality
constraints. Such instances occur, in a hidden form, all the time in
HList -- when checking for membership in a type-level list,
for example. There are naturally two cases: when the sought type is at
the head of the list, or it is (probably) at the tail of the list. 

class Member (h :: *) (t :: List *)
instance Member h (Cons h t)
instance Member h t = Member h (Cons h' t)

Of course instances above are overlapping. And when we add functional
dependencies (since we really want type-functions rather type
relations), they stop working at all. We had to employ work-arounds,
which are described in detail in the HList paper (which is 8 years old
already).



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


[Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alexander Foremny
Hello list,

I am currently thinking that a problem of mine would best be solved if
there was a Map-like data structure in which the value returned is
parametrized over the lookup type.

I wonder is this makes sense and if such a data structure exists or if
it could be created while still being well typed. I essentially want
to statically define a scope of Key values and dynamically define a
list of keys.

 -- Scope of possible keys.
 type Label = String
 data Key a where
 KeyStr :: Label - Key String
 KeyInt :: Label - Key Int
 KeyChoice :: Label - [a] - Key a

 -- Some key values, to be extended at runtime.
 strKey Some String
 strKey' Another String
 intKey Some integer
 choiceKey Chose one [ a, b, c ] :: KeyChoice String

Now I need a data structure to possibly associate a value to the key.

 data MapG = ...
 type Value a = a
 insert :: Key a - Value a - MapG Key Value - MapG Key Value
 lookup :: Key a - MapG Key Value - Maybe (Value a)

I tried implementing this with multiple Map k a's. I tried adding a
phantom type on some storage type of to implement KeyChoice as of type
Key Int, but I ran into troubles with this approach. I wonder if
Dynamic or Type Families could achieve this, but I am quite at a loss
and would like to hear your opinion.

I did try to search for this a bit, but I don't quite know how to
phrase my problem. I'd like to apologize in advance if this question
has been asked already.

Regards,
Alexander Foremny

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


Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Michael Snoyman
On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
alexanderfore...@gmail.com wrote:
 Hello list,

 I am currently thinking that a problem of mine would best be solved if
 there was a Map-like data structure in which the value returned is
 parametrized over the lookup type.

 I wonder is this makes sense and if such a data structure exists or if
 it could be created while still being well typed. I essentially want
 to statically define a scope of Key values and dynamically define a
 list of keys.

 -- Scope of possible keys.
 type Label = String
 data Key a where
 KeyStr :: Label - Key String
 KeyInt :: Label - Key Int
 KeyChoice :: Label - [a] - Key a

 -- Some key values, to be extended at runtime.
 strKey Some String
 strKey' Another String
 intKey Some integer
 choiceKey Chose one [ a, b, c ] :: KeyChoice String

 Now I need a data structure to possibly associate a value to the key.

 data MapG = ...
 type Value a = a
 insert :: Key a - Value a - MapG Key Value - MapG Key Value
 lookup :: Key a - MapG Key Value - Maybe (Value a)

 I tried implementing this with multiple Map k a's. I tried adding a
 phantom type on some storage type of to implement KeyChoice as of type
 Key Int, but I ran into troubles with this approach. I wonder if
 Dynamic or Type Families could achieve this, but I am quite at a loss
 and would like to hear your opinion.

 I did try to search for this a bit, but I don't quite know how to
 phrase my problem. I'd like to apologize in advance if this question
 has been asked already.

 Regards,
 Alexander Foremny

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

I think you might be looking for something like vault[1].

HTH,
Michael

[1] http://hackage.haskell.org/package/vault

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


[Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Sai Hemanth K
Hi,


I am trying to use haskell for building a tool (in a commercial setting).
 I am trying to figure out what all licenses are involved here.
Is there a single license for the entire haskell platform (and the runtime)
or is it that I need to look at the individual licenses of all the
 libraries and tools that make up the platform and point to them separately?

The wikipedia page on haskell platform [0] says Haskell Platform is BSD
licensed. But I do not find any such info elsewhere.
Any pointers on this would be greatly appreciated,

Thanks,
Hemanth K

[0] Haskell platform on wikipedia :
http://en.wikipedia.org/wiki/Haskell_Platform
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alexander Foremny
Dear Michael,

thank you very much for your quick and interesting response. This
looks very much like what I want!

Regards,
Alexander Foremny

2012/7/31 Michael Snoyman mich...@snoyman.com:
 On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
 alexanderfore...@gmail.com wrote:
 Hello list,

 I am currently thinking that a problem of mine would best be solved if
 there was a Map-like data structure in which the value returned is
 parametrized over the lookup type.

 I wonder is this makes sense and if such a data structure exists or if
 it could be created while still being well typed. I essentially want
 to statically define a scope of Key values and dynamically define a
 list of keys.

 -- Scope of possible keys.
 type Label = String
 data Key a where
 KeyStr :: Label - Key String
 KeyInt :: Label - Key Int
 KeyChoice :: Label - [a] - Key a

 -- Some key values, to be extended at runtime.
 strKey Some String
 strKey' Another String
 intKey Some integer
 choiceKey Chose one [ a, b, c ] :: KeyChoice String

 Now I need a data structure to possibly associate a value to the key.

 data MapG = ...
 type Value a = a
 insert :: Key a - Value a - MapG Key Value - MapG Key Value
 lookup :: Key a - MapG Key Value - Maybe (Value a)

 I tried implementing this with multiple Map k a's. I tried adding a
 phantom type on some storage type of to implement KeyChoice as of type
 Key Int, but I ran into troubles with this approach. I wonder if
 Dynamic or Type Families could achieve this, but I am quite at a loss
 and would like to hear your opinion.

 I did try to search for this a bit, but I don't quite know how to
 phrase my problem. I'd like to apologize in advance if this question
 has been asked already.

 Regards,
 Alexander Foremny

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

 I think you might be looking for something like vault[1].

 HTH,
 Michael

 [1] http://hackage.haskell.org/package/vault

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


Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alexander Foremny
At first glance I noticed some problems with the vault library for my
particular approach.

Despite from being unique, Key values don't appear to carry any
information like the Label I need. However, it might be possible to
work around that.

The more grave problem seems to be that a Key cannot be
(de-)serialized. This might be impossible due to the type parameter a
in Key a.
However, it is no problem to fix the types of values to some finite collection.

Because of this some solution built around Dynamic seems to be more
and more appropriate. But I'll try to investigate vault further.

Regards,
Alexander Foremny

2012/7/31 Alexander Foremny alexanderfore...@gmail.com:
 Dear Michael,

 thank you very much for your quick and interesting response. This
 looks very much like what I want!

 Regards,
 Alexander Foremny

 2012/7/31 Michael Snoyman mich...@snoyman.com:
 On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
 alexanderfore...@gmail.com wrote:
 Hello list,

 I am currently thinking that a problem of mine would best be solved if
 there was a Map-like data structure in which the value returned is
 parametrized over the lookup type.

 I wonder is this makes sense and if such a data structure exists or if
 it could be created while still being well typed. I essentially want
 to statically define a scope of Key values and dynamically define a
 list of keys.

 -- Scope of possible keys.
 type Label = String
 data Key a where
 KeyStr :: Label - Key String
 KeyInt :: Label - Key Int
 KeyChoice :: Label - [a] - Key a

 -- Some key values, to be extended at runtime.
 strKey Some String
 strKey' Another String
 intKey Some integer
 choiceKey Chose one [ a, b, c ] :: KeyChoice String

 Now I need a data structure to possibly associate a value to the key.

 data MapG = ...
 type Value a = a
 insert :: Key a - Value a - MapG Key Value - MapG Key Value
 lookup :: Key a - MapG Key Value - Maybe (Value a)

 I tried implementing this with multiple Map k a's. I tried adding a
 phantom type on some storage type of to implement KeyChoice as of type
 Key Int, but I ran into troubles with this approach. I wonder if
 Dynamic or Type Families could achieve this, but I am quite at a loss
 and would like to hear your opinion.

 I did try to search for this a bit, but I don't quite know how to
 phrase my problem. I'd like to apologize in advance if this question
 has been asked already.

 Regards,
 Alexander Foremny

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

 I think you might be looking for something like vault[1].

 HTH,
 Michael

 [1] http://hackage.haskell.org/package/vault

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


Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-31 Thread Richard Cobbe
On Mon, Jul 30, 2012 at 11:45:38PM +1000, Ivan Lazar Miljenovic wrote:
 On 30 July 2012 04:04, Richard Cobbe co...@ccs.neu.edu wrote:
  I'm working on an application that involves processing a lot of Unicode
  data, and I'm finding the built-in Show implementation for Char to be
  really inconvenient.  Specifically, it renders all characters at U+0080 and
  above with decimal escapes:
 
  Prelude '\x80'
  '\128'
 
  This is annoying because all of the Unicode charts give the code points in
  hex, and indeed the charts are split into different PDFs at numbers that
  are nice and round in hex but not in decimal.  So in order to figure out
  which character I'm looking at, I have to convert back to hex and then look
  it up in the charts.

 Can I ask what you're doing here? Are you printing individual
 characters or entire chunks of text?

Mostly, I'm working with expressions of type String, rather than Text; the
Char above was merely an example to demonstrate the problem.  The two I/O
cases that most concern me are evaluating a String expression at the GHCi
REPL, and working with HUnit test cases built around String expressions.

I suppose I could wrap putStrLn around all string exprs at the repl, but a)
that's a pain; b) it's important for this app that I be able to distinguish
between precomposed characters and combining characters; and c) some of the
characters I'm dealing with are very similar in my terminal fonts, such as
U+1F00 and U+1F01.  It's much nicer to be able to just see the code points.

The other problem is with HUnit tests.  When a test fails (under runTestTT,
anyway) you get a diagnostic printed to stdout.  I'm not sure exactly what
logic HUnit uses to produce these error messages, but it's almost certainly
calling 'show' on the underlying strings.  So there's no place, as far as I
know, where I can insert a call to putStrLn.

Richard

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


Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Magnus Therning
On Tue, Jul 31, 2012 at 12:29 PM, Sai Hemanth K saihema...@gmail.com wrote:
 Hi,


 I am trying to use haskell for building a tool (in a commercial setting).  I
 am trying to figure out what all licenses are involved here.
 Is there a single license for the entire haskell platform (and the runtime)
 or is it that I need to look at the individual licenses of all the
 libraries and tools that make up the platform and point to them separately?

 The wikipedia page on haskell platform [0] says Haskell Platform is BSD
 licensed. But I do not find any such info elsewhere.
 Any pointers on this would be greatly appreciated,

A quick search suggests that this still hasn't been decided:

http://trac.haskell.org/haskell-platform/ticket/85
http://trac.haskell.org/haskell-platform/wiki/AddingPackages#Interimlicensepolicy

I believe it still holds that all packages included in
haskell-platform are BSD3 licensed.

/M

-- 
Magnus Therning  OpenPGP: 0xAB4DFBA4
email: mag...@therning.org   jabber: mag...@therning.org
twitter: magthe   http://therning.org/magnus

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


Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-31 Thread Ivan Lazar Miljenovic
On 31 July 2012 21:01, Richard Cobbe co...@ccs.neu.edu wrote:
 On Mon, Jul 30, 2012 at 11:45:38PM +1000, Ivan Lazar Miljenovic wrote:
 On 30 July 2012 04:04, Richard Cobbe co...@ccs.neu.edu wrote:
  I'm working on an application that involves processing a lot of Unicode
  data, and I'm finding the built-in Show implementation for Char to be
  really inconvenient.  Specifically, it renders all characters at U+0080 and
  above with decimal escapes:
 
  Prelude '\x80'
  '\128'
 
  This is annoying because all of the Unicode charts give the code points in
  hex, and indeed the charts are split into different PDFs at numbers that
  are nice and round in hex but not in decimal.  So in order to figure out
  which character I'm looking at, I have to convert back to hex and then look
  it up in the charts.

 Can I ask what you're doing here? Are you printing individual
 characters or entire chunks of text?

 Mostly, I'm working with expressions of type String, rather than Text;

Any particular reason why?  Using Text will probably solve your
problem and give you a performance improvement at the same time.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-31 Thread Henk-Jan van Tuyl

On Tue, 31 Jul 2012 00:42:40 +0200, timothyho...@seznam.cz wrote:

On a side note, image based CAPACHA's can cause problems for blind  
people.


Googles ReCaptcha can pronounce the text to type.

Regards,
Henk-Jan van Tuyl


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


Re: [Haskell-cafe] What does unpacking an MVar really mean?

2012-07-31 Thread Bertram Felgenhauer
Leon Smith wrote:
 I am familiar with the source of Control.Concurrent.MVar,  and I do see {-#
 UNPACK #-}'ed MVars around,  for example in GHC's IO manager. What I
 should have asked is,  what does an MVar# look like?  This cannot be
 inferred from Haskell source;  though I suppose I could have tried to read
 the Runtime source.

So let's have a brief look at the source. MVar# is an RTS specific
heap object which contains three pointers:

(from ghc/includes/rts/storage/Closures.h)

typedef struct {
StgHeaderheader;
struct StgMVarTSOQueue_ *head;
struct StgMVarTSOQueue_ *tail;
StgClosure*  value;
} StgMVar;

The 'value' pointer refers to the actual value held by the mutable
variable, if any. The 'head' and 'tail' pointers are used for
managing a linked list of threads blocked on the mutable variable.

An MVar (if evaluated) contains just a pointer the MVar# object.

To access the value of an MVar, one starts with a pointer to the MVar
heap object. Then,

  1. Make sure that the MVar is evaluated, using standard lazy
 evaluation (follow indirections, enter thunks, ...).

 In the best case that's a check of a tag bit in the pointer.

  2. Read the pointer to the MVar# in the MVar.

  3. access the 'value' field of the StgMVar record, which
 results in another pointer to a heap object representing
 the actual data held by the MVar.

 (In reality the code has to check whether the MVar is full
 or not, and block if necessary. This is quite involved; see
 stg_takeMVarzh  in  ghc/rts/PrimOps.cmm)

That's two dereferences and some bookkeeping work.

In loops, the compiler will often unpack the MVar, so that you can
expect the first two steps to be performed just once.

Unpacking an MVar into a bigger record means that the pointer to the
MVar# will be stored in the record directly, rather than a pointer
to an MVar object that holds a pointer to the MVar#.

Note that MVar# itself cannot be unpacked -- the StgMVar record will
always be a separate heap object.

 I was asking the dual question:  if the MVar# exists in some data
 structure,  can that data structure still be garbage collected when there
 is a reference to the MVar#,  but not the data structure it is contained
 within.

Yes, because the data structure only contains a pointer to an MVar#
(StgMVar record) that will live on.

Best regards,

Bertram

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


Re: [Haskell-cafe] [Haskell] Spam on the Haskell wiki

2012-07-31 Thread Henk-Jan van Tuyl
On Tue, 31 Jul 2012 00:59:28 +0200, Alexander Solla alex.so...@gmail.com  
wrote:



Does anybody have statistics about how often pages are edited/added?


In the last seven days, there were 251 new (user)pages created; there was  
no spam added to existing pages.


I also discovered spam added to pages at  
http://hackage.haskell.org/trac/hackage/
A search for rio bouygues[0] gave 118 results, virgin mobile gave 124  
results; there are probably more.


Regards,
Henk-Jan van Tuyl


[0]  
http://hackage.haskell.org/trac/hackage/search?q=%22rio+bouygues%22noquickjump=1ticket=onmilestone=onwiki=on


--
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--

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


Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Sai Hemanth K
Thanks Magnus.
I guess it means that the license of individual packages is what
that matters.
The platform on the whole does not have any single license.

In other words, I cannot just say that am using haskell platform but that I
have to say, I am using x,y and z libraries which in turn are using a, b, c
and d libraries.


 A quick search suggests that ..:
Ouch! Apologies. Guess I was looking at all the wrong places or my
google-fu is embarrassingly bad.



Thanks again for the links!

Hemanth K


On Tue, Jul 31, 2012 at 4:41 PM, Magnus Therning mag...@therning.orgwrote:

 On Tue, Jul 31, 2012 at 12:29 PM, Sai Hemanth K saihema...@gmail.com
 wrote:
  Hi,
 
 
  I am trying to use haskell for building a tool (in a commercial
 setting).  I
  am trying to figure out what all licenses are involved here.
  Is there a single license for the entire haskell platform (and the
 runtime)
  or is it that I need to look at the individual licenses of all the
  libraries and tools that make up the platform and point to them
 separately?
 
  The wikipedia page on haskell platform [0] says Haskell Platform is BSD
  licensed. But I do not find any such info elsewhere.
  Any pointers on this would be greatly appreciated,

 A quick search suggests that this still hasn't been decided:

 http://trac.haskell.org/haskell-platform/ticket/85

 http://trac.haskell.org/haskell-platform/wiki/AddingPackages#Interimlicensepolicy

 I believe it still holds that all packages included in
 haskell-platform are BSD3 licensed.

 /M

 --
 Magnus Therning  OpenPGP: 0xAB4DFBA4
 email: mag...@therning.org   jabber: mag...@therning.org
 twitter: magthe   http://therning.org/magnus




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


Re: [Haskell-cafe] specifying using type class

2012-07-31 Thread Patrick Browne
Hi,Thanks for all the very useful feed back on this thread.I would like to present my possibly incorrect summarized  view:Class signatures can contain placeholders for constructors.These place-holder-constructors cannot be used in the class to define functions (I assume other in-scope constructors can be used). In the instance a real constructor can be substituted for the place-holder-constructor.Does this restrict the type of equation that can be used in a type class? It seems that some equations respecting the constructor discipline are not allowed.I appreciate that in Haskell the most equations occur in the instances, but from my earlier post: I merely wish to identify the strengths and weakness of *current Haskell type classes* as a pure *unit of specification* Is my summarized view is correct?Regards,Pat On 31/07/12, Ryan Ingram  ryani.s...@gmail.com wrote:Generally the way this is done in Haskell is that the interface to the type is specified in a typeclass (or, alternatively, in a module export list, for concrete types), and the axioms are specified in a method to be tested in some framework (i.e. QuickCheck, SmallCheck, SmartCheck) which can automatically generate instances of your type and test that the axioms hold.
For example:class QueueLike q where    empty :: q a    insert :: a - q a - q a    viewFirst :: q a - Maybe (a, q a)    size :: q a - Integer-- can use a single proxy type if have kind polymorphism, but that's an experimental feature right now
data Proxy2 (q :: * - *) = Proxy2instance Arbitrary (Proxy2 q) where arbitrary = return Proxy2prop_insertIncrementsSize :: forall q. QueueLike q = q () - Boolprop_insertIncrementsSize q = size (insert () q) == size q + 1
prop_emptyQueueIsEmpty :: forall q. QueueLike q = Proxy2 q = Boolprop_emptyQueueIsEmpty Proxy2 = maybe True (const False) $ view (empty :: q ())Then you specialize these properties to your type and test them:
instance QueueLike [] where ...ghci quickCheck (prop_insertIncrementsSize :: [()] - Bool)Valid, passed 100 testsorFailed with: [(), (), ()]QuickCheck randomly generates objects of your data structure and tests your property against them.  While not as strong as a proof, programs with 100% quickcheck coverage are *extremely* reliable.  SmartCheck is an extension of QuickCheck that tries to reduce test cases to the minimum failing size.
SmallCheck does exhaustive testing on the properties for finite data structures up to a particular size.  It's quite useful when you can prove your algorithms 'generalize' after a particular point.
There aren't any libraries that I know of for dependent-type style program proof for haskell; I'm not sure it's possible.  The systems I know of have you program in a more strongly typed language (Coq/agda) and export Haskell programs once they are proven safe.  Many of these rely on unsafeCoerce in the Haskell code because they have proven stronger properties about the types than Haskell can; I look at that code with some trepidation--I am not sure what guarantees the compiler makes about unsafeCoerce.
  -- ryanOn Sun, Jul 22, 2012 at 7:19 AM, Patrick Browne patrick.bro...@dit.ie patrick.bro...@dit.ie wrote:
{-Below is a *specification* of a queue. If possible I would like to write the equations in type class.Does the type class need two type variables? How do I represent the constructors?Can the equations be written in the type class rather than the instance?
-}module QUEUE_SPEC wheredata Queue e   = New | Insert (Queue e) e deriving ShowisEmpty :: Queue  e  - BoolisEmpty  New  = True isEmpty (Insert q e) = False first :: Queue  e  - e
first (Insert q e) =  if (isEmpty q) then e else (first q) rest :: Queue  e  - Queue  erest (Insert  q e ) = if (isEmpty q) then New  else (Insert (rest q) e)size :: Queue  e  - Int
size New  = 0 size (Insert q e) = succ (size q){- some tests of above codesize (Insert (Insert (Insert New 5) 6) 3)rest (Insert (Insert (Insert New 5) 6) 3)My first stab at a classclass QUEUE_SPEC q e where
 new :: q e insert :: q e - q e isEmpty :: q  e  - Bool first :: q  e  - e rest :: q  e  - q e size :: q e  - Int-}
 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie


This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean.  http://www.dit.ie



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


 Tá an teachtaireacht seo scanta ó thaobh ábhar agus víreas ag Seirbhís Scanta Ríomhphost de chuid Seirbhísí Faisnéise, ITBÁC agus meastar í a bheith slán.  http://www.dit.ie
This message has been scanned for content and viruses by the DIT Information Services E-Mail Scanning Service, and is believed to be clean.  http://www.dit.ie




Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread Alp Mestanogullari
Would ixset or HiggsSet be suitable?

http://hackage.haskell.org/package/ixsethttp://hackage.haskell.org/package/ixset-1.0.5
http://hackage.haskell.org/package/HiggsSet

On Tue, Jul 31, 2012 at 12:56 PM, Alexander Foremny 
alexanderfore...@gmail.com wrote:

 At first glance I noticed some problems with the vault library for my
 particular approach.

 Despite from being unique, Key values don't appear to carry any
 information like the Label I need. However, it might be possible to
 work around that.

 The more grave problem seems to be that a Key cannot be
 (de-)serialized. This might be impossible due to the type parameter a
 in Key a.
 However, it is no problem to fix the types of values to some finite
 collection.

 Because of this some solution built around Dynamic seems to be more
 and more appropriate. But I'll try to investigate vault further.

 Regards,
 Alexander Foremny

 2012/7/31 Alexander Foremny alexanderfore...@gmail.com:
  Dear Michael,
 
  thank you very much for your quick and interesting response. This
  looks very much like what I want!
 
  Regards,
  Alexander Foremny
 
  2012/7/31 Michael Snoyman mich...@snoyman.com:
  On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
  alexanderfore...@gmail.com wrote:
  Hello list,
 
  I am currently thinking that a problem of mine would best be solved if
  there was a Map-like data structure in which the value returned is
  parametrized over the lookup type.
 
  I wonder is this makes sense and if such a data structure exists or if
  it could be created while still being well typed. I essentially want
  to statically define a scope of Key values and dynamically define a
  list of keys.
 
  -- Scope of possible keys.
  type Label = String
  data Key a where
  KeyStr :: Label - Key String
  KeyInt :: Label - Key Int
  KeyChoice :: Label - [a] - Key a
 
  -- Some key values, to be extended at runtime.
  strKey Some String
  strKey' Another String
  intKey Some integer
  choiceKey Chose one [ a, b, c ] :: KeyChoice String
 
  Now I need a data structure to possibly associate a value to the key.
 
  data MapG = ...
  type Value a = a
  insert :: Key a - Value a - MapG Key Value - MapG Key Value
  lookup :: Key a - MapG Key Value - Maybe (Value a)
 
  I tried implementing this with multiple Map k a's. I tried adding a
  phantom type on some storage type of to implement KeyChoice as of type
  Key Int, but I ran into troubles with this approach. I wonder if
  Dynamic or Type Families could achieve this, but I am quite at a loss
  and would like to hear your opinion.
 
  I did try to search for this a bit, but I don't quite know how to
  phrase my problem. I'd like to apologize in advance if this question
  has been asked already.
 
  Regards,
  Alexander Foremny
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
  I think you might be looking for something like vault[1].
 
  HTH,
  Michael
 
  [1] http://hackage.haskell.org/package/vault

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




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


Re: [Haskell-cafe] Key-Parametrized Lookup Table

2012-07-31 Thread James Cook
Another option which allows you to define your own key type is the 
dependent-map[1] package.  It requires implementing some classes for your key 
type that encode a proof that key equality entails equality of the type 
indices. If the documentation is insufficient feel free to ask me for more 
details or examples.

[1] http://hackage.haskell.org/package/dependent-map

On Jul 31, 2012, at 6:56 AM, Alexander Foremny alexanderfore...@gmail.com 
wrote:

 At first glance I noticed some problems with the vault library for my
 particular approach.
 
 Despite from being unique, Key values don't appear to carry any
 information like the Label I need. However, it might be possible to
 work around that.
 
 The more grave problem seems to be that a Key cannot be
 (de-)serialized. This might be impossible due to the type parameter a
 in Key a.
 However, it is no problem to fix the types of values to some finite 
 collection.
 
 Because of this some solution built around Dynamic seems to be more
 and more appropriate. But I'll try to investigate vault further.
 
 Regards,
 Alexander Foremny
 
 2012/7/31 Alexander Foremny alexanderfore...@gmail.com:
 Dear Michael,
 
 thank you very much for your quick and interesting response. This
 looks very much like what I want!
 
 Regards,
 Alexander Foremny
 
 2012/7/31 Michael Snoyman mich...@snoyman.com:
 On Tue, Jul 31, 2012 at 1:13 PM, Alexander Foremny
 alexanderfore...@gmail.com wrote:
 Hello list,
 
 I am currently thinking that a problem of mine would best be solved if
 there was a Map-like data structure in which the value returned is
 parametrized over the lookup type.
 
 I wonder is this makes sense and if such a data structure exists or if
 it could be created while still being well typed. I essentially want
 to statically define a scope of Key values and dynamically define a
 list of keys.
 
 -- Scope of possible keys.
 type Label = String
 data Key a where
KeyStr :: Label - Key String
KeyInt :: Label - Key Int
KeyChoice :: Label - [a] - Key a
 
 -- Some key values, to be extended at runtime.
 strKey Some String
 strKey' Another String
 intKey Some integer
 choiceKey Chose one [ a, b, c ] :: KeyChoice String
 
 Now I need a data structure to possibly associate a value to the key.
 
 data MapG = ...
 type Value a = a
 insert :: Key a - Value a - MapG Key Value - MapG Key Value
 lookup :: Key a - MapG Key Value - Maybe (Value a)
 
 I tried implementing this with multiple Map k a's. I tried adding a
 phantom type on some storage type of to implement KeyChoice as of type
 Key Int, but I ran into troubles with this approach. I wonder if
 Dynamic or Type Families could achieve this, but I am quite at a loss
 and would like to hear your opinion.
 
 I did try to search for this a bit, but I don't quite know how to
 phrase my problem. I'd like to apologize in advance if this question
 has been asked already.
 
 Regards,
 Alexander Foremny
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 I think you might be looking for something like vault[1].
 
 HTH,
 Michael
 
 [1] http://hackage.haskell.org/package/vault
 
 ___
 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] How to define a Monad instance

2012-07-31 Thread Thiago Negri
Thanks for the reply Ryan.

That's exactly the type of thing I was trying to do: use the
syntactical sugar of do-notation to express some replacement rules.

Why am I doing this?

A long time ago, when I was learning C, I did a small project
(spaghetti code) to encrypt text files in some user-defined language.
It supported exact replacement (char - char) and some other stuff
that I called sessions of encryption and masked string replacement.

The sessions can be turned on or off at the same time of matching a
char, e.g. the user could define that when the char 'a' was matched
inside the session foo, it will change it to a 'b', turn off the
session foo and turn on the sessions bar and baz.

So, I'm trying to create a similar thing in Haskell.

In my view, it fits in the Monad class, as I'm doing pattern matching
and replacing at the same time as sequencing other things like
changing the state of the replacement machine.

The char-to-char replacement is the first step.

I'll try your exercises later, when I get home.

Thanks,
Thiago.

2012/7/31 Ryan Ingram ryani.s...@gmail.com:
 A couple typos:

 instance Monad Replacer1 where
 -
 instance Monad (Replacer1 k) where


 instance Monad Replacer2 k where
 -
 instance Monad (Replacer2 k) where

 I haven't tested any of this code, so you may have to fix some minor type
 errors.


 On Mon, Jul 30, 2012 at 10:38 PM, Ryan Ingram ryani.s...@gmail.com wrote:

 To take this a step further, if what you really want is the syntax sugar
 for do-notation (and I understand that, I love sweet, sweet syntactical
 sugar), you are probably implementing a Writer monad over some monoid.

 Here's two data structures that can encode this type;

 data Replacer1 k a = Replacer1 (k - Maybe k) a
 data Replacer2 k a = Replacer2 [(k,k)] a

 instance Monad Replacer1 where
 return x = Replacer1 (\_ - Nothing) x
 Replacer1 ka a = f = result where
 Replacer1 kb b = f a
 result = Replacer1 (\x - ka x `mplus` kb x) b

 (!) :: Eq k = k - k - Replacer1 k ()
 x ! y = Replacer1 (\k - if k == x then Just y else Nothing) ()

 replace1 :: Replacer1 k () - [k] - [k]-- look ma, no Eq requirement!
 replace1 (Replacer k ()) = map (\x - fromMaybe x $ k x) -- from
 Data.Maybe

 table1 :: Replacer1 Char ()
 table1 = do
 'a' ! 'b'
 'A' ! 'B'

 test = replace1 table1 All I want

 -- Exercise: what changes if we switch ka and kb in the result of (=)?
 When does it matter?

 -- Exercises for you to implement:
 instance Monad Replacer2 k where
 replacer :: Eq k = Replacer2 k - [k] - [k]
 ($) :: k - k - Replacer2 k

 -- Exercise: Lets make use of the fact that we're a monad!
 --
 -- What if the operator ! had a different type?
 -- (!) :: Eq k = k - k - Replacer k Integer
 -- which returns the count of replacements done.
 --
 -- table3 = do
 -- count - 'a' ! 'b'
 -- when (count  3) ('A' ! 'B')
 -- return ()
 --
 -- Do any of the data structures I've given work?  Why or why not?
 -- Can you come up with a way to implement this?

   -- ryan


 On Sat, Jul 28, 2012 at 10:07 AM, Steffen Schuldenzucker
 sschuldenzuc...@uni-bonn.de wrote:

 On 07/28/2012 03:35 PM, Thiago Negri wrote:
  [...]

 As Monads are used for sequencing, first thing I did was to define the
 following data type:

 data TableDefinition a = Match a a (TableDefinition a) | Restart


 So TableDefinition a is like [(a, a)].

 [...]

 

 So, to create a replacement table:

 table' :: TableDefinition Char
 table' =
  Match 'a' 'b'
  (Match 'A' 'B'
   Restart)

 It look like a Monad (for me), as I can sequence any number of
 replacement values:

 table'' :: TableDefinition Char
 table'' = Match 'a' 'c'
   (Match 'c' 'a'
   (Match 'b' 'e'
   (Match 'e' 'b'
Restart)))


 Yes, but monads aren't just about sequencing. I like to see a monad as a
 generalized computation (e.g. nondeterministic, involving IO, involving
 state etc). Therefore, you should ask yourself if TableDefinition can be
 seen as some kind of abstract computation. In particular, can you
 execute a computation and extract its result? as in

   do
 r - Match 'a' 'c' Restart
 if r == 'y' then Restart else Match 2 3 (Match 3 4 Restart)

 Doesn't immediately make sense to me. In particular think about the
 different possible result types of a TableDefinition computation.

 If all you want is sequencing, you might be looking for a Monoid instance
 instead, corresponding to the Monoid instance of [b], where b=(a,a) here.

  [...]

 

 I'd like to define the same data structure as:

 newTable :: TableDefinition Char
 newTable = do
  'a' :  'b'
  'A' :  'B'

 But I can't figure a way to define a Monad instance for that. :(


 The desugaring of the example looks like this:

   ('a' : 'b')  ('A' : 'B')

 Only () is used, but not (=) (i.e. results are always discarded). If
 this is the only case that makes sense, you're probably looking for a Monoid
 instead (see above)

 -- 

[Haskell-cafe] IMAGE_FILE_LARGE_ADDRESS_AWARE (4GB on Win64) ... any best practices??

2012-07-31 Thread Nick Rudnick
Dear Haskellers,

did anybody of you stumble about surprisingly having a 2GB memory limit on
Win64? I admit I didn't get it at once (just about to finish a complete
memcheck... ;-) -- but of course there already is a discussion of this:


http://stackoverflow.com/questions/10743041/making-use-of-all-available-ram-in-a-haskell-program

Unfortunately, this left me a little stupid about how to actually get a
program running with IMAGE_FILE_LARGE_ADDRESS_AWARE -- did anybody try this
successfully (or even not...) and has experience to share?

Usually a Linuxer, I am just about to begin exploring the possibilities of
Haskell on Windows, please forgive.

Thanks a lot advance, Nick
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] What does unpacking an MVar really mean?

2012-07-31 Thread Leon Smith
On Tue, Jul 31, 2012 at 7:37 AM, Bertram Felgenhauer 
bertram.felgenha...@googlemail.com wrote:

 Note that MVar# itself cannot be unpacked -- the StgMVar record will
 always be a separate heap object.


One could imagine a couple of techniques to unpack the MVar# itself,  and
was curious if GHC might employ one of them.

So, really,  unpacking the MVar does not eliminate a layer of indirection,
 it just eliminates the need to check a pointer tag (and possibly execute a
thunk or follow some redirects if you don't have a pointer to an MVar#).
 I think this is what I was ultimately after.

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


[Haskell-cafe] ANN: stm-sbchan-0.1 - STM channel with maximum total size of items

2012-07-31 Thread Joey Adams
This package provides a bounded channel type for STM.  TBChan (in
stm-chans) and TBQueue (introduced in stm 2.4) are bounded channels
that limit the number of items in the channel.  SBChan, on the other
hand, limits the total size of items in the channel, where size is
defined by providing an instance of the ItemSize class:

data Entry = Entry Int64 ByteString Time

-- | Estimated amount of memory an 'Entry' requires,
-- including channel overhead
instance ItemSize Entry where
itemSize (Entry _ s _) = B.length s + 200

Then, SBChan Entry is a channel that limits (approximately) the
amount of memory the entries take up.

SBChan can also be used as a regular count-bounded channel by using
the SBCItem newtype wrapper, where itemSize is always 1.

http://hackage.haskell.org/package/stm-sbchan

Enjoy!
-Joey

--- Implementation details ---

itemSize returns an Int.  I originally considered using an associated
type, so users could pick their own number type to use.  However, this
would have made the implementation harder to reason about, if we had
to worry about the user picking an ill-behaved number type like Float.
 Besides, Int is usually adequate for representing in-memory sizes.

This library takes a lot of ideas from TChan and TBChan.  I decided to
use the linked list of TVars approach that TChan uses, rather than the
pair of lists approach T(B)Queue uses, to avoid a potential problem
with code like this:

msg - readTBQueue
case msg of
Foo - ...
Bar - ...

If the transaction is repeated a lot due to retries or invalidation,
and readTBQueue needs to turn around the list at this point, then
we'll end up repeating O(n) work a bunch of times.

SBChan uses stm-tlist, a library I wrote that is based on TChan's
internal representation.  Also, SBChan uses the usual trick for
reducing reader-writer contention by having two counters for capacity,
one for readers and one for writers.

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


[Haskell-cafe] Explicit forall - Strange Error

2012-07-31 Thread Shayan Najd Javadipour
Hi,

I wonder why the following code doesn't typecheck in GHC 7.4.1:

{-# LANGUAGE GADTs,RankNTypes #-}data T a where T1 :: (forall b. b -
b) - (forall a. Int - T a)
{- Error:
Data constructor `T1' returns type `forall a. Int - T a'
  instead of an instance of its parent type `T a'
In the definition of data constructor `T1'
In the data type declaration for `T'
Failed, modules loaded: none. -}
While:


{-# LANGUAGE GADTs,RankNTypes #-}
f :: (forall b. b - b) - (forall a. Int - Maybe a)f = undefined
{-
ghci :t f
f :: (forall b. b - b) - Int - Maybe a
-}


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


Re: [Haskell-cafe] Detecting numeric overflows

2012-07-31 Thread Andres Löh
Hi.

On Mon, Jul 30, 2012 at 8:47 AM, Евгений Пермяков permea...@gmail.com wrote:
 Can someone tell me if there are any primitives, that used to detect machine
 type overflows, in ghc haskell ? I perfectly understand, that I can build
 something based on preconditioning of variables, but this will kill any
 performance, if needed.

There's

  http://hackage.haskell.org/package/safeint/

It's not implemented quite as efficiently as it theoretically could
be, but it might do more or less what you want.

Cheers,
  Andres

-- 
Andres Löh, 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


Re: [Haskell-cafe] Explicit forall - Strange Error

2012-07-31 Thread MigMit
It really seems to me that the error message you've got explains everything 
quite clear.

Отправлено с iPad

31.07.2012, в 22:59, Shayan Najd Javadipour sh.n...@gmail.com написал(а):

 Hi, 
 
 I wonder why the following code doesn't typecheck in GHC 7.4.1:
 
 {-# LANGUAGE GADTs,RankNTypes #-}
 data T a where T1 :: (forall b. b - b) - (forall a. Int - T a)
 
 {- Error:
 Data constructor `T1' returns type `forall a. Int - T a'
   instead of an instance of its parent type `T a'
 In the definition of data constructor `T1'
 In the data type declaration for `T'
 Failed, modules loaded: none. -}
 
 While:
 
 {-# LANGUAGE GADTs,RankNTypes #-}
 
 f :: (forall b. b - b) - (forall a. Int - Maybe a)
 f = undefined
 
 {- 
 ghci :t f
 f :: (forall b. b - b) - Int - Maybe a
 -} 
 
 Thanks, 
  Shayan
 ___
 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] Explicit forall - Strange Error

2012-07-31 Thread Shayan Najd Javadipour
If GHC handles the explicit forall in constructor T1 in the same way as
it does for function f, we have:

data T a where T1 :: (forall b. b - b) - Int - T a


Which is totally fine! The main question is then why the foralls are
handled differently?

On Tue, Jul 31, 2012 at 9:07 PM, MigMit miguelim...@yandex.ru wrote:

 It really seems to me that the error message you've got explains
 everything quite clear.

 Отправлено с iPad

 31.07.2012, в 22:59, Shayan Najd Javadipour sh.n...@gmail.com
 написал(а):

 Hi,

 I wonder why the following code doesn't typecheck in GHC 7.4.1:

 {-# LANGUAGE GADTs,RankNTypes #-}data T a where T1 :: (forall b. b - b) - 
 (forall a. Int - T a)
 {- Error:
 Data constructor `T1' returns type `forall a. Int - T a'
   instead of an instance of its parent type `T a'
 In the definition of data constructor `T1'
 In the data type declaration for `T'
 Failed, modules loaded: none. -}
 While:


 {-# LANGUAGE GADTs,RankNTypes #-}
 f :: (forall b. b - b) - (forall a. Int - Maybe a)f = undefined
 {-
 ghci :t f
 f :: (forall b. b - b) - Int - Maybe a
 -}


 Thanks,
  Shayan

 ___
 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] Explicit forall - Strange Error

2012-07-31 Thread Brandon Allbery
On Tue, Jul 31, 2012 at 2:59 PM, Shayan Najd Javadipour
sh.n...@gmail.comwrote:

 {-# LANGUAGE GADTs,RankNTypes #-}data T a where T1 :: (forall b. b - b) - 
 (forall a. Int - T a)
 {- Error:
 Data constructor `T1' returns type `forall a. Int - T a'
   instead of an instance of its parent type `T a'


This looks to me like other cases where GHC requires an exact type match
even though you used something equivalent.  Similarly, for example, it
rejects (contrived example)

foo :: Num a = a - a - a
foo 0 0 = -1
foo = (+)

because the explicit arity of the cases must match exactly, even though
(+)'s type matches the required arity.  I am under the impression that it's
difficult to make those kinds of things work nicely in the typechecker.

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Reddy on Referential Transparency

2012-07-31 Thread Chris Dornan
Uday Reddy has followed up with another substantial and interesting post on 
referential transparency here:


http://stackoverflow.com/questions/210835/what-is-referential-transparency/11740176#11740176

The thrust of his argument appears to be that functional programmers have 
created a lot of confusion around the ideas of referential transparency. I 
sympathize but I think he is going too far. 

As I see it, while the very close association of functional programming and 
related concepts with referential transparency may have led to some confusion 
around the concept that doesn't mean that the specific means that functional 
programmers have been using to increase (classically understood) RT in 
functional programs is somehow invalid.

Reddy has responded to my comment here

http://stackoverflow.com/a/11680011/306550

and I have followed up in turn.

Chris


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


Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Carter Schonwald
it looks like ghc itself is under a BSD3 style license, if thats any help.
So per se, I think you can assume youre dealing with a BSD3 through and
through system.

see here for the ghc info
http://www.haskell.org/ghc/license

(this is something i've been sorting out for my own projects too, and to
the best of my knowledge its all bsd3)

admission: I'm actually likely to be providing a repackaging of ghc  the
haskell platform with some additional tools for data analysis / machine
learning to some enterprise customers come the fall, so thats why I have
any thoughts on this matter. (but bear in mind that folks are this list
aren't lawyers :) )

On Tue, Jul 31, 2012 at 7:46 AM, Sai Hemanth K saihema...@gmail.com wrote:

 Thanks Magnus.
 I guess it means that the license of individual packages is what
 that matters.
 The platform on the whole does not have any single license.

 In other words, I cannot just say that am using haskell platform but that
 I have to say, I am using x,y and z libraries which in turn are using a, b,
 c and d libraries.


  A quick search suggests that ..:
 Ouch! Apologies. Guess I was looking at all the wrong places or my
 google-fu is embarrassingly bad.



 Thanks again for the links!

 Hemanth K


 On Tue, Jul 31, 2012 at 4:41 PM, Magnus Therning mag...@therning.orgwrote:

 On Tue, Jul 31, 2012 at 12:29 PM, Sai Hemanth K saihema...@gmail.com
 wrote:
  Hi,
 
 
  I am trying to use haskell for building a tool (in a commercial
 setting).  I
  am trying to figure out what all licenses are involved here.
  Is there a single license for the entire haskell platform (and the
 runtime)
  or is it that I need to look at the individual licenses of all the
  libraries and tools that make up the platform and point to them
 separately?
 
  The wikipedia page on haskell platform [0] says Haskell Platform is BSD
  licensed. But I do not find any such info elsewhere.
  Any pointers on this would be greatly appreciated,

 A quick search suggests that this still hasn't been decided:

 http://trac.haskell.org/haskell-platform/ticket/85

 http://trac.haskell.org/haskell-platform/wiki/AddingPackages#Interimlicensepolicy

 I believe it still holds that all packages included in
 haskell-platform are BSD3 licensed.

 /M

 --
 Magnus Therning  OpenPGP: 0xAB4DFBA4
 email: mag...@therning.org   jabber: mag...@therning.org
 twitter: magthe   http://therning.org/magnus




 --
 I drink I am thunk.

 ___
 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] The following is supposed to be initializing a 2D array but it doesn't seem to work.

2012-07-31 Thread KC
newArr :: (Ix i) = i - i - e - Array i e
newArr n m x = listArray (n,m) (repeat
http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v:repeat
x)

-

Prelude http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html
Data.Array newArr 0 10 0
array (0,10) 
[(0,0),(1,0),(2,0),(3,0),(4,0),(5,0),(6,0),(7,0),(8,0),(9,0),(10,0)]

Prelude http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html
Data.Array newArr (0,0) (5,5) 0
array ((0,0),(5,5))
[((0,0),0),((0,1),0),((0,2),0),((0,3),0),((0,4),0),((0,5),0),((1,0),0),((1,1),0),((1,2),0),((1,3),0),((1,4),0),((1,5),0),((2,0),0),((2,1),0),((2,2),0),((2,3),0),((2,4),0),((2,5),0),((3,0),0),((3,1),0),((3,2),0),((3,3),0),((3,4),0),((3,5),0),((4,0),0),((4,1),0),((4,2),0),((4,3),0),((4,4),0),((4,5),0),((5,0),0),((5,1),0),((5,2),0),((5,3),0),((5,4),0),((5,5),0)]


All I am getting is this:
array ((1,5),(1,5)) [((1,5),1.0)]

Maybe the behaviour of ghc was changed since the article was written.


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


Re: [Haskell-cafe] The following is supposed to be initializing a 2D array but it doesn't seem to work.

2012-07-31 Thread Ivan Lazar Miljenovic
On 1 August 2012 07:52, KC kc1...@gmail.com wrote:
 newArr :: (Ix i) = i - i - e - Array i e

 newArr n m x = listArray (n,m) (repeat x)


 -

 Prelude Data.Array newArr 0 10 0

 array (0,10)
 [(0,0),(1,0),(2,0),(3,0),(4,0),(5,0),(6,0),(7,0),(8,0),(9,0),(10,0)]


 Prelude Data.Array newArr (0,0) (5,5) 0

 array ((0,0),(5,5))
 [((0,0),0),((0,1),0),((0,2),0),((0,3),0),((0,4),0),((0,5),0),((1,0),0),((1,1),0),((1,2),0),((1,3),0),((1,4),0),((1,5),0),((2,0),0),((2,1),0),((2,2),0),((2,3),0),((2,4),0),((2,5),0),((3,0),0),((3,1),0),((3,2),0),((3,3),0),((3,4),0),((3,5),0),((4,0),0),((4,1),0),((4,2),0),((4,3),0),((4,4),0),((4,5),0),((5,0),0),((5,1),0),((5,2),0),((5,3),0),((5,4),0),((5,5),0)]


 All I am getting is this:
 array ((1,5),(1,5)) [((1,5),1.0)]

 Maybe the behaviour of ghc was changed since the article was written.

Works for me:

$ghci
GHCi, version 7.4.2: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :m +Data.Array
Prelude Data.Array let newArr n m x = listArray (n,m) (repeat x)
Prelude Data.Array newArr (0,0) (5,5) 0
array ((0,0),(5,5))
[((0,0),0),((0,1),0),((0,2),0),((0,3),0),((0,4),0),((0,5),0),((1,0),0),((1,1),0),((1,2),0),((1,3),0),((1,4),0),((1,5),0),((2,0),0),((2,1),0),((2,2),0),((2,3),0),((2,4),0),((2,5),0),((3,0),0),((3,1),0),((3,2),0),((3,3),0),((3,4),0),((3,5),0),((4,0),0),((4,1),0),((4,2),0),((4,3),0),((4,4),0),((4,5),0),((5,0),0),((5,1),0),((5,2),0),((5,3),0),((5,4),0),((5,5),0)]
Prelude Data.Array


Which article are you referring to?



 --
 --
 Regards,
 KC

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




-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
http://IvanMiljenovic.wordpress.com

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


Re: [Haskell-cafe] specifying using type class

2012-07-31 Thread Ertugrul Söylemez
Patrick Browne patrick.bro...@dit.ie wrote:

 Thanks for all the very useful feed back on this thread.
 I would like to present my possibly incorrect summarized  view:
 Class signatures can contain placeholders for constructors.
 These place-holder-constructors cannot be used in the class to define
 functions (I assume other in-scope constructors can be used). In the
 instance a real constructor can be substituted for the
 place-holder-constructor. Does this restrict the type of equation
 that can be used in a type class? It seems that some equations
 respecting the constructor discipline are not allowed.

Your intuition seems to be near the truth, although your terminology is
currently wrong.  Let's look at an example:

class Functor f where
fmap :: (a - b) - (f a - f b)

The 'f' in the class header is probably what you call a placeholder for
constructors.  This is not a placeholder, but a type variable.  It
represents a type.  Incidentally in this case it indeed represents a
constructor, namely a /type/ constructor (like Maybe).  This is an
important distinction, because generally when we talk about
constructors, we mean /value/ constructors (like Just or Nothing):

data Maybe a = Just a | Nothing

Here Maybe is a type constructor.  This is because it's not a type in
its own right, but is applied to another type (like Int) to yield an
actual type (Maybe Int).  The type Maybe is applied to is represented
by the type variable 'a' in the code above.  To simplify communication
we often call Maybe itself also a type, but it's really not.

Let's write the Functor instance for Maybe.  It is common to use a
helper function (a so-called fold function), which allows us to express
many operations more easily.  It's called 'maybe' for Maybe:

maybe :: b - (a - b) - Maybe a - b
maybe n j (Just x) = j x
maybe n j Nothing  = n

instance Functor Maybe where
fmap f = maybe Nothing (Just . f)

This is the instance for Maybe.  The type variable 'f' from the class
now becomes a concrete type constructor Maybe.  In this instance you
have f = Maybe, so the type of 'fmap' for this particular instance
becomes:

fmap :: (a - b) - (Maybe a - Maybe b)

The notable thing here is that this is really not a
placeholder/replacement concept, but much more like a function and
application concept.  There is nothing that stops you from having type
variables in an instance:

instance Functor (Reader e) where

As you can see there is still what you called a placeholder in this
instance, so the placeholder concept doesn't really make sense here.
The declaration can be read as:

For every type 'e' the type 'Reader e' is an instance of the
Functor type class.


 I appreciate that in Haskell the most equations occur in the
 instances, [...]

Not at all.  When programming Haskell you write lots and lots of
equations outside of class instances.  Whenever you write = you
introduce an equation, for example in top-level definitions and in 'let'
and 'where' bindings.


 [...] but from my earlier post: I merely wish to identify the
 strengths and weakness of *current Haskell type classes* as a pure
 *unit of specification*

I think you will be interested in this Stack Overflow answer:

http://stackoverflow.com/a/8123973

Even though the actual question answered is different, it does give a
nice overview of the strengths and weaknesses of type classes.


Greets,
Ertugrul

-- 
Not to be or to be and (not to be or to be and (not to be or to be and
(not to be or to be and ... that is the list monad.


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


Re: [Haskell-cafe] CRIP: the Curiously Reoccuring Instance Pattern

2012-07-31 Thread AntC
 oleg at okmij.org writes:

 
 [... snip]
 
 Of course instances above are overlapping. And when we add functional
 dependencies (since we really want type-functions rather type
 relations), they stop working at all. We had to employ work-arounds,
 which are described in detail in the HList paper (which is 8 years old
 already).
 
Yes, it's adding the FunDeps that puts the spanner in the works.

Oleg, did you see this, and the discussion around that time?
http://www.haskell.org/pipermail/haskell-prime/2012-May/003688.html

I implemented hDeleteMany without FunDeps -- and it works in Hugs (using 
TypeCast -- but looks prettier in GHC with equality constraints).

Essentially it's a FunDep-like mechanism without FunDeps (as SPJ calls it), to 
achieve what Ryan's talking about. But you are quite right that we still need 
overlapping instances for parts of the type-level logic.

AntC



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


Re: [Haskell-cafe] The following is supposed to be initializing a 2D array but it doesn't seem to work.

2012-07-31 Thread KC
That was it!

On Tue, Jul 31, 2012 at 3:34 PM, Jan-Willem Maessen
jmaes...@alum.mit.eduwrote:



 On Tue, Jul 31, 2012 at 5:52 PM, KC kc1...@gmail.com wrote:

 All I am getting is this:

 array ((1,5),(1,5)) [((1,5),1.0)]

 Maybe the behaviour of ghc was changed since the article was written.


 I think you've made a common mistake here.  Array bounds are (lower in all
 dimensions, upper in all dimensions).  So perhaps you intended to use the
 bounds ((1,1), (5,5)) in your code?

 I make this mistake frequently.

 -Jan-Willem Maessen




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


Re: [Haskell-cafe] GHC rendering of non-ASCII characters configurable?

2012-07-31 Thread Richard Cobbe
On Tue, Jul 31, 2012 at 09:17:34PM +1000, Ivan Lazar Miljenovic wrote:
 On 31 July 2012 21:01, Richard Cobbe co...@ccs.neu.edu wrote:
  On Mon, Jul 30, 2012 at 11:45:38PM +1000, Ivan Lazar Miljenovic wrote:

  Can I ask what you're doing here? Are you printing individual
  characters or entire chunks of text?
 
  Mostly, I'm working with expressions of type String, rather than Text;

 Any particular reason why?  Using Text will probably solve your
 problem and give you a performance improvement at the same time.

Well, I initially went with String because I didn't want to clutter up my
code with all of the calls to 'pack', especially around string literals.
I'm open to being convinced that it's worth it to switch, though.

In any case, while Text is undoubtedly faster than String, it unfortunately
doesn't solve my problem with output rendering:

[vimes:~]$ ghci
GHCi, version 7.4.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :m +Data.Text
Prelude Data.Text pack \x1f00
Loading package array-0.4.0.0 ... linking ... done.
Loading package bytestring-0.9.2.1 ... linking ... done.
Loading package deepseq-1.3.0.0 ... linking ... done.
Loading package text-0.11.2.0 ... linking ... done.
\7936
Prelude Data.Text pack \x1f01
\7937

Richard

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


Re: [Haskell-cafe] Haskell Platform - BSD License?

2012-07-31 Thread Thomas Schilling
You may concatenate the licenses of all the packages you are using. GHC
includes the LGPL libgmp. The license file for each package is mentioned in
the .cabal file.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe