[Haskell-cafe] Documentation operator

2012-12-26 Thread Christopher Done
Hello chums,

I've been playing around with an idea, something that has obvious pros
and cons, but I'll sell it to you because there might be some positive
ideas out of it. Consider the following operator:

{-# LANGUAGE TypeOperators, DataKinds, KindSignatures #-}

module Docs where

import GHC.TypeLits

type a ? (sym :: Symbol) = a

First I'll describe how I'd want to use this and then what I think
are the advantages and disadvantages.

I call this (?) operator “the documentation operator”, to be used for:

* Things that either don't belong or can't be encoded in the type
  system, or for things need to be in English.
* Things that cannot be encoded in Haddock.

The simple case of ye olde days:

-- | Lorem ipsum dolor sit amet. Suspendisse lacinia nibh et
--   leo. Aenean auctor aliquam dapibus.
loremIpsum :: Int - Int - String

Which has since been somewhat evolved into:

loremIpsum :: Int-- ^ Lorem ipsum dolor sit amet.
   - Int-- ^ Suspendisse lacinia nibh et leo.
   - String -- ^ Aenean auctor aliquam dapibus.

But could now be written:

loremIpsum :: Int? Lorem ipsum dolor sit amet.
   - Int? Suspendisse lacinia nibh et leo.
   - String ? Aenean auctor aliquam dapibus.

Here is a contrived case I'll use later on:

data Person = Person

describeAge :: Int ? an age - String ? description of their
elderliness
describeAge n = undefined

personAge :: Person ? a person - Int ? their age
personAge = undefined

One could also encode previously informal specifications more formally,
so that

-- | The action 'hFlush' @hdl@ causes any items buffered for output
-- in handle @hdl@ to be sent immediately to the operating system.
--
-- This operation may fail with:
--
--  * 'isFullError' if the device is full;
--
--  * 'isPermissionError' if a system resource limit would be exceeded.
--It is unspecified whether the characters in the buffer are
discarded
--or retained under these circumstances.
hFlush :: Handle - IO ()
hFlush handle = wantWritableHandle hFlush handle flushWriteBuffer

with

type Throws ex (docs :: Symbol) = docs

could now be written

hFlush :: Handle ? flush buffered items for output on this handle -
IO ()
  ? Throws IsFullError if the device is full
  ? Throws IsPermissionError
   if a system resource limit would be exceeded. It is \
   \unspecified whether the characters in the  buffer are \
   \discarded or retained under these circumstances.
hFlush handle = wantWritableHandle hFlush handle flushWriteBuffer

With this in place, in GHCi you get documentation lookup for free:

 :t hFlush
hFlush
  :: (Handle ? flush buffered items for output on this handle)
 - (IO () ? Throws IsFullError if the device is full)
? Throws
IsPermissionError
if a system resource limit would be exceeded. It is
unspecified
 whether the characters in the  buffer are discarded or
retained
 under these circumstances.

And you get function composition, or “documentation composition” for free:

 :t describeAge . personAge
describeAge . personAge
  :: (Person ? a person)
 - String ? description of their elderliness

We could have a :td command to print it with docs, and otherwise docs
could be stripped out trivially by removing the ? annotations:

 :t describeAge . personAge
describeAge . personAge
  :: Person - String
 :td describeAge . personAge
describeAge . personAge
  :: (Person ? a person)
 - String ? description of their elderliness

You could even add clever printing of such “documentation types”:

 :t hFlush
hFlush
  :: Handle — flush buffered items for output on this handle
  - IO ()
Throws IsFullError if the device is full
Throws IsPermissionError if a system resource limit would be
  exceeded. It is unspecified whether the characters in the buffer
  are discarded or retained under these circumstances.

Unfortunately it doesn't work with monadic composition, of course.

So here are the advantages:

* You get parsing for free (and anyone using haskell-src-exts).
* You get checking for free (i.e. GHC can check that IsFullError exists
  for you).
* You get a continuity of documentation through your operations
  including composition.
* You can extend the documentation language easily by just defining
  some types (like the Throws I used above). SeeMore, Author,
  Deprecated, etc. Whatever.
* You can print out some helpful looking documentation in GHCi based on
  these simple types.
* There's no longer this informal it might throw this exception kind
  of pros we're forced to write.
* It could also be used for annotations other than pure documentation,
  including testing. E.g. add a Testable property and then your test

[Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread Rustom Mody
In haskell, we have

Prelude :t 4
4 :: Num a = a
Prelude

This may be nice in its generality but it makes it hard (for me at least)
when teaching a beginners course to teach polymorphic vs monomorphic
types.  The above leads to even more 'advanced' results like this:

Prelude :t [[1],2]
[[1],2] :: (Num [t], Num t) = [[t]]


Prelude [[1],2]

interactive:5:6:
No instance for (Num [t0])
  arising from the literal `2'
Possible fix: add an instance declaration for (Num [t0])
In the expression: 2
In the expression: [[1], 2]
In an equation for `it': it = [[1], 2]


By contrast in gofer, numeric literals are monomorphic and no such
peculiarities arise

? :t [[1],2]
ERROR: Type error in list
*** expression : [[1],2]
*** term   : 2
*** type   : Int
*** does not match : [Int]

[[1],2]
ERROR: Type error in list
*** expression : [[1],2]
*** term   : 2
*** type   : Int
*** does not match : [Int]


So is there any set of flags to make haskell literals less polymorphic?
ie I want 3 to have type Int and 3.0 to have type Float.

This is of course for beginning students to not see type classes too early
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Substituting values

2012-12-26 Thread Chaddaï Fouché
Since recently, the notion of prisms from the lens library can achieve
that : to modify a value only in certain conditions but you have to
write the prism so it's not that convenient, though at least you'll
have an uniform API.
See 
http://hackage.haskell.org/packages/archive/lens/3.7.0.2/doc/html/Control-Lens-Prism.html
, especially the nat example.

--
Jedaï

On Fri, Dec 21, 2012 at 6:46 PM, Radical radi...@google.com wrote:
 Sometimes I'll need something like:

   if value == Foo then Bar else value

 Or some syntactic variation thereof:

   case value of { Foo - Bar; _ - value }

 Is there a better/shorter way to do it? I'm surprised that it's more
 complicated to substitute a value on its own than e.g. in a list, using
 filter. Or perhaps I'm missing the right abstraction?

 Thanks,

 Alvaro




 ___
 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] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread koomi
You should note that GHCi uses extended defaulting rules as explained in
[1].
This means that a literal like 5 will only be of type Num a = a in GHCi
while in a normal Haskell program it will default to some concrete type
(Integer if there are no other constraints). Also, if you define x = 5
in a .hs file and load the file in GHCi, x will have type Integer.

In my short search I could not find out how to reverse this behavior,
:unset -XExtendedDefaultRules does not seem to work.


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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread koomi
Sorry, forgot the link:
http://www.haskell.org/ghc/docs/7.0.4/html/users_guide/interactive-evaluation.html
Section 2.4.5 Type defaulting in GHCi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread Roman Cheplyaka
* Rustom Mody rustompm...@gmail.com [2012-12-26 20:12:17+0530]
 So is there any set of flags to make haskell literals less polymorphic?

Yes, there is!

  % ghci -XRebindableSyntax
  GHCi, version 7.6.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.
   import Prelude hiding (fromInteger)
  Prelude let fromInteger = id
  Prelude :t 3
  3 :: Integer

Roman

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


[Haskell-cafe] ANNOUNCE: Haskell BOF on 29c3 in Hamburg, Germany

2012-12-26 Thread Matthias Fischmann

Hi everybody, we will be running a nano-hackathon on the CCC congress
in Hamburg on Thursday, 2012-12-27, 5pm German time:

  https://events.ccc.de/congress/2012/wiki/Haskell_BOF

Sorry for the short notice.  If you would like to meet up later during
the congress please drop us a line.

cheers,
matthias

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


[Haskell-cafe] Type error when trying to adapt http-proxy to new conduit

2012-12-26 Thread Pieter Laeremans
Hi,

The http-proxy package isn't  compatible any longer with the latest
conduit. Since it is open source, I thought, I might as well try to adapt
it and submit a patch.

However I run into some difficulties.

For example I get this type error when I'm trying to compile it :

Network/HTTP/Proxy.hs:254:15:
Couldn't match expected type `ResourceT
IO (CIN.Pipe () () ByteString ()
(ResourceT IO) ())'
with actual type `IO
(CIN.Pipe () () ByteString ()
(ResourceT IO) ())'

I can't figure it out. To me it reads like : Expected x, actual x.

Anyone has a clue?

thanks,

Pieter


-- 
Pieter Laeremans pie...@laeremans.org

The future is here. It's just not evenly distributed yet.  W. Gibson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type error when trying to adapt http-proxy to new conduit

2012-12-26 Thread Brandon Allbery
On Wed, Dec 26, 2012 at 6:22 PM, Pieter Laeremans pie...@laeremans.orgwrote:

 Network/HTTP/Proxy.hs:254:15:
 Couldn't match expected type `ResourceT
 IO (CIN.Pipe () () ByteString ()
 (ResourceT IO) ())'
 with actual type `IO
 (CIN.Pipe () () ByteString ()
 (ResourceT IO) ())'

 I can't figure it out. To me it reads like : Expected x, actual x.


There's an extra ResourceT in the former.

expected `ResourceT IO (CIN.Pipe () () ByteString () (ResourceT IO) ())'
actual `IO (CIN.Pipe () () ByteString () (ResourceT IO) ())'

Might just need an extra lift?

-- 
brandon s allbery kf8nh   sine nomine associates
allber...@gmail.com  ballb...@sinenomine.net
unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: haskell-docs - Given a module name and a name, it will find and display the documentation of that name.

2012-12-26 Thread Christopher Done
Ahoy hoy,

Just thought I'd announce a tool I whipped up these evening to take a
module name and a name and output the installed Haddock documentation
for it. Examples with my GHCi session:

λ :doc Data.List.Split split
Split a list according to the given splitting strategy. This is
 how to run a Splitter that has been built using the other
 combinators.
λ :doc Control.Concurrent.MVar swapMVar
Take a value from an MVar, put a new value into the MVar and
 return the value taken. This function is atomic only if there are
 no other producers for this MVar.
λ :doc Data.List sort
Ambiguous module, belongs to more than one package: base haskell2010-1.1.0.1
Continuing anyway...
Package: base
The sort function implements a stable sorting algorithm.
 It is a special case of sortBy, which allows the programmer to supply
 their own comparison function.

Please have a play with it, the package is at:
http://hackage.haskell.org/package/haskell-docs It has installation
instructions. Feel free to share any issues that you have, either
here, or on the Github page: https://github.com/chrisdone/haskell-docs
There are some issues to do with versioning that I'm not sure how to
solve in a standard way.

The obvious next step is to have a -package-conf flag so that it can
be used with cabal-dev.

The wizards on #haskell are currently thinking of a way to avoid
having to write the module name and just use what's in scope.

Ciao!

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


Re: [Haskell-cafe] Non polymorphic numerals option -- avoiding type classes

2012-12-26 Thread Rustom Mody
On Thu, Dec 27, 2012 at 1:48 AM, Roman Cheplyaka r...@ro-che.info wrote:

 * Rustom Mody rustompm...@gmail.com [2012-12-26 20:12:17+0530]
  So is there any set of flags to make haskell literals less polymorphic?

 Yes, there is!

   % ghci -XRebindableSyntax
   GHCi, version 7.6.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.
import Prelude hiding (fromInteger)
   Prelude let fromInteger = id
   Prelude :t 3
   3 :: Integer

 Roman



Thanks Roman -- that helps.
And yet the ghci error is much more obscure than the gofer error:

--- contents of .ghci ---
:set -XRebindableSyntax
let fromInteger = id
-- ghci session -
$ 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 :t 5
5 :: Integer
Prelude :t [[1,2],3]

interactive:1:8:
Couldn't match expected type `[Integer]' with actual type `Integer'
Expected type: Integer - [Integer]
  Actual type: Integer - Integer
In the expression: 3
In the expression: [[1, 2], 3]


- The same in gofer -
Gofer session for:
pustd.pre
? :t [[1,2],3]

ERROR: Type error in list
*** expression : [[1,2],3]
*** term   : 3
*** type   : Int
*** does not match : [Int]
--
So the error is occurring at the point of the fromInteger (= id) but the
message does not indicate that

-- 
http://www.the-magus.in
http://blog.languager.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: haskell-docs - Given a module name and a name, it will find and display the documentation of that name.

2012-12-26 Thread Alfredo Di Napoli
Excellent work, Chris!
Looking forward to using your tool!

Ciao!
Alfredo

Sent from my iPad

On 27/dic/2012, at 01:43, Christopher Done chrisd...@gmail.com wrote:

 Ahoy hoy,
 
 Just thought I'd announce a tool I whipped up these evening to take a
 module name and a name and output the installed Haddock documentation
 for it. Examples with my GHCi session:
 
 λ :doc Data.List.Split split
 Split a list according to the given splitting strategy. This is
 how to run a Splitter that has been built using the other
 combinators.
 λ :doc Control.Concurrent.MVar swapMVar
 Take a value from an MVar, put a new value into the MVar and
 return the value taken. This function is atomic only if there are
 no other producers for this MVar.
 λ :doc Data.List sort
 Ambiguous module, belongs to more than one package: base haskell2010-1.1.0.1
 Continuing anyway...
 Package: base
 The sort function implements a stable sorting algorithm.
 It is a special case of sortBy, which allows the programmer to supply
 their own comparison function.
 
 Please have a play with it, the package is at:
 http://hackage.haskell.org/package/haskell-docs It has installation
 instructions. Feel free to share any issues that you have, either
 here, or on the Github page: https://github.com/chrisdone/haskell-docs
 There are some issues to do with versioning that I'm not sure how to
 solve in a standard way.
 
 The obvious next step is to have a -package-conf flag so that it can
 be used with cabal-dev.
 
 The wizards on #haskell are currently thinking of a way to avoid
 having to write the module name and just use what's in scope.
 
 Ciao!
 
 ___
 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] Type error when trying to adapt http-proxy to new conduit

2012-12-26 Thread Erik de Castro Lopo
Pieter Laeremans wrote:

 Hi,
 
 The http-proxy package isn't  compatible any longer with the latest
 conduit. Since it is open source, I thought, I might as well try to adapt
 it and submit a patch.

Have you looked int git?

It currently compiles from git but there is a space leak that
I haven't managed to fix yet.

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