Re: [Haskell-cafe] TypeLits Typeable

2013-08-26 Thread Iavor Diatchki
Hi guys,

Yep, we know about this and, I believe, the plan is to add custom rules to
the constraint solver to solve `Typable n` constraints (where n is  a
number or symbol).   Just for the record, the other design choice was to
add instance `Typeable (n :: Symbol)`, but that conflicted with some of the
polymorphic instances already present in the library, so we decided to go
for the custom constraint solver rules.

This should not be hard to do, I just need to sit down and do it---my
current priority has been to catch up the type-nats solver with HEAD and
clean up things for merging.

-Iavor





On Mon, Aug 26, 2013 at 1:19 AM, José Pedro Magalhães j...@cs.uu.nl wrote:

 Hi Nicolas,

 It's not intentional, but Iavor is aware of this, and we want to change it.
 I'm CC-ing him as he might know more about what the current plan is.


 Cheers,
 Pedro


 On Sat, Aug 24, 2013 at 3:20 PM, Nicolas Trangez nico...@incubaid.comwrote:

 Hello Cafe,

 I was playing around with TypeLits in combination with Typeable (using
 GHC 7.7.7.20130812 FWIW), but was surprised to find Symbols aren't
 Typeable, and as such the following doesn't work. Is this intentional,
 or am I missing something?

 Thanks,

 Nicolas

 {-# LANGUAGE DataKinds,
  KindSignatures,
  DeriveFunctor,
  DeriveDataTypeable #-}
 module Main where

 import Data.Typeable
 import GHC.TypeLits

 data NoSymbol n a b = NoSymbol a b
   deriving (Typeable)

 data WithSymbol (n :: Symbol) a b = WithSymbol a b
   deriving (Typeable)

 data Sym
   deriving (Typeable)

 main :: IO ()
 main = do
 print $ typeOf (undefined :: NoSymbol Sym Int Int)

 let d = undefined :: WithSymbol sym Int Int
 {-
 print $ typeOf d

 No instance for (Typeable Symbol sym)
   arising from a use of ‛typeOf’
 -}

 return ()


 ___
 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] Job opportunities at Galois

2013-06-27 Thread Iavor Diatchki
Hello,

Galois is hiring!  We're looking for researchers, principal investigators,
and software engineers, including those with expertise in functional
programming, formal methods, computer security, control systems,
informatics, or networking.

For more information, take a look at http://corp.galois.com/careers and
please feel free to drop me an e-mail if you have questions.

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


Re: [Haskell-cafe] Job opportunities at Galois

2013-06-27 Thread Iavor Diatchki
Hello,
(Alejandro, sorry for the duplicate message but a couple of folks asked the
same, so I thought I'd reply to the list).

We are looking for people to work at our office (i.e., not remotely).
 Unfortunately, H1B visas have run out for this year, so right now we are
looking for folks who are already eligible to work in the US.

-Iavor


On Thu, Jun 27, 2013 at 9:03 AM, Alejandro Serrano Mena
trup...@gmail.comwrote:

 Hello,
 Are there any specific details to consider when applying? For example, is
 living in the US or having a visa required for application?

 Thanks in advance.


 2013/6/27 Iavor Diatchki iavor.diatc...@gmail.com

 Hello,

 Galois is hiring!  We're looking for researchers, principal
 investigators, and software engineers, including those with expertise in
 functional programming, formal methods, computer security, control systems,
 informatics, or networking.

 For more information, take a look at http://corp.galois.com/careers and
 please feel free to drop me an e-mail if you have questions.

 Cheers,
 -Iavor



 ___
 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] Status of GHC type-nats branch

2013-02-25 Thread Iavor Diatchki
Hello,
I haven't merged the type-nats branch with GHC master recently, so some of
the libraries probably moved forward, which could be the source of the
problem.  I'll make sure to fix it over the next couple of days.
-Iavor


On Mon, Feb 25, 2013 at 6:39 AM, Takayuki Muranushi muranu...@gmail.comwrote:

 Hi, everyone,

 In order to merge two type-level key-value pairs
 (More specifically, to use TypeNats branch of unittyped:

 https://bitbucket.org/xnyhps/haskell-unittyped/commits/all/tip/branch%28%22TypeNats%22%29
 )
 I'd like to use overlapping type families and the type level Naturals
 at the same time.

 However, I couldn't build the type-nats branch of ghc, as I've been
 trying this week.
 I could build that in late 2012, so maybe this is due to updates in
 the git submodules.

 Do you reproduce this? Is there anyone else trying to build the
 type-nats branch?

 Any advice is helpful, including negative ones, if it's temporally
 broken or no more supported. And, I'm particularly glad if anyone has
 a x86-64 linux tarball of type-nats branch, and share it with me :)

 Best regards,

 --
 Takayuki MURANUSHI
 The Hakubi Center for Advanced Research, Kyoto University
 http://www.hakubi.kyoto-u.ac.jp/02_mem/h22/muranushi.html

 ___
 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] Text.JSON and utf8

2013-02-16 Thread Iavor Diatchki
Hello Martin,

the change that you propose seems to already be in json-0.7.  Perhaps you
just need to 'cabal update' and install the most recent version?

About your other question:  I have not used CouchDB but a common mistake is
to mix up strings and bytes.  Perhaps the `getDoc` function does not do
utf-8 decoding and so it is giving you back list of bytes (as a String)?

In general, the JSON package only converts between JSON and String, and is
agnostic to what encoding is used to represent the strings.   There are
other packages that convert Strings into bytes (e.g.,
http://hackage.haskell.org/package/utf8-string), so typically you want to
encode the string to bytes before you export it (say to CouchDB), and
decode it back into a string just after you've imported it.

-Iavor





On Mon, Feb 11, 2013 at 5:56 AM, Martin Hilbig li...@mhilbig.de wrote:

 hi,

 tl;dr: i propose this patch to Text/JSON/String.hs and would like to
 know why it is needed:

 @@ -375,7 +375,7 @@
where
go s1 =
  case s1 of
 -  (x   :xs) | x  '\x20' || x  '\x7e' - '\\' : encControl x (go xs)
 +  (x   :xs) | x  '\x20' - '\\' : encControl x (go xs)
('' :xs)  - '\\' : ''  : go xs
('\\':xs)  - '\\' : '\\' : go xs
(x   :xs)  - x: go xs


 i recently stumbled upon CouchDB telling me i'm sending invalid json.

 i basically read lines from a utf8 file with german umlauts and send
 them to CouchDB using Text.JSON and Database.CouchDB.

   $ file lines.txt
   lines.txt: UTF-8 Unicode text

 lets take 'ö' as an example. i use LANG=de_DE.utf8

 ghci tells

  'ö'
 '\246'

  putChar '\246'
 ö

  putChar 'ö'
 ö

  :m + Text.JSON Database.CouchDB
  runCouchDB' $ newNamedDoc (db foo) (doc bar) (showJSON $ toJSObject
 [(test,ö)])
 *** Exception: HTTP/1.1 400 Bad Request
 Server: CouchDB/1.2.1 (Erlang OTP/R15B03)
 Date: Mon, 11 Feb 2013 13:24:49 GMT
 Content-Type: text/plain; charset=utf-8
 Content-Length: 48
 Cache-Control: must-revalidate

 couchdb log says:

   Invalid JSON: {{error,{10,lexical error: invalid bytes in UTF8
 string.\n}},{\test\:\**F6\}}

 this is indeed hex ö:

  :m + Numeric
  putChar $ toEnum $ fst $ head $ readHex f6
 ö

 if i apply the above patch and reinstall JSON and CouchDB the doc
 creation works:

  runCouchDB' $ newNamedDoc (db db) (doc foo) (showJSON $ toJSObject
 [(test, ö)])
 Right someRev

 but i dont get back the ö i expected:

  Just (_,_,x) -runCouchDB' $ getDoc (db foo) (doc bar) :: IO (Maybe
 (Doc,Rev,JSObject String))
  let Ok y = valFromObj test = readJSON x :: Result String
  y
 \195\188
  putStrLn y
 ü

 apperently with curl everything works fine:

 $ curl localhost:5984/db/foo -XPUT -d '{test: ö}'
 {ok:true,id:foo,rev:**someOtherRev}
 $ curl localhost:5984/db/foo
 {_id:bars,_rev:**someOtherRev,test:ö}

 so how can i get my precious ö back? what am i doing wrong or does
 Text.JSON need another patch?

 another question: why does encControl in Text/JSON/String.hs handle the
 cases x  '\x100' and x  '\x1000' even though they can never be
 reached with the old predicate in encJSString (x  '\x20')

 finally: is '\x7e' the right literal for the job?

 thanks for reading

 have fun
 martin

 __**_
 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] Advice on type families and non-injectivity?

2013-01-13 Thread Iavor Diatchki
Hello Conal,

The issue with your example is that it is ambiguous, so GHC can't figure
out how to instantiate the use of `foo`.   It might be easier to see why
this is if you write it in this form:

 foo :: (F a ~ b) = b
 foo = ...

Now, we can see that only `b` appears on the RHS of the `=`, so there is
really no way for GHC to figure out what is the intended value for `a`.
 Replacing `a` with a concrete type (such as `Bool`) eliminates the
problem, because now GHC does not need to come up with a value for `a`.
Another way to eliminate the ambiguity would be if `F` was injective---then
we'd know that `b` uniquely determines `a` so again there would be no
ambiguity.

If `F` is not injective, however, the only workaround would be to write the
type in such a way that the function arguments appear in the signature
directly (e.g., something like 'a - F a' would be ok).

-Iavor








On Sun, Jan 13, 2013 at 11:10 AM, Conal Elliott co...@conal.net wrote:

 I sometimes run into trouble with lack of injectivity for type families.
 I'm trying to understand what's at the heart of these difficulties and
 whether I can avoid them. Also, whether some of the obstacles could be
 overcome with simple improvements to GHC.

 Here's a simple example:

  {-# LANGUAGE TypeFamilies #-}
 
  type family F a
 
  foo :: F a
  foo = undefined
 
  bar :: F a
  bar = foo

 The error message:

 Couldn't match type `F a' with `F a1'
 NB: `F' is a type function, and may not be injective
 In the expression: foo
 In an equation for `bar': bar = foo

 A terser (but perhaps subtler) example producing the same error:

  baz :: F a
  baz = baz

 Replacing `a` with a monotype (e.g., `Bool`) eliminates the error.

 Does the difficulty here have to do with trying to *infer* the type and
 then compare with the given one? Or is there an issue even with type
 *checking* in such cases?

 Other insights welcome, as well as suggested work-arounds.

 I know about (injective) data families but don't want to lose the
 convenience of type synonym families.

 Thanks,  -- Conal


 ___
 Glasgow-haskell-users mailing list
 glasgow-haskell-us...@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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


Re: [Haskell-cafe] Advice on type families and non-injectivity?

2013-01-13 Thread Iavor Diatchki
Hello,


On Sun, Jan 13, 2013 at 12:05 PM, Conal Elliott co...@conal.net wrote:


 so there is really no way for GHC to figure out what is the intended value
 for `a`.


 Indeed. Though I wonder: does the type-checker really need to find a
 binding for `a` in this case, i.e., given the equation `(forall a. F a) ==
 (forall a'. F a')`?


Wouldn't that make `F` a constant type family, and so one could just skip
the `a` parameter?   Anyway, if there was a way to assert something like
that about a type-function, than there would be no problem.   When
something like that happens (i.e., GHC figures out that it does not know
how to instantiate a type variable, but it is sure that the actual
instantiation does not matter), GHC instantiates the variable a special
type called `Any`, which has a very polymorphic kind.

By the way, Simon recently reworked the ambiguity checker in GHC, and now
HEAD correctly rejects `foo` as being ambiguous (the new ambiguity check
uses exactly what's in your example: a value `f :: S` is ambiguous, if `g
:: S; g = f` results in an error).

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


Re: [Haskell-cafe] Documentation operator

2012-12-27 Thread Iavor Diatchki
Hi,

I think that this is a neat idea that should be explored more!   GHC's
parser has a bunch of awkward duplication to handle attaching documentation
to types, and it'd be cool if we could replace it with an actual language
construct.

Happy holidays!
-Iavor

On Wed, Dec 26, 2012 at 3:27 AM, Christopher Done chrisd...@gmail.comwrote:

 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 

Re: [Haskell-cafe] curl package broken in Windows

2012-11-12 Thread Iavor Diatchki
Hi,

the curl binding certainly needs some love---if anyone has the time to fix
it up and maintain it, help would be most appreciated.  There is a repo for
it over here: https://github.com/GaloisInc/curl which is the most up-to
date version I know of, but since the last commit there seems to be from 4
years ago, I'm not going to bet that there aren't any additional fixes
floating around.  (cc-ing Don, who is listed as the maintainer, but I'm not
sure if he has time to deal with curl right now)

-Iavor



On Sun, Nov 11, 2012 at 3:34 PM, Erik de Castro Lopo
mle...@mega-nerd.comwrote:

 Kevin Cantu wrote:

  With the curl package on Hackage, I merely need an SSL enabled version
  of libcurl, and every Linux distro I've tried this on has several
  variations of such a package.  (You have a choice of OpenSSL or
  GNUTLS, for example.)

 I tried the CURL bindings on Linux some time ago and I personally
 found the thing pretty much un-usable. The API was incomplete,
 inconsistent and way too close to the C API.

 However, I have had much better luck with Michael Snoyman's http-conduit
 package, which being pure Haskell (ie no C) should be much easier to
 install on windows.

 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] curl package broken in Windows

2012-11-12 Thread Iavor Diatchki
Hi,

Ok, there were only minor differences between the repo and the version on
hackage so I imported the changes into the repo, which should now be the
same as version 1.3.7 on hackage.
Please feel free to submit merge requestsall the folks I know who
worked on this originally are busy with other stuff, so we really need
someone who's using the library to help.

Thanks!
-Iavor



On Mon, Nov 12, 2012 at 2:06 PM, Iustin Pop iu...@k1024.org wrote:

 On Mon, Nov 12, 2012 at 10:57:25PM +0100, Iustin Pop wrote:
  On Mon, Nov 12, 2012 at 01:48:23PM -0800, Iavor Diatchki wrote:
   Hi,
  
   the curl binding certainly needs some love---if anyone has the time to
 fix
   it up and maintain it, help would be most appreciated.  There is a
 repo for
   it over here: https://github.com/GaloisInc/curl which is the most
 up-to
   date version I know of, but since the last commit there seems to be
 from 4
   years ago, I'm not going to bet that there aren't any additional fixes
   floating around.  (cc-ing Don, who is listed as the maintainer, but
 I'm not
   sure if he has time to deal with curl right now)
 
  I've tried to contact Don multiple times over the past month with offers
  of whatever help I can give, but I heard nothing back.
 
  I didn't know about the github repo (it's not listed on the hackage
  page), so thanks a lot for that info, I'll try to send some merge
  requests and file bugs (there is a least one critical bug w.r.t. SSL
  usage on Linux and another small-impact bug with cookie jars usage).

 Hmm, checking again, the github repo is at version 1.3.5 (April 2009),
 whereas hackage is at version 1.3.7 (uploaded in May 2011).

 Still hunting for a correct upstream project page or tracker…

 regards,
 iustin

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


Re: [Haskell-cafe] Computed promoted natural

2012-11-08 Thread Iavor Diatchki
Hello Arie,

One way to achieve the additional static checking is to use values of type
`Sing (n :: Nat)` in the places where you've used `Integer` (and
parameterize data structures by the `n`).  If the code is fully polymorphic
in the `n`, then you can use it with values whose types as not statically
know by using an existential.  Here is an example:

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

import GHC.TypeLits

data SomeNat = forall (n :: Nat). SomeNat (Sing n)

getSomeNat :: IO SomeNat
getSomeNat =
  do x - getLine
 case reads x of
   -- The use of `unsafeSingNat` is OK here because it is wrapped in
`SomeNat`
   -- so we are not assuming anything about the actual number.
   [(n,_)] | n = 0 - return $ SomeNat $ unsafeSingNat n
   _ - putStrLn Invalid number, try again.  getSomeNat

main :: IO ()
main =
  do x - getSomeNat
 case x of
   SomeNat s - polyFun s s

-- The argument of this function are always going to be the same.
-- (just an example, one could probably get more interesting properties)
polyFun :: Sing (n :: Nat) - Sing n - IO ()
polyFun x y = print (x,y)

I can elaborate more, just ask if this does not make sense.   One issue at
the moment is that you have to pass the explicit `Sing` values everywhere,
and it is a lot more convenient to use the `SingI` class in GHC.TypeLits.
 Unfortunately at the moment this only works for types that are statically
known at compile time.  I think that we should be able to find a way to
work around this, but we're not quite there yet.

-Iavor






On Thu, Nov 8, 2012 at 7:54 AM, Arie Peterson ar...@xs4all.nl wrote:

 Hi,


 I'm trying to use data kinds, and in particular promoted naturals, to
 simplify
 an existing program.

 The background is as follows: I have a big computation, that uses a certain
 natural number 'd' throughout, which is computed from the input.
 Previously,
 this number was present as a field in many of my data types, for instance

  data OldA = OldA Integer …

 . There would be many values of this type (and others) floating around,
 with
 all the same value of 'd'. I would like to move this parameter to the type
 level, like this:

  data NewA (d :: Nat) = NewA …

 The advantage would be, that the compiler can verify that the same value of
 'd' is used throughout the computation.

 Also, it would then be possible to make 'NewA' a full instance of 'Num',
 because 'fromInteger :: Integer - NewA d' has a natural meaning (where the
 value of 'd' is provided by the type, i.e. the context in which the
 expression
 is used), while 'fromInteger :: Integer - OldA' does not, because it is
 not
 possible to create the right value of 'd' out of thin air.


 Is this a sane idea? I seem to get stuck when trying to /use/ the
 computation,
 because it is not possible to create 'd :: Nat', at the type level, from
 the
 computed integer.

 Can one somehow instantiate the type variable 'd :: Nat' at an integer
 that is
 not statically known?

 Formulated this way, it sounds like this should not be possible, because
 all
 types are erased at compile time.

 However, it feels as though it might not be unreasonable in this situation,
 because the computation is polymorphic in the type 'd :: Nat'. I just want
 to
 substitute a specific value for 'd'.


 Maybe there is another way to approach this?


 Thanks for any advice,

 Arie


 ___
 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] [Security] Put haskell.org on https

2012-11-02 Thread Iavor Diatchki
Hello,

I think that getting a certificate is a good idea.  I think this could
probably be arranged by the haskell.org committee, which even has a budget
for things like that, I believe.  I'm cc-ing Jason, who's on the committee
and might have more input on what's the best way to proceed.

Thanks for bringing this up!
-Iavor


On Fri, Nov 2, 2012 at 5:14 AM, Ramana Kumar ramana.ku...@cl.cam.ac.ukwrote:

 Who is the webmaster for haskell.org? Presumably they will be required in
 the process of installing the certificate.

 As far as obtaining goes, one can obtain a free certificate from StartSSL
 - see https://www.startssl.com
 There are other CAs, but if nobody has any strong preferences, I recommend
 going with them.


 On Tue, Oct 30, 2012 at 8:52 PM, Niklas Hambüchen m...@nh2.me wrote:

 So how do we go forward about getting the SSL certificate and installing
 it?

 On 29/10/12 01:06, Patrick Mylund Nielsen wrote:
  Sure. No matter what's done in Cabal, the clients for everything else
  will still be mainly browsers.
 
  On Mon, Oct 29, 2012 at 12:59 AM, Niklas Hambüchen m...@nh2.me
  mailto:m...@nh2.me wrote:
 
  No matter what we do with cabal, it would be great if I could soon
 point
  my browser at https://haskell.org *anyway*.
 
  On 28/10/12 23:55, Patrick Mylund Nielsen wrote:
   Of course, as long as Cabal itself is distributed through this
 same
   https-enabled site, you have the same PKI-backed security as just
  about
   any major website. This model has problems, yes, but it's good
 enough,
   and it's easy to use. If you really want to improve it (without
   impacting usability), have Google/the browser vendors pin the
 public
   cert for haskell.org http://haskell.org http://haskell.org.
  
   On Mon, Oct 29, 2012 at 12:45 AM, Patrick Mylund Nielsen
   hask...@patrickmylund.com mailto:hask...@patrickmylund.com
  mailto:hask...@patrickmylund.com
  mailto:hask...@patrickmylund.com wrote:
  
   PGP tends to present many usability issues, and in this case
 it
   would make more sense/provide a clearer win if there were many
   different, semi-untrusted hackage mirrors. Just enable HTTPS
 and
   have Cabal validate the server certificate against a CA pool
  of one.
   PKI/trusting obscure certificate authorities in Egypt and
 Syria is
   the biggest concern here, not somebody MITMing your initial
 Cabal
   installation (which in a lot of cases happens through apt-get
 or
   yum, anyway.)
  
  
   On Mon, Oct 29, 2012 at 12:34 AM, Changaco
  chang...@changaco.net mailto:chang...@changaco.net
   mailto:chang...@changaco.net mailto:chang...@changaco.net
 
  wrote:
  
   On Sun, 28 Oct 2012 17:07:24 -0400 Patrick Hurst wrote:
How do you get a copy of cabal while making sure that
  somebody
   hasn't MITMed you and replaced the PGP key?
  
   Ultimately it is a DNS problem. To establish a secure
  connection
   with
   haskell.org http://haskell.org http://haskell.org
  you'd have to get the
   certificate from the DNS, but that
   technology is not ready yet, so all you can do is check
  the key
   against
   as many sources as possible like Michael Walker said.
  
   On Sun, 28 Oct 2012 17:46:06 -0400 Patrick Hurst wrote:
So why not use HTTPS?
  
   Because it doesn't solve the problem.
  
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
 
  mailto:Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
  
  
  
  
  
   ___
   Haskell-Cafe mailing list
   Haskell-Cafe@haskell.org mailto:Haskell-Cafe@haskell.org
   http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org mailto: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 mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type-directed functions with data kinds

2012-10-25 Thread Iavor Diatchki
Hello Paul,

If you don't want to use the class system, you could write `repeat` with a
type like this:

repeat :: Proxy n - a - Vector n a

(`Proxy` is the singleton family 'data Proxy n = Proxy`).

You can't really do it with a function of type `a - Vector n a` because
there is no way for the function to know how many elements to generate.
You cannot determine the length from the type `n` because polymorphism in
Haskell is _parametric_, which means that the function needs to behave
uniformly for all types.
This is nice because it makes reasoning about programs easier, but also, it
allows for efficient implementation---there is no need to pass
type-representations at run-time.
In contrast, overloaded values may behave differently depending on their
type, just like your implementation of `repeat` below.  This is perfectly
OK, and it is clearly marked in the type.


I hope this helps,
-Iavor



On Thu, Oct 25, 2012 at 8:22 AM, Paul Visschers m...@paulvisschers.netwrote:

 Hello everyone,

 I've been playing around with the data kinds extension to implement
 vectors that have a known length at compile time. Some simple code to
 illustrate:
  {-# LANGUAGE DataKinds, GADTs, KindSignatures #-}
 
  import Prelude hiding (repeat)
 
  data Nat = Zero | Succ Nat
  data Vector (n :: Nat) a where
Nil :: Vector Zero a
Cons :: a - Vector n a - Vector (Succ n) a
 
  class VectorRepeat (n :: Nat) where
repeat :: a - Vector n a
 
  instance VectorRepeat Zero where
repeat _ = Nil
 
  instance VectorRepeat n = VectorRepeat (Succ n) where
repeat x = Cons x (repeat x)

 In this code I have defined a repeat function that works in a similar way
 to the one in the prelude, except that the length of the resulting vector
 is determined by the type of the result. I would have hoped that its type
 would become 'repeat :: a - Vector n a', yet it is 'repeat :: VectorRepeat
 n = a - Vector n a'. As far as I can tell, this class constraint should
 no longer be necessary, as all possible values for 'n' are an instance of
 this class. I actually really just want to define a closed type-directed
 function and would rather not (ab)use the type class system at all.

 Is there a way to write the repeat function so that it has the type
 'repeat :: a - Vector n a' that I've missed? If not, is this just because
 it isn't implemented or are there conceptual caveats?

 Paul Visschers

 ___
 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-directed functions with data kinds

2012-10-25 Thread Iavor Diatchki
Hello,

Sorry, I made a mistake, the version of 'repeat :: Proxy n - a - Vector n
a' won't work either, as Andres noticed, because `Proxy` still won't give
you information about how many times to repeat.
You'd have to use a structured singleton family, where the values are
linked to the types:

data SNat :: Nat - * where
  SZero :: SNat Zero
  SSucc :: SNat n - SNat (Succ n)

repeat :: SNat n - a - Vector n a

Apologies for the confusion,
-Iavor





On Thu, Oct 25, 2012 at 9:03 AM, Andres Löh andres.l...@gmail.com wrote:

 Hi Iavor.

  If you don't want to use the class system, you could write `repeat` with
 a
  type like this:
 
  repeat :: Proxy n - a - Vector n a
 
  (`Proxy` is the singleton family 'data Proxy n = Proxy`).

 How is the polymorphism becoming any less parametric by using this
 particular Proxy type?

 Cheers,
   Andres

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


[Haskell-cafe] ANN: monadLib-3.7.1 on Hackage

2012-10-01 Thread Iavor Diatchki
Hello,

I am pleased to announce the availability of monadLib-3.7.1 on Hackage.

MonadLib is a library intended to help programmers to quickly and easily
construct various monads.   The library has support for a wide range of
effects:  threading state, read-only variables, collecting output,
exception handling, back-tracking computation, and working with explicit
continuations.  It provides similar functionality to libraries such as MTL,
but it has a simpler interface and improved functionality for a number of
the transformers.

The main change in this version is improved support for working with
continuations:  now we support invoking the same continuation in contexts
that have different types.

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


Re: [Haskell-cafe] Simple shell scripts

2012-08-27 Thread Iavor Diatchki
Hello,
this happens because head probably closes the file descriptor after 3
lines, and then the Haskell program tries to write to a closed handle
(i.e., it's stdout is not there anymore).  The best thing to do depends on
the program. One fairly simple option would be to handle the exception, and
do something (perhaps ignore it).
-Iavor

On Mon, Aug 27, 2012 at 10:55 AM, Eric Tanter etan...@dcc.uchile.cl wrote:

 Hi,

 Here is a simple shell script (upper.hs):

 import Data.Char
 main = interact $ map toUpper

 which composes fine with other scripts:

 bash-3.2$ yes | head -n 3 | runghc upper.hs
 Y
 Y
 Y

 but not always:

 bash-3.2$ yes | runghc upper.hs | head -n 3
 Y
 Y
 Y
 stdout: hFlush: resource vanished (Broken pipe)

 Any idea why this error occurs/how to avoid it?

 (running just:
 yes | runghc upper.hs
 gives the expected infinite stream of Ys)

 Thanks!

 -- Éric

 ___
 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] Platform Versioning Policy: upper bounds are not our friends

2012-08-20 Thread Iavor Diatchki
Hello,

I also completely agree with Bryan's point which is why I usually don't add
upper bounds on the dependencies of the packages that I maintain---I find
that the large majority of updates to libraries tend to be backward
compatible, so being optimistic seems like a good idea.

By the way, something I encounter quite often is a situation where two
packages both build on Hacakge just fine, but are not compatible with each
other.  Usually it goes like this:

  1. Package A requires library X = V  (typically, because it needs a bug
fix or a new feature).
  2. Package B requires library X  V (typically, because someone added a
conservative upper bound that needs to be updated).

Trying to use A and B together leads to failure, which is usually resolved
by having to install B manually, and remove it's upper bound by hand.  This
is rather unfortunate, because not only it's inconvenient but, also, now
there is no released version of package B that you can explicitly depend on.

-Iavor



On Mon, Aug 20, 2012 at 7:11 AM, Brent Yorgey byor...@seas.upenn.eduwrote:

 On Thu, Aug 16, 2012 at 06:07:06PM -0400, Joey Adams wrote:
  On Wed, Aug 15, 2012 at 3:38 PM, Bryan O'Sullivan b...@serpentine.com
 wrote:
   I propose that the sense of the recommendation around upper bounds in
 the
   PVP be reversed: upper bounds should be specified only when there is a
 known
   problem with a new version of a depended-upon package.
 
  I, too, agree.  Here is my assortment of thoughts on the matter.
 
  Here's some bad news: with cabal 1.14 (released with Haskell Platform
  2012.2), cabal init defaults to bounds like these:
 
build-depends:   base ==4.5.*, bytestring ==0.9.*,
http-types ==0.6.*

 I'm not sure why you think this is bad news.  I designed this to
 conform exactly to the current PVP.  If the PVP is changed then I will
 update cabal init to match.

 -Brent

 ___
 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] Fundeps and overlapping instances

2012-06-01 Thread Iavor Diatchki
Hello,

There is no problem if an instances uses a type family in it's
assumption---the instances should be accepted only if GHC can see enough of
the definition of the type family to ensure that the functional dependency
holds.  This is exactly the same as what it would do to check that a super
class constraint holds.

-Iavor


On Wed, May 30, 2012 at 11:14 PM, Etienne Laurin etie...@atnnn.com wrote:

 2012/5/31 Iavor Diatchki iavor.diatc...@gmail.com:
  Hello,
 
  the notion of a functional dependency is well established, and it was
 used
  well before it was introduced to Haskell (for example, take a look
  at http://en.wikipedia.org/wiki/Functional_dependency).  So I'd be
 weary to
  redefine it lightly.

 Indeed, GHC's functional dependencies are not the same. I see you have
 already talked about this on the GHC bug tracker.

 http://hackage.haskell.org/trac/ghc/ticket/1241

  1. Check that an instance is consistent with itself.  For example, this
 should be rejected:
 
  instance C a b
 
  because it allows C Int Bool and C Int Char which violate the functional
 dependency.

 This check may not always be as straightforward. When would this be a
 valid instance?

 instance K a b ⇒ C a b

 With a few extra extensions, K could be a type family.

 C currently has the kind (a - b - Constraint), with no mention of
 functional dependencies. Perhaps the kind of C should include the
 functional dependencies of C?

 Etienne Laurin

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


Re: [Haskell-cafe] Fundeps and overlapping instances

2012-05-30 Thread Iavor Diatchki
Hello,

On Wed, Jul 7, 2010 at 2:14 PM, Simon Peyton-Jones simo...@microsoft.comwrote:

  We can’t permit overlap for type families because it is *unsound *to do
 so (ie you can break “well typed programs don’t go wrong”). But if it’s
 unsound for type families, it would not be surprising if it was unsound for
 fundeps too.  (I don’t think anyone has done a soundness proof for fundeps
 + local constraints + overlapping instances, have they?)  And indeed I
 think it is.


It would be unsound only if the functional dependencies are not checked
properly (which, as you say, is similar to the check for type families).
 Here is an example of a sound overlap:

class C a b | a - b
instance C String Char
instance C [a] a

Indeed, it would be OK to allow this sort of overlap for type families too,
although there it would not be useful, because the more general case
already provides the same information as the more specific one.   In the
case of overlapping instances, the more specific instance might provide a
different implementation for the class methods, as usual.  (disclaimer:
 I'm not a fan of overlapping instancesI think that some of
the alternative proposals, such as the instance chains work, are nicer, but
one would have to do same sort of checks there too).


**

 Imagine a system “FDL” that has functional dependencies and local type
 constraints.  The big deal about this is that you get to exploit type
 equalities in **given** constraints.  Consider Oleg’s example, cut down a
 bit:

 ** **

 class C a b | a - b

 instance C Int Bool

 newtype N2 a = N2 (forall b. C a b = b)

 ** **

 t2 :: N2 Int

 t2 = N2 True

 ** **

 We end up type-checking (True :: forall b. C Int b = b).   From the
 functional dependency we know that (b~Bool), so the function should
 typecheck.  GHC rejects this program; FDL would not.

 ** **

 But making use of these extra equalities in “given” constraints is quite
 tricky.  To see why look first at Example 1:  

 ** **

 *module* X where

class C a b | a - b

 ** **

data T a where

  MkT :: C a b = b - T a

 ** **

 ** **

 *module* M1 where

   import X

   instance C Int Char where ...

   f :: Char - T Int

   f c = MkT c

 ** **

 *module* M2 where

   import X

   instance C Int Bool

   g :: T Int - Bool

   g (MkT x) = x

 ** **

 *module* Bad where

   import M1

   import M2

   bad :: Char - Bool

   bad = g . f

 ** **

 This program is unsound: it lets you cast an Int to a Bool; result is a
 seg-fault. 


 

 You may say that the problem is the inconsistent functional dependencies
 in M1 and M2.  But GHC won’t spot that.  For type families, to avoid this
 we “*eagerly*” check for conflicts in type-family instances.  In this
 case the conflict would be reported when compiling module Bad, because that
 is the first time when both instances are visible together.

 **

So any FDL system should also make this eager check for conflicts.


I completely agree with this---we should never allow inconsistent instances
to exist in the same scope.



 

 ** **

 What about overlap?  Here’s Example 2: 

 ** **

 {-# LANGUAGE IncoherentInstances #-}

 *module* Bad where

   import X

   -- Overlapping instances

   instance C Int Bool -- Instance 1

   instance C a [a]   -- Instance 2

 ** **

   f :: Char - T Int

   f c = MkT c   -- Uses Instance 1

 ** **

   g :: T a - a

   g (MkT x) = x-- Uses Instance 2

 ** **

   bad :: Char - Int

   bad = g . f

 **


As in the above example, this program violates the functional dependency on
class C and should be rejected, because the two instances are not
consistent with each other.



 But at the moment GHC makes an exception for **existentials**.  Consider
 Example 3:

 ** **

   class C a b | a - b

 ** **

   -- Overlapping instances

   instance C Int Bool -- Instance 1

   instance C a [a]   -- Instance 2

 ** **

   data T where

 MkT :: C a b = a - b - T

 ** **

   f :: Bool - T

   f x = MkT (3::Int) x  -- Uses Instance 1

 ** **

   g :: T - T

   g (MkT n x) = MkT n (reverse x)   -- Uses Instance 2

 ** **

   bad :: Bool - T

   bad = g . f

 ** **

 This program is malformed for the same reason as the previous one: the two
instances violate the functional dependency on the class.



 ** **

 But even nuking IncoherentInstances altogether is not enough.  Consider
 this variant of Example 3, call it Example 4:

  *module* M where

   class C a b | a - b

 ** **

   instance C a [a]   -- Instance 2

 ** **

   data T where

 MkT :: C a b = a - b - T

 ** **

   g :: T - T

   g (MkT n x) = MkT n (reverse x)   -- Uses Instance 2 

 ** **

 *module* 

Re: [Haskell-cafe] Fundeps and overlapping instances

2012-05-30 Thread Iavor Diatchki
Hello,

the notion of a functional dependency is well established, and it was used
well before it was introduced to Haskell (for example, take a look at
http://en.wikipedia.org/wiki/Functional_dependency).  So I'd be weary to
redefine it lightly.
Note that placing a functional dependency constraint is just one way to
allow class methods that don't mention all class variables.  If the
instances for the class do not satisfy the functional dependency (as in
your example), you can refactor your class hierarchy, instead.  For example:

class D a where  k :: a
class D a = C a b where  f :: a - b

instance D Int where k = 2
instance C Int b where f _ = Nothing

I hope this helps,
-Iavor



On Wed, May 30, 2012 at 1:31 PM, Etienne Laurin etie...@atnnn.com wrote:

 Hello,

 I disagree with your example.

  1. Check that an instance is consistent with itself.  For example, this
  should be rejected:
 
  instance C a b
 
  because it allows C Int Bool and C Int Char which violate the functional
  dependency.

 Functional dependencies are not used to pick types, they are used to
 pick instances.

 class C a b | a → b where
  k ∷ a
  f ∷ a → Maybe b

 The functional dependency allows you to have a method such as k that
 doesn't use all the arguments of the class.

 I expect to be able to make a instance that works for any b.

 instance C Int b where
  k = 2
  f _ = Nothing

 Etienne Laurin

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


Re: [Haskell-cafe] Data Kinds and superfluous (in my opinion) constraints contexts

2012-05-17 Thread Iavor Diatchki
Hi,

It is quite likely that the error that you are getting with approach 2 is
because when you are constructing the `Combinator` value, there is not
enough type information to figure out how to solve the constraint (and it
sounds like this happens because there is not enough type information to
reduce the type function).   The fix depends on the concrete program but it
might be something as simple as adding a type signature somewhere.

Note, again, that it is not sufficient to know that the constraint could be
solved for any type of the appropriate kind: we need to actually solve the
constraint so that we can determine what the program should do.

The difference between the two `data` definitions is that the second one
uses a technique called _existential quantification_, which hides the
type `s`.  If this type appears nowhere else in the surrounding expressions
and the constraint could not be solved, then the constraint is ambiguous.
I could explain that in more detail, if it is unclear please ask.

Happy hacking,
-Iavor







On Thu, May 17, 2012 at 4:18 AM, Serguey Zefirov sergu...@gmail.com wrote:

 I can write something like that:

 data Combinator s a where
Combinator :: Class (TypeFamExpr s) = ... - Combinator s a

 And I cannot write something like that:
 data Combinator a where
Combinator :: Class (TypeFamExpr s) = .mentions s.. - Combinator a

 If my TypeFamExpr does have type variables, I get a wild type error
 messages that mentions partially computed TypeFamExpr as an argument
 to constraint.


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


Re: [Haskell-cafe] Data Kinds and superfluous (in my opinion) constraints contexts

2012-05-16 Thread Iavor Diatchki
Hello,

The context in your example serves an important purpose: it records the
fact that the behavior of the function may differ depending on which type
it is instantiated with.   This is quite different from ordinary
polymorphic functions, such as `const` for example,  which work in exactly
the same way, no matter how you instantiate them.   Note that it doesn't
matter that we can solve the constraint for all types of kind `D`---the
constraint is there because we can't solve it _uniformly_ for all types.

-Iavor
PS: As an aside, these two forms of polymorphism are sometimes called
parametric (when functions work in the same way for all types), and
ad-hoc (when the behavior depends on which type is being used).




On Sun, May 6, 2012 at 9:48 AM, Serguey Zefirov sergu...@gmail.com wrote:

 I decided to take a look at DataKinds extension, which became
 available in GHC 7.4.

 My main concerns is that I cannot close type classes for promoted data
 types. Even if I fix type class argument to a promoted type, the use
 of encoding function still requires specification of context. I
 consider this an omission of potentially very useful feature.

 Example is below.

 -
 {-# LANGUAGE TypeOperators, DataKinds, TemplateHaskell, TypeFamilies,
 UndecidableInstances #-}
 {-# LANGUAGE GADTs #-}

 -- a binary numbers.
 infixl 5 :*
 data D =
D0
|   D1
|   D :* D
deriving Show

 -- encoding for them.
 data EncD :: D - * where
EncD0 :: EncD D0
EncD1 :: EncD D1
EncDStar :: EncD (a :: D) - EncD (b :: D) - EncD (a :* b)

 -- decode of values.
 fromD :: D - Int
 fromD D0 = 0
 fromD D1 = 1
 fromD (d :* d0) = fromD d * 2 + fromD d0

 -- decode of encoded values.
 fromEncD :: EncD d - Int
 fromEncD EncD0 = 0
 fromEncD EncD1 = 1
 fromEncD (EncDStar a b) = fromEncD a * 2 + fromEncD b

 -- constructing encoded values from type.
 -- I've closed possible kinds for class parameter (and GHC
 successfully compiles it).
 -- I fully expect an error if I will try to apply mkD to some type
 that is not D.
 -- (and, actually, GHC goes great lengths to prevent me from doing that)
 -- By extension of argument I expect GHC to stop requiring context
 with MkD a where
 -- I use mkD constant function and it is proven that a :: D.
 class MkD (a :: D) where
mkD :: EncD a
 instance MkD D0 where
mkD = EncD0
 instance MkD D1 where
mkD = EncD1
 -- But I cannot omit context here...
 instance (MkD a, MkD b) = MkD (a :* b) where
mkD = EncDStar mkD mkD

 data BV (size :: D) where
BV :: EncD size - Integer - BV size

 bvSize :: BV (size :: D) - Int
 bvSize (BV size _) = fromEncD size

 -- ...and here.
 -- This is bad, because this context will arise in other places, some of
 which
 -- are autogenerated and context for them is incomprehensible to human
 -- reader.
 -- (they are autogenerated precisely because of that - it is tedious
 and error prone
 -- to satisfy type checker.)
 fromIntgr :: Integer - BV (size :: D) -- doesn't work, but desired.
 -- fromIntgr :: MkD size = Integer - BV (size :: D) -- does work,
 but is not that useful.
 fromIntgr int = BV mkD int

 -

 ___
 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] ANN: hp2html, a tool for viewing GHC heap-profiles

2012-02-20 Thread Iavor Diatchki
Hello,

On Mon, Feb 20, 2012 at 7:03 PM, Johan Tibell johan.tib...@gmail.comwrote:


 Looks really nice.

Thanks!


 The hovering behavior is nice, but I'd like to see
 the legend as well. It makes it quicker when you want to get a quick
 overview of what types there are, as the eye can travel back-and-forth
 between the graph and the legend.


I started with the legend but it was too big on the program that i was
profiling, so i switched to the hovering mode. I agree that it is not
optimal. Perhaps there's a way to instruct flot to show only some of the
entries or, better, order them in some useful way.  I'm no flot expert, so
ideas (or patches) on how to do it would be most appreciated!

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


Re: [Haskell-cafe] instance Enum Double considered notentirelygreat?

2011-09-27 Thread Iavor Diatchki
Hello,

On Tue, Sep 27, 2011 at 8:49 AM, Chris Smith cdsm...@gmail.com wrote:
 You could calculate the entire range using Rational and then convert
 each individual value after the fact.  That doesn't seem like a
 reasonable default, since it has a runtime performance cost.  Of course
 you're welcome to do it when that's what you need.

 last ([0.1, 0.2 .. 0.5]) == 0.5
 False

 last (map fromRational [0.1, 0.2 .. 0.5]) == 0.5
 True


As Ross pointed out in a previous e-mail the instance for Rationals is
also broken:

 last (map fromRational [1,3 .. 20])
 21.0

-Iavor

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


Re: [Haskell-cafe] Could not deduce ... using functional dependencies with GHC7

2011-03-18 Thread Iavor Diatchki
Hi,
that's a bug in GHC---it erroneously accepts polymorphic instances which
violate the FD of a class.
-Iavor

On Fri, Mar 18, 2011 at 7:08 AM, Daniel Fischer 
daniel.is.fisc...@googlemail.com wrote:

 On Friday 18 March 2011 14:40:40, JP Moresmau wrote:
  Thanks to you all, I think I understand better.
  instance Search Id Id where
search _ _ i = only (FoundId i)
 
  Is too restrictive on the first type, so declaring instead:
  instance Search id Id where
search _ _ i = only (FoundId i)

 Not sure what GHC does with that, but at least in spirit that violates the
 FunDep of

 class Search id a | a - id where ...

 Even if it works now, it may well not work in the future.
 I'd go for a more stable solution respecting the intent of FunDeps
 (i.e. there should only be one type t with an instance Search t Id).

 
  Fixed the issue!! Now the initial id is not Id and everybody is
  happy (and the code still seems to work as intended)
 
  thanks again
 
  JP

 ___
 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] Unrecognized function symbols in .prof

2011-02-07 Thread Iavor Diatchki
Hi Lee,
I would also guess that these are probably the implementations of equality
in the given modules.

One way to test this would be to name the equality function explicitly.  For
example, something like this:

myEquality x y = ...
instance Eq MyType where (==) = myEquality

Another option would be to look at the generated core by using -ddump-simpl
when compiling. This will generate a whole bunch of output, which you can
redirect to a file and the search for the mysterious symbols inside.

Hope this helps,
-Iavor


On Mon, Feb 7, 2011 at 11:12 PM, Lee Pike leep...@gmail.com wrote:

 Hi,

 I am profiling a Haskell program using GHC, and after executing the
 program with +RTS -p, I get a .prof file that lists the cost centers
 of the program.  Some of the cost centers listed are for function
 symbols that do not exist in the given module.  For example, I have in
 my .prof file:

 COST CENTRE  MODULE   %time %alloc
 ==_a2MTFoo   19.80.0
 ==_a2R8 Foo   17.80.0
 ==_a2Bg Bar   13.70.0
   

 It appears these are generated symbols; how do I find out what those
 function symbols correspond to?  (In this case, my assumption is that
 these symbols refer to instances of the Eq class, but I'm not sure.)

 [I couldn't find anything about this in the GHC online documentation
 or via Googling, but sorry if I missed it.]

 Thanks,
 Lee

 ___
 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] Deep concatenation [Was: Incorrectly inferring type [t]]

2010-12-31 Thread Iavor Diatchki
Hello,
I just noticed that the instances for this example look more readable when
written with two recently proposed Haskell extensions. Perhaps we should
consider implementing these in GHC?

Using chain instances: (http://web.cecs.pdx.edu/~mpj/pubs/instancechains.pdf
)

 instance DeepFlat a b = DeepFlat [a] b where dflat = concatMap dflat
else  DeepFlat a   a where dflat = id
else fails

And with the fun. deps. in functional notation: (
http://web.cecs.pdx.edu/~mpj/pubs/fundeps-design.pdf)

 instance DeepFlat [a] (DeepFlat a) where dflat = concatMap dflat
 else DeepFlat a   awhere dflat = id
 else fails

Happy new year!
-Iavor





On Thu, Dec 30, 2010 at 3:52 AM,  o...@okmij.org wrote:

 William Murphy wrote:
 I've spent a lot of time trying to write a version of concat, which
 concatenates lists of any depth:

 It is a little bit more involved, but quite possible. The code is not
 much longer than the one you wrote (essentially, three lines: one
 class and two instance declarations). Here is the complete code:


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

 module DeepFlat where


 class DeepFlat a b | a - b where
dflat :: [a] - [b]

 -- If we flatten a list of lists
 instance DeepFlat a b = DeepFlat [a] b where
dflat = concatMap dflat

 -- If we are given a list of non-lists
 instance a ~ b = DeepFlat a b where
dflat = id

 test1 = dflat abracadabra
 -- abracadabra

 test2 = dflat [abra,cadabra]

 test3 = dflat [[ab,ra],[cad,abra]]
 test4 = dflat [[[a,b],[ra]],[[cad,abra]]]




 ___
 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] Proof in Haskell

2010-12-21 Thread Iavor Diatchki
Hi Patrick,

Indeed, you cannot really write proofs in Haskell because it is just
an ordinary (more or less) programming language and not a theorem
prover. (As an aside: you could write tests, i.e. properties which
may or may not be theorems about your program, and test them on random
data (see QuickCheck), or exhaustively---if you managed to test a
property for all possible inputs, then you have essentially proved
it.).

Now about dependent types.  Some programming languages have very
expressive type systems (even more so then Haskell!) and they allow
for types which are parameterized by values.   Such types are called
dependent types.  Here is an example:

decrement :: (x :: Int) - (if x  0 then Int else String)
decrement x = if x  0 then x - 1 else Cannot decrement

This function maps values of type Int to either Ints or Strings.
 Note that the _type_ of the result of the function depends on the
_value_ of the input, which is why this function has a dependent type.

It turns out---and this is not at all obvious at first---that
languages with dependent types (and some other features) are suitable
not only for writing programs but, also, for proving theorems.
Theorems are expressed as types (often, dependent types), while proofs
are programs inhabiting the type of the theorem.  So, true theorems
correspond to types which have some inhabitants (proofs), while
false theorems correspond to empty types.

The correspondence between proofs-theorems and programs-types is
known as the Curry-Howard isomorphism.  Examples of some languages
which use depend types are Coq, Agda, and Cayenne.

I hope that this helps,
-Iavor

PS: The foralls in your example are just depend function types:  in
this setting, to prove forall (x :: A). P x amounts writing a
function of type: (x :: A) - P x.  In other words, this is a
function, that maps values of type A to proofs of the property.
Because the function can be applied to any value of type A, we have
prove the result forall (x::A). P x).   The dependent type arises
because the property depends on the value in question.





On Tue, Dec 21, 2010 at 8:15 AM, aditya siram aditya.si...@gmail.com wrote:
 I don't know the formal definition, but dependent types seem analogous
 to checking an invariant at runtime.
 -deech

 On Tue, Dec 21, 2010 at 5:53 AM, Patrick Browne patrick.bro...@dit.ie wrote:
 Hi,
 In a previous posting[1] I asked was there a way to achieve a proof of
 mirror (mirror x) = x

 in Haskell itself. The code for the tree/mirror is below:

  module BTree where
  data Tree a = Tip | Node (Tree a) a (Tree a)

  mirror ::  Tree a - Tree a
  mirror (Node x y z) = Node (mirror z) y (mirror x)
  mirror Tip = Tip

 The reply from Eugene Kirpichov was:
 It is not possible at the value level, because Haskell does not
 support dependent types and thus cannot express the type of the
 proposition
 forall a . forall x:Tree a, mirror (mirror x) = x,
 and therefore a proof term also cannot be constructed.

 Could anyone explain what *dependent types* mean in this context?
 What is the exact meaning of forall a and forall x?

 Thanks,
 Pat
 [1] http://www.mail-archive.com/haskell-cafe@haskell.org/msg64842.html








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


Re: [Haskell-cafe] [Haskell] Functor = Applicative = Monad

2010-12-16 Thread Iavor Diatchki
Hello,

I think that we should make both changes (make Applicative a
super-class of Monad, and remove the fail method from Monad).  Code
will break but we can fix it.

By the way, just for reference, the proposal to have a separate
failure class and using it in the do notation, is how things used to
be back in Haskell 1.4 (one version before Haskell 98).  For the
curious, take a look at page 21 of
http://haskell.org/definition/haskell-report-1.4.ps.gz

-Iavor


On Thu, Dec 16, 2010 at 3:57 PM, Lennart Augustsson
lenn...@augustsson.net wrote:
 IO

 On Thu, Dec 16, 2010 at 6:03 PM, John Smith volderm...@hotmail.com wrote:

 On 15/12/2010 14:31, Lennart Augustsson wrote:

 Yes, I think there should be a MonadFail distinct from MonadPlus.
 Some types, like IO, are not in MonadPlus, but have a special
 implementation of the fail method.

 Personally, I think fail should just be removed, but that would break
 existing code.
 The fail method was introduced for the wrong reasons (better error
 messages was the excuse).

 Which other monads (other than MonadPlus subclasses) define fail?


 ___
 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


Re: [Haskell-cafe] Categorical description of systems with dependent types

2010-12-02 Thread Iavor Diatchki
Hi,
Bart Jacobs's book Categorical Logic and Type Theory has a
categorical description of a system with dependent types (among
others).  The book is fairly advanced but it has lots of details about
the constructions.
Hope this helps,
-Iavor

On Thu, Dec 2, 2010 at 8:18 AM,  rocon...@theorem.ca wrote:
 On Thu, 2 Dec 2010, Petr Pudlak wrote:

 Hi,

 recently, I was studying how cartesian closed categories can be used to
 describe typed functional languages. Types are objects and morphisms are
 functions from one type to another.

 Since I'm also interested in systems with dependent types, I wonder if
 there is a categorical description of such systems. The problem (as I see
 it) is that the codomain of a function depends on a value passed to the
 function.

 I'd happy if someone could give me some pointers to some papers or other
 literature.

 Voevodsky talks about the category of contexts in
 http://www.mefeedia.com/watch/31778282, which I understand is described in
 more detail in Semantics of type theory : correctness, completeness, and
 independence results by Thomas Streicher.

 --
 Russell O'Connor                                      http://r6.ca/
 ``All talk about `theft,''' the general counsel of the American Graphophone
 Company wrote, ``is the merest claptrap, for there exists no property in
 ideas musical, literary or artistic, except as defined by statute.''

 ___
 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] Categorical description of systems with dependent types

2010-12-02 Thread Iavor Diatchki
Hi,
You have it exactly right, and I don't think that there's a
particularly deep reason to prefer the one over the other.  It seems
that computer science people
tend to go with the (product-function) terminology, while math people
seem to prefer the (sum-product) version, but it is all largely a
matter of taste.
-Iavor


On Thu, Dec 2, 2010 at 11:03 AM, Larry Evans cppljev...@suddenlink.net wrote:
 On 12/02/10 11:19, Iavor Diatchki wrote:
 Hi,
 Bart Jacobs's book Categorical Logic and Type Theory has a
 categorical description of a system with dependent types (among
 others).  The book is fairly advanced but it has lots of details about
 the constructions.
 Hope this helps,
 -Iavor


 Page 586 of Jacobs' book mentions dependent products and dependent sums.
 What confuses me is that Nuprl defines the dependent product as
 a dependent function:


 http://www.cs.cornell.edu/Info/People/sfa/Nuprl/NuprlPrimitives/Xfunctionality2_doc.html

 and the dependent sum as the dependent product:


 http://www.cs.cornell.edu/Info/People/sfa/Nuprl/NuprlPrimitives/Xpairs_doc.html

 I sorta see that because the disjoint sum (i.e. the dependent product
 in Nuprl terms) is actually a pair of values, the discriminant (1st
 part) and the value whose type depends on the value of the discriminant.
 And I can see Nuprl's choice to call the dependent product as a
 dependent function because passing an index to this function returns
 a value whose type is dependent on the index. This is just like
 the value constructed by a haskell datatypes with field labels:

  data Record = MkRec { f1::T1, f2::T2, ..., fn::Tn }
  r = MkRec{ f1 = t1, f2 = t2,..., fn = tn}

 However, instead of r as the dependent function, the fields are the
 functions:

   fi r :: Ti,  for i=1...n

 instead of Nuprl's notion:

   r fi :: Ti,  for i=1...n

 Anybody know a good reason why the categorical and nuprl terms
 differ, leading, to (at least in my case) a bit of confusion?


 -Larry




 ___
 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 instance class with functional dependency?

2010-11-26 Thread Iavor Diatchki
Hi,
It sounds like your use of `ioctl'' at topIO.hs:21:35-60 is passing
an Int as the 3rd argument to ioctl, when your instance
declaration states that this argument should be a C'winsize.
-Iavor

On Wed, Nov 24, 2010 at 11:27 PM, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 Hi,
  In System.Posix.IOCtl, there is such a class:
 class Storable d = IOControl req d | req - d where
 ioctlReqSource :: req - CInt
  How to instance it? I do it as:
 data TIOCGWINSZ = TIOCGWINSZ

 #starttype struct winsize
 #field ws_row , CUShort
 #field ws_col , CUShort
 #field ws_xpixel , CUShort
 #field ws_ypixel , CUShort
 #stoptype

 instance IOControl TIOCGWINSZ C'winsize where
  ioctlReq _ = #const TIOCGWINSZ

  Then I got:
 topIO.hs:19:0:
    Couldn't match expected type `C'winsize'
           against inferred type `Int'
    When using functional dependencies to combine
      IOControl
        (Foreign.C.Types.CUShort
         - Foreign.C.Types.CUShort
         - Foreign.C.Types.CUShort
         - Foreign.C.Types.CUShort
         - C'winsize)
        Int,
        arising from a use of `ioctl'' at topIO.hs:21:35-60
      IOControl
        (Foreign.C.Types.CUShort
         - Foreign.C.Types.CUShort
         - Foreign.C.Types.CUShort
         - Foreign.C.Types.CUShort
         - C'winsize)
        C'winsize,
        arising from a use of `ioctl'' at topIO.hs:20:12-37
    When generalising the type(s) for `main'
 --
 竹密岂妨流水过
 山高哪阻野云飞
 ___
 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] Sifflet dependencies

2010-08-16 Thread Iavor Diatchki
Hi,
according to this page:
http://hackage.haskell.org/package/pango-0.11.0
pango should work with cairo 0.11.0 (or any other 0.11.* version)

So it seems that the problem is that cabal tried to use pango-0.11.1,
and I am guessing that it does not backtrack and try an older version
if a build fails (which is reasonable).  So why did Cabal choose
pango-0.11.1?  Because gtk-0.11.0 claims to work with _any_ 0.11.*
version of pango and cairo, so Cabal just picked the latest one.

Therefore, the problem seems to be with the dependencies of gtk-0.11.0
and pango-0.11.0 (indeed, later versions of gtk have more precise
dependencies).   Unfortunately, we have no way of improving the
dependencies of a package without changing its version, which suggests
that it is never safe to depend on gtk-0.11.0.  This might be
something that we should look into, but in the meantime,  it may be
better to make sifflet depend on a later specific version of gtk
(e.g.,  0.11.2) rather then claiming that works with any 0.11.*
version.

By the way, it is unfortunate that packages which only differ in their
third version field (e.g., 0.11.0 vs 0.11.1) are incompatible with
each other, I thought that the recommendation was to increase the
second version field to avoid that.

-Iavor



On Mon, Aug 16, 2010 at 12:56 PM, Don Stewart d...@galois.com wrote:
    $ cabal update
    Downloading the latest package list from hackage.haskell.org

    $ cabal install sifflet
    Resolving dependencies...
    cabal: cannot configure pango-0.11.1. It requires cairo =0.11.1  0.12 
 and glib =0.11.1  0.12
    For the dependency on cairo =0.11.1  0.12 there are these packages:

    cairo-0.11.1. However none of them are available.
    cairo-0.11.1 was excluded because sifflet-lib-1.0 requires cairo ==0.11.0
    cairo-0.11.1 was excluded because cairo-0.11.0 was selected instead
    cairo-0.11.1 was excluded because sifflet-1.0 requires cairo ==0.11.0

    For the dependency on glib =0.11.1  0.12 there are these packages:
    glib-0.11.1. However none of them are available.
    glib-0.11.1 was excluded because sifflet-lib-1.0 requires glib ==0.11.0
    glib-0.11.1 was excluded because glib-0.11.0 was selected instead
    glib-0.11.1 was excluded because sifflet-1.0 requires glib ==0.11.0


 So that's pretty simple. 'sifflet' requires cairo ==0.11.0 and pango. But 
 since
 pango doesn't work with cairo 0.11.0, the package can't be built. The solution
 is to ask the sifflet author to adjust the dependencies to be more flexible.

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

 Those specific versions of packages are overly constrained. They should 
 follow the PVP, and be thus,

    0.11.*

 -- Don
 ___
 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] MonadLib usage

2010-07-18 Thread Iavor Diatchki
Hi,
When using monadLib, I use newtype deriving to get the Functor,
Applicative, and Monad instances for my custom newtyped monad.  Those
work just fine, and there is nothing unsafe about them.

For a custom monad, I usually don't derive MonadLib's effect classes
directly.  Instead, I tend to define new operations specific to the
monad.  This has the benefit of abstracting away internal
implementation details, which makes it easier to change or extend the
monad later.  For example, to implement a monad which provides a
source of unique identifiers, I might use a state transformer:

newtype MyMonad a = MyMonad (StateT Int ...)

Now, instead of deriving a StateM instance, I would define a custom
operation for obtaining new names, something like this:

newName :: MyMonad Name
newName = MyMonad (do x - get; set (x + 1); return (mkName x))

This is why GHC's limitation of deriving only the last argument of a
class has not been too much of a problem for me.   On a more general
note, I don't think that there is anything particularly difficult
about lifting the deriving only the last argument restriction,
except for picking a reasonable notation and finding a willing
contributor to hack it up.  (Generalized generalized deriving anyone
:-) ?)  If you are interested in some of the issues with generalized
newtype deriving in general, this thread has some examples:
http://osdir.com/ml/haskell-cafe@haskell.org/2010-03/msg00388.html

Hope that this helps,
-Iavor

On Sun, Jul 18, 2010 at 9:59 AM, Emil Melnikov emilm...@gmail.com wrote:
 On 2010, July 18, 23:27
 Ivan Lazar Miljenovic ivan.miljeno...@gmail.com wrote:

 When discussing a similar issue with Manuel Chakravarty, he convinced me
 that cunning newtype deriving is actually rather bad in practice and
 shouldn't be used as there's a lack of proofs or some such (I can't
 remember the arguments, but I remember being convinced by them :p).

 Hmm...  I can't imagine how it is possible, since new and
 original types are isomorphic.

 Can you give me some pointers to this discussion (links or
 keywords)?

 --
 Emil.
 ___
 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] Design for 2010.2.x series Haskell Platform site

2010-07-18 Thread Iavor Diatchki
The changelog feature would be very useful---dumping repository
history is no substitute for it because it is too low level (contains
too much noise).  Generally, I would expect that whoever makes the
release of a piece of software should be in charge of writing a
summary of what's new since the last release.  In the case of the
Haskell platform I would expect just a highlight of major new things
(e.g., adding/removing new packages, or updates that solve some well
known problem, or add an interesting new feature).

It would be nice to standardize on the format of a CHANGES file: then
hackage could render it nicely, and the HP could automatically compute
a mashup of the CHANGES files for the packages that it distributes.

-Iavor

On Sun, Jul 18, 2010 at 11:16 AM, Don Stewart d...@galois.com wrote:
 dave:
 
  Actually, it just got trivial:
 
     $ diffcabal old-platform.cabal haskell-platform.cabal
     Cabal 1.8.0.2 - 1.8.0.6
     QuickCheck 2.1.0.3 - 2.1.1.1
 [etc.]

 Okay, so where do I go to find out the difference between, say,
 QuickCheck 2.1.0.3 and 2.1.1.1?

 --

 Currently, the way to do this is:

    * Visit:
        http://hackage.haskell.org/package/QuickCheck-2.1.1.1

    * Visit:
        http://hackage.haskell.org/package/QuickCheck-2.1.0.3

 And note any differences in the documentation.

 Hackage doesn't yet provide support for changelogs. However, it does
 provide support for repository links, from which we can construct a
 changelog. That's right: you have to read each repo to get the full
 changelog, unless the author has been nice to add it to the .cabal file.

 I think what we need is:

    * Every HP package has to have a .cabal file with the source
      repository type and link.

 If we have the source repo and type, I can write a tool to extract the
 changelogs between each release automatically.

 -- Don

 E.g.
    * darcs
    * http://code.haskell.org/QuickCheck/

 From here we can:

    $ darcs get http://code.haskell.org/QuickCheck/

 And running darcs changes:

    Thu Jun 17 07:52:28 PDT 2010
    * Bump version number

    Thu Jun 17 06:53:22 PDT 2010
    * Change of plan: look at GHC's version number instead of the
    * version of base when deciding whether to depend on the ghc
    * library

    Thu Jun 17 06:40:22 PDT 2010
    * Added README to the source distribution

    Thu Jun 17 06:33:38 PDT 2010
    * Updated the README

    Thu Jun 17 06:33:27 PDT 2010
    * GHC 6.8 support

    Thu Jun 17 06:13:54 PDT 2010
    * Added support for the new base library (I hope!)

    Thu Jun 17 02:59:14 PDT 2010
    * Remove the pointless last field of the version number

    Thu Jun 17 02:32:46 PDT 2010
    * Fix homepage link

    Wed Apr 28 08:04:02 PDT 2010
    * Added my file of weird examples

    Thu Apr 22 08:37:11 PDT 2010
    * Bump the version number

    Thu Apr 22 08:27:39 PDT 2010
    * Don't force the shrink list too early

    Fri Jan 22 10:25:20 PST 2010
    * Added an Arbitrary instance for complex numbers

    Tue Jan 12 07:34:00 PST 2010
    * Changed the way that size increases

    Tue Jan 12 07:33:52 PST 2010
    * Changed the cabal version number

    Tue Jan 12 06:47:25 PST 2010
    * Skip shrinking on interrupt

    Tue Jan 12 06:47:04 PST 2010
    * Added isInterrupt to Test.QuickCheck.Exception




 ___
 Haskell-platform mailing list
 haskell-platf...@projects.haskell.org
 http://projects.haskell.org/cgi-bin/mailman/listinfo/haskell-platform

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


Re: [Haskell-cafe] corner case in Text.JSON 0.4.3

2010-05-12 Thread Iavor Diatchki
Hi,
I think it was probably I who wrote this, so I'll take the blame :-)
It seems like a genuine bug, where we are not checking for strings
that are not terminated.  Thanks for spotting it, and also for the
patch!  I'll try to update the package soon.
-Iavor

On Wed, May 12, 2010 at 12:53 PM, Martin Hilbig mar...@mhilbig.de wrote:
 hi,

 since i got no answer from the maintainer, maybe someone else can take care
 of it, or at least point out, what i did wrong.

 so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

  Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 indeed ghc warned:

  [5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs,
 dist/build/Text/JSON/String.o )

  Text/JSON/String.hs:127:4:
      Warning: Pattern match(es) are non-exhaustive
               In a case alternative: Patterns not matched: []

 from looking at the code i couldn't see how this would ever happen, but you
 can reproduce it be running the files from [2]:

  $ ./test  problem
  Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString
 (JSONString {fromJSString = is}),JSString (JSONString {fromJSString =
 some}),JSString (JSONString {fromJSString = json}),JSObject (JSONObject
 {fromJSObject = [(that,JSString (JSONString {fromJSString =
 works}))]})])
 test: Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 the patch i put there fixes it (at least for me) to return an Error instead
 of dying:

  $ ./test  problem
  Ok (JSArray [JSString (JSONString {fromJSString = this}),JSString
 (JSONString {fromJSString = is}),JSString (JSONString {fromJSString =
 some}),JSString (JSONString {fromJSString = json}),JSObject (JSONObject
 {fromJSObject = [(that,JSString (JSONString {fromJSString =
 works}))]})])
  Error Unexpected end of String: does
  Error Malformed JSON: invalid token in this context not\]
  test: stdin: hGetLine: end of file

 have fun
 martin hilbig

 [1]: http://hackage.haskell.org/package/json
 [2]: http://friendpaste.com/3IvnChRMoczf0mIKpOtrYE
 ___
 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] corner case in Text.JSON 0.4.3

2010-05-12 Thread Iavor Diatchki
Hi,
it seems that this was already fixed in the repo, I've put a new
version (0.4.4) on hackage.  Thanks, again, for spotting this!
-Iavor

On Wed, May 12, 2010 at 1:24 PM, Daniel Fischer
daniel.is.fisc...@web.de wrote:
 On Wednesday 12 May 2010 21:53:41, Martin Hilbig wrote:
 hi,

 since i got no answer from the maintainer, maybe someone else can take
 care of it, or at least point out, what i did wrong.

 so, i recently stumbled upon some error while using Text.JSON 0.4.3 [1]:

    Text/JSON/String.hs:(127,4)-(137,49): Non-exhaustive patterns in case

 indeed ghc warned:

    [5 of 7] Compiling Text.JSON.String ( Text/JSON/String.hs,
 dist/build/Text/JSON/String.o )

    Text/JSON/String.hs:127:4:
        Warning: Pattern match(es) are non-exhaustive
                 In a case alternative: Patterns not matched: []

 from looking at the code i couldn't see how this would ever happen, but

 readJSString will die a horrible death if the closing quote is missing.
 Your input misses the closing quote, so...

 ___
 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] Re: Asynchronous exception wormholes kill modularity

2010-04-10 Thread Iavor Diatchki
Hello,
It seems that rank-2 types are sufficient to make the more polymorphic types:


{-# LANGUAGE Rank2Types #-}
import Control.Exception

data Mask = Mask (forall a. IO a - IO a)

mask :: (Mask - IO a) - IO a
mask io = do
 b - blocked
 if b
then io (Mask id)
else block $ io (Mask unblock)

restore :: Mask - IO a - IO a
restore (Mask f) a = f a
--

This is useful in an example like this:

forkThen :: IO () - IO a - IO a
forkThen io k = mask $ \m -
  do tid - forkIO (restore m io)
 restore m k `catch` \e -
   do when (e == ThreadKilled) (killThread tid)
  throwIO e

-Iavor


On Thu, Apr 8, 2010 at 1:23 AM, Simon Marlow marlo...@gmail.com wrote:
 On 07/04/2010 18:54, Isaac Dupree wrote:

 On 04/07/10 11:12, Simon Marlow wrote:

 It's possible to mis-use the API, e.g.

 getUnmask = mask return

 ...incidentally,
 unmask a = mask (\restore - return restore) = (\restore - restore a)

 That doesn't work, as in it can't be used to unmask exceptions when they are
 masked.  The 'restore' you get just restores the state to its current, i.e.
 masked, state.

 mask :: ((IO a - IO a) - IO b) - IO b

 It needs to be :: ((forall a. IO a - IO a) - IO b) - IO b
 so that you can use 'restore' on two different pieces of IO if you need
 to. (alas, this requires not just Rank2Types but RankNTypes. Also, it
 doesn't cure the loophole. But I think it's still essential.)

 Sigh, yes I suppose that's true, but I've never encountered a case where I
 needed to call unmask more than once, let alone at different types, within
 the scope of a mask.  Anyone else?

 Cheers,
        Simon
 ___
 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] Re: Asynchronous exception wormholes kill modularity

2010-04-10 Thread Iavor Diatchki
Hello,
I wonder if it might be possible to use just one primitive which atomically
changes the interrupt mask for a thread?  Here is an example of what I'm
thinking:

data MaskingState   = Unmasked
   | MaskedInterruptible
   | MaskedNonInterruptible

-- Atomically changes the interrupt mask for a thread, and returns the old
mask.
setMask:: MaskingState - IO MaskingState
setMask = error primitive?

-- Change the mask for the duration of an IO action.
-- The action is passed the old mask.
scopedSetMask  :: MaskingState - (MaskingState - IO a) - IO a
scopedSetMask m io  = do m1 - setMask m
a  - io m1
setMask m1
return a

-- Change the mask for the duration of an IO action.
scopedSetMask_ :: MaskingState - IO a - IO a
scopedSetMask_ m io = scopedSetMask m $ \_ -
   io
-- Simon's mask:
mask   :: ((IO a - IO a) - IO b) - IO b
mask f  = scopedSetMask MaskedInterruptible $ \m -
   f (scopedSetMask_ m)


-Iavor


On Sat, Apr 10, 2010 at 11:42 AM, Iavor Diatchki iavor.diatc...@gmail.com
wrote:
 Hello,
 It seems that rank-2 types are sufficient to make the more polymorphic
types:

 
 {-# LANGUAGE Rank2Types #-}
 import Control.Exception

 data Mask = Mask (forall a. IO a - IO a)

 mask :: (Mask - IO a) - IO a
 mask io = do
  b - blocked
  if b
then io (Mask id)
else block $ io (Mask unblock)

 restore :: Mask - IO a - IO a
 restore (Mask f) a = f a
 --

 This is useful in an example like this:

 forkThen :: IO () - IO a - IO a
 forkThen io k = mask $ \m -
  do tid - forkIO (restore m io)
 restore m k `catch` \e -
   do when (e == ThreadKilled) (killThread tid)
  throwIO e

 -Iavor


 On Thu, Apr 8, 2010 at 1:23 AM, Simon Marlow marlo...@gmail.com wrote:
 On 07/04/2010 18:54, Isaac Dupree wrote:

 On 04/07/10 11:12, Simon Marlow wrote:

 It's possible to mis-use the API, e.g.

 getUnmask = mask return

 ...incidentally,
 unmask a = mask (\restore - return restore) = (\restore - restore a)

 That doesn't work, as in it can't be used to unmask exceptions when they
are
 masked.  The 'restore' you get just restores the state to its current,
i.e.
 masked, state.

 mask :: ((IO a - IO a) - IO b) - IO b

 It needs to be :: ((forall a. IO a - IO a) - IO b) - IO b
 so that you can use 'restore' on two different pieces of IO if you need
 to. (alas, this requires not just Rank2Types but RankNTypes. Also, it
 doesn't cure the loophole. But I think it's still essential.)

 Sigh, yes I suppose that's true, but I've never encountered a case where
I
 needed to call unmask more than once, let alone at different types,
within
 the scope of a mask.  Anyone else?

 Cheers,
Simon
 ___
 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] Re: Haskell.org re-design

2010-04-07 Thread Iavor Diatchki
Hi everyone,

thanks for your efforts to improve the site!  To be honest, I don't
really like the current design, so here are some suggestions that
might help:

* I find the color scheme a bit bleak;  I'd prefer something more colorful.
* Some graphics might improve the overall style.
* We need to be more consistent in the use of fonts: the current
design has text in almost all combinations of blue, black, orange,
bold, italic, and normal, and at least 3 different font sizes.  This
makes the page complex and somewhat disorganized.
* I realized that this is just a mock-up but there seems to be a lot
of duplication in the content (e.g., multiple links to the Haskell
platform, online interpreter, hackage, GHC).  Avoiding unnecessary
duplication might lead to a simpler and more organized page.
* It would be nice if the page layout provided more visual cues to
separate the bits of the page that are likely to change a lot (e.g.,
news  events) from the more static bits (e.g., downloads,
documentation, community resources, etc.).  Perhaps the more static
bits could be factored into some kind of menu?

Hope that this helps,
-Iavor




On Tue, Apr 6, 2010 at 8:03 PM, Antoine Latter aslat...@gmail.com wrote:
 On Tue, Apr 6, 2010 at 8:22 PM, Thomas Schilling
 nomin...@googlemail.com wrote:
 Ok, last revision for tonight:  http://i.imgur.com/d3ARq.png

 I'm no web design guru, but this is definitely better than what we
 have now. Good job on it.

 Antoine
 ___
 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] Parsers for Text Adventures

2010-01-17 Thread Iavor Diatchki
Hi Mark,

On Sun, Jan 17, 2010 at 5:30 AM, Mark Spezzano
mark.spezz...@chariot.net.au wrote:
 Question: Am I going about this the right way? I want to put together lots of 
 data types like Verb and Noun etc so that I can build a kind of BNF 
 grammar.

Your basic idea to use a datatype is a good one.  You just need to
implement it in a slightly different way.  For example, you could
write a function:

string :: String - Parser ()

Given a string, this function returns a parser that will try to
recognize the string in the input.  If successful, the parser returns
a single trivial result, otherwise it fails (i.e. returns an empty
list of result).

You will also need a function, say (+):

(+) :: Parser a - Parser a - Parser a

This function will apply two parser two the same input and combine
their results.  Now you can write your verb parser:


verb :: Parser Verb
verb = (string jump  return Jump)
 +
   ((string get + string take)  return Get)   --
supports synonyms
+
  ... etc ..

Hope that this helps.
-Iavor
PS: By the way, there are a number of libraries that already implement
such basic parser combinators so you can use one of them if you are
not interested in the actual low level details of how the parser
works.  One such library is parsimony, another is parsec.








 Question: If I am going about this the right way then what do I about the 
 read x bit failing when the user stops typing in a recognised keyword. I 
 could catch the exception, but typing an incorrect sentence is just a typo, 
 not really appropriate for an exception, I shouldn't think. If it IS 
 appropriate to do this in Haskell, then how do I catch this exception and 
 continue processing.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Data.Ring -- Pre-announce

2009-12-31 Thread Iavor Diatchki
Hi,
I usually refer to this structure as a RingBuffer, just an idea.  If
you have the time, I would add rough complexity estimates to the
documentation for the different functions.  Thanks for your work!
Happy new year,
Iavor

On Thu, Dec 31, 2009 at 1:13 PM, John Van Enk vane...@gmail.com wrote:
 I've decided to settle on Data.CircularList. The renamed git repository is
 here:

 http://github.com/sw17ch/data-clist

 On Thu, Dec 31, 2009 at 3:29 PM, Twan van Laarhoven twa...@gmail.com
 wrote:

 John Van Enk wrote:

 Hi Heinrich,

 I think I like Ring more than Necklace or Tom's suggestion of Circular. I
 chose Ring simply because that's what I was searching for when I wanted the
 data structure. The package will be named data-ring, so that should
 hopefully be enough to clue in the user that it's not dealing with the
 mathematical concept.

 The mathematical concept would likely also go in Data, unfortunately. See
 for example Data.Monoid. If someone does at a Ring class sometime, it is
 very likely to go into Data.Ring, which would lead to conflicts. In fact it
 already exists, see the monoids package [1]

 I would prefer the name RingList or CircularList. As long as you put the
 word ring in the package description users will still find it when
 searching on hackage.


 [1]
 http://hackage.haskell.org/packages/archive/monoids/0.1.25/doc/html/Data-Ring.html

 Twan


 ___
 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] Are functional dependencies around to stay?

2009-12-22 Thread Iavor Diatchki
Hi,
Not everyone in the community is keen on replacing functional
dependencies with type families.  My advice would be to use whichever
language construct seems more suitable to your problem and disregard
the occasional posts by people claiming that functional dependencies
are obsolete or deprecated.
-Iavor


On Tue, Dec 22, 2009 at 9:18 AM, Eduard Sergeev
eduard.serg...@gmail.com wrote:

 Hi Stephen,


 Stephen Tetley-2 wrote:
 Currently this seems a more like a rumour than a fact - from [1] Type
 Families and Fun Deps are equivalently expressive which seems a
 worthwhile point to restate.

 I've got the same impresion initially and was keen to use TF in favor to FD.
 And I'm probably missing something here... but here is wiki example which, I
 think, gives an example of the 'difference' I was refering to:
 http://www.haskell.org/haskellwiki/GHC/AdvancedOverlap (see '2 Notes and
 variations', last part).

 As an additional example I can point to Oleg Kiselyov's TypeCast
 implementation (http://okmij.org/ftp/Haskell/deepest-functor.lhs), here is
 its slightly modified version:

 {-# OPTIONS -fglasgow-exts #-}
 {-# OPTIONS -fallow-undecidable-instances #-}
 {-# OPTIONS -fallow-overlapping-instances #-}

 module FMAP where

 data Atom

 -- Check if a type is a collection type. This is the only typeclass that
 -- needs overlapping instances
 class IsCollection  t coll | t - coll
 instance IsCollection (m a) (m ())
 instance Atom ~ coll = IsCollection t coll

 -- The desired deep functor. Needs no overlapping instances
 class Funct a b c1 c2 | c1 - a, c1 b - c2 where
    f_map :: (a - b) - c1 - c2

 instance (IsCollection c1 coll, Funct' coll a b c1 c2)
    = Funct a b c1 c2 where
    f_map = f_map' (undefined::coll)

 class Funct' coll a b c1 c2 | coll c1 - a, coll c1 b - c2 where
    f_map' :: coll - (a - b) - c1 - c2

 instance Funct' Atom a b a b where
    f_map' _ = id

 instance (Functor m, Funct a b c d) = Funct' (m ()) a b (m c) (m d) where
    f_map' _ = fmap . f_map


 test1 = f_map (+1) [[[1::Int,2,3]]]
 test2 = f_map not [[True], [False]]
 test3 = f_map not (Just [Just True, Nothing])
 test4 = f_map not (print here 
                   return (Just (Just [Just [True], Nothing])))
        = print


 Still I am not sure how to rewrite this example using Type Families..


 --
 View this message in context: 
 http://old.nabble.com/Are-functional-dependencies-around-to-stay--tp26873777p26891353.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.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] Re: Optimizing Parsec 3 -- was: Wiki software?

2009-12-16 Thread Iavor Diatchki
Hi everyone,
While you are discussing performance of parsing combinator libraries,
I though I'd mention parsimony, available from Hackage.  It has as
good performance as parsec v2 but it also has support for different
buffer types (e.g., byte strings, including support for utf8 decoding,
etc) which is similar to parsec v3.  I also think that it has a
slightly simpler API.
-Iavor


On Wed, Dec 16, 2009 at 4:45 AM, Stephen Tetley
stephen.tet...@gmail.com wrote:
 Hi Jason

 UU parsing somewhat invented the Applicative style - it defined the
 usual combinators from Control.Applicative ($), (*), (*), (*)
 etc. but didn't have an 'Applicative' type class.


 By obligation, I mean relying only on the Applicative class for the
 derived operations, here manyTill, choice etc.

 Best wishes

 Stephen

 2009/12/16 Jason Dusek jason.du...@gmail.com:
 ...
  Is UU parsing more Applicative aware, then?

  When you say obligation, what do you mean?
 ___
 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] Re: ANNOUNCE: Clutterhs 0.1

2009-12-01 Thread Iavor Diatchki
Hi,
I work with Trevor on the other Clutter binding.  We did exchange a
few messages with Matt, but we were not sure how to combine the two
libraries because our approaches to writing the binding were a bit
different.  In general, I don't think that having two similar
libraries is a huge problem.  I tend to do this kind of hacking for
fun, and I really do not enjoy the competition that is being
encouraged when we try to select the one true library (e.g., with
efforts such as the Haskell platform).  Let a thousand flowers bloom,
I say :-)
-Iavor

On Mon, Nov 30, 2009 at 7:12 PM, Matt Arsenault arse...@rpi.edu wrote:
 On Mon, 2009-11-30 at 09:22 +0100, Gour wrote:

 Do you have some public repo for the project's code?

 I thought I mentioned this somewhere, but I've been using this git repo:

 http://jayne.hortont.com/git/cgit.cgi/clutterhs.git/


 ___
 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] Re: ANNOUNCE: Clutterhs 0.1

2009-12-01 Thread Iavor Diatchki
Hi

On Tue, Dec 1, 2009 at 11:02 AM, Gour g...@gour-nitai.com wrote:
 Iavor In general, I don't think that having two similar libraries is a
 Iavor huge problem.  I tend to do this kind of hacking for fun, and I
 Iavor really do not enjoy the competition that is being encouraged
 Iavor when we try to select the one true library (e.g., with efforts
 Iavor such as the Haskell platform).  Let a thousand flowers bloom, I
 Iavor say :-)

 I do not object of having choice - that's why I like Linux, but, otoh,
 prefer to have one fully-baked lib than several half-baked solutions
 which was/is problem with some Haskell packages.

We are baking ;)

 btw, are you interested in binding nbtk/mx toolkit for Moblin which is
 based on Clutter?

I am not that familiar with it, but it might be interesting to have
some Clutter based widgets for GUIs.

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


Re: [Haskell-cafe] What is a number. (Was: Num instances for 2-dimensional types)

2009-10-06 Thread Iavor Diatchki
Hi,

On Tue, Oct 6, 2009 at 2:37 AM, Henning Thielemann
lemm...@henning-thielemann.de wrote:
 Numeric literals are treated as Integer or Rational, and are then converted
 with the function fromInteger or fromRational, respectively, to the required
 type. Whatever fromInteger function is in scope, will be used. If
 fromInteger is in a class other than Num (in NumericPrelude it is Ring, but
 it can be also a function that is not a class method), then number literals
 have a type like:
  2 :: MyNumClass a = a

This is only the case if you use GHC's NoImplicitPrelude extension,
otherwise the fromInteger of the Prelude is used, even if it is not
in scope.  Here is an example:

module A where

  boolLit :: Integer - Bool
  boolLit 0 = False
  boolLit _ = True


{-# LANGUAGE NoImplicitPrelude #-}
module Main where

  import A(boolLit)
  import Prelude(Integer,Bool,print)

  fromInteger :: Integer - Bool
  fromInteger = boolLit

  main = print 0


Note that 0 means different things in the different modules!

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


Re: [Haskell-cafe] Bug in writeArray?

2009-09-24 Thread Iavor Diatchki
I agree with Grzegorz.  Perhaps we should file a bug-report, if there
isn't one already?
-Iavor

2009/9/24 Grzegorz Chrupała pite...@gmail.com:
 2009/9/23 Bulat Ziganshin bulat.zigans...@gmail.com:
 Hello Grzegorz,

 Wednesday, September 23, 2009, 7:19:59 PM, you wrote:

 This seems like a bug in the implementation of writeArray: when passed
   let (l,u) = ((0,10),(20,20))

 writeArray computes raw index (from 0 to total number of array
 elements) and check that this index is correct. with multi-dimensional
 arrays this approach may lead to wrong results, as you mentioned. it's
 known problem that isn't fixed for a long time probably due to
 efficiency cautions.

 Hmm, I understand that efficiency is an issue, but in that case
 shouldn't unsafe writing be provided by and unsafeWriteArray function,
 while writeArray does proper range checking?

 Or at least this problem with writeArray should be clearly indicated
 in the documentation. I for one spent several hours debugging before
 finding out about this lack of proper range checks so it's not an
 imaginary problem.

 --
 Grzegorz
 ___
 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] why these two are not equivalent?

2009-09-13 Thread Iavor Diatchki
Hi,
It seems that the problem is the site is using GHC 6.6.1, and
something was broken at the time (I have not looked into what that
is).
Here are the outputs that I get for the little example on the site
that you posted:

GHC 6.10.3 and C++:





On Sun, Sep 13, 2009 at 10:15 AM, Diego Souza dso...@bitforest.org wrote:
 On Sun, Sep 13, 2009 at 11:34:16AM +0200, Max Rabkin wrote:
 That is part of the contract of toAscList (the Asc stands for
 ascending order), but because of the way Map is implemented, the
 result of toList is also sorted.

 Cool. It is good to know that toAscList and toList would produce the
 same output.

 However, I think the question remains open. Is this piece of haskell
 code any different (in terms of the output it produces) from the C++
 version?

 Thanks,
 --
 ~dsouza
 yahoo!im: paravinicius
 gpg key fingerprint: 71B8 CE21 3A6E F894 5B1B  9ECE F88E 067F E891 651E
 ___
 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] why these two are not equivalent?

2009-09-13 Thread Iavor Diatchki
(argh, sorry about that, I pressed something and gmail sent my
unfinished email!)

On Sun, Sep 13, 2009 at 9:54 PM, Iavor Diatchki
iavor.diatc...@gmail.com wrote:
 Hi,
 It seems that the problem is the site is using GHC 6.6.1, and
 something was broken at the time (I have not looked into what that
 is).
 Here are the outputs that I get for the little example on the site
 that you posted:

 GHC 6.10.3 and C++:

03 10103538  1233 6160 0141  1
03 10103538  1233 6160 0142  1
30 10103538  1233 6160 0141  2
30 10103538  1233 6160 0142  2

30 10103538  1233 6160 0142  1
30 10103538  1233 6160 0143  1
30 10103538  1233 6160 0144  1
30 10103538  1233 6160 0145  1
30 10103538  1233 6160 0146  1

With GHC 6.6.1:
03 10103538  1233 6160 0141  1
03 10103538  1233 6160 0142  1
30 10103538  1233 6160 0141  2
30 10103538  1233 6160 0142  2

30 10103538  1233 6160 0142  1
30 10103538  1233 6160 0143  1
30 10103538  1233 6160 0145  1
30 10103538  1233 6160 0146  1

Note that in the second test case one line is missing, the one ending in 44.

-Iavor







 On Sun, Sep 13, 2009 at 10:15 AM, Diego Souza dso...@bitforest.org wrote:
 On Sun, Sep 13, 2009 at 11:34:16AM +0200, Max Rabkin wrote:
 That is part of the contract of toAscList (the Asc stands for
 ascending order), but because of the way Map is implemented, the
 result of toList is also sorted.

 Cool. It is good to know that toAscList and toList would produce the
 same output.

 However, I think the question remains open. Is this piece of haskell
 code any different (in terms of the output it produces) from the C++
 version?

 Thanks,
 --
 ~dsouza
 yahoo!im: paravinicius
 gpg key fingerprint: 71B8 CE21 3A6E F894 5B1B  9ECE F88E 067F E891 651E
 ___
 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 interface files: Why used? What about same data in object files?

2009-08-05 Thread Iavor Diatchki
Hello,

On Tue, Aug 4, 2009 at 2:50 PM, Neil Mitchellndmitch...@gmail.com wrote:
 Hi

 Some good reasons for having a separate interface are:  they can be
 human-readable and human-writable (ghc's do not fulfill this criterion);
 they can be used to bootstrap mutually recursive modules in the absence of
 any object files (ghc uses .hs-boot files instead); other tools can extract
 information about modules without having to understand either the full
 Haskell syntax or the object language.

 An additional reason is that for some changes of .hs file (where just
 the implementation changes) the .o file can be regenerated without
 touching the .hi file. This allows more accurate build dependencies
 and less recompilation.

Is that really the case?  I thought that GHC may add code to the
interface files for cross-module inlining purposes, which means that
changing the implementation might change the interface too.
-Iavor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Adding a field to a data record

2009-07-28 Thread Iavor Diatchki
Hello,
you may also find the package pretty-show
(http://hackage.haskell.org/package/pretty-show) useful.  It contains
code to convert automatically derived instances of Show into an
explicit data structure, which you can then manipulate (e.g., by
adding the extra field), and then render back to text.
-Iavor


On Tue, Jul 28, 2009 at 6:07 PM, Malcolm
Wallacemalcolm.wall...@cs.york.ac.uk wrote:
 the part I would really like to avoid is writing the
 New.Foo { a=a, b=b, ... z=1 } part, where the field
 names are many, long, and varied.

 OK, here is another hack-ish trick, since I notice your data is stored on
 disk as text, using show.  I assume you are using something like Read to
 retrieve it.  Well, how about using a real parser instead?  The parser
 during conversion can be slightly more lax, automatically adding in the
 extra field.

 For instance, using polyparse's Text.Parse, and DrIFT to derive the
 appropriate Parse instance for your datatype:

    module Foo where
    data Foo = Foo { a :: Int
                   , b :: Bool
                   , c :: Maybe Foo }
      {-! derive : Parse !-}

 DrIFT gives you this instance:

    {-* Generated by DrIFT : Look, but Don't Touch. *-}
    instance Parse Foo where
        parse = constructors
            [ ( Foo
              , return Foo `discard` isWord { `apply` field a
                       `discard` isWord , `apply` field b
                       `discard` isWord , `apply` field c
                       `discard` isWord }
              )
            ]

 Let's say the field 'b' is new, and your existing data does not have it.  So
 just take the parser generated by DrIFT and make a small modification:

    {-* Generated by DrIFT but modified by hand for conversion purposes *-}
    instance Parse Foo where
        parse = constructors
            [ ( Foo
              , return Foo `discard` isWord { `apply` field a
                       `apply` return True -- this field does not yet exist
 in data
                       `discard` isWord , `apply` field c
                       `discard` isWord }
              )
            ]

 Then do the obvious thing: parse the old data, immediately write it out
 again, and then throw away the modified parser in favour of the pure
 generated one.

 Regards,
    Malcolm
 ___
 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] generalize RecordPuns and RecordWildCards to work with qualified names?

2009-07-24 Thread Iavor Diatchki
Hello,
I think that Even refers to an example like this:

module A where
  data A = A { a :: Int }

The following works:

{-# LANGUAGE NamedFieldPuns #-}
module B where
  import A

  f (A { a }) = a


However, if we import A qualified, then punning does not seem to work:

{-# LANGUAGE NamedFieldPuns #-}
module B where
  import qualified A

  f (A.A { a }) = a

This results in: Not in scope: `a'



{-# LANGUAGE NamedFieldPuns #-}
module B where
  import qualified A

  f (A.A { A.a }) = a

This results in: Qualified variable in pattern: A.a

Even is suggesting that instead of reporting an error, in the second
case we could use the translation:

  f (A.A { A.a }) = a
--
  f (A.A { A.a = a })

(i.e., when punning occurs with a qualified name, use just the
unqualified part of the name in the pattern)

Hope that this helps,
-Iavor




On Thu, Jul 23, 2009 at 12:51 PM, Simon
Peyton-Jonessimo...@microsoft.com wrote:
 Can you give a concrete program to illustrate your point, please?  I'm not 
 getting it.

 Simon

 | -Original Message-
 | From: haskell-cafe-boun...@haskell.org 
 [mailto:haskell-cafe-boun...@haskell.org] On
 | Behalf Of Evan Laforge
 | Sent: 17 July 2009 23:57
 | To: haskell
 | Subject: [Haskell-cafe] generalize RecordPuns and RecordWildCards to work 
 with
 | qualified names?
 |
 | Record punning is not all that useful with qualified module names.  If
 | I write '(M.Record { M.rec_x })' it says  Qualified variable in
 | pattern and if I write '(M.Record { rec_x })' it says 'Not in scope:
 | `rec_x''.  Could it be this extension be further extended slightly so
 | that 'f (M.Record { M.rec_x })' will desugar to 'f (M.Record { M.rec_x
 | = rec_x })'?
 |
 | Similarly, RecordWildCards could support this too.
 |
 | It seems simple and useful to me... am I missing anything fatally
 | problematic about this?  Would anyone else use it?
 | ___
 | 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] Re: what about moving the record system to an addendum?

2009-07-07 Thread Iavor Diatchki
Hello,
I do not think that we should remove the current record/named fields
syntax, at least for the moment.  I use it a lot, and I do not want to
add extra pragmas or extensions to my cabal file.  In fact, one of
the purposes of Haskell', the way I understand it, is exactly to just
choose a stable set of extensions and give a name to them (so
decrease, not increase the number of pragmas).  I think that a new
reocrd/label system is way beyond the scope of Haskell'.  If people
want to experiment with new record systems they may already do so, by
defining a new extension.  A case in point is the Trex record system,
which is implemented in Hugs.
-Iavor

2009/7/7 Ravi Nanavati r...@bluespec.com:
 2009/7/7 Duncan Coutts duncan.cou...@worc.ox.ac.uk:
 On Mon, 2009-07-06 at 18:28 -0700, John Meacham wrote:
 Well, without a replacement, it seems odd to remove it. Also, Haskell
 currently doesn't _have_ a record syntax (I think it was always a
 misnomer to call it that) it has 'labeled fields'. None of the proposed
 record syntaxes fit the same niche as labeled fields so I don't see them
 going away even if a record syntax is added to haskell in the future.

 The people proposing this can correct me if I'm wrong but my
 understanding of their motivation is not to remove record syntax or
 immediately to replace it, but to make it easier to experiment with
 replacements by making the existing labelled fields syntax a modular
 part of the language that can be turned on or off (like the FFI).

 I'm not sure that I agree that it's the best approach but it is one idea
 to try and break the current impasse. It seems currently we cannot
 experiment with new record systems because they inevitably clash with
 the current labelled fields and thus nothing changes.

 I think it is a powerful approach to try and break the current impasse
 for the following reasons:

 1. Once implemented, Hackage and Cabal will soon give us accurate data
 on what publicly available Haskell code does and does not depend on
 NamedFields/TraditionalRecordSyntax/WhateverWeEndUpCallingIt
 2. Once deprecated, people will be encouraged to not depend on the
 traditional record syntax where the cost of avoiding it is small (I'm
 thinking of situations like the mtl-accessors / run functions where
 the traditional syntax is saving something like one function
 definition).
 3. Champions of alternative record syntaxes will know what on Hackage
 they can use out-of-the-box and what things they'd want to consider
 re-writing as examples of how their approach is superior.

 Does anyone have a concrete dea of what it would take to carve out the
 existing syntax as an addendum?

 Thanks,

  - Ravi
 ___
 Haskell-prime mailing list
 haskell-pr...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime

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


Re: [Haskell-cafe] Incremental XML parsing with namespaces?

2009-06-09 Thread Iavor Diatchki
Hi,
you may also want to look at:
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xml
It knows about namespaces and, also, it's parser is lazy.
-Iavor


On Mon, Jun 8, 2009 at 11:39 AM, John Millikinjmilli...@gmail.com wrote:
 I'm trying to convert an XML document, incrementally, into a sequence
 of XML events. A simple example XML document:

 doc xmlns=org:myproject:mainns xmlns:x=org:myproject:otherns
    titleDoc title/title
    x:refabc1234/x:ref
    html xmlns=http://www.w3.org/1999/xhtml;bodyHello world!/body/html
 /doc

 The document can be very large, and arrives in chunks over a socket,
 so I need to be able to feed the text data into a parser and receive
 a list of XML events per chunk. Chunks can be separated in time by
 intervals of several minutes to an hour, so pausing processing for the
 arrival of the entire document is not an option. The type signatures
 would be something like:

 type Namespace = String
 type LocalName = String

 data Attribute = Attribute Namespace LocalName String

 data XMLEvent =
    EventElementBegin Namespace LocalName [Attribute] |
    EventElementEnd Namespace LocalName |
    EventContent String |
   EventError String

 parse :: Parser - String - (Parser, [XMLEvent])

 I've looked at HaXml, HXT, and hexpat, and unless I'm missing
 something, none of them can achieve this:

 + HaXml and hexpat seem to disregard namespaces entirely -- that is,
 the root element is parsed to doc instead of
 (org:myproject:mainns, doc), and the second child is x:ref
 instead of (org:myproject:otherns, ref). Obviously, this makes
 parsing mixed-namespace documents effectively impossible. I found an
 email from 2004[1] that mentions a filter for namespace support in
 HaXml, but no further information and no working code.

 + HXT looks promising, because I see explicit mention in the
 documentation of recording and propagating namespaces. However, I
 can't figure out if there's an incremental mode. A page on the wiki[2]
 suggests that SAX is supported in the html tag soup parser, but I
 want incremental parsing of *valid* documents. If incremental parsing
 is supported by the standard arrow interface, I don't see any
 obvious way to pull events out into a list -- I'm a Haskell newbie,
 and still haven't quite figured out monads yet, let alone Arrows.

 Are there any libraries that support namespace-aware incremental parsing?

 [1] http://www.haskell.org/pipermail/haskell-cafe/2004-June/006252.html
 [2] 
 http://www.haskell.org/haskellwiki/HXT/Conversion_of_Haskell_data_from/to_XML
 ___
 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] Re: Building network package on Windows

2009-06-08 Thread Iavor Diatchki
Hi,
Interesting.  In that case, does anyone have any ideas about the
linker errors?
-Iavor

On Mon, Jun 8, 2009 at 12:42 AM, Thomas ten Catettenc...@gmail.com wrote:
 On Mon, Jun 8, 2009 at 02:04, Iavor Diatchkiiavor.diatc...@gmail.com wrote:
 Hello,
 Here is an update, in case anyone else runs into the same problem.

 My understanding, is that the problem was caused by a mistake in the
 configure script for the network package, which after (correctly)
 detecting that IPv6 functionality was not available on my platform, it
 (incorrectly) tried to gain this functionality by redefining the
 version of my platform.  Concretely, apparently I have Windows Vista
 Basic Home Edition, which seems to identify itself as version 0x400,
 while the missing functions are only available on versions of windows
= 0x501.

 0x400 is, if I'm not mistaken, Windows 95. Vista is 0x600 [1]. I don't
 think they *identify* themselves as such; rather, the program itself
 specifies what Windows versions it wants to be able to run on.

 In particular, the macros _WIN32_WINNT and WINVER should be defined as
 the *minimum* platform version on which the compiled binary is to
 work. Therefore, if functionality from XP (0x501) is needed, it is
 perfectly okay to redefine these macros to 0x501. This will flip some
 switches in included header files that enable declarations for the
 desired functionality. Of course, the binary will then only run on
 platforms that actually have this functionality.

 Hope that clears things up a bit.

 Thomas

 [1] http://msdn.microsoft.com/en-us/library/aa383745.aspx

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


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

2009-06-08 Thread Iavor Diatchki
Hi,
As Thomas pointed out, it is not clear if this is a bug, or if there
is something confused between the different versions of Windows and
MinGW (or I just did something wrong) but I'll make a ticket so that
we can track the issue.  I am by no means a Windows developer but I
would be happy to try out fixes/ideas on my Windows machine as I think
that it is important that we have as good support for Windows as we do
on the various Unix-like systems.
-Iavor

On Mon, Jun 8, 2009 at 1:23 PM, Bryan O'Sullivanb...@serpentine.com wrote:
 On Sun, Jun 7, 2009 at 5:04 PM, Iavor Diatchki iavor.diatc...@gmail.com
 wrote:

 Here is an update, in case anyone else runs into the same problem.

 Thanks for following up. I wrote the code that performs that check, but
 unfortunately I don't have access to all of the permutations of Windows that
 are out there, so my ability to test is rather limited. I'm sorry for the
 trouble it caused you. Perhaps Vista Home Basic doesn't have IPv6 support?
 If that conjecture is true, I'm not sure how I'd have found it out :-( More
 likely, the name mangling is going wrong.

 As for your point that the network package exhibits different APIs depending
 on the underlying system, that's true, but it's hard to avoid. Writing a
 compatibility API for systems that don't have functioning IPv6 APIs is a
 chunk of boring work, and I had thought that such systems were rare.

 Anyway, please do file a bug, and we'll take the discussion of how to
 reproduce and fix your problem there.

 Thanks,
 Bryan.

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


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

2009-06-08 Thread Iavor Diatchki
Hi,
OK, I think that I found and fixed the problem.  As Thomas pointed
out, the configure script is not wrong.  The problem turned out to be
the foreign import for getnameinfo (this was the missing symbol).
Attached to this e-mail should be a darcs patch that fixes the
problem.
-Iavor


On Mon, Jun 8, 2009 at 4:48 PM, Iavor Diatchkiiavor.diatc...@gmail.com wrote:
 Hi,
 As Thomas pointed out, it is not clear if this is a bug, or if there
 is something confused between the different versions of Windows and
 MinGW (or I just did something wrong) but I'll make a ticket so that
 we can track the issue.  I am by no means a Windows developer but I
 would be happy to try out fixes/ideas on my Windows machine as I think
 that it is important that we have as good support for Windows as we do
 on the various Unix-like systems.
 -Iavor

 On Mon, Jun 8, 2009 at 1:23 PM, Bryan O'Sullivanb...@serpentine.com wrote:
 On Sun, Jun 7, 2009 at 5:04 PM, Iavor Diatchki iavor.diatc...@gmail.com
 wrote:

 Here is an update, in case anyone else runs into the same problem.

 Thanks for following up. I wrote the code that performs that check, but
 unfortunately I don't have access to all of the permutations of Windows that
 are out there, so my ability to test is rather limited. I'm sorry for the
 trouble it caused you. Perhaps Vista Home Basic doesn't have IPv6 support?
 If that conjecture is true, I'm not sure how I'd have found it out :-( More
 likely, the name mangling is going wrong.

 As for your point that the network package exhibits different APIs depending
 on the underlying system, that's true, but it's hard to avoid. Writing a
 compatibility API for systems that don't have functioning IPv6 APIs is a
 chunk of boring work, and I had thought that such systems were rare.

 Anyway, please do file a bug, and we'll take the discussion of how to
 reproduce and fix your problem there.

 Thanks,
 Bryan.




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


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

2009-06-07 Thread Iavor Diatchki
Hello,
Here is an update, in case anyone else runs into the same problem.

My understanding, is that the problem was caused by a mistake in the
configure script for the network package, which after (correctly)
detecting that IPv6 functionality was not available on my platform, it
(incorrectly) tried to gain this functionality by redefining the
version of my platform.  Concretely, apparently I have Windows Vista
Basic Home Edition, which seems to identify itself as version 0x400,
while the missing functions are only available on versions of windows
= 0x501.

My workaround was to:
  1. checkout the network package from the repository on code.haskell.com
  2. modify configure.ac to comment out the section where it sets the
windows version to 0x501
  3. autoreconf
  4. build using the usual cabal way

Another thing to watch out for:  if you already have packages that
were built against the old version of network, they will continue to
use that.  So, I had to:
  1. remove all of these packages,
  2. remove the old version of network (to avoid confusion), and
  3. then resintall the packages.
It would be nice if we had a more automatic way to do that (perhaps we
do, but I don't know it?).  It seems that if this is not done GHC
could panic, which is what happened to me.  I am not sure why that
happened but I am guessing that it was related to the fact that
interface to the package changed without its version changing.

In general, it seems a bad idea that the same version of the network
package exhibits different APIs, depending on the configuration of the
underlying system.

-Iavor







On Sat, Jun 6, 2009 at 9:43 PM, Iavor Diatchkiiavor.diatc...@gmail.com wrote:
 Hi,
 I have been trying to build the package network from hackage
 (version 2.2.1.3) on Windows Vista, and I could really use some help.

 Building on the command line, or under cygwin completely failed
 (command line due to cabal not being able to execute
 something---possibly configure---although it would not say; cygwin
 first due to lack of gcc, which is tested but, apparently, the outcome
 ignored, and after gcc was installed some incompatibility with the
 header files which were detected but reported unusable).

 I managed to build the library under MinGW with msys without serious
 obstacles.  I can also build my package against the result and all is
 well.  Unfortunately, if I try to use my package to build an
 executable application I get a linker error, reporting a missing
 symbol during linking:
 C:\Users\diatchki\AppData\Roaming\cabal\network-2.2.1.3\ghc-6.10.3/libHSnetwork-2.2.1.3.a(Socket.o):fake:(.text+0xb014):
 undefined reference to `getnameinfo'
 collect2: ld returned 1 exit status

 Now, getnameinfo is present in the header files, and it is also
 defined in the library ws2_32.a which is being passed to GHC so I am
 not sure what is going on.  Any ideas?  Searching the web suggests
 that the problem may be somehow related to the standard calling
 conventions but I don't really understand.  Also, if I understand
 correctly, this functionality is related to IPv6 support, which I do
 not need at the moment, so it would be great if it could be easily
 disabled in some way.

 Any ideas, suggestion, workarounds, etc. would be greatly appreciated,
 -Iavor

 PS: I am using GHC 6.10.3

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


[Haskell-cafe] Building network package on Windows

2009-06-06 Thread Iavor Diatchki
Hi,
I have been trying to build the package network from hackage
(version 2.2.1.3) on Windows Vista, and I could really use some help.

Building on the command line, or under cygwin completely failed
(command line due to cabal not being able to execute
something---possibly configure---although it would not say; cygwin
first due to lack of gcc, which is tested but, apparently, the outcome
ignored, and after gcc was installed some incompatibility with the
header files which were detected but reported unusable).

I managed to build the library under MinGW with msys without serious
obstacles.  I can also build my package against the result and all is
well.  Unfortunately, if I try to use my package to build an
executable application I get a linker error, reporting a missing
symbol during linking:
C:\Users\diatchki\AppData\Roaming\cabal\network-2.2.1.3\ghc-6.10.3/libHSnetwork-2.2.1.3.a(Socket.o):fake:(.text+0xb014):
undefined reference to `getnameinfo'
collect2: ld returned 1 exit status

Now, getnameinfo is present in the header files, and it is also
defined in the library ws2_32.a which is being passed to GHC so I am
not sure what is going on.  Any ideas?  Searching the web suggests
that the problem may be somehow related to the standard calling
conventions but I don't really understand.  Also, if I understand
correctly, this functionality is related to IPv6 support, which I do
not need at the moment, so it would be great if it could be easily
disabled in some way.

Any ideas, suggestion, workarounds, etc. would be greatly appreciated,
-Iavor

PS: I am using GHC 6.10.3
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] web musing

2009-06-05 Thread Iavor Diatchki
Hi Conor,
As someone pointed out, CGI is one way to go.
Another option is to write a small Haskell web server. This path is
better if you have an app that needs to keep state, ans uses the
browser mostly as a GUI.

I have just made a package that should make doing this fairly easy.  I
have not uploaded it to hackage yet because I want to make some small
changes still.  You can try out the pre-release from here (the usual
cabal steps should work for making a package/installing)

git clone git://code.galois.com/http-server.git

For an example, take a look in the example directory, there is a
small web-server there, which shows how to all kinds of things,
including ajax interactions with javascript using jQuery.  For
processing form data there is the module:
Network.HTTP.Server.HtmlForm.

Let me know if you have questions, comments, or other feed-back!
-Iavor



On Fri, Jun 5, 2009 at 8:18 AM, Conor McBrideco...@strictlypositive.org wrote:
 Comrades

 I'm in a perplexing situation and I'd like to appeal to the
 sages.

 I've never written anything other than static HTML in my life,
 and I'd like to make a wee web service: I've heard some
 abbreviations, but I don't really know what they mean.

 I've got a function (possibly the identity, possibly const ,
 who knows?)

  assistant :: String - String

 and I want to make a webpage with an edit box and a submit
 button. If I press the submit button with the edit box
 containing string s, I'd like the page to reload with the
 edit box reset to (assistant s).

 Will I need to ask systems support to let me install some
 haskelly sort of web server? Looks likely, I suppose.

 In general, what's an easy way to put a web front end on
 functionality implemented in Haskell?

 Hoping this isn't a hard question

 Conor

 ___
 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 implement this? A case for scoped record labels?

2009-05-31 Thread Iavor Diatchki
Hi,
Using a type class in the way Wren suggests seems to be the right way
to do this in Haskell, as it is at the moment.  I don't think that
this an inappropriate use of type classes at all---in fact, it is
exactly what type classes were designed to do (i.e., allow you to
reuse the same name at different types).  Note that you can combine
type classes and records to cut down on the typing:

data Request = Request { request_channel :: Channel, ... }
data Response = Response { response_channel :: Channel, ... }

class HasChannel t where
  get_channel :: t - Channel
  set_channel :: Channel - t - t

instance HasChannel Request where
  get_channel = request_channel
  set_channel x t = t { response_channel = x }

and so on.  It is a bit verbose, but you only have to do it once for
your protocol, and then you get the nice overloaded interface.
Actually, having the non-overloaded names might also be useful in some
contexts (e.g., to resolve ambiguities).

-Iavor






On Mon, May 25, 2009 at 7:32 PM, wren ng thornton w...@freegeek.org wrote:
 ntu...@googlemail.com wrote:

 This however does not work because record selectors have module scope,
 so the compiler will complain that channel et. al. are defined
 multiple times. As a workaround I could put each type into its own
 module, but at least GHC requires a file per module (which is *very*
 inconvenient IMO). If we would have scoped labels (e.g. like proposed
 here: http://legacy.cs.uu.nl/daan/pubs.html#scopedlabels) it seems
 like it would have been straightforward.

 So certainly I am missing something and there is a better way to
 design this. Hence this e-mail. I welcome any advice how this would
 best be done in Haskell with GHC.

 One alternative is to use Haskell's support for ad-hoc overloading. Define a
 typeclass for each selector (or group of selectors that must always occur
 together) which is polymorphic in the record type. Combine this with the
 separate constructor types to get something like:

    data HandshakeRequest = HandshakeRequest String ...
    data HandshakeResponse = HandshakeResponse String Bool ...
    ...
    data BayeuxMessage
        = HSReq HandshakeRequest
        | HSRes HandshakeResponse
        ...

    class BayeuxChannel r where
        channel :: r - String
    instance BayeuxChannel HandshakeRequest where
        channel (HandshakeRequest ch ...) = ch
    instance BayeuxChannel HandshakeResponse where
        channel (HandshakeResponse ch _ ...) = ch
    ...
    class BayeuxSuccessful r where
        successful :: r - Bool
    ...


 It's not pretty, but it gets the job done. Many people decry this as
 improper use of typeclasses though (and rightly so). A better approach would
 probably be to use GADTs or the new data families which give a sort of dual
 of typeclasses (typeclasses give a small set of functions for a large set of
 types; GADTs give a large set of functions for a small set of types[0]).
 Someone more familiar with those approaches should give those versions.

 If you want to be able to set the fields as well as read them then the
 classes should be more like lenses than projectors. For instance, this[1]
 discussion on Reddit. The two obvious options are a pair of setter and
 getter functions: (Whole-Part, Whole-Part-Whole); or a factored version
 of the same: Whole-(Part, Part-Whole).

 You should also take a look at the data-accessor packages[2][3] which aim to
 give a general solution to the lens problem. Also take a look at hptotoc[4],
 the Haskell implementation of Google's Protocol Buffers which has many
 similar problems to your Bayeaux protocol. In general, protocols designed
 for OO are difficult to translate into non-OO languages.



 [0] http://blog.codersbase.com/tag/gadt/
 [1]
 http://www.reddit.com/r/haskell/comments/86oc3/yet_another_proposal_for_haskell_the_ever_growing/c08f4bp
 [2] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor
 [3]
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/data-accessor-template
 [4] http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hprotoc

 --
 Live well,
 ~wren
 ___
 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] Re: ANNOUNCE: vacuum-cairo: a cairo frontend to vacuum for live Haskell data visualization

2009-04-02 Thread Iavor Diatchki
Hi,
The linking problem might be due to a bug in the cabal file:  if you
have modules that are not exposed, you still need to list them in the
other-modules section.
-Iavor

On Thu, Apr 2, 2009 at 10:01 AM, Gleb Alexeyev gleb.alex...@gmail.com wrote:
 Don Stewart wrote:

 Please upload!!


 I've run into 2 problems while trying to do this.
 The first one - haxr won't build with HTTP-4000, so I had to edit haxr.cabal
 and add the upper version bound for HTTP.

 The second one is puzzling me.

 I've cabal-installed the package, but keep getting linking errors from ghci
 (though interactive loading of the same module from source works fine):

 Prelude :m + System.Vacuum.Ubigraph
 Prelude System.Vacuum.Ubigraph view 42
 Loading package syb ... linking ... done.
 Loading lots of packages skipped
 Loading package vacuum-0.0.6 ... linking ... done.
 Loading package haxr-3000.1.1.2 ... linking ... done.
 Loading package vacuum-ubigraph-0.1.0.2 ... linking ... interactive:
 /home/gleb/.cabal/lib/vacuum-ubigraph-0.1.0.2/ghc-6.10.1/HSvacuum-ubigraph-0.1.0.2.o:
 unknown symbol `vacuumzmubigraphzm0zi1zi0zi2_GraphicsziUbigraph_lvl_closure'
 ghc: unable to load package `vacuum-ubigraph-0.1.0.2'
 Prelude System.Vacuum.Ubigraph

 Non-working package is here:
 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/vacuum-ubigraph-0.1.0.1.

 Any hints appreciated.

 ___
 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] Re: a newbies confusion with repositories - darcs or git

2009-03-02 Thread Iavor Diatchki
Hi,
Just another point of information, when you make your decision:  I
work at a company where we frequently use Haskell and we use git for
almost all of our projects (other VCSs that we use are mercurial and
svn).  Also, I use git for all of my open source projects and I find
that it works very well.  Darcs is a fine VCS (although I've had
problems with it in the past) but you should not feel that you have to
choose it so that you are considered a real Haskeller :-)  Good
luck, and welcome to the community!
-Iavor


On Mon, Mar 2, 2009 at 8:58 AM, Maurí­cio briqueabra...@yahoo.com wrote:
 now that I'm finished with my haskell app I take the opportunity to follow
 up on some things I hadn't quite understood in my so far short venture into
 the haskell world.

 Means: Prepare for a number of naive posts to follow.

 We (most of we, actually) have all been there. Some of
 us (me, probably) are still there.

 But since I have the ambition to become a real haskeller I was gonna make
 myself acquainted with darcs. Should I skip that and head straight for git?

 Whatever you choose, you'll take some time to get
 used to it. So, if you decided that in the end you'll
 use git, but you want to have a taste of darcs first,
 I recommend you to read the Patch theory of darcs
 manual instead:

 http://darcs.net/manual/node9.html

 There you'll find the best of darcs. If, instead, you
 just use darcs for a little amount of time, you'll
 only taste the beginner headache.

 Best,
 Maurício

 ___
 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] lazy evaluation is not complete

2009-02-09 Thread Iavor Diatchki
Hi,
Just for fun, here is the code that does this:

newtype Int' = I Int deriving Eq

instance Show Int' where
  show (I x) = show x

instance Num Int' where
  I x + I y = I (x + y)

  I 0 * _   = I 0
  I x * I y = I (x * y)

  I x - I y = I (x - y)

  abs (I x) = I (abs x)

  signum (I x)  = I (signum x)

  negate (I x)  = I (negate x)

  fromInteger n = I (fromInteger n)

foo x = if x == 0 then 0 else foo (x - 1) * foo (x + 1)

*Main foo 5 :: Int'
0

-Iavor


On Mon, Feb 9, 2009 at 7:19 AM, Jochem Berndsen joc...@functor.nl wrote:
 Peter Padawitz wrote:
 A simplied version of Example 5-16 in Manna's classical book
 Mathematical Theory of Computation:

 foo x = if x == 0 then 0 else foo (x-1)*foo (x+1)

 If run with ghci, foo 5 does not terminate, i.e., Haskell does not look
 for all outermost redices in parallel. Why? For efficiency reasons?

 It's a pity because a parallel-outermost strategy would be complete.

 (*) is strict in both arguments for Int. If you want to avoid this, you
 could do
 newtype X = X Int
 and write your own implementation of (*) that is nonstrict.

 --
 Jochem Berndsen | joc...@functor.nl
 GPG: 0xE6FABFAB
 ___
 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] Factoring into type classes

2009-01-20 Thread Iavor Diatchki
Hello,

I don't mean to be negative here but I really fail to see how do any
of these ideas help the situation. (I do think it would be cool to
have a generic way to lift functions from one type to another that is
isomorphic to it).  The fundamental problem is that there are multiple
functions of type Int - Int - Int   (Int being just an example, for
the sake of concreteness), that can be the binary operation of a
monoid.  Therefore, we cannot use the type system to determine how to
resolve the overloading of symbols like mappend.  Monoids are
general enough so that many types have multiple monoidal structure,
which is why I wrote that I don't think that they are good match for
the class system.

Defining a newtype and passing around isomorphisms seems more complex
to me than simply passing around the operations directly (i.e., not
using the class system).  By the way, Miguel's preference can be coded
almost verbatim in ML using local declarations (I am referring to
the let-like construct that allows the definition of local values
that scope over multiple declarations) without any fancy type magic.

-Iavor



On Tue, Jan 20, 2009 at 8:42 AM, Conor McBride
co...@strictlypositive.org wrote:
 Hi folks

 I have been known to venture the viewpoint that the
 newtype trick might benefit from improved library
 support, for example, here

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

 This is in a similar vein to Derek's approach, if
 accompanied by a little more grotesque whizzbangery.

 On 19 Jan 2009, at 21:51, Derek Elkins wrote:

 On Mon, 2009-01-19 at 12:10 -0800, Iavor Diatchki wrote:

 Sure, the point is that you are essentially adding a type annotation,
 which is like using a non-overloaded function.  Compare, for example:
 mappend add x y  and getSum (mappend (Sum x) (Sum y)).  I think
 that the first one is quite a bit more readable but, of course, this
 is somewhat subjective.

 data Iso a b = Iso { to :: a - b, from :: b - a }

 under :: Iso a b - (b - b) - (a - a)
 under iso = to iso ~ from iso

 under2 :: Iso a b - (b - b - b) - (a - a - a)
 under2 iso = to iso ~ under iso

 sumIso = Iso Sum getSum

 (+) = under2 sumIso mappend


 Perhaps it's worth trying to push in this direction,
 in search of a coherent kit.

 After all, there's a lot of structure out there.

 All the best

 Conor


 ___
 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] Factoring into type classes

2009-01-19 Thread Iavor Diatchki
Hello,
The multitude of newtypes in the Monoid module are a good indication
that the Monoid class is not a good fit for the class system (it is
ironic that discussing it resulted in such a huge thread recently :-).
   How I'd approach the situation that you describe would depend on
the context (did I design the class, or am I just using it?  am I
writing a library that is to be used by other people, or is the class
just used in an internal part of my program?, etc.) but, in general,
here are some ideas:
1. If one type can be made into an instance of a class in multipe ways
and I have no control over the class:
   - I would provide non-overloaded versions for each implementation
   - if there is a natural one (something that is quite commonly
used) I would use it for an instance
   - if most uses are equally likely to be useful, then I would not
provide an instance but just use the non-overloaded functions.  If I
did provide an instance, then I would be careful to document the
choice I made.
2. If I have control over the class I may consider changing it:
  - Consider using a different class, that has operations that are
more specific to what I am doing (e.g., use a PrettyPrint class
instead of Show class)
  - If many types are members of the same classes, then it may be
useful to combine them (i.e., add multiple methods that perform the
different operations).

I think that I have done all of the above in different situations, and
so I don't think that there is a single correct answer.  I usually
avoid using the newtype trick as I find it inconvenient:  usually
the newtype does not have the same operations as the underlying type
and so it cannot be used directly, and if you are going to wrap thing
just when you use the class methods, then you may as well use the
non-overloaded operations.

Hope that this helps,
Iavor


On Mon, Jan 19, 2009 at 9:40 AM, Patai Gergely
patai_gerg...@fastmail.fm wrote:
 As a side curiosity, I would love to see an example of any data structure
 which has more than one Functor instance.  Especially those which have
 more than one useful functor instance.

 data Record a b = R { field1 :: a, field2 :: b }

 If I want to use fmap to transform either field, I have to declare the
 type to have the corresponding type variable at the end, i.e. choosing
 Record a b or Record b a is already a design decision, and it is
 driven by the standard Functor class in this case. I can define custom
 functions fmap1 and fmap2 manually, but then I don't get the advantages
 of overloading, like fmapping over a data structure containing my
 records.

 Now I understand that I can't get everything, and my question is mainly
 what to do when such a dilemma comes up. Those who have already
 encountered such a dilemma: how did it come up and what did you do to
 solve it?

 Gergely

 --
 http://www.fastmail.fm - Same, same, but different...

 ___
 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] Factoring into type classes

2009-01-19 Thread Iavor Diatchki
Hi,

On Mon, Jan 19, 2009 at 11:06 AM, Jonathan Cast
jonathancc...@fastmail.fm wrote:
 On Mon, 2009-01-19 at 10:59 -0800, Iavor Diatchki wrote:
 Hello,
 The multitude of newtypes in the Monoid module are a good indication
 that the Monoid class is not a good fit for the class system

 I would say rather that the class system is not a good fit for Monoid.
 Proposals for local instances, multiple instances, instance
 import/export control, etc. come up quite frequently on this list; the
 phenomena in question are not restricted to Monoid.

I disagree with you but that is a moot point because we are discussing
Haskell, which does not have any of these features.  Also, I find that
in many situations where people want to use them, simpler solutions
(like some of the ideas I mentioned in my  previous post) suffice.
That is not to say that we should stop trying to figure out how to
improve the class system, but language changes require a lot more work
than improving the design of the libraries.

 I usually
 avoid using the newtype trick as I find it inconvenient:  usually
 the newtype does not have the same operations as the underlying type
 and so it cannot be used directly, and if you are going to wrap thing
 just when you use the class methods,

 OTOH, I think you mean here `when you use class methods and when you use
 overloaded functions'.

Sure, the point is that you are essentially adding a type annotation,
which is like using a non-overloaded function.  Compare, for example:
mappend add x y  and getSum (mappend (Sum x) (Sum y)).  I think
that the first one is quite a bit more readable but, of course, this
is somewhat subjective.

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


Re: [Haskell-cafe] Type Family Relations

2009-01-04 Thread Iavor Diatchki
Hi,
I like collecting examples of different type system related issues,
and I am curious in what way is the solution that I posted limited. Do
you happen to have an example?
Thanks,
Iavor

On Sat, Jan 3, 2009 at 8:35 PM, Thomas DuBuisson
thomas.dubuis...@gmail.com wrote:
 Thank you all for the responses.  I find the solution that omits type
 families [Diatchki] to be too limiting while the solution 'class (Dual
 (Dual s) ~ s) =' [Ingram] isn't globally enforced.  I've yet to
 closely study your first solution, Ryan, but it appears to be what I
 was looking for - I'll give it a try in the coming week.

 Tom

 On Sat, Jan 3, 2009 at 8:18 PM, Iavor Diatchki iavor.diatc...@gmail.com 
 wrote:
 Hello,
 Usually, you can program such things by using super-classes.  Here is
 how you could encode your example:

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

 class HeaderOf addr hdr | addr - hdr
 class HeaderOf addr hdr = AddressOf hdr addr | addr - hdr

 data IPv4Header = C1
 data IPv4   = C2
 data AppAddress = C3
 data AppHeader  = C4

 instance AddressOf IPv4Header IPv4
 instance HeaderOf IPv4 IPv4Header

 {- results in error:
 instance AddressOf AppHeader AppAddress
 instance HeaderOf AppAddress [AppHeader]
 -}

 Hope that this helps,
 Iavor



 On Sat, Jan 3, 2009 at 7:22 AM, Thomas DuBuisson
 thomas.dubuis...@gmail.com wrote:
 Cafe,
 I am wondering if there is a way to enforce compile time checking of
 an axiom relating two separate type families.

 Mandatory contrived example:

 type family AddressOf h
 type family HeaderOf a

 -- I'm looking for something to the effect of:
 type axiom HeaderOf (AddressOf x) ~ x

 -- Valid:
 type instance AddressOf IPv4Header = IPv4
 type instance HeaderOf IPv4 = IPv4Header

 -- Invalid
 type instance AddressOf AppHeader = AppAddress
 type instance HeaderOf AppAddress = [AppHeader]

 So this is  a universally enforced type equivalence.  The stipulation
 could be arbitrarily complex, checked at compile time, and must hold
 for all instances of either type family.

 Am I making this too hard?  Is there already a solution I'm missing?

 Cheers,
 Tom
 ___
 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


Re: [Haskell-cafe] Type Family Relations

2009-01-03 Thread Iavor Diatchki
Hello,
Usually, you can program such things by using super-classes.  Here is
how you could encode your example:

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

class HeaderOf addr hdr | addr - hdr
class HeaderOf addr hdr = AddressOf hdr addr | addr - hdr

data IPv4Header = C1
data IPv4   = C2
data AppAddress = C3
data AppHeader  = C4

instance AddressOf IPv4Header IPv4
instance HeaderOf IPv4 IPv4Header

{- results in error:
instance AddressOf AppHeader AppAddress
instance HeaderOf AppAddress [AppHeader]
-}

Hope that this helps,
Iavor



On Sat, Jan 3, 2009 at 7:22 AM, Thomas DuBuisson
thomas.dubuis...@gmail.com wrote:
 Cafe,
 I am wondering if there is a way to enforce compile time checking of
 an axiom relating two separate type families.

 Mandatory contrived example:

 type family AddressOf h
 type family HeaderOf a

 -- I'm looking for something to the effect of:
 type axiom HeaderOf (AddressOf x) ~ x

 -- Valid:
 type instance AddressOf IPv4Header = IPv4
 type instance HeaderOf IPv4 = IPv4Header

 -- Invalid
 type instance AddressOf AppHeader = AppAddress
 type instance HeaderOf AppAddress = [AppHeader]

 So this is  a universally enforced type equivalence.  The stipulation
 could be arbitrarily complex, checked at compile time, and must hold
 for all instances of either type family.

 Am I making this too hard?  Is there already a solution I'm missing?

 Cheers,
 Tom
 ___
 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] Re: Is this related to monomorphism restriction?

2008-12-22 Thread Iavor Diatchki
Hi,

On Sun, Dec 21, 2008 at 11:45 AM, Luke Palmer lrpal...@gmail.com wrote:
 2008/12/21 Iavor Diatchki iavor.diatc...@gmail.com


 g :: TestClass a = a - Integer
 g = fst (a :: (a - Integer, a - Integer))

 Which I believe needs to be written:

 g :: forall a. TestClass a = a - Integer
 g = fst (a :: (a - Integer, a - Integer))


quite right!  sorry for not testing my code.
-iavor



 Here we are using another GHC extension called scoped type variables
 to associate the a in the type signature of g with the a in the
 type annotation for the value a.

 Hope that this helps,
 Iavor




 On Sun, Dec 21, 2008 at 9:21 AM, Maurí­cio briqueabra...@yahoo.com
 wrote:
  Why isn't the last line of this code allowed?
  f :: (TestClass a) = a - Integer
  f = const 1
  a = (f,f)
  g = fst a
  The only thing I can think about is monomorphism
  restriction, but it's allowed (...)
 
  (...) The reason is that a has type
  a :: (TestClass a, TestClass b) = (a,b)
  and then when we take 'fst' of this value (as in g) we get
 
  g :: (TestClass a, TestClass b) = a
  which is an ambiguous type, (...)
 
  Is there some version (i.e., set of extensions) of
  Haskell where this would be allowed?
 
  ___
  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


Re: [Haskell-cafe] Re: Is this related to monomorphism restriction?

2008-12-21 Thread Iavor Diatchki
Hello,
You can work around the monomorphism restriction with extensions but
to fix the ambiguity in your program that Reiner pointed out you'll
have to change the program to specify how you'd like to instantiate
a.
here are all the types once again:
f :: (TestClass a) = a - Integer
f = const 1

a :: (TestClass a, TestClass b) = (a - Integer, b - Integer)
a = (f,f)

g :: (TestClass a, TestClass b) = a - Integer  -- ambiguous
g = fst a

Note that the type of 'g' to the right of '=' does not mention 'b'.
This means that the type of 'g' is ambiguos because the type checker
does not know how to pick a type for 'b'.  To fix that, you could:
  1. Give 'a' a less general type, for example:  a :: (TestClass a) =
(a - Integer, a - Integer)
  2. Write a type signature on the use of 'a':

g :: TestClass a = a - Integer
g = fst (a :: (a - Integer, a - Integer))

Here we are using another GHC extension called scoped type variables
to associate the a in the type signature of g with the a in the
type annotation for the value a.

Hope that this helps,
Iavor




On Sun, Dec 21, 2008 at 9:21 AM, Maurí­cio briqueabra...@yahoo.com wrote:
 Why isn't the last line of this code allowed?
 f :: (TestClass a) = a - Integer
 f = const 1
 a = (f,f)
 g = fst a
 The only thing I can think about is monomorphism
 restriction, but it's allowed (...)

 (...) The reason is that a has type
 a :: (TestClass a, TestClass b) = (a,b)
 and then when we take 'fst' of this value (as in g) we get

 g :: (TestClass a, TestClass b) = a
 which is an ambiguous type, (...)

 Is there some version (i.e., set of extensions) of
 Haskell where this would be allowed?

 ___
 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] Flexible instances

2008-10-14 Thread Iavor Diatchki
Hi,
There is some discussion about the different design choices relevant
for Haskell's class system in the following paper:
Type classes: exploring the design space
Simon Peyton Jones, Mark Jones, Erik Meijer
Presented at the 1997 Haskell Workshop.
Section 4.5 discusses options related to the restrictions on the instance heads.

-Iavor

On Tue, Oct 14, 2008 at 7:32 PM, Derek Elkins [EMAIL PROTECTED] wrote:
 On Tue, 2008-10-14 at 19:20 -0700, George Pollard wrote:
 I'm a little confused. Why is this allowed:

  data Blah = Blah
 
  instance Eq Blah where
  x == y = True

 But not this:

  class Stringable a where
  toString :: a - String
 
  instance Stringable [Char] where
  toString = id

 (Resulting in:)

  Illegal instance declaration for `Stringable [Char]'
  (All instance types must be of the form (T a1 ... an)
   where a1 ... an are distinct type *variables*
   Use -XFlexibleInstances if you want to disable this.)
  In the instance declaration for `Stringable [Char]'

 'Blah' isn't a type variable, is it? Is my brain just not working right
 today?

 Blah = T

 for [Char], T = [] and a1 = Char where it should be a variable.

 Why this is an error is basically because the Report says so.

 ___
 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] Re: Improving MTL instances (was: Overlapping/Incoherent instances)

2008-10-13 Thread Iavor Diatchki
Hello,
The currently released version of monadLib does not use overlapping
instances, indeed.
However, in the monadLib  repo (http://github.com/yav/monadlib) there
is a file called MonadLib4.hs which contains a version of the
library that is implemented with overlapping instances, so you can
play around with it.  I'd be interested to get feedback on this
version of moandLib.
-Iavor

On Mon, Oct 13, 2008 at 12:44 AM, J. Garrett Morris
[EMAIL PROTECTED] wrote:
 On Mon, Oct 13, 2008 at 12:29 AM, Ryan Ingram [EMAIL PROTECTED] wrote:
 Of course, the point of this message isn't just to complain.  The
 overlap implementation was abhorrent and it *is* better now than it
 was before.

 I'm curious what you find abhorrent about the overlap implementation
 that was there before - in particular, it seems like it was designed
 to handle both the combinatorial explosion and the corner cases you
 mentioned.  Did you find writing the MonadTrans instances unpleasant?
 Was it the presence of overlapping instances at all?

 On Mon, Oct 13, 2008 at 12:35 AM, Don Stewart [EMAIL PROTECTED] wrote:
 I just want to make one small point here encouraging people to try out
 new 'mtl' libraries. There are lots of *new* monad libraries,

 Without knowing better myself: do any of these libraries address the
 issue Ryan's brought up?  I know that monadLib takes the same approach
 the MTL does to this, and so is likely to have the same difficulties.

  /g

 --
 I am in here
 ___
 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] couple of questions on monads

2008-10-13 Thread Iavor Diatchki
Hello,

On Mon, Oct 13, 2008 at 3:16 PM, Stephen Hicks [EMAIL PROTECTED] wrote:
 2008/10/13 Daryoush Mehrtash [EMAIL PROTECTED]:
 Is there a write up on what makes an implementation lazy vs strict?

 I would be interested in seeing this, too!

Typically it has to do with the strictness of the bind operation.
Here is an example to illustrate the difference.
evalState (undefined  return True) undefined

When you evaluate this in the context of Control.Monad.State, the
result is True, while if you evaluate it in the context of
Control.Monad.State.Strict you will get undefined.

It may be interesting to compare MTL's approach to what's done in
monadLib (another monad transformer library).  In monadLib,
transformers like state inherit the strictness of their bind operation
from the underlying monad.  There are two base level monads: Id, which
is lazy, and Lift which is strict.  So to get a strict state monad in
monadLIb, you would write StateT s Lift, and to get the lazy version
you would use StateT s Id.

Hope that this helps,
Iavor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: SourceGraph-0.1 and Graphalyze-0.3

2008-10-06 Thread Iavor Diatchki
Hi all,
(this message is an ad:-)
For people interested in visualizing dependencies between the modules
in their project: on Hackage there is another simple tool called
graphmod that can generate a dot graph from your Haskell source
code.
-Iavor

2008/10/6 Magnus Therning [EMAIL PROTECTED]:
 On Mon, Oct 6, 2008 at 1:19 PM, Niklas Broberg [EMAIL PROTECTED] wrote:
  * the dependency on haskell-src-exts says any version should do, but
  the one shipped in Debian Sid
  (http://packages.debian.org/sid/libghc6-src-exts-dev) doesn't do, so
  some extra versioning info seems to be required

 Ouch, that one's pretty old. Don't the wheels of debian packaging spin
 faster than that? But yeah, it should be haskell-src-exts (= 0.3), to
 avoid trying to dig up that should-be-long-dead-and-buried 0.2.1
 version...

 Yeah, I know.  I reported a bug against it and if I find the time
 tonight I'll try to build an updated debian package.  Not sure what
 the policy is ATM for NMUs though.

 /M

 --
 Magnus Therning(OpenPGP: 0xAB4DFBA4)
 magnus@therning.org  Jabber: magnus@therning.org
 http://therning.org/magnus identi.ca|twitter: magthe

 ___
 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] Views

2008-09-14 Thread Iavor Diatchki
Hi,

On Sun, Sep 14, 2008 at 7:01 AM, Stephan Friedrichs
[EMAIL PROTECTED] wrote:
 I agree that the MonadZero class with a useful 'zero' :: m a would be
 the right abstraction for views. But MonadZero is not part of base, mtl
 or any other common package, or am I missing something? Changing this is
 beyond a simple heap package ;)

The class ExceptionM from monadLib captures this functionality.
However, for this simple case 'Maybe' seems quite enough because it is
what you need most of the time.   Furthermore, it does not loose any
generality because you can use a function of type :: MonadZero m =
Maybe a - m a, to convert to other monads, if it is necessary.
-Iavor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] typeclass question

2008-09-11 Thread Iavor Diatchki
Hi Tim,
Your example seems like a perfect fit for functional dependencies.

On Thu, Sep 11, 2008 at 3:36 AM, Tim Docker [EMAIL PROTECTED] wrote:
 Well, it's a library that others might use, so I would prefer to avoid
 using language extensions, especially functional deps which I don't
 understand, and which seem to have an uncertain future.

I completely agree with you that it is a good idea to stick to
Haskell'98 when you can, especially in library code, so you'll have to
decide if you really want to use the class.  As for not understanding
functional dependencies, it sounds like you are not giving yourself
enough credit.  Your previous comment basically contains the
definition of a functional dependency:

| But the above is, I think, too general for my needs. I don't want
| to be able to generate Renderables of different type b for a single input
| type a.

This is all there is to a fun. dep., from a programmer's
perspective---it adds a constraint on the instances one can declare
for a given multi-parameter type class.

Hope this helps,
-Iavor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hackage policy question

2008-09-08 Thread Iavor Diatchki
Hi,
I just noticed that hackage has introduced a new policy to disallow
changes to a package without bumping the version.  I understand that
this is probably a good idea for changes to the source code, but it
really would be nice to have a backdoor that allows for other changes.
 For example, I just uploaded a package, and realized that I forgot to
add a home-page entry in the cabal file.  I do not plan to increase
the version number of my application, only so that I can upload a new
version (the source code has not changed after all!).  I can imagine
similar problems related to fixing typos in the description, and other
fixes to the meta-data.

So, could we please revert to the old policy? (if we really want to be
fancy, the hackage upload script could check that the source code, and
other fields, such as LICENSE have not changed, as these should really
bump the version... in the mean time though, I think just being
responsible members of the community would work just as well!).

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


Re: [Haskell-cafe] Cyclic Inclusions

2008-08-13 Thread Iavor Diatchki
Hello,

The Haskell'98 report does not specify if/how recursive modules should
work.  I wrote a paper a long time ago that formalizes and implements
this feature (http://www.purely-functional.net/yav/publications/modules98.pdf).
 I very much doubt that separate compilation is much of a problem in
practise because you only need to compile modules that are _recursive_
at the same time, and usually these tend to be fairly small.  Figuring
out the interface of the modules is a bit trickier in some
pathological cases involving module re-exports, but this is already
the case with non-recursive modules.

One real technical problem that I remember was implementing
defaulting, which is specified in terms of a single module.  With
recursive modules, one could get mutually recursive functions from
different modules, in which case it is not clear which set of
defaulting rules to apply or how to combine them.

Hope that this helps,
-Iavor



On Wed, Aug 13, 2008 at 4:30 AM,  [EMAIL PROTECTED] wrote:
 G'day.

 Quoting C.M.Brown [EMAIL PROTECTED]:

 However I saw no real argument for not having cyclic inclusions. You
 say we shouldn't have to spend time writing hi-boot files, and yet  you
 also think
 that GHC should not do it automatically. So we have to restrict all
 programmers to never writing cyclic inclusions?  :)

 GHC generates .hi files for most modules automatically.  The only reason
 why hi-boot files are needed for cyclic imports is because of the
 possibility that you can't generate a .hi file from the module alone.  If
 you could do that, then you could support cyclic imports without needing
 hi-boot files.

 Cheers,
 Andrew Bromage
 ___
 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] Using fundeps to resolve polymorphic types to concrete types

2008-08-02 Thread iavor . diatchki
Hi,

On 7/29/08, Bryan Donlan [EMAIL PROTECTED] wrote:
 Hi,

 Is there any theoretical reason that functional dependencies can't be used
 to resolve a polymorphic type to a concrete type? For example:

 -- compile with -fglasgow-exts

 class DeriveType a b | a - b

 data A = A
 data B = B

 instance DeriveType A B


 simpleNarrow :: DeriveType A b = b - B
 simpleNarrow = id

 Since 'b' is uniquely determined by the fundep in DeriveType, it seems that
 this ought to work; ie, since the only type equation satisfying DeriveType A
 b
 is B - B, it should reduce to that before trying to fit its type against
 its
 body.

According to the theory of functional dependencies this function
should type check
but there is a bug in the current implementation (or you may view it
as an incompleteness---the compiler is not smart enough to infer that
b in this case is really B while checking the signature).

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


Re: [Haskell-cafe] is there some book about haskell and data struct and alg?

2008-05-28 Thread Iavor Diatchki
Hi,
Purely Functional Data Structures by Chris Okasaki is a good one.
Here is a link to it on Amazon:
http://www.amazon.com/Purely-Functional-Structures-Chris-Okasaki/dp/0521663504
Good luck!
-Iavor



2008/5/28 smellcode [EMAIL PROTECTED]:
 is there some book about haskell and data struct and alg?
 i mean data struct and algorithm in haskell

 i am freshman

 i want to study haskell with data struct and alg

 --
 Hu Jinpu (nickname: smellcode)
 Web developer
 email =~ /(^hujinpu)\@(gmail)\.(com)$/
 or email.gsub!(/hujinpu/, 'smellcode')
 http://hujinpu.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] Data.Tree.Zipper in the standard libraries

2008-05-24 Thread Iavor Diatchki
Hello,
I think that the modified API (no state monad, and using Maybe) is
quite nice!  I implemented a version of the the suggested API using a
slightly different data structure, which makes the code a bit simpler,
I think.   I put the code in the Haskell wiki:
http://www.haskell.org/sitewiki/images/2/2d/RoseZipper.hs
I also added a couple of extra functions that seemed useful, and
renamed a few of the functions to be more consistent.

As for how to distribute the code, it seems that Zipper should live in
the same place as Data.Tree.  I think that Data.Tree is part of the
containers package, so it would make sense to add the Zipper there
as well.

-Iavor



On Sat, May 24, 2008 at 1:24 AM, Neil Mitchell [EMAIL PROTECTED] wrote:
 Hi,

 It doesn't use State monad anymore and it returns Maybe. This seems to
 be the common preference, is it? Feel free to vote against. Should we
 change Data.Map also? There is another proposal for changes in
 findMin/findMax so it is better to make this two breaking changes
 together rather than in a later release.

 The standard libraries proposal thingy is to go via the libraries
 list, create tickets etc. What reason is there to make this part of
 the base libraries, rather than a separate package on hackage? I can't
 see much reason to make Data.Tree part of the base libraries, other
 than the fact it already is, and it could easily get moved out at a
 future date.

 We've seen there is some advantage in leaving the implementation
 outside the base library, as its already changed several times in the
 past few days.

 Thnanks

 Neil
 ___
 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] Re: Control.Exception.evaluate - 'correct definition' not so correct

2008-05-04 Thread Iavor Diatchki
Hello,

On Sat, May 3, 2008 at 3:56 AM, apfelmus [EMAIL PROTECTED] wrote:
 Bryan Donlan wrote:

 
evaluate x = (return $! x) = return
 
  However, if = is strict on its first argument, then this definition is
  no better than (return $! x).
 

  According to the monad law

   f = return = f

  every (=) ought to be strict in its first argument, so it indeed seems
 that the implementation given in the documentation is wrong.

From the monad law we can conclude only that (= return) is strict,
not (=) in general.
For example, (=) for the reader monad is not strict in its first argument:

m = f = \r - f (m r) r

So, (undefined  return 2) = (return 2)

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


Re: [Haskell-cafe] Help with complicated type inference

2008-04-27 Thread Iavor Diatchki
Hello,
How about defining the types like this:

data PVal a = Unit a | Array [a]
data Val = IntVal (PVal Int) | BoolVal (PVal Bool) -- | etc

instance Serialize Int where ...
instance Serialize a = Serialize (PVal a) where ...
instance Serialize Val where ...

Hope this helps.
-Iavor



On Sun, Apr 27, 2008 at 4:07 AM, Paul Johnson [EMAIL PROTECTED] wrote:
 I'm trying to write an AMQP framing layer.  AMQP has two very similar union
 types: there is a variant that contains a single item, and an array
 which consists of a list of elements of the same type.  So I thought I could
 define a Unit type container thus:

   newtype Unit a = Unit {unUnit :: a}

  So now I can say:

   type AmqpVariant = AmqpVariantBase Unit
   type AmqpArray = AmqpVariantBase []

  Then the AmqpVariantBase type looks something like this (except that it
 doesn't work, see below):

   data forall a . (AmqpWire a, AmqpWire (c a)) =
  AmqpVariantBase c = AmqpVarBin8 (c Bin8)
 | AmqpVarInt8 (c Int8)
 | AmqpVarUint8 (c Word8)
 | AmqpVarChar (c Word8)
 | AmqpVarBoolean (c Bool)
 | AmqpVarBin16 (c Bin16)
 | AmqpVarInt16 (c Int16)
 | AmqpVarUint16 (c Word16)
 | AmqpVarBin32 (c Bin32)
 | AmqpVarInt32 (c Int32)
-- And on for about 20 more types, including compound types.

  All AMQP types have to be seralised, so I've defined a class AmqpWire for
 serialisation in AMQP format.  All the individual types (Bin8, Int8 etc) are
 instances of this class.  I've also defined instances for Unit and [] such
 as:

   instance (AmqpWire a) = AmqpWire (Unit a) where
  amqpPut = amqpPut . unUnit
  amqpGet = map Unit amqpGet

  The problem is with the type constraint for AmqpVariantBase.  I need to say
 AmqpWire (c a) without explicitly listing all the values of a (i.e.
 Bin8, Int8, etc) because any time I use AmqpVariantBase I have to repeat the
 same constraint.  How do I do this?

  Paul.
  ___
  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] Re: [Haskell] How to define tail function for Even/Odd GADT lists?

2008-04-23 Thread Iavor Diatchki
Hello,
I am not sure of the use case here but you could also do the following:

data EvenList a = Nil
| ConsE a (OddList a)

data OddList a  = ConsO a (EvenList a)

This does not use any type system extensions.

-Iavor

On Wed, Apr 23, 2008 at 4:46 PM, David Roundy [EMAIL PROTECTED] wrote:
 2008/4/23 Martijn Schrage [EMAIL PROTECTED]:

   It depends a bit on what you want to use these lists for, but the following
   encoding works for your examples and doesn't need the type class.
  
   data E
data O
  
type Even = (E,O)
type Odd  = (O,E)

  That's a nice little trick!  I like how you achieve type signatures
  relating two distinct types just by sticking them in a tuple.  :)

  David
  ___
  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] looking for examples of non-full Functional Dependencies

2008-04-18 Thread Iavor Diatchki
Hello,

On Thu, Apr 17, 2008 at 12:05 PM, Martin Sulzmann
[EMAIL PROTECTED] wrote:
  Can you pl specify the improvement rules for your interpretation of FDs.
 That would help!

Each functional dependency on a class adds one extra axiom to the
system (aka CHR rule, improvement rule).  For the example in question
we have:

class D a b | a - b where ...

the extra axiom is:

forall a b c. (D a b, D a c) = (b = c)

This is the definition of functional dependency---it specifies that
the relation 'D' is functional.  An improvement rule follows from a
functional dependency if it can be derived from this rule.  For
example, if we have an instance (i.e., another axiom):

instance D Char Bool

Then we can derive the following theorem:

(D Char a) = (a = Bool)

I think that in the CHR paper this was called instance improvement.
Note that this is not an extra axiom but rather a theorem---adding it
to the system as an axiom does not make the system any more
expressive.  Now consider what happens when we have a qualified
instance:

instance D a a = D [a] [a]

We can combine this with the FD axiom to get:

(D a a, D [a] b) = b = [a]

This is all that follows from the functional dependency.  Of course,
in the presence of other instances, we could obtain more improvement
rules.

As for the consistency rule, it is intended to ensure that instances
are consistent with the FD axiom.  As we saw from the previous
examples, it is a bit conservative in that it rejects some instances
that do not violate the functional dependency.   Now, we could choose
to exploit this fact to compute stronger improvement rules---nothing
wrong with that.  However, this goes beyond FDs.

-Iavor









  I'm simply following Mark Jones' style FDs.

  Mark's ESOP'00 paper has a consistency condition:
  If two instances match on the FD domain then the must also match on their
 range.
  The motivation for this condition is to avoid inconsistencies when
  deriving improvement rules from instances.

  For




  class D a b | a - b

  instance D a a = D [a] [a]
  instance D [Int] Char


  we get

  D [a] b == b =[a]
  D [Int] b == b=Char

  In case of

  D [Int] b we therefore get b=Char *and* b =[a] which leads to a
 (unification) error.
  The consistency condition avoids such situations.


  The beauty of formalism FDs with CHRs (or type functions/families) is that
  the whole improvement process becomes explicit. Of course, it has to match
  the programmer's intuition. See the discussion regarding multi-range FDs.

  Martin


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


Re: [Haskell-cafe] looking for examples of non-full Functional Dependencies

2008-04-17 Thread Iavor Diatchki
Hello,

On Wed, Apr 16, 2008 at 11:06 PM, Martin Sulzmann
[EMAIL PROTECTED] wrote:
  3) Multi-range FDs

  Consider

  class C a b c | a - b c

  instance C a b b = C [a] [b] [b]

  This time it's straightforward.

  C [x] y z yields the improvement y = [b] and z = [b]
  which then allows us to apply the instance.

I don't think that this improvement rule is justified (unless there
are some assumptions that are added to the system that go beyond FD?).
  By the way, note that the above example does not have any instances
for C, so lets first add a base case like this:

instance C Char Bool Bool

Now the instances for C are: { C Char Bool Bool, C [Char] [Bool]
[Bool], ... }.  Certainly, if you just consider these instances, then
the improvement rule that you suggest is valid.  However, suppose that
we also add the instance:

instance C [Int] Char Bool

Note that this instance does not violate the FD: if we know the first
argument, then we know exactly what are the other two arguments.  In
this context, it is not OK to improve C [x] y z as you suggest because
'x' may be instantiate to 'Int'.

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


Re: [Haskell-cafe] looking for examples of non-full Functional Dependencies

2008-04-17 Thread Iavor Diatchki
Hello,

On Thu, Apr 17, 2008 at 10:26 AM, Martin Sulzmann
[EMAIL PROTECTED] wrote:
  leads to an instance improvement/instance improvement conflict,
  like in the single-range FD case

  class D a b | a - b

  instance D a a = D [a] [a]
  instance D [Int] Char

Sorry to be picky but there is no violation of the FD here.  Note that
the class D has only a single ground instance and to violate an FD you
need at least two.  As in the previous example, we can add an instance
like this:

instance D Char Char

This results in more ground instances: { D [Int] Char, D Char Char, D
[Char] [Char], ... } but again, there is no violation of the FD.

I think that a lot of the confusion in discussions such as this one
(and we've had a few of those :-) stems from the fact that the term
functional dependency seems to have become heavily overloaded.
Often, the basic concept is mixed with (i) concepts related to
checking that the basic concept holds (e.g., various restrictions on
instances, etc), (ii) concepts related to how we might want to use the
basic concept (e.g., what improvement rules to use).  Of course, (i)
and (ii) are very important, and there are a lot possible design
choices.  However, a number of the discussions I have seen go like
this:
  1) In general, it is hard to check if instances violate the stated
functional dependencies.
  2) So we have more restrictive rules, that are easier to check.
  3) These more restrictive rules give us stronger guarantees, so we
have more opportunity for improvement.
While there is nothing inherently wrong with this, it is important to
note that the extra improvement is not a result of the use of FDs but
rather, from the extra restrictions that we placed on the instances.
I think that this distinction is important because (i) it avoids
mixing concepts, and (ii) points to new things that we may want to
consider.  For example, I think that there is an opportunity for
improvement in situations where is class is not exported from a
module.  Then we know the full set of instances for the class, and we
may be able to compute improvement rules.

Hope this helps!
-Iavor





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


Re: [Haskell-cafe] looking for examples of non-full Functional Dependencies

2008-04-16 Thread Iavor Diatchki
Hello,

On Wed, Apr 16, 2008 at 8:06 AM, Martin Sulzmann
[EMAIL PROTECTED] wrote:
 We're also looking for (practical) examples of multi-range functional
 dependencies

  class C a b c | c - a b

  Notice that there are multiple (two) parameters in the range of the FD.

  It's tempting to convert the above to

  class C a b c | c - a, c - b

  but this yields a weaker (in terms of type improvement) system.

Could you elaborate on this?  I think that a system that distinguishes
these two would be very confusing.   If you think of the FDs as
logical statements about what is known of type variables, then the FDs
on the two classes correspond to equivalent logical statements, so I
am not sure why would we distinguish them for improvement purposes.
Also, it seems fairly easy to convert between the two forms purely
based on syntax, so if the one somehow results in better improvements,
why would we ever use the other one?

As for examples of interesting uses of functional dependencies,
perhaps the literature on relational databases would provide some?

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


Re: [Haskell-cafe] Re: HTTP client libraries

2008-03-30 Thread Iavor Diatchki
Hi,

On Fri, Mar 28, 2008 at 6:42 AM, John Goerzen [EMAIL PROTECTED] wrote:
 On 2008-03-28, Don Stewart [EMAIL PROTECTED] wrote:
   paulrbrown+haskell-cafe:

  And we have a curl binding, already in wide use.
  
   http://code.haskell.org/curl.git/
  
   a release to hackage is imminent.

  Do you mean this?

  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/curl-1.3.1

  Looks like it's not quite as current as your Git repo.

Is this surprising?  Hackage is not a revision control system.
The curl package on hackage is a fairly recent version of the git repo.

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


Re: [Haskell-cafe] Re: [Haskell] Nested guards?

2007-12-04 Thread Iavor Diatchki
Hello everyone,
Just to clarify, the intended semantics of my example was that it
should behave as if we were to duplicate the common prefix:

server text
  | Just xs - parse text, field1 `elem` xs   = ... do one thing ...
  | Just xs - parse text, field2 `elem` xs   = ... do something else ...

server  _ = ... invalid request ...

The difference is that the nested version is shorter, and probably way
easier for the compiler to produce reasonable code.As I said in my
first post, I am not sure what would be a nice notation for nesting
the guards:  the notation that I used in the example was just the
first thing that came to mind, we might be able to do better.

-Iavor


On Dec 4, 2007 7:26 PM, Nicolas Frisby [EMAIL PROTECTED] wrote:
 It seems there is previous background here that I am unaware of. I'll
 chime in anyway.

 What you describe as the wrong semantics seems to me to be the more
 appropriate. I am inferring that your expected behavior is explained
 such that the first server match ought to fail (and fall through to
 the second server match) because the pattern in the let fails. This
 seems odd to me. If the parse test expression yields a Just
 constructor, then hasn't the first server match succeeded and we ought
 now commit to the let expression?

 I apologize if this should be obvious to anyone familiar with the extension.


 On Dec 4, 2007 2:46 PM, Neil Mitchell [EMAIL PROTECTED] wrote:
  Hi
 
   server text
  | Just xs - parse text = let
x | field1 `elem` xs   = error ... do one thing ...
  | field2 `elem` xs   = error ... do something else ...
in x
   server  _ = error ... invalid request ...
 
  This now has the wrong semantics - before if parse text returned Just
  [] the error invalid request branch was invoked, now its a pattern
  match failure.
 
  I haven't used pattern guards that much (but will once Haskell'
  standardises them, or they get implemented in Hugs!), but their syntax
  seems quite natural. This extension seems to make it harder to
  understand them, and gives some nasty , | parsing issues for a human
  at least - quite possibly for a compiler too. Perhaps if you gave a
  little grammar for extended pattern guards (compared to the original)
  it would be easier to see how naturally they fit in.
 
  Thanks
 
  Neil
  ___
  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


Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Iavor Diatchki
Hi,

We have no binary literals in Haskell and there are situations when it
would have been useful to have this feature (e.g., if the spec of
something that you are working with is already provided using this
notation).

While it may be useful to have overloaded binary literals in the usual
Haskell style, during my PhD work I found that it is also useful
(perhaps even more so) to add non-overloaded binary literals where the
number of digits in the literal determines its type.  The notation
that I used was B00010011 to be a literal of type Word8.  I chose this
notation over one like 0b00010011 because I think that the leading
zero is confusing (the literal usually has plenty of 0s already!).
Also, I like it that my notation suggests that the literals are the
constructors of the corresponding word type.

I think that binary literals are more useful when you work with fairly
short bit sequences, mixing and matching to make longer ones.
Unfortunately, in current Haskell we don't have a family of word types
but instead, a few predefined ones, the shortest of which is Word8, so
perhaps this notation is not so useful.   (I have encoded families of
word types in Haskell, but I think that having language support for
such things as in my work on bitdata, in bluespec, or cryptol is much
nicer).

Hope this helps!
-Iavor

On 10/25/07, Ketil Malde [EMAIL PROTECTED] wrote:
 Dusan Kolar [EMAIL PROTECTED] writes:

   // PLS, no flame

 I apologize if my post came across as such, that was certainly not the
 intent.

  I think the question was [..] whether there's such a literal or not
  and whether it is bad idea to have something like 0b10111011.

 I agree.

   From my point of view, the difference between 0b10111011 and
  (bin[1,0,1,1,1,0,1,1]) is 22-10 that is 12 characters.

 And from my point of view, 0xEE or 0x273 are equally readable, and
 even more succinct.  If you are into bit-twiddling, that is.  For
 user-friendly bitfields you should obviously provide a higher level
 interface.

   So, i would expect only two answers: NO, it is ...,  or YES, in
  version 6.9.0 it is possible. ;-)

 As far as I know, there are no such plans.  Send in a patch and see if
 it gets accepted :-)

 -k
 --
 If I haven't seen further, it is by standing in the footprints of giants
 ___
 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: [Haskell] [Fwd: undecidable overlapping instances: a bug?]

2007-10-21 Thread Iavor Diatchki
Hello,

On 10/19/07, Martin Sulzmann [EMAIL PROTECTED] wrote:
 Simon Peyton-Jones writes:
   ...
   Like you, Iavor, I find it very hard to internalise just why (B) and (C) 
 are important.  But I believe the paper gives examples of why they are, and 
 Martin is getting good at explaining it. Martin: can you give an example, 
 once more, of the importance of (B) (=fullness)?
  

 Fullness (B) is a necessary condition to guarantee that the constraint
 solver (aka CHR solver) derived from the type class program is confluent.

 Here's an example (taken from the paper).

   class F a b c | a-b
   instance F Int Bool Char
   instance F a b Bool = F [a] [b] Bool

 The FD is not full because the class parameter c is not involved in
 the FD. We will show now that the CHR solver is not confluent.

 Here is the translation to CHRs (see the paper for details)

   rule F a b1 c, F a b2 d  == b1=b2  -- (FD)
   rule F Int Bool Char== True   -- (Inst1)
   rule F Int a b   == a=Bool -- (Imp1)
   rule F [a] [b] Bool == F a b Bool -- (Inst2)
   rule F [a] c d   == c=[b]  -- (Imp2)


 The above CHRs are not confluent. For example,
 there are two possible CHR derivations for the initial
 constraint store F [a] [b] Bool, F [a] b2 d

 F [a] [b] Bool, F [a] b2 d
 --_FD (means apply the FD rule)
 F [a] [b] Bool, F [a] [b] d , b2=[b]
 -- Inst2
 F a b Bool, F [a] [b] d , b_2=[b] (*)


 Here's the second CHR derivation

 F [a] [b] Bool, F [a] b2 d
 --_Inst2
 F a b Bool, F [a] b2 d
 --_Imp2
 F a b Bool, F [a] [c] d, b2=[c]   (**)


 (*) and (**) are final stores (ie no further CHR are applicable).
 Unfortunately, they are not logically equivalent (one store says
 b2=[b] whereas the other store says b2=[c]).

But what is wrong with applying the following logical reasoning:

Starting with (**):
F a b Bool, F [a] [c] d, b2=[c]
(by inst2)
F a b Bool, F [a] [c] d, b2=[c], F [a] [b] Bool
(by FD)
F a b Bool, F [a] [c] d, b2=[c], F [a] [b] Bool, [c] = [b]
(applying equalities and omitting unnecessary predicates)
F [a] [b] Bool, F [a] b2 d
(...and then follow your argument to reach (*)...)

Alternatively, if we start at (*):
F a b Bool, F [a] [b] d , b_2=[b]
(by inst2)
F a b Bool, F [a] [b] d , b_2=[b], F [a] [b] Bool
(applying equalities, rearranging, and omitting unnecessary predicates)
F [a] [b] Bool, F [a] b_2 d
(... and then follow you reasoning to reach (**) ...)

So it would appear that the two sets of predicates are logically equivalent.

 To conclude, fullness is a necessary condition to establish confluence
 of the CHR solver. Confluence is vital to guarantee completeness of
 type inference.


 I don't think that fullness is an onerous condition.

I agree with you that, in practice, many classes probably use full
FDs.  However, these extra conditions make the system more
complicated, and we should make clear what exactly are we getting in
return for the added complexity.

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


Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-21 Thread Iavor Diatchki
Hello,

On 10/17/07, Lennart Augustsson [EMAIL PROTECTED] wrote:
 Check Wikipedia.  Peirce law, law of excluded middle, double negation, ...
 they are all equivalent and it can be instructive to see how one can derive
 one from the other.

Apparently these axioms are not all equivalent (I was quite surprised
to learn that :-).  Here is some interesting---but perhaps a bit
advanced for a tutorial on CH---reading which studies the relation
between classical logic and computation:
http://coq.inria.fr/~herbelin/publis/icalp-AriHer03-minimal-classical.ps.gz

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


[Haskell-cafe] Re: [Haskell] [Fwd: undecidable overlapping instances: a bug?]

2007-10-18 Thread Iavor Diatchki
Hello,

I believe that this weak coverage condition (which is also called
the dependency condition somewhere on the wiki) is exactly what GHC
6.4 used to implement but than in 6.6 this changed.  According to
Simon's comments on the trac ticket, this rule requires FDs to be
full to preserve the confluence of the system that is described in
the Understanding Fds via CHRs paper.  I have looked at the paper
many times, and I am very unclear on this point, any enlightenment
would be most appreciated (by the way, there was a post about that on
the haskell-prime list a couple of days ago, which contains a concrete
example as well).

To answer Mark's question, this rule provides enough power for mtl and
monadLib.  They use classes like class StateM m s | m - s and
instances like instance StateM m s = StateM (ExceptionT m) s.  (The
full source code for monadLib is at
http://www.galois.com/~diatchki/monadLib/monadLib-3.3.0/src/MonadLib.hs)

Martin, could you elaborate on the problem with non-termination?  I
have seen examples where the type-checker could loop while trying to
prove things, but I was not aware that there were implications related
to soundness as well.

-Iavor


On 10/18/07, Martin Sulzmann [EMAIL PROTECTED] wrote:
 Mark P Jones writes:
   [Sorry, I guess this should have been in the cafe ...]
  
   Simon Peyton-Jones wrote:
The trouble is that
a) the coverage condition ensures that everything is well behaved
b) but it's too restrictive for some uses of FDs, notably the MTL library
c) there are many possibilities for more generous conditions, but
the useful ones all seem complicated
   
Concerning the last point I've dumped the current brand leader
for (c) into http://hackage.haskell.org/trac/ghc/ticket/1241#comment:15.
   
Better ideas for (c) would be welcome.
  
   Let's take the declaration:  instance P = C t where ...
   The version of the coverage condition in my paper [1] requires
   that TV(t_Y) \subseteq TV(t_X), for each dependency (X-Y) \in F_C.
   (I'm using the notation from the paper; let me know if you need more
   help to parse it.)  This formulation is simple and sound, but it
   doesn't use any dependency information that could be extracted from P.
   To remedy this, calculate L = F_P, the set of functional dependencies
   induced by P, and then expand the right hand side of the set inequality
   above by taking the closure of TV(t_X) with respect to L.  In symbols,
   we have to check that:
  
  TV(t_Y) \subseteq TV(t_X)^+_L, for each (X-Y) \in F_C.
  
   I believe (but haven't formally proved) that this is sound; I don't
   know how to make a more general coverage condition without losing
   that.  I don't know if it's sufficient for examples like MTL (because
   I'm not sure where to look for details of what that requires), but
   if it isn't then I'd be very suspicious ...
  
   All the best,
   Mark
  
   [1] http://www.cs.pdx.edu/~mpj/pubs/fundeps-esop2000.pdf


 I think the above is equivalent to the (refined) weak coverage
 condition in [2] (see Section 6, p26). The weak coverage condition
 give us soundness. More precisely, we obtain confluence from which we
 can derive consistency (which in turn guarantees that the type class
 program is sound).

 *BUT* this only works if we have termination which is often very
 tricky to establish.

 For the example,

  class Concrete a b | a - b where
  bar :: a - String
 
  instance (Show a) = Concrete a b

 termination holds, but the weak coverage condition does *not*
 hold. Indeed, this program should be therefore rejected.

 Martin

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


Re: [Haskell-cafe] Re: Rank-2-polymorphism problem

2007-03-23 Thread Iavor Diatchki

Hello,
What Ian suggested is a very GHC 6.6 specific solution that uses much
more that simply rank-2 types.  Here is another solution that uses
just rank-2 types (and, by the way, all type signatures are optional,
as in ordinary Haskell):

module Value where

class SqlBind a where
 fromSqlValue :: String - a

data Field
data Value

emptyValue :: Field - Value
emptyValue _ = undefined

data Binder = Binder (forall s. SqlBind s = s)

readValue :: Field - Binder - Value
readValue _ (Binder _) = undefined

readOptValue :: Field - Maybe Binder - Value
readOptValue f x = maybe (emptyValue f) (readValue f) x


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


Re: [Haskell-cafe] Re: MPTCs and rigid variables

2007-03-07 Thread Iavor Diatchki

Hello,

On 3/7/07, Claus Reinke [EMAIL PROTECTED] wrote:

AT: associated types, as in GHC


ATs are not in any of the official GHC releases... Are they in the CVS head?

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


Re: [Haskell-cafe] MPTCs and rigid variables

2007-03-04 Thread Iavor Diatchki

Hello,

There is nothing wrong with this program.   I have run into this
problem and I consider it to be a bug/weakness of the type checking
algorithm used by the implementation.

(I also agree with you that the term rigid variable is rather
confusing because it is an artifact of the type checking algorithm
used by GHC.)

-Iavor

On 3/3/07, David House [EMAIL PROTECTED] wrote:

class Foo a b | a - b
instance Foo Int String
bar :: Foo Int b = b
bar = rargh

Is there any reason why that shouldn't work? GHC gives one of its
silly b is a rigid variable errors (aside: that's a really confusing
error; I'd prefer something like Hugs's Infered type is not general
enough).

--
-David House, [EMAIL PROTECTED]
___
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] State monad strictness - how?

2007-01-10 Thread Iavor Diatchki

Hello,


Unfortunately, the current situation is that State is only
available as a lazy monad, and StateT is only available
as a strict monad.


There is no such distinction in monadLib.  The state transformer
inherits its behavior from the underlying monad. For example: StateT
Int IO is strict, but StatT Int Id is lazy.   One way to get a strict
state monad with monadLib is like this:

import MonadLib

data Lift a = Lift { runLift :: a }

instance Monad Lift where
 return x  = Lift x
 Lift x = f  = f x


strict = runLift $ runStateT 2 $
do undefined
   return 5

lazy   = runId $ runStateT 2 $
do undefined
   return 5

The difference between those two is that strict == undefined, while
lazy = (5,undefined).
Unfortunately the monad Lift is not part of monadLib at the moment
so you have to define it on your own, like I did above, but I think
that this is a good example of when it is useful, so I will probably
add it to the next release.

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


  1   2   >