From lightquake at amateurtopologist.com Wed Jan 1 05:02:37 2014 From: lightquake at amateurtopologist.com (Patrick Hurst) Date: Tue, 31 Dec 2013 23:02:37 -0600 Subject: [Haskell-cafe] Get expected type of expression using GHC API? Message-ID: Using the GHC API, you can get the inferred type of an `LHsExpr Id` via a `TypecheckedModule`, as hdevtools does[1]. Is there any way to get the expected type? This would be useful for cases where the expected type is much more polymorphic than the inferred type (or possibly for debugging type errors with -fdefer-type-errors, depending on what GHC does in that case). [1] https://github.com/bennofs/hdevtools/blob/master/src/Info.hs#L133 -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmitdase at gmail.com Wed Jan 1 05:38:58 2014 From: jmitdase at gmail.com (Joey) Date: Tue, 31 Dec 2013 23:38:58 -0600 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? Message-ID: <52C3A9F2.8050608@gmail.com> I'm looking at writing a simple Haskell to Elm translator. Thankfully, the Elm compiler is in Haskell, so I'm just trying transforming syntax trees. I'm wondering, is there a standard way to do this sort of thing? Template Haskell looked promising, but it seems there isn't much of a way to do introspection on function definition. Has there been any work/progress on this? The GHC API seemed useful for compiling, but it seems tricky to use, and I haven't been able to find many tutorials for this sort of thing. I could just be looking in the wrong place. What are the ways I could go about this? Are there any similar projects I could use as reference? What packages are useful for generating and manipulating Haskell ASTs? Does anybody have experience in this area they could share? I've posted a similar question to the Haskell Reddit at http://www.reddit.com/r/haskell/comments/1u55rl/standard_way_to_translate_haskell_to_other/. Thanks! Joey Eremondi From malcolm.wallace at me.com Wed Jan 1 11:13:20 2014 From: malcolm.wallace at me.com (Malcolm Wallace) Date: Wed, 01 Jan 2014 11:13:20 +0000 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? In-Reply-To: <52C3A9F2.8050608@gmail.com> References: <52C3A9F2.8050608@gmail.com> Message-ID: On 1 Jan 2014, at 05:38, Joey wrote: > I'm looking at writing a simple Haskell to Elm translator. Thankfully, the Elm compiler is in Haskell, so I'm just trying transforming syntax trees. > > I'm wondering, is there a standard way to do this sort of thing? Yes. Use the haskell-src-exts parser. It gives you a somewhat standard syntax tree. Then you can use straight pattern-matching equations for transformation, or if that leads to lots of boilerplate code, then something like uniplate can be useful. Regards, Malcolm From omeragacan at gmail.com Wed Jan 1 13:24:30 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Wed, 1 Jan 2014 15:24:30 +0200 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? In-Reply-To: <52C3A9F2.8050608@gmail.com> References: <52C3A9F2.8050608@gmail.com> Message-ID: Compiling Haskell to another language is huge effort, maybe instead of this you can compile Haskell to JS using GHCJS or Fay, and then use Elm FFI to use compiled Haskell functions. --- ?mer Sinan A?acan http://osa1.net 2014/1/1 Joey : > I'm looking at writing a simple Haskell to Elm translator. Thankfully, the > Elm compiler is in Haskell, so I'm just trying transforming syntax trees. > > I'm wondering, is there a standard way to do this sort of thing? Template > Haskell looked promising, but it seems there isn't much of a way to do > introspection on function definition. Has there been any work/progress on > this? > > The GHC API seemed useful for compiling, but it seems tricky to use, and I > haven't been able to find many tutorials for this sort of thing. I could > just be looking in the wrong place. > > What are the ways I could go about this? Are there any similar projects I > could use as reference? What packages are useful for generating and > manipulating Haskell ASTs? Does anybody have experience in this area they > could share? > > I've posted a similar question to the Haskell Reddit at > http://www.reddit.com/r/haskell/comments/1u55rl/standard_way_to_translate_haskell_to_other/. > > Thanks! > > Joey Eremondi > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From iavor.diatchki at gmail.com Wed Jan 1 21:47:09 2014 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Wed, 1 Jan 2014 13:47:09 -0800 Subject: [Haskell-cafe] Consistency issue with type level numeric literals In-Reply-To: <59543203684B2244980D7E4057D5FBC1486FDB16@DB3EX14MBXC306.europe.corp.microsoft.com> References: <20131228085452.38189.qmail@www1.g3.pair.com> <59543203684B2244980D7E4057D5FBC1486FDB16@DB3EX14MBXC306.europe.corp.microsoft.com> Message-ID: Hello, Yep, in 7.8 these are actually built-in constructors (which are not open families) so if you try to define a custom instance you get an error about an illegal instance for a closed type family. Happy new year! Iavor On Dec 30, 2013 6:23 AM, "Simon Peyton-Jones" wrote: > Iavor > > > > Shouldn?t (+) be a closed type family (now that we have such things)? > Then the user couldn?t give new instances. > > > > Simon > > > > *From:* Haskell-Cafe [mailto:haskell-cafe-bounces at haskell.org] *On Behalf > Of *Iavor Diatchki > *Sent:* 29 December 2013 18:30 > *To:* oleg at okmij.org > *Cc:* Haskell Cafe > *Subject:* Re: [Haskell-cafe] Consistency issue with type level numeric > literals > > > > Hi Oleg, > > > > yes, this is a bug, you are not supposed to define custom instances for > the built-in operators. I just left it open until we hook in the solver. > > > > Happy holidays, > > -Iavor > > > > On Sat, Dec 28, 2013 at 12:54 AM, wrote: > > > GHC 7.6.3 has quite convenient type-level numeric literals. We can use > numbers like 1 and 2 in types. However, using the type level numeral > has been quite a bit of a challenge, illustrated, for example, by > the following SO question. > > > http://stackoverflow.com/questions/20809998/type-level-nats-with-literals-and-an-injective-successor > > It seems the challenge has the reason: the type level numerals and > their operations provided in GHC.TypeLits have a consistency > issue. The following code demonstrates the issue: it constructs two > distinct values of the type Sing 2. Singletons aren't singletons. > > {-# LANGUAGE KindSignatures #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE ScopedTypeVariables #-} > {-# LANGUAGE TypeOperators #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE GADTs #-} > {-# LANGUAGE PolyKinds #-} > > module NotSing where > > import GHC.TypeLits > > -- GHC strangely enough lets us define instances for (+) > type instance 1 + 1 = 0 > type instance 0 + 1 = 2 > > -- A singular representative of 1::Nat > s1 :: Sing 1 > s1 = withSing id > > -- A singular representative of 2::Nat > s2 :: Sing 2 > s2 = withSing id > > is2 :: IsZero 0 > is2 = IsSucc s1 > > tran :: IsZero 0 -> Sing 2 > tran (IsSucc x) = case isZero x of > IsSucc y -> case isZero y of > IsZero -> x > > -- Another singular representative of 2::Nat > -- A singular representative of 2::Nat > s2' :: Sing 2 > s2' = tran is2 > > > {- > *NotSing> s2 > 2 > *NotSing> s2' > 1 > -} > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dhrosa at gmail.com Thu Jan 2 01:40:17 2014 From: dhrosa at gmail.com (Diony Rosa) Date: Wed, 1 Jan 2014 20:40:17 -0500 Subject: [Haskell-cafe] Fwd: HFuse Patch In-Reply-To: <20140102000645.GF10627@romba.sitecomwl614> References: <20140101151540.GE16322@romba.sitecomwl614> <20140102000645.GF10627@romba.sitecomwl614> Message-ID: I was told to email this list: Hello, I wish to become maintainer of the HFuse (FUSE bindings for Haskell) package on hackage. The package's github URL and email are both dead, and the package doesn't compile under GHC7. I've gotten the package to work under GHC7 with a patch, and have gotten permission from the original maintainer to take over. My hackage username is dhrosa, and here's the package page: http://hackage.haskell.org/package/HFuse , and the referenced patch is here: http://bugs.debian.org/cgi-bin/bugreport.cgi?bug=703417 Are there any objections? ---------- Forwarded message ---------- From: Paul van der Walt Date: Wed, Jan 1, 2014 at 7:06 PM Subject: Re: HFuse Patch To: Diony Rosa On Wed, Jan 01, 2014 at 19:00:18 -0500, quoth Diony Rosa: In that case, may I take it over? I know how to fix it and am interested in > this package. > That would suit me down to the ground! Feel free to remove all references to me, my name or my website! Thank you very much! Paul -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmitdase at gmail.com Thu Jan 2 04:08:19 2014 From: jmitdase at gmail.com (Joey) Date: Wed, 01 Jan 2014 22:08:19 -0600 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? In-Reply-To: References: <52C3A9F2.8050608@gmail.com> Message-ID: <52C4E633.70802@gmail.com> It would be hard, but the languages are nearly identical, so the translation is pretty trivial AST transforming. I'm also not looking to be complete: my main goal is sharing client and server-side code. Thanks to Malcolm Wallace for the haskell-src-extensions suggestion, it looks great. On 14-01-01 07:24 AM, ?mer Sinan A?acan wrote: > Compiling Haskell to another language is huge effort, maybe instead of > this you can compile Haskell to JS using GHCJS or Fay, and then use > Elm FFI to use compiled Haskell functions. > > --- > ?mer Sinan A?acan > http://osa1.net > > > 2014/1/1 Joey : >> I'm looking at writing a simple Haskell to Elm translator. Thankfully, the >> Elm compiler is in Haskell, so I'm just trying transforming syntax trees. >> >> I'm wondering, is there a standard way to do this sort of thing? Template >> Haskell looked promising, but it seems there isn't much of a way to do >> introspection on function definition. Has there been any work/progress on >> this? >> >> The GHC API seemed useful for compiling, but it seems tricky to use, and I >> haven't been able to find many tutorials for this sort of thing. I could >> just be looking in the wrong place. >> >> What are the ways I could go about this? Are there any similar projects I >> could use as reference? What packages are useful for generating and >> manipulating Haskell ASTs? Does anybody have experience in this area they >> could share? >> >> I've posted a similar question to the Haskell Reddit at >> http://www.reddit.com/r/haskell/comments/1u55rl/standard_way_to_translate_haskell_to_other/. >> >> Thanks! >> >> Joey Eremondi >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe From carter.schonwald at gmail.com Thu Jan 2 04:19:14 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 1 Jan 2014 23:19:14 -0500 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? In-Reply-To: <52C4E633.70802@gmail.com> References: <52C3A9F2.8050608@gmail.com> <52C4E633.70802@gmail.com> Message-ID: have you considered using GHCJS? On Wed, Jan 1, 2014 at 11:08 PM, Joey wrote: > It would be hard, but the languages are nearly identical, so the > translation is pretty trivial AST transforming. I'm also not looking to be > complete: my main goal is sharing client and server-side code. > Thanks to Malcolm Wallace for the haskell-src-extensions suggestion, it > looks great. > > > On 14-01-01 07:24 AM, ?mer Sinan A?acan wrote: > >> Compiling Haskell to another language is huge effort, maybe instead of >> this you can compile Haskell to JS using GHCJS or Fay, and then use >> Elm FFI to use compiled Haskell functions. >> >> --- >> ?mer Sinan A?acan >> http://osa1.net >> >> >> 2014/1/1 Joey : >> >>> I'm looking at writing a simple Haskell to Elm translator. Thankfully, >>> the >>> Elm compiler is in Haskell, so I'm just trying transforming syntax trees. >>> >>> I'm wondering, is there a standard way to do this sort of thing? Template >>> Haskell looked promising, but it seems there isn't much of a way to do >>> introspection on function definition. Has there been any work/progress on >>> this? >>> >>> The GHC API seemed useful for compiling, but it seems tricky to use, and >>> I >>> haven't been able to find many tutorials for this sort of thing. I could >>> just be looking in the wrong place. >>> >>> What are the ways I could go about this? Are there any similar projects I >>> could use as reference? What packages are useful for generating and >>> manipulating Haskell ASTs? Does anybody have experience in this area they >>> could share? >>> >>> I've posted a similar question to the Haskell Reddit at >>> http://www.reddit.com/r/haskell/comments/1u55rl/ >>> standard_way_to_translate_haskell_to_other/. >>> >>> Thanks! >>> >>> Joey Eremondi >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmitdase at gmail.com Thu Jan 2 06:06:50 2014 From: jmitdase at gmail.com (Joey) Date: Thu, 02 Jan 2014 00:06:50 -0600 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? In-Reply-To: References: <52C3A9F2.8050608@gmail.com> <52C4E633.70802@gmail.com> Message-ID: <52C501FA.6060604@gmail.com> It looked interesting, but when I initially started my project (about six months ago) it seemed pretty immature. It also seems to be less focused on graphical programming, which Elm is superb at with its FRP. I'd also heard GHCJS was pretty heavyweight, getting the entire runtime going. I'm really only using JS for rednering. On 14-01-01 10:19 PM, Carter Schonwald wrote: > have you considered using GHCJS? > > > On Wed, Jan 1, 2014 at 11:08 PM, Joey > wrote: > > It would be hard, but the languages are nearly identical, so the > translation is pretty trivial AST transforming. I'm also not > looking to be complete: my main goal is sharing client and > server-side code. > Thanks to Malcolm Wallace for the haskell-src-extensions > suggestion, it looks great. > > > On 14-01-01 07:24 AM, ?mer Sinan A?acan wrote: > > Compiling Haskell to another language is huge effort, maybe > instead of > this you can compile Haskell to JS using GHCJS or Fay, and > then use > Elm FFI to use compiled Haskell functions. > > --- > ?mer Sinan A?acan > http://osa1.net > > > 2014/1/1 Joey >: > > I'm looking at writing a simple Haskell to Elm translator. > Thankfully, the > Elm compiler is in Haskell, so I'm just trying > transforming syntax trees. > > I'm wondering, is there a standard way to do this sort of > thing? Template > Haskell looked promising, but it seems there isn't much of > a way to do > introspection on function definition. Has there been any > work/progress on > this? > > The GHC API seemed useful for compiling, but it seems > tricky to use, and I > haven't been able to find many tutorials for this sort of > thing. I could > just be looking in the wrong place. > > What are the ways I could go about this? Are there any > similar projects I > could use as reference? What packages are useful for > generating and > manipulating Haskell ASTs? Does anybody have experience in > this area they > could share? > > I've posted a similar question to the Haskell Reddit at > http://www.reddit.com/r/haskell/comments/1u55rl/standard_way_to_translate_haskell_to_other/. > > Thanks! > > Joey Eremondi > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Jan 2 06:17:49 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 2 Jan 2014 01:17:49 -0500 Subject: [Haskell-cafe] Standard way to translate Haskell to other languages? In-Reply-To: <52C501FA.6060604@gmail.com> References: <52C3A9F2.8050608@gmail.com> <52C4E633.70802@gmail.com> <52C501FA.6060604@gmail.com> Message-ID: oh, in that case you should check out three-peny gui! hackage.haskell.org/package/threepenny-gui On Thu, Jan 2, 2014 at 1:06 AM, Joey wrote: > It looked interesting, but when I initially started my project (about > six months ago) it seemed pretty immature. It also seems to be less focused > on graphical programming, which Elm is superb at with its FRP. I'd also > heard GHCJS was pretty heavyweight, getting the entire runtime going. I'm > really only using JS for rednering. > > > On 14-01-01 10:19 PM, Carter Schonwald wrote: > > have you considered using GHCJS? > > > On Wed, Jan 1, 2014 at 11:08 PM, Joey wrote: > >> It would be hard, but the languages are nearly identical, so the >> translation is pretty trivial AST transforming. I'm also not looking to be >> complete: my main goal is sharing client and server-side code. >> Thanks to Malcolm Wallace for the haskell-src-extensions suggestion, it >> looks great. >> >> >> On 14-01-01 07:24 AM, ?mer Sinan A?acan wrote: >> >>> Compiling Haskell to another language is huge effort, maybe instead of >>> this you can compile Haskell to JS using GHCJS or Fay, and then use >>> Elm FFI to use compiled Haskell functions. >>> >>> --- >>> ?mer Sinan A?acan >>> http://osa1.net >>> >>> >>> 2014/1/1 Joey : >>> >>>> I'm looking at writing a simple Haskell to Elm translator. Thankfully, >>>> the >>>> Elm compiler is in Haskell, so I'm just trying transforming syntax >>>> trees. >>>> >>>> I'm wondering, is there a standard way to do this sort of thing? >>>> Template >>>> Haskell looked promising, but it seems there isn't much of a way to do >>>> introspection on function definition. Has there been any work/progress >>>> on >>>> this? >>>> >>>> The GHC API seemed useful for compiling, but it seems tricky to use, >>>> and I >>>> haven't been able to find many tutorials for this sort of thing. I could >>>> just be looking in the wrong place. >>>> >>>> What are the ways I could go about this? Are there any similar projects >>>> I >>>> could use as reference? What packages are useful for generating and >>>> manipulating Haskell ASTs? Does anybody have experience in this area >>>> they >>>> could share? >>>> >>>> I've posted a similar question to the Haskell Reddit at >>>> >>>> http://www.reddit.com/r/haskell/comments/1u55rl/standard_way_to_translate_haskell_to_other/ >>>> . >>>> >>>> Thanks! >>>> >>>> Joey Eremondi >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas at incubaid.com Thu Jan 2 20:30:20 2014 From: nicolas at incubaid.com (Nicolas Trangez) Date: Thu, 02 Jan 2014 21:30:20 +0100 Subject: [Haskell-cafe] Designing somewhat-type-safe RPC Message-ID: <1388694620.28084.11.camel@tau.nicolast.be> Hi, While working on the design of an RPC library (for an existing protocol), I got somewhat stuck. The system is fairly simple: for some call, a client first sends an identifier of the call, followed by a serialized form of the argument. Then the server returns some serialized result. A server exposes several procedures, all taking a certain argument type and returning a certain result type. Below is some code which sketches my current approach. The 'client' side seems straight-forward and working (hence 'runCall'), but I didn't manage to implement the server side as I imagine it to be (i.e. the parts commented out). Any pointers would be appreciated. Thanks, Nicolas {-# LANGUAGE GADTs, RankNTypes, OverloadedStrings, KindSignatures, ScopedTypeVariables #-} module RPC where import Data.Word (Word32) import Data.Binary (Binary, decode, encode) class RPC (a :: * -> * -> *) where rpcProcedureId :: a req res -> Word32 {- rpcProcedure :: Word32 -> Maybe (a req res) -} data Service req res where Ping :: Service () () Add :: Service (Word32, Word32) Word32 instance RPC Service where rpcProcedureId p = case p of Ping -> 1 Add -> 2 {- rpcProcedure i = case i of 1 -> Just Ping 2 -> Just Add _ -> Nothing -} runCall :: forall call req res. (RPC call, Binary req, Binary res) => call req res -> req -> IO res runCall call req = do let bs = encode req idx = rpcProcedureId call -- Send idx & bs to network, read stuff from network and interpret s <- return $ encode (3 :: Word32) return $ decode s runServer :: (RPC call, Binary req, Binary res) => (call req res -> req -> IO res) -> IO () {- runServer handler = do i <- return 2 -- Read from network case rpcProcedure i of Nothing -> error "No such procedure" Just (call :: call req res) -> do -- Read request from network s <- return $ encode (1 :: Word32, 2 :: Word32) let (req :: req) = decode s (res :: res) <- handler call req -- Send reply to network let res' = encode res return () -} runServer handler = undefined main :: IO () main = do runCall Ping () >>= print runCall Add (1, 2) >>= print {- runServer handler where handler :: Service req res -> req -> IO res handler c (r :: req) = case c of Ping -> return () Add -> case r of (a, b) -> return (a + b) -} From jwlato at gmail.com Thu Jan 2 23:55:42 2014 From: jwlato at gmail.com (John Lato) Date: Thu, 2 Jan 2014 15:55:42 -0800 Subject: [Haskell-cafe] Designing somewhat-type-safe RPC In-Reply-To: <1388694620.28084.11.camel@tau.nicolast.be> References: <1388694620.28084.11.camel@tau.nicolast.be> Message-ID: This looks very similar to some code that I was working on a few months ago, https://github.com/JohnLato/lifted-lens. I never really started to use it, but everything that's there works (sadly I don't have any examples right now, but the module Language.Lens.Lifted is the top-level, and I could add an example if you're interested). First, consider how something might work without using GADTs. You'd want your server to read the identifiers, figure out the types to use for everything, and instantiate its argument at the correct types. This means you'd have a function like: > runServer :: (forall call req res. (RPC call, Binary req, Binary res) => call req res -> req -> IO res) -> IO () Now, I'm not entirely sure how this will interact with GADTs as you're using them. The problem I had with lifted-lens was convincing GHC that various constraints (that are required by certain GADT constructors) were satisfiable at the point the constructor would be applied. I ended up needing to do a lot of CPS-like transforms in more places than I expected. On Thu, Jan 2, 2014 at 12:30 PM, Nicolas Trangez wrote: > Hi, > > While working on the design of an RPC library (for an existing > protocol), I got somewhat stuck. > The system is fairly simple: for some call, a client first sends an > identifier of the call, followed by a serialized form of the argument. > Then the server returns some serialized result. > A server exposes several procedures, all taking a certain argument type > and returning a certain result type. > > Below is some code which sketches my current approach. The 'client' side > seems straight-forward and working (hence 'runCall'), but I didn't > manage to implement the server side as I imagine it to be (i.e. the > parts commented out). > > Any pointers would be appreciated. > > Thanks, > > Nicolas > > > {-# LANGUAGE GADTs, > RankNTypes, > OverloadedStrings, > KindSignatures, > ScopedTypeVariables #-} > > module RPC where > > import Data.Word (Word32) > import Data.Binary (Binary, decode, encode) > > class RPC (a :: * -> * -> *) where > rpcProcedureId :: a req res -> Word32 > {- > rpcProcedure :: Word32 -> Maybe (a req res) > -} > > data Service req res where > Ping :: Service () () > Add :: Service (Word32, Word32) Word32 > > instance RPC Service where > rpcProcedureId p = case p of > Ping -> 1 > Add -> 2 > {- > rpcProcedure i = case i of > 1 -> Just Ping > 2 -> Just Add > _ -> Nothing > -} > > runCall :: forall call req res. (RPC call, Binary req, Binary res) => > call req res -> req -> IO res > runCall call req = do > let bs = encode req > idx = rpcProcedureId call > -- Send idx & bs to network, read stuff from network and interpret > s <- return $ encode (3 :: Word32) > > return $ decode s > > > runServer :: (RPC call, Binary req, Binary res) => (call req res -> req > -> IO res) -> IO () > {- > runServer handler = do > i <- return 2 -- Read from network > case rpcProcedure i of > Nothing -> error "No such procedure" > Just (call :: call req res) -> do > -- Read request from network > s <- return $ encode (1 :: Word32, 2 :: Word32) > let (req :: req) = decode s > (res :: res) <- handler call req > -- Send reply to network > let res' = encode res > return () > -} > runServer handler = undefined > > main :: IO () > main = do > runCall Ping () >>= print > runCall Add (1, 2) >>= print > {- > runServer handler > where > handler :: Service req res -> req -> IO res > handler c (r :: req) = case c of > Ping -> return () > Add -> case r of (a, b) -> return (a + b) > -} > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Fri Jan 3 05:14:31 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 3 Jan 2014 05:14:31 -0000 Subject: [Haskell-cafe] Designing somewhat-type-safe RPC Message-ID: <20140103051431.10937.qmail@www1.g3.pair.com> The remote procedure call is obviously a partial function: first of all, it may fail because of various network problems. It may also fail if a client and a server disagree on the types of the arguments and the results of the function call. For example, the client may think that "Add" service adds integers while the server takes "Add" to sum floats. There is nothing in the type system that can enforce the agreement between distributed entities. So, we are liable to get serialization/deserialization errors. It is inevitable that the communication part is a big "Dynamic", and getting data from that Dynamic may fail because of `type' errors (the data were serialized at a different type than expected, or the data were corrupted in transit). With these assumptions, the implementation is straightforward (enclosed). Both the server and the client operations are typed (but the middle part, the communication, is necessarily `untyped'). Incidentally, some three years ago I wrote a quite more advanced RPC library, in OCaml. It didn't use any GADTs and other bleeding stuff (first, OCaml did not have GADTs at the time; second, I'm minimalist). It did much more, including semi-automatic request batching and some fairly complex server programs including conditionals. It already does more than X protocol and Java RPC. If I added server-side loops, it would do even more. Alas, I didn't have time to come back to that project since. http://okmij.org/ftp/meta-future/meta-future.html {-# LANGUAGE ExistentialQuantification #-} module RPC where import System.IO import qualified Data.Map as M -- identifiers of functions to call type ServiceID = String -- ------------------------------------------------------------------------ -- Server part -- For simplicity, we use Read for deserialization and Show for -- serialization. Binary would've been a better choice for both -- All functions are supposed to be uncurried. -- ServerFn essentially packs a function together with the serializer -- of the result and the deserializer for arguments. data ServerFn = forall a b. (Read a, Show b) => ServerFn (a->b) type Services = M.Map ServiceID ServerFn -- For simplicity, we handle just one request, which we read from -- the handle. We write the result to stdio. It is easy to generalize: -- write the result to an output handle and loop. runServer :: Services -> Handle -> IO () runServer services h = do service_id <- hGetLine h putStrLn $ service_id args <- hGetLine h maybe (fail $ "no such service: " ++ service_id) (handle args) $ M.lookup service_id services where handle sargs (ServerFn f) = do let args = read sargs print $ f args -- Sample services services :: Services services = M.fromList [ ("Ping", ServerFn (\ () -> ())), ("Add", ServerFn (\ (x,y) -> x + y :: Int)) ] -- ------------------------------------------------------------------------ -- Client part -- Stubs of server fn -- ClientFn a b represents a function a->b to be executed by a server data ClientFn a b = ClientFn ServiceID ping :: ClientFn () () ping = ClientFn "Ping" add :: ClientFn (Int,Int) Int add = ClientFn "Add" -- the set of functions is open; more can be added at any time -- Do the remote function application rpc :: (Show a, Read b) => Handle -> ClientFn a b -> a -> IO b rpc h (ClientFn fid) x = do hPutStrLn h fid hPutStrLn h (show x) -- read the result: currently stabbed result_str <- return "stubbed" return $ read result_str -- ------------------------------------------------------------------------ -- Test comm_file = "/tmp/connection" main = do h <- openFile comm_file WriteMode -- send the request down to h. In this example, the return communication -- is not implemented res <- rpc h add (2::Int,3::Int) -- don't look at the result: it this example, it is undefined hClose h h <- openFile comm_file ReadMode runServer services h From oleg at okmij.org Fri Jan 3 05:21:22 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 3 Jan 2014 05:21:22 -0000 Subject: [Haskell-cafe] SYB supports genuine gmap Message-ID: <20140103052122.31606.qmail@www1.g3.pair.com> For the record, I have described the implementation of generic map (which is fmap implemented generically, once and for all). http://okmij.org/ftp/Haskell/generics.html#gmap The article stresses a drawback of a fake gmap in terms of gfoldl: a fake gmap is non-parametric. It fails the law gmap f . gmap g == gmap (f.g). OTH, the genuine gmap satisfies the law, as behooves to the generic version of fmap. Although gmap is implemented in terms of the parametricity-breaking type-introspecting SYB, the gmap is parametric nevertheless. From leza.ml at fecrd.cujae.edu.cu Fri Jan 3 17:19:46 2014 From: leza.ml at fecrd.cujae.edu.cu (Leza Morais Lutonda) Date: Fri, 03 Jan 2014 09:19:46 -0800 Subject: [Haskell-cafe] "Segmentation fault/access violation" when working with FFI Message-ID: <52C6F132.4060203@fecrd.cujae.edu.cu> Hi, I has trying to use the portaudio [1] package to play some sound, and running the examples [2] and it results in the "Segmentation fault/access violation" error. Any idea? Thanks. [1] http://hackage.haskell.org/package/portaudio [2] https://github.com/sw17ch/portaudio/blob/master/examples/Example1.h From adam at bergmark.nl Fri Jan 3 13:55:47 2014 From: adam at bergmark.nl (Adam Bergmark) Date: Fri, 3 Jan 2014 08:55:47 -0500 Subject: [Haskell-cafe] (automatically) adding import statements in vim In-Reply-To: <20131229183031.GA24744@machine> References: <20131226163820.GA29020@machine> <20131229183031.GA24744@machine> Message-ID: Hi Daniel, > If I'm getting this correctly, than Halberd uses some kind of static database, right? Right. > I think the nice approach of 'vim-hsimport' is, that by using 'hdevtools' in conjunction with a 'cabal sandbox', only the modules of the packages are considered, which your project depends on, and this information is dynamically "established" by 'hdevtools' reading the package database of the 'cabal sandbox'. I recall Erik and others discussing ways of restricting halberd to a sandbox as well, but you'd have to ask him about the progress. Cheers, Adam On Sun, Dec 29, 2013 at 1:30 PM, Daniel Trstenjak < daniel.trstenjak at gmail.com> wrote: > > Hi Adam, > > > You may also be interested in Halberd[1][2] which uses hs-gen-iface[3] to > > do automatically insert missing imports by finding modules with the > > desired names. It does not have a vim plugin yet, but I imagine a > > simplistic one should be easy to make. > > If I'm getting this correctly, than Halberd uses some kind of static > database, right? > > I think the nice approach of 'vim-hsimport' is, that by using 'hdevtools' > in > conjunction with a 'cabal sandbox', only the modules of the packages are > considered, > which your project depends on, and this information is dynamically > "established" > by 'hdevtools' reading the package database of the 'cabal sandbox'. > > But I have to confess, that hsimport/vim-hsimport are still in a quite > early stage. > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rda at lemma-one.com Fri Jan 3 16:28:28 2014 From: rda at lemma-one.com (Rob Arthan) Date: Fri, 3 Jan 2014 16:28:28 +0000 Subject: [Haskell-cafe] Infelicity in StdGen? Message-ID: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> Either I am misunderstanding something or there is an infelicity in the implementation of StdGen. The documentation on mkStdGen says that distinct arguments should be likely to produce distinct generators. This made me think that I would get a reasonable pseudo-random function to simulate n rolls of a die by using n to seed the random number generator: import System.Random roll :: Int -> String roll n = take n . randomRs ('1', '6') . mkStdGen $ n However, this produces a string beginning with a '6' for 0 <= n <= 53667. In fact the dependency of the first value on the seed seems to be far from random: map (\l -> (head l, length l)) . group . map (fst . randomR (1, 6) . mkStdGen) $ [0..25*53668+6] returns: [(6,53668),(5,53668),(4,53668),(3,53669),(2,53668),(1,53668),(6,53669),(5,53668),(4,53668),(3,53669),(2,53668),(1,53668),(6,53668),(5,53669),(4,53668),(3,53668),(2,53669),(1,53668),(6,53668),(5,53669),(4,53668),(3,53668),(2,53669),(1,53668),(6,53668)] The behaviour seems to be related to the length of the range. You get similar behaviour for ranges of length 2, 3, 6 and 9 for example, but not for 4, 5, 7 or 8. If it is relevant, I am using ghc version 7.6.3. Regards, Rob. -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas at incubaid.com Fri Jan 3 17:41:31 2014 From: nicolas at incubaid.com (Nicolas Trangez) Date: Fri, 03 Jan 2014 18:41:31 +0100 Subject: [Haskell-cafe] Designing somewhat-type-safe RPC In-Reply-To: <1388694620.28084.11.camel@tau.nicolast.be> References: <1388694620.28084.11.camel@tau.nicolast.be> Message-ID: <1388770891.24039.6.camel@tau.nicolast.be> On Thu, 2014-01-02 at 21:30 +0100, Nicolas Trangez wrote: > Hi, > > While working on the design of an RPC library (for an existing > protocol), I got somewhat stuck. > The system is fairly simple: for some call, a client first sends an > identifier of the call, followed by a serialized form of the argument. > Then the server returns some serialized result. > A server exposes several procedures, all taking a certain argument type > and returning a certain result type. I figured out how to get my intentions into working code thanks to the input of John Lato (which got me to the correct type signature... I always have troubles with those RankN types) and Oleg (for using an existential type in his solution. I tried that before, but must have done something wrong). Thanks! The end result only uses GADTs and Rank2Types, so I think that's fairly reasonable. Code below. Regards, Nicolas {-# LANGUAGE Rank2Types, GADTs #-} {-# OPTIONS_GHC -Wall #-} module RPC2 where import Data.Word (Word32) import Data.Binary (Binary, decode, encode) import Control.Monad (forever) import Control.Monad.IO.Class (MonadIO(liftIO)) import System.IO (hFlush, stdout) -- Library code -- Not exported, use `procedure` instead data SomeProcedure a = forall req res. (Binary req, Binary res) => SomeProcedure (a req res) class RPC a where rpcProcedureId :: a req res -> Word32 rpcProcedure :: Word32 -> Maybe (SomeProcedure a) procedure :: (Binary req, Binary res) => a req res -> Maybe (SomeProcedure a) procedure = Just . SomeProcedure runServer :: (MonadIO m, RPC call) => (forall req res. call req res -> req -> m res) -> m () runServer handler = forever $ do -- Read tag from network tag <- liftIO $ do putStr "Procedure tag: " >> hFlush stdout read `fmap` getLine case rpcProcedure tag of Nothing -> liftIO $ putStrLn "Unknown procedure!" -- TODO Handle correctly Just (SomeProcedure c) -> do -- Read request data from network input <- recvData let req = decode input res <- handler c req let res' = encode res -- Write result to network liftIO $ putStrLn $ "Result data: " ++ show res' where -- Fake data coming from network -- (Note: when the request is 'Ping', `()` can be read from this as -- well) recvData = return $ encode (1 :: Word32, 2 :: Word32) -- API user code data Service req res where Ping :: Service () () Add :: Service (Word32, Word32) Word32 instance RPC Service where rpcProcedureId p = case p of Ping -> 0 Add -> 1 rpcProcedure i = case i of 0 -> procedure Ping 1 -> procedure Add _ -> Nothing serviceHandler :: Service req res -> req -> IO res serviceHandler call req = case call of Ping -> putStrLn $ "Ping " ++ show req Add -> do putStrLn $ "Add " ++ show req return (fst req + snd req) main :: IO () main = runServer serviceHandler From gtener at gmail.com Fri Jan 3 19:22:08 2014 From: gtener at gmail.com (=?UTF-8?Q?Krzysztof_Skrz=C4=99tnicki?=) Date: Fri, 3 Jan 2014 20:22:08 +0100 Subject: [Haskell-cafe] Infelicity in StdGen? In-Reply-To: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> References: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> Message-ID: I think the confusion may be come from the understanding of "distinct". The documentation is right that the generators are not equal which is easily checked e.g. using their Show instance. They *will* produce different random numbers. The user of the library might OTOH assume that "distinct" mean "producing uncorrelated output". This is harder and may simply not hold, especially that it doesn't mention sequentially increasing integers or any other kinds of sequences. The property you seem to be looking for is "have vastly different output for similar numbers". Sounds a lot like a hash function to me. > import Data.Hashable -- hashable > import System.Random -- random > hGen :: (Hashable a) => a -> StdGen > hGen = mkStdGen . hash GHCi: > mkStdGen <$> [1..10] [2 1,3 1,4 1,5 1,6 1,7 1,8 1,9 1,10 1,11 1] > hGen <$> [1..10] [2113803271 1,707778093 1,377439146 1,354368904 1,1689773631 1,1515981814 1,1419492475 1,1232077631 1,2037530173 1,1078099554 1] You can also ask System.Random for a required set of random numbers for use as seeds. > map mkStdGen <$> replicateM 10 randomIO [817657009 1,491059977 1,1962205061 1,375413047 1,626395891 1,1694342924 1,1145131839 1,441215930 1,1278080790 1,1524285256 1] Finally, StdGen provides 'split' since it implements RandomGen typeclass. Using Data.List.unfoldr: > take 10 $ unfoldr (Just . split) (mkStdGen 1) [3 40692,80029 2147442707,1054756830 2147402015,545291968 2147361323,879767459 2147320631,1464499717 2147279939,2107652444 2147239247,1777851630 2147198555,1414574869 2147157863,1574498162 2147117171] The question is what really are your needs here. Different applications will require different properties. I hope the above will give some hints. On Fri, Jan 3, 2014 at 5:28 PM, Rob Arthan wrote: > Either I am misunderstanding something or there is an infelicity > in the implementation of StdGen. The documentation on mkStdGen says > that distinct arguments should be likely to produce distinct generators. > This made me think that I would get a reasonable pseudo-random function > to simulate n rolls of a die by using n to seed the random > number generator: > > import System.Random > roll :: Int -> String > roll n = take n . randomRs ('1', '6') . mkStdGen $ n > > However, this produces a string beginning with a '6' for 0 <= n <= 53667. > In fact the dependency of the first value on the seed seems to be far from > random: > > map (\l -> (head l, length l)) . group . map (fst . randomR (1, 6) . > mkStdGen) $ [0..25*53668+6] > > returns: > > > [(6,53668),(5,53668),(4,53668),(3,53669),(2,53668),(1,53668),(6,53669),(5,53668),(4,53668),(3,53669),(2,53668),(1,53668),(6,53668),(5,53669),(4,53668),(3,53668),(2,53669),(1,53668),(6,53668),(5,53669),(4,53668),(3,53668),(2,53669),(1,53668),(6,53668)] > > The behaviour seems to be related to the length of the range. > You get similar behaviour for ranges of length 2, 3, 6 and 9 for example, > but not for 4, 5, 7 or 8. > > If it is relevant, I am using ghc version 7.6.3. > > Regards, > > Rob. > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Fri Jan 3 22:57:13 2014 From: trebla at vex.net (Albert Y. C. Lai) Date: Fri, 03 Jan 2014 17:57:13 -0500 Subject: [Haskell-cafe] Infelicity in StdGen? In-Reply-To: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> References: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> Message-ID: <52C74049.20709@vex.net> On 14-01-03 11:28 AM, Rob Arthan wrote: > roll n = take n . randomRs ('1', '6') . mkStdGen $ n > > However, this produces a string beginning with a '6' for 0 <= n <= 53667. It seems to me such small numbers do not have enough entropy to be worthy seeds to begin with. Say, in the 64-bit binary form of 53667, how many consecutive 0's are there? From threads at felicity.iiit.ac.in Sat Jan 4 00:21:42 2014 From: threads at felicity.iiit.ac.in (Threads) Date: Sat, 04 Jan 2014 05:51:42 +0530 Subject: [Haskell-cafe] An Invitation to Gordian Knot, a mathematics and computing problem solving contest Message-ID: Hello everyone! Felicity, the annual festival of IIIT Hyderabad, brings to you Felicity Threads 2014, the tenth annual edition of the celebration of spirit of computing and engineering. We bring to you a wide range of online contests in various fields of programming and mathematics. Our series of online events includes contests on algorithmic programming (Codecraft), parallel programming (Kernel Cruise), combinatorial search and game playing bot design (Strange Loop), and a CTF-style security contest (Break In). Our first event, Gordian Knot, a Project Euler-inspired contest full of mathematical problems, starts TODAY at 1600 Hrs (IST), and will run for atleast a day. Being a mathematics and computing contest, Gordian Knot challenges you to come up with solutions to problems and untangle complex yet elegant knots, using any methods and computational tools at your disposal. http://www.felicity.iiit.ac.in/threads/gordian-knot/ [1] The only prerequisite to participate is the urge to learn. Let us learn and rejoice the spirit of computing and engineering together. There are exciting prizes for the event too! So let the mathematician inside you come out and to know more about Threads, visit us at : http://felicity.iiit.ac.in/threads/ [2] Sincerely, Threads 2014 Team Links: ------ [1] http://www.felicity.iiit.ac.in/threads/gordian-knot/ [2] http://felicity.iiit.ac.in/threads/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Sat Jan 4 14:49:18 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sat, 4 Jan 2014 15:49:18 +0100 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements Message-ID: <20140104144918.GA24476@machine> Hi all, vim-hsimport is a Vim plugin that automatically creates import statements for Haskell source files for the symbol/identifier under the cursor. vim-hsimport can create import statements for the whole module, for only the desired symbol/indentifier and is also able to create qualified module import statements. By using hdevtools in conjunction with a cabal sandbox, dynamically only the modules of packages are considered, which your project depends on. vim-hsimport does also consider the modules of your current project. If the symbol/identifier is contained in multiple modules, then a selection dialog is shown. In conjunction to the hsimport command the Vim plugin also uses the command hdevtools and the Vim plugin vim-hdevtools. Currently you need to use forks of hdevtools and vim-hdevtools to get a working version of vim-hsimport, please see the installation section for details. Currently the biggest issue is if and how modules of your current project are considered for the import, please see the issues section. https://github.com/dan-t/vim-hsimport Greetings, Daniel From ierton at gmail.com Sat Jan 4 15:51:42 2014 From: ierton at gmail.com (Sergey Mironov) Date: Sat, 4 Jan 2014 19:51:42 +0400 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements In-Reply-To: <20140104144918.GA24476@machine> References: <20140104144918.GA24476@machine> Message-ID: Oh, my dream! Great! 2014/1/4 Daniel Trstenjak > > Hi all, > > vim-hsimport is a Vim plugin that automatically creates import > statements for Haskell source files for the symbol/identifier under the > cursor. > > vim-hsimport can create import statements for the whole module, for only > the desired symbol/indentifier and is also able to create qualified > module import statements. > > By using hdevtools in conjunction with a cabal sandbox, dynamically > only the modules of packages are considered, which your project depends on. > > vim-hsimport does also consider the modules of your current project. > > If the symbol/identifier is contained in multiple modules, then a > selection dialog is shown. > > In conjunction to the hsimport command the Vim plugin also uses the > command hdevtools and the Vim plugin vim-hdevtools. > > Currently you need to use forks of hdevtools and vim-hdevtools to get a > working version of vim-hsimport, please see the installation section for > details. > > Currently the biggest issue is if and how modules of your current project > are > considered for the import, please see the issues section. > > https://github.com/dan-t/vim-hsimport > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Sat Jan 4 17:23:01 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sat, 4 Jan 2014 18:23:01 +0100 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements In-Reply-To: <20140104144918.GA24476@machine> References: <20140104144918.GA24476@machine> Message-ID: <20140104172300.GA27499@machine> > https://github.com/dan-t/vim-hsimport It's more or less a quite thin wrapper around the commands hsimport and hdevtools, so having support for other editors shouldn't be that much work. Greetings, Daniel From hesselink at gmail.com Sat Jan 4 20:13:03 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Sat, 4 Jan 2014 21:13:03 +0100 Subject: [Haskell-cafe] (automatically) adding import statements in vim In-Reply-To: References: <20131226163820.GA29020@machine> <20131229183031.GA24744@machine> Message-ID: On Fri, Jan 3, 2014 at 2:55 PM, Adam Bergmark wrote: > Hi Daniel, > >> If I'm getting this correctly, than Halberd uses some kind of static >> database, right? > > Right. To be more clear, it uses the database built by hs-gen-iface [0], which is a compile-like tool that generates an interface database for your packages. You have to make a separate `cabal` call to use it and build the database for each package you compile. Hopefully in the future, cabal will have a way to automatically call compiler-like tools (think haddock as wel). But for now, it's a bit impractical. >> I think the nice approach of 'vim-hsimport' is, that by using 'hdevtools' >> in > conjunction with a 'cabal sandbox', only the modules of the packages are > considered, > which your project depends on, and this information is dynamically > "established" > by 'hdevtools' reading the package database of the 'cabal sandbox'. > > I recall Erik and others discussing ways of restricting halberd to a sandbox > as well, but you'd have to ask him about the progress. Right now halberd uses the global and user database. It should be fairly trivial to add support for cabal sandboxes, although there will probably be some duplication with cabal in the sandbox flags at least. Let me know if you're interested. Regards, Erik [0] http://hackage.haskell.org/package/hs-gen-iface From daniel.trstenjak at gmail.com Sun Jan 5 08:43:21 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 5 Jan 2014 09:43:21 +0100 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements In-Reply-To: <20140104144918.GA24476@machine> References: <20140104144918.GA24476@machine> Message-ID: <20140105084320.GA10455@machine> There has been an issue building hsimport from hackage which is now fixed with hsimport 0.2.6.3. Greetings, Daniel From magnus at therning.org Sun Jan 5 12:00:45 2014 From: magnus at therning.org (Magnus Therning) Date: Sun, 5 Jan 2014 13:00:45 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? Message-ID: <20140105120045.GC1366@mteis.lan> I get the following error when trying to build hsimports: [7 of 7] Compiling HsImport ( src/HsImport.hs, dist/build/HsImport.dyn_o ) /usr/bin/ld: dist/build/HsImport/Args.dyn_o: relocation R_X86_64_PC32 against undefined symbol `hsimportzm0zi2zi6zi3_Pathszuhsimport_version1_closure' can not be used when making a shared object; recompile with -fPIC /usr/bin/ld: final link failed: Bad value collect2: error: ld returned 1 exit status What could be causing this? /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus Do not meddle in the affairs of Wizards, for they are subtle and quick to anger. -- J.R.R Tolkien -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From alexander at plaimi.net Sun Jan 5 12:17:54 2014 From: alexander at plaimi.net (Alexander Berntsen) Date: Sun, 05 Jan 2014 13:17:54 +0100 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements In-Reply-To: <20140104144918.GA24476@machine> References: <20140104144918.GA24476@machine> Message-ID: <52C94D72.1040802@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 Please add a licence that permits us to use, improve and share it. - -- Alexander alexander at plaimi.net http://plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlLJTXIACgkQRtClrXBQc7WIcgD+N8hkrZHvdqlkvMPddjowxIwc ixCvoRm1jMp5oOv+WWQBALWs/ohWyXm9R09fJ9MCp19Bow8/ZwP6hPBz+U4KSBuR =QL+s -----END PGP SIGNATURE----- From daniel.trstenjak at gmail.com Sun Jan 5 12:21:30 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 5 Jan 2014 13:21:30 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140105120045.GC1366@mteis.lan> References: <20140105120045.GC1366@mteis.lan> Message-ID: <20140105122130.GA16826@machine> Hi Magnus, On Sun, Jan 05, 2014 at 01:00:45PM +0100, Magnus Therning wrote: > I get the following error when trying to build hsimports: > > [7 of 7] Compiling HsImport ( src/HsImport.hs, dist/build/HsImport.dyn_o ) > /usr/bin/ld: dist/build/HsImport/Args.dyn_o: relocation R_X86_64_PC32 against undefined symbol `hsimportzm0zi2zi6zi3_Pathszuhsimport_version1_closure' can not be used when making a shared object; recompile with -fPIC > /usr/bin/ld: final link failed: Bad value > collect2: error: ld returned 1 exit status > > What could be causing this? Could you please test it with hsimport 0.2.6.4. Greetings, Daniel From magnus at therning.org Sun Jan 5 12:34:45 2014 From: magnus at therning.org (Magnus Therning) Date: Sun, 5 Jan 2014 13:34:45 +0100 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements In-Reply-To: <20140104144918.GA24476@machine> References: <20140104144918.GA24476@machine> Message-ID: <20140105123445.GD1366@mteis.lan> On Sat, Jan 04, 2014 at 03:49:18PM +0100, Daniel Trstenjak wrote: [...] > Currently you need to use forks of hdevtools and vim-hdevtools to > get a working version of vim-hsimport, please see the installation > section for details. Any luck with getting your changes to hdevtools and vim-hdevtools into upstream? /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus "Sendmail" and "make" are two well known programs that are pretty widely regarded as being debugged into existence. That's why their command languages are so poorly thought out and difficult to learn. It's not just you -- everyone finds them troublesome. -- Peter van der Linden, Expert C Programming, p. 220 -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From magnus at therning.org Sun Jan 5 12:44:56 2014 From: magnus at therning.org (Magnus Therning) Date: Sun, 5 Jan 2014 13:44:56 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140105122130.GA16826@machine> References: <20140105120045.GC1366@mteis.lan> <20140105122130.GA16826@machine> Message-ID: <20140105124456.GE1366@mteis.lan> On Sun, Jan 05, 2014 at 01:21:30PM +0100, Daniel Trstenjak wrote: > > Hi Magnus, > > On Sun, Jan 05, 2014 at 01:00:45PM +0100, Magnus Therning wrote: > > I get the following error when trying to build hsimports: > > > > [7 of 7] Compiling HsImport ( src/HsImport.hs, dist/build/HsImport.dyn_o ) > > /usr/bin/ld: dist/build/HsImport/Args.dyn_o: relocation R_X86_64_PC32 against undefined symbol `hsimportzm0zi2zi6zi3_Pathszuhsimport_version1_closure' can not be used when making a shared object; recompile with -fPIC > > /usr/bin/ld: final link failed: Bad value > > collect2: error: ld returned 1 exit status > > > > What could be causing this? > > Could you please test it with hsimport 0.2.6.4. Still same problem. /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus As far as the laws of mathematics refer to reality, they are not certain, and as far as they are certain, they do not refer to reality. -- Albert Einstein -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From daniel.trstenjak at gmail.com Sun Jan 5 13:14:59 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 5 Jan 2014 14:14:59 +0100 Subject: [Haskell-cafe] [ANN] vim-hsimport - automatically create Haskell import statements In-Reply-To: <20140105123445.GD1366@mteis.lan> References: <20140104144918.GA24476@machine> <20140105123445.GD1366@mteis.lan> Message-ID: <20140105131459.GA24611@machine> On Sun, Jan 05, 2014 at 01:34:45PM +0100, Magnus Therning wrote: > Any luck with getting your changes to hdevtools and vim-hdevtools into upstream? I've send pull requests for both and think that the addition is quite sensible and fitting into the scheme of hdevtools. So I'm hopeful for getting the additions merged. Greetings, Daniel From daniel.trstenjak at gmail.com Sun Jan 5 13:19:40 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 5 Jan 2014 14:19:40 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140105124456.GE1366@mteis.lan> References: <20140105120045.GC1366@mteis.lan> <20140105122130.GA16826@machine> <20140105124456.GE1366@mteis.lan> Message-ID: <20140105131940.GB24611@machine> On Sun, Jan 05, 2014 at 01:44:56PM +0100, Magnus Therning wrote: > Still same problem. Looking at the symbol name 'hsimportzm0zi2zi6zi3_Pathszuhsimport_version1_closure' I thought that I might just forgot to add the cabal created module 'Paths_hsimport' to the 'other-modules' list. But this doesn't seem to be the only issue. Greetings, Daniel From daniel.trstenjak at gmail.com Sun Jan 5 13:36:07 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 5 Jan 2014 14:36:07 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140105124456.GE1366@mteis.lan> References: <20140105120045.GC1366@mteis.lan> <20140105122130.GA16826@machine> <20140105124456.GE1366@mteis.lan> Message-ID: <20140105133607.GA25194@machine> It seems to be a problem with the building of 'HsImport/Args.hs', which is the only module using the cabal module 'Paths_hsimport'. The in this regard relevant parts of 'HsImport/Args.hs' seem to be: {-# LANGUAGE ... CPP #-} ... #ifdef CABAL import Data.Version (showVersion) import Paths_hsimport (version) #endif And in 'hsimport.cabal' there's: ... Executable hsimport ... cpp-options: -DCABAL Could you try modifying the hsimport executable section: ... Executable hsimport ... cpp-options: -DCABAL extensions: CPP Greetings, Daniel From magnus at therning.org Sun Jan 5 14:36:22 2014 From: magnus at therning.org (Magnus Therning) Date: Sun, 5 Jan 2014 15:36:22 +0100 Subject: [Haskell-cafe] Turning off warning in ghc-mod (in vim) Message-ID: <20140105143622.GA30382@mteis.lan> On the command line I can do the following: % ghc-mod check -g -isrc -g dist/build/autogen src/Main.hs | grep Top-level Binary file (standard input) matches % ghc-mod check -g -isrc -g dist/build/autogen -g -fno-warn-missing-signatures src/Main.hs | grep Top-level % That is, there is no output on the second call, just as expected. However, I can't work out out to turn off the warning in Vim. AFAIU the following should work: g:ghcmod_ghc_options = ['-isrc', '-idist/build/autogen', '-fno-warn-missing-signatures'] but it doesn't. I'm obviously missing something, but what? /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus Beauty is more important in computing than anywhere else in technology because software is so complicated. Beauty is the ultimate defence against complexity. -- David Gelernter -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From mail at eax.me Sun Jan 5 15:59:01 2014 From: mail at eax.me (Alexander Alexeev) Date: Sun, 5 Jan 2014 19:59:01 +0400 Subject: [Haskell-cafe] Cloud Haskell, spawn, link and spawnLink Message-ID: <20140105195901.77ea2f30@portege> Hi. Let's consider the following code: pid <- spawnLocal ... link pid Is it true, that a parent process will always be terminated when child process terminates, even if child process will be terminated between calls of spawnLocal and link? I wrote a test program and it seems to be so. But I wanted to be sure, that this is not some coincidence, but a real Cloud Haskell semantics. Is the same true for monitors? -- Best regards, Alexander Alexeev http://eax.me/ From andrew.gibiansky at gmail.com Sun Jan 5 17:46:07 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 12:46:07 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell Message-ID: Hello all, I need to do something strange and terrible in Haskell: intercept `stdin`. In other words, I need to detect (in another thread, probably?) when my running program is trying to read from `stdin`, and then feed it some data. I know I can use `hDupTo` and other similar things to replace the stdin handle with my own handle, and I know I could probably use `createPipe` or similar from the `unix` package in order to write things to these handles, but I have no idea how I might go about detecting that a handle is being read from. Any ideas? I've racked my brain and cannot come up with a way to do this. I am using the GHC API elsewhere if that leads to any sort of crazy hackery that might save the day. -- Andrew -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jan 5 19:12:46 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 5 Jan 2014 14:12:46 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: What's the motivation / use case? You could alternatively do the redirection from launching the program from shell if you can't midify the Haskell code yourself. On Sunday, January 5, 2014, Andrew Gibiansky wrote: > Hello all, > > I need to do something strange and terrible in Haskell: intercept `stdin`. > In other words, I need to detect (in another thread, probably?) when my > running program is trying to read from `stdin`, and then feed it some data. > > I know I can use `hDupTo` and other similar things to replace the stdin > handle with my own handle, and I know I could probably use `createPipe` or > similar from the `unix` package in order to write things to these handles, > but I have no idea how I might go about detecting that a handle is being > read from. > > Any ideas? I've racked my brain and cannot come up with a way to do this. > I am using the GHC API elsewhere if that leads to any sort of crazy hackery > that might save the day. > > -- Andrew > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Sun Jan 5 19:49:04 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 14:49:04 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: I cannot modify the Haskell code. I am working on IHaskell - it is effectively a Haskell interpreter. It reads some code from the user, which may contain something like `getLine`. However, the frontend to the interpreter is not a shell but is a GUI in the web browser (IPython!). In order to do input, the interpreter sends a message to the frontend via the network saying "give me input", the frontend reads some input, and then sends things back. In order to do this communication, I need to know when the getLine is called so that I know I need to send the message to the frontend. Ideas? The thing is, getLine needs to not actually read from any shell - it will read from a pipe I create, and I simply need to know when to put stuff into that pipe. -- Andrew -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jan 5 19:52:01 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 5 Jan 2014 14:52:01 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: Hrm. Have you considered using the ghc API? Ghci itself is written using it, and I imagine you could adapt that code for your purposes perhaps? On Sunday, January 5, 2014, Andrew Gibiansky wrote: > I cannot modify the Haskell code. > > I am working on IHaskell - it is effectively a Haskell interpreter. It > reads some code from the user, which may contain something like `getLine`. > However, the frontend to the interpreter is not a shell but is a GUI in the > web browser (IPython!). In order to do input, the interpreter sends a > message to the frontend via the network saying "give me input", the > frontend reads some input, and then sends things back. > > In order to do this communication, I need to know when the getLine is > called so that I know I need to send the message to the frontend. > > Ideas? The thing is, getLine needs to not actually read from any shell - > it will read from a pipe I create, and I simply need to know when to put > stuff into that pipe. > > -- Andrew > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Sun Jan 5 20:03:31 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 15:03:31 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: I am using the GHC API extensively. The entire application is built on the GHC API, with the occasional bit of code practically stolen from GHCi :) However, I don't know of a way to intercept stdin even if I am using the GHC API. Given a block of code, there is no sane static analysis than can be done to detect whether it reads from stdin, as far as I know. Is there any way to check whether a process is blocked when reading from a Handle or an Fd? Maybe there are some low-level hacks with unsafeCoerce or something that would let me pass a non-handle as a Handle, and do it that way? The only other option is just disabling all uses of stdin, or perhaps reimplementing myself the Prelude functions that use stdin. (But this would still break libraries that have already compiled in the Prelude versions.) On Sun, Jan 5, 2014 at 2:52 PM, Carter Schonwald wrote: > Hrm. Have you considered using the ghc API? Ghci itself is written using > it, and I imagine you could adapt that code for your purposes perhaps? > > > On Sunday, January 5, 2014, Andrew Gibiansky wrote: > >> I cannot modify the Haskell code. >> >> I am working on IHaskell - it is effectively a Haskell interpreter. It >> reads some code from the user, which may contain something like `getLine`. >> However, the frontend to the interpreter is not a shell but is a GUI in the >> web browser (IPython!). In order to do input, the interpreter sends a >> message to the frontend via the network saying "give me input", the >> frontend reads some input, and then sends things back. >> >> In order to do this communication, I need to know when the getLine is >> called so that I know I need to send the message to the frontend. >> >> Ideas? The thing is, getLine needs to not actually read from any shell - >> it will read from a pipe I create, and I simply need to know when to put >> stuff into that pipe. >> >> -- Andrew >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From creswick at gmail.com Sun Jan 5 20:09:32 2014 From: creswick at gmail.com (Rogan Creswick) Date: Sun, 5 Jan 2014 12:09:32 -0800 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: On Sun, Jan 5, 2014 at 12:03 PM, Andrew Gibiansky < andrew.gibiansky at gmail.com> wrote: > I am using the GHC API extensively. The entire application is built on the > GHC API, with the occasional bit of code practically stolen from GHCi :) > > However, I don't know of a way to intercept stdin even if I am using the > GHC API. Given a block of code, there is no sane static analysis than can > be done to detect whether it reads from stdin, as far as I know. > Could you rebind stdin to the ipython input channel every time a cell from the ipython interface is evaluated? (and then reset it, if necessary, after the cell finishes and in related exception handlers, of course). --Rogan > > Is there any way to check whether a process is blocked when reading from a > Handle or an Fd? Maybe there are some low-level hacks with unsafeCoerce or > something that would let me pass a non-handle as a Handle, and do it that > way? > > The only other option is just disabling all uses of stdin, or perhaps > reimplementing myself the Prelude functions that use stdin. (But this would > still break libraries that have already compiled in the Prelude versions.) > > > On Sun, Jan 5, 2014 at 2:52 PM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> Hrm. Have you considered using the ghc API? Ghci itself is written using >> it, and I imagine you could adapt that code for your purposes perhaps? >> >> >> On Sunday, January 5, 2014, Andrew Gibiansky wrote: >> >>> I cannot modify the Haskell code. >>> >>> I am working on IHaskell - it is effectively a Haskell interpreter. It >>> reads some code from the user, which may contain something like `getLine`. >>> However, the frontend to the interpreter is not a shell but is a GUI in the >>> web browser (IPython!). In order to do input, the interpreter sends a >>> message to the frontend via the network saying "give me input", the >>> frontend reads some input, and then sends things back. >>> >>> In order to do this communication, I need to know when the getLine is >>> called so that I know I need to send the message to the frontend. >>> >>> Ideas? The thing is, getLine needs to not actually read from any shell - >>> it will read from a pipe I create, and I simply need to know when to put >>> stuff into that pipe. >>> >>> -- Andrew >>> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Sun Jan 5 20:19:43 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 15:19:43 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: That's a good idea, but there's no IPython input channel. Instead, the backend (my interpreter) has to *request* input from the frontend, which then supplies this input. The input is entered via a web browser, so there's not even a handle or file descriptor to speak of. -------------- next part -------------- An HTML attachment was scrubbed... URL: From creswick at gmail.com Sun Jan 5 20:42:00 2014 From: creswick at gmail.com (Rogan Creswick) Date: Sun, 5 Jan 2014 12:42:00 -0800 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: On Sun, Jan 5, 2014 at 12:19 PM, Andrew Gibiansky < andrew.gibiansky at gmail.com> wrote: > That's a good idea, but there's no IPython input channel. Instead, the > backend (my interpreter) has to *request* input from the frontend, which > then supplies this input. The input is entered via a web browser, so > there's not even a handle or file descriptor to speak of. > Ugh, so you really do need to trigger an event when the code in the cell requests input. How does python handle this? Here's a horrible idea, but in the spirit of brainstorming... you could run the cell code in a separate app (fork off your interpreter), using ptrace (for linux; I'm not sure how to do this on other OSes) to detect system calls that involve stdin, and then supply input based on that. Aside from being tricky to do for all platforms, that's also going to have a horrible user experience for any code that loops over std in rapidly to get what would otherwise appear as a single input to the user, but I'm grasping at straws... --Rogan -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Sun Jan 5 20:49:10 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 15:49:10 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: Yeah, I am pretty sure I have no choice but trigger an event when the code requests input. I think Python is just much more flexible - you can probably just substitute something that isn't a file for sys.stdin, and when you call getline() on it it just does what it needs to. Flexible dynamic languages and all that. That's an interesting way to go about it. Will look into it, maybe. So far I've been browsing the source of GHC.IO.Handle in the hopes of finding a way to do this - maybe use the underlying IORefs in the Handle_ constructor for the Handle data type in order to unsafeCoerce something... I don't even know. I'm beginning to think this is just more or less impossible, though. On Sun, Jan 5, 2014 at 3:42 PM, Rogan Creswick wrote: > On Sun, Jan 5, 2014 at 12:19 PM, Andrew Gibiansky < > andrew.gibiansky at gmail.com> wrote: > >> That's a good idea, but there's no IPython input channel. Instead, the >> backend (my interpreter) has to *request* input from the frontend, which >> then supplies this input. The input is entered via a web browser, so >> there's not even a handle or file descriptor to speak of. >> > > Ugh, so you really do need to trigger an event when the code in the cell > requests input. How does python handle this? > > Here's a horrible idea, but in the spirit of brainstorming... you could > run the cell code in a separate app (fork off your interpreter), using > ptrace (for linux; I'm not sure how to do this on other OSes) to detect > system calls that involve stdin, and then supply input based on that. > > Aside from being tricky to do for all platforms, that's also going to have > a horrible user experience for any code that loops over std in rapidly to > get what would otherwise appear as a single input to the user, but I'm > grasping at straws... > > --Rogan > -------------- next part -------------- An HTML attachment was scrubbed... URL: From donn at avvanta.com Sun Jan 5 21:14:19 2014 From: donn at avvanta.com (Donn Cave) Date: Sun, 5 Jan 2014 13:14:19 -0800 (PST) Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: Message-ID: <20140105211419.0356A93C2E@mail.avvanta.com> I bet a quarter you can't do it. You'd need access to the process state - whether it's blocking for I/O and whether one of the units in the input set is 0 ("stdin".) Even if you could get that? you'd have to poll for it, which would be hideous. That's the UNIX I/O model. I've always found it a little annoying, because I could do this with the VMS `mailbox' device, analogous to UNIX pipes - in various ways a more sophisticated interprocess communication system than UNIX's. Donn From andrew.gibiansky at gmail.com Sun Jan 5 22:19:06 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 17:19:06 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: <20140105211419.0356A93C2E@mail.avvanta.com> References: <20140105211419.0356A93C2E@mail.avvanta.com> Message-ID: I think we found a way! (With a *ton* of help from @aavogt - might actually be more correct to say he found the way :) ) You can use `hDupTo` to change what a Handle points to. You can use `mkFileHandle` in GHC.IO.Internal to create a new file handle. You can implement your own IODevice and BufferedIO datatype to give to `mkFileHandle` instead of using `Fd`. Then, when your "device" is being read from, you just implement `newBuffer` and `readBuffer` to do whatever you need them to. Results pending. -- Andrew On Sun, Jan 5, 2014 at 4:14 PM, Donn Cave wrote: > I bet a quarter you can't do it. You'd need access to the process state - > whether it's blocking for I/O and whether one of the units in the input set > is 0 ("stdin".) Even if you could get that? you'd have to poll for it, > which > would be hideous. > > That's the UNIX I/O model. I've always found it a little annoying, because > I could do this with the VMS `mailbox' device, analogous to UNIX pipes - > in various ways a more sophisticated interprocess communication system than > UNIX's. > > Donn > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Sun Jan 5 23:14:25 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 18:14:25 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: <20140105211419.0356A93C2E@mail.avvanta.com> Message-ID: Looks like the excitement was a bit premature. The types work, and in Haskell that often means the program works... but looks like hDupTo relies on the `dup2` of the IODevice class, and attempts to cast one IODevice to another IODevice. Since I'm trying to replace stdin (with IODevice type Fd) with my own IODevice, the cast fails and raises an exception. Practically ClassCastException.... yeesh. On Sun, Jan 5, 2014 at 5:19 PM, Andrew Gibiansky wrote: > I think we found a way! (With a *ton* of help from @aavogt - might > actually be more correct to say he found the way :) ) > > You can use `hDupTo` to change what a Handle points to. You can use > `mkFileHandle` in GHC.IO.Internal to create a new file handle. You can > implement your own IODevice and BufferedIO datatype to give to > `mkFileHandle` instead of using `Fd`. Then, when your "device" is being > read from, you just implement `newBuffer` and `readBuffer` to do whatever > you need them to. > > Results pending. > > -- Andrew > > > On Sun, Jan 5, 2014 at 4:14 PM, Donn Cave wrote: > >> I bet a quarter you can't do it. You'd need access to the process state - >> whether it's blocking for I/O and whether one of the units in the input >> set >> is 0 ("stdin".) Even if you could get that? you'd have to poll for it, >> which >> would be hideous. >> >> That's the UNIX I/O model. I've always found it a little annoying, >> because >> I could do this with the VMS `mailbox' device, analogous to UNIX pipes - >> in various ways a more sophisticated interprocess communication system >> than >> UNIX's. >> >> Donn >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Mon Jan 6 00:11:37 2014 From: jwlato at gmail.com (John Lato) Date: Sun, 5 Jan 2014 16:11:37 -0800 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: <20140105211419.0356A93C2E@mail.avvanta.com> Message-ID: Here's a stupid idea: A Handle contains an MVar Handle__, and when a thread calls hGetLine stdin, it will take that MVar, attempt to read from the buffered device, and then block until there's data available to be read from the device. You could check if the MVar is empty, and if so, assume that something is trying to read from stdin and write your input into the device. Horrible, unsound hack, I'm sure, but it's all I've got... On Sun, Jan 5, 2014 at 3:14 PM, Andrew Gibiansky wrote: > Looks like the excitement was a bit premature. The types work, and in > Haskell that often means the program works... but looks like hDupTo relies > on the `dup2` of the IODevice class, and attempts to cast one IODevice to > another IODevice. Since I'm trying to replace stdin (with IODevice type Fd) > with my own IODevice, the cast fails and raises an exception. Practically > ClassCastException.... yeesh. > > > On Sun, Jan 5, 2014 at 5:19 PM, Andrew Gibiansky < > andrew.gibiansky at gmail.com> wrote: > >> I think we found a way! (With a *ton* of help from @aavogt - might >> actually be more correct to say he found the way :) ) >> >> You can use `hDupTo` to change what a Handle points to. You can use >> `mkFileHandle` in GHC.IO.Internal to create a new file handle. You can >> implement your own IODevice and BufferedIO datatype to give to >> `mkFileHandle` instead of using `Fd`. Then, when your "device" is being >> read from, you just implement `newBuffer` and `readBuffer` to do whatever >> you need them to. >> >> Results pending. >> >> -- Andrew >> >> >> On Sun, Jan 5, 2014 at 4:14 PM, Donn Cave wrote: >> >>> I bet a quarter you can't do it. You'd need access to the process state >>> - >>> whether it's blocking for I/O and whether one of the units in the input >>> set >>> is 0 ("stdin".) Even if you could get that? you'd have to poll for it, >>> which >>> would be hideous. >>> >>> That's the UNIX I/O model. I've always found it a little annoying, >>> because >>> I could do this with the VMS `mailbox' device, analogous to UNIX pipes - >>> in various ways a more sophisticated interprocess communication system >>> than >>> UNIX's. >>> >>> Donn >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Mon Jan 6 00:45:32 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Sun, 5 Jan 2014 19:45:32 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: <20140105211419.0356A93C2E@mail.avvanta.com> Message-ID: You are a saviour! We'd actually already tried going down this path with takeMVars and putMVars, but somehow it didn't quite work. Let's see if this works in practice in IHaskell! Working program below: import Control.Concurrent import Control.Monad import GHC.IO.Handle import GHC.IO.Handle.Types import System.IO import System.Posix.IO main = do -- Create a pipe using System.Posix and turn it into handles. (readEnd, writeEnd) <- createPipe newStdin <- fdToHandle readEnd stdinInput <- fdToHandle writeEnd -- Store old stdin and swap in new stdin. oldStdin <- hDuplicate stdin hDuplicateTo newStdin stdin -- In a separate thread, wait for the read. forkIO $ forever $ do let FileHandle _ mvar = stdin threadDelay $ 200 * 1000 empty <- isEmptyMVar mvar when empty $ do putStrLn "Empty!" hPutStrLn stdinInput "foo" hFlush stdinInput putStrLn "Waiting." threadDelay $ 3 * 1000 * 1000 putStrLn "Reading." getChar >>= print On Sun, Jan 5, 2014 at 7:11 PM, John Lato wrote: > Here's a stupid idea: > > A Handle contains an MVar Handle__, and when a thread calls hGetLine > stdin, it will take that MVar, attempt to read from the buffered device, > and then block until there's data available to be read from the device. > You could check if the MVar is empty, and if so, assume that something is > trying to read from stdin and write your input into the device. > > Horrible, unsound hack, I'm sure, but it's all I've got... > > > On Sun, Jan 5, 2014 at 3:14 PM, Andrew Gibiansky < > andrew.gibiansky at gmail.com> wrote: > >> Looks like the excitement was a bit premature. The types work, and in >> Haskell that often means the program works... but looks like hDupTo relies >> on the `dup2` of the IODevice class, and attempts to cast one IODevice to >> another IODevice. Since I'm trying to replace stdin (with IODevice type Fd) >> with my own IODevice, the cast fails and raises an exception. Practically >> ClassCastException.... yeesh. >> >> >> On Sun, Jan 5, 2014 at 5:19 PM, Andrew Gibiansky < >> andrew.gibiansky at gmail.com> wrote: >> >>> I think we found a way! (With a *ton* of help from @aavogt - might >>> actually be more correct to say he found the way :) ) >>> >>> You can use `hDupTo` to change what a Handle points to. You can use >>> `mkFileHandle` in GHC.IO.Internal to create a new file handle. You can >>> implement your own IODevice and BufferedIO datatype to give to >>> `mkFileHandle` instead of using `Fd`. Then, when your "device" is being >>> read from, you just implement `newBuffer` and `readBuffer` to do whatever >>> you need them to. >>> >>> Results pending. >>> >>> -- Andrew >>> >>> >>> On Sun, Jan 5, 2014 at 4:14 PM, Donn Cave wrote: >>> >>>> I bet a quarter you can't do it. You'd need access to the process >>>> state - >>>> whether it's blocking for I/O and whether one of the units in the input >>>> set >>>> is 0 ("stdin".) Even if you could get that? you'd have to poll for it, >>>> which >>>> would be hideous. >>>> >>>> That's the UNIX I/O model. I've always found it a little annoying, >>>> because >>>> I could do this with the VMS `mailbox' device, analogous to UNIX pipes - >>>> in various ways a more sophisticated interprocess communication system >>>> than >>>> UNIX's. >>>> >>>> Donn >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>> >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Mon Jan 6 01:20:19 2014 From: vogt.adam at gmail.com (adam vogt) Date: Sun, 5 Jan 2014 20:20:19 -0500 Subject: [Haskell-cafe] Intercept stdin in Haskell In-Reply-To: References: <20140105211419.0356A93C2E@mail.avvanta.com> Message-ID: Hello, That last version was still off. I think we are going with John's idea, which is slightly more concretely in: http://lpaste.net/98017 I expect there are still issues concerning how much input to request, so that getLine, getChar and getContents all behave as they do in the console. -- Adam On Sun, Jan 5, 2014 at 7:45 PM, Andrew Gibiansky wrote: > You are a saviour! > > We'd actually already tried going down this path with takeMVars and > putMVars, but somehow it didn't quite work. Let's see if this works in > practice in IHaskell! > > Working program below: > > import Control.Concurrent > import Control.Monad > import GHC.IO.Handle > import GHC.IO.Handle.Types > import System.IO > import System.Posix.IO > > main = do > -- Create a pipe using System.Posix and turn it into handles. > (readEnd, writeEnd) <- createPipe > newStdin <- fdToHandle readEnd > stdinInput <- fdToHandle writeEnd > > -- Store old stdin and swap in new stdin. > oldStdin <- hDuplicate stdin > hDuplicateTo newStdin stdin > > -- In a separate thread, wait for the read. > forkIO $ forever $ do > let FileHandle _ mvar = stdin > threadDelay $ 200 * 1000 > empty <- isEmptyMVar mvar > when empty $ do > putStrLn "Empty!" > hPutStrLn stdinInput "foo" > hFlush stdinInput > > > > putStrLn "Waiting." > threadDelay $ 3 * 1000 * 1000 > putStrLn "Reading." > getChar >>= print > > > > On Sun, Jan 5, 2014 at 7:11 PM, John Lato wrote: >> >> Here's a stupid idea: >> >> A Handle contains an MVar Handle__, and when a thread calls hGetLine >> stdin, it will take that MVar, attempt to read from the buffered device, and >> then block until there's data available to be read from the device. You >> could check if the MVar is empty, and if so, assume that something is trying >> to read from stdin and write your input into the device. >> >> Horrible, unsound hack, I'm sure, but it's all I've got... >> >> >> On Sun, Jan 5, 2014 at 3:14 PM, Andrew Gibiansky >> wrote: >>> >>> Looks like the excitement was a bit premature. The types work, and in >>> Haskell that often means the program works... but looks like hDupTo relies >>> on the `dup2` of the IODevice class, and attempts to cast one IODevice to >>> another IODevice. Since I'm trying to replace stdin (with IODevice type Fd) >>> with my own IODevice, the cast fails and raises an exception. Practically >>> ClassCastException.... yeesh. >>> >>> >>> On Sun, Jan 5, 2014 at 5:19 PM, Andrew Gibiansky >>> wrote: >>>> >>>> I think we found a way! (With a *ton* of help from @aavogt - might >>>> actually be more correct to say he found the way :) ) >>>> >>>> You can use `hDupTo` to change what a Handle points to. You can use >>>> `mkFileHandle` in GHC.IO.Internal to create a new file handle. You can >>>> implement your own IODevice and BufferedIO datatype to give to >>>> `mkFileHandle` instead of using `Fd`. Then, when your "device" is being read >>>> from, you just implement `newBuffer` and `readBuffer` to do whatever you >>>> need them to. >>>> >>>> Results pending. >>>> >>>> -- Andrew >>>> >>>> >>>> On Sun, Jan 5, 2014 at 4:14 PM, Donn Cave wrote: >>>>> >>>>> I bet a quarter you can't do it. You'd need access to the process >>>>> state - >>>>> whether it's blocking for I/O and whether one of the units in the input >>>>> set >>>>> is 0 ("stdin".) Even if you could get that? you'd have to poll for it, >>>>> which >>>>> would be hideous. >>>>> >>>>> That's the UNIX I/O model. I've always found it a little annoying, >>>>> because >>>>> I could do this with the VMS `mailbox' device, analogous to UNIX pipes >>>>> - >>>>> in various ways a more sophisticated interprocess communication system >>>>> than >>>>> UNIX's. >>>>> >>>>> Donn >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> Haskell-Cafe at haskell.org >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>>> >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From fuuzetsu at fuuzetsu.co.uk Mon Jan 6 01:37:03 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 06 Jan 2014 01:37:03 +0000 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! Message-ID: <52CA08BF.90301@fuuzetsu.co.uk> Greetings caf?, As some of you might have noticed recently, there seems to be quite a few packages with broken documentation on Hackage recently. If you are an owner of such package, please consider fixing it. There's a thread on cabal-devel about this if you're interested in details. Here's a list of packages uploaded since beginning of 2013 for which the documentation was broken as of yesterday: http://fuuzetsu.co.uk/misc/sorted.txt If your package is on that list, your documentation is broken. Only the most recent versions of packages were being considered. I outline how to fix your documentation (in most cases this means uploading it by hand) in a blog post I just published. Please refer to: http://fuuzetsu.co.uk/blog/posts/2014-01-06-Fix-your-Hackage-documentation.html The post contains a link to as script which naively attempts to automate the burden of uploading the docs manually. If your package can't be built simply with ?cabal configure && cabal build && cabal haddock --hyperlink-source?, you'll have to adapt it to your situation. Thanks. I hope to see fewer packages with broken documentation in the future. -- Mateusz K. From cgaebel at uwaterloo.ca Mon Jan 6 01:47:27 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Sun, 5 Jan 2014 20:47:27 -0500 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CA08BF.90301@fuuzetsu.co.uk> References: <52CA08BF.90301@fuuzetsu.co.uk> Message-ID: Is there any way you could tag that list with the author so that we can Ctrl+f ourselves? On Sun, Jan 5, 2014 at 8:37 PM, Mateusz Kowalczyk wrote: > Greetings caf?, > > As some of you might have noticed recently, there seems to be quite a > few packages with broken documentation on Hackage recently. If you are > an owner of such package, please consider fixing it. There's a thread on > cabal-devel about this if you're interested in details. > > Here's a list of packages uploaded since beginning of 2013 for which the > documentation was broken as of yesterday: > http://fuuzetsu.co.uk/misc/sorted.txt > > If your package is on that list, your documentation is broken. Only the > most recent versions of packages were being considered. > > I outline how to fix your documentation (in most cases this means > uploading it by hand) in a blog post I just published. Please refer to: > > http://fuuzetsu.co.uk/blog/posts/2014-01-06-Fix-your-Hackage-documentation.html > > The post contains a link to as script which naively attempts to automate > the burden of uploading the docs manually. If your package can't be > built simply with ?cabal configure && cabal build && cabal haddock > --hyperlink-source?, you'll have to adapt it to your situation. > > Thanks. I hope to see fewer packages with broken documentation in the > future. > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Mon Jan 6 01:50:35 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 06 Jan 2014 01:50:35 +0000 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> Message-ID: <52CA0BEB.7040803@fuuzetsu.co.uk> On 06/01/14 01:47, Clark Gaebel wrote: > Is there any way you could tag that list with the author so that we can > Ctrl+f ourselves? > > Not without fetching the data again. I can do it if you find it absolutely necessary but you'd have to wait. Do you want it? This is the third time in ~24 hours where I wish I simply saved the pages? -- Mateusz K. From cgaebel at uwaterloo.ca Mon Jan 6 02:01:51 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Sun, 5 Jan 2014 21:01:51 -0500 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CA0BEB.7040803@fuuzetsu.co.uk> References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> Message-ID: Haha it's alright. I'll survive. I feel sorry for ekemett, bos, and friends, though. On Sun, Jan 5, 2014 at 8:50 PM, Mateusz Kowalczyk wrote: > On 06/01/14 01:47, Clark Gaebel wrote: > > Is there any way you could tag that list with the author so that we can > > Ctrl+f ourselves? > > > > > > Not without fetching the data again. I can do it if you find it > absolutely necessary but you'd have to wait. Do you want it? > > This is the third time in ~24 hours where I wish I simply saved the pages? > > > -- > Mateusz K. > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From creswick at gmail.com Mon Jan 6 03:54:42 2014 From: creswick at gmail.com (Rogan Creswick) Date: Sun, 5 Jan 2014 19:54:42 -0800 Subject: [Haskell-cafe] hackage build failure (?) - but no log Message-ID: Mateusz Kowalczyk's recent message about fixing hackage documentation made me realize that one of my packages (chatter) has no build log, and indeed, the documentation was not showing up on hackage. Is there any way to figure out what is causing the failure? Chatter has no non-Haskell dependencies, and it builds just fine in a sandbox on the major three architectures (including building documentation on at least two of them - I haven't tested haddock on Windows). Manually posting the documentation is more than a little inconvenient at the moment, and given the nature of the library, I'm pretty surprised this is an issue. (I did post the docs for chatter-0.0.0.3 manually, if you're wondering why they appear despite my complaints...) Does anyone have suggestions? Thanks! Rogan -------------- next part -------------- An HTML attachment was scrubbed... URL: From k.bleijenberg at lijbrandt.nl Mon Jan 6 08:13:25 2014 From: k.bleijenberg at lijbrandt.nl (Kees Bleijenberg) Date: Mon, 6 Jan 2014 09:13:25 +0100 Subject: [Haskell-cafe] preprocessor, how to? Message-ID: <009901cf0ab7$2c860fb0$85922f10$@bleijenberg@lijbrandt.nl> In a program I use a lot of hamlet files. All these hamlet files are in a submap of the source map. In code: allHtml = Mconcat [ $(hamletFile "hamlet\\belastingen.hamlet") renderUrl ,$(hamletFile "hamlet\\winddruk.hamlet") renderUrl .. ,$(hamletFile "hamlet\\berekeningDruk.hamlet") renderUrl ,$(hamletFile "hamlet\\drukNaarBuigTrek.hamlet") renderUrl] This is a Windows program. For another project I want to use this piece of code on Linux. The code should now be: .. $(hamletFile "hamlet/winddruk.hamlet") renderUrl I can't use pathSeparator here, because this is all happening at compile time. So I think I need a preprocessor. I would like to have a kind of hamletDir macro and change the code to something like: #ifdef Win32 hamletDir = "hamlet\\" #else hamletDir = "hamlet/" #endif ... $(hamletFile "{hamletDir}winddruk.hamlet") renderUrl Is it possible in Haskell and how do I it? All examples of preprocessing in Haskell I found are something like this: #ifdef xxx aaaa #else Bbbbb #endif I could use that. But a user defined macro is less code. Kees From magnus at therning.org Mon Jan 6 08:15:57 2014 From: magnus at therning.org (Magnus Therning) Date: Mon, 6 Jan 2014 09:15:57 +0100 Subject: [Haskell-cafe] Turning off warning in ghc-mod (in vim) In-Reply-To: <20140105143622.GA30382@mteis.lan> References: <20140105143622.GA30382@mteis.lan> Message-ID: <20140106081557.GA1566@mteis.lan> On Sun, Jan 05, 2014 at 03:36:22PM +0100, Magnus Therning wrote: > On the command line I can do the following: > > % ghc-mod check -g -isrc -g dist/build/autogen src/Main.hs | grep Top-level > Binary file (standard input) matches > % ghc-mod check -g -isrc -g dist/build/autogen -g -fno-warn-missing-signatures src/Main.hs | grep Top-level > % > > That is, there is no output on the second call, just as expected. > However, I can't work out out to turn off the warning in Vim. AFAIU > the following should work: > > g:ghcmod_ghc_options = ['-isrc', '-idist/build/autogen', '-fno-warn-missing-signatures'] > > but it doesn't. I'm obviously missing something, but what? This was due to my confusion. Once I realised that the markings in Vim wasn't due to the ghc-mod.vim, but due to syntastic it became a lot easier to fix my configuration. In short g:ghcmod_ghc_options = ['-isrc', '-idist/build/autogen', '-fno-warn-missing-signatures'] works fine for controlling the GhcMod* commands. To configure the arguments syntastic pass to ghc-mod use this: g:syntastic_haskell_ghc_mod_args = '-g -fno-warn-missing-signatures' /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus You do not examine legislation in the light of the benefits it will convey if properly administered, but in the light of the wrongs it would do and the harms it would cause if improperly administered. -- Lyndon Johnson -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From chrisyco+haskell-cafe at gmail.com Mon Jan 6 08:25:25 2014 From: chrisyco+haskell-cafe at gmail.com (Chris Wong) Date: Mon, 6 Jan 2014 21:25:25 +1300 Subject: [Haskell-cafe] preprocessor, how to? In-Reply-To: <52ca65c3.08d80e0a.3fb8.fffff955SMTPIN_ADDED_BROKEN@mx.google.com> References: <52ca65c3.08d80e0a.3fb8.fffff955SMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: You can use forward slashes in Windows as well. On Jan 6, 2014 9:13 PM, "Kees Bleijenberg" wrote: > In a program I use a lot of hamlet files. All these hamlet files are in a > submap of the source map. In code: > allHtml = Mconcat [ $(hamletFile "hamlet\\belastingen.hamlet") renderUrl > ,$(hamletFile "hamlet\\winddruk.hamlet") renderUrl > .. > ,$(hamletFile "hamlet\\berekeningDruk.hamlet") > renderUrl > ,$(hamletFile "hamlet\\drukNaarBuigTrek.hamlet") > renderUrl] > This is a Windows program. > > For another project I want to use this piece of code on Linux. The code > should now be: > .. $(hamletFile "hamlet/winddruk.hamlet") renderUrl > > I can't use pathSeparator here, because this is all happening at compile > time. So I think I need a preprocessor. > I would like to have a kind of hamletDir macro and change the code to > something like: > > #ifdef Win32 > hamletDir = "hamlet\\" > #else > hamletDir = "hamlet/" > #endif > ... > $(hamletFile "{hamletDir}winddruk.hamlet") renderUrl > Is it possible in Haskell and how do I it? > > All examples of preprocessing in Haskell I found are something like this: > #ifdef xxx > aaaa > #else > Bbbbb > #endif > I could use that. But a user defined macro is less code. > > Kees > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From magnus at therning.org Mon Jan 6 10:19:37 2014 From: magnus at therning.org (Magnus Therning) Date: Mon, 6 Jan 2014 11:19:37 +0100 Subject: [Haskell-cafe] preprocessor, how to? In-Reply-To: References: <52ca65c3.08d80e0a.3fb8.fffff955SMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: <20140106101937.GA7391@mteis.lan> On Mon, Jan 06, 2014 at 09:25:25PM +1300, Chris Wong wrote: > You can use forward slashes in Windows as well. It's worth clarifying this somewhat I think. I found this at http://is.gd/a5gCuk: Every version of Windows has accepted "/" as a path separator. So has every version of MS-DOS beginning with DOS 2.0 (the first version that had subdirectories). It's only been in command lines that "/" was not allowed, because it had already been used as a switch delimiter in MS-DOS 1.0. So as long as you keep away from stuff like System.Process.system you should be fine with ordinary slashes. /M > On Jan 6, 2014 9:13 PM, "Kees Bleijenberg" > wrote: > > > In a program I use a lot of hamlet files. All these hamlet files are in a > > submap of the source map. In code: > > allHtml = Mconcat [ $(hamletFile "hamlet\\belastingen.hamlet") renderUrl > > ,$(hamletFile "hamlet\\winddruk.hamlet") renderUrl > > .. > > ,$(hamletFile "hamlet\\berekeningDruk.hamlet") > > renderUrl > > ,$(hamletFile "hamlet\\drukNaarBuigTrek.hamlet") > > renderUrl] > > This is a Windows program. > > > > For another project I want to use this piece of code on Linux. The code > > should now be: > > .. $(hamletFile "hamlet/winddruk.hamlet") renderUrl > > > > I can't use pathSeparator here, because this is all happening at compile > > time. So I think I need a preprocessor. > > I would like to have a kind of hamletDir macro and change the code to > > something like: > > > > #ifdef Win32 > > hamletDir = "hamlet\\" > > #else > > hamletDir = "hamlet/" > > #endif > > ... > > $(hamletFile "{hamletDir}winddruk.hamlet") renderUrl > > Is it possible in Haskell and how do I it? > > > > All examples of preprocessing in Haskell I found are something like this: > > #ifdef xxx > > aaaa > > #else > > Bbbbb > > #endif > > I could use that. But a user defined macro is less code. > > > > Kees > > > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus Unreadable code, Why would anyone use it? Learn a better way. -- Geoff Kuenning's contribution to the 2004 Perl Haiku Contest, Haikus about Perl - 'Dishonerable Mention' winner -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From mail at eax.me Mon Jan 6 13:36:14 2014 From: mail at eax.me (Alexander Alexeev) Date: Mon, 6 Jan 2014 17:36:14 +0400 Subject: [Haskell-cafe] Cloud Haskell, spawn, link and spawnLink In-Reply-To: <20140105195901.77ea2f30@portege> References: <20140105195901.77ea2f30@portege> Message-ID: <20140106173614.19260160@portege> If someone is interested, I got an answer on this question in Cloud Haskell mailing list: https://groups.google.com/forum/#!topic/parallel-haskell/x280cGqJWGo > Hi. > > Let's consider the following code: > > pid <- spawnLocal ... > link pid > > Is it true, that a parent process will always be terminated when > child process terminates, even if child process will be terminated > between calls of spawnLocal and link? I wrote a test program and it > seems to be so. But I wanted to be sure, that this is not some > coincidence, but a real Cloud Haskell semantics. > > Is the same true for monitors? > > -- > Best regards, > Alexander Alexeev > http://eax.me/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Best regards, Alexander Alexeev http://eax.me/ From mail at nh2.me Mon Jan 6 14:46:03 2014 From: mail at nh2.me (=?ISO-8859-1?Q?Niklas_Hamb=FCchen?=) Date: Mon, 06 Jan 2014 15:46:03 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> Message-ID: <52CAC1AB.5080100@nh2.me> Here is the package <-> maintainer list. Hackage should have a feature for this. (Did this with the Hackage API: for p in `cat packages`; do echo -n "$p "; curl http://hackage.haskell.org/package/$p/uploader; echo; done) bindings-cctools BadiAbdulWahid bitcoin-rpc JanVornberger cctools-workqueue BadiAbdulWahid commsec-keyexchange ThomasDuBuisson CurryDB HideyukiTanaka egison SatoshiEgi FreeTypeGL EyalLotem hbro-contrib koral hoodle-core IanWooKim hoodle IanWooKim hOpenPGP ClintAdams hs-excelx MarkBaran hsimport DanielTrstenjak MagicHaskeller SusumuKatayama module-management DavidFox OpenVG StephenTetley OpenVGRaw StephenTetley python-pickle VoMinhThu tkyprof MitsutoshiAoe webkitgtk3 HamishMackenzie Yablog HiromiIshii yesod-markdown PatrickBrisbin free-theorems-counterexamples DanielSeidel gemstone CorbinSimpson haskell-openflow BrianBrooks hbro koral nettle-frp AndreasVoellmy satchmo JohannesWaldmann bogre-banana DavidEichmann FailureT MatthewFarkasDyck HGamer3D PeterAlthainz hois DavidEichmann l-bfgs-b GardSpreemann libsystemd-daemon CedricStaub lojbanXiragan YoshikuniJujo marxup JeanPhilippeBernardy PandocAgda PeterDivianszky Ref CarterSchonwald biophd DanFornika chuchu FelipeLessa clckwrks-theme-geo-bootstrap JeremyShaw halipeto PeterSimons hsc3-graphs RohanDrape ipopt-hs AdamVogt linear-algebra-cblas CarterSchonwald miniball GardSpreemann mount NicolaSquartini musicbrainz-email OliverCharles Obsidian JoelSvensson ois-input-manager GregHorn Range ThomasEding TrieMap LouisWasserman unpack-funcs LouisWasserman Win32-junction-point MichaelSteele zmcat LucasDiCioccio datalog TristanRavitch decepticons JoeQuinn hunit-rematch TomCrayford iptables-helpers EvgenyTarasov linux-blkid NicolaSquartini live-sequencer HenningThielemann llvm-base CarterSchonwald llvm-extra HenningThielemann llvm CarterSchonwald llvm-tf HenningThielemann noise TomBrow quickcheck-rematch TomCrayford simple-firewire VilleTirronen synthesizer-core HenningThielemann synthesizer-llvm HenningThielemann unordered-containers-rematch TomCrayford aeson-schema TimBaumann atom-msp430 DanielBuckmaster binding-wx GideonSireling embeddock-example TakayukiMuranushi equational-reasoning HiromiIshii graph-rewriting-gl JanRochel kontrakcja-templates MariuszRak padKONTROL FumiakiKinoshita posix-pty MerijnVerstraaten saltine JosephAbrahamson watcher NateSoares Win32-services-wrapper GaneshSittampalam z3 IagoAbal atomic-primops RyanNewton bindings-libzip SergeyAstanin nitro ErinDahlgren qhull-simple GardSpreemann terrahs SergioCosta yesod-vend KrzysztofSkrzetnicki Capabilities BaldurBlondal cloudfront-signer ChrisDornan data-store PetrPilar hemokit NiklasHambuechen heukarya HeChienTsai hidapi NiklasHambuechen Hs2lib TamarChristina io-manager MihaiMaruseac Konf GoktugKayaalp LibZip SergeyAstanin NXTDSL AlexanderThiemann parsek JeanPhilippeBernardy sifflet-lib GregoryWeber Win32-services MichaelSteele xkbcommon AukeBooij hat OlafChitil henet JohnEricson kqueue ErikHesselink memexml FlorianEggenhofer ncurses JohnMillikin parcom-lib TobiasDammers proj4-hs-bindings PavelPenev geni-gui EricKow goa ChrisDone hist-pl JakubWaszczuk hoopl HerbertValerioRiedel karakuri FumiakiKinoshita lvish RyanNewton mysql BryanOSullivan nanomsg DavidHimmelstrup sarasvati outoftune snaplet-rest TimothyJones accelerate-cuda TrevorMcDonell accelerate-fft TrevorMcDonell cci FacundoDominguez chatter RoganCreswick concraft JakubWaszczuk concraft-pl JakubWaszczuk crf-chain2-tiers JakubWaszczuk cuda TrevorMcDonell data-variant TobiasDammers DirectSound BalazsKomuves flowdock-api gabemc ftree ConalElliott gitlib-s3 JohnWiegley glib HamishMackenzie gloss-accelerate TrevorMcDonell gloss-raster-accelerate TrevorMcDonell GraphHammer-examples AlexanderVershilov gtksourceview3 HamishMackenzie HaLeX joaoSaraiva hmatrix AlbertoRuiz hpaco-lib TobiasDammers imagemagick AlexanderVershilov lambda-devs alios missing-py2 domdere nerf JakubWaszczuk parsestar MichalGajda persistent-redis PavelRyzhov reorderable AlexCole sgd JakubWaszczuk sorted JosephAbrahamson webkitgtk3-javascriptcore HamishMackenzie Win32-extras KidoTakahiro wraxml HenningThielemann ajhc KiwamuOkabe ALUT SvenPanne cufft RobEverest dirfiles HugoGomes DnaProteinAlignment ChristianHoener Dust-crypto BrandonWiley Dust BrandonWiley Dust-tools BrandonWiley easyrender PeterSelinger fay-dom AdamBergmark fay-jquery AdamBergmark fay AdamBergmark FModExRaw DimitriSabadie FormalGrammars ChristianHoener fpco-api ChrisDone ghcjs-dom HamishMackenzie gitlib-libgit2 JohnWiegley GrammarProducts ChristianHoener gstreamer HamishMackenzie gtk3-mac-integration HamishMackenzie gtk-mac-integration HamishMackenzie hfsevents LuiteStegeman hledger-lib SimonMichael hledger SimonMichael hledger-web SimonMichael holy-project yogsototh hopfield NiklasHambuechen hPushover WJWH hzk DiegoSouza ihaskell gibiansky jsc HamishMackenzie language-puppet SimonMarechal newsynth PeterSelinger nm ChrisDone pretty-show IavorDiatchki quickcheck-property-comb jfeltz resource-effect ClarkGaebel RNAdesign ChristianHoener scotty-fay hdgarrood SDL2-ttf OmerAgacan SFML-control AlfredoDiNapoli SFML AlfredoDiNapoli singletons RichardEisenberg snaplet-mysql-simple ibotty tempodb ParnellSpringmeyer UISF dwincort units RichardEisenberg valid-names JoelTaylor ViennaRNA-bindings ChristianHoener wai-handler-webkit MichaelSnoyman yesod-pure MichaelSnoyman yesod-static MichaelSnoyman yi-monokai MateuszKowalczyk zeromq3-haskell ToralfWittner zeromq4-haskell ToralfWittner From svenpanne at gmail.com Mon Jan 6 15:35:53 2014 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 6 Jan 2014 16:35:53 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CAC1AB.5080100@nh2.me> References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> Message-ID: To be honest, I actively encourage people to *not* fix their package documentation manually. This is tedious, error-prone, and I bet there will be tons of packages then where the actual code and documentation will disagree (worse than no documentation at all), we're humans after all. Fixing Hackage is the way to go, not some guaranteed-to-fail crowd-sourcing... :-/ From rda at lemma-one.com Mon Jan 6 15:47:10 2014 From: rda at lemma-one.com (Rob Arthan) Date: Mon, 6 Jan 2014 15:47:10 +0000 Subject: [Haskell-cafe] Infelicity in StdGen? In-Reply-To: <52C74049.20709@vex.net> References: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> <52C74049.20709@vex.net> Message-ID: <6F9A17A2-73C2-47ED-9623-A69273910358@lemma-one.com> On 3 Jan 2014, at 22:57, Albert Y. C. Lai wrote: > On 14-01-03 11:28 AM, Rob Arthan wrote: >> roll n = take n . randomRs ('1', '6') . mkStdGen $ n >> >> However, this produces a string beginning with a '6' for 0 <= n <= 53667. > > It seems to me such small numbers do not have enough entropy to be worthy seeds to begin with. Say, in the 64-bit binary form of 53667, how many consecutive 0's are there? I don't think the entropy of the number considered as a string of bits is relevant. The later part of my post strongly suggests that there is a pattern. And in fact this pattern turns out to repeat indefinitely. The following calculates about 10^7+1 values starting with a large integer that I obtained from /dev/urandom: map (\l -> (head l, length l)) . group . map (fst . randomR (1, 6) . mkStdGen) $ [0x383b0d54718ac75f..0x383b0d54718ac75f+1000000] The result is: [(2,36076),(1,53669),(6,53668),(5,53668),(4,53669),(3,53668),(2,53668),(1,53669),(6,53668),(5,53668),(4,53668),(3,53669),(2,53668),(1,53668),(6,53669),(5,53668),(4,53668),(3,53669),(2,51563)] So we keep on getting long runs of seed values that produce the same value on the first call of randomR even when we start with a seed that will have around 60 bits of entropy (if /dev/urandom on my heavily used iMac is doing its job). Regards, Rob. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Mon Jan 6 15:47:57 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 6 Jan 2014 16:47:57 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> Message-ID: In some cases it actually makes sense. For example, my kqueue package is in the list above. It is a binding to a MacOS/BSD C library, and the hackage build bot runs on linux. So I should actually upload the documentation... Erik On Mon, Jan 6, 2014 at 4:35 PM, Sven Panne wrote: > To be honest, I actively encourage people to *not* fix their package > documentation manually. This is tedious, error-prone, and I bet there > will be tons of packages then where the actual code and documentation > will disagree (worse than no documentation at all), we're humans after > all. Fixing Hackage is the way to go, not some guaranteed-to-fail > crowd-sourcing... :-/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mail at nh2.me Mon Jan 6 15:55:51 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Mon, 06 Jan 2014 16:55:51 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> Message-ID: <52CAD207.3080705@nh2.me> Yes, it does make a lot of sense in these cases. It is not tedious. This Python script automates it for you: https://gist.github.com/nh2/8284831 (The original block post also contains a minimal script.) Maybe we can add a command `cabal upload-docs` that does this? On Mon 06 Jan 2014 16:47:57 CET, Erik Hesselink wrote: > In some cases it actually makes sense. For example, my kqueue package > is in the list above. It is a binding to a MacOS/BSD C library, and > the hackage build bot runs on linux. So I should actually upload the > documentation... > > Erik > > On Mon, Jan 6, 2014 at 4:35 PM, Sven Panne wrote: >> To be honest, I actively encourage people to *not* fix their package >> documentation manually. This is tedious, error-prone, and I bet there >> will be tons of packages then where the actual code and documentation >> will disagree (worse than no documentation at all), we're humans after >> all. Fixing Hackage is the way to go, not some guaranteed-to-fail >> crowd-sourcing... :-/ >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe From svenpanne at gmail.com Mon Jan 6 16:14:14 2014 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 6 Jan 2014 17:14:14 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CAD207.3080705@nh2.me> References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD207.3080705@nh2.me> Message-ID: 2014/1/6 Niklas Hamb?chen : > [...] It is not tedious. This Python script automates it for you: [...] If you have to use a long Python script, it totally fulfills my definition of "tedious". :-} Another question is: Do the hyperlinks to other packages work when docs are uploaded like this? This is extremely important IMHO. From svenpanne at gmail.com Mon Jan 6 16:16:54 2014 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 6 Jan 2014 17:16:54 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> Message-ID: 2014/1/6 Erik Hesselink : > In some cases it actually makes sense. For example, my kqueue package > is in the list above. It is a binding to a MacOS/BSD C library, and > the hackage build bot runs on linux. [...] Good point. But why is it necessary that the package actually *builds* when generating the docs? I think parsing + type checking/inference should be enough, or did I miss something? From mail at nh2.me Mon Jan 6 16:18:15 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Mon, 06 Jan 2014 17:18:15 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> Message-ID: <52CAD747.7010600@nh2.me> On Mon 06 Jan 2014 17:16:54 CET, Sven Panne wrote: > Good point. But why is it necessary that the package actually *builds* > when generating the docs? I think parsing + type checking/inference > should be enough, or did I miss something? Haddock can't do it. The "Broken documentation on Hackage." thread explains it. From svenpanne at gmail.com Mon Jan 6 16:23:33 2014 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 6 Jan 2014 17:23:33 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CAD747.7010600@nh2.me> References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: 2014/1/6 Niklas Hamb?chen : > Haddock can't do it. The "Broken documentation on Hackage." thread > explains it. That's not a good reason, it is just a technical accident and an artifact of how the documentation is currently built. My point is: To build the documentation, we should probably not build the package itself, this seems to be the source of most problems. Doxygen doesn't generate *.o files, either AFAIK... From hesselink at gmail.com Mon Jan 6 16:34:50 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 6 Jan 2014 17:34:50 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CAD207.3080705@nh2.me> References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD207.3080705@nh2.me> Message-ID: That's a nice script. I've forked it [0] and fixed two issues: the matching on Version is now case insensitive, and it uses --format instead of -H to also work on MacOS/BSD tar. Now my package has documentation! All the links in it are wrong, though. Some regex replace might be able to fix that. Erik [0] https://gist.github.com/hesselink/8285419 On Mon, Jan 6, 2014 at 4:55 PM, Niklas Hamb?chen wrote: > Yes, it does make a lot of sense in these cases. > > It is not tedious. This Python script automates it for you: > > https://gist.github.com/nh2/8284831 > > (The original block post also contains a minimal script.) > > Maybe we can add a command `cabal upload-docs` that does this? > > On Mon 06 Jan 2014 16:47:57 CET, Erik Hesselink wrote: >> In some cases it actually makes sense. For example, my kqueue package >> is in the list above. It is a binding to a MacOS/BSD C library, and >> the hackage build bot runs on linux. So I should actually upload the >> documentation... >> >> Erik >> >> On Mon, Jan 6, 2014 at 4:35 PM, Sven Panne wrote: >>> To be honest, I actively encourage people to *not* fix their package >>> documentation manually. This is tedious, error-prone, and I bet there >>> will be tons of packages then where the actual code and documentation >>> will disagree (worse than no documentation at all), we're humans after >>> all. Fixing Hackage is the way to go, not some guaranteed-to-fail >>> crowd-sourcing... :-/ >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe From malcolm.wallace at me.com Mon Jan 6 16:39:38 2014 From: malcolm.wallace at me.com (Malcolm Wallace) Date: Mon, 06 Jan 2014 16:39:38 +0000 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: On 6 Jan 2014, at 16:23, Sven Panne wrote: > 2014/1/6 Niklas Hamb?chen : >> Haddock can't do it. > > Doxygen doesn't generate *.o files, either AFAIK... Ya! Haddock's insistence on actually compiling the module (rather than just generating documentation) was the source of one of our most puzzling bugs ever. (1) Compile library with ghc. (2) Generate docs with Haddock. (3) Link library. Who would ever suspect that the code got recompiled with different options in that middle step? Regards, Malcolm From mail at nh2.me Mon Jan 6 16:40:54 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Mon, 06 Jan 2014 17:40:54 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: <52CADC96.4000400@nh2.me> Evil! This doesn't happen with cabal, does it? On Mon 06 Jan 2014 17:39:38 CET, Malcolm Wallace wrote: > > On 6 Jan 2014, at 16:23, Sven Panne wrote: > >> 2014/1/6 Niklas Hamb?chen : >>> Haddock can't do it. >> >> Doxygen doesn't generate *.o files, either AFAIK... > > Ya! Haddock's insistence on actually compiling the module (rather than just generating documentation) was the source of one of our most puzzling bugs ever. > > (1) Compile library with ghc. > (2) Generate docs with Haddock. > (3) Link library. > > Who would ever suspect that the code got recompiled with different options in that middle step? > > Regards, > Malcolm > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From star.tim.star at gmail.com Mon Jan 6 16:47:22 2014 From: star.tim.star at gmail.com (timmy tofu) Date: Mon, 6 Jan 2014 11:47:22 -0500 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! Message-ID: With authors (no emails), quick and dirty: http://lpaste.net/raw/98035 Date: Sun, 5 Jan 2014 20:47:27 -0500 > From: Clark Gaebel > To: Mateusz Kowalczyk > Cc: haskell-cafe > Subject: Re: [Haskell-cafe] Please fix documentation for you Hackage > packages! > Message-ID: > qTchiCMeLgtjeFbw at mail.gmail.com> > Content-Type: text/plain; charset="utf-8" > > Is there any way you could tag that list with the author so that we can > Ctrl+f ourselves? > > > On Sun, Jan 5, 2014 at 8:37 PM, Mateusz Kowalczyk > wrote: > > > Greetings caf?, > > > > As some of you might have noticed recently, there seems to be quite a > > few packages with broken documentation on Hackage recently. If you are > > an owner of such package, please consider fixing it. There's a thread on > > cabal-devel about this if you're interested in details. > > > > Here's a list of packages uploaded since beginning of 2013 for which the > > documentation was broken as of yesterday: > > http://fuuzetsu.co.uk/misc/sorted.txt > > > > If your package is on that list, your documentation is broken. Only the > > most recent versions of packages were being considered. > > > > I outline how to fix your documentation (in most cases this means > > uploading it by hand) in a blog post I just published. Please refer to: > > > > > http://fuuzetsu.co.uk/blog/posts/2014-01-06-Fix-your-Hackage-documentation.html > > > > The post contains a link to as script which naively attempts to automate > > the burden of uploading the docs manually. If your package can't be > > built simply with ?cabal configure && cabal build && cabal haddock > > --hyperlink-source?, you'll have to adapt it to your situation. > > > > Thanks. I hope to see fewer packages with broken documentation in the > > future. > > -- > > Mateusz K. > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > -------------- next part -------------- > An HTML attachment was scrubbed... > URL: < > http://www.haskell.org/pipermail/haskell-cafe/attachments/20140105/61df048c/attachment-0001.html > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From miguelimo38 at yandex.ru Mon Jan 6 16:47:55 2014 From: miguelimo38 at yandex.ru (MigMit) Date: Mon, 6 Jan 2014 20:47:55 +0400 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: Hmmm, what if some parts of the code are TemplateHaskell-generated using some macros defined in the same package? On 06 Jan 2014, at 20:23, Sven Panne wrote: > 2014/1/6 Niklas Hamb?chen : >> Haddock can't do it. The "Broken documentation on Hackage." thread >> explains it. > > That's not a good reason, it is just a technical accident and an > artifact of how the documentation is currently built. My point is: To > build the documentation, we should probably not build the package > itself, this seems to be the source of most problems. Doxygen doesn't > generate *.o files, either AFAIK... > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From nicolas at incubaid.com Mon Jan 6 17:06:55 2014 From: nicolas at incubaid.com (Nicolas Trangez) Date: Mon, 06 Jan 2014 18:06:55 +0100 Subject: [Haskell-cafe] Associated types, kind constraints & typelits Message-ID: <1389028015.21320.4.camel@tau.nicolast.be> All, While toying with typelits I wanted to get the following to work, but failed to. Is it intended not to work at all, should I change something to get it to work, or is this something which needs some GHC support? Note I obviously tried to add the constraint mentioned in the compiler error, but failed to: I seem to add too many type arguments to SingI, which somewhat puzzles me. Thanks, Nicolas {-# LANGUAGE TypeFamilies, DataKinds #-} module Main where import GHC.TypeLits class C a where type T a :: Nat data D = D instance C D where type T D = 10 {- This is not allowed, as intended: data E = E instance C E where type T E = Int -} -- This works: tOfD :: D -> Integer tOfD D = fromSing $ (sing :: Sing (T D)) {- This doesn't work: - Could not deduce (SingI Nat (T a1)) arising from a use of `sing' - from the context (C a) tOf :: C a => a -> Integer tOf _ = fromSing $ (sing :: Sing (T a)) -} main :: IO () main = return () From nathan.d.howell at gmail.com Mon Jan 6 17:15:58 2014 From: nathan.d.howell at gmail.com (Nathan Howell) Date: Mon, 6 Jan 2014 09:15:58 -0800 Subject: [Haskell-cafe] Associated types, kind constraints & typelits In-Reply-To: <1389028015.21320.4.camel@tau.nicolast.be> References: <1389028015.21320.4.camel@tau.nicolast.be> Message-ID: This requires -XScopedTypeVariables and some constraints: tOf :: forall a . (SingI (T a), C a) => a -> Integer tOf _ = fromSing $ (sing :: Sing (T a)) On Mon, Jan 6, 2014 at 9:06 AM, Nicolas Trangez wrote: > All, > > While toying with typelits I wanted to get the following to work, but > failed to. Is it intended not to work at all, should I change something > to get it to work, or is this something which needs some GHC support? > > Note I obviously tried to add the constraint mentioned in the compiler > error, but failed to: I seem to add too many type arguments to SingI, > which somewhat puzzles me. > > Thanks, > > Nicolas > > {-# LANGUAGE TypeFamilies, > DataKinds #-} > module Main where > > import GHC.TypeLits > > class C a where > type T a :: Nat > > data D = D > instance C D where > type T D = 10 > > {- This is not allowed, as intended: > > data E = E > instance C E where > type T E = Int > -} > > -- This works: > tOfD :: D -> Integer > tOfD D = fromSing $ (sing :: Sing (T D)) > > {- This doesn't work: > - Could not deduce (SingI Nat (T a1)) arising from a use of `sing' > - from the context (C a) > > tOf :: C a => a -> Integer > tOf _ = fromSing $ (sing :: Sing (T a)) > -} > > main :: IO () > main = return () > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas at incubaid.com Mon Jan 6 17:21:13 2014 From: nicolas at incubaid.com (Nicolas Trangez) Date: Mon, 06 Jan 2014 18:21:13 +0100 Subject: [Haskell-cafe] Associated types, kind constraints & typelits In-Reply-To: References: <1389028015.21320.4.camel@tau.nicolast.be> Message-ID: <1389028873.21320.6.camel@tau.nicolast.be> On Mon, 2014-01-06 at 09:15 -0800, Nathan Howell wrote: > This requires -XScopedTypeVariables and some constraints: > > tOf :: forall a . (SingI (T a), C a) => a -> Integer > tOf _ = fromSing $ (sing :: Sing (T a)) Wonderful, thanks. I tried using ScopedTypeVariables, but "SingI Nat (T a)" didn't work out, although the compiler error hinted in that direction. Thanks, Nicolas From hesselink at gmail.com Mon Jan 6 17:27:17 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 6 Jan 2014 18:27:17 +0100 Subject: [Haskell-cafe] Associated types, kind constraints & typelits In-Reply-To: References: <1389028015.21320.4.camel@tau.nicolast.be> Message-ID: Small additions: the 'Nat' in the original argument is the kind argument to the class. It seems to be a bug that GHC provided this in the error, and the latest HEAD doesn't seem to do so anymore. Also, in the latest HEAD, I think you need to use the singletons library, as all the singletons stuff is gone from base. My working code: {-# LANGUAGE TypeFamilies , DataKinds , FlexibleContexts , ScopedTypeVariables #-} module Main where import GHC.TypeLits import Data.Singletons class C a where type T a :: Nat data D = D instance C D where type T D = 10 {- This is not allowed, as intended: data E = E instance C E where type T E = Int -} -- This works: tOfD :: D -> Integer tOfD D = fromSing $ (sing :: Sing (T D)) tOf :: forall a. (KnownNat (T a), C a) => a -> Integer tOf _ = fromSing $ (sing :: Sing (T a)) main :: IO () main = return () Erik On Mon, Jan 6, 2014 at 6:15 PM, Nathan Howell wrote: > This requires -XScopedTypeVariables and some constraints: > > tOf :: forall a . (SingI (T a), C a) => a -> Integer > tOf _ = fromSing $ (sing :: Sing (T a)) > > > On Mon, Jan 6, 2014 at 9:06 AM, Nicolas Trangez > wrote: >> >> All, >> >> While toying with typelits I wanted to get the following to work, but >> failed to. Is it intended not to work at all, should I change something >> to get it to work, or is this something which needs some GHC support? >> >> Note I obviously tried to add the constraint mentioned in the compiler >> error, but failed to: I seem to add too many type arguments to SingI, >> which somewhat puzzles me. >> >> Thanks, >> >> Nicolas >> >> {-# LANGUAGE TypeFamilies, >> DataKinds #-} >> module Main where >> >> import GHC.TypeLits >> >> class C a where >> type T a :: Nat >> >> data D = D >> instance C D where >> type T D = 10 >> >> {- This is not allowed, as intended: >> >> data E = E >> instance C E where >> type T E = Int >> -} >> >> -- This works: >> tOfD :: D -> Integer >> tOfD D = fromSing $ (sing :: Sing (T D)) >> >> {- This doesn't work: >> - Could not deduce (SingI Nat (T a1)) arising from a use of `sing' >> - from the context (C a) >> >> tOf :: C a => a -> Integer >> tOf _ = fromSing $ (sing :: Sing (T a)) >> -} >> >> main :: IO () >> main = return () >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From dgorin at dc.uba.ar Mon Jan 6 18:08:47 2014 From: dgorin at dc.uba.ar (=?windows-1252?Q?Daniel_Gor=EDn?=) Date: Mon, 6 Jan 2014 19:08:47 +0100 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: On 06 Jan 2014, at 17:23, Sven Panne wrote: > [?] To build the documentation, we should probably not build the package > itself, this seems to be the source of most problems. Doxygen doesn't > generate *.o files, either AFAIK? Some packages that have bindings to foreign libraries are not built in hackage since *cabal* is rejecting them; otherwise ghc would be happy to build them and produce haddocks. Cabal rejects them since they list libraries in the extra-libraries or pkgconfig-depends field that are not found, but as long as header files are not needed in building the package, only the linking process would ultimately fail. If this check by cabal could be overridden with some flag, then we?d easily get more packages to build and have docs. Daniel From rda at lemma-one.com Mon Jan 6 18:21:24 2014 From: rda at lemma-one.com (Rob Arthan) Date: Mon, 6 Jan 2014 18:21:24 +0000 Subject: [Haskell-cafe] Infelicity in StdGen? In-Reply-To: References: <62B1DAD5-8437-4BF6-A2C4-E63AD9E23FDB@lemma-one.com> Message-ID: On 3 Jan 2014, at 19:22, Krzysztof Skrz?tnicki wrote: > I think the confusion may be come from the understanding of "distinct". The documentation is right that the generators are not equal which is easily checked e.g. using their Show instance. They will produce different random numbers. The user of the library might OTOH assume that "distinct" mean "producing uncorrelated output". I agree that my example doesn't refute the precise meaning of the words. May I suggest that the statement that the generators are likely to be distinct on distinct inputs isn't really that useful to someone using StdGen. > This is harder and may simply not hold, especially that it doesn't mention sequentially increasing integers or any other kinds of sequences. > > The property you seem to be looking for is "have vastly different output for similar numbers". Sounds a lot like a hash function to me. > I think most people would expect the function that maps the seed of a pseudo-random number generator to the first (or second or third or ...) value it generates to be a reasonably good hash function. As this turns out not to be the case for the algorithm used by StdGen for certain lengths of the range, the statement about distinct generators is somewhat misleading. I had a look at the StdGen source and don't know enough about the algorithm it is using to comment on why it has this surprising behaviour for some lengths of the range. It really is surprising in my view: one way of describing the behaviour is that if you use StdGen to generate a random boolean with seeds n and n+1, the probability that the two values are different is less than 1/50,000. Thanks for suggesting the useful work-arounds. Regards, Rob. -------------- next part -------------- An HTML attachment was scrubbed... URL: From pcaspers1973 at gmail.com Mon Jan 6 18:49:23 2014 From: pcaspers1973 at gmail.com (Peter Caspers) Date: Mon, 6 Jan 2014 19:49:23 +0100 Subject: [Haskell-cafe] Haddock - How to write formulas ? Message-ID: Hi, I am still very new to Haskell, trying to start my very first project. For its documentation I want to use Haddock and suitable comments in the source code. I notice that (e.g. different from doxygen) there is no direct way of writing formulas, say in TeX style. Looking into some projects on Hackage, formulas there seem to be written in "pseudo-code" more or less like TeX but not following any strict standard. As far as I can see. What would be your recommendations concerning this ? Is there some guideline on how to include formulas ? I understand that there is "literal programming" where you can e.g. write a TeX article with embedded code blocks that can be extracted for the compiler. However, I do not want to follow this path, also the result is a bit different from what is produced in the "traditional" approach, isn't it. Thanks a lot Peter From creswick at gmail.com Mon Jan 6 19:02:56 2014 From: creswick at gmail.com (Rogan Creswick) Date: Mon, 6 Jan 2014 11:02:56 -0800 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: On Mon, Jan 6, 2014 at 8:47 AM, MigMit wrote: > Hmmm, what if some parts of the code are TemplateHaskell-generated using > some macros defined in the same package? > I'd be happy with it failing in that case. It would be better than what we have now! I tend to think this could also be fixed (in many situations) but we *don't need* a perfect solution. --Rogan > On 06 Jan 2014, at 20:23, Sven Panne wrote: > > > 2014/1/6 Niklas Hamb?chen : > >> Haddock can't do it. The "Broken documentation on Hackage." thread > >> explains it. > > > > That's not a good reason, it is just a technical accident and an > > artifact of how the documentation is currently built. My point is: To > > build the documentation, we should probably not build the package > > itself, this seems to be the source of most problems. Doxygen doesn't > > generate *.o files, either AFAIK... > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jgm at berkeley.edu Mon Jan 6 19:15:53 2014 From: jgm at berkeley.edu (John MacFarlane) Date: Mon, 6 Jan 2014 11:15:53 -0800 Subject: [Haskell-cafe] ANN: cheapskate 0.1, markdown parser Message-ID: <20140106191553.GA49308@Johns-MacBook-Air-2.local> I've released a new markdown library on Hackage: http://hackage.haskell.org/package/cheapskate This library is designed to be used in web applications. It is small, accurate, and fast, in pure Haskell with few dependencies. All output is sanitized through a whitelist by default. It is designed to have performance that varies linearly with the input size, even with garbage input. To illustrate: % head -c 100000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null cheapskate > /dev/null 0.15s user 0.01s system 82% cpu 0.199 total % head -c 1000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null cheapskate > /dev/null 1.53s user 0.03s system 88% cpu 1.770 total % head -c 10000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null cheapskate > /dev/null 15.50s user 0.20s system 89% cpu 17.632 total This is a test that many markdown parsers fail (including my own pandoc and the markdown package on Hackage). Performance is about seven times faster than pandoc (with five times less memory used), and about 25% faster than the markdown package on Hackage. Generic functions are provided that allow transformations of the AST prior to rendering (e.g., promotion of headers, insertion of syntax highlighting, or the conversion of specially marked code blocks into diagrams). Several markdown extensions are supported, and sensible decisions have been made about several aspects of markdown syntax that are left vague by John Gruber's specification. For details, see the README at https://github.com/jgm/cheapskate. From carter.schonwald at gmail.com Mon Jan 6 19:31:51 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 6 Jan 2014 14:31:51 -0500 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: Point being: we need more people to get involved in dev / admin of hackage and help with associated hackage infrastructure. On Monday, January 6, 2014, Rogan Creswick wrote: > On Mon, Jan 6, 2014 at 8:47 AM, MigMit > > wrote: > >> Hmmm, what if some parts of the code are TemplateHaskell-generated using >> some macros defined in the same package? >> > > I'd be happy with it failing in that case. It would be better than what > we have now! > > I tend to think this could also be fixed (in many situations) but we > *don't need* a perfect solution. > > --Rogan > > >> On 06 Jan 2014, at 20:23, Sven Panne > >> wrote: >> >> > 2014/1/6 Niklas Hamb?chen > 'mail at nh2.me');>>: >> >> Haddock can't do it. The "Broken documentation on Hackage." thread >> >> explains it. >> > >> > That's not a good reason, it is just a technical accident and an >> > artifact of how the documentation is currently built. My point is: To >> > build the documentation, we should probably not build the package >> > itself, this seems to be the source of most problems. Doxygen doesn't >> > generate *.o files, either AFAIK... >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org > 'Haskell-Cafe at haskell.org');> >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org > 'Haskell-Cafe at haskell.org');> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Mon Jan 6 20:16:13 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Mon, 6 Jan 2014 21:16:13 +0100 Subject: [Haskell-cafe] preprocessor, how to? In-Reply-To: <52ca65c5.81240f0a.169b.ffffdf29SMTPIN_ADDED_BROKEN@mx.google.com> References: <52ca65c5.81240f0a.169b.ffffdf29SMTPIN_ADDED_BROKEN@mx.google.com> Message-ID: I don't quite understand why you can't just use pathSeparator (or ) here. The code in the quotes is still Haskell, and it's going to compile on the same platform it's going to run on, right? Erik On Mon, Jan 6, 2014 at 9:13 AM, Kees Bleijenberg wrote: > In a program I use a lot of hamlet files. All these hamlet files are in a > submap of the source map. In code: > allHtml = Mconcat [ $(hamletFile "hamlet\\belastingen.hamlet") renderUrl > ,$(hamletFile "hamlet\\winddruk.hamlet") renderUrl > .. > ,$(hamletFile "hamlet\\berekeningDruk.hamlet") > renderUrl > ,$(hamletFile "hamlet\\drukNaarBuigTrek.hamlet") > renderUrl] > This is a Windows program. > > For another project I want to use this piece of code on Linux. The code > should now be: > .. $(hamletFile "hamlet/winddruk.hamlet") renderUrl > > I can't use pathSeparator here, because this is all happening at compile > time. So I think I need a preprocessor. > I would like to have a kind of hamletDir macro and change the code to > something like: > > #ifdef Win32 > hamletDir = "hamlet\\" > #else > hamletDir = "hamlet/" > #endif > ... > $(hamletFile "{hamletDir}winddruk.hamlet") renderUrl > Is it possible in Haskell and how do I it? > > All examples of preprocessing in Haskell I found are something like this: > #ifdef xxx > aaaa > #else > Bbbbb > #endif > I could use that. But a user defined macro is less code. > > Kees > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From jgbailey at gmail.com Mon Jan 6 21:07:35 2014 From: jgbailey at gmail.com (Justin Bailey) Date: Mon, 6 Jan 2014 13:07:35 -0800 Subject: [Haskell-cafe] ANN: cheapskate 0.1, markdown parser In-Reply-To: <20140106191553.GA49308@Johns-MacBook-Air-2.local> References: <20140106191553.GA49308@Johns-MacBook-Air-2.local> Message-ID: Looks like an excellent library! How did you manage to maintain linear growth in running time? Seems like quite an achievement. On Mon, Jan 6, 2014 at 11:15 AM, John MacFarlane wrote: > I've released a new markdown library on Hackage: > http://hackage.haskell.org/package/cheapskate > > This library is designed to be used in web applications. It is small, > accurate, and fast, in pure Haskell with few dependencies. All output > is sanitized through a whitelist by default. It is designed to have > performance that varies linearly with the input size, even with garbage > input. To illustrate: > > % head -c 100000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > cheapskate > /dev/null 0.15s user 0.01s system 82% cpu 0.199 total > % head -c 1000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > cheapskate > /dev/null 1.53s user 0.03s system 88% cpu 1.770 total > % head -c 10000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > cheapskate > /dev/null 15.50s user 0.20s system 89% cpu 17.632 total > > This is a test that many markdown parsers fail (including my own pandoc > and the markdown package on Hackage). > > Performance is about seven times faster than pandoc (with five times > less memory used), and about 25% faster than the markdown package on Hackage. > > Generic functions are provided that allow transformations of the AST > prior to rendering (e.g., promotion of headers, insertion of syntax > highlighting, or the conversion of specially marked code blocks into > diagrams). > > Several markdown extensions are supported, and sensible decisions have > been made about several aspects of markdown syntax that are left vague > by John Gruber's specification. For details, see the README > at https://github.com/jgm/cheapskate. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From headprogrammingczar at gmail.com Mon Jan 6 21:40:27 2014 From: headprogrammingczar at gmail.com (Joe Quinn) Date: Mon, 06 Jan 2014 16:40:27 -0500 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> Message-ID: <52CB22CB.2050702@gmail.com> On 1/6/2014 11:39 AM, Malcolm Wallace wrote: > Doxygen doesn't generate *.o files, either AFAIK... > Ya! Haddock's insistence on actually compiling the module (rather than just generating documentation) was the source of one of our most puzzling bugs ever. > > (1) Compile library with ghc. > (2) Generate docs with Haddock. > (3) Link library. > > Who would ever suspect that the code got recompiled with different options in that middle step? > You never know when you will want to have your documentation automatically generated by Template Haskell... From carter.schonwald at gmail.com Mon Jan 6 22:12:13 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 6 Jan 2014 17:12:13 -0500 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: <52CB22CB.2050702@gmail.com> References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD747.7010600@nh2.me> <52CB22CB.2050702@gmail.com> Message-ID: truth. I think theres a few libs that do this, though their names escape me right now. On Mon, Jan 6, 2014 at 4:40 PM, Joe Quinn wrote: > On 1/6/2014 11:39 AM, Malcolm Wallace wrote: > >> Doxygen doesn't generate *.o files, either AFAIK... >> Ya! Haddock's insistence on actually compiling the module (rather than >> just generating documentation) was the source of one of our most puzzling >> bugs ever. >> >> (1) Compile library with ghc. >> (2) Generate docs with Haddock. >> (3) Link library. >> >> Who would ever suspect that the code got recompiled with different >> options in that middle step? >> >> You never know when you will want to have your documentation > automatically generated by Template Haskell... > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Mon Jan 6 22:13:38 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 06 Jan 2014 22:13:38 +0000 Subject: [Haskell-cafe] Please fix documentation for you Hackage packages! In-Reply-To: References: <52CA08BF.90301@fuuzetsu.co.uk> <52CA0BEB.7040803@fuuzetsu.co.uk> <52CAC1AB.5080100@nh2.me> <52CAD207.3080705@nh2.me> Message-ID: <52CB2A92.1010704@fuuzetsu.co.uk> On 06/01/14 16:14, Sven Panne wrote: > 2014/1/6 Niklas Hamb?chen : >> [...] It is not tedious. This Python script automates it for you: [...] > > If you have to use a long Python script, it totally fulfills my > definition of "tedious". :-} > > Another question is: Do the hyperlinks to other packages work when > docs are uploaded like this? This is extremely important IMHO. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > No, they don't. Someone pointed out to me yesterday that maybe something like ?--html-location='//hackage.haskell.org/package/'? would allow it to work but I have not tried yet. -- Mateusz K. From magnus at therning.org Mon Jan 6 22:17:39 2014 From: magnus at therning.org (Magnus Therning) Date: Mon, 6 Jan 2014 23:17:39 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140105133607.GA25194@machine> References: <20140105120045.GC1366@mteis.lan> <20140105122130.GA16826@machine> <20140105124456.GE1366@mteis.lan> <20140105133607.GA25194@machine> Message-ID: <20140106221739.GA4145@mteis.lan> On Sun, Jan 05, 2014 at 02:36:07PM +0100, Daniel Trstenjak wrote: > It seems to be a problem with the building of 'HsImport/Args.hs', > which is the only module using the cabal module 'Paths_hsimport'. > > The in this regard relevant parts of 'HsImport/Args.hs' seem to be: > > {-# LANGUAGE ... CPP #-} > > ... > > #ifdef CABAL > import Data.Version (showVersion) > import Paths_hsimport (version) > #endif > > > And in 'hsimport.cabal' there's: > > ... > Executable hsimport > ... > cpp-options: -DCABAL > > > Could you try modifying the hsimport executable section: > > ... > Executable hsimport > ... > cpp-options: -DCABAL > extensions: CPP Still no luck :( /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus You do not examine legislation in the light of the benefits it will convey if properly administered, but in the light of the wrongs it would do and the harms it would cause if improperly administered. -- Lyndon Johnson -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From fuuzetsu at fuuzetsu.co.uk Mon Jan 6 22:20:01 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 06 Jan 2014 22:20:01 +0000 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: Message-ID: <52CB2C11.4010405@fuuzetsu.co.uk> On 06/01/14 18:49, Peter Caspers wrote: > Hi, > > I am still very new to Haskell, trying to start my very first project. > For its documentation I want to use Haddock and suitable comments in > the source code. > > I notice that (e.g. different from doxygen) there is no direct way of > writing formulas, say in TeX style. Looking into some projects on > Hackage, formulas there > seem to be written in "pseudo-code" more or less like TeX but not > following any strict standard. As far as I can see. That's right, there's no direct way to embed maths in Haddock. It has been a somewhat requested feature for Haddock over summer when I did work on it but it didn't make it in. > What would be your recommendations concerning this ? Is there some > guideline on how to include formulas ? I understand that there is > "literal programming" > where you can e.g. write a TeX article with embedded code blocks that > can be extracted for the compiler. However, I do not want to follow > this path, also the > result is a bit different from what is produced in the "traditional" > approach, isn't it. If you want manually-written LaTeX, this is probably the only way at the moment. If all you want is some LaTeX snippets (maths), your best bet is to probably write those separately, make images out of them and then embed them into your documentation. There's currently no way for Haddock to do this for you. We do however have a LaTeX back-end so it's not like it's impossible to generate but it'd require some work that has not yet been put in. > Thanks a lot > Peter > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Mateusz K. From alexander.vershilov at gmail.com Mon Jan 6 23:44:19 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Tue, 7 Jan 2014 03:44:19 +0400 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: <52CB2C11.4010405@fuuzetsu.co.uk> References: <52CB2C11.4010405@fuuzetsu.co.uk> Message-ID: It's possible to use latex render sites [1], then shrink link by tiny URL [2]. Then paste like usual image. [1] http://www.codecogs.com/latex/eqneditor.php [2] http://tinyurl.com -- Alexander On Jan 7, 2014 2:20 AM, "Mateusz Kowalczyk" wrote: > On 06/01/14 18:49, Peter Caspers wrote: > > Hi, > > > > I am still very new to Haskell, trying to start my very first project. > > For its documentation I want to use Haddock and suitable comments in > > the source code. > > > > I notice that (e.g. different from doxygen) there is no direct way of > > writing formulas, say in TeX style. Looking into some projects on > > Hackage, formulas there > > seem to be written in "pseudo-code" more or less like TeX but not > > following any strict standard. As far as I can see. > > That's right, there's no direct way to embed maths in Haddock. It has > been a somewhat requested feature for Haddock over summer when I did > work on it but it didn't make it in. > > > What would be your recommendations concerning this ? Is there some > > guideline on how to include formulas ? I understand that there is > > "literal programming" > > where you can e.g. write a TeX article with embedded code blocks that > > can be extracted for the compiler. However, I do not want to follow > > this path, also the > > result is a bit different from what is produced in the "traditional" > > approach, isn't it. > > If you want manually-written LaTeX, this is probably the only way at the > moment. If all you want is some LaTeX snippets (maths), your best bet is > to probably write those separately, make images out of them and then > embed them into your documentation. There's currently no way for Haddock > to do this for you. We do however have a LaTeX back-end so it's not like > it's impossible to generate but it'd require some work that has not yet > been put in. > > > Thanks a lot > > Peter > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Mon Jan 6 23:50:25 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 06 Jan 2014 23:50:25 +0000 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> Message-ID: <1389052225.9235.53.camel@kirk> Hi, it should also be possible to render Formulas to SVG, and embed the SVG-File using a data-URL, and get a vector rendering of your formular.... similar to the image in http://hackage.haskell.org/package/circle-packing-0.1.0.3/docs/Optimisation-CirclePacking.html But probably that will hit size bounds very soon. http://hackage.haskell.org/package/diagrams-haddock works similarly, and also explains how to ship the SVG files separately, to not hit size bounds. I guess a tool similar to that, latex-haddock, would be feasible and useful. Greetings, Joachim Am Dienstag, den 07.01.2014, 03:44 +0400 schrieb Alexander V Vershilov: > It's possible to use latex render sites [1], then shrink link by tiny > URL [2]. Then paste like usual image. > > [1] http://www.codecogs.com/latex/eqneditor.php > [2] http://tinyurl.com > > -- > Alexander > > On Jan 7, 2014 2:20 AM, "Mateusz Kowalczyk" > wrote: > On 06/01/14 18:49, Peter Caspers wrote: > > Hi, > > > > I am still very new to Haskell, trying to start my very > first project. > > For its documentation I want to use Haddock and suitable > comments in > > the source code. > > > > I notice that (e.g. different from doxygen) there is no > direct way of > > writing formulas, say in TeX style. Looking into some > projects on > > Hackage, formulas there > > seem to be written in "pseudo-code" more or less like TeX > but not > > following any strict standard. As far as I can see. > > That's right, there's no direct way to embed maths in Haddock. > It has > been a somewhat requested feature for Haddock over summer when > I did > work on it but it didn't make it in. > > > What would be your recommendations concerning this ? Is > there some > > guideline on how to include formulas ? I understand that > there is > > "literal programming" > > where you can e.g. write a TeX article with embedded code > blocks that > > can be extracted for the compiler. However, I do not want to > follow > > this path, also the > > result is a bit different from what is produced in the > "traditional" > > approach, isn't it. > > If you want manually-written LaTeX, this is probably the only > way at the > moment. If all you want is some LaTeX snippets (maths), your > best bet is > to probably write those separately, make images out of them > and then > embed them into your documentation. There's currently no way > for Haddock > to do this for you. We do however have a LaTeX back-end so > it's not like > it's impossible to generate but it'd require some work that > has not yet > been put in. > > > Thanks a lot > > Peter > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Joachim Breitner e-Mail: mail at joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata at joachim-breitner.de -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 198 bytes Desc: This is a digitally signed message part URL: From suhailshergill at gmail.com Tue Jan 7 00:31:14 2014 From: suhailshergill at gmail.com (Suhail Shergill) Date: Tue, 07 Jan 2014 00:31:14 +0000 Subject: [Haskell-cafe] liboleg Message-ID: <874n5gaazx.fsf@chaos.shergill.su> hi, i would like to take over as maintainer of the liboleg package on hackage . i have gotten permission from the author (oleg) and the current maintainer (don) regarding the same via email. my hackage username is shergill. if there are no objections, could i be added to the maintainer group for liboleg and be granted upload rights? -- Suhail From dagitj at gmail.com Tue Jan 7 00:36:29 2014 From: dagitj at gmail.com (Jason Dagit) Date: Mon, 6 Jan 2014 16:36:29 -0800 Subject: [Haskell-cafe] liboleg In-Reply-To: <874n5gaazx.fsf@chaos.shergill.su> References: <874n5gaazx.fsf@chaos.shergill.su> Message-ID: As a user, it would be nicer if the collection is split into separate libraries based on functionality. I think his has been done for some of Oleg's ideas (reflection, iteratee, etc). Just throwing in my $0.02 even though you didn't ask :) -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Jan 7 01:42:23 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 6 Jan 2014 20:42:23 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: <1389052225.9235.53.camel@kirk> References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> Message-ID: I would really love to use MathJax in the haddock HTML backend. Is there any way (however hacky) that I could do that? On Monday, January 6, 2014, Joachim Breitner wrote: > Hi, > > it should also be possible to render Formulas to SVG, and embed the > SVG-File using a data-URL, and get a vector rendering of your > formular.... similar to the image in > > http://hackage.haskell.org/package/circle-packing-0.1.0.3/docs/Optimisation-CirclePacking.html > > But probably that will hit size bounds very soon. > > http://hackage.haskell.org/package/diagrams-haddock works similarly, and > also explains how to ship the SVG files separately, to not hit size > bounds. > > I guess a tool similar to that, latex-haddock, would be feasible and > useful. > > Greetings, > Joachim > > > Am Dienstag, den 07.01.2014, 03:44 +0400 schrieb Alexander V Vershilov: > > It's possible to use latex render sites [1], then shrink link by tiny > > URL [2]. Then paste like usual image. > > > > [1] http://www.codecogs.com/latex/eqneditor.php > > [2] http://tinyurl.com > > > > -- > > Alexander > > > > On Jan 7, 2014 2:20 AM, "Mateusz Kowalczyk" > > wrote: > > On 06/01/14 18:49, Peter Caspers wrote: > > > Hi, > > > > > > I am still very new to Haskell, trying to start my very > > first project. > > > For its documentation I want to use Haddock and suitable > > comments in > > > the source code. > > > > > > I notice that (e.g. different from doxygen) there is no > > direct way of > > > writing formulas, say in TeX style. Looking into some > > projects on > > > Hackage, formulas there > > > seem to be written in "pseudo-code" more or less like TeX > > but not > > > following any strict standard. As far as I can see. > > > > That's right, there's no direct way to embed maths in Haddock. > > It has > > been a somewhat requested feature for Haddock over summer when > > I did > > work on it but it didn't make it in. > > > > > What would be your recommendations concerning this ? Is > > there some > > > guideline on how to include formulas ? I understand that > > there is > > > "literal programming" > > > where you can e.g. write a TeX article with embedded code > > blocks that > > > can be extracted for the compiler. However, I do not want to > > follow > > > this path, also the > > > result is a bit different from what is produced in the > > "traditional" > > > approach, isn't it. > > > > If you want manually-written LaTeX, this is probably the only > > way at the > > moment. If all you want is some LaTeX snippets (maths), your > > best bet is > > to probably write those separately, make images out of them > > and then > > embed them into your documentation. There's currently no way > > for Haddock > > to do this for you. We do however have a LaTeX back-end so > > it's not like > > it's impossible to generate but it'd require some work that > > has not yet > > been put in. > > > > > Thanks a lot > > > Peter > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > -- > > Mateusz K. > > _______________________________________________ > > Haskell-Cafe mailing list > > Joachim Breitner > e-Mail: mail at joachim-breitner.de > Homepage: http://www.joachim-breitner.de > Jabber-ID: nomeata at joachim-breitner.de > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Jan 7 02:52:12 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 07 Jan 2014 02:52:12 +0000 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> Message-ID: <52CB6BDC.1020105@fuuzetsu.co.uk> On 07/01/14 01:42, Carter Schonwald wrote: > I would really love to use MathJax in the haddock HTML backend. Is there > any way (however hacky) that I could do that? I looked up how MathJax is used and as far as I can tell, it's just the case of putting the MathJax JavaScript header into the file, right? We already use JavaScript on the Haddock-generated HTML pages, for example the synopsis box. While I prefer JavaScript-free web I think that for viewing on Hackage, it'd be possible to just stick the header into the generated files and be done with it. Here are some caveats: * You suddenly allow for part of documentation to be rendered by someone else, over the Internet. The problem is that documentation suddenly becomes worse for everyone browsing without JavaScript or browsing locally, without an Internet connection. Embedding images avoids both of these problems. * With the wealth of characters you're likely to use while writing LaTeX, it would clash with existing Haddock syntax sooner or later so this would have to be handled. I spent my summer working on Haddock parser and the new version allows you to escape things properly but the currently used one is very limited in that aspect. You'd probably end up having to introduce some kind of ?verbatim? block to Haddock's syntax which tells it to just take things at face value. It'd not be too hard with the new parser. We're having problems getting the new parser merged however (problems validating GHC to check that we haven't broken everything ever). * This touches on frequently overlooked problem: Haddock targets more than just the HTML back-end. We also have the LaTeX back-end and the Hoogle back-end. This is why we don't allow things like verbatim HTML in the markup, it doesn't make sense for anything but HTML. Admittedly, LaTeX back-end could just generate the maths itself but we then suddenly have to change the ?verbatim? block to the ?LaTeX? block. It's also unclear how Hoogle back-end would deal with this. Even if we add the ?LaTeX structure? to Haddock, I'm afraid that it might end up with people just writing LaTeX for their documentation which is useless for anyone not using that back-end. So, yes, it'd be possible but it'd be very hacky. Not from the code aspect of things, but from the design aspect of it. Perhaps it'd be possible to have pieces of documentation targeting specific back-ends, kind of like internal Haddock pragma if you will, which would allow the user to write differently looking docs for each back-end. At this point however, it becomes clunky to use, horrible to maintain and simply including images in your docs is the easier way out, especially because you're no longer limited by what Haddock can do. I recommend against this kind of thought and I expect that most people that have worked on Haddock would agree. In conclusion, if you want maths in your comments, use images. -- Mateusz K. From andrew.gibiansky at gmail.com Tue Jan 7 03:17:21 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Mon, 6 Jan 2014 22:17:21 -0500 Subject: [Haskell-cafe] Class Instance with ExistentialQuantification Message-ID: Why is the following not allowed? {-# LANGUAGE ExistentialQuantification, ExplicitForAll, RankNTypes, FlexibleInstances #-} class Class a where test :: a -> Bool instance Class (forall m. m -> m) where test _ = True main = do putStrLn $ test id Is there a reason that this is forbidden? Just curious. -- Andrew -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Tue Jan 7 09:16:31 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Tue, 7 Jan 2014 10:16:31 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140106221739.GA4145@mteis.lan> References: <20140105120045.GC1366@mteis.lan> <20140105122130.GA16826@machine> <20140105124456.GE1366@mteis.lan> <20140105133607.GA25194@machine> <20140106221739.GA4145@mteis.lan> Message-ID: <20140107091631.GA4189@machine> Hi Magnus, > Still no luck :( One last thing you could try, is to remove 'cpp-options: -DCABAL' from 'hsimport.cabal', then 'HsImport/Args.hs' shouldn't need 'Paths_hsimport' anymore. But the whole thing seems to be a cabal build issue, so asking for help on the cabal mailing list might make sense. Greetings, Daniel From pcaspers1973 at gmail.com Tue Jan 7 09:22:27 2014 From: pcaspers1973 at gmail.com (Peter Caspers) Date: Tue, 7 Jan 2014 10:22:27 +0100 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: <52CB6BDC.1020105@fuuzetsu.co.uk> References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> Message-ID: Thanks. I guess the best way for me is just writing the formulas as TeX - code fragments, then it should be easy to adapt to any potential Haddock extensions to come in the future. At the same time this notation is readable enough even as plain text in my opinion. Peter On 7 January 2014 03:52, Mateusz Kowalczyk wrote: > On 07/01/14 01:42, Carter Schonwald wrote: >> I would really love to use MathJax in the haddock HTML backend. Is there >> any way (however hacky) that I could do that? > > I looked up how MathJax is used and as far as I can tell, it's just > the case of putting the MathJax JavaScript header into the file, > right? We already use JavaScript on the Haddock-generated HTML pages, > for example the synopsis box. > > While I prefer JavaScript-free web I think that for viewing on > Hackage, it'd be possible to just stick the header into the generated > files and be done with it. Here are some caveats: > > * You suddenly allow for part of documentation to be rendered by > someone else, over the Internet. The problem is that documentation > suddenly becomes worse for everyone browsing without JavaScript or > browsing locally, without an Internet connection. Embedding images > avoids both of these problems. > > * With the wealth of characters you're likely to use while writing > LaTeX, it would clash with existing Haddock syntax sooner or later > so this would have to be handled. I spent my summer working on > Haddock parser and the new version allows you to escape things > properly but the currently used one is very limited in that aspect. > You'd probably end up having to introduce some kind of ?verbatim? > block to Haddock's syntax which tells it to just take things at face > value. It'd not be too hard with the new parser. We're having > problems getting the new parser merged however (problems validating > GHC to check that we haven't broken everything ever). > > * This touches on frequently overlooked problem: Haddock targets more > than just the HTML back-end. We also have the LaTeX back-end and the > Hoogle back-end. This is why we don't allow things like verbatim > HTML in the markup, it doesn't make sense for anything but HTML. > Admittedly, LaTeX back-end could just generate the maths itself but > we then suddenly have to change the ?verbatim? block to the ?LaTeX? > block. It's also unclear how Hoogle back-end would deal with this. > Even if we add the ?LaTeX structure? to Haddock, I'm afraid that it > might end up with people just writing LaTeX for their documentation > which is useless for anyone not using that back-end. > > So, yes, it'd be possible but it'd be very hacky. Not from the code > aspect of things, but from the design aspect of it. > > Perhaps it'd be possible to have pieces of documentation targeting > specific back-ends, kind of like internal Haddock pragma if you will, > which would allow the user to write differently looking docs for each > back-end. At this point however, it becomes clunky to use, horrible to > maintain and simply including images in your docs is the easier way > out, especially because you're no longer limited by what Haddock can > do. I recommend against this kind of thought and I expect that most > people that have worked on Haddock would agree. > > In conclusion, if you want maths in your comments, use images. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From hesselink at gmail.com Tue Jan 7 09:49:35 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Tue, 7 Jan 2014 10:49:35 +0100 Subject: [Haskell-cafe] liboleg In-Reply-To: <874n5gaazx.fsf@chaos.shergill.su> References: <874n5gaazx.fsf@chaos.shergill.su> Message-ID: Hi Suhail, In principle, maintainers can (and should) do this themselves. There's a link to the "maintainer's corner" at the bottom of the package page, which allows adding and removing of maintainers. In cases where the maintainer is unresposive/unavailable, we (hackage admins) can do it, but that doesn't seem to be the case here. Regards, Erik On Tue, Jan 7, 2014 at 1:31 AM, Suhail Shergill wrote: > hi, > > i would like to take over as maintainer of the liboleg package on hackage > . i have gotten permission from the > author (oleg) and the current maintainer (don) regarding the same via email. > > my hackage username is shergill. if there are no objections, could i be added to > the maintainer group for liboleg and be granted upload rights? > > -- > Suhail From roma at ro-che.info Tue Jan 7 10:18:12 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 7 Jan 2014 12:18:12 +0200 Subject: [Haskell-cafe] Class Instance with ExistentialQuantification In-Reply-To: References: Message-ID: <20140107101812.GA8094@sniper> * Andrew Gibiansky [2014-01-06 22:17:21-0500] > Why is the following not allowed? > > {-# LANGUAGE ExistentialQuantification, ExplicitForAll, RankNTypes, > FlexibleInstances #-} > > class Class a where > test :: a -> Bool > > instance Class (forall m. m -> m) where > test _ = True > > main = do > putStrLn $ test id > > Is there a reason that this is forbidden? Just curious. I believe the rule is that all constraints (including class constraints) range over monotypes. What are you trying to achieve? You can do this, for example: newtype Poly = Poly (forall a . a -> a) instance Class Poly where test = const True main = print $ test $ Poly id BTW, this has nothing to do with ExistentialQuantification. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From me at lelf.lu Tue Jan 7 12:18:51 2014 From: me at lelf.lu (Antonio Nikishaev) Date: Tue, 07 Jan 2014 16:18:51 +0400 Subject: [Haskell-cafe] Haddock - How to write formulas ? References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> Message-ID: Mateusz Kowalczyk writes: > On 07/01/14 01:42, Carter Schonwald wrote: >> I would really love to use MathJax in the haddock HTML backend. Is there >> any way (however hacky) that I could do that? > > I looked up how MathJax is used and as far as I can tell, it's just > the case of putting the MathJax JavaScript header into the file, > right? We already use JavaScript on the Haddock-generated HTML pages, > for example the synopsis box. > > While I prefer JavaScript-free web I think that for viewing on > Hackage, it'd be possible to just stick the header into the generated > files and be done with it. Here are some caveats: > > * You suddenly allow for part of documentation to be rendered by > someone else, over the Internet. The problem is that documentation > suddenly becomes worse for everyone browsing without JavaScript or > browsing locally, without an Internet connection. Embedding images > avoids both of these problems. No. It's rendered in the browser. -- lelf From suhailshergill at gmail.com Tue Jan 7 12:34:42 2014 From: suhailshergill at gmail.com (Suhail Shergill) Date: Tue, 07 Jan 2014 12:34:42 +0000 Subject: [Haskell-cafe] liboleg In-Reply-To: (Erik Hesselink's message of "Tue, 7 Jan 2014 10:49:35 +0100") References: <874n5gaazx.fsf@chaos.shergill.su> Message-ID: <87zjn87yxo.fsf@chaos.shergill.su> Erik Hesselink writes: > In cases where the maintainer is unresposive/unavailable, we (hackage admins) > can do it, but that doesn't seem to be the case here. though don did grant me permission via email, i never heard back from him when i asked him to add me to the maintainers group (i verified by trying to log in to ). should i be able to access that area *before* i upload a copy of liboleg, or only afterwards? i'm cc-ing don to this thread as well. since this will be the first time i'll be maintaining a package on hackage it's possible i'm making some fundamental mistake; if so please do correct me (and excuse my bumbling ways). -- Suhail From roma at ro-che.info Tue Jan 7 13:10:38 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 7 Jan 2014 15:10:38 +0200 Subject: [Haskell-cafe] haddock backends In-Reply-To: <52CB6BDC.1020105@fuuzetsu.co.uk> References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> Message-ID: <20140107131038.GA9521@sniper> * Mateusz Kowalczyk [2014-01-07 02:52:12+0000] > * This touches on frequently overlooked problem: Haddock targets more > than just the HTML back-end. We also have the LaTeX back-end and the > Hoogle back-end. This is why we don't allow things like verbatim > HTML in the markup, it doesn't make sense for anything but HTML. > Admittedly, LaTeX back-end could just generate the maths itself but > we then suddenly have to change the ?verbatim? block to the ?LaTeX? > block. It's also unclear how Hoogle back-end would deal with this. > Even if we add the ?LaTeX structure? to Haddock, I'm afraid that it > might end up with people just writing LaTeX for their documentation > which is useless for anyone not using that back-end. I see no reason why haddock should have a hoogle backend, as opposed to hoogle using the GHC API directly. It's just a hack that exists for historical reasons. Other than that, HTML is the only backend really in use at the moment, I believe. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From malcolm.wallace at me.com Tue Jan 7 13:24:38 2014 From: malcolm.wallace at me.com (malcolm.wallace) Date: Tue, 07 Jan 2014 13:24:38 +0000 (GMT) Subject: [Haskell-cafe] haddock backends In-Reply-To: <20140107131038.GA9521@sniper> Message-ID: <5c04bd3c-ab67-4996-9a7f-d3eb5b32d725@me.com> I believe the LaTeX backend for Haddock is used to generate the libraries part of the Haskell Report. Regards, Malcolm On 07 Jan, 2014,at 01:10 PM, Roman Cheplyaka wrote: * Mateusz Kowalczyk [2014-01-07 02:52:12+0000] * This touches on frequently overlooked problem: Haddock targets more than just the HTML back-end. We also have the LaTeX back-end and the Hoogle back-end. This is why we don't allow things like verbatim HTML in the markup, it doesn't make sense for anything but HTML. Admittedly, LaTeX back-end could just generate the maths itself but we then suddenly have to change the ?verbatim? block to the ?LaTeX? block. It's also unclear how Hoogle back-end would deal with this. Even if we add the ?LaTeX structure? to Haddock, I'm afraid that it might end up with people just writing LaTeX for their documentation which is useless for anyone not using that back-end. I see no reason why haddock should have a hoogle backend, as opposed to hoogle using the GHC API directly. It's just a hack that exists for historical reasons. Other than that, HTML is the only backend really in use at the moment, I believe. Roman _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Tue Jan 7 14:38:48 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 7 Jan 2014 09:38:48 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> Message-ID: On Tue, Jan 7, 2014 at 7:18 AM, Antonio Nikishaev wrote: > Mateusz Kowalczyk writes: > > * You suddenly allow for part of documentation to be rendered by > > someone else, over the Internet. The problem is that documentation > > suddenly becomes worse for everyone browsing without JavaScript or > > browsing locally, without an Internet connection. Embedding images > > avoids both of these problems. > > No. It's rendered in the browser. > For me as a programmer writing documentation, your random browser and its random collection of javascript and css bugs --- or potentially lack of one/both --- is "someone else" that I must potentially deal with. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From vanenkj at gmail.com Tue Jan 7 15:03:21 2014 From: vanenkj at gmail.com (John Van Enk) Date: Tue, 7 Jan 2014 10:03:21 -0500 Subject: [Haskell-cafe] "Segmentation fault/access violation" when working with FFI In-Reply-To: <52C6F132.4060203@fecrd.cujae.edu.cu> References: <52C6F132.4060203@fecrd.cujae.edu.cu> Message-ID: Hi Leza, Unfortunately, this project is really really old and rather broken. I've tried to address it in the last few years a few times, but I've been unable to block out enough time to give portaudio's bindings the love and care they need. I'm truly sorry for the condition of the code. I don't believe the package can be relied upon right now. John Van Enk On Fri, Jan 3, 2014 at 12:19 PM, Leza Morais Lutonda < leza.ml at fecrd.cujae.edu.cu> wrote: > Hi, > > I has trying to use the portaudio [1] package to play some sound, and > running the examples [2] and it results in the "Segmentation fault/access > violation" error. > > Any idea? > > Thanks. > > [1] http://hackage.haskell.org/package/portaudio > [2] https://github.com/sw17ch/portaudio/blob/master/examples/Example1.h > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew.gibiansky at gmail.com Tue Jan 7 15:11:40 2014 From: andrew.gibiansky at gmail.com (Andrew Gibiansky) Date: Tue, 7 Jan 2014 10:11:40 -0500 Subject: [Haskell-cafe] Class Instance with ExistentialQuantification In-Reply-To: <20140107101812.GA8094@sniper> References: <20140107101812.GA8094@sniper> Message-ID: Ah, I see. I wasn't aware that constraints had to be over monotypes. I figured that since you could write a function f :: (forall a. a -> a) -> Bool Then you could also do similar things with a class. (The reason I was doing this was that I wanted a typeclass to match something like "return 'a'" without using IncoherentInstances or other sketchiness, and found that trying to have a typeclass with an instance for 'forall m. Monad m => m Char` gave me this error.) Thanks! Andrew On Tue, Jan 7, 2014 at 5:18 AM, Roman Cheplyaka wrote: > * Andrew Gibiansky [2014-01-06 22:17:21-0500] > > Why is the following not allowed? > > > > {-# LANGUAGE ExistentialQuantification, ExplicitForAll, RankNTypes, > > FlexibleInstances #-} > > > > class Class a where > > test :: a -> Bool > > > > instance Class (forall m. m -> m) where > > test _ = True > > > > main = do > > putStrLn $ test id > > > > Is there a reason that this is forbidden? Just curious. > > I believe the rule is that all constraints (including class constraints) > range over monotypes. > > What are you trying to achieve? > > You can do this, for example: > > newtype Poly = Poly (forall a . a -> a) > instance Class Poly where test = const True > > main = print $ test $ Poly id > > BTW, this has nothing to do with ExistentialQuantification. > > Roman > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Tue Jan 7 15:16:15 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Tue, 07 Jan 2014 15:16:15 +0000 Subject: [Haskell-cafe] Class Instance with ExistentialQuantification In-Reply-To: References: <20140107101812.GA8094@sniper> Message-ID: <1389107775.14997.3.camel@kirk> Hi, is it not allowed simply because none has needed it yet, or is there a deeper theoretical problem with it? I?m asking because the implementation of Coercible behaves as if there is an instance instance forall a. (Coercible (t1 a) (t2 a)) => Coercible (forall a. t1 a) (forall a. t2 a) and if were theoretically dubious, I?d like to know about it :-) Greetings, Joachim Am Dienstag, den 07.01.2014, 10:11 -0500 schrieb Andrew Gibiansky: > Ah, I see. I wasn't aware that constraints had to be over monotypes. I > figured that since you could write a function > > > f :: (forall a. a -> a) -> Bool > > > Then you could also do similar things with a class. > > > (The reason I was doing this was that I wanted a typeclass to match > something like "return 'a'" without using IncoherentInstances or other > sketchiness, and found that trying to have a typeclass with an > instance for 'forall m. Monad m => m Char` gave me this error.) > > > Thanks! > Andrew > > > On Tue, Jan 7, 2014 at 5:18 AM, Roman Cheplyaka > wrote: > * Andrew Gibiansky [2014-01-06 > 22:17:21-0500] > > Why is the following not allowed? > > > > {-# LANGUAGE ExistentialQuantification, ExplicitForAll, > RankNTypes, > > FlexibleInstances #-} > > > > class Class a where > > test :: a -> Bool > > > > instance Class (forall m. m -> m) where > > test _ = True > > > > main = do > > putStrLn $ test id > > > > Is there a reason that this is forbidden? Just curious. > > > I believe the rule is that all constraints (including class > constraints) > range over monotypes. > > What are you trying to achieve? > > You can do this, for example: > > newtype Poly = Poly (forall a . a -> a) > instance Class Poly where test = const True > > main = print $ test $ Poly id > > BTW, this has nothing to do with ExistentialQuantification. > > Roman > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 198 bytes Desc: This is a digitally signed message part URL: From leza.ml at fecrd.cujae.edu.cu Tue Jan 7 19:16:11 2014 From: leza.ml at fecrd.cujae.edu.cu (Leza Morais Lutonda) Date: Tue, 07 Jan 2014 11:16:11 -0800 Subject: [Haskell-cafe] "Segmentation fault/access violation" when working with FFI In-Reply-To: References: <52C6F132.4060203@fecrd.cujae.edu.cu> Message-ID: <52CC527B.8030306@fecrd.cujae.edu.cu> El 1/7/2014 07:03, John Van Enk escribi?: > Hi Leza, > > Unfortunately, this project is really really old and rather broken. > I've tried to address it in the last few years a few times, but I've > been unable to block out enough time to give portaudio's bindings the > love and care they need. > > I'm truly sorry for the condition of the code. I don't believe the > package can be relied upon right now. > > John Van Enk > Fortunately I could solve the problem (unfortunately without knowing exactly what was causing it). I guess there is a bug in Sound.PortAudio module that causes the problem. What I did is to work directly with the bindings functions to the C Api in module Sound.PortAudio.Base and make my own `play` function. Maybe someday I can contribute to the package since I am very interested in easily playing sound with haskell. Thanks. -- Leza Morais Lutonda https://github.com/lemol From nathan.d.howell at gmail.com Tue Jan 7 16:54:33 2014 From: nathan.d.howell at gmail.com (Nathan Howell) Date: Tue, 7 Jan 2014 08:54:33 -0800 Subject: [Haskell-cafe] Associated types, kind constraints & typelits In-Reply-To: References: <1389028015.21320.4.camel@tau.nicolast.be> Message-ID: natVal accepts any type witness now, not just sing. One such type in base is the polykinded Data.Proxy.Proxy, e.g. `natVal (Proxy :: Proxy 0`. For types of kind * you can use almost anything, including an empty list. On Mon, Jan 6, 2014 at 9:27 AM, Erik Hesselink wrote: > Small additions: the 'Nat' in the original argument is the kind > argument to the class. It seems to be a bug that GHC provided this in > the error, and the latest HEAD doesn't seem to do so anymore. Also, in > the latest HEAD, I think you need to use the singletons library, as > all the singletons stuff is gone from base. My working code: > > {-# LANGUAGE TypeFamilies > , DataKinds > , FlexibleContexts > , ScopedTypeVariables > #-} > module Main where > > import GHC.TypeLits > import Data.Singletons > > class C a where > type T a :: Nat > > data D = D > instance C D where > type T D = 10 > > {- This is not allowed, as intended: > > data E = E > instance C E where > type T E = Int > -} > > -- This works: > tOfD :: D -> Integer > tOfD D = fromSing $ (sing :: Sing (T D)) > > tOf :: forall a. (KnownNat (T a), C a) => a -> Integer > tOf _ = fromSing $ (sing :: Sing (T a)) > > main :: IO () > main = return () > > Erik > > On Mon, Jan 6, 2014 at 6:15 PM, Nathan Howell > wrote: > > This requires -XScopedTypeVariables and some constraints: > > > > tOf :: forall a . (SingI (T a), C a) => a -> Integer > > tOf _ = fromSing $ (sing :: Sing (T a)) > > > > > > On Mon, Jan 6, 2014 at 9:06 AM, Nicolas Trangez > > wrote: > >> > >> All, > >> > >> While toying with typelits I wanted to get the following to work, but > >> failed to. Is it intended not to work at all, should I change something > >> to get it to work, or is this something which needs some GHC support? > >> > >> Note I obviously tried to add the constraint mentioned in the compiler > >> error, but failed to: I seem to add too many type arguments to SingI, > >> which somewhat puzzles me. > >> > >> Thanks, > >> > >> Nicolas > >> > >> {-# LANGUAGE TypeFamilies, > >> DataKinds #-} > >> module Main where > >> > >> import GHC.TypeLits > >> > >> class C a where > >> type T a :: Nat > >> > >> data D = D > >> instance C D where > >> type T D = 10 > >> > >> {- This is not allowed, as intended: > >> > >> data E = E > >> instance C E where > >> type T E = Int > >> -} > >> > >> -- This works: > >> tOfD :: D -> Integer > >> tOfD D = fromSing $ (sing :: Sing (T D)) > >> > >> {- This doesn't work: > >> - Could not deduce (SingI Nat (T a1)) arising from a use of `sing' > >> - from the context (C a) > >> > >> tOf :: C a => a -> Integer > >> tOf _ = fromSing $ (sing :: Sing (T a)) > >> -} > >> > >> main :: IO () > >> main = return () > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jgm at berkeley.edu Tue Jan 7 18:18:29 2014 From: jgm at berkeley.edu (John MacFarlane) Date: Tue, 7 Jan 2014 10:18:29 -0800 Subject: [Haskell-cafe] ANN: cheapskate 0.1, markdown parser In-Reply-To: References: <20140106191553.GA49308@Johns-MacBook-Air-2.local> Message-ID: <20140107181829.GC70235@Johns-MacBook-Air-2.local> +++ Justin Bailey [Jan 06 14 13:07 ]: > Looks like an excellent library! How did you manage to maintain linear > growth in running time? Seems like quite an achievement. I tried very hard to avoid any backtracking. Parsing occurs in two phases. In the first phase, we process each line of the input in turn (this could even be done with streaming input; we never need to "rewind"). Each line transforms a "container stack," which container stack represents the nested containers, e.g. list items or blockquotes, that are open at that point in the document. Depending on the contents of the line, we might add new containers to the stack and/or close some of the open containers, adding them as children to the elements below them. The end of the line, after the bits that indicate container structure, will generally be added as a leaf element (text line or blank line) to the top container. I had to make a couple small changes in markdown syntax to make this line-by-line strategy feasible. If an opening code fence isn't matched by a closing code fence, the whole remainder of the document gets parsed as code. (Otherwise we'd have to backtrack an indefinite number of lines.) There is a also a change in how raw HTML works (documented in the README). A raw HTML block begins with an opening block HTML tag, and ends, not with a matching closing tag, but with the next blank line. An advantage of this system is that we can easily include markdown content in HTML tags (just surround it with blank lines), yet we can still have literal HTML blocks (just make sure they don't contain blanks). So I think this is superior to Gruber's original specification for raw HTML blocks, not just from a parsing point of view but from an expressive point of view. After we've read all the input, we close the container stack. We now have a Document element that represents the container structure and the text lines under each container. We also have a reference map with the link references. You can inspect this structure using 'cheapskate --debug'; here's an example: (Document ListItem {markerColumn = 1, padding = 3, listType = Numbered PeriodFollowing 1} "Foo" ListItem {markerColumn = 3, padding = 2, listType = Bullet '-'} "bar" BlankLine "" "baz" BlankLine "" ListItem {markerColumn = 1, padding = 3, listType = Numbered PeriodFollowing 2} "Bim",fromList []) In the second phase, we walk this container structure and produce a proper AST. This involves assembling list items into lists and assembling lists of text lines into paragraphs, parsing their contents as markdown inline elements, using the reference map to resolve reference links. Inline parsing uses parser combinators. I avoid backtracking by using fallbacks. For example, if we start parsing an emphasized section beginning with '*' and don't find the closing '*', we don't backtrack; instead, we just emit a '*' and the content we've parsed so far. I'd love to make the library faster. It is the fastest pure Haskell implementation I'm aware of, but C libraries like discount are still quite a bit faster. (Note: often they skimp on proper unicode support, which accounts for some of this.) Profiling does not show me any particular bottleneck, but I'd welcome suggestions. John > On Mon, Jan 6, 2014 at 11:15 AM, John MacFarlane wrote: > > I've released a new markdown library on Hackage: > > http://hackage.haskell.org/package/cheapskate > > > > This library is designed to be used in web applications. It is small, > > accurate, and fast, in pure Haskell with few dependencies. All output > > is sanitized through a whitelist by default. It is designed to have > > performance that varies linearly with the input size, even with garbage > > input. To illustrate: > > > > % head -c 100000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > > cheapskate > /dev/null 0.15s user 0.01s system 82% cpu 0.199 total > > % head -c 1000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > > cheapskate > /dev/null 1.53s user 0.03s system 88% cpu 1.770 total > > % head -c 10000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > > cheapskate > /dev/null 15.50s user 0.20s system 89% cpu 17.632 total > > > > This is a test that many markdown parsers fail (including my own pandoc > > and the markdown package on Hackage). > > > > Performance is about seven times faster than pandoc (with five times > > less memory used), and about 25% faster than the markdown package on Hackage. > > > > Generic functions are provided that allow transformations of the AST > > prior to rendering (e.g., promotion of headers, insertion of syntax > > highlighting, or the conversion of specially marked code blocks into > > diagrams). > > > > Several markdown extensions are supported, and sensible decisions have > > been made about several aspects of markdown syntax that are left vague > > by John Gruber's specification. For details, see the README > > at https://github.com/jgm/cheapskate. > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From fuuzetsu at fuuzetsu.co.uk Tue Jan 7 18:23:54 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 07 Jan 2014 18:23:54 +0000 Subject: [Haskell-cafe] haddock backends In-Reply-To: <20140107131038.GA9521@sniper> References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> <20140107131038.GA9521@sniper> Message-ID: <52CC463A.3040502@fuuzetsu.co.uk> On 07/01/14 13:10, Roman Cheplyaka wrote: > * Mateusz Kowalczyk [2014-01-07 02:52:12+0000] >> * This touches on frequently overlooked problem: Haddock targets more >> than just the HTML back-end. We also have the LaTeX back-end and the >> Hoogle back-end. This is why we don't allow things like verbatim >> HTML in the markup, it doesn't make sense for anything but HTML. >> Admittedly, LaTeX back-end could just generate the maths itself but >> we then suddenly have to change the ?verbatim? block to the ?LaTeX? >> block. It's also unclear how Hoogle back-end would deal with this. >> Even if we add the ?LaTeX structure? to Haddock, I'm afraid that it >> might end up with people just writing LaTeX for their documentation >> which is useless for anyone not using that back-end. > > I see no reason why haddock should have a hoogle backend, as opposed to > hoogle using the GHC API directly. It's just a hack that exists for > historical reasons. I also don't see why it's there but I don't think we can just remove it. There are bugs reported against it which means that it's being used. It is quite broken. I think a separate application to generate the .hoo files would effectively be replicating Haddock. > Other than that, HTML is the only backend really in use at the moment, > I believe. I have also thought this until we started considering removal of the LaTeX back-end. It turns out that there are people who do use it. In any case, I'm open to the back-end changes/removal/addition discussions but I think it should be done in a separate thread. > > Roman > -- Mateusz K. From fuuzetsu at fuuzetsu.co.uk Tue Jan 7 18:35:47 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 07 Jan 2014 18:35:47 +0000 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> Message-ID: <52CC4903.4020003@fuuzetsu.co.uk> On 07/01/14 12:18, Antonio Nikishaev wrote: > Mateusz Kowalczyk writes: > >> On 07/01/14 01:42, Carter Schonwald wrote: >>> I would really love to use MathJax in the haddock HTML backend. Is there >>> any way (however hacky) that I could do that? >> >> I looked up how MathJax is used and as far as I can tell, it's just >> the case of putting the MathJax JavaScript header into the file, >> right? We already use JavaScript on the Haddock-generated HTML pages, >> for example the synopsis box. >> >> While I prefer JavaScript-free web I think that for viewing on >> Hackage, it'd be possible to just stick the header into the generated >> files and be done with it. Here are some caveats: >> >> * You suddenly allow for part of documentation to be rendered by >> someone else, over the Internet. The problem is that documentation >> suddenly becomes worse for everyone browsing without JavaScript or >> browsing locally, without an Internet connection. Embedding images >> avoids both of these problems. > > No. It's rendered in the browser. > It still requires an Internet connection, does it not? Many people prefer to browse without JavaScript anyway (myself included) and if the documentation suddenly requires JavaScript to view properly, this is a problem. -- Mateusz K. From branimir.maksimovic at gmail.com Tue Jan 7 18:55:54 2014 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Tue, 07 Jan 2014 19:55:54 +0100 Subject: [Haskell-cafe] Slow mvar when compiled with threaded Message-ID: <52CC4DBA.2050907@gmail.com> I have test network client, something like apache bench tool. It uses mvars to synchronize and everything is ok when compiled without -threaded. real 0m2.995s user 0m0.601s sys 0m2.391s With -threaded compile option result is following: real 0m18.196s user 0m2.054s sys 0m3.313s Seems that program is sleeping most of the time for some reason. I can't explain behavior as it seems that program is ok. It starts `concurrency` threads which wait on mvar to process next task. Program follows: {-# Language OverloadedStrings #-} import System.CPUTime import System.IO --import System.IO.Error import Network.Socket hiding(recv) import Network.Socket.ByteString import System.Environment import Control.Concurrent import Control.Exception main = do n <- getArgs let (host,port,conc,reqs) = parse n putStrLn $ "Connecting to " ++ host ++ " " ++ port s <- getAddrInfo Nothing (Just host) (Just port) let servAddr = head s begin <- getCPUTime process servAddr conc reqs end <- getCPUTime let diff = (fromIntegral (end - begin))/(10^12) :: Double putStrLn $ show (round (fromIntegral reqs / diff)) ++ " r/s" parse [h,p,conc,reqs] = (h,p,read conc::Int,read reqs::Int) parse _ = error "usage client host port concurrency requests" process servAddr conc reqs = do let niter = if reqs >= conc then conc else reqs putStrLn $ "loop " ++ show niter mvars <- initThreads niter [] putStrLn $ "Initialized " ++ show niter let loop n (m:mvs) f | n>0 = do flag <- isEmptyMVar m if f > length mvars then putStrLn "busy" else return () if flag || f > length mvars then do putMVar m () loop (n-1) mvs 0 else loop n mvs (f+1) | otherwise = return () loop n [] f = if n>0 then loop n mvars f else return () putStrLn $ "length " ++ show (length mvars) loop (reqs-niter) mvars 0 where initThreads niter vars | niter > 0 = do mvar <- newMVar () forkIO $ process mvar initThreads (niter-1) (mvar:vars) | otherwise = return vars process mvar = do sock <- socket (addrFamily servAddr) Stream defaultProtocol connect sock (addrAddress servAddr) sendAll sock "Hello World!\n" buf <- recv sock 1024 close sock takeMVar mvar process mvar From carter.schonwald at gmail.com Tue Jan 7 19:08:38 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 7 Jan 2014 14:08:38 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: <52CC4903.4020003@fuuzetsu.co.uk> References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> <52CC4903.4020003@fuuzetsu.co.uk> Message-ID: In the case of MathJax, the fall back is you just get some inline latex. On Tuesday, January 7, 2014, Mateusz Kowalczyk wrote: > On 07/01/14 12:18, Antonio Nikishaev wrote: > > Mateusz Kowalczyk > writes: > > > >> On 07/01/14 01:42, Carter Schonwald wrote: > >>> I would really love to use MathJax in the haddock HTML backend. Is > there > >>> any way (however hacky) that I could do that? > >> > >> I looked up how MathJax is used and as far as I can tell, it's just > >> the case of putting the MathJax JavaScript header into the file, > >> right? We already use JavaScript on the Haddock-generated HTML pages, > >> for example the synopsis box. > >> > >> While I prefer JavaScript-free web I think that for viewing on > >> Hackage, it'd be possible to just stick the header into the generated > >> files and be done with it. Here are some caveats: > >> > >> * You suddenly allow for part of documentation to be rendered by > >> someone else, over the Internet. The problem is that documentation > >> suddenly becomes worse for everyone browsing without JavaScript or > >> browsing locally, without an Internet connection. Embedding images > >> avoids both of these problems. > > > > No. It's rendered in the browser. > > > > It still requires an Internet connection, does it not? Many people > prefer to browse without JavaScript anyway (myself included) and if the > documentation suddenly requires JavaScript to view properly, this is a > problem. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Tue Jan 7 19:34:36 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Tue, 7 Jan 2014 20:34:36 +0100 Subject: [Haskell-cafe] relocation R_X86_64_PC32 against undefined symbol? In-Reply-To: <20140106221739.GA4145@mteis.lan> References: <20140105120045.GC1366@mteis.lan> <20140105122130.GA16826@machine> <20140105124456.GE1366@mteis.lan> <20140105133607.GA25194@machine> <20140106221739.GA4145@mteis.lan> Message-ID: <20140107193436.GB31458@machine> On Mon, Jan 06, 2014 at 11:17:39PM +0100, Magnus Therning wrote: > Still no luck :( Perhaps 'hsimport 0.2.6.5' now finally solves the issue. Greetings, Daniel From bob at redivi.com Tue Jan 7 20:39:40 2014 From: bob at redivi.com (Bob Ippolito) Date: Tue, 7 Jan 2014 12:39:40 -0800 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: <52CC4DBA.2050907@gmail.com> References: <52CC4DBA.2050907@gmail.com> Message-ID: Here's a much simpler implementation for that sort of pattern, using channels to fan out work to threads. I added a dependency on Criterion because getCPUTime is basically useless for this kind of measurement on Mac OS X since it doesn't include the time that the process spent waiting on IO: {-# Language OverloadedStrings #-} import System.CPUTime import Network.Socket hiding(recv) import Network.Socket.ByteString import Control.Exception (handle, IOException) import System.Environment import Control.Concurrent import Control.Monad import Data.Either (partitionEithers) import Data.List (intercalate) import Criterion.Measurement (time, time_, secs) main :: IO () main = do (host, port, conc, reqs) <- fmap parse getArgs putStrLn $ "Connecting to " ++ host ++ " " ++ port (servAddr:_) <- getAddrInfo Nothing (Just host) (Just port) (diff, results) <- time $ process servAddr conc reqs let (errs, succs) = partitionEithers results numSuccs = length succs numErrs = length errs succTime = sum succs succAvg = succTime / fromIntegral numSuccs putStrLn $ unwords [show numSuccs, "successes,", show numErrs, "errors in", secs diff] when (numSuccs > 0) $ do putStrLn $ "min/max/avg request time: " ++ intercalate " / " (map secs [minimum succs, maximum succs, succAvg]) putStrLn $ show (round (fromIntegral reqs / diff) :: Int) ++ " r/s" parse :: [String] -> (String, String, Int, Int) parse [h,p,conc,reqs] = (h, p, read conc, read reqs) parse _ = error "usage client host port concurrency requests" process :: AddrInfo -> Int -> Int -> IO [Either IOException Double] process servAddr conc reqs = do reqChan <- newChan ackChan <- newChan let processThread = forever $ do _ <- readChan reqChan handle (return . Left) (fmap Right socketAction) >>= writeChan ackChan socketAction = time_ $ do sock <- socket (addrFamily servAddr) Stream defaultProtocol connect sock (addrAddress servAddr) sendAll sock "GET /\r\n\r\n" void $ recv sock 1024 close sock replicateM_ reqs (writeChan reqChan ()) replicateM_ (min conc reqs) (forkIO processThread) replicateM reqs (readChan ackChan) On Tue, Jan 7, 2014 at 10:55 AM, Branimir Maksimovic < branimir.maksimovic at gmail.com> wrote: > I have test network client, something like apache bench tool. > It uses mvars to synchronize and everything is ok when > compiled without -threaded. > real 0m2.995s > user 0m0.601s > sys 0m2.391s > > With -threaded compile option result is following: > real 0m18.196s > user 0m2.054s > sys 0m3.313s > > Seems that program is sleeping most of the time for some > reason. I can't explain behavior as it seems that > program is ok. It starts `concurrency` threads which > wait on mvar to process next task. > > Program follows: > > {-# Language OverloadedStrings #-} > import System.CPUTime > import System.IO > --import System.IO.Error > import Network.Socket hiding(recv) > import Network.Socket.ByteString > import System.Environment > import Control.Concurrent > import Control.Exception > > main = do > n <- getArgs > let (host,port,conc,reqs) = parse n > putStrLn $ "Connecting to " ++ host ++ " " ++ port > s <- getAddrInfo Nothing (Just host) (Just port) > let servAddr = head s > begin <- getCPUTime > process servAddr conc reqs > end <- getCPUTime > let diff = (fromIntegral (end - begin))/(10^12) :: Double > putStrLn $ show (round (fromIntegral reqs / diff)) ++ " r/s" > > parse [h,p,conc,reqs] = (h,p,read conc::Int,read reqs::Int) > parse _ = error "usage client host port concurrency requests" > > process servAddr conc reqs = do > let niter = if reqs >= conc then conc else reqs > putStrLn $ "loop " ++ show niter > mvars <- initThreads niter [] > putStrLn $ "Initialized " ++ show niter > let loop n (m:mvs) f | n>0 = do > flag <- isEmptyMVar m > if f > length mvars then putStrLn "busy" else return () > if flag || f > length mvars > then do > putMVar m () > loop (n-1) mvs 0 > else loop n mvs (f+1) > | otherwise = return () > loop n [] f = if n>0 then loop n mvars f else return () > putStrLn $ "length " ++ show (length mvars) > loop (reqs-niter) mvars 0 > where > initThreads niter vars | niter > 0 = do > mvar <- newMVar () > forkIO $ process mvar > initThreads (niter-1) (mvar:vars) > | otherwise = return vars > process mvar = do > sock <- socket (addrFamily servAddr) Stream defaultProtocol > connect sock (addrAddress servAddr) > sendAll sock "Hello World!\n" > buf <- recv sock 1024 > close sock > takeMVar mvar > process mvar > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tomberek at gmail.com Tue Jan 7 20:54:17 2014 From: tomberek at gmail.com (Thomas Bereknyei) Date: Tue, 7 Jan 2014 15:54:17 -0500 Subject: [Haskell-cafe] happstack-fastcgi maintenance Message-ID: I've patched happstack-fastcgi to work with the latest versions of ghc and happstack. The maintainers have expressed that they consider it unmaintained. I would like to gauge the interest in the library and perhaps maintain it. Let me know if this is of interest to anyone. Have you used it in the past? What features would you need added? Any changes? -Tom From jeremy at n-heptane.com Tue Jan 7 21:11:58 2014 From: jeremy at n-heptane.com (Jeremy Shaw) Date: Tue, 7 Jan 2014 15:11:58 -0600 Subject: [Haskell-cafe] happstack-fastcgi maintenance In-Reply-To: References: Message-ID: I, for one, would love to see happstack-fastcgi maintained. I'd kind of like to see a straight up cgi interface maintained as well. :) - jeremy On Tue, Jan 7, 2014 at 2:54 PM, Thomas Bereknyei wrote: > I've patched happstack-fastcgi to work with the latest versions of ghc > and happstack. The maintainers have expressed that they consider it > unmaintained. I would like to gauge the interest in the library and > perhaps maintain it. Let me know if this is of interest to anyone. > Have you used it in the past? What features would you need added? Any > changes? > > -Tom > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From nikita at karetnikov.org Tue Jan 7 21:38:33 2014 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Wed, 08 Jan 2014 01:38:33 +0400 Subject: [Haskell-cafe] Drop or update the upper bounds of numerals and numerals-base Message-ID: <87a9f7cw12.fsf@karetnikov.org> I?ve built both packages locally, and they seem to work fine with GHC 7.6.3. However, I can?t install them from Hackage due to the required dependencies. Could anyone drop or update the upper bounds? Alternatively, I could try to do so myself if someone provides the required permissions. -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 835 bytes Desc: not available URL: From roma at ro-che.info Tue Jan 7 22:33:07 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 8 Jan 2014 00:33:07 +0200 Subject: [Haskell-cafe] Class Instance with ExistentialQuantification In-Reply-To: <1389107775.14997.3.camel@kirk> References: <20140107101812.GA8094@sniper> <1389107775.14997.3.camel@kirk> Message-ID: <20140107223307.GA11962@sniper> * Joachim Breitner [2014-01-07 15:16:15+0000] > Hi, > > is it not allowed simply because none has needed it yet, or is there a > deeper theoretical problem with it? FWIW, here's Simon's answer on a similar topic: http://osdir.com/ml/glasgow-haskell-users at haskell.org/2013-03/msg00048.html > I?m asking because the implementation of Coercible behaves as if there > is an instance > instance forall a. (Coercible (t1 a) (t2 a)) => Coercible (forall a. t1 a) (forall a. t2 a) > and if were theoretically dubious, I?d like to know about it :-) > > Greetings, > Joachim > > Am Dienstag, den 07.01.2014, 10:11 -0500 schrieb Andrew Gibiansky: > > Ah, I see. I wasn't aware that constraints had to be over monotypes. I > > figured that since you could write a function > > > > > > f :: (forall a. a -> a) -> Bool > > > > > > Then you could also do similar things with a class. > > > > > > (The reason I was doing this was that I wanted a typeclass to match > > something like "return 'a'" without using IncoherentInstances or other > > sketchiness, and found that trying to have a typeclass with an > > instance for 'forall m. Monad m => m Char` gave me this error.) > > > > > > Thanks! > > Andrew > > > > > > On Tue, Jan 7, 2014 at 5:18 AM, Roman Cheplyaka > > wrote: > > * Andrew Gibiansky [2014-01-06 > > 22:17:21-0500] > > > Why is the following not allowed? > > > > > > {-# LANGUAGE ExistentialQuantification, ExplicitForAll, > > RankNTypes, > > > FlexibleInstances #-} > > > > > > class Class a where > > > test :: a -> Bool > > > > > > instance Class (forall m. m -> m) where > > > test _ = True > > > > > > main = do > > > putStrLn $ test id > > > > > > Is there a reason that this is forbidden? Just curious. > > > > > > I believe the rule is that all constraints (including class > > constraints) > > range over monotypes. > > > > What are you trying to achieve? > > > > You can do this, for example: > > > > newtype Poly = Poly (forall a . a -> a) > > instance Class Poly where test = const True > > > > main = print $ test $ Poly id > > > > BTW, this has nothing to do with ExistentialQuantification. > > > > Roman > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? http://www.joachim-breitner.de/ > Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C > Debian Developer: nomeata at debian.org > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From roma at ro-che.info Tue Jan 7 22:41:33 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 8 Jan 2014 00:41:33 +0200 Subject: [Haskell-cafe] haddock backends In-Reply-To: <5c04bd3c-ab67-4996-9a7f-d3eb5b32d725@me.com> References: <20140107131038.GA9521@sniper> <5c04bd3c-ab67-4996-9a7f-d3eb5b32d725@me.com> Message-ID: <20140107224133.GB11962@sniper> Interesting, I didn't know that. So the libraries part of the Haskell Report simply documents the status quo? * malcolm.wallace [2014-01-07 13:24:38+0000] > I believe the LaTeX backend for Haddock is used to generate the libraries part of the Haskell Report. > Regards, > Malcolm > > On 07 Jan, 2014,at 01:10 PM, Roman Cheplyaka wrote: > > * Mateusz Kowalczyk [2014-01-07 02:52:12+0000] > * This touches on frequently overlooked problem: Haddock targets more > than just the HTML back-end. We also have the LaTeX back-end and the > Hoogle back-end. This is why we don't allow things like verbatim > HTML in the markup, it doesn't make sense for anything but HTML. > Admittedly, LaTeX back-end could just generate the maths itself but > we then suddenly have to change the ?verbatim? block to the ?LaTeX? > block. It's also unclear how Hoogle back-end would deal with this. > Even if we add the ?LaTeX structure? to Haddock, I'm afraid that it > might end up with people just writing LaTeX for their documentation > which is useless for anyone not using that back-end. > > I see no reason why haddock should have a hoogle backend, as opposed to > hoogle using the GHC API directly. It's just a hack that exists for > historical reasons. > > Other than that, HTML is the only backend really in use at the moment, > I believe. > > Roman > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From roma at ro-che.info Tue Jan 7 22:44:54 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 8 Jan 2014 00:44:54 +0200 Subject: [Haskell-cafe] Drop or update the upper bounds of numerals and numerals-base In-Reply-To: <87a9f7cw12.fsf@karetnikov.org> References: <87a9f7cw12.fsf@karetnikov.org> Message-ID: <20140107224454.GC11962@sniper> * Nikita Karetnikov [2014-01-08 01:38:33+0400] > I?ve built both packages locally, and they seem to work fine with GHC > 7.6.3. However, I can?t install them from Hackage due to the required > dependencies. > > Could anyone drop or update the upper bounds? Alternatively, I could > try to do so myself if someone provides the required permissions. The page http://hackage.haskell.org/package/numerals lists the issue tracker and maintainer's email. Have you tried those? Also, as a quick workaround, Cabal's master branch has the option '--allow-newer'. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From allbery.b at gmail.com Tue Jan 7 22:52:27 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 7 Jan 2014 17:52:27 -0500 Subject: [Haskell-cafe] Drop or update the upper bounds of numerals and numerals-base In-Reply-To: <87a9f7cw12.fsf@karetnikov.org> References: <87a9f7cw12.fsf@karetnikov.org> Message-ID: On Tue, Jan 7, 2014 at 4:38 PM, Nikita Karetnikov wrote: > drop (...) the upper bounds Sigh. The community really does like the versioning equivalent of unsafePerformIO, doesn't it? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Tue Jan 7 23:49:35 2014 From: jwlato at gmail.com (John Lato) Date: Tue, 7 Jan 2014 15:49:35 -0800 Subject: [Haskell-cafe] Drop or update the upper bounds of numerals and numerals-base In-Reply-To: References: <87a9f7cw12.fsf@karetnikov.org> Message-ID: On Tue, Jan 7, 2014 at 2:52 PM, Brandon Allbery wrote: > On Tue, Jan 7, 2014 at 4:38 PM, Nikita Karetnikov wrote: > >> drop (...) the upper bounds > > > Sigh. The community really does like the versioning equivalent of > unsafePerformIO, doesn't it? > Yes, it's extremely popular. I think it's a combination of no way to express soft/hard upper bounds and not enough people having been bitten by broken bound issues before the PVP. -------------- next part -------------- An HTML attachment was scrubbed... URL: From brandon.m.simmons at gmail.com Wed Jan 8 01:19:14 2014 From: brandon.m.simmons at gmail.com (Brandon Simmons) Date: Tue, 7 Jan 2014 20:19:14 -0500 Subject: [Haskell-cafe] Right approach to profiling and optimizing a concurrent data structure? Message-ID: Happy New Year, all, I started what I thought would be a pretty straightforward project to implement a concurrent queue (with semantics like Chan) which I hoped would be faster, but the process of trying to measure and test performance has been super frustrating. I started with a really big criterion benchmark suite that ran through a bunch of Chan-like implementations as well as comparing different var primitives; I was compiling that with `-O2 -threaded` and running with +RTS -N (as that seemed realistic, and results were very consistent). Short version: at some point I realized I had (in my cabal config) enabled executable-profiling, which when disabled completely changed all timing and actually *hurt* performance. Then after a lot more head-banging I realized that +RTS -N seems to run on only one core when compiled with -prof (I didn't see that documented anywhere) although I could *force* the -prof version to use more with -N2, and so apparently for my tests[1], running on a single core just *happened* to be faster (I can see why it might; I probably can't expect a speedup when I'm just measuring throughput). I'd be interested in any comments on above, but mostly I'm trying to understand what my approach should be at this point; should I be benchmarking on 1 core and trying to maximize throughput? Should I also profile on just 1 core? How should I benchmark the effects of lots of contention and interpret the results? How can I avoid benchmarking arbitrary decisions of the thread scheduler, while still having my benchmarks be realistic? Are there any RTS flags or compile-time settings that I should *definitely* have on? Thanks for any clarity on this, Brandon http://brandon.si [1] Here's the test I used while most of the forehead-bloodying occurred, here using `Control.Concurrent.Chan`; for no combination of readers/writers/messages could I manage to get this going as fast on 2 cores as on the single-core bound -prof version runC :: Int -> Int -> Int -> IO () runC writers readers n = do let nNice = n - rem n (lcm writers readers) perReader = nNice `quot` readers perWriter = (nNice `quot` writers) vs <- replicateM readers newEmptyMVar c <- C.newChan let doRead = replicateM_ perReader $ theRead theRead = C.readChan c doWrite = replicateM_ perWriter $ theWrite theWrite = C.writeChan c (1 :: Int) mapM_ (\v-> forkIO (doRead >> putMVar v ())) vs replicateM writers $ forkIO $ doWrite mapM_ takeMVar vs -- await readers -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Wed Jan 8 01:45:47 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Wed, 8 Jan 2014 05:45:47 +0400 Subject: [Haskell-cafe] ANN: cheapskate 0.1, markdown parser In-Reply-To: <20140106191553.GA49308@Johns-MacBook-Air-2.local> References: <20140106191553.GA49308@Johns-MacBook-Air-2.local> Message-ID: Cool! By the way, I've noticed that you've rolled your own parser combinator library. May I ask you, what is the reason for that? Are other parser libraries not fast enough for the needs? Thanks On Mon, Jan 6, 2014 at 11:15 PM, John MacFarlane wrote: > I've released a new markdown library on Hackage: > http://hackage.haskell.org/package/cheapskate > > This library is designed to be used in web applications. It is small, > accurate, and fast, in pure Haskell with few dependencies. All output > is sanitized through a whitelist by default. It is designed to have > performance that varies linearly with the input size, even with garbage > input. To illustrate: > > % head -c 100000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > cheapskate > /dev/null 0.15s user 0.01s system 82% cpu 0.199 total > % head -c 1000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > cheapskate > /dev/null 1.53s user 0.03s system 88% cpu 1.770 total > % head -c 10000000 /dev/urandom | iconv -f latin1 -t utf-8 | time cheapskate >/dev/null > cheapskate > /dev/null 15.50s user 0.20s system 89% cpu 17.632 total > > This is a test that many markdown parsers fail (including my own pandoc > and the markdown package on Hackage). > > Performance is about seven times faster than pandoc (with five times > less memory used), and about 25% faster than the markdown package on Hackage. > > Generic functions are provided that allow transformations of the AST > prior to rendering (e.g., promotion of headers, insertion of syntax > highlighting, or the conversion of specially marked code blocks into > diagrams). > > Several markdown extensions are supported, and sensible decisions have > been made about several aspects of markdown syntax that are left vague > by John Gruber's specification. For details, see the README > at https://github.com/jgm/cheapskate. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sincerely yours, -- Daniil From jwlato at gmail.com Wed Jan 8 01:49:52 2014 From: jwlato at gmail.com (John Lato) Date: Tue, 7 Jan 2014 17:49:52 -0800 Subject: [Haskell-cafe] Right approach to profiling and optimizing a concurrent data structure? In-Reply-To: References: Message-ID: First, be aware of https://ghc.haskell.org/trac/ghc/ticket/8453, which causes programs compiled with -threaded and -prof to occasionally die with an assertion failure (there are a few other, possibly related, tickets about rts problems with -threaded and non-vanilla ways). Next, define what you mean by "faster": more throughput? Lower latency? Something else? One approach is to build with profiling and try to optimize the functions exposed by your API. You could do this on one core. The optimizations you'd get from this would be generally useful, but they wouldn't be optimizations to reduce contention. To look into contention issues, I think the best way is to build with the eventlog enabled and use threadscope. This will show pretty clearly where threads are blocked, for how long, etc. I've also had success with timing actions within my test executable and adding that information to the eventlog with Debug.Trace.traceEventIO. Then you can see that information within threadscope, or grep it out of the eventlog for extra processing (min/max/mean, that sort of thing). Running with -N1 can be faster because there essentially is no contention: only a single Haskell thread will be executing at any given time. If -N1 is markedly faster than -N2 (as in, the runtime is longer to complete the same amount of work), I would try debugging with Threadscope first. One example of a test driver I used is https://github.com/JohnLato/kickchan/blob/master/bench/bench_t3.hs . (KickChan is similar to a bounded Chan, but heavily biased towards fast writes) I'd appreciate any further suggestions also. John L. On Tue, Jan 7, 2014 at 5:19 PM, Brandon Simmons wrote: > Happy New Year, all, > > I started what I thought would be a pretty straightforward project to > implement a concurrent queue (with semantics like Chan) which I hoped would > be faster, but the process of trying to measure and test performance has > been super frustrating. > > I started with a really big criterion benchmark suite that ran through a > bunch of Chan-like implementations as well as comparing different var > primitives; I was compiling that with `-O2 -threaded` and running with > +RTS -N (as that seemed realistic, and results were very consistent). > > Short version: at some point I realized I had (in my cabal config) enabled > executable-profiling, which when disabled completely changed all timing and > actually *hurt* performance. Then after a lot more head-banging I realized > that +RTS -N seems to run on only one core when compiled with -prof (I > didn't see that documented anywhere) although I could *force* the -prof > version to use more with -N2, and so apparently for my tests[1], running on > a single core just *happened* to be faster (I can see why it might; I > probably can't expect a speedup when I'm just measuring throughput). > > I'd be interested in any comments on above, but mostly I'm trying to > understand what my approach should be at this point; should I be > benchmarking on 1 core and trying to maximize throughput? Should I also > profile on just 1 core? How should I benchmark the effects of lots of > contention and interpret the results? How can I avoid benchmarking > arbitrary decisions of the thread scheduler, while still having my > benchmarks be realistic? Are there any RTS flags or compile-time settings > that I should *definitely* have on? > > Thanks for any clarity on this, > Brandon > http://brandon.si > > > [1] Here's the test I used while most of the forehead-bloodying occurred, > here using `Control.Concurrent.Chan`; for no combination of > readers/writers/messages could I manage to get this going as fast on 2 > cores as on the single-core bound -prof version > > runC :: Int -> Int -> Int -> IO () > runC writers readers n = do > let nNice = n - rem n (lcm writers readers) > perReader = nNice `quot` readers > perWriter = (nNice `quot` writers) > vs <- replicateM readers newEmptyMVar > c <- C.newChan > let doRead = replicateM_ perReader $ theRead > theRead = C.readChan c > doWrite = replicateM_ perWriter $ theWrite > theWrite = C.writeChan c (1 :: Int) > mapM_ (\v-> forkIO (doRead >> putMVar v ())) vs > replicateM writers $ forkIO $ doWrite > mapM_ takeMVar vs -- await readers > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From icfp.publicity at googlemail.com Wed Jan 8 01:48:10 2014 From: icfp.publicity at googlemail.com (David Van Horn) Date: Tue, 7 Jan 2014 20:48:10 -0500 Subject: [Haskell-cafe] ICFP 2014: Call for papers Message-ID: ===================================================================== 19th ACM SIGPLAN International Conference on Functional Programming ICFP 2014 Gothenburg, Sweden, 1-3 September 2014 http://www.icfpconference.org/icfp2014 ===================================================================== Important Dates ~~~~~~~~~~~~~~~ Submissions due: Saturday, 1 March 2014, 23:59 UTC-11 (anywhere in the world) Author response: Wednesday, 23 April, 2014 Friday, 25 April, 2014 Notification: Monday, 5 May, 2014 Final copy due: Wednesday, 11 June, 2014 Scope ~~~~~ ICFP 2014 seeks original papers on the art and science of functional programming. Submissions are invited on all topics from principles to practice, from foundations to features, and from abstraction to application. The scope includes all languages that encourage functional programming, including both purely applicative and imperative languages, as well as languages with objects, concurrency, or parallelism. Topics of interest include (but are not limited to): * Language Design: concurrency and distribution; modules; components and composition; metaprogramming; interoperability; type systems; relations to imperative, object-oriented, or logic programming * Implementation: abstract machines; virtual machines; interpretation; compilation; compile-time and run-time optimization; memory management; multi-threading; exploiting parallel hardware; interfaces to foreign functions, services, components, or low-level machine resources * Software-Development Techniques: algorithms and data structures; design patterns; specification; verification; validation; proof assistants; debugging; testing; tracing; profiling * Foundations: formal semantics; lambda calculus; rewriting; type theory; monads; continuations; control; state; effects; program verification; dependent types * Analysis and Transformation: control-flow; data-flow; abstract interpretation; partial evaluation; program calculation * Applications and Domain-Specific Languages: symbolic computing; formal-methods tools; artificial intelligence; systems programming; distributed-systems and web programming; hardware design; databases; XML processing; scientific and numerical computing; graphical user interfaces; multimedia programming; scripting; system administration; security * Education: teaching introductory programming; parallel programming; mathematical proof; algebra * Functional Pearls: elegant, instructive, and fun essays on functional programming * Experience Reports: short papers that provide evidence that functional programming really works or describe obstacles that have kept it from working If you are concerned about the appropriateness of some topic, do not hesitate to contact the program chair. Abbreviated instructions for authors ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ * By Saturday, 1 March 2014, 23:59 UTC-11 (anywhere in the world), submit a full paper of at most 12 pages (6 pages for an Experience Report), including bibliography and figures. The deadlines will be strictly enforced and papers exceeding the page limits will be summarily rejected. * Authors have the option to attach supplementary material to a submission, on the understanding that reviewers may choose not to look at it. * Each submission must adhere to SIGPLAN's republication policy, as explained on the web at http://www.sigplan.org/Resources/Policies/Republication * Authors of resubmitted (but previously rejected) papers have the option to attach an annotated copy of the reviews of their previous submission(s), explaining how they have addressed these previous reviews in the present submission. If a reviewer identifies him/herself as a reviewer of this previous submission and wishes to see how his/her comments have been addressed, the program chair will communicate to this reviewer the annotated copy of his/her previous review. Otherwise, no reviewer will read the annotated copies of the previous reviews. Overall, a submission will be evaluated according to its relevance, correctness, significance, originality, and clarity. It should explain its contributions in both general and technical terms, clearly identifying what has been accomplished, explaining why it is significant, and comparing it with previous work. The technical content should be accessible to a broad audience. Functional Pearls and Experience Reports are separate categories of papers that need not report original research results and must be marked as such at the time of submission. Detailed guidelines on both categories are on the conference web site. Proceedings will be published by ACM Press. Authors of accepted submissions are expected to transfer the copyright to the ACM. Presentations will be videotaped and released online if the presenter consents. The proceedings will be freely available for download from the ACM Digital Library from one week before the start of the conference until two weeks after the conference. Formatting: Submissions must be in PDF format printable in black and white on US Letter sized paper and interpretable by Ghostscript. Papers must adhere to the standard ACM conference format: two columns, nine-point font on a ten-point baseline, with columns 20pc (3.33in) wide and 54pc (9in) tall, with a column gutter of 2pc (0.33in). A suitable document template for LaTeX is available: http://www.acm.org/sigs/sigplan/authorInformation.htm Submission: Submissions will be accepted on the web at https://www.easychair.org/conferences/?conf=icfp2014 . Improved versions of a paper may be submitted at any point before the submission deadline using the same web interface. Author response: Authors will have a 72-hour period, starting at 0:00 UTC-11 on Wednesday, 23 April 2014, to read reviews and respond to them. ACM Author-Izer is a unique service that enables ACM authors to generate and post links on either their home page or institutional repository for visitors to download the definitive version of their articles from the ACM Digital Library at no charge. Downloads through Author-Izer links are captured in official ACM statistics, improving the accuracy of usage and impact measurements. Consistently linking the definitive version of ACM article should reduce user confusion over article versioning. After your article has been published and assigned to your ACM Author Profile page, please visit http://www.acm.org/publications/acm-author-izer-service to learn how to create your links for fee downloads from the ACM DL. General Chair: Johan Jeuring, Utrecht University Program Chair: Manuel Chakravarty, University of New South Wales Program Committee: Edwin Brady, University of St Andrews Derek Dreyer, Max Planck Institute for Software Systems Ralf Hinze, University of Oxford Zhenjiang Hu, National Institute of Informatics Patricia Johann, Appalachian State University Ken Larsen, University of Copenhagen Yukiyoshi Kameyama, University of Tsukuba Anil Madhavapeddy, University of Cambridge Geoffrey Mainland, Drexel University David Mazi?res, Stanford University Jay McCarthy, Brigham Young University Matthew Might, University of Utah Ulf Norell, Chalmers University of Technology Tiark Rompf, Swiss Federal Institute of Technology in Lausanne Chung-chieh Shan, Indiana University Mary Sheeran, Chalmers University of Technology Matt Sottile, Galois Don Syme, Microsoft Research Jesse Tov, Harvard University From branimir.maksimovic at gmail.com Wed Jan 8 03:01:29 2014 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Wed, 08 Jan 2014 04:01:29 +0100 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: References: <52CC4DBA.2050907@gmail.com> Message-ID: <52CCBF89.6030503@gmail.com> On 01/07/2014 09:39 PM, Bob Ippolito wrote: > Here's a much simpler implementation for that sort of pattern, using > channels to fan out work to threads. I added a dependency on Criterion > because getCPUTime is basically useless for this kind of measurement > on Mac OS X since it doesn't include the time that the process spent > waiting on IO: Great, thank you very much. You gave me material for learning ;) However, my version is significantly faster when compiling without -threaded. With -threaded option, your version is much faster than mine, but both are significantly slower then compile without -threaded. Thanks! From bob at redivi.com Wed Jan 8 03:15:17 2014 From: bob at redivi.com (Bob Ippolito) Date: Tue, 7 Jan 2014 19:15:17 -0800 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: <52CCBF89.6030503@gmail.com> References: <52CC4DBA.2050907@gmail.com> <52CCBF89.6030503@gmail.com> Message-ID: On Tuesday, January 7, 2014, Branimir Maksimovic wrote: > On 01/07/2014 09:39 PM, Bob Ippolito wrote: > >> Here's a much simpler implementation for that sort of pattern, using >> channels to fan out work to threads. I added a dependency on Criterion >> because getCPUTime is basically useless for this kind of measurement on Mac >> OS X since it doesn't include the time that the process spent waiting on IO: >> > Great, thank you very much. You gave me material for learning ;) > However, my version is significantly faster when compiling without > -threaded. > With -threaded option, your version is much faster than mine, but both are > significantly slower > then compile without -threaded. > Happy to look into it, I didn't have time today to do benchmarks (and Mac OS X is the worst platform to do this kind of testing on regardless of language, its network stack is inconsistent at best). I need to know more: How exactly are you compiling? Which OS? What version of GHC and Haskell Platform? What is the exact command line you execute it with? What timings do you get? What's the code for the server are you connecting to? Loopback, local network, or internet? -bob -------------- next part -------------- An HTML attachment was scrubbed... URL: From branimir.maksimovic at gmail.com Wed Jan 8 03:27:55 2014 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Wed, 08 Jan 2014 04:27:55 +0100 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: References: <52CC4DBA.2050907@gmail.com> <52CCBF89.6030503@gmail.com> Message-ID: <52CCC5BB.7080001@gmail.com> On 01/08/2014 04:15 AM, Bob Ippolito wrote: > On Tuesday, January 7, 2014, Branimir Maksimovic wrote: > > On 01/07/2014 09:39 PM, Bob Ippolito wrote: > > Here's a much simpler implementation for that sort of pattern, > using channels to fan out work to threads. I added a > dependency on Criterion because getCPUTime is basically > useless for this kind of measurement on Mac OS X since it > doesn't include the time that the process spent waiting on IO: > > Great, thank you very much. You gave me material for learning ;) > However, my version is significantly faster when compiling without > -threaded. > With -threaded option, your version is much faster than mine, but > both are significantly slower > then compile without -threaded. > > > Happy to look into it, I didn't have time today to do benchmarks > (and Mac OS X is the worst platform to do this kind of testing on > regardless of language, its network stack is inconsistent at best). I > need to know more: > > How exactly are you compiling? ghc-7.6.3 --make -O2 client.hs > Which OS? Ubuntu 13.10 with 3.13-rc7 kernel. > What version of GHC and Haskell Platform? bmaxa at maxa:~$ apt-cache policy haskell-platform haskell-platform: Installed: 2013.2.0.0 Candidate: 2013.2.0.0 Version table: *** 2013.2.0.0 0 500 http://archive.ubuntu.com/ubuntu/ saucy/universe amd64 Packages 100 /var/lib/dpkg/status > What is the exact command line you execute it with? time ./client maxa 5055 1000 100000 > What timings do you get? with your version: real 0m4.235s user 0m1.589s sys 0m2.642s with my version real 0m3.010s user 0m0.590s sys 0m2.417s that is, of course, without -threaded > What's the code for the server are you connecting to? import Network (listenOn,PortID(..)) import Network.Socket (accept,close) import Network.Socket.ByteString import System.Environment import Control.Concurrent (forkIO) main = do n <- getArgs let nn = (read.head) n :: Int putStrLn $ "Listening on " ++ show nn sock <- listenOn $ PortNumber $ fromIntegral nn serve sock serve sock = do (s,_) <- accept sock forkIO $ process s serve sock process sock = do buf <- recv sock 1024 sendAll sock buf close sock > Loopback, local network, or internet? loopback. Testing is on same computer. Thanks! -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Wed Jan 8 03:47:10 2014 From: bob at redivi.com (Bob Ippolito) Date: Tue, 7 Jan 2014 19:47:10 -0800 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: <52CCC5BB.7080001@gmail.com> References: <52CC4DBA.2050907@gmail.com> <52CCBF89.6030503@gmail.com> <52CCC5BB.7080001@gmail.com> Message-ID: On Tuesday, January 7, 2014, Branimir Maksimovic wrote: > On 01/08/2014 04:15 AM, Bob Ippolito wrote: > > On Tuesday, January 7, 2014, Branimir Maksimovic wrote: > >> On 01/07/2014 09:39 PM, Bob Ippolito wrote: >> >>> Here's a much simpler implementation for that sort of pattern, using >>> channels to fan out work to threads. I added a dependency on Criterion >>> because getCPUTime is basically useless for this kind of measurement on Mac >>> OS X since it doesn't include the time that the process spent waiting on IO: >>> >> Great, thank you very much. You gave me material for learning ;) >> However, my version is significantly faster when compiling without >> -threaded. >> With -threaded option, your version is much faster than mine, but both >> are significantly slower >> then compile without -threaded. >> > > Happy to look into it, I didn't have time today to do benchmarks > (and Mac OS X is the worst platform to do this kind of testing on > regardless of language, its network stack is inconsistent at best). I need > to know more: > > How exactly are you compiling? > > > ghc-7.6.3 --make -O2 client.hs > > Which OS? > > > Ubuntu 13.10 with 3.13-rc7 kernel. > > What version of GHC and Haskell Platform? > > > bmaxa at maxa:~$ apt-cache policy haskell-platform > haskell-platform: > Installed: 2013.2.0.0 > Candidate: 2013.2.0.0 > Version table: > *** 2013.2.0.0 0 > 500 http://archive.ubuntu.com/ubuntu/ saucy/universe amd64 > Packages > 100 /var/lib/dpkg/status > > > What is the exact command line you execute it with? > > > time ./client maxa 5055 1000 100000 > What happens if you add +RTS -N to the end of that command line? > > > What timings do you get? > > with your version: > real 0m4.235s > user 0m1.589s > sys 0m2.642s > > with my version > real 0m3.010s > user 0m0.590s > sys 0m2.417s > that is, of course, without -threaded > > What's the code for the server are you connecting to? > > import Network (listenOn,PortID(..)) > import Network.Socket (accept,close) > import Network.Socket.ByteString > import System.Environment > import Control.Concurrent (forkIO) > > main = do > n <- getArgs > let nn = (read.head) n :: Int > putStrLn $ "Listening on " ++ show nn > sock <- listenOn $ PortNumber $ fromIntegral nn > serve sock > > serve sock = do > (s,_) <- accept sock > forkIO $ process s > serve sock > > process sock = do > buf <- recv sock 1024 > sendAll sock buf > close sock > > Loopback, local network, or internet? > > > loopback. Testing is on same computer. > > Thanks! > Great, I'll look closer later tonight or tomorrow morning. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jgm at berkeley.edu Wed Jan 8 04:12:22 2014 From: jgm at berkeley.edu (John MacFarlane) Date: Tue, 7 Jan 2014 20:12:22 -0800 Subject: [Haskell-cafe] ANN: cheapskate 0.1, markdown parser In-Reply-To: References: <20140106191553.GA49308@Johns-MacBook-Air-2.local> Message-ID: <20140108041222.GB19945@berkeley.edu> +++ Daniil Frumin [Jan 08 14 05:45 ]: > Cool! > > By the way, I've noticed that you've rolled your own parser combinator > library. May I ask you, what is the reason for that? > Are other parser libraries not fast enough for the needs? I started out using attoparsec, but I really needed the ability to query source position, which attoparsec doesn't provide. I also added a way to peek at the character *before* the current position (peekLastChar), which simplified some of my parsers. Otherwise it's very similar to attoparsec, with similar performance. From bob at redivi.com Wed Jan 8 15:50:53 2014 From: bob at redivi.com (Bob Ippolito) Date: Wed, 8 Jan 2014 07:50:53 -0800 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: References: <52CC4DBA.2050907@gmail.com> <52CCBF89.6030503@gmail.com> <52CCC5BB.7080001@gmail.com> Message-ID: I haven't yet been able to sort out the performance difference, and probably won't have time to dig in deeper with profiling tools today. I've put together a gist with all of the files and a cabal file so it's easy to build with the right options. https://gist.github.com/etrepum/8312165 On Tue, Jan 7, 2014 at 7:47 PM, Bob Ippolito wrote: > > > On Tuesday, January 7, 2014, Branimir Maksimovic wrote: > >> On 01/08/2014 04:15 AM, Bob Ippolito wrote: >> >> On Tuesday, January 7, 2014, Branimir Maksimovic wrote: >> >>> On 01/07/2014 09:39 PM, Bob Ippolito wrote: >>> >>>> Here's a much simpler implementation for that sort of pattern, using >>>> channels to fan out work to threads. I added a dependency on Criterion >>>> because getCPUTime is basically useless for this kind of measurement on Mac >>>> OS X since it doesn't include the time that the process spent waiting on IO: >>>> >>> Great, thank you very much. You gave me material for learning ;) >>> However, my version is significantly faster when compiling without >>> -threaded. >>> With -threaded option, your version is much faster than mine, but both >>> are significantly slower >>> then compile without -threaded. >>> >> >> Happy to look into it, I didn't have time today to do benchmarks >> (and Mac OS X is the worst platform to do this kind of testing on >> regardless of language, its network stack is inconsistent at best). I need >> to know more: >> >> How exactly are you compiling? >> >> >> ghc-7.6.3 --make -O2 client.hs >> >> Which OS? >> >> >> Ubuntu 13.10 with 3.13-rc7 kernel. >> >> What version of GHC and Haskell Platform? >> >> >> bmaxa at maxa:~$ apt-cache policy haskell-platform >> haskell-platform: >> Installed: 2013.2.0.0 >> Candidate: 2013.2.0.0 >> Version table: >> *** 2013.2.0.0 0 >> 500 http://archive.ubuntu.com/ubuntu/ saucy/universe amd64 >> Packages >> 100 /var/lib/dpkg/status >> >> >> What is the exact command line you execute it with? >> >> >> time ./client maxa 5055 1000 100000 >> > > What happens if you add +RTS -N to the end of that command line? > > >> >> >> What timings do you get? >> >> with your version: >> real 0m4.235s >> user 0m1.589s >> sys 0m2.642s >> >> with my version >> real 0m3.010s >> user 0m0.590s >> sys 0m2.417s >> that is, of course, without -threaded >> >> What's the code for the server are you connecting to? >> >> import Network (listenOn,PortID(..)) >> import Network.Socket (accept,close) >> import Network.Socket.ByteString >> import System.Environment >> import Control.Concurrent (forkIO) >> >> main = do >> n <- getArgs >> let nn = (read.head) n :: Int >> putStrLn $ "Listening on " ++ show nn >> sock <- listenOn $ PortNumber $ fromIntegral nn >> serve sock >> >> serve sock = do >> (s,_) <- accept sock >> forkIO $ process s >> serve sock >> >> process sock = do >> buf <- recv sock 1024 >> sendAll sock buf >> close sock >> >> Loopback, local network, or internet? >> >> >> loopback. Testing is on same computer. >> >> Thanks! >> > > Great, I'll look closer later tonight or tomorrow morning. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Wed Jan 8 17:23:05 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Wed, 8 Jan 2014 12:23:05 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> <52CC4903.4020003@fuuzetsu.co.uk> Message-ID: I tend to opt for writing plaintext LaTeX, and if the reader wants it to be pretty, they can use TeX the World (although it looks like this is now unmaintained and only viable in chrome). On Jan 7, 2014 2:08 PM, "Carter Schonwald" wrote: > In the case of MathJax, the fall back is you just get some inline latex. > > On Tuesday, January 7, 2014, Mateusz Kowalczyk wrote: > >> On 07/01/14 12:18, Antonio Nikishaev wrote: >> > Mateusz Kowalczyk writes: >> > >> >> On 07/01/14 01:42, Carter Schonwald wrote: >> >>> I would really love to use MathJax in the haddock HTML backend. Is >> there >> >>> any way (however hacky) that I could do that? >> >> >> >> I looked up how MathJax is used and as far as I can tell, it's just >> >> the case of putting the MathJax JavaScript header into the file, >> >> right? We already use JavaScript on the Haddock-generated HTML pages, >> >> for example the synopsis box. >> >> >> >> While I prefer JavaScript-free web I think that for viewing on >> >> Hackage, it'd be possible to just stick the header into the generated >> >> files and be done with it. Here are some caveats: >> >> >> >> * You suddenly allow for part of documentation to be rendered by >> >> someone else, over the Internet. The problem is that documentation >> >> suddenly becomes worse for everyone browsing without JavaScript or >> >> browsing locally, without an Internet connection. Embedding images >> >> avoids both of these problems. >> > >> > No. It's rendered in the browser. >> > >> >> It still requires an Internet connection, does it not? Many people >> prefer to browse without JavaScript anyway (myself included) and if the >> documentation suddenly requires JavaScript to view properly, this is a >> problem. >> >> -- >> Mateusz K. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Wed Jan 8 19:40:01 2014 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Wed, 8 Jan 2014 14:40:01 -0500 Subject: [Haskell-cafe] Class Instance with ExistentialQuantification In-Reply-To: <1389107775.14997.3.camel@kirk> References: <20140107101812.GA8094@sniper> <1389107775.14997.3.camel@kirk> Message-ID: I think allowing polytype instances would lead to incoherence. This is, of course, OK with Coercible (where incoherence is rife and completely appropriate). But, consider > instance Foo (forall a. [a]) where ... > instance Foo [Int] where ... > > bar :: Foo b => b -> ... > > quux = bar [] Which instance should be used in the call to `bar`? Perhaps those two instances would just be considered overlapping. Another related issue is that making polytype instances useful seems to require impredicativity. Recall that impredicativity means allowing type variables to take on polytype values. (Normally, type variables are always instantiated to monotypes.) Type inference in the presence of impredicativity is wonky at best. A colleague (Hamidhasan Ahmed) is working on allowing explicit type applications, which would greatly help with impredicative inference. When that's working, I think polytype instances may make more sense. Though, in the end, I agree that this takes some Careful Thought. Richard On Jan 7, 2014, at 10:16 AM, Joachim Breitner wrote: > Hi, > > is it not allowed simply because none has needed it yet, or is there a > deeper theoretical problem with it? > > I?m asking because the implementation of Coercible behaves as if there > is an instance > instance forall a. (Coercible (t1 a) (t2 a)) => Coercible (forall a. t1 a) (forall a. t2 a) > and if were theoretically dubious, I?d like to know about it :-) > > Greetings, > Joachim > > Am Dienstag, den 07.01.2014, 10:11 -0500 schrieb Andrew Gibiansky: >> Ah, I see. I wasn't aware that constraints had to be over monotypes. I >> figured that since you could write a function >> >> >> f :: (forall a. a -> a) -> Bool >> >> >> Then you could also do similar things with a class. >> >> >> (The reason I was doing this was that I wanted a typeclass to match >> something like "return 'a'" without using IncoherentInstances or other >> sketchiness, and found that trying to have a typeclass with an >> instance for 'forall m. Monad m => m Char` gave me this error.) >> >> >> Thanks! >> Andrew >> >> >> On Tue, Jan 7, 2014 at 5:18 AM, Roman Cheplyaka >> wrote: >> * Andrew Gibiansky [2014-01-06 >> 22:17:21-0500] >>> Why is the following not allowed? >>> >>> {-# LANGUAGE ExistentialQuantification, ExplicitForAll, >> RankNTypes, >>> FlexibleInstances #-} >>> >>> class Class a where >>> test :: a -> Bool >>> >>> instance Class (forall m. m -> m) where >>> test _ = True >>> >>> main = do >>> putStrLn $ test id >>> >>> Is there a reason that this is forbidden? Just curious. >> >> >> I believe the rule is that all constraints (including class >> constraints) >> range over monotypes. >> >> What are you trying to achieve? >> >> You can do this, for example: >> >> newtype Poly = Poly (forall a . a -> a) >> instance Class Poly where test = const True >> >> main = print $ test $ Poly id >> >> BTW, this has nothing to do with ExistentialQuantification. >> >> Roman >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? http://www.joachim-breitner.de/ > Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C > Debian Developer: nomeata at debian.org > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From nikita at karetnikov.org Wed Jan 8 20:12:58 2014 From: nikita at karetnikov.org (Nikita Karetnikov) Date: Thu, 09 Jan 2014 00:12:58 +0400 Subject: [Haskell-cafe] Drop or update the upper bounds of numerals and numerals-base In-Reply-To: <20140107224454.GC11962@sniper> (Roman Cheplyaka's message of "Wed, 8 Jan 2014 00:44:54 +0200") References: <87a9f7cw12.fsf@karetnikov.org> <20140107224454.GC11962@sniper> Message-ID: <874n5egrlh.fsf@karetnikov.org> > The page http://hackage.haskell.org/package/numerals lists the issue > tracker and maintainer's email. Have you tried those? I don?t use GitHub. Anyway, the tracker shows five open issues from 2012. And the latest commit was pushed on July 16, 2012. When I sent the previous message, I CC?d the maintainer. Apologies for the noise, but my emails to Gmail users usually end up in spam. I wanted to make sure that someone with the right permissions would see my message. How long should I wait before I can do the required work myself? > Also, as a quick workaround, Cabal's master branch has the option > '--allow-newer'. Thanks for letting me know, but I can?t expect that the users of my package would have that version installed. -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 835 bytes Desc: not available URL: From michael at orlitzky.com Wed Jan 8 22:28:04 2014 From: michael at orlitzky.com (Michael Orlitzky) Date: Wed, 08 Jan 2014 17:28:04 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> <52CC4903.4020003@fuuzetsu.co.uk> Message-ID: <52CDD0F4.7070900@orlitzky.com> On 01/08/2014 12:23 PM, Ben Foppa wrote: > I tend to opt for writing plaintext LaTeX, and if the reader wants it to > be pretty, they can use TeX the World (although it looks like this is > now unmaintained and only viable in chrome). The Sage project[1] has to solve a similar problem with its python reference documentation for various mathy things. These days MathJax is used, but in my opinion the previous solution was better. While the HTML documentation was being generated from RST, various magics were employed to convert the embedded formulas to PNGs which were then inserted directly into the markup. Haddock could probably be convinced to do the same. The downside to images is that they don't scale, but they do have the alt attribute as a plain-text fallback. The problem with MathJax is that it takes forever to load and slows the browser to a crawl -- especially annoying when you know what you're looking for and can't scroll to it because the document keeps jumping around as formulas load for 30 seconds. Images load instantly and look good enough. [1] http://sagemath.org/ From carter.schonwald at gmail.com Wed Jan 8 23:04:12 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Wed, 8 Jan 2014 18:04:12 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: <52CDD0F4.7070900@orlitzky.com> References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> <52CB6BDC.1020105@fuuzetsu.co.uk> <52CC4903.4020003@fuuzetsu.co.uk> <52CDD0F4.7070900@orlitzky.com> Message-ID: i've had a positive experience with mathjax even on a mobile device / smart phone. and being able to copy paste math is a HUGE thing for me. On Wed, Jan 8, 2014 at 5:28 PM, Michael Orlitzky wrote: > On 01/08/2014 12:23 PM, Ben Foppa wrote: > > I tend to opt for writing plaintext LaTeX, and if the reader wants it to > > be pretty, they can use TeX the World (although it looks like this is > > now unmaintained and only viable in chrome). > > The Sage project[1] has to solve a similar problem with its python > reference documentation for various mathy things. These days MathJax is > used, but in my opinion the previous solution was better. While the HTML > documentation was being generated from RST, various magics were employed > to convert the embedded formulas to PNGs which were then inserted > directly into the markup. Haddock could probably be convinced to do the > same. > > The downside to images is that they don't scale, but they do have the > alt attribute as a plain-text fallback. The problem with MathJax is that > it takes forever to load and slows the browser to a crawl -- especially > annoying when you know what you're looking for and can't scroll to it > because the document keeps jumping around as formulas load for 30 > seconds. Images load instantly and look good enough. > > > > [1] http://sagemath.org/ > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alex.solla at gmail.com Wed Jan 8 23:24:40 2014 From: alex.solla at gmail.com (Alexander Solla) Date: Wed, 8 Jan 2014 15:24:40 -0800 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: <52CB2C11.4010405@fuuzetsu.co.uk> <1389052225.9235.53.camel@kirk> Message-ID: +1 for MathJax. It was my first thought when the question came up. On Mon, Jan 6, 2014 at 5:42 PM, Carter Schonwald wrote: > I would really love to use MathJax in the haddock HTML backend. Is there > any way (however hacky) that I could do that? > > > On Monday, January 6, 2014, Joachim Breitner wrote: > >> Hi, >> >> it should also be possible to render Formulas to SVG, and embed the >> SVG-File using a data-URL, and get a vector rendering of your >> formular.... similar to the image in >> >> http://hackage.haskell.org/package/circle-packing-0.1.0.3/docs/Optimisation-CirclePacking.html >> >> But probably that will hit size bounds very soon. >> >> http://hackage.haskell.org/package/diagrams-haddock works similarly, and >> also explains how to ship the SVG files separately, to not hit size >> bounds. >> >> I guess a tool similar to that, latex-haddock, would be feasible and >> useful. >> >> Greetings, >> Joachim >> >> >> Am Dienstag, den 07.01.2014, 03:44 +0400 schrieb Alexander V Vershilov: >> > It's possible to use latex render sites [1], then shrink link by tiny >> > URL [2]. Then paste like usual image. >> > >> > [1] http://www.codecogs.com/latex/eqneditor.php >> > [2] http://tinyurl.com >> > >> > -- >> > Alexander >> > >> > On Jan 7, 2014 2:20 AM, "Mateusz Kowalczyk" >> > wrote: >> > On 06/01/14 18:49, Peter Caspers wrote: >> > > Hi, >> > > >> > > I am still very new to Haskell, trying to start my very >> > first project. >> > > For its documentation I want to use Haddock and suitable >> > comments in >> > > the source code. >> > > >> > > I notice that (e.g. different from doxygen) there is no >> > direct way of >> > > writing formulas, say in TeX style. Looking into some >> > projects on >> > > Hackage, formulas there >> > > seem to be written in "pseudo-code" more or less like TeX >> > but not >> > > following any strict standard. As far as I can see. >> > >> > That's right, there's no direct way to embed maths in Haddock. >> > It has >> > been a somewhat requested feature for Haddock over summer when >> > I did >> > work on it but it didn't make it in. >> > >> > > What would be your recommendations concerning this ? Is >> > there some >> > > guideline on how to include formulas ? I understand that >> > there is >> > > "literal programming" >> > > where you can e.g. write a TeX article with embedded code >> > blocks that >> > > can be extracted for the compiler. However, I do not want to >> > follow >> > > this path, also the >> > > result is a bit different from what is produced in the >> > "traditional" >> > > approach, isn't it. >> > >> > If you want manually-written LaTeX, this is probably the only >> > way at the >> > moment. If all you want is some LaTeX snippets (maths), your >> > best bet is >> > to probably write those separately, make images out of them >> > and then >> > embed them into your documentation. There's currently no way >> > for Haddock >> > to do this for you. We do however have a LaTeX back-end so >> > it's not like >> > it's impossible to generate but it'd require some work that >> > has not yet >> > been put in. >> > >> > > Thanks a lot >> > > Peter >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > Haskell-Cafe at haskell.org >> > > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > >> > >> > >> > -- >> > Mateusz K. >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Joachim Breitner >> e-Mail: mail at joachim-breitner.de >> Homepage: http://www.joachim-breitner.de >> Jabber-ID: nomeata at joachim-breitner.de >> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vandijk.roel at gmail.com Thu Jan 9 11:07:22 2014 From: vandijk.roel at gmail.com (Roel van Dijk) Date: Thu, 9 Jan 2014 12:07:22 +0100 Subject: [Haskell-cafe] Drop or update the upper bounds of numerals and numerals-base In-Reply-To: <87a9f7cw12.fsf@karetnikov.org> References: <87a9f7cw12.fsf@karetnikov.org> Message-ID: Hello, maintainer here. It's true I haven't done much maintenance in the past year. At the very least the packages should build with the latest libraries so let's focus on that. I've pushed two patches to numerals-base and numerals to update the upper bounds of some dependencies. This includes the test suites. Regards, Roel On 7 January 2014 22:38, Nikita Karetnikov wrote: > I?ve built both packages locally, and they seem to work fine with GHC > 7.6.3. However, I can?t install them from Hackage due to the required > dependencies. > > Could anyone drop or update the upper bounds? Alternatively, I could > try to do so myself if someone provides the required permissions. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Thu Jan 9 14:50:16 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 15:50:16 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? Message-ID: <52CEB728.8040807@gmail.com> Hello Cafe, With my current knowledge of Haskell, I do not see why is there Maybe if we have Either. For example, Functor and Monad instances (and many others) of Maybe and Either are the same (except for fail). In other words, this should hold: Maybe a = Either String a -- String or something else Nothing = Left "" Just a = Right a I'm curious to find out what was the reasoning to make Maybe? What is the added value with introducing it? In which situations the above substitution does not hold? Best regards, vlatko From Hannes_E at gmx.de Thu Jan 9 15:07:48 2014 From: Hannes_E at gmx.de (Johannes Erber) Date: Thu, 09 Jan 2014 15:07:48 +0000 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEB728.8040807@gmail.com> References: <52CEB728.8040807@gmail.com> Message-ID: <52CEBB44.5070003@gmx.de> Hi Vlatko, to keep programs clear, short and simple. What makes you choose String as type to replace Nothing? Best, Johannes On 09/01/2014 14:50, Vlatko Basic wrote: > Hello Cafe, > > With my current knowledge of Haskell, I do not see why is there Maybe > if we have Either. > > For example, Functor and Monad instances (and many others) of Maybe > and Either are the same (except for fail). > > In other words, this should hold: > > Maybe a = Either String a -- String or something else > Nothing = Left "" > Just a = Right a > > > I'm curious to find out what was the reasoning to make Maybe? > What is the added value with introducing it? > In which situations the above substitution does not hold? > > > > Best regards, > > vlatko > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From allbery.b at gmail.com Thu Jan 9 15:10:07 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 9 Jan 2014 10:10:07 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEB728.8040807@gmail.com> References: <52CEB728.8040807@gmail.com> Message-ID: On Thu, Jan 9, 2014 at 9:50 AM, Vlatko Basic wrote: > With my current knowledge of Haskell, I do not see why is there Maybe if > we have Either. > Because, while Either () a is isomorphic to Maybe a, it can be rather less convenient to have to track that Left (). We can easily define a type that doesn't need the extra work; why not use it? Especially when that particular case turns out to be very common. The fact that you *can* build up a standard library from first principles every time you write a program does not mean that you *should*. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Thu Jan 9 15:13:17 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Thu, 9 Jan 2014 16:13:17 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEB728.8040807@gmail.com> References: <52CEB728.8040807@gmail.com> Message-ID: <20140109151317.GA26566@machine> Hi Vlatko, On Thu, Jan 09, 2014 at 03:50:16PM +0100, Vlatko Basic wrote: > I'm curious to find out what was the reasoning to make Maybe? > What is the added value with introducing it? > In which situations the above substitution does not hold? If you just want to signalize a fail case without any additional information, then a Maybe fits better than an Either, because why should you need this bogus empty string? How should you know that the string doesn't contain something relevant? Greetings, Daniel From nickolay.kudasov at gmail.com Thu Jan 9 15:14:03 2014 From: nickolay.kudasov at gmail.com (Nickolay Kudasov) Date: Thu, 9 Jan 2014 19:14:03 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEB728.8040807@gmail.com> References: <52CEB728.8040807@gmail.com> Message-ID: Hi Vlatko, Actually, Maybe can be seen as Either () a. Not String or Int because then you would have multiple Nothings (if Left "" is Nothing then what would Left "hello" be?). So Either e a is (generally) somewhat *bigger* than Maybe a. Since Either can be used to represent strictly bigger types, you may not want it sometimes. lookup function (to find element in a list by its index) is an example. It is unnecessary to keep extra information in () or Stringor Int about what caused failure. So if we either *don?t care what caused failure* or *can unambiguously determine the cause* Maybe suits better (is more readable) than Either (). Nick 2014/1/9 Vlatko Basic > Hello Cafe, > > With my current knowledge of Haskell, I do not see why is there Maybe if > we have Either. > > For example, Functor and Monad instances (and many others) of Maybe and > Either are the same (except for fail). > > In other words, this should hold: > > Maybe a = Either String a -- String or something else > Nothing = Left "" > Just a = Right a > > > I'm curious to find out what was the reasoning to make Maybe? > What is the added value with introducing it? > In which situations the above substitution does not hold? > > > > Best regards, > > vlatko > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From yom at artyom.me Thu Jan 9 15:23:11 2014 From: yom at artyom.me (Artyom Kazak) Date: Thu, 09 Jan 2014 19:23:11 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEB728.8040807@gmail.com> References: <52CEB728.8040807@gmail.com> Message-ID: <52CEBEDF.5070908@artyom.me> Besides, even defining type Maybe a = Either () a in standard library wouldn?t be the same as data Maybe a = Nothing | Just a since in Haskell 98 type synonyms aren?t allowed in instance declarations, which means that programmers would still have to remember that `Maybe` is actually `Either ()` under-the-hood every time when writing an instance. From vlatko.basic at gmail.com Thu Jan 9 15:26:58 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 16:26:58 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEBB44.5070003@gmx.de> References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> Message-ID: <52CEBFC2.3080900@gmail.com> Hi Johannes, I thought there was some "more important" reason than convenience, so I asked. :-O) I put String because I'm currently thinking about error handling, and Left String is the usual way of reporting failure, and I see Maybe as a type for reporting errors, failures and similar. Somehow it looks to me that famous "8 ways to report errors in Haskell" could be shortened by one if Maybe is replaced with Either (with appropriate synonyms, of course). vlatko -------- Original Message -------- Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? From: Johannes Erber To: vlatko.basic at gmail.com, haskell-cafe at haskell.org Date: 09.01.2014 16:07 > Hi Vlatko, > > to keep programs clear, short and simple. What makes you choose String as type > to replace Nothing? > > Best, > Johannes > > On 09/01/2014 14:50, Vlatko Basic wrote: >> Hello Cafe, >> >> With my current knowledge of Haskell, I do not see why is there Maybe if we >> have Either. >> >> For example, Functor and Monad instances (and many others) of Maybe and Either >> are the same (except for fail). >> >> In other words, this should hold: >> >> Maybe a = Either String a -- String or something else >> Nothing = Left "" >> Just a = Right a >> >> >> I'm curious to find out what was the reasoning to make Maybe? >> What is the added value with introducing it? >> In which situations the above substitution does not hold? >> >> >> >> Best regards, >> >> vlatko >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > From allbery.b at gmail.com Thu Jan 9 15:35:32 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 9 Jan 2014 10:35:32 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEBFC2.3080900@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> Message-ID: On Thu, Jan 9, 2014 at 10:26 AM, Vlatko Basic wrote: > I put String because I'm currently thinking about error handling, and Left > String is the usual way of reporting failure, and I see Maybe as a type for > reporting errors, failures and similar. > Actually, the fact that all you can convey is "something failed" makes Maybe not a good error reporting type. And this is fine; there is still the "no value" niche (Perl's undefined, SQL's NULL, etc.) --- and the evidence from C's NULL that an *out of band* representation is often a very good idea (and from IEEE754's NaN that multiple out of band values is often a very bad idea). Also, a point that seems to often be missed in considering what is "more important": ultimately, what is *most* important is letting the programmer do what they need to do with a minimum of fuss or extra work. Predefining very useful stuff like Maybe which could be reinvented on the fly based on Either is about minimizing even the trivial extra work. Pedagogy is only rarely a useful design goal. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Thu Jan 9 15:36:55 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 16:36:55 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <20140109151317.GA26566@machine> References: <52CEB728.8040807@gmail.com> <20140109151317.GA26566@machine> Message-ID: <52CEC217.7040402@gmail.com> Hi Daniel, > If you just want to signalize a fail case without any additional > information, then a Maybe fits better than an Either, because > why should you need this bogus empty string? Now it looks to me that it might be better and more consistent to write an empty bogus string (as with: nothing = Left "") than to have two distinct ways of error reporting, and both are used widely and often should be intermixed. And at the end, call site could decide does it want to use the string or not. vlatko -------- Original Message -------- Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? From: Daniel Trstenjak To: haskell-cafe at haskell.org Date: 09.01.2014 16:13 > > Hi Vlatko, > > On Thu, Jan 09, 2014 at 03:50:16PM +0100, Vlatko Basic wrote: >> I'm curious to find out what was the reasoning to make Maybe? >> What is the added value with introducing it? >> In which situations the above substitution does not hold? > > If you just want to signalize a fail case without any additional > information, then a Maybe fits better than an Either, because > why should you need this bogus empty string? > > How should you know that the string doesn't contain something relevant? > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From vlatko.basic at gmail.com Thu Jan 9 15:46:29 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 16:46:29 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> Message-ID: <52CEC455.4060909@gmail.com> An HTML attachment was scrubbed... URL: From Hannes_E at gmx.de Thu Jan 9 16:00:01 2014 From: Hannes_E at gmx.de (Johannes Erber) Date: Thu, 09 Jan 2014 16:00:01 +0000 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEBFC2.3080900@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> Message-ID: <52CEC781.3030700@gmx.de> Hi Vlatko, it is not only about convenience, but also about readability and conciseness which are quite important in order to maintain software and to prevent it from getting cluttered up unnecessarily. Also Maybe evolves naturally as minimal complete type for use cases in which you can have either a value or no value. Either extends Maybe by more information why no value is returned by a function. Of course you could replace Maybe with Eithers and your code would still work, but it would be much less concise and hence maintainable. Best, Johannes On 09/01/2014 15:26, Vlatko Basic wrote: > Hi Johannes, > > I thought there was some "more important" reason than convenience, so > I asked. :-O) > > I put String because I'm currently thinking about error handling, and > Left String is the usual way of reporting failure, and I see Maybe as > a type for reporting errors, failures and similar. > > > Somehow it looks to me that famous "8 ways to report errors in > Haskell" could be shortened by one if Maybe is replaced with Either > (with appropriate synonyms, of course). > > > vlatko > > -------- Original Message -------- > Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? > From: Johannes Erber > To: vlatko.basic at gmail.com, haskell-cafe at haskell.org > > Date: 09.01.2014 16:07 > >> Hi Vlatko, >> >> to keep programs clear, short and simple. What makes you choose >> String as type >> to replace Nothing? >> >> Best, >> Johannes >> >> On 09/01/2014 14:50, Vlatko Basic wrote: >>> Hello Cafe, >>> >>> With my current knowledge of Haskell, I do not see why is there >>> Maybe if we >>> have Either. >>> >>> For example, Functor and Monad instances (and many others) of Maybe >>> and Either >>> are the same (except for fail). >>> >>> In other words, this should hold: >>> >>> Maybe a = Either String a -- String or something else >>> Nothing = Left "" >>> Just a = Right a >>> >>> >>> I'm curious to find out what was the reasoning to make Maybe? >>> What is the added value with introducing it? >>> In which situations the above substitution does not hold? >>> >>> >>> >>> Best regards, >>> >>> vlatko >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >> From vlatko.basic at gmail.com Thu Jan 9 16:25:58 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 17:25:58 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> Message-ID: <52CECD96.6010909@gmail.com> An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Jan 9 16:32:01 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 9 Jan 2014 11:32:01 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CECD96.6010909@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> <52CECD96.6010909@gmail.com> Message-ID: On Thu, Jan 9, 2014 at 11:25 AM, Vlatko Basic wrote: > > ... is letting the programmer do what they need to do with a minimum of > fuss or extra work ... > But doesn't the need of mixing Maybe and Either cause more work for the > programmer? Programmer of library, or programmer using the library? > Arguably if you need to switch from Maybe to Either then you did not think out your program sufficiently beforehand. And if you did think it out, what exactly is the problem with using appropriate data types in appropriate places? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Thu Jan 9 16:36:06 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 17:36:06 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEBEDF.5070908@artyom.me> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> Message-ID: <52CECFF6.4040007@gmail.com> Hi Artyom, Yes, indeed. But instance declarations wouldn't be needed because we already have all the instances for Either. The point would be to have them unified. But it is a problem that there are no data constructor synonyms in Haskell. So at least pattern matching wouldn't be possible the simple way. Maybe ViewPatterns could (partially) solve that. vlatko -------- Original Message -------- Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? From: Artyom Kazak To: haskell-cafe at haskell.org Date: 09.01.2014 16:23 > Besides, even defining > > type Maybe a = Either () a > > in standard library wouldn?t be the same as > > data Maybe a = Nothing | Just a > > since in Haskell 98 type synonyms aren?t allowed in instance declarations, which > means that programmers would still have to remember that `Maybe` is actually > `Either ()` under-the-hood every time when writing an instance. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From clint at debian.org Thu Jan 9 16:39:25 2014 From: clint at debian.org (Clint Adams) Date: Thu, 9 Jan 2014 16:39:25 +0000 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CECFF6.4040007@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> Message-ID: <20140109163925.GA13923@scru.org> On Thu, Jan 09, 2014 at 05:36:06PM +0100, Vlatko Basic wrote: > But instance declarations wouldn't be needed because we already have > all the instances for Either. The point would be to have them > unified. http://hackage.haskell.org/package/errors-1.4.5/docs/Control-Error-Util.html From frantisek at farka.eu Thu Jan 9 17:41:51 2014 From: frantisek at farka.eu (Frantisek Farka) Date: Thu, 9 Jan 2014 18:41:51 +0100 Subject: [Haskell-cafe] Altering Class hierarchy Message-ID: <20140109184151.1a287d58@farka.eu> Hi all, I was toying with Haskell classes and came across Functor-Applicative-Monad proposal[1]. It shows out that adding a super class (Applicative) to a class (Monad) is not an easy task when the class hierarchy is already in use. In this case it result in stepwise approach (step1 e. g. [2]) in order not to break already existing code which uses Monad. I am interested in other examples of such changes. Which alterings of your class hierarchy do you usually need when rewriting your code? I don't mean only adding superclass here, other modifications could be also handy, e. g. dropping out a class or splitting a class into two. Can you point me to some actual examples on real source code? How do you deal with this kind of problem on your projects? Thanks for a reply :) FF [1] http://www.haskell.org/haskellwiki/Functor-Applicative-Monad_Proposal [2] https://ghc.haskell.org/trac/ghc/ticket/8004 From difrumin at gmail.com Thu Jan 9 16:42:57 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Thu, 9 Jan 2014 20:42:57 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CECFF6.4040007@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> Message-ID: But you actually might want different instances for `Maybe` and for `Either`. For example, let's say that you have a typeclasse for serializing data-structures into a database. In case of Maybe you want to serialize `Nothing` into 'NULL' or something similar; in case of Either you want to have an entirely different structure. Additionally, as it have been mentioned, `Either String a` is not the same thing as `Maybe a`. Say, you have a value of type `Either String a`. How do you know that all `Left`-values are suppose to be empty string? What do you actually want is `Either () a`. On Thu, Jan 9, 2014 at 8:36 PM, Vlatko Basic wrote: > Hi Artyom, > > Yes, indeed. > > But instance declarations wouldn't be needed because we already have all the > instances for Either. The point would be to have them unified. > But it is a problem that there are no data constructor synonyms in Haskell. > So at least pattern matching wouldn't be possible the simple way. Maybe > ViewPatterns could (partially) solve that. > > > > vlatko > > -------- Original Message -------- > Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? > From: Artyom Kazak > To: haskell-cafe at haskell.org > Date: 09.01.2014 16:23 > >> Besides, even defining >> >> type Maybe a = Either () a >> >> in standard library wouldn?t be the same as >> >> data Maybe a = Nothing | Just a >> >> since in Haskell 98 type synonyms aren?t allowed in instance declarations, >> which >> means that programmers would still have to remember that `Maybe` is >> actually >> `Either ()` under-the-hood every time when writing an instance. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sincerely yours, -- Daniil From yom at artyom.me Thu Jan 9 16:51:38 2014 From: yom at artyom.me (Artyom Kazak) Date: Thu, 09 Jan 2014 20:51:38 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CECFF6.4040007@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> Message-ID: <52CED39A.4060505@artyom.me> On 01/09/2014 08:36 PM, Vlatko Basic wrote: > But instance declarations wouldn't be needed because we already have > all the instances for Either. The point would be to have them unified. Consider a generic Show instance for Either ? there?s no way? to make it behave differently for Either () (or Maybe if it was a type synonym). I think there are other cases in which we want Maybe to behave differently from Either, but I can?t think of any on the spot. ? this point also applies to String, which is a type synonym for [Char] ? and it was solved somewhat inelegantly by adding an additional method to Show typeclass *specifically* for showing lists of things. From vlatko.basic at gmail.com Thu Jan 9 16:52:41 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 09 Jan 2014 17:52:41 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> <52CECD96.6010909@gmail.com> Message-ID: <52CED3D9.5000108@gmail.com> An HTML attachment was scrubbed... URL: From metaniklas at gmail.com Thu Jan 9 17:01:23 2014 From: metaniklas at gmail.com (Niklas Larsson) Date: Thu, 9 Jan 2014 18:01:23 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? Message-ID: <52ced5fb.6d2a700a.56f3.4803@mx.google.com> Maybe doesn't have to be used for error reporting. Optional values is a very big use case for it. ----- Ursprungligt meddelande ----- Fr?n: "Vlatko Basic" Skickat: ?2014-?01-?09 16:37 Till: "haskell-cafe at haskell.org" ?mne: Re: [Haskell-cafe] Why Maybe exists if there is Either? Hi Daniel, > If you just want to signalize a fail case without any additional > information, then a Maybe fits better than an Either, because > why should you need this bogus empty string? Now it looks to me that it might be better and more consistent to write an empty bogus string (as with: nothing = Left "") than to have two distinct ways of error reporting, and both are used widely and often should be intermixed. And at the end, call site could decide does it want to use the string or not. vlatko -------- Original Message -------- Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? From: Daniel Trstenjak To: haskell-cafe at haskell.org Date: 09.01.2014 16:13 > > Hi Vlatko, > > On Thu, Jan 09, 2014 at 03:50:16PM +0100, Vlatko Basic wrote: >> I'm curious to find out what was the reasoning to make Maybe? >> What is the added value with introducing it? >> In which situations the above substitution does not hold? > > If you just want to signalize a fail case without any additional > information, then a Maybe fits better than an Either, because > why should you need this bogus empty string? > > How should you know that the string doesn't contain something relevant? > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Thu Jan 9 17:11:49 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Thu, 9 Jan 2014 12:11:49 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52ced5fb.6d2a700a.56f3.4803@mx.google.com> References: <52ced5fb.6d2a700a.56f3.4803@mx.google.com> Message-ID: I'm generally of the opinion that if things can be unified under the hood, it makes for fewer edge cases and easier testing. It also seems to me that I describe Maybe and Either () in the same way, if I were to explain verbally: "it's either nothing, or it's something". Aside from the point made about typeclass instances, I don't see an issue with: type Maybe = Either () nothing :: Maybe a nothing = Left () just :: a -> Maybe a just = Right On Jan 9, 2014 12:02 PM, "Niklas Larsson" wrote: > Maybe doesn't have to be used for error reporting. Optional values is a > very big use case for it. > ------------------------------ > Fr?n: Vlatko Basic > Skickat: 2014-01-09 16:37 > Till: haskell-cafe at haskell.org > ?mne: Re: [Haskell-cafe] Why Maybe exists if there is Either? > > Hi Daniel, > > > If you just want to signalize a fail case without any additional > > information, then a Maybe fits better than an Either, because > > why should you need this bogus empty string? > > Now it looks to me that it might be better and more consistent to write an > empty > bogus string (as with: nothing = Left "") than to have two distinct ways > of > error reporting, and both are used widely and often should be intermixed. > And at the end, call site could decide does it want to use the string or > not. > > > vlatko > > > -------- Original Message -------- > Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? > From: Daniel Trstenjak > To: haskell-cafe at haskell.org > Date: 09.01.2014 16:13 > > > > > Hi Vlatko, > > > > On Thu, Jan 09, 2014 at 03:50:16PM +0100, Vlatko Basic wrote: > >> I'm curious to find out what was the reasoning to make Maybe? > >> What is the added value with introducing it? > >> In which situations the above substitution does not hold? > > > > If you just want to signalize a fail case without any additional > > information, then a Maybe fits better than an Either, because > > why should you need this bogus empty string? > > > > How should you know that the string doesn't contain something relevant? > > > > > > Greetings, > > Daniel > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Jan 9 17:12:52 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 9 Jan 2014 12:12:52 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CED3D9.5000108@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> <52CECD96.6010909@gmail.com> <52CED3D9.5000108@gmail.com> Message-ID: On Thu, Jan 9, 2014 at 11:52 AM, Vlatko Basic wrote: > > ... what exactly is the problem with using appropriate data types in > appropriate places ... > It is a good thing. Very good. But I do not think all library writers are > using it in correct places. But that's another problem. > In Haskell it's even a solved one: use an appropriate typeclass. We have several error-like typeclasses. Admittedly, if some library does not take advantage of this your recourse may be to submit a patch. And you still seem to be fixated on the notion that Maybe is only for errors. What exactly is the error in "user did not provide an optional parameter"? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Jan 9 17:15:02 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 9 Jan 2014 12:15:02 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEC217.7040402@gmail.com> References: <52CEB728.8040807@gmail.com> <20140109151317.GA26566@machine> <52CEC217.7040402@gmail.com> Message-ID: On Thu, Jan 9, 2014 at 10:36 AM, Vlatko Basic wrote: > > If you just want to signalize a fail case without any additional > > information, then a Maybe fits better than an Either, because > > why should you need this bogus empty string? > > Now it looks to me that it might be better and more consistent to write an > empty bogus string (as with: nothing = Left "") than to have two distinct > ways of error reporting, and both are used widely and often should be > intermixed. > And at the end, call site could decide does it want to use the string or > not. I should note here that this is pretty much the "fail" method for Monad, which is widely considered to have been a mistake. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Jan 9 17:16:08 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 9 Jan 2014 12:16:08 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52ced5fb.6d2a700a.56f3.4803@mx.google.com> Message-ID: On Thu, Jan 9, 2014 at 12:11 PM, Ben Foppa wrote: > Aside from the point made about typeclass instances, I don't see an issue > with: > > type Maybe = Either () > > nothing :: Maybe a > nothing = Left () > > just :: a -> Maybe a > just = Right > Not until you try to pattern match on it.... -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell at patrickmylund.com Thu Jan 9 17:17:42 2014 From: haskell at patrickmylund.com (Patrick Mylund Nielsen) Date: Thu, 9 Jan 2014 12:17:42 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> <52CECD96.6010909@gmail.com> <52CED3D9.5000108@gmail.com> Message-ID: On Thu, Jan 9, 2014 at 12:12 PM, Brandon Allbery wrote: > On Thu, Jan 9, 2014 at 11:52 AM, Vlatko Basic wrote: > >> > ... what exactly is the problem with using appropriate data types in >> appropriate places ... >> It is a good thing. Very good. But I do not think all library writers are >> using it in correct places. But that's another problem. >> > > In Haskell it's even a solved one: use an appropriate typeclass. We have > several error-like typeclasses. Admittedly, if some library does not take > advantage of this your recourse may be to submit a patch. > > And you still seem to be fixated on the notion that Maybe is only for > errors. What exactly is the error in "user did not provide an optional > parameter"? > Indeed. I use Maybe for non-errors, namely optional values, all the time. To compare with some other languages: Maybe is like a nil vs. non-nil pointer. Either is like returning two values/a tuple of Foo and Error. (For that matter, I sometimes use Either when a value can be either something or the other, but neither of them are errors.) -------------- next part -------------- An HTML attachment was scrubbed... URL: From andreas.abel at ifi.lmu.de Thu Jan 9 18:39:43 2014 From: andreas.abel at ifi.lmu.de (Andreas Abel) Date: Thu, 09 Jan 2014 19:39:43 +0100 Subject: [Haskell-cafe] ANN: MiniAgda-0.2014.1.9 Toy language with dependent and sized types Message-ID: <52CEECEF.1010609@ifi.lmu.de> For what it's worth, I finally uploaded MiniAgda to hackage. If you want to play around with type-based termination and coinduction in a dependently-typed setting, try: cabal install MiniAgda Some examples and pointers to literature are (still) on my old homepage: http://www2.tcs.ifi.lmu.de/~abel/miniagda/ Source code and issue tracker are on the darcs hub: http://hub.darcs.net/abel/miniagda/ Have fun playing (or despair of the horrible error messages), and have a happy new year, Andreas -- Andreas Abel <>< Du bist der geliebte Mensch. From stephen.tetley at gmail.com Thu Jan 9 18:52:55 2014 From: stephen.tetley at gmail.com (Stephen Tetley) Date: Thu, 9 Jan 2014 18:52:55 +0000 Subject: [Haskell-cafe] Altering Class hierarchy In-Reply-To: <20140109184151.1a287d58@farka.eu> References: <20140109184151.1a287d58@farka.eu> Message-ID: The Functor-Applicative-Monad hierarchy change has been a difficult change _because_ Functor and Monad are primary parts to the Prelude (standard library). Individual projects don't change the standard library, so changing a class hierarchy is no more problematic than any other substantial / breaking change to a code base. Best wishes Stephen From carlo at carlo-hamalainen.net Thu Jan 9 19:00:15 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Thu, 09 Jan 2014 20:00:15 +0100 Subject: [Haskell-cafe] How to determine the right path to haddock html documentation? In-Reply-To: <52AEF81F.7010200@carlo-hamalainen.net> References: <52AB8130.3030903@carlo-hamalainen.net> <20131213222827.GA31144@sniper> <52AC6284.1080103@carlo-hamalainen.net> <20131214140215.GA970@sniper> <52AEF81F.7010200@carlo-hamalainen.net> Message-ID: <52CEF1BF.3040400@carlo-hamalainen.net> On 16/12/13 13:54, Carlo Hamalainen wrote: > For the benefit of the list archive, here is what I have worked out so > far. And here is what I've worked out since my last email. I learned more about the GHC API, read a bit more about how ghc-mod works, and came up with this prototype: https://github.com/carlohamalainen/ghc-imported-from Here is a screencast showing it in action with my forked version of ghcmod-vim: http://www.youtube.com/watch?v=VVc8uupYJGs (pick 720p otherwise the text is hard to read) -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From bgamari.foss at gmail.com Thu Jan 9 19:29:04 2014 From: bgamari.foss at gmail.com (Ben Gamari) Date: Thu, 09 Jan 2014 14:29:04 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52ced5fb.6d2a700a.56f3.4803@mx.google.com> Message-ID: <87mwj5lzsv.fsf@gmail.com> Brandon Allbery writes: > On Thu, Jan 9, 2014 at 12:11 PM, Ben Foppa wrote: > >> Aside from the point made about typeclass instances, I don't see an issue >> with: >> >> type Maybe = Either () >> >> nothing :: Maybe a >> nothing = Left () >> >> just :: a -> Maybe a >> just = Right >> > Not until you try to pattern match on it.... > Although with pattern synonyms[1][2] this will become possible if I'm not mistaken, pattern Nothing = Left () pattern Just a = Right a Cheers, - Ben [1] https://ghc.haskell.org/trac/ghc/ticket/5144 [2] https://ghc.haskell.org/trac/ghc/wiki/PatternSynonyms -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 489 bytes Desc: not available URL: From lightquake at amateurtopologist.com Thu Jan 9 20:57:58 2014 From: lightquake at amateurtopologist.com (Patrick Hurst) Date: Thu, 9 Jan 2014 15:57:58 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CEB728.8040807@gmail.com> References: <52CEB728.8040807@gmail.com> Message-ID: Why have Bool? Just let true = 1, false = 0, (||) = (+), (&&) = (*). Why have Ordering? Just use Integer and let lt = -1, eq = 0, gt = 1. Why have three-tuples (a, b, c)? Just use ((a, b), c). Why have Data.Map a b? Just use a -> Maybe b. You don't even need an Ord constraint any more! Why have Data.Set a? Just use a -> Bool (or, a -> Integer). For that matter, why use algebraic data types? data Person = Person String Int is isomorphic to type Person = (String, Int). On Thu, Jan 9, 2014 at 9:50 AM, Vlatko Basic wrote: > Hello Cafe, > > With my current knowledge of Haskell, I do not see why is there Maybe if > we have Either. > > For example, Functor and Monad instances (and many others) of Maybe and > Either are the same (except for fail). > > In other words, this should hold: > > Maybe a = Either String a -- String or something else > Nothing = Left "" > Just a = Right a > > > I'm curious to find out what was the reasoning to make Maybe? > What is the added value with introducing it? > In which situations the above substitution does not hold? > > > > Best regards, > > vlatko > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Thu Jan 9 22:56:37 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 09 Jan 2014 22:56:37 +0000 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> Message-ID: <52CF2925.1080502@fuuzetsu.co.uk> On 09/01/14 20:57, Patrick Hurst wrote: > Why have Bool? Just let true = 1, false = 0, (||) = (+), (&&) = (*). > > Why have Ordering? Just use Integer and let lt = -1, eq = 0, gt = 1. > > Why have three-tuples (a, b, c)? Just use ((a, b), c). > > Why have Data.Map a b? Just use a -> Maybe b. You don't even need an Ord > constraint any more! > > Why have Data.Set a? Just use a -> Bool (or, a -> Integer). > > For that matter, why use algebraic data types? data Person = Person String > Int is isomorphic to type Person = (String, Int). > > > Hey, you're right, I should have been using C all along! Thanks for showing me the light. -- Mateusz K. From bob at redivi.com Fri Jan 10 00:03:12 2014 From: bob at redivi.com (Bob Ippolito) Date: Thu, 9 Jan 2014 16:03:12 -0800 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: References: <52CC4DBA.2050907@gmail.com> <52CCBF89.6030503@gmail.com> <52CCC5BB.7080001@gmail.com> Message-ID: So I dug a bit deeper (trying N different ways to write the code, ThreadScope, etc.) and I have some good news some bad news. The good news is that I figured out how to fix it, and it's an "easy" fix. The bad news is that the fix is to compile it with GHC HEAD (~7.8, I built ec4af3f), which has the new Mio high-performance multicore IO manager [1]. Apparently the old IO manager wasn't well suited to this use case. With the latest GHC, the -threaded version outperforms the single threaded version, and the numbers for both are better than with GHC 7.6.3. I've updated the gist with a README that has some more details: https://gist.github.com/etrepum/8312165 [1] http://haskell.cs.yale.edu/wp-content/uploads/2013/08/hask035-voellmy.pdf -bob On Wed, Jan 8, 2014 at 7:50 AM, Bob Ippolito wrote: > I haven't yet been able to sort out the performance difference, and > probably won't have time to dig in deeper with profiling tools today. I've > put together a gist with all of the files and a cabal file so it's easy to > build with the right options. > > https://gist.github.com/etrepum/8312165 > > > On Tue, Jan 7, 2014 at 7:47 PM, Bob Ippolito wrote: > >> >> >> On Tuesday, January 7, 2014, Branimir Maksimovic wrote: >> >>> On 01/08/2014 04:15 AM, Bob Ippolito wrote: >>> >>> On Tuesday, January 7, 2014, Branimir Maksimovic wrote: >>> >>>> On 01/07/2014 09:39 PM, Bob Ippolito wrote: >>>> >>>>> Here's a much simpler implementation for that sort of pattern, using >>>>> channels to fan out work to threads. I added a dependency on Criterion >>>>> because getCPUTime is basically useless for this kind of measurement on Mac >>>>> OS X since it doesn't include the time that the process spent waiting on IO: >>>>> >>>> Great, thank you very much. You gave me material for learning ;) >>>> However, my version is significantly faster when compiling without >>>> -threaded. >>>> With -threaded option, your version is much faster than mine, but both >>>> are significantly slower >>>> then compile without -threaded. >>>> >>> >>> Happy to look into it, I didn't have time today to do benchmarks >>> (and Mac OS X is the worst platform to do this kind of testing on >>> regardless of language, its network stack is inconsistent at best). I need >>> to know more: >>> >>> How exactly are you compiling? >>> >>> >>> ghc-7.6.3 --make -O2 client.hs >>> >>> Which OS? >>> >>> >>> Ubuntu 13.10 with 3.13-rc7 kernel. >>> >>> What version of GHC and Haskell Platform? >>> >>> >>> bmaxa at maxa:~$ apt-cache policy haskell-platform >>> haskell-platform: >>> Installed: 2013.2.0.0 >>> Candidate: 2013.2.0.0 >>> Version table: >>> *** 2013.2.0.0 0 >>> 500 http://archive.ubuntu.com/ubuntu/ saucy/universe amd64 >>> Packages >>> 100 /var/lib/dpkg/status >>> >>> >>> What is the exact command line you execute it with? >>> >>> >>> time ./client maxa 5055 1000 100000 >>> >> >> What happens if you add +RTS -N to the end of that command line? >> >> >>> >>> >>> What timings do you get? >>> >>> with your version: >>> real 0m4.235s >>> user 0m1.589s >>> sys 0m2.642s >>> >>> with my version >>> real 0m3.010s >>> user 0m0.590s >>> sys 0m2.417s >>> that is, of course, without -threaded >>> >>> What's the code for the server are you connecting to? >>> >>> import Network (listenOn,PortID(..)) >>> import Network.Socket (accept,close) >>> import Network.Socket.ByteString >>> import System.Environment >>> import Control.Concurrent (forkIO) >>> >>> main = do >>> n <- getArgs >>> let nn = (read.head) n :: Int >>> putStrLn $ "Listening on " ++ show nn >>> sock <- listenOn $ PortNumber $ fromIntegral nn >>> serve sock >>> >>> serve sock = do >>> (s,_) <- accept sock >>> forkIO $ process s >>> serve sock >>> >>> process sock = do >>> buf <- recv sock 1024 >>> sendAll sock buf >>> close sock >>> >>> Loopback, local network, or internet? >>> >>> >>> loopback. Testing is on same computer. >>> >>> Thanks! >>> >> >> Great, I'll look closer later tonight or tomorrow morning. >> >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From branimir.maksimovic at gmail.com Fri Jan 10 00:13:08 2014 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Fri, 10 Jan 2014 01:13:08 +0100 Subject: [Haskell-cafe] Slow mvar when compiled with threaded In-Reply-To: References: <52CC4DBA.2050907@gmail.com> <52CCBF89.6030503@gmail.com> <52CCC5BB.7080001@gmail.com> Message-ID: <52CF3B14.7020304@gmail.com> On 01/10/2014 01:03 AM, Bob Ippolito wrote: > > The bad news is that the fix is to compile it with GHC HEAD (~7.8, I > built ec4af3f), which has the new Mio high-performance multicore IO > manager [1]. Apparently the old IO manager wasn't well suited to this > use case. > > With the latest GHC, the -threaded version outperforms the single > threaded version, and the numbers for both are better than with GHC 7.6.3. > Thanks. Glad to hear that! From jwlato at gmail.com Fri Jan 10 00:17:54 2014 From: jwlato at gmail.com (John Lato) Date: Thu, 9 Jan 2014 16:17:54 -0800 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CED39A.4060505@artyom.me> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> Message-ID: On Thu, Jan 9, 2014 at 8:51 AM, Artyom Kazak wrote: > > On 01/09/2014 08:36 PM, Vlatko Basic wrote: > >> But instance declarations wouldn't be needed because we already have all >> the instances for Either. The point would be to have them unified. >> > Consider a generic Show instance for Either ? there?s no way? to make it > behave differently for Either () (or Maybe if it was a type synonym). I > think there are other cases in which we want Maybe to behave differently > from Either, but I can?t think of any on the spot. > > ? this point also applies to String, which is a type synonym for [Char] ? > and it was solved somewhat inelegantly by adding an additional method to > Show typeclass *specifically* for showing lists of things. I think this is a really important point. If I may go further, it's arguable that 'type String = [Char]' was a poor decision, and one of the arguments is that it's not possible to make different instances for String and [a] (hence the showsList issue). Also, due to laziness, Either () a is bigger than Maybe a. It should be 'Either Void a'. But Void has only recently been added to the standard-ish library, which means if we'd used Either () from the start now we'd be stuck with the wrong type. I'd rather have a separate Maybe that does exactly what it's meant to. John L. -------------- next part -------------- An HTML attachment was scrubbed... URL: From yom at artyom.me Fri Jan 10 01:29:07 2014 From: yom at artyom.me (Artyom Kazak) Date: Fri, 10 Jan 2014 05:29:07 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> Message-ID: <52CF4CE3.2010502@artyom.me> On 01/10/2014 04:17 AM, John Lato wrote: > I think this is a really important point. If I may go further, it's > arguable that 'type String = [Char]' was a poor decision, and one of > the arguments is that it's not possible to make different instances > for String and [a] (hence the showsList issue). Actually, I think it?s an instance of a bigger problem: *newtypes aren?t as transparent as they should?ve been*. The very first thing a beginner is told about newtypes is that they bear no additional runtime cost at all ? which, in fact, hasn?t been strictly true until the recent introduction of Roles ? but the first thing they learn *by theirself* is that newtypes are only ?free? for the computer, not for the programmer! Imagine an alternative Prelude in which `String` is a newtype for `[Char]` and not a type synonym: you wouldn?t be able to `map` over it without deconstructing it first, or `reverse` it, or even compute its `length`... And having to type `f (Str s)` instead of `f s` would already discourage people enough that most of them would be trying to avoid Strings, even if only subconsciously. General tendency to follow the path of least resistance is probably the reason why newtypes aren?t used as often as they should be. Have there been any proposals aiming to solve this issue? (A quick search didn?t bring up anything, but maybe I was just searching for a wrong thing.) From christian at ponies.io Fri Jan 10 07:22:45 2014 From: christian at ponies.io (christian at ponies.io) Date: Fri, 10 Jan 2014 18:22:45 +1100 Subject: [Haskell-cafe] ANN: xxHash, fast, high quality, non-cryptographic checksums. Message-ID: <20140110072245.GA5579@cucumber.bridge.anchor.net.au> I've just finished implementing a haskell version of the xxHash algorithm, which is documented briefly here (mostly in code): https://code.google.com/p/xxhash/ The haskell version is *almost* as fast as C and allows the generation of a better quality checksum than adler32, in less time. Benchmarks are here: http://ponies.io/posts/2013-01-10-xxhash.html Code is here: https://github.com/christian-marie/xxhash Critique welcome! -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 836 bytes Desc: not available URL: From jwlato at gmail.com Fri Jan 10 07:36:13 2014 From: jwlato at gmail.com (John Lato) Date: Thu, 9 Jan 2014 23:36:13 -0800 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CF4CE3.2010502@artyom.me> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> Message-ID: On Thu, Jan 9, 2014 at 5:29 PM, Artyom Kazak wrote: > > On 01/10/2014 04:17 AM, John Lato wrote: > >> I think this is a really important point. If I may go further, it's >> arguable that 'type String = [Char]' was a poor decision, and one of the >> arguments is that it's not possible to make different instances for String >> and [a] (hence the showsList issue). >> > Actually, I think it?s an instance of a bigger problem: *newtypes aren?t > as transparent as they should?ve been*. The very first thing a beginner is > told about newtypes is that they bear no additional runtime cost at all ? > which, in fact, hasn?t been strictly true until the recent introduction of > Roles ? but the first thing they learn *by theirself* is that newtypes are > only ?free? for the computer, not for the programmer! > > Imagine an alternative Prelude in which `String` is a newtype for `[Char]` > and not a type synonym: you wouldn?t be able to `map` over it without > deconstructing it first, or `reverse` it, or even compute its `length`... > And having to type `f (Str s)` instead of `f s` would already discourage > people enough that most of them would be trying to avoid Strings, even if > only subconsciously. > > General tendency to follow the path of least resistance is probably the > reason why newtypes aren?t used as often as they should be. Have there been > any proposals aiming to solve this issue? (A quick search didn?t bring up > anything, but maybe I was just searching for a wrong thing.) > The programmer overhead from newtypes is greater than I would like, even as minimal as it is. I find that using isomorphisms from the lens package goes a long way to reducing the programmer overhead from using newtypes. I recently did a very lens-heavy project, and I found that the ease of working with newtype'd values via isomorphisms made me much more likely to define newtypes in the first place. So that's one solution, YMMV. Of course, that's assuming that String would just be a newtype instead of a type alias. If it were an actual abstract type, then we couldn't use map/fmap at all. However, we've had type class based solutions for that problem for some time now, e.g. the ListLike package, and newer alternatives like mono-traversable. (Incidentally, I've been toying with the idea of making ListLike depend on mono-traversable. It would basically just be an API re-skinning, plus we could have more efficient definitions of some functions). An abstract String would also be better than our current situation because Data.List functions on Strings are just plain wrong anyway. Simple example: what should be the reverse of "This is two lines\r\nbecause Windows!\r\n"? It gets even more fun with unicode. Oddly, I was just looking at http://msmvps.com/blogs/jon_skeet/archive/2009/11/02/omg-ponies-aka-humanity-epic-fail.aspx 10 minutes ago. (Of course if String were properly abstract, you could still define an isomorphism between String and [Char] somehow. And somewhere in Turkey a tier-1 techie cries out...) -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Fri Jan 10 09:55:35 2014 From: difrumin at gmail.com (Dan Frumin) Date: Fri, 10 Jan 2014 13:55:35 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> Message-ID: <280FAC0C-DDBF-4077-8EE1-7CC4514432F5@gmail.com> > On 10 Jan 2014, at 04:17, John Lato wrote: > >> On Thu, Jan 9, 2014 at 8:51 AM, Artyom Kazak wrote: >> >>> On 01/09/2014 08:36 PM, Vlatko Basic wrote: >>> But instance declarations wouldn't be needed because we already have all the instances for Either. The point would be to have them unified. >> Consider a generic Show instance for Either ? there?s no way? to make it behave differently for Either () (or Maybe if it was a type synonym). I think there are other cases in which we want Maybe to behave differently from Either, but I can?t think of any on the spot. >> >> ? this point also applies to String, which is a type synonym for [Char] ? and it was solved somewhat inelegantly by adding an additional method to Show typeclass *specifically* for showing lists of things. > > I think this is a really important point. If I may go further, it's arguable that 'type String = [Char]' was a poor decision, and one of the arguments is that it's not possible to make different instances for String and [a] (hence the showsList issue). > > Also, due to laziness, Either () a is bigger than Maybe a. It should be 'Either Void a'. But Void has only recently been added to the standard-ish library, which means if we'd used Either () from the start now we'd be stuck with the wrong type. I'd rather have a separate Maybe that does exactly what it's meant to. > Why is 'Either Void a' isomorphic to 'Maybe a'. What would 'Nothing' be in this case? Either () a is the correct version. Roughly speaking 'Maybe a' contains |a|+1 values while Either Void a contains only |a| values, since you can not construct any Left's > John L. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Fri Jan 10 09:56:59 2014 From: difrumin at gmail.com (Dan Frumin) Date: Fri, 10 Jan 2014 13:56:59 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CED3D9.5000108@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBB44.5070003@gmx.de> <52CEBFC2.3080900@gmail.com> <52CECD96.6010909@gmail.com> <52CED3D9.5000108@gmail.com> Message-ID: <1B7478E9-FFA5-4913-B339-37EFBE689EA7@gmail.com> > On 09 Jan 2014, at 20:52, Vlatko Basic wrote: > > Hi Brandon, > > > ... you did not think out your program sufficiently beforehand ... > Yes, that is quite possible. I consider myself an FP beginner still. > I encountered that mixing Maybe and Either problem few months ago and I think it was about using parseUri and simpleHTTP and I had to `case` them separately to provide a meaningful error message. Haven't been able to simply chain them. In other words, it was not a nice looking function. > Maybe today I'd write it differently. I suggest taking a loon at the 'errors' package mentioned earlier in this thread, it somewhat simplified my issues with unifying Maybe/Either/EitherT > > > ... what exactly is the problem with using appropriate data types in appropriate places ... > It is a good thing. Very good. But I do not think all library writers are using it in correct places. But that's another problem. > > > vlatko > >> -------- Original Message -------- >> Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? >> From: Brandon Allbery >> To: Vlatko Ba?i? >> Cc: Johannes Erber , "haskell-cafe at haskell.org" >> Date: 09.01.2014 17:32 >> >> >> On Thu, Jan 9, 2014 at 11:25 AM, Vlatko Basic wrote: >>> > ... is letting the programmer do what they need to do with a minimum of fuss or extra work ... >>> But doesn't the need of mixing Maybe and Either cause more work for the programmer? Programmer of library, or programmer using the library? >> >> Arguably if you need to switch from Maybe to Either then you did not think out your program sufficiently beforehand. And if you did think it out, what exactly is the problem with using appropriate data types in appropriate places? >> >> -- >> brandon s allbery kf8nh sine nomine associates >> allbery.b at gmail.com ballbery at sinenomine.net >> unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From nickolay.kudasov at gmail.com Fri Jan 10 10:10:37 2014 From: nickolay.kudasov at gmail.com (Nickolay Kudasov) Date: Fri, 10 Jan 2014 14:10:37 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <280FAC0C-DDBF-4077-8EE1-7CC4514432F5@gmail.com> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <280FAC0C-DDBF-4077-8EE1-7CC4514432F5@gmail.com> Message-ID: Actually, Left absurd is perfect Nothing (mind laziness!). On the other hand, with Either () a you have 2 different Nothings: Left ()and Left _|_. 2014/1/10 Dan Frumin > > > On 10 Jan 2014, at 04:17, John Lato wrote: > > On Thu, Jan 9, 2014 at 8:51 AM, Artyom Kazak wrote: > >> >> On 01/09/2014 08:36 PM, Vlatko Basic wrote: >> >>> But instance declarations wouldn't be needed because we already have all >>> the instances for Either. The point would be to have them unified. >>> >> Consider a generic Show instance for Either ? there?s no way? to make it >> behave differently for Either () (or Maybe if it was a type synonym). I >> think there are other cases in which we want Maybe to behave differently >> from Either, but I can?t think of any on the spot. >> >> ? this point also applies to String, which is a type synonym for [Char] ? >> and it was solved somewhat inelegantly by adding an additional method to >> Show typeclass *specifically* for showing lists of things. > > > I think this is a really important point. If I may go further, it's > arguable that 'type String = [Char]' was a poor decision, and one of the > arguments is that it's not possible to make different instances for String > and [a] (hence the showsList issue). > > Also, due to laziness, Either () a is bigger than Maybe a. It should be > 'Either Void a'. But Void has only recently been added to the > standard-ish library, which means if we'd used Either () from the start now > we'd be stuck with the wrong type. I'd rather have a separate Maybe that > does exactly what it's meant to. > > > Why is 'Either Void a' isomorphic to 'Maybe a'. What would 'Nothing' be in > this case? > > Either () a is the correct version. Roughly speaking 'Maybe a' contains > |a|+1 values while Either Void a contains only |a| values, since you can > not construct any Left's > > > John L. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Fri Jan 10 10:12:00 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Fri, 10 Jan 2014 11:12:00 +0100 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> Message-ID: <52CFC770.3050202@gmail.com> An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Jan 10 15:28:35 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 10 Jan 2014 10:28:35 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CFC770.3050202@gmail.com> References: <52CEB728.8040807@gmail.com> <52CFC770.3050202@gmail.com> Message-ID: On Fri, Jan 10, 2014 at 5:12 AM, Vlatko Basic wrote: > However, what I was trying to find out were the reasons for the way it is > *implemented*. When I look at the code for Maybe and Either, it seems to me > like the violation of the "do not repeat yourself" principle. That > principle is taken rather seriously in Haskell. Even HLint has "Reduce > duplication" suggestion. *Some* of the code I looked at appears the same. > Less so than you'd think, or there wouldn't be so much resistance to (for example) replacing list-specific stuff in Prelude with the more general Foldable/Traversable ones. The pressure for simple and easy to understand stuff (like Maybe vs. Either () or whatever) turns out to be stronger. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Fri Jan 10 18:19:45 2014 From: jwlato at gmail.com (John Lato) Date: Fri, 10 Jan 2014 10:19:45 -0800 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <52CFC770.3050202@gmail.com> References: <52CEB728.8040807@gmail.com> <52CFC770.3050202@gmail.com> Message-ID: Hi Vlatko, Apologies for taking part in the de-railing of this topic. I can't answer authoritatively, however I do have a challenge: Try to implement a module that exposes the same interface as Data.Maybe but defines 'newtype Maybe a = Maybe {unMaybe :: Either () a}'. We're targeting base as of several years ago, so you can't use any packages outside base or any GHC extensions. In particular, you can't use GeneralizedNewtypeDeriving or any of the 'Derive*' extensions. See how much repetition you're able to avoid. John L. On Fri, Jan 10, 2014 at 2:12 AM, Vlatko Basic wrote: > Hi Patrick, > > Due to my poor wording of the question (and the choice of String, instead > of unit or Void, for Left), this discussion went the wrong way. Completely. > I also noticed that some of my comments went in the "usage" direction. > > My intent was to ask the question about implementation of Maybe, *not it's > usage*. Seems that most people understood that I'm arguing whether the > Maybe is needed and/or should it be switched with Either. I'm not. > > However, what I was trying to find out were the reasons for the way it is > *implemented*. When I look at the code for Maybe and Either, it seems to me > like the violation of the "do not repeat yourself" principle. That > principle is taken rather seriously in Haskell. Even HLint has "Reduce > duplication" suggestion. *Some* of the code I looked at appears the same. > > I wanted to find out what were the reasons/restrictions/functionalities > why Maybe wasn't (somehow) built on Either, so there will be less code > duplication. > > The first reason would be that there are no data constructor synonyms, so > it will not be elegant (although, that might be solved with > PatternSynonyms, as Ben Gamari suggested). > > The other reason, that probably couldn't be solved, was pointed out by > Nickolay Kudasov, and that is the generic functions like Show (for Left > String) and probably more, like Read. > > > vlatko > > -------- Original Message -------- > Subject: Re: [Haskell-cafe] Why Maybe exists if there is Either? > From: Patrick Hurst > To: vlatko.basic at gmail.com > Cc: "haskell-cafe at haskell.org" > > Date: 09.01.2014 21:57 > > > Why have Bool? Just let true = 1, false = 0, (||) = (+), (&&) = (*). > > Why have Ordering? Just use Integer and let lt = -1, eq = 0, gt = 1. > > Why have three-tuples (a, b, c)? Just use ((a, b), c). > > Why have Data.Map a b? Just use a -> Maybe b. You don't even need an Ord > constraint any more! > > Why have Data.Set a? Just use a -> Bool (or, a -> Integer). > > For that matter, why use algebraic data types? data Person = Person > String Int is isomorphic to type Person = (String, Int). > > > > On Thu, Jan 9, 2014 at 9:50 AM, Vlatko Basic wrote: > >> Hello Cafe, >> >> With my current knowledge of Haskell, I do not see why is there Maybe if >> we have Either. >> >> For example, Functor and Monad instances (and many others) of Maybe and >> Either are the same (except for fail). >> >> In other words, this should hold: >> >> Maybe a = Either String a -- String or something else >> Nothing = Left "" >> Just a = Right a >> >> >> I'm curious to find out what was the reasoning to make Maybe? >> What is the added value with introducing it? >> In which situations the above substitution does not hold? >> >> >> >> Best regards, >> >> vlatko >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Sat Jan 11 18:44:49 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Sat, 11 Jan 2014 13:44:49 -0500 Subject: [Haskell-cafe] Licenses and dependencies Message-ID: Many permissive licenses (I'm specifically looking at MIT and BSD3) include a clause that the license file must be included in distributions of the source or the binary. It seems to me that if I have a project on Github, that qualifies as redistribution of the source. My questions are thus: Do I need to include the license files from all my dependencies in my Github repository? Does having them listed as dependencies in my .cabal file "implicitly" include them? Does making a project "PublicDomain" only refer to the code contained in that project, or would it (unintentionally and unlawfully) give distributors of that source code the freedom to not include the BSD3/MIT license files from dependencies? Essentially my goal is to waive all intellectual property rights to most of my Haskell projects, to the extent that, were I to unintentionally sign away my intellectual property, my open-source contributions would be safe - what's the easiest way to do this? Thanks, Ben Foppa -------------- next part -------------- An HTML attachment was scrubbed... URL: From mukeshtiwari.iiitm at gmail.com Sat Jan 11 19:12:49 2014 From: mukeshtiwari.iiitm at gmail.com (mukesh tiwari) Date: Sun, 12 Jan 2014 00:42:49 +0530 Subject: [Haskell-cafe] Parse Error ( Parsec ) Message-ID: Hello Cafe, I am trying to write a parser for propositional logic[1]. It's working fine for every input except equivalence ( <=> ). *Main> calculator "a=>b" Imp (Lit 'a') (Lit 'b') *Main> calculator "a<=b" Red (Lit 'a') (Lit 'b') *Main> calculator "a<=>b" *** Exception: failed to parse I think, the reason is parser taking equivalence ( <=> ) as reduction ( <= ) and next character is '>' so it is parse error . If I remove both implication and reduction then equivalence is working fine. *Main> calculator "a<=>b" Eqi (Lit 'a') (Lit 'b') Could some please tell me how to solve this problem. I also tried fixity declaration but got this error LogicPraser.hs:12:10: The fixity signature for `<=>' lacks an accompanying binding -Mukesh Tiwari [1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html {-# LANGUAGE NoMonomorphismRestriction #-} import Text.Parsec.Token import Text.Parsec.Prim import Text.Parsec.Char import Text.Parsec.Expr import Text.Parsec.Combinator import Text.Parsec.Language import Control.Applicative hiding ( ( <|> ) , many ) import Data.Maybe ( fromJust ) --infixl 9 <=> data LExpr = Lit Char | Not LExpr | And LExpr LExpr | Or LExpr LExpr | Imp LExpr LExpr -- (=>) | Red LExpr LExpr -- ( <= ) | Eqi LExpr LExpr -- ( <=> ) deriving Show exprCal = buildExpressionParser table atom table = [ [ Prefix ( Not <$ string "~" ) ] , [ Infix ( And <$ string "&" ) AssocLeft ] , [ Infix ( Or <$ string "|" ) AssocLeft ] , [ Infix ( Imp <$ string "=>" ) AssocLeft , Infix ( Red <$ string "<=" ) AssocLeft , Infix ( Eqi <$ string "<=>" ) AssocLeft ] ] atom = char '(' *> exprCal <* char ')' <|> ( Lit <$> letter ) calculator :: String -> LExpr calculator expr = case parse exprCal "" expr of Left msg -> error "failed to parse" Right ( val ) -> val ~ -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Sat Jan 11 19:26:56 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sat, 11 Jan 2014 19:26:56 +0000 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: References: Message-ID: <52D19B00.7080900@fuuzetsu.co.uk> Disclaimer: I'm not a lawyer. On 11/01/14 18:44, Ben Foppa wrote: > Many permissive licenses (I'm specifically looking at MIT and BSD3) include > a clause that the license file must be included in distributions of the > source or the binary. It seems to me that if I have a project on Github, > that qualifies as redistribution of the source. My questions are thus: You can put things up on GitHub without a license and legally, no one is allowed to do anything with it. > Do I need to include the license files from all my dependencies in my > Github repository? Only if you include the source of dependencies themselves, so most likely you don't have to. > Does having them listed as dependencies in my .cabal file "implicitly" > include them? I'm unsure. Considering you're referring to packages by name, one would imagine that you're restricting the project to that particular source. On the other hand, anyone is free to come in and replace dependencies with their own source, under their own license. I think you're safe releasing code under whatever license you want as long as: * You don't release dependencies with it * You don't build the project and distribute it Once you distribute the binary, you have probably pulled in and used the licensed libraries (unless replaced) so you're subject to the strongest license used. So overall, I think you're safe publishing under whatever license suits you and it's up to the programmer using your code to decide whether or not they want to build and/or distribute it as-is. > Does making a project "PublicDomain" only refer to the code contained in > that project, or would it (unintentionally and unlawfully) give > distributors of that source code the freedom to not include the BSD3/MIT > license files from dependencies? Making your code public domain would not affect the dependencies at all, after all, someone can come later, take half of your code and use it for something totally different. > Essentially my goal is to waive all intellectual property rights to most of > my Haskell projects, to the extent that, were I to unintentionally sign > away my intellectual property, my open-source contributions would be safe - > what's the easiest way to do this? I think you'll be fine just choosing the PublicDomain license option. Things you can't do with such an option: * bundle other people's code which isn't under public domain * somehow enforce that only certain libraries will run with your program: the user should be able to replace the BSD3 licensed dependencies with their own if they want to I think in the end, the fact that pretty much every package ever depends on ?base? which is BSD3 and PublicDomain option exists in Cabal should be convincing enough that you are in fact able to publish your part of the code under more lenient license. > Thanks, > Ben Foppa If anything's wrong in my post, I hope someone can correct me. -- Mateusz K. From fuuzetsu at fuuzetsu.co.uk Sat Jan 11 19:32:03 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sat, 11 Jan 2014 19:32:03 +0000 Subject: [Haskell-cafe] Parse Error ( Parsec ) In-Reply-To: References: Message-ID: <52D19C33.5030407@fuuzetsu.co.uk> On 11/01/14 19:12, mukesh tiwari wrote: > Hello Cafe, > I am trying to write a parser for propositional logic[1]. It's working > fine for every input except equivalence ( <=> ). > > > *Main> calculator "a=>b" > Imp (Lit 'a') (Lit 'b') > *Main> calculator "a<=b" > Red (Lit 'a') (Lit 'b') > *Main> calculator "a<=>b" > *** Exception: failed to parse > > > I think, the reason is parser taking equivalence ( <=> ) as reduction ( <= > ) and next character is '>' so it is parse error . If I remove both > implication and reduction then equivalence is working fine. > > *Main> calculator "a<=>b" > Eqi (Lit 'a') (Lit 'b') > > Could some please tell me how to solve this problem. I also tried fixity > declaration but got this error > LogicPraser.hs:12:10: > The fixity signature for `<=>' lacks an accompanying binding > > -Mukesh Tiwari > > > [1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html > [snip] Hi, I have not studied your code but if the problem is what you describe it, you should try with back-tracking so that the parser can retry when it fails. I believe Parsec offers the ?try? function for this. Regarding your ?infix <=>?, of course that would not work. It's a Haskell declaration, not something Parsec does. You're getting an error because you're saying that ?<=>? has left fixity of 9 but then you aren't giving a definition for ?<=>?. The "<=>" you're parsing has nothing to do with this. Haskell sees the fixity declaration and then doesn't see you defining the ?<=>? operator anywhere so it complains. -- Mateusz K. From hilco.wijbenga at gmail.com Sat Jan 11 19:42:15 2014 From: hilco.wijbenga at gmail.com (Hilco Wijbenga) Date: Sat, 11 Jan 2014 11:42:15 -0800 Subject: [Haskell-cafe] Parse Error ( Parsec ) In-Reply-To: References: Message-ID: On 11 January 2014 11:12, mukesh tiwari wrote: > table = [ [ Prefix ( Not <$ string "~" ) ] > , [ Infix ( And <$ string "&" ) AssocLeft ] > , [ Infix ( Or <$ string "|" ) AssocLeft ] > , [ Infix ( Imp <$ string "=>" ) AssocLeft > , Infix ( Red <$ string "<=" ) AssocLeft > , Infix ( Eqi <$ string "<=>" ) AssocLeft Have you tried changing the order here? I would expect the "<=>" check to have to come before the "<=" check? I haven't played with this so I'm just guessing. From creswick at gmail.com Sat Jan 11 19:49:46 2014 From: creswick at gmail.com (Rogan Creswick) Date: Sat, 11 Jan 2014 11:49:46 -0800 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: <52D19B00.7080900@fuuzetsu.co.uk> References: <52D19B00.7080900@fuuzetsu.co.uk> Message-ID: On Sat, Jan 11, 2014 at 11:26 AM, Mateusz Kowalczyk wrote: > Disclaimer: I'm not a lawyer. > I'm also not a lawyer. So overall, I think you're safe publishing under whatever license suits > you and it's up to the programmer using your code to decide whether or > not they want to build and/or distribute it as-is. I can't comment on the legality of this; it sounds like it may be correct in a technical sense, but in any case, I would like to plead that you /do not do this/, for one reason: Someone may want to use your project (and, transitively, the dependencies you rely on) in a binary distribution someday, and it's unlikely that they will think to check all the licenses all the way down. Granted, that *is* their responsibility, but I think it's irresponsible to create a product that "silently" causes a license violation based on how the compiled result is used. Please make a good faith effort to keep your software license compatible with the licenses on your dependencies. This is just my perspective on the question, and not something I'm interested in debating, but I wanted to put it out there since it will impact the usability of your software in some situations. --Rogan > Does making a project "PublicDomain" only refer to the code contained in > > that project, or would it (unintentionally and unlawfully) give > > distributors of that source code the freedom to not include the BSD3/MIT > > license files from dependencies? > > Making your code public domain would not affect the dependencies at all, > after all, someone can come later, take half of your code and use it for > something totally different. > > > Essentially my goal is to waive all intellectual property rights to most > of > > my Haskell projects, to the extent that, were I to unintentionally sign > > away my intellectual property, my open-source contributions would be > safe - > > what's the easiest way to do this? > > I think you'll be fine just choosing the PublicDomain license option. > Things you can't do with such an option: > > * bundle other people's code which isn't under public domain > * somehow enforce that only certain libraries will run with your > program: the user should be able to replace the BSD3 licensed > dependencies with their own if they want to > > I think in the end, the fact that pretty much every package ever depends > on ?base? which is BSD3 and PublicDomain option exists in Cabal should > be convincing enough that you are in fact able to publish your part of > the code under more lenient license. > > > Thanks, > > Ben Foppa > > If anything's wrong in my post, I hope someone can correct me. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Sat Jan 11 20:31:56 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Sat, 11 Jan 2014 15:31:56 -0500 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: References: <52D19B00.7080900@fuuzetsu.co.uk> Message-ID: Thanks for your help, everyone! It sounds like leaving my open-source projects licensed MIT (probably) protects them from retroactive ownership by a vaguely-worded contract. Just as a disclaimer for all past, present, future replies: No information from this thread shall be construed as legal advice; I'm seeking to understand the *opinions* on what the law appears to be. On Sat, Jan 11, 2014 at 2:49 PM, Rogan Creswick wrote: > On Sat, Jan 11, 2014 at 11:26 AM, Mateusz Kowalczyk < > fuuzetsu at fuuzetsu.co.uk> wrote: > >> Disclaimer: I'm not a lawyer. >> > > I'm also not a lawyer. > > So overall, I think you're safe publishing under whatever license suits >> you and it's up to the programmer using your code to decide whether or >> not they want to build and/or distribute it as-is. > > > I can't comment on the legality of this; it sounds like it may be correct > in a technical sense, but in any case, I would like to plead that you /do > not do this/, for one reason: > > Someone may want to use your project (and, transitively, the dependencies > you rely on) in a binary distribution someday, and it's unlikely that they > will think to check all the licenses all the way down. > > Granted, that *is* their responsibility, but I think it's irresponsible to > create a product that "silently" causes a license violation based on how > the compiled result is used. > > Please make a good faith effort to keep your software license compatible > with the licenses on your dependencies. > > This is just my perspective on the question, and not something I'm > interested in debating, but I wanted to put it out there since it will > impact the usability of your software in some situations. > > --Rogan > > > Does making a project "PublicDomain" only refer to the code contained in >> > that project, or would it (unintentionally and unlawfully) give >> > distributors of that source code the freedom to not include the BSD3/MIT >> > license files from dependencies? >> >> Making your code public domain would not affect the dependencies at all, >> after all, someone can come later, take half of your code and use it for >> something totally different. >> >> > Essentially my goal is to waive all intellectual property rights to >> most of >> > my Haskell projects, to the extent that, were I to unintentionally sign >> > away my intellectual property, my open-source contributions would be >> safe - >> > what's the easiest way to do this? >> >> I think you'll be fine just choosing the PublicDomain license option. >> Things you can't do with such an option: >> >> * bundle other people's code which isn't under public domain >> * somehow enforce that only certain libraries will run with your >> program: the user should be able to replace the BSD3 licensed >> dependencies with their own if they want to >> >> I think in the end, the fact that pretty much every package ever depends >> on ?base? which is BSD3 and PublicDomain option exists in Cabal should >> be convincing enough that you are in fact able to publish your part of >> the code under more lenient license. >> >> > Thanks, >> > Ben Foppa >> >> If anything's wrong in my post, I hope someone can correct me. >> >> -- >> Mateusz K. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mwm at mired.org Sat Jan 11 21:03:55 2014 From: mwm at mired.org (Mike Meyer) Date: Sat, 11 Jan 2014 15:03:55 -0600 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: <52D1A6E2.1090700@fuuzetsu.co.uk> References: <52D19B00.7080900@fuuzetsu.co.uk> <52D1A6E2.1090700@fuuzetsu.co.uk> Message-ID: On Sat, Jan 11, 2014 at 2:17 PM, Mateusz Kowalczyk wrote: > Hey, > Perhaps you should have CC'd the list as well for this reply. Oops. I've moved it back, since you suggested it. > On 11/01/14 20:04, Mike Meyer wrote: > >> On 11/01/14 18:44, Ben Foppa wrote: > >> Once you distribute the binary, you have probably pulled in and used the > >> licensed libraries (unless replaced) so you're subject to the strongest > >> license used. > > > > Not "strongest", but all. Well, the GPL licenses sort of "stack", > > since they explicitly allow you to use newer (and usually stronger) > > versions of themselves, but other license don't. > > > > The GNU project provides a description of many of the available > > licenses at: http://www.gnu.org/licenses/license-list.html, including > > compatibility notes. > Right, all, but what this usually entices is that the strongest one > prevails. For example, code with BSD3 and GPLv3 sources will have to > be released under GPLv3 as a whole (although each part is still what > it was licensed under individually). I worked under the assumption > that all dependencies are have compatible licenses (and their > dependencies too &c). No, it's not a contest. You *have* to abide by them all. If you're dealing with the GPL, it may look like the "strongest" prevails, but that's a property of the GPL. It specifically requires any derived work be distributed under the GPL, with no added restrictions. So a compatible license will have no extra restrictions, and appear "weaker". A "stronger" license with extra restrictions (like the 4-clause BSD license) will be incompatible with the GPL, so you can't distributed a derived work at all. If you take the GPL out of the mix, and wanted to distributed a work derived from something covered by (for instance) BSD4 and the CPL - well, that would be fine, because I don't think either prevents the restrictions in the other. But the derived work would be covered by both, not just the stronger of the two (whichever that is). Your usual case may well be GPL'ed code. I happen to work with BSD-licensed code bases more often than not. > >> I think you'll be fine just choosing the PublicDomain license option. [...] > >> Things you can't do with such an option: > >> > >> * bundle other people's code which isn't under public domain > > > > This is vague. If your bundle is a single work (like a static binary), > > then it has to obey all the applicable licenses, and probably can't be > > in the public domain. If it's a collection of works, then it can > > include anything you want, so long as each element in the collection > > obeys it's license. > > I meant bundle as in the repository/source tarball/however you publish > your source, _not_ the binary (I explicitly mention binary somewhere else). In that case, you're perfectly free to include sources with other licenses in the tarball. You just need to make sure you follow their license for their entry in the collection. It's well-established that a simple collection of works (a tarball, etc.) is not a derived work. > >> * somehow enforce that only certain libraries will run with your > >> program: the user should be able to replace the BSD3 licensed > >> dependencies with their own if they want to > > Is there any license that enforces that? That seems more like a > > technical issue than a legal one. Though if you're dynamically linking > > the libraries, things get incredibly confusing. > LGPL, does it not? It even outlines what constitutes as a prevention > of other libraries. I believe the LGPL does just the opposite - it *permits* linking with non-free code without creating a derived work. I think I may not be understanding what you're saying, though. I think you're implying that it's possible to force users to use specific libraries. That is indeed the case - you could write a modified version of the GPL that says "You may only redistribute works derived from my project if they use my libraries". You are correct in that you can't do that if you place the work in the public domain. On the other hand, I don't know of any commonly used open source library that does that. From fuuzetsu at fuuzetsu.co.uk Sat Jan 11 21:17:25 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sat, 11 Jan 2014 21:17:25 +0000 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: References: <52D19B00.7080900@fuuzetsu.co.uk> <52D1A6E2.1090700@fuuzetsu.co.uk> Message-ID: <52D1B4E5.5000308@fuuzetsu.co.uk> Alright, thanks for some clarifications. I agreed with everything you said. -- Mateusz K. From carter.schonwald at gmail.com Sat Jan 11 23:06:55 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 11 Jan 2014 18:06:55 -0500 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: <52D1B4E5.5000308@fuuzetsu.co.uk> References: <52D19B00.7080900@fuuzetsu.co.uk> <52D1A6E2.1090700@fuuzetsu.co.uk> <52D1B4E5.5000308@fuuzetsu.co.uk> Message-ID: you can absolutely write BSD licensed ffi bindings to a GPL library, however, the user of the library will be subject to the fact that the underlying object code is derived from GPL code, But that does not mean that client ffi has to be GPL. A good example of this might an api that can connect to backends written under various licenses (bsd, gpl, proprietary etc). A good example of such a lib is SciPy https://github.com/scipy/scipy/blob/master/LICENSE.txt GPL (along with many other licenses) have never been tested in court. Additionally, if as an IP laywer, they'll say that the precise interpretation of the GPL licenses is unclear (but that the FSF's interpretation of the GPL is overreaching and requires magical powers beyond the scope of copyright law) You can write code in any license you want, and you should! Just because a lib dep is GPL or LPGL doesn't mean your lib must be. However, you should explicitly note the presence of any dependencies that may have restrictive licenses like (L)GPL very very prominantly. Do no try to use opinions to make legal decisions. Feelings have very very little to do with how law works. Its a complex organism that has (at this point) 1+ Millenia of legacy (legal) code. Often times, legal matters are even more complex than software, sadly unlike in software where its "cheap" to experiment with compiler / linker flags, disambiguating legal matters tends to require court cases and legal proceedings that can be quite expensive. Use whatever license makes you happy, but (if you're wanting it to be used in the haskell community as a library) make it MIT/BSD/Apache/equivalent. GPL is appropriate for end user applications and black box server applications (certain DB application servers that shall not be named), and sometimes OSes too *(though the BSDers may argue otherwise). LGPL with a Static linking exception is also hypothetically acceptable for haskell libraries, but theres some cultural bias against them, and its a somewhat a complex variant to use. TL;DR -- if you ever want code you're writing to land in GHC/cabal/hackage-server/base, it needs to be MIT/BSD compatible. For anything else, talk with a lawyer cheers -Carter On Sat, Jan 11, 2014 at 4:17 PM, Mateusz Kowalczyk wrote: > Alright, thanks for some clarifications. I agreed with everything you said. > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Sun Jan 12 02:40:01 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Sat, 11 Jan 2014 21:40:01 -0500 Subject: [Haskell-cafe] TypeLits and ScopedTypeVariables Message-ID: I've been playing with TypeLits recently, trying to create a vector with type-fixed size. I've hit a stumbling block trying to compile this (simplified) code: {-# LANGUAGE DataKinds #-} {-# LANGUAGE KindSignatures #-} import Control.Exception (assert) import GHC.TypeLits data Foo (n :: Nat) a = Foo a size :: SingI n => Foo n a -> Int size = fromInteger . fromSing . sizeSing where sizeSing :: Foo n a -> Sing n sizeSing _ = sing The error is: Could not deduce (SingI Nat n1) arising from a use of `sing' from the context (SingI Nat n) bound by the type signature for size :: SingI Nat n => Foo n a -> Int at /home/ben/test.hs:10:9-33 Possible fix: add an instance declaration for (SingI Nat n1) In the expression: sing In an equation for `sizeSing': sizeSing _ = sing In an equation for `size': size = fromInteger . fromSing . sizeSing where sizeSing :: Foo n a -> Sing n sizeSing _ = sing Can anybody shed light on this? It seems like the kind of thing that ScopedTypeVariables should solve, but it doesn't make a difference. -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Jan 12 02:45:12 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 11 Jan 2014 21:45:12 -0500 Subject: [Haskell-cafe] TypeLits and ScopedTypeVariables In-Reply-To: References: Message-ID: On Sat, Jan 11, 2014 at 9:40 PM, Ben Foppa wrote: > I've been playing with TypeLits recently, trying to create a vector with > type-fixed size. I've hit a stumbling block trying to compile this > (simplified) code: > (...) > Can anybody shed light on this? It seems like the kind of thing that > ScopedTypeVariables should solve, but it doesn't make a difference. > ScopedTypeVariables works here. Did you remember that explicit top level `forall` is needed to actually declare type variables to be scoped? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Sun Jan 12 02:54:48 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Sat, 11 Jan 2014 21:54:48 -0500 Subject: [Haskell-cafe] TypeLits and ScopedTypeVariables In-Reply-To: References: Message-ID: That would explain why it worked in my instance declarations with ScopedTypeVariables. Boy do I feel silly. On Sat, Jan 11, 2014 at 9:45 PM, Brandon Allbery wrote: > On Sat, Jan 11, 2014 at 9:40 PM, Ben Foppa wrote: > >> I've been playing with TypeLits recently, trying to create a vector with >> type-fixed size. I've hit a stumbling block trying to compile this >> (simplified) code: >> > (...) > >> Can anybody shed light on this? It seems like the kind of thing that >> ScopedTypeVariables should solve, but it doesn't make a difference. >> > > ScopedTypeVariables works here. Did you remember that explicit top level > `forall` is needed to actually declare type variables to be scoped? > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mukeshtiwari.iiitm at gmail.com Sun Jan 12 03:55:20 2014 From: mukeshtiwari.iiitm at gmail.com (mukesh tiwari) Date: Sun, 12 Jan 2014 09:25:20 +0530 Subject: [Haskell-cafe] Parse Error ( Parsec ) In-Reply-To: <52D19C33.5030407@fuuzetsu.co.uk> References: <52D19C33.5030407@fuuzetsu.co.uk> Message-ID: Hi Mateusz, Thank you. Now it's working fine by using 'try' function. -Mukesh Tiwari On Sun, Jan 12, 2014 at 1:02 AM, Mateusz Kowalczyk wrote: > On 11/01/14 19:12, mukesh tiwari wrote: > > Hello Cafe, > > I am trying to write a parser for propositional logic[1]. It's working > > fine for every input except equivalence ( <=> ). > > > > > > *Main> calculator "a=>b" > > Imp (Lit 'a') (Lit 'b') > > *Main> calculator "a<=b" > > Red (Lit 'a') (Lit 'b') > > *Main> calculator "a<=>b" > > *** Exception: failed to parse > > > > > > I think, the reason is parser taking equivalence ( <=> ) as reduction ( > <= > > ) and next character is '>' so it is parse error . If I remove both > > implication and reduction then equivalence is working fine. > > > > *Main> calculator "a<=>b" > > Eqi (Lit 'a') (Lit 'b') > > > > Could some please tell me how to solve this problem. I also tried fixity > > declaration but got this error > > LogicPraser.hs:12:10: > > The fixity signature for `<=>' lacks an accompanying binding > > > > -Mukesh Tiwari > > > > > > [1] http://logic.stanford.edu/classes/cs157/2010/notes/chap02.html > > [snip] > > Hi, > > I have not studied your code but if the problem is what you describe > it, you should try with back-tracking so that the parser can retry > when it fails. I believe Parsec offers the ?try? function for this. > > Regarding your ?infix <=>?, of course that would not work. It's a > Haskell declaration, not something Parsec does. > > You're getting an error because you're saying that ?<=>? has left fixity > of 9 but then you aren't giving a definition for ?<=>?. The "<=>" you're > parsing has nothing to do with this. Haskell sees the fixity > declaration and then doesn't see you defining the ?<=>? operator > anywhere so it complains. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From headprogrammingczar at gmail.com Sun Jan 12 13:22:06 2014 From: headprogrammingczar at gmail.com (Joe Quinn) Date: Sun, 12 Jan 2014 08:22:06 -0500 Subject: [Haskell-cafe] Parse Error ( Parsec ) In-Reply-To: References: Message-ID: <52D296FE.60804@gmail.com> On 1/11/2014 2:42 PM, Hilco Wijbenga wrote: > On 11 January 2014 11:12, mukesh tiwari wrote: >> table = [ [ Prefix ( Not <$ string "~" ) ] >> , [ Infix ( And <$ string "&" ) AssocLeft ] >> , [ Infix ( Or <$ string "|" ) AssocLeft ] >> , [ Infix ( Imp <$ string "=>" ) AssocLeft >> , Infix ( Red <$ string "<=" ) AssocLeft >> , Infix ( Eqi <$ string "<=>" ) AssocLeft > Have you tried changing the order here? I would expect the "<=>" check > to have to come before the "<=" check? I haven't played with this so > I'm just guessing. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe This would have the same problem, in the other direction. Parsing "a<=b" would get to "<", start matching against "<=>", then find "b" instead of ">" and fail again. From alexander at plaimi.net Sun Jan 12 13:28:00 2014 From: alexander at plaimi.net (Alexander Berntsen) Date: Sun, 12 Jan 2014 14:28:00 +0100 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: References: <52D19B00.7080900@fuuzetsu.co.uk> <52D1A6E2.1090700@fuuzetsu.co.uk> <52D1B4E5.5000308@fuuzetsu.co.uk> Message-ID: <52D29860.5000104@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 11/01/14 19:44, Ben Foppa wrote: > Essentially my goal is to waive all intellectual property rights to > most of my Haskell projects, to the extent that, were I to > unintentionally sign away my intellectual property, my open-source > contributions would be safe - what's the easiest way to do this? "Intellectual property" is not really a thing[0]. What it sounds like you want to do is ensure that your code stays free software. For this you need a licence that prevents people from using it for proprietary development. Here I recommend the GNU GPL[1]. But see [2] for a short introduction to "what licence should I be using". On 12/01/14 00:06, Carter Schonwald wrote: > GPL [has] never been tested in court. This is false[3]. [0] [1] [2] [3] See for some specific cases - -- Alexander alexander at plaimi.net http://plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlLSmGAACgkQRtClrXBQc7VYUwEAh41sGz5JUc8IUMnTmAPCLBpj ekk3+Y3oxs6gRm+wPzEA/0aPTYRUZgGBOmhv4yzrSy07SQwW+3NqOAqV9ZDu9k+z =u7fp -----END PGP SIGNATURE----- From carter.schonwald at gmail.com Sun Jan 12 16:16:57 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 12 Jan 2014 11:16:57 -0500 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: <52D29860.5000104@plaimi.net> References: <52D19B00.7080900@fuuzetsu.co.uk> <52D1A6E2.1090700@fuuzetsu.co.uk> <52D1B4E5.5000308@fuuzetsu.co.uk> <52D29860.5000104@plaimi.net> Message-ID: Wikipedia does not constitute legal advise For those who wish to make their code public domain, SQLite is a good role model. The SQLite license is essentially the equivalent of being public domain. On Sunday, January 12, 2014, Alexander Berntsen wrote: > -----BEGIN PGP SIGNED MESSAGE----- > Hash: SHA256 > > On 11/01/14 19:44, Ben Foppa wrote: > > Essentially my goal is to waive all intellectual property rights to > > most of my Haskell projects, to the extent that, were I to > > unintentionally sign away my intellectual property, my open-source > > contributions would be safe - what's the easiest way to do this? > "Intellectual property" is not really a thing[0]. What it sounds like > you want to do is ensure that your code stays free software. For this > you need a licence that prevents people from using it for proprietary > development. Here I recommend the GNU GPL[1]. But see [2] for a short > introduction to "what licence should I be using". > > On 12/01/14 00:06, Carter Schonwald wrote: > > GPL [has] never been tested in court. > This is false[3]. > > [0] > [1] > [2] > [3] See for some > specific cases > - -- > Alexander > alexander at plaimi.net > http://plaimi.net/~alexander > -----BEGIN PGP SIGNATURE----- > Version: GnuPG v2.0.22 (GNU/Linux) > Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ > > iF4EAREIAAYFAlLSmGAACgkQRtClrXBQc7VYUwEAh41sGz5JUc8IUMnTmAPCLBpj > ekk3+Y3oxs6gRm+wPzEA/0aPTYRUZgGBOmhv4yzrSy07SQwW+3NqOAqV9ZDu9k+z > =u7fp > -----END PGP SIGNATURE----- > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Sun Jan 12 18:11:55 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sun, 12 Jan 2014 19:11:55 +0100 Subject: [Haskell-cafe] access programs own documentation Message-ID: Hi guys, I'd like to access, from within my program, the program own haddock documentation. >From the cabal autogen path file, I can access the location of the program's data file, binaries etc. (getBinDir, getLibDir, getDataDir) but not the location of the doc. How to do that? For example on my machine: datadir = "/home/kau/.cabal/share/i386-linux-ghc-7.6.3/Nomyx-0.4.1" The documentation is generated in "/home/kau/.cabal/share/doc/i386-linux-ghc-7.6.3/Nomyx-0.4.1", but it depends on the configuration. Thanks, Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Sun Jan 12 19:45:48 2014 From: vogt.adam at gmail.com (adam vogt) Date: Sun, 12 Jan 2014 14:45:48 -0500 Subject: [Haskell-cafe] access programs own documentation In-Reply-To: References: Message-ID: Hi Corentin, One way is to call `ghc-pkg describe Nomyx-0.4.1` and look for the line starting with haddock-html. Or maybe look at how ghc-pkg does it . This can fail sometimes (though perhaps not for documentation), since you can have multiple packages with the same name and version installed, and I don't know how you can get the ABI hash of a dependency into a program. Regards, Adam On Sun, Jan 12, 2014 at 1:11 PM, Corentin Dupont wrote: > Hi guys, > I'd like to access, from within my program, the program own haddock > documentation. > From the cabal autogen path file, I can access the location of the program's > data file, binaries etc. (getBinDir, getLibDir, getDataDir) but not the > location of the doc. How to do that? > For example on my machine: > > datadir = "/home/kau/.cabal/share/i386-linux-ghc-7.6.3/Nomyx-0.4.1" > > The documentation is generated in > "/home/kau/.cabal/share/doc/i386-linux-ghc-7.6.3/Nomyx-0.4.1", but it > depends on the configuration. > > Thanks, > Corentin > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From difrumin at gmail.com Sun Jan 12 21:27:20 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Mon, 13 Jan 2014 01:27:20 +0400 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: Message-ID: What do you folks think of MathML? On Mon, Jan 6, 2014 at 10:49 PM, Peter Caspers wrote: > Hi, > > I am still very new to Haskell, trying to start my very first project. > For its documentation I want to use Haddock and suitable comments in > the source code. > > I notice that (e.g. different from doxygen) there is no direct way of > writing formulas, say in TeX style. Looking into some projects on > Hackage, formulas there > seem to be written in "pseudo-code" more or less like TeX but not > following any strict standard. As far as I can see. > > What would be your recommendations concerning this ? Is there some > guideline on how to include formulas ? I understand that there is > "literal programming" > where you can e.g. write a TeX article with embedded code blocks that > can be extracted for the compiler. However, I do not want to follow > this path, also the > result is a bit different from what is produced in the "traditional" > approach, isn't it. > > Thanks a lot > Peter > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sincerely yours, -- Daniil From roma at ro-che.info Sun Jan 12 21:46:32 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 12 Jan 2014 23:46:32 +0200 Subject: [Haskell-cafe] access programs own documentation In-Reply-To: References: Message-ID: <20140112214632.GA31272@sniper> Except Nomyx is a pure executable[1] and thus won't have a ghc package db entry. [1]: http://hackage.haskell.org/package/Nomyx-0.4.1/Nomyx.cabal * adam vogt [2014-01-12 14:45:48-0500] > Hi Corentin, > > One way is to call `ghc-pkg describe Nomyx-0.4.1` and look for the > line starting with haddock-html. Or maybe look at how ghc-pkg does it > . > > This can fail sometimes (though perhaps not for documentation), since > you can have multiple packages with the same name and version > installed, and I don't know how you can get the ABI hash of a > dependency into a program. > > Regards, > Adam > > > > On Sun, Jan 12, 2014 at 1:11 PM, Corentin Dupont > wrote: > > Hi guys, > > I'd like to access, from within my program, the program own haddock > > documentation. > > From the cabal autogen path file, I can access the location of the program's > > data file, binaries etc. (getBinDir, getLibDir, getDataDir) but not the > > location of the doc. How to do that? > > For example on my machine: > > > > datadir = "/home/kau/.cabal/share/i386-linux-ghc-7.6.3/Nomyx-0.4.1" > > > > The documentation is generated in > > "/home/kau/.cabal/share/doc/i386-linux-ghc-7.6.3/Nomyx-0.4.1", but it > > depends on the configuration. > > > > Thanks, > > Corentin > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 836 bytes Desc: Digital signature URL: From corentin.dupont at gmail.com Sun Jan 12 21:52:11 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sun, 12 Jan 2014 22:52:11 +0100 Subject: [Haskell-cafe] access programs own documentation In-Reply-To: <20140112214632.GA31272@sniper> References: <20140112214632.GA31272@sniper> Message-ID: In fact, the documentation location I am interrested in is a library (Nomyx-Language). Sorry, I should have mentionned that! I want to access the documentation of Nomyx-Language from Nomyx. On Sun, Jan 12, 2014 at 10:46 PM, Roman Cheplyaka wrote: > Except Nomyx is a pure executable[1] and thus won't have a ghc package db > entry. > > [1]: http://hackage.haskell.org/package/Nomyx-0.4.1/Nomyx.cabal > > * adam vogt [2014-01-12 14:45:48-0500] > > Hi Corentin, > > > > One way is to call `ghc-pkg describe Nomyx-0.4.1` and look for the > > line starting with haddock-html. Or maybe look at how ghc-pkg does it > > . > > > > This can fail sometimes (though perhaps not for documentation), since > > you can have multiple packages with the same name and version > > installed, and I don't know how you can get the ABI hash of a > > dependency into a program. > > > > Regards, > > Adam > > > > > > > > On Sun, Jan 12, 2014 at 1:11 PM, Corentin Dupont > > wrote: > > > Hi guys, > > > I'd like to access, from within my program, the program own haddock > > > documentation. > > > From the cabal autogen path file, I can access the location of the > program's > > > data file, binaries etc. (getBinDir, getLibDir, getDataDir) but not the > > > location of the doc. How to do that? > > > For example on my machine: > > > > > > datadir = "/home/kau/.cabal/share/i386-linux-ghc-7.6.3/Nomyx-0.4.1" > > > > > > The documentation is generated in > > > "/home/kau/.cabal/share/doc/i386-linux-ghc-7.6.3/Nomyx-0.4.1", but it > > > depends on the configuration. > > > > > > Thanks, > > > Corentin > > > > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Jan 12 21:56:21 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 12 Jan 2014 16:56:21 -0500 Subject: [Haskell-cafe] access programs own documentation In-Reply-To: <20140112214632.GA31272@sniper> References: <20140112214632.GA31272@sniper> Message-ID: On Sun, Jan 12, 2014 at 4:46 PM, Roman Cheplyaka wrote: > Except Nomyx is a pure executable[1] and thus won't have a ghc package db > entry. > Are we at the point where pure executables should be refactored into (possibly dummy) libraries just to get around this weakness of cabal? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Sun Jan 12 22:07:17 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sun, 12 Jan 2014 23:07:17 +0100 Subject: [Haskell-cafe] different behaviours with or without putStrLn Message-ID: Hi guys, I'm experimenting different behaviours with or without a "putStrLn"! :( Basically, with the following code, I want the evaluation to really happen on the "evaluate". I found out that it doesn't: it is evaluated elsewhere (I don't know where). If I put a putStrLn (commented below), the evaluation really happens there. *execCommand :: (TVar MyState) -> StateT MyState IO () -> IO ()execCommand ts sm = do s <- atomically $ readTVar ts s' <- execStateT sm s s'' <- evaluate s' --evaluation should happen here, but it doesn't --putStrLn $ displayMulti $ _multi s'' atomically $ writeTVar ts s''* To give you more context, I have a state that, when evaluated, might not terminate. So I added a watchdog (like in mueval), that will kill the thread in case the evaluation doesn't terminate. That's why I need to be sure of where the evaluation takes place. Thanks! Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Jan 12 22:10:20 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 12 Jan 2014 17:10:20 -0500 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: On Sun, Jan 12, 2014 at 5:07 PM, Corentin Dupont wrote: > Basically, with the following code, I want the evaluation to really happen > on the "evaluate". > I found out that it doesn't: it is evaluated elsewhere (I don't know > where). > If I put a putStrLn (commented below), the evaluation really happens there. > `evaluate` only evaluates to the first constructor, I believe. `putStrLn` must necessarily do full evaluation. Perhaps `deepseq` would help? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Sun Jan 12 22:10:43 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Sun, 12 Jan 2014 17:10:43 -0500 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: Depending on the kind of state, WHNF may not be enough - have you tried with deepseq? On Sun, Jan 12, 2014 at 5:07 PM, Corentin Dupont wrote: > Hi guys, > I'm experimenting different behaviours with or without a "putStrLn"! :( > > Basically, with the following code, I want the evaluation to really happen > on the "evaluate". > I found out that it doesn't: it is evaluated elsewhere (I don't know > where). > If I put a putStrLn (commented below), the evaluation really happens there. > > > > > > > > *execCommand :: (TVar MyState) -> StateT MyState IO () -> IO () > execCommand ts sm = do s <- atomically $ readTVar ts s' <- execStateT > sm s s'' <- evaluate s' --evaluation should happen here, but it > doesn't --putStrLn $ displayMulti $ _multi s'' atomically $ writeTVar > ts s''* > > To give you more context, I have a state that, when evaluated, might not > terminate. > So I added a watchdog (like in mueval), that will kill the thread in case > the evaluation doesn't terminate. > That's why I need to be sure of where the evaluation takes place. > > Thanks! > Corentin > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jan 12 22:19:41 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 12 Jan 2014 17:19:41 -0500 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: Message-ID: I seem to recall that certain browsers have dropped mathml support. Recent Firefox I think? I'm away from my computer so I can't look it up right now On Sunday, January 12, 2014, Daniil Frumin wrote: > What do you folks think of MathML? > > On Mon, Jan 6, 2014 at 10:49 PM, Peter Caspers > > wrote: > > Hi, > > > > I am still very new to Haskell, trying to start my very first project. > > For its documentation I want to use Haddock and suitable comments in > > the source code. > > > > I notice that (e.g. different from doxygen) there is no direct way of > > writing formulas, say in TeX style. Looking into some projects on > > Hackage, formulas there > > seem to be written in "pseudo-code" more or less like TeX but not > > following any strict standard. As far as I can see. > > > > What would be your recommendations concerning this ? Is there some > > guideline on how to include formulas ? I understand that there is > > "literal programming" > > where you can e.g. write a TeX article with embedded code blocks that > > can be extracted for the compiler. However, I do not want to follow > > this path, also the > > result is a bit different from what is produced in the "traditional" > > approach, isn't it. > > > > Thanks a lot > > Peter > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -- > Sincerely yours, > -- Daniil > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Sun Jan 12 22:26:19 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sun, 12 Jan 2014 23:26:19 +0100 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: deepseq seems interresting (didn't know it). Do I have to create instances of NFDatafor all my types? Too bad it's not derivable. On Sun, Jan 12, 2014 at 11:10 PM, Ben Foppa wrote: > Depending on the kind of state, WHNF may not be enough - have you tried > with deepseq? > > > On Sun, Jan 12, 2014 at 5:07 PM, Corentin Dupont < > corentin.dupont at gmail.com> wrote: > >> Hi guys, >> I'm experimenting different behaviours with or without a "putStrLn"! :( >> >> Basically, with the following code, I want the evaluation to really >> happen on the "evaluate". >> I found out that it doesn't: it is evaluated elsewhere (I don't know >> where). >> If I put a putStrLn (commented below), the evaluation really happens >> there. >> >> >> >> >> >> >> >> *execCommand :: (TVar MyState) -> StateT MyState IO () -> IO () >> execCommand ts sm = do s <- atomically $ readTVar ts s' <- execStateT >> sm s s'' <- evaluate s' --evaluation should happen here, but it >> doesn't --putStrLn $ displayMulti $ _multi s'' atomically $ writeTVar >> ts s''* >> >> To give you more context, I have a state that, when evaluated, might not >> terminate. >> So I added a watchdog (like in mueval), that will kill the thread in case >> the evaluation doesn't terminate. >> That's why I need to be sure of where the evaluation takes place. >> >> Thanks! >> Corentin >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From twey at twey.co.uk Sun Jan 12 22:49:04 2014 From: twey at twey.co.uk (=?UTF-8?Q?James_=E2=80=98Twey=E2=80=99_Kay?=) Date: Sun, 12 Jan 2014 22:49:04 +0000 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: You can (probably) automatically derive it via Template Haskell using the deepseq-th package: {-# LANGUAGE TemplateHaskell #-} import Control.DeepSeq.TH data MyState = ... $(deriveNFData ''MyState) On 2014-01-12 22:26, Corentin Dupont wrote: > deepseq seems interresting (didn't know it). > Do I have to create instances of NFData [2] for all my types? Too bad > it's not derivable. > > On Sun, Jan 12, 2014 at 11:10 PM, Ben Foppa > wrote: > >> Depending on the kind of state, WHNF may not be enough - have you >> tried with deepseq? >> >> On Sun, Jan 12, 2014 at 5:07 PM, Corentin Dupont >> wrote: >> >>> Hi guys, >>> I'm experimenting different behaviours with or without a >>> "putStrLn"! :( >>> >>> Basically, with the following code, I want the evaluation to >>> really happen on the "evaluate". >>> >>> I found out that it doesn't: it is evaluated elsewhere (I don't >>> know where). >>> >>> If I put a putStrLn (commented below), the evaluation really >>> happens there. >>> >>> execCommand :: (TVar MyState) -> StateT MyState IO () -> IO () >>> execCommand ts sm = do >>> ?? s <- atomically $ readTVar ts >>> ?? s' <- execStateT sm s >>> ?? s'' <- evaluate s'????????? --evaluation should >>> happen here, but it doesn't >>> ?? --putStrLn $ displayMulti $ _multi s'' >>> ?? atomically $ writeTVar ts s'' >>> >>> To give you more context, I have a state that, when evaluated, >>> might not terminate. >>> So I added a watchdog (like in mueval), that will kill the thread >>> in case the evaluation doesn't terminate. >>> >>> That's why I need to be sure of where the evaluation takes place. >>> >>> Thanks! >>> >>> Corentin >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe [1] > > > > Links: > ------ > [1] http://www.haskell.org/mailman/listinfo/haskell-cafe > [2] > http://hackage.haskell.org/package/deepseq-1.3.0.2/docs/Control-DeepSeq.html#t:NFData > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mle+hs at mega-nerd.com Sun Jan 12 23:08:03 2014 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Mon, 13 Jan 2014 10:08:03 +1100 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: <20140113100803.94145615b512ebfc0ec17665@mega-nerd.com> James ?Twey? Kay wrote: > You can (probably) automatically derive it via Template Haskell using > the deepseq-th package: > > {-# LANGUAGE TemplateHaskell #-} > import Control.DeepSeq.TH > > data MyState = ... > > $(deriveNFData ''MyState) In most cases where you think You should probably try the deepseq-generics package before you try deepseq-th. The generics version was suggested to me by the author of the TH version, Herbert Valerio Riedel. It seems to be just as fast as the TH version and doesn't require TH. Cheers, Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From yom at artyom.me Sun Jan 12 23:10:28 2014 From: yom at artyom.me (Artyom Kazak) Date: Mon, 13 Jan 2014 03:10:28 +0400 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: Message-ID: <52D320E4.6060506@artyom.me> On 01/13/2014 02:19 AM, Carter Schonwald wrote: > I seem to recall that certain browsers have dropped mathml support. > Recent Firefox I think? I'm away from my computer so I can't look it > up right now It?s the opposite ? currently Firefox and Safari are the *only* browsers which support MathML. So, right now it simply isn?t an option. From corentin.dupont at gmail.com Sun Jan 12 23:40:54 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 13 Jan 2014 00:40:54 +0100 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: <20140113100803.94145615b512ebfc0ec17665@mega-nerd.com> References: <20140113100803.94145615b512ebfc0ec17665@mega-nerd.com> Message-ID: I doesn't seems to be easy, either with deepseq-th or deepseq-generic... With deepseq-generic, the derivation of Generic doesn't work because I'm using a GATD. It says *"NewVar must be a vanilla data constructor"*. For deepseq-th, I have this error: *deriveNFData: 'forall' not supported in constructor declaration* I have some complex data constructor... So it looks like both deepseq-th and deepseq-generic are out of the game :(( On Mon, Jan 13, 2014 at 12:08 AM, Erik de Castro Lopo wrote: > James ?Twey? Kay wrote: > > > You can (probably) automatically derive it via Template Haskell using > > the deepseq-th package: > > > > {-# LANGUAGE TemplateHaskell #-} > > import Control.DeepSeq.TH > > > > data MyState = ... > > > > $(deriveNFData ''MyState) > > In most cases where you think > > You should probably try the deepseq-generics package before you try > deepseq-th. > > The generics version was suggested to me by the author of the TH version, > Herbert Valerio Riedel. It seems to be just as fast as the TH version and > doesn't require TH. > > Cheers, > Erik > -- > ---------------------------------------------------------------------- > Erik de Castro Lopo > http://www.mega-nerd.com/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Sun Jan 12 23:44:05 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 13 Jan 2014 00:44:05 +0100 Subject: [Haskell-cafe] different behaviours with or without putStrLn Message-ID: One question: Since it works with putStrLn, can I simulate the behaviour of putStrLn without actually... printing anything? As a workaround... On Mon, Jan 13, 2014 at 12:40 AM, Corentin Dupont wrote: > I doesn't seems to be easy, either with deepseq-th or deepseq-generic... > With deepseq-generic, the derivation of Generic doesn't work because I'm > using a GATD. > It says *"NewVar must be a vanilla data constructor"*. > > For deepseq-th, I have this error: > > *deriveNFData: 'forall' not supported in constructor declaration* > I have some complex data constructor... > > > So it looks like both deepseq-th and deepseq-generic are out of the game > :(( > > > > > On Mon, Jan 13, 2014 at 12:08 AM, Erik de Castro Lopo < > mle+hs at mega-nerd.com> wrote: > >> James ?Twey? Kay wrote: >> >> > You can (probably) automatically derive it via Template Haskell using >> > the deepseq-th package: >> > >> > {-# LANGUAGE TemplateHaskell #-} >> > import Control.DeepSeq.TH >> > >> > data MyState = ... >> > >> > $(deriveNFData ''MyState) >> >> In most cases where you think >> >> You should probably try the deepseq-generics package before you try >> deepseq-th. >> >> The generics version was suggested to me by the author of the TH version, >> Herbert Valerio Riedel. It seems to be just as fast as the TH version and >> doesn't require TH. >> >> Cheers, >> Erik >> -- >> ---------------------------------------------------------------------- >> Erik de Castro Lopo >> http://www.mega-nerd.com/ >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Mon Jan 13 00:08:57 2014 From: bob at redivi.com (Bob Ippolito) Date: Sun, 12 Jan 2014 16:08:57 -0800 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: Sure, something along the lines of deepseq . show will probably have the same effect. On Sunday, January 12, 2014, Corentin Dupont wrote: > One question: > Since it works with putStrLn, can I simulate the behaviour of putStrLn > without actually... printing anything? As a workaround... > > > On Mon, Jan 13, 2014 at 12:40 AM, Corentin Dupont < > corentin.dupont at gmail.com 'corentin.dupont at gmail.com');>> wrote: > >> I doesn't seems to be easy, either with deepseq-th or deepseq-generic... >> With deepseq-generic, the derivation of Generic doesn't work because I'm >> using a GATD. >> It says *"NewVar must be a vanilla data constructor"*. >> >> For deepseq-th, I have this error: >> >> *deriveNFData: 'forall' not supported in constructor declaration* >> I have some complex data constructor... >> >> >> So it looks like both deepseq-th and deepseq-generic are out of the game >> :(( >> >> >> >> >> On Mon, Jan 13, 2014 at 12:08 AM, Erik de Castro Lopo < >> mle+hs at mega-nerd.com >> > wrote: >> >>> James ?Twey? Kay wrote: >>> >>> > You can (probably) automatically derive it via Template Haskell using >>> > the deepseq-th package: >>> > >>> > {-# LANGUAGE TemplateHaskell #-} >>> > import Control.DeepSeq.TH >>> > >>> > data MyState = ... >>> > >>> > $(deriveNFData ''MyState) >>> >>> In most cases where you think >>> >>> You should probably try the deepseq-generics package before you try >>> deepseq-th. >>> >>> The generics version was suggested to me by the author of the TH version, >>> Herbert Valerio Riedel. It seems to be just as fast as the TH version and >>> doesn't require TH. >>> >>> Cheers, >>> Erik >>> -- >>> ---------------------------------------------------------------------- >>> Erik de Castro Lopo >>> http://www.mega-nerd.com/ >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >> 'Haskell-Cafe at haskell.org');> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Mon Jan 13 00:10:56 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 12 Jan 2014 19:10:56 -0500 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: On Sun, Jan 12, 2014 at 6:44 PM, Corentin Dupont wrote: > One question: > Since it works with putStrLn, can I simulate the behaviour of putStrLn > without actually... printing anything? As a workaround... > Worst case, open a handle on /dev/null and hPutStr to it. I'd probably try to figure out how to write appropriate NFData instances, though. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander at plaimi.net Mon Jan 13 00:58:35 2014 From: alexander at plaimi.net (Alexander Berntsen) Date: Mon, 13 Jan 2014 01:58:35 +0100 Subject: [Haskell-cafe] Licenses and dependencies In-Reply-To: References: <52D19B00.7080900@fuuzetsu.co.uk> <52D1A6E2.1090700@fuuzetsu.co.uk> <52D1B4E5.5000308@fuuzetsu.co.uk> <52D29860.5000104@plaimi.net> Message-ID: <52D33A3B.3010100@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 12/01/14 17:16, Carter Schonwald wrote: > Wikipedia does not constitute legal advise If you visit the page, you will find several links for prolific cases where the GPL has been tested in court. - -- Alexander alexander at plaimi.net http://plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlLTOjsACgkQRtClrXBQc7VIuAD+KZTTJ0qyEC4pt+fX3e5UGMbm Z+5ZmGCbScRQ0pvAw5MA+QGq4eG01x/OAJaNq6IzrEsYD3EmBa0TZAWb1qjGvAy+ =rje1 -----END PGP SIGNATURE----- From ccherng at gmail.com Mon Jan 13 01:00:23 2014 From: ccherng at gmail.com (Cary Cherng) Date: Sun, 12 Jan 2014 17:00:23 -0800 Subject: [Haskell-cafe] Structural typing of records in Haskell? Message-ID: Are there statically typed languages that treat records with structural typing, either imperative or functional? Why should records not be structurally typed in Haskell? From what I understand, in the below foo cannot take a Rec2 even though Rec1 and Rec2 are essentially the same. data Rec1 = Rec1 { a :: Int, b :: Bool} data Rec2 = Rec2 { a :: Int, b :: Bool} foo :: Rec1 -> Bool Rec1 and Rec2 could be in totally different code libraries. I've read that preventing Rec2 being used in foo is good for the type safety in that Rec1 and Rec2 are likely intended to have semantically different meanings and allowing interchangeability breaks this. But then why is map structurally typed. map takes an argument of type a -> b and suppose some other higher order function bar also takes an argument of type a -> b. Should map instead have the below type which prevents a function of type a -> b semantically intended for bar from being accidentally used in map. newtype Mapper a b = Mapper { fn :: a -> b } map :: Mapper a b -> [a] -> [b] map _ [] = [] map f (x:xs) = (fn f) x : map f xs If there is a mechanism that prevents something of type Rec2 from accidentally being used in foo, then why shouldn't there be something analogous that prevents something of type a -> b (meant for bar) from accidentally being used in map? From fuuzetsu at fuuzetsu.co.uk Mon Jan 13 01:37:29 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 13 Jan 2014 01:37:29 +0000 Subject: [Haskell-cafe] Haddock changes pushed upstream Message-ID: <52D34359.3050401@fuuzetsu.co.uk> Hi all, As some of you might know, I hacked on Haddock over summer as part of GSOC. After some tedious fighting with GHC validation process and help of the guys on ghc-devs, the changes were finally pushed upstream couple of hours ago. While I'm waiting for the maintainer to make a call on the official release, you can already get the changes if you compile GHC HEAD. For those not so eager about compiling HEAD, 7.8 should be coming out the changes will be in that. You can read the brief changelog at [1] and the updated documentation at [2]. We were careful to not make changes to any existing syntax that would result in a large amount of packages breaking. If you're a package maintainer, here are some things to consider: * If your documentation looks fine how it is now, you're probably fine. Read the changelog[1] as it mentions some issues that were fixed. Amongst others, Haddock will now link qualified function names properly so that's something to look out for. * none of your documentation should get parse failures: any previously-failing documentation should now be displayed. This means that if you have parse failures, now is the time to go and fix them up or your documentation probably won't look pretty. On an upside, this means that we won't have whole Hackage packages missing documentation due to a minor mistake in one of the comments. * You no longer need to break up lists of the same type with newlines. Previously you'd get two lists merged on a single line in an incoherent mess. Now it'll be rendered properly. I know that even GHC documentation is guilty of this mistake. * You can now escape the markup properly. Before, you were very limited on how the markup could be escaped. For example, <r>> would result in a parse failure. * Bold markup added. The syntax is two underscores around what you want bold. Note, we still do not support multi-line markup. It's possible but it's a design choice not to support it. * You previously have gotten a document coverage report. We now have --print-missing-docs flag which will also tell you where the undocumented entities are: ``` ? misaki shana % haddock -h -U F.hs --print-missing-docs -o . Haddock coverage: 33% ( 2 / 6) in 'F' Missing documentation for: Baz (F.hs:5) Bar (F.hs:6) Foo (F.hs:7) add ``` * You can now nest paragraphs inside of lists. For most people this simply means that you can now have multiple levels of lists. We allow arbitrary nesting depth. The rules are: 4 spaces of indentation, new paragraphs have to be preceded by an empty line. ``` 1. Foo 1. Nested inside of Foo 2. Another thing inside of Foo >>> example inside of Foo example result 2. Back after Foo ``` * You can now have headings inside of your documentation rather than only for splitting up sections of your module. Example usage: ``` = Heading level one >>> some code example hello == Heading level two * Hello Haddock! ``` Up to 6 ?=?s are currently supported. LaTeX back-end only honours up to three ?=?s but it is not an error to have >3, they'll simply be treated as 3. * You can now display enabled module extensions in the generated documentation with {-# OPTIONS_HADDOCK show-extensions #-}. * Picture syntax now documented. * You can now have the title attribute for your hyperlinks. The syntax is I think that about covers it all. Perhaps I will write a more visual guide to the new changes but please don't hold your breath! Feel free to ask questions. If you have bugs to report or features to ask for, please head to the Haddock Trac[3]. [1]: http://www.haskell.org/haddock/CHANGES.txt [2]: http://www.haskell.org/haddock/doc/html/ [3]: http://trac.haskell.org/haddock -- Mateusz K. From fuuzetsu at fuuzetsu.co.uk Mon Jan 13 01:46:41 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 13 Jan 2014 01:46:41 +0000 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: <52D34359.3050401@fuuzetsu.co.uk> References: <52D34359.3050401@fuuzetsu.co.uk> Message-ID: <52D34581.9030602@fuuzetsu.co.uk> Oops, something else I forgot to mention. You can now nest markup properly. For example, before it was incorrect to have other markup inside of emphasis. This even meant that the HTML escape codes (which we convert ourselves) would not be converted or that you can't have structures like /@foo@/ as you'd end up with ?@foo@? verbatim rather than emphasised, monospaced ?foo?. This is now fixed. I see this kind of documentation a lot on Hackage so you might want to go and either change it if you're relying on the broken behaviour or leave it as it is and bask in its new glory. More reading at [1]. Thanks [1]: http://trac.haskell.org/haddock/ticket/252 -- Mateusz K. From michael at orlitzky.com Mon Jan 13 02:34:45 2014 From: michael at orlitzky.com (Michael Orlitzky) Date: Sun, 12 Jan 2014 21:34:45 -0500 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: <52D34359.3050401@fuuzetsu.co.uk> References: <52D34359.3050401@fuuzetsu.co.uk> Message-ID: <52D350C5.7000705@orlitzky.com> On 01/12/2014 08:37 PM, Mateusz Kowalczyk wrote: > > * You can now nest paragraphs inside of lists. For most people this > simply means that you can now have multiple levels of lists. We allow > arbitrary nesting depth. The rules are: 4 spaces of indentation, new > paragraphs have to be preceded by an empty line. > > ... > > * You can now have headings inside of your documentation rather than > only for splitting up sections of your module. Example usage: Awwwwwwwwwwwwww yiss. This is wonderful. Thank you. From ltclifton at gmail.com Mon Jan 13 03:38:03 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Mon, 13 Jan 2014 11:38:03 +0800 Subject: [Haskell-cafe] Restrict values in type Message-ID: Hi, I'm quite new to Haskell, and have been loving exploring it. I've always been a huge fan of languages that let me catch errors at compile time, finding dynamic languages like Python a nightmare to work in. I'm finding with Haskell I can take this compile time checking even further than most static languages and it has gotten me rather excited. So I was wondering if there is a Haskell way of solving my problem. I'm trying to represent an image made up of a list of strokes. Strokes are either lines, arcs or spots, and can be made using different pen shapes. data Image = Image [Stroke] data Stroke = Line Point Point PenShape | Arc Point Point Point PenShape | Spot Point PenShape data PenShape = Circle Float | Rectangle Float Float | ArbitraryPen -- Stuff (not relevant) And this is all great and works. But now I have a problem. I want to extend this such that Arc strokes are only allowed to have the Circle pen shape, and Lines are only allowed to have the Rectangle or Circle pen shapes. What is the best way of enforcing this in the type system. I could make more Strokes like LineCircle, LineRectangle, Arc, PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape type altogether. But this doesn't really feel good to me (and seems like the amount of work I have to do is bigger than it needs to be, especially if I added more basic pen shapes). I thought about making the different PenShapes different types, using typeclasses and making Stroke an algebraic data type, but then my strokes would be of different types, and I wouldn't be able to have a list of strokes. I have been looking at DataKinds and GADTs, but I can't quite figure out if they actually help me here at all. I'm sure there is a way to do this, I'm just not googling properly. What I want to write is... data Image = Image [Stroke] data Stroke = Line Point Point (Circle or Rectangle) | Arc Point Point Point Circle | Spot Point PenShape data PenShape = Circle Float | Rectangle Float Float | ArbitraryPen -- Stuff (not relevant) Regards, Luke -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Jan 13 03:55:30 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 12 Jan 2014 22:55:30 -0500 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Hey Luke, have you seen the diagrams project? http://projects.haskell.org/diagrams/ they've struggled through some of the same problems, and they've worked very hard to write a power user friendly expressive DSL lib for that problem domain. check it out! -Carter On Sun, Jan 12, 2014 at 10:38 PM, Luke Clifton wrote: > Hi, > > I'm quite new to Haskell, and have been loving exploring it. I've always > been a huge fan of languages that let me catch errors at compile time, > finding dynamic languages like Python a nightmare to work in. I'm finding > with Haskell I can take this compile time checking even further than most > static languages and it has gotten me rather excited. So I was wondering if > there is a Haskell way of solving my problem. > > I'm trying to represent an image made up of a list of strokes. Strokes are > either lines, arcs or spots, and can be made using different pen shapes. > > data Image = Image [Stroke] > > data Stroke = Line Point Point PenShape > | Arc Point Point Point PenShape > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > And this is all great and works. > > But now I have a problem. I want to extend this such that Arc strokes are > only allowed to have the Circle pen shape, and Lines are only allowed to > have the Rectangle or Circle pen shapes. > > What is the best way of enforcing this in the type system. > > I could make more Strokes like LineCircle, LineRectangle, Arc, > PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape > type altogether. But this doesn't really feel good to me (and seems like > the amount of work I have to do is bigger than it needs to be, especially > if I added more basic pen shapes). > > I thought about making the different PenShapes different types, using > typeclasses and making Stroke an algebraic data type, but then my strokes > would be of different types, and I wouldn't be able to have a list of > strokes. > > I have been looking at DataKinds and GADTs, but I can't quite figure out > if they actually help me here at all. > > I'm sure there is a way to do this, I'm just not googling properly. > > What I want to write is... > > data Image = Image [Stroke] > > data Stroke = Line Point Point (Circle or Rectangle) > | Arc Point Point Point Circle > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > Regards, > > Luke > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Mon Jan 13 03:58:44 2014 From: bob at redivi.com (Bob Ippolito) Date: Sun, 12 Jan 2014 19:58:44 -0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: You can have a heterogeneous list of items that implement a typeclass if you have a wrapper that uses ExistentialQuantification. See http://www.haskell.org/haskellwiki/Heterogenous_collections I don't have enough experience with the type system to properly answer your actual question though. On Sun, Jan 12, 2014 at 7:38 PM, Luke Clifton wrote: > Hi, > > I'm quite new to Haskell, and have been loving exploring it. I've always > been a huge fan of languages that let me catch errors at compile time, > finding dynamic languages like Python a nightmare to work in. I'm finding > with Haskell I can take this compile time checking even further than most > static languages and it has gotten me rather excited. So I was wondering if > there is a Haskell way of solving my problem. > > I'm trying to represent an image made up of a list of strokes. Strokes are > either lines, arcs or spots, and can be made using different pen shapes. > > data Image = Image [Stroke] > > data Stroke = Line Point Point PenShape > | Arc Point Point Point PenShape > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > And this is all great and works. > > But now I have a problem. I want to extend this such that Arc strokes are > only allowed to have the Circle pen shape, and Lines are only allowed to > have the Rectangle or Circle pen shapes. > > What is the best way of enforcing this in the type system. > > I could make more Strokes like LineCircle, LineRectangle, Arc, > PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape > type altogether. But this doesn't really feel good to me (and seems like > the amount of work I have to do is bigger than it needs to be, especially > if I added more basic pen shapes). > > I thought about making the different PenShapes different types, using > typeclasses and making Stroke an algebraic data type, but then my strokes > would be of different types, and I wouldn't be able to have a list of > strokes. > > I have been looking at DataKinds and GADTs, but I can't quite figure out > if they actually help me here at all. > > I'm sure there is a way to do this, I'm just not googling properly. > > What I want to write is... > > data Image = Image [Stroke] > > data Stroke = Line Point Point (Circle or Rectangle) > | Arc Point Point Point Circle > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > Regards, > > Luke > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ltclifton at gmail.com Mon Jan 13 04:09:17 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Mon, 13 Jan 2014 12:09:17 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Hi Carter, Yes, I have seen the diagrams project, and in fact am hoping to use them when I actually get to rendering. Perhaps, I should have provided more info to try and explain why I am doing this. I am trying to implement a Gerber file viewer (and maybe editor... we'll see) http://www.ucamco.com/Portals/0/Public/The_Gerber_File_Format_Specification.pdf I am using parsec to parse the gerber format and build my gerber data type so that I can make modifications to it, and write it back out. I'll take a closer look at diagrams source and see if I can come up with some inspiration. Thanks, Luke On Mon, Jan 13, 2014 at 11:55 AM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Hey Luke, > have you seen the diagrams project? http://projects.haskell.org/diagrams/ > they've struggled through some of the same problems, and they've worked > very hard to write a power user friendly expressive DSL lib for that > problem domain. > check it out! > -Carter > > > On Sun, Jan 12, 2014 at 10:38 PM, Luke Clifton wrote: > >> Hi, >> >> I'm quite new to Haskell, and have been loving exploring it. I've always >> been a huge fan of languages that let me catch errors at compile time, >> finding dynamic languages like Python a nightmare to work in. I'm finding >> with Haskell I can take this compile time checking even further than most >> static languages and it has gotten me rather excited. So I was wondering if >> there is a Haskell way of solving my problem. >> >> I'm trying to represent an image made up of a list of strokes. Strokes >> are either lines, arcs or spots, and can be made using different pen shapes. >> >> data Image = Image [Stroke] >> >> data Stroke = Line Point Point PenShape >> | Arc Point Point Point PenShape >> | Spot Point PenShape >> >> data PenShape = Circle Float >> | Rectangle Float Float >> | ArbitraryPen -- Stuff (not relevant) >> >> And this is all great and works. >> >> But now I have a problem. I want to extend this such that Arc strokes are >> only allowed to have the Circle pen shape, and Lines are only allowed to >> have the Rectangle or Circle pen shapes. >> >> What is the best way of enforcing this in the type system. >> >> I could make more Strokes like LineCircle, LineRectangle, Arc, >> PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape >> type altogether. But this doesn't really feel good to me (and seems like >> the amount of work I have to do is bigger than it needs to be, especially >> if I added more basic pen shapes). >> >> I thought about making the different PenShapes different types, using >> typeclasses and making Stroke an algebraic data type, but then my strokes >> would be of different types, and I wouldn't be able to have a list of >> strokes. >> >> I have been looking at DataKinds and GADTs, but I can't quite figure out >> if they actually help me here at all. >> >> I'm sure there is a way to do this, I'm just not googling properly. >> >> What I want to write is... >> >> data Image = Image [Stroke] >> >> data Stroke = Line Point Point (Circle or Rectangle) >> | Arc Point Point Point Circle >> | Spot Point PenShape >> >> data PenShape = Circle Float >> | Rectangle Float Float >> | ArbitraryPen -- Stuff (not relevant) >> >> Regards, >> >> Luke >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ltclifton at gmail.com Mon Jan 13 04:12:32 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Mon, 13 Jan 2014 12:12:32 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Hi Bob, You can have a heterogeneous list of items that implement a typeclass if > you have a wrapper that uses ExistentialQuantification. See > http://www.haskell.org/haskellwiki/Heterogenous_collections > Hmm.. I'll take a closer look at that. It might be good enough, though I would prefer to be able to pattern match on the elements in the list. Regards, Luke -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew at operationaldynamics.com Mon Jan 13 04:30:43 2014 From: andrew at operationaldynamics.com (Andrew Cowie) Date: Mon, 13 Jan 2014 15:30:43 +1100 Subject: [Haskell-cafe] Haddock - How to write formulas ? In-Reply-To: References: Message-ID: <1389587443.4255.5.camel@nervous-energy.bridge.anchor.net.au> On Mon, 2014-01-13 at 01:27 +0400, Daniil Frumin wrote: > What do you folks think of MathML? Well, the de facto way to render MathML *is* with Mathjax. Rendering Latex is a side thing (obviously significant for adoption, but still a sideline) for them. So either way, whether it's inline Latex or inline MathML, the nicest outcome for rendering math in a browser is Mathjax. AfC Sydney From vogt.adam at gmail.com Mon Jan 13 06:52:03 2014 From: vogt.adam at gmail.com (adam vogt) Date: Mon, 13 Jan 2014 01:52:03 -0500 Subject: [Haskell-cafe] Structural typing of records in Haskell? In-Reply-To: References: Message-ID: Hi Cary, Have you looked at http://www.haskell.org/haskellwiki/Extensible_record and https://ghc.haskell.org/trac/ghc/wiki/Records ? The named-fields stuff in haskell 2010 is bad because none of the proposals/implementations really stand out as the right choice. You still have a choice whether you want to use newtypes to help you keep things straight. Maybe your `newtype Mapper` could help you catch some bugs. Or maybe it just makes some busywork for you, where you just add some noise (`fn` and `Mapper`) whenever the types don't match up. Also consider that the type of "map" doesn't have to be changed to catch mistakes of using the wrong function: if the concrete types that end up replacing the `a` and `b` in your actual program are not all String, the typechecker may still be able to point out a place where you've been inconsistent (say by using the wrong function). -- Adam On Sun, Jan 12, 2014 at 8:00 PM, Cary Cherng wrote: > Are there statically typed languages that treat records with > structural typing, either imperative or functional? > > Why should records not be structurally typed in Haskell? From what I > understand, in the below foo cannot take a Rec2 even though Rec1 and > Rec2 are essentially the same. > > data Rec1 = Rec1 { a :: Int, b :: Bool} > data Rec2 = Rec2 { a :: Int, b :: Bool} > foo :: Rec1 -> Bool > > Rec1 and Rec2 could be in totally different code libraries. I've read > that preventing Rec2 being used in foo is good for the type safety in > that Rec1 and Rec2 are likely intended to have semantically different > meanings and allowing interchangeability breaks this. > > But then why is map structurally typed. map takes an argument of type > a -> b and suppose some other higher order function bar also takes an > argument of type a -> b. Should map instead have the below type which > prevents a function of type a -> b semantically intended for bar from > being accidentally used in map. > > newtype Mapper a b = Mapper { fn :: a -> b } > map :: Mapper a b -> [a] -> [b] > map _ [] = [] > map f (x:xs) = (fn f) x : map f xs > > If there is a mechanism that prevents something of type Rec2 from > accidentally being used in foo, then why shouldn't there be something > analogous that prevents something of type a -> b (meant for bar) from > accidentally being used in map? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From carlo at carlo-hamalainen.net Mon Jan 13 07:52:34 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Mon, 13 Jan 2014 08:52:34 +0100 Subject: [Haskell-cafe] access programs own documentation In-Reply-To: References: <20140112214632.GA31272@sniper> Message-ID: <52D39B42.5010305@carlo-hamalainen.net> On 12/01/14 22:52, Corentin Dupont wrote: > In fact, the documentation location I am interrested in is a library > (Nomyx-Language). Sorry, I should have mentionned that! > I want to access the documentation of Nomyx-Language from Nomyx. If you use "ghc-pkg field somepackage haddock-html" then you have to deal with a few cases: * somepackage is a system package (e.g. installed with apt-get on Linux). * somepackage is a user cabal package (in ~/.cabal). * somepackage is in a cabal sandbox (could be anywhere). * what else? I found this page helpful: http://www.vex.net/~trebla/haskell/sicp.xhtml Cheers, -- Carlo Hamalainen http://carlo-hamalainen.net From aeyakovenko at gmail.com Mon Jan 13 08:09:49 2014 From: aeyakovenko at gmail.com (Anatoly Yakovenko) Date: Mon, 13 Jan 2014 00:09:49 -0800 Subject: [Haskell-cafe] any idea why binary isn't bulding on OSX Message-ID: src/Data/Binary/Get.hs:423:3: error: invalid preprocessing directive #-} ^ src/Data/Binary/Get.hs:511:53: warning: missing terminating ' character [-Winvalid-pp-token] -- host order, host endian form, for the machine you're on. On a 64 bit ^ 12 warnings and 1 error generated. Failed to install binary-0.7.1.0 cabal: Error: some packages failed to install: JuicyPixels-3.1.2 depends on binary-0.7.1.0 which failed to install. binary-0.7.1.0 failed during the building phase. The exception was: ExitFailure 1 From raabe at froglogic.com Mon Jan 13 08:13:29 2014 From: raabe at froglogic.com (Frerich Raabe) Date: Mon, 13 Jan 2014 09:13:29 +0100 Subject: [Haskell-cafe] any idea why binary isn't bulding on OSX In-Reply-To: References: Message-ID: On 2014-01-13 09:09, Anatoly Yakovenko wrote: > src/Data/Binary/Get.hs:423:3: > > error: invalid preprocessing directive > > #-} > > ^ > > > src/Data/Binary/Get.hs:511:53: > > warning: missing terminating ' character [-Winvalid-pp-token] > > -- host order, host endian form, for the machine you're on. On a 64 > bit Do you use OS X 10.9 (Mavericks) and/or Xcode 5 by any chance? If so, this is a known issue. The issue is that Xcode 5 uses clang as the C compiler, and the clang preprocessor (which ghc calls) works slightly differently - that's what's causing the issue. There's a workaround given on http://www.haskell.org/platform/mac.html In the 'Xcode 5 ^ OS X 10.9 (Mavericks' section. -- Frerich Raabe - raabe at froglogic.com www.froglogic.com - Multi-Platform GUI Testing From miguelimo38 at yandex.ru Mon Jan 13 08:27:01 2014 From: miguelimo38 at yandex.ru (MigMit) Date: Mon, 13 Jan 2014 12:27:01 +0400 Subject: [Haskell-cafe] any idea why binary isn't bulding on OSX In-Reply-To: References: Message-ID: Installing gcc 4.2 from MacPorts (and port selecting it) helped with this problem. Gcc 4.8 didn't. ?????????? ? iPhone > 13 ???. 2014 ?., ? 12:09, Anatoly Yakovenko ???????(?): > > src/Data/Binary/Get.hs:423:3: > > error: invalid preprocessing directive > > #-} > > ^ > > > src/Data/Binary/Get.hs:511:53: > > warning: missing terminating ' character [-Winvalid-pp-token] > > -- host order, host endian form, for the machine you're on. On a 64 bit > > ^ > > 12 warnings and 1 error generated. > > Failed to install binary-0.7.1.0 > > cabal: Error: some packages failed to install: > > JuicyPixels-3.1.2 depends on binary-0.7.1.0 which failed to install. > > binary-0.7.1.0 failed during the building phase. The exception was: > > ExitFailure 1 > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From svenpanne at gmail.com Mon Jan 13 08:58:42 2014 From: svenpanne at gmail.com (Sven Panne) Date: Mon, 13 Jan 2014 09:58:42 +0100 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: <52D34359.3050401@fuuzetsu.co.uk> References: <52D34359.3050401@fuuzetsu.co.uk> Message-ID: 2014/1/13 Mateusz Kowalczyk : > [...] * none of your documentation should get parse failures: any > previously-failing documentation should now be displayed. [...] Do we still get warnings or is there a command line flag to get errors back? I definitely don't want to browse through dozens of HTML pages to check if they look OK. For developing purposes I want as many errors I can get. (well, almost ;-) From jwlato at gmail.com Mon Jan 13 09:05:04 2014 From: jwlato at gmail.com (John Lato) Date: Mon, 13 Jan 2014 01:05:04 -0800 Subject: [Haskell-cafe] Structural typing of records in Haskell? In-Reply-To: References: Message-ID: On Sun, Jan 12, 2014 at 5:00 PM, Cary Cherng wrote: > Are there statically typed languages that treat records with > structural typing, either imperative or functional? > OCaml uses structural typing for objects, and it's statically typed. > > Why should records not be structurally typed in Haskell? From what I > understand, in the below foo cannot take a Rec2 even though Rec1 and > Rec2 are essentially the same. > > data Rec1 = Rec1 { a :: Int, b :: Bool} > data Rec2 = Rec2 { a :: Int, b :: Bool} > foo :: Rec1 -> Bool > > Rec1 and Rec2 could be in totally different code libraries. I've read > that preventing Rec2 being used in foo is good for the type safety in > that Rec1 and Rec2 are likely intended to have semantically different > meanings and allowing interchangeability breaks this. > > But then why is map structurally typed. map takes an argument of type > a -> b and suppose some other higher order function bar also takes an > argument of type a -> b. Should map instead have the below type which > prevents a function of type a -> b semantically intended for bar from > being accidentally used in map. > > newtype Mapper a b = Mapper { fn :: a -> b } > map :: Mapper a b -> [a] -> [b] > map _ [] = [] > map f (x:xs) = (fn f) x : map f xs > > If there is a mechanism that prevents something of type Rec2 from > accidentally being used in foo, then why shouldn't there be something > analogous that prevents something of type a -> b (meant for bar) from > accidentally being used in map? > Because it's not possible to break anything by passing a total function to map. Data structures can have internal invariants that functions meant for structurally identical values will break. For example: -- a natural number > data Nat = Nat { unNat :: Int } if we used structural typing, then ( 1-2 :: Nat ) would work, violating an invariant that our custom API would preserve. However, breaking code like this simply isn't possible with map. For whatever 'a' type you're mapping over, a total function (a->b) will handle it properly. Or perhaps another way to think about it: map *cannot* care about the types of the values it's operating over. It's the function's responsibility to handle the input type appropriately, for whichever input it claims to take. So long as the function is actually a function, map will do the right thing. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Mon Jan 13 09:19:45 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 13 Jan 2014 09:19:45 +0000 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: References: <52D34359.3050401@fuuzetsu.co.uk> Message-ID: <52D3AFB1.6010601@fuuzetsu.co.uk> On 13/01/14 08:58, Sven Panne wrote: > 2014/1/13 Mateusz Kowalczyk : >> [...] * none of your documentation should get parse failures: any >> previously-failing documentation should now be displayed. [...] > > Do we still get warnings or is there a command line flag to get errors > back? I definitely don't want to browse through dozens of HTML pages > to check if they look OK. For developing purposes I want as many > errors I can get. (well, almost ;-) > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > No there is no way to get warnings or errors because it no longer makes sense to do so. The reason for failures in the past was due to Haddock's shortcomings rather than user failures: if your docs failed to parse, you probably tried escaping something where it didn't expect it &c. Ideally, it should have never had parse failures in the past but the parser had many short-comings. It's very hard to give warnings because we can't tell what the user actually wanted to do, only whether they have input valid markup or not. The only change is that now all markup should check out as valid. If your docs look OK now, they will almost certainly look OK with the new version. If they are broken now, they might look terrible in the new version BUT if they are broken now, it's very easy to tell as you'll be getting parse failures. I suggest that if you have any broken documentation right now, go and fix it. If you don't, great, you should be set. Note that even the old/current version of Haddock would never present you with any warnings: it would either error or not. I did start to write a tool which would look at your existing documentation and try to point out any changes between the versions that might affect you but I did not have the time to finish it and it would be very naive even if I did. You can find it at [1] but it does close to nothing. All in all you should be safe. The new markup rules are a lot more intuitive than the old ones and we have not changed anything that would greatly change existing, well-formed documentation. I don't think there is any documentation that will start to look worse except for few edge cases, such as people relying on Haddock not being able to nest markup to put in some other markup symbols verbatim into their text. You can now nest markup so that might end up looking slightly differently. Nothing major. John MacFarlane suggested that I create a sort of dingus which would allow people to input some Haddock markup and be able to see the output from various versions. I think it'd be a useful tool not only for migration but for daily use. I did not have the time to start it but it's certainly in my plans. I'm starting to sit my mid-terms from tomorrow until the end of the month but I might be able to code something up after that. If someone is interested in doing this themselves, let me know so we don't duplicate efforts. [1]: http://hackage.haskell.org/package/doccheck -- Mateusz K. From emax at chalmers.se Mon Jan 13 11:20:06 2014 From: emax at chalmers.se (Emil Axelsson) Date: Mon, 13 Jan 2014 12:20:06 +0100 Subject: [Haskell-cafe] ANN: tree-view-0.1 Message-ID: <52D3CBE6.9020702@chalmers.se> tree-view is a package for rendering trees as foldable HTML and Unicode art. http://hackage.haskell.org/package/tree-view Example: *Data.Tree.View> drawTree $ Node "Add" [Node "Sub" [Node "3" [], Node "Mul" [Node "1" [], Node "2" []]], Node "4" []] Add ??Sub ? ??3 ? ??Mul ? ??1 ? ??2 ??4 / Emil From fuuzetsu at fuuzetsu.co.uk Mon Jan 13 11:24:05 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 13 Jan 2014 11:24:05 +0000 Subject: [Haskell-cafe] ANN: tree-view-0.1 In-Reply-To: <52D3CBE6.9020702@chalmers.se> References: <52D3CBE6.9020702@chalmers.se> Message-ID: <52D3CCD5.3080703@fuuzetsu.co.uk> On 13/01/14 11:20, Emil Axelsson wrote: > tree-view is a package for rendering trees as foldable HTML and Unicode art. > > http://hackage.haskell.org/package/tree-view > > Example: > > *Data.Tree.View> drawTree $ Node "Add" [Node "Sub" [Node "3" [], Node > "Mul" [Node "1" [], Node "2" []]], Node "4" []] > Add > ??Sub > ? ??3 > ? ??Mul > ? ??1 > ? ??2 > ??4 > > > / Emil > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Hi, What does tree-view offer over pretty-tree[1]? [1]: http://hackage.haskell.org/package/pretty-tree -- Mateusz K. From fuuzetsu at fuuzetsu.co.uk Mon Jan 13 11:26:20 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 13 Jan 2014 11:26:20 +0000 Subject: [Haskell-cafe] ANN: tree-view-0.1 In-Reply-To: <52D3CCD5.3080703@fuuzetsu.co.uk> References: <52D3CBE6.9020702@chalmers.se> <52D3CCD5.3080703@fuuzetsu.co.uk> Message-ID: <52D3CD5C.5020109@fuuzetsu.co.uk> On 13/01/14 11:24, Mateusz Kowalczyk wrote: > > Hi, > > What does tree-view offer over pretty-tree[1]? > > [1]: http://hackage.haskell.org/package/pretty-tree > Sorry, I didn't read that properly. It'd be nice if we could get the result of htmlTree without having to write it out to the file. -- Mateusz K. From angeljalvarezmiguel at gmail.com Mon Jan 13 11:37:14 2014 From: angeljalvarezmiguel at gmail.com (Angel Alvarez (GMAIL)) Date: Mon, 13 Jan 2014 12:37:14 +0100 Subject: [Haskell-cafe] upgrading from Xcode4 to Xcode5 on Mountain Lion Message-ID: Hi, I have pending the Xcode 4 -> 5 upgrade for a while in my mountain lion, have any of you any pointers to fixes needed in order to get Xcode 5 runnignwith the current haskell platform? from time to time I've seen people having trouble and don't know really if its recommended to upgrade on Mountain Lion... regards, Angel Alvarez (GMAIL) angeljalvarezmiguel at gmail.com From jmacristovao at gmail.com Mon Jan 13 11:47:58 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Mon, 13 Jan 2014 11:47:58 +0000 Subject: [Haskell-cafe] Future imports in GHC/Base Message-ID: Hello all, I was wondering if there is any particular reason for Haskell/GHC not having a kind of "import from Future", similar to Python import __future__, or, in a different take, stuff like modernizr for javascript. Was this done already? My quite simple use case: I could really use the Foldable instance for Either, and also ended up defining my own 'isLeft' and 'isRight'. Felt guilty of re-inventing the wheel after seeing it defined elsewhere, it was so obvious, of course. Then I see it defined in GHC Head - but unfortunatelly not all packages support it yet. And I can only guess that installing base 4.7 on top of GHC 7.6.3 would certainly result in Cabal Hell. I ended up copying the parts that I needed. Any one else doing this? My proposal is simple, and quite restricted: 1) Include only stuff with no dependencies on new compiler features 2) Focus mainly on additional typeclasses instances 3) Or new functions, that otherwise should not interfere with existing code. 4) Use CPP to translate the code into NOP when the new compiler finally enters the Haskell Platform. Thus, a very simple "FutureGHC" package (I'm open to alternative names) would, for isLeft/isRight, be like the code proposed below - taken from GHC Head libraries, of course. What do you think? Joao {-# LANGUAGE CPP #-} -- (...) module Data.Either.GHC707 ( module Data.Either #if __GLASGOW_HASKELL__ < 707 , isLeft , isRight #endif ) where #if __GLASGOW_HASKELL__ < 707 import Data.Either -- | Return `True` if the given value is a `Left`-value, `False` otherwise. -- -- /Since: 4.7.0.0/ isLeft :: Either a b -> Bool isLeft (Left _) = True isLeft (Right _) = False -- | Return `True` if the given value is a `Right`-value, `False` otherwise. -- -- /Since: 4.7.0.0/ isRight :: Either a b -> Bool isRight (Left _) = False isRight (Right _) = True #endif -------------- next part -------------- An HTML attachment was scrubbed... URL: From waldmann at imn.htwk-leipzig.de Mon Jan 13 12:01:02 2014 From: waldmann at imn.htwk-leipzig.de (J. Waldmann) Date: Mon, 13 Jan 2014 12:01:02 +0000 (UTC) Subject: [Haskell-cafe] ANN: tree-view-0.1 References: <52D3CBE6.9020702@chalmers.se> <52D3CCD5.3080703@fuuzetsu.co.uk> <52D3CD5C.5020109@fuuzetsu.co.uk> Message-ID: Mateusz Kowalczyk fuuzetsu.co.uk> writes: > It'd be nice if we could get the result of htmlTree without having to > write it out to the file. htmlTree file = writeFile file . showTreeHtml . enumTree so, just export 'showTreeHtml . enumTree' I am reading 'String', '++' and 'concat' all over the place and that makes me somewhat nervous about performance. I thought 'showTreeHtml' should produce some abstract Html representation (say, Text.Blaze.Html), then the user can decide how to render, and to what type (String, Text, ByteString). - J.W. From emax at chalmers.se Mon Jan 13 12:22:55 2014 From: emax at chalmers.se (Emil Axelsson) Date: Mon, 13 Jan 2014 13:22:55 +0100 Subject: [Haskell-cafe] ANN: tree-view-0.1 In-Reply-To: References: <52D3CBE6.9020702@chalmers.se> <52D3CCD5.3080703@fuuzetsu.co.uk> <52D3CD5C.5020109@fuuzetsu.co.uk> Message-ID: <52D3DA9F.8020309@chalmers.se> 2014-01-13 13:01, J.Waldmann skrev: > Mateusz Kowalczyk fuuzetsu.co.uk> writes: > >> It'd be nice if we could get the result of htmlTree without having to >> write it out to the file. > > htmlTree file = writeFile file . showTreeHtml . enumTree > > so, just export 'showTreeHtml . enumTree' OK, I didn't think there was a use case for this, but I have fixed it now. > I am reading 'String', '++' and 'concat' all over the place and that makes > me somewhat nervous about performance. Yes, but note that `++` is only used on single lines. If anyone runs into performance issues, feel free to submit a patch. > I thought 'showTreeHtml' should produce some abstract Html representation > (say, Text.Blaze.Html), then the user can decide how to render, and to what > type (String, Text, ByteString). That sounds like a good idea! Personally I'm only interested in very simple use cases. But please go ahead if anyone wants to add more flexible outputs. / Emil From haskell-cafe at maartenfaddegon.nl Mon Jan 13 12:45:21 2014 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Mon, 13 Jan 2014 12:45:21 +0000 Subject: [Haskell-cafe] High level overview of GHCi? Message-ID: <52D3DFE1.9050708@maartenfaddegon.nl> Dear Caf?, I was reading http://www.aosabook.org/en/ghc.html. Figure 5.2 gives a high level overview of the compiler passes when compiling Haskell with GHC. Is anyone aware of a similar figure that gives an overview of the passes when Haskell code is interpreted with GHCi? Thank you! Maarten Faddegon From allbery.b at gmail.com Mon Jan 13 14:25:16 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 13 Jan 2014 09:25:16 -0500 Subject: [Haskell-cafe] Future imports in GHC/Base In-Reply-To: References: Message-ID: On Mon, Jan 13, 2014 at 6:47 AM, Jo?o Crist?v?o wrote: > Then I see it defined in GHC Head - but unfortunatelly not all packages > support it yet. And I can only guess that installing base 4.7 on top of GHC > 7.6.3 would certainly result in Cabal Hell. > It's not even possible, since base includes the runtime. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Mon Jan 13 14:32:36 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 13 Jan 2014 09:32:36 -0500 Subject: [Haskell-cafe] upgrading from Xcode4 to Xcode5 on Mountain Lion In-Reply-To: References: Message-ID: On Mon, Jan 13, 2014 at 6:37 AM, Angel Alvarez (GMAIL) < angeljalvarezmiguel at gmail.com> wrote: > I have pending the Xcode 4 -> 5 upgrade for a while in my mountain lion, > have any of you > any pointers to fixes needed in order to get Xcode 5 runnignwith the > current haskell platform? > http://is.gd/H4sEub Or use MacPorts or the Homebrew recipe at https://github.com/darinmorrison/homebrew-haskell. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmacristovao at gmail.com Mon Jan 13 14:35:51 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Mon, 13 Jan 2014 14:35:51 +0000 Subject: [Haskell-cafe] Future imports in GHC/Base In-Reply-To: References: Message-ID: Brandon, yes, it makes sense. So, I've uploaded this into github. Its really small and simple, as expected, but it may be useful to anybody else. https://github.com/jcristovao/BaseFuture Feedback welcomed, Cheers Jo?o 2014/1/13 Brandon Allbery > On Mon, Jan 13, 2014 at 6:47 AM, Jo?o Crist?v?o wrote: > >> Then I see it defined in GHC Head - but unfortunatelly not all packages >> support it yet. And I can only guess that installing base 4.7 on top of GHC >> 7.6.3 would certainly result in Cabal Hell. >> > > It's not even possible, since base includes the runtime. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From davidleothomas at gmail.com Mon Jan 13 15:09:26 2014 From: davidleothomas at gmail.com (David Thomas) Date: Mon, 13 Jan 2014 07:09:26 -0800 Subject: [Haskell-cafe] Structural typing of records in Haskell? In-Reply-To: References: Message-ID: In a sense, Haskell does have structurally typed records - we call them tuples. type Rec1 = (Int, Bool) type Rec2 = (Int, Bool) Now you can pass either to foo :: Rec1 -> Bool On Sun, Jan 12, 2014 at 5:00 PM, Cary Cherng wrote: > Are there statically typed languages that treat records with > structural typing, either imperative or functional? > > Why should records not be structurally typed in Haskell? From what I > understand, in the below foo cannot take a Rec2 even though Rec1 and > Rec2 are essentially the same. > > data Rec1 = Rec1 { a :: Int, b :: Bool} > data Rec2 = Rec2 { a :: Int, b :: Bool} > foo :: Rec1 -> Bool > > Rec1 and Rec2 could be in totally different code libraries. I've read > that preventing Rec2 being used in foo is good for the type safety in > that Rec1 and Rec2 are likely intended to have semantically different > meanings and allowing interchangeability breaks this. > > But then why is map structurally typed. map takes an argument of type > a -> b and suppose some other higher order function bar also takes an > argument of type a -> b. Should map instead have the below type which > prevents a function of type a -> b semantically intended for bar from > being accidentally used in map. > > newtype Mapper a b = Mapper { fn :: a -> b } > map :: Mapper a b -> [a] -> [b] > map _ [] = [] > map f (x:xs) = (fn f) x : map f xs > > If there is a mechanism that prevents something of type Rec2 from > accidentally being used in foo, then why shouldn't there be something > analogous that prevents something of type a -> b (meant for bar) from > accidentally being used in map? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Mon Jan 13 16:25:26 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Mon, 13 Jan 2014 20:25:26 +0400 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: I devised the following (unarguably verbose) solution using the singletons [1] library {-# LANGUAGE DataKinds, TypeFamilies, MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell, GADTs, FlexibleContexts #-} module Image where import Data.Singletons type Point = (Float,Float) $(singletons [d| data Shape' = Circle' | Rectangle' | Arbitrary' deriving (Eq) data Stroke' = Line' | Arc' | Spot' deriving (Eq) |]) data PenShape shape where Circle :: SingI Circle' => Float -> PenShape Circle' Rectangle :: SingI Rectangle' => Float -> Float -> PenShape Rectangle' ArbitraryPen :: PenShape Arbitrary' class AllowedStroke (a::Stroke') (b::Shape') where instance AllowedStroke Line' Circle' instance AllowedStroke Line' Rectangle' instance AllowedStroke Arc' Circle' instance AllowedStroke Spot' Circle' instance AllowedStroke Spot' Rectangle' instance AllowedStroke Spot' Arbitrary' data Stroke where Line :: AllowedStroke Line' a => Point -> Point -> PenShape a -> Stroke Arc :: AllowedStroke Arc' a => Point -> Point -> Point -> PenShape a -> Stroke Spot :: AllowedStroke Spot' a => Point -> PenShape a -> Stroke {- h> :t Line (1,1) (1,1) (Circle 3) Line (1,1) (1,1) (Circle 3) :: Stroke h> :t Line (1,1) (1,1) (Rectangle 3 3) Line (1,1) (1,1) (Rectangle 3 3) :: Stroke h> :t Line (1,1) (1,1) ArbitraryPen :1:1: No instance for (AllowedStroke 'Line' 'Arbitrary') arising from a use of `Line' Possible fix: add an instance declaration for (AllowedStroke 'Line' 'Arbitrary') In the expression: Line (1, 1) (1, 1) ArbitraryPen -} --- unfortunately this still gives non-exhaustive pattern match --- warning :( showStroke :: Stroke -> String showStroke (Line _ _ (Circle _)) = "Line + Circle" showStroke (Line _ _ (Rectangle _ _)) = "Line + Rect" showStroke (Arc _ _ _ (Circle _)) = "Arc" showStroke (Spot _ _) = "Spot" The shortcomings of this approach are the following: - verbosity and repetition (eg: Shape' and Shape) - still gives pattern matching warning ( I suspect that's because typeclasses are open and there is really no way of determining whether something is an 'AllowedStroke' or not) Feel free to improve the code and notify the list :) [1] http://hackage.haskell.org/package/singletons On Mon, Jan 13, 2014 at 7:38 AM, Luke Clifton wrote: > Hi, > > I'm quite new to Haskell, and have been loving exploring it. I've always > been a huge fan of languages that let me catch errors at compile time, > finding dynamic languages like Python a nightmare to work in. I'm finding > with Haskell I can take this compile time checking even further than most > static languages and it has gotten me rather excited. So I was wondering if > there is a Haskell way of solving my problem. > > I'm trying to represent an image made up of a list of strokes. Strokes are > either lines, arcs or spots, and can be made using different pen shapes. > > data Image = Image [Stroke] > > data Stroke = Line Point Point PenShape > | Arc Point Point Point PenShape > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > And this is all great and works. > > But now I have a problem. I want to extend this such that Arc strokes are > only allowed to have the Circle pen shape, and Lines are only allowed to > have the Rectangle or Circle pen shapes. > > What is the best way of enforcing this in the type system. > > I could make more Strokes like LineCircle, LineRectangle, Arc, PointCircle, > PointRectangle, PointArbitrary and get rid of the PenShape type altogether. > But this doesn't really feel good to me (and seems like the amount of work I > have to do is bigger than it needs to be, especially if I added more basic > pen shapes). > > I thought about making the different PenShapes different types, using > typeclasses and making Stroke an algebraic data type, but then my strokes > would be of different types, and I wouldn't be able to have a list of > strokes. > > I have been looking at DataKinds and GADTs, but I can't quite figure out if > they actually help me here at all. > > I'm sure there is a way to do this, I'm just not googling properly. > > What I want to write is... > > data Image = Image [Stroke] > > data Stroke = Line Point Point (Circle or Rectangle) > | Arc Point Point Point Circle > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > Regards, > > Luke > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sincerely yours, -- Daniil From aeyakovenko at gmail.com Mon Jan 13 16:42:46 2014 From: aeyakovenko at gmail.com (anatoly yakovenko) Date: Mon, 13 Jan 2014 08:42:46 -0800 Subject: [Haskell-cafe] any idea why binary isn't bulding on OSX In-Reply-To: References: Message-ID: > > There's a workaround given on > > http://www.haskell.org/platform/mac.html > > In the 'Xcode 5 ^ OS X 10.9 (Mavericks' section. Thanks, that worked. Anatoly From carter.schonwald at gmail.com Mon Jan 13 16:50:18 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 13 Jan 2014 11:50:18 -0500 Subject: [Haskell-cafe] any idea why binary isn't bulding on OSX In-Reply-To: References: Message-ID: That because you need to make sure the GCC in your path points to it , AND you need to edit your ghc settings file, because ghc has a hard coded path to the GCC that it was built with by default. On Monday, January 13, 2014, MigMit wrote: > Installing gcc 4.2 from MacPorts (and port selecting it) helped with this > problem. Gcc 4.8 didn't. > > ?????????? ? iPhone > > > 13 ???. 2014 ?., ? 12:09, Anatoly Yakovenko > > ???????(?): > > > > src/Data/Binary/Get.hs:423:3: > > > > error: invalid preprocessing directive > > > > #-} > > > > ^ > > > > > > src/Data/Binary/Get.hs:511:53: > > > > warning: missing terminating ' character [-Winvalid-pp-token] > > > > -- host order, host endian form, for the machine you're on. On a 64 bit > > > > ^ > > > > 12 warnings and 1 error generated. > > > > Failed to install binary-0.7.1.0 > > > > cabal: Error: some packages failed to install: > > > > JuicyPixels-3.1.2 depends on binary-0.7.1.0 which failed to install. > > > > binary-0.7.1.0 failed during the building phase. The exception was: > > > > ExitFailure 1 > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Jan 13 16:57:41 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 13 Jan 2014 11:57:41 -0500 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: <52D3AFB1.6010601@fuuzetsu.co.uk> References: <52D34359.3050401@fuuzetsu.co.uk> <52D3AFB1.6010601@fuuzetsu.co.uk> Message-ID: Thank you for your great work on haddock. We all appreciate it and look forward to your other works in progress. On Monday, January 13, 2014, Mateusz Kowalczyk wrote: > On 13/01/14 08:58, Sven Panne wrote: > > 2014/1/13 Mateusz Kowalczyk >: > >> [...] * none of your documentation should get parse failures: any > >> previously-failing documentation should now be displayed. [...] > > > > Do we still get warnings or is there a command line flag to get errors > > back? I definitely don't want to browse through dozens of HTML pages > > to check if they look OK. For developing purposes I want as many > > errors I can get. (well, almost ;-) > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > No there is no way to get warnings or errors because it no longer makes > sense to do so. The reason for failures in the past was due to Haddock's > shortcomings rather than user failures: if your docs failed to parse, > you probably tried escaping something where it didn't expect it &c. > Ideally, it should have never had parse failures in the past but the > parser had many short-comings. It's very hard to give warnings because > we can't tell what the user actually wanted to do, only whether they > have input valid markup or not. The only change is that now all markup > should check out as valid. > > If your docs look OK now, they will almost certainly look OK with the > new version. If they are broken now, they might look terrible in the new > version BUT if they are broken now, it's very easy to tell as you'll be > getting parse failures. > > I suggest that if you have any broken documentation right now, go and > fix it. If you don't, great, you should be set. Note that even the > old/current version of Haddock would never present you with any > warnings: it would either error or not. > > I did start to write a tool which would look at your existing > documentation and try to point out any changes between the versions that > might affect you but I did not have the time to finish it and it would > be very naive even if I did. You can find it at [1] but it does close to > nothing. > > All in all you should be safe. The new markup rules are a lot more > intuitive than the old ones and we have not changed anything that would > greatly change existing, well-formed documentation. I don't think there > is any documentation that will start to look worse except for few edge > cases, such as people relying on Haddock not being able to nest markup > to put in some other markup symbols verbatim into their text. You can > now nest markup so that might end up looking slightly differently. > Nothing major. > > John MacFarlane suggested that I create a sort of dingus which would > allow people to input some Haddock markup and be able to see the output > from various versions. I think it'd be a useful tool not only for > migration but for daily use. I did not have the time to start it but > it's certainly in my plans. I'm starting to sit my mid-terms from > tomorrow until the end of the month but I might be able to code > something up after that. If someone is interested in doing this > themselves, let me know so we don't duplicate efforts. > > [1]: http://hackage.haskell.org/package/doccheck > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From marco-oweber at gmx.de Mon Jan 13 21:15:22 2014 From: marco-oweber at gmx.de (Marc Weber) Date: Mon, 13 Jan 2014 22:15:22 +0100 Subject: [Haskell-cafe] OT - targeting many systems Message-ID: <1389646684-sup-3978@nixos> I love Haskell, and it gets many things right. However eg its hard to target JS in an efficient way. Sometimes I just need a quick and dirty (somewhat typesafe) program which gets the job done - sometimes its js, sometimes a tool in console, sometimse web/client code (also smartphone applets). haxe.org comes close, but while the language is fun to use it still has some shortcomings - and sometimes I hit unexpected bugs. The real question I have is: - Haskell is cool - being lazy is cool - having OO is cool (because you can target Java/Flash/.. easily) - how to get best of all worlds? So I think about creating my own language is should look like more like a source code generator than language which contains different sub universes. The idea is to code some parts - such as a parser - in a Haskell like dialect, then reuse it in quick and dirty OO world (Java like). Of course additional targets could be just plain old C, because C++ is known to be very complex - and there are tons of legacy code which should be maintained (such as Vim) - but there is no true upstream, because coding C takes so much more time. I also just don't get why it should not be possible to write code once (such as parsing snippets or highlighting), then reuse it for Vim, Emacs, Yi, .. There is no way, you cannot merge such editors - but eventually there is a way to "code once" and compile down to elisp, C, Haskell ... Live is too short to duplicate much work .. I'm writing to this mailinglist because the knowledge in the Haskell community is incredible - and I want to know * who would join such an effort (maybe write drafts, get funded by kickstarter) * does such attempt already exist ? Languages like impredicative.com/ur, Haskell, lisp, Java, Haxe cleary also illustrate the power of "meta programming" or "source code generation at compile time", yet they all come with their own limitations, eg ur cannot create generate code which is useful outside of a web server and so on. So I feel I'm reinventing the wheel again and again - I'd like to stop this. So the goal would be trying to write "functors/code" which you can instantiate with different memeory management models, tell to target different backends etc. I love Haskell, its community and what it achieved, but somehow I feel that its only 80% of the true story getting everything done. Eg haxe already allows me to write code like such - and then compile it twice: once to create a .js file, once to create server side js/php/neko/whatsoever. class FormComponentGeoLocation { new (opts){ this.opts = opts; } function check(value){ // check with regular expression that value has lat lon numbers } #if SERVER function assignValuesFromInputs(post_data, values){ var value = post_data[opts.name]; check(value); values[opts.name] = post_data[opts.name]; } #end #if js additional client code eg use geo location apis to fill in lat/lon function assignValuesFromInputs(values); var value = post_data[opts.name]; check(value); values[opts.name] = value; } #end } So this is what I'd call modular code I can reuse which has all logic it needs. While Haskell is great I'm unsure wether it allows me to create modules by code (I know about template haskell, but that's only about adding code) - and while being lazy is a feature sometimes I'd like to be strict. (I know that people work on simplifying this) ideas/thougts/links/you'd like to join understanding whether such a goal would be reachable at all? Marc Weber From carter.schonwald at gmail.com Mon Jan 13 21:39:01 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 13 Jan 2014 16:39:01 -0500 Subject: [Haskell-cafe] OT - targeting many systems In-Reply-To: <1389646684-sup-3978@nixos> References: <1389646684-sup-3978@nixos> Message-ID: mark, have you seen ghcjs? It uses the ghc pass hooks to provide a JS targeting backend for full GHC haskell. I imagine you could reuse some of that work to cook up GHC backends for other systems like JVM too! NB: depending on the target, you may want to take over from GHC after core or after CMM, depending on the system in mind.https://github.com/ghcjs/ghcjs On Mon, Jan 13, 2014 at 4:15 PM, Marc Weber wrote: > I love Haskell, and it gets many things right. > However eg its hard to target JS in an efficient way. > Sometimes I just need a quick and dirty (somewhat typesafe) > program which gets the job done - sometimes its js, sometimes a tool in > console, sometimse web/client code (also smartphone applets). > > haxe.org comes close, but while the language is fun to use it still has > some shortcomings - and sometimes I hit unexpected bugs. > > The real question I have is: > - Haskell is cool > - being lazy is cool > - having OO is cool (because you can target Java/Flash/.. easily) > - how to get best of all worlds? > > So I think about creating my own language is should look like more like > a source code generator than language which contains different sub > universes. The idea is to code some parts - such as a parser - in a > Haskell like dialect, then reuse it in quick and dirty OO world (Java > like). > > Of course additional targets could be just plain old C, because C++ is > known to be very complex - and there are tons of legacy code which > should be maintained (such as Vim) - but there is no true upstream, > because coding C takes so much more time. > I also just don't get why it should not be possible to write code once > (such as parsing snippets or highlighting), then reuse it for Vim, > Emacs, Yi, .. > There is no way, you cannot merge such editors - but eventually there is > a way to "code once" and compile down to elisp, C, Haskell ... > Live is too short to duplicate much work .. > > I'm writing to this mailinglist because the knowledge in the Haskell > community is incredible - and I want to know > > * who would join such an effort (maybe write drafts, get funded by > kickstarter) > > * does such attempt already exist ? > > Languages like impredicative.com/ur, Haskell, lisp, Java, Haxe cleary > also illustrate > the power of "meta programming" or "source code generation at compile > time", yet they all come with their own limitations, eg ur cannot create > generate code which is useful outside of a web server and so on. > So I feel I'm reinventing the wheel again and again - I'd like to stop > this. > > So the goal would be trying to write "functors/code" which you can > instantiate with different memeory management models, tell to target > different backends etc. > > I love Haskell, its community and what it achieved, but somehow I feel > that its only 80% of the true story getting everything done. > > Eg haxe already allows me to write code like such - and then compile it > twice: once to create a .js file, once to create server side > js/php/neko/whatsoever. > > class FormComponentGeoLocation { > new (opts){ > this.opts = opts; > } > > function check(value){ > // check with regular expression that value has lat lon numbers > } > > #if SERVER > function assignValuesFromInputs(post_data, values){ > var value = post_data[opts.name]; > check(value); > values[opts.name] = post_data[opts.name]; > } > #end > > #if js > additional client code > eg use geo location apis to fill in lat/lon > > function assignValuesFromInputs(values); > var value = post_data[opts.name]; > check(value); > values[opts.name] = value; > } > #end > > } > > So this is what I'd call modular code I can reuse which has all logic it > needs. > > While Haskell is great I'm unsure wether it allows me to create modules > by code (I know about template haskell, but that's only about adding > code) - and while being lazy is a feature sometimes I'd like to be > strict. (I know that people work on simplifying this) > > ideas/thougts/links/you'd like to join understanding whether such a > goal would be reachable at all? > > Marc Weber > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Mon Jan 13 21:50:19 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 13 Jan 2014 22:50:19 +0100 Subject: [Haskell-cafe] Error management in Happstack Message-ID: Hi Jeremy, all, In Happstack when I throw an error, I obtain a blank page with "server error: my message". How can I decorate this page? I'd like to have it look like the other pages of my website, and a "back to login" link, for example. Thanks! Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From danburton.email at gmail.com Mon Jan 13 21:50:38 2014 From: danburton.email at gmail.com (Dan Burton) Date: Mon, 13 Jan 2014 13:50:38 -0800 Subject: [Haskell-cafe] OT - targeting many systems In-Reply-To: <1389646684-sup-3978@nixos> References: <1389646684-sup-3978@nixos> Message-ID: I think the closest existing thing to what you have described is Roy: http://roy.brianmckenna.org/ Roy is a delightful "it's just JavaScript" language with some type/safety checking and syntactic sugar. From my extremely limited experience with Roy, it's still very alpha, and it's one of those "not quite Haskell syntax" experiences that will bite you if you forget. Roy is strict by default. Eg haxe already allows me to write code like such - and then compile it > twice: once to create a .js file, once to create server side > js/php/neko/whatsoever. That sounds a lot like what Fay is used for. You can share some .hs files between server-side and client-side code. And Fay is "just [a subset of] Haskell," which is really nice. Fay is lazy by default. https://github.com/faylang/fay/wiki -- Dan Burton On Mon, Jan 13, 2014 at 1:15 PM, Marc Weber wrote: > I love Haskell, and it gets many things right. > However eg its hard to target JS in an efficient way. > Sometimes I just need a quick and dirty (somewhat typesafe) > program which gets the job done - sometimes its js, sometimes a tool in > console, sometimse web/client code (also smartphone applets). > > haxe.org comes close, but while the language is fun to use it still has > some shortcomings - and sometimes I hit unexpected bugs. > > The real question I have is: > - Haskell is cool > - being lazy is cool > - having OO is cool (because you can target Java/Flash/.. easily) > - how to get best of all worlds? > > So I think about creating my own language is should look like more like > a source code generator than language which contains different sub > universes. The idea is to code some parts - such as a parser - in a > Haskell like dialect, then reuse it in quick and dirty OO world (Java > like). > > Of course additional targets could be just plain old C, because C++ is > known to be very complex - and there are tons of legacy code which > should be maintained (such as Vim) - but there is no true upstream, > because coding C takes so much more time. > I also just don't get why it should not be possible to write code once > (such as parsing snippets or highlighting), then reuse it for Vim, > Emacs, Yi, .. > There is no way, you cannot merge such editors - but eventually there is > a way to "code once" and compile down to elisp, C, Haskell ... > Live is too short to duplicate much work .. > > I'm writing to this mailinglist because the knowledge in the Haskell > community is incredible - and I want to know > > * who would join such an effort (maybe write drafts, get funded by > kickstarter) > > * does such attempt already exist ? > > Languages like impredicative.com/ur, Haskell, lisp, Java, Haxe cleary > also illustrate > the power of "meta programming" or "source code generation at compile > time", yet they all come with their own limitations, eg ur cannot create > generate code which is useful outside of a web server and so on. > So I feel I'm reinventing the wheel again and again - I'd like to stop > this. > > So the goal would be trying to write "functors/code" which you can > instantiate with different memeory management models, tell to target > different backends etc. > > I love Haskell, its community and what it achieved, but somehow I feel > that its only 80% of the true story getting everything done. > > Eg haxe already allows me to write code like such - and then compile it > twice: once to create a .js file, once to create server side > js/php/neko/whatsoever. > > class FormComponentGeoLocation { > new (opts){ > this.opts = opts; > } > > function check(value){ > // check with regular expression that value has lat lon numbers > } > > #if SERVER > function assignValuesFromInputs(post_data, values){ > var value = post_data[opts.name]; > check(value); > values[opts.name] = post_data[opts.name]; > } > #end > > #if js > additional client code > eg use geo location apis to fill in lat/lon > > function assignValuesFromInputs(values); > var value = post_data[opts.name]; > check(value); > values[opts.name] = value; > } > #end > > } > > So this is what I'd call modular code I can reuse which has all logic it > needs. > > While Haskell is great I'm unsure wether it allows me to create modules > by code (I know about template haskell, but that's only about adding > code) - and while being lazy is a feature sometimes I'd like to be > strict. (I know that people work on simplifying this) > > ideas/thougts/links/you'd like to join understanding whether such a > goal would be reachable at all? > > Marc Weber > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ccherng at gmail.com Tue Jan 14 03:58:16 2014 From: ccherng at gmail.com (Cary Cherng) Date: Mon, 13 Jan 2014 19:58:16 -0800 Subject: [Haskell-cafe] Records vs Tuples Message-ID: What exactly is the purpose in having both records and tuples? They seem to behave rather similarly although records do have the extra naming of the fields that tuples don't. From ivan.miljenovic at gmail.com Tue Jan 14 05:27:35 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Tue, 14 Jan 2014 16:27:35 +1100 Subject: [Haskell-cafe] Records vs Tuples In-Reply-To: References: Message-ID: On 14 January 2014 14:58, Cary Cherng wrote: > What exactly is the purpose in having both records and tuples? They > seem to behave rather similarly although records do have the extra > naming of the fields that tuples don't. Tuples: let you quickly group values together for one-off cases. Custom data types: named grouping of values so you can give them a specific type; optionally not exposing constructor so that you can hide internals. Record syntax is a a way of naming specific fields within these data types. Note that what you actually seem to be asking is "why have any data type whose constructor can take more than one value", as this is what a tuple is a specific instance of: data Pair a b = Pair a b data Triple a b c = Triple a b c etc. You can consider tuples to be pre-defined types with convenient syntax. But if you want to properly type your code you should define your own types as appropriate. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From christian at ponies.io Tue Jan 14 05:48:23 2014 From: christian at ponies.io (Christian Marie) Date: Tue, 14 Jan 2014 16:48:23 +1100 Subject: [Haskell-cafe] flip1 through flip9, useful? Message-ID: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> I have defined a bunch of functions like this: -- | Move the fourth argument to the first place rotate4 :: (a -> b -> c -> d -> e) -> (d -> a -> b -> c -> e) -- | Reverse four arguments flip4 :: (a -> b -> c -> d -> e) -> (d -> c -> b -> a -> e) I decided to upload this as a library to hackage, as I personally find it useful, especially for writing FFI bindings. It seems like I can't be the first to write a library like this though, am I missing something obvious? Is this useful or stupid? Does it exist already? Full definition here: https://github.com/christian-marie/flippers/blob/master/src/Control/Flippers.hs -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 836 bytes Desc: not available URL: From ivan.miljenovic at gmail.com Tue Jan 14 06:06:27 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Tue, 14 Jan 2014 17:06:27 +1100 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> Message-ID: On 14 January 2014 16:48, Christian Marie wrote: > I have defined a bunch of functions like this: > > -- | Move the fourth argument to the first place > rotate4 :: (a -> b -> c -> d -> e) -> (d -> a -> b -> c -> e) > > -- | Reverse four arguments > flip4 :: (a -> b -> c -> d -> e) -> (d -> c -> b -> a -> e) > > I decided to upload this as a library to hackage, as I personally find it > useful, especially for writing FFI bindings. > > It seems like I can't be the first to write a library like this though, am I > missing something obvious? Is this useful or stupid? Does it exist already? > > Full definition here: > > https://github.com/christian-marie/flippers/blob/master/src/Control/Flippers.hs Except for completeness, I don't see the point of rotate1 and flip1. I'd also be tempted to possibly shift the module to Data.Function.Flippers (as flip is re-exported by Data.Function in base, and it seems like a more valid location to me). That said, whilst I do use flip upon occasion, I think in the general case it'd be too easy to abuse these kinds of functions and could be more difficult to work any errors if you used the wrong one or had some arguments in the wrong order. -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From tonymorris at gmail.com Tue Jan 14 06:57:14 2014 From: tonymorris at gmail.com (Tony Morris) Date: Tue, 14 Jan 2014 16:57:14 +1000 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> Message-ID: <52D4DFCA.8000703@gmail.com> On 14/01/14 15:48, Christian Marie wrote: > I have defined a bunch of functions like this: > > -- | Move the fourth argument to the first place > rotate4 :: (a -> b -> c -> d -> e) -> (d -> a -> b -> c -> e) > > -- | Reverse four arguments > flip4 :: (a -> b -> c -> d -> e) -> (d -> c -> b -> a -> e) > > I decided to upload this as a library to hackage, as I personally find it > useful, especially for writing FFI bindings. > > It seems like I can't be the first to write a library like this though, am I > missing something obvious? Is this useful or stupid? Does it exist already? > > Full definition here: > > https://github.com/christian-marie/flippers/blob/master/src/Control/Flippers.hs > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe Why not generalise to any functor? let flip f a = fmap ($a) f -- Tony Morris http://tmorris.net/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Tue Jan 14 07:07:40 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Tue, 14 Jan 2014 14:07:40 +0700 Subject: [Haskell-cafe] Records vs Tuples In-Reply-To: References: Message-ID: On Tue, Jan 14, 2014 at 10:58 AM, Cary Cherng wrote: > What exactly is the purpose in having both records and tuples? They > seem to behave rather similarly > What's the purpose of distinguishing between US dollars, OZ dollars, Can dollars, etc? At the end of the day, aren't they just _numbers_? -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From alex.solla at gmail.com Tue Jan 14 07:12:54 2014 From: alex.solla at gmail.com (Alexander Solla) Date: Mon, 13 Jan 2014 23:12:54 -0800 Subject: [Haskell-cafe] Records vs Tuples In-Reply-To: References: Message-ID: On Mon, Jan 13, 2014 at 11:07 PM, Kim-Ee Yeoh wrote: > > On Tue, Jan 14, 2014 at 10:58 AM, Cary Cherng wrote: > >> What exactly is the purpose in having both records and tuples? They >> seem to behave rather similarly >> > > What's the purpose of distinguishing between US dollars, OZ dollars, Can > dollars, etc? At the end of the day, aren't they just _numbers_? > > -- Kim-Ee > Maybe I'm tired, but I thought you were serious there for a moment. :) -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Jan 14 07:26:34 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 14 Jan 2014 07:26:34 +0000 Subject: [Haskell-cafe] Records vs Tuples In-Reply-To: References: Message-ID: <52D4E6AA.9080004@fuuzetsu.co.uk> On 14/01/14 03:58, Cary Cherng wrote: > What exactly is the purpose in having both records and tuples? They > seem to behave rather similarly although records do have the extra > naming of the fields that tuples don't. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Didn't we just have this thread the other day but the case being ?Maybe a? vs ?Either () a?? I'm sure all the arguments that come up in this thread have already been answered there. -- Mateusz K. From hvr at gnu.org Tue Jan 14 07:46:00 2014 From: hvr at gnu.org (Herbert Valerio Riedel) Date: Tue, 14 Jan 2014 08:46:00 +0100 Subject: [Haskell-cafe] Future imports in GHC/Base In-Reply-To: (=?utf-8?B?Ikpvw6NvIENyaXN0w7N2w6NvIidz?= message of "Mon, 13 Jan 2014 11:47:58 +0000") References: Message-ID: <8738kr2eh3.fsf@gnu.org> Hi, On 2014-01-13 at 12:47:58 +0100, Jo?o Crist?v?o wrote: > I was wondering if there is any particular reason for Haskell/GHC not > having a kind of "import from Future", similar to Python import __future__, > or, in a different take, stuff like modernizr for javascript. > > Was this done already? Have you seen http://hackage.haskell.org/package/base-compat ? Cheers, hvr From ky3 at atamo.com Tue Jan 14 08:14:45 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Tue, 14 Jan 2014 15:14:45 +0700 Subject: [Haskell-cafe] Records vs Tuples In-Reply-To: References: Message-ID: On Tue, Jan 14, 2014 at 2:12 PM, Alexander Solla wrote: > Maybe I'm tired, but I thought you were serious there for a moment. :) Channeling Socrates, who tends to be under-rated. ;) p.s. not that I consider myself anywhere that good -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Tue Jan 14 08:34:01 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 14 Jan 2014 08:34:01 -0000 Subject: [Haskell-cafe] Records vs Tuples Message-ID: <20140114083401.76969.qmail@www1.g3.pair.com> Cary Cherng wrote: > What exactly is the purpose in having both records and tuples? They > seem to behave rather similarly although records do have the extra > naming of the fields that tuples don't. In SML there is really no difference: In fact, in Standard ML, tuples are simply a special case of records; for example, the type int * string * bool is the same as the type { 1 : int, 2 : string, 3 : bool }. http://en.wikibooks.org/wiki/Standard_ML_Programming/Types In some programming languages (C, OCaml, Haskell), records, or structures, have to be declared and are not extensible. OCaml also has extensible records, which don't have to be declared and whose field names may be reused. Tuples may be thought of as `extensible' records that don't have to be declared (and HList takes this thought quite seriously). > data Rec1 = Rec1 { a :: Int, b :: Bool} > data Rec2 = Rec2 { a :: Int, b :: Bool} > foo :: Rec1 -> Bool > > Rec1 and Rec2 could be in totally different code libraries. I've read > that preventing Rec2 being used in foo is good for the type safety in > that Rec1 and Rec2 are likely intended to have semantically different > meanings and allowing interchangeability breaks this. The reason is not type safety but type inference, or the ease of it. Given > data Rec1 = Rec1 { rec1a :: Int, rec1b :: Bool} > data Rec2 = Rec2 { rec2a :: Int, rec2b :: Bool} and the term \x -> rec2a x + 1 the type checker quickly determines that x must be of a type Rec2, and the inferred type is Rec2 -> Int. With extensible records, using OCaml: # fun x -> x#rec2a + 1;; - : < rec2a : int; .. > -> int = we infer a polymorphic type. That's all nice, until we look at the OCaml type checker and see the complexity of inference. Open records bring up lots of interesting problems (e.g., variance), which interact in interesting and not yet worked out ways with other features (e.g., GADTs). Also, open records can often mask problems. For example, in Haskell \x -> rec1a x + rec2a x won't type check but the corresponding code in OCaml will -- although the programmer may have never intended a record with both fields rec1a and rec2a. OCaml community has had a lot of experience with extensible and non-extensible records (and their dual -- extensible and non-extensible variants). The conclusion seems to be that both are needed. Often a programmer does mean closed records/variants; and non-extensible forms match the programmer's intent closely and give better, and earlier, error messages. From alan.zimm at gmail.com Tue Jan 14 10:04:03 2014 From: alan.zimm at gmail.com (AlanKim Zimmerman) Date: Tue, 14 Jan 2014 12:04:03 +0200 Subject: [Haskell-cafe] Target Selection in HaRe Message-ID: The Haskell Refactorer now makes use of the GHC API to load and typecheck the code to be refactored. It uses ghc-mod internally to identify a project cabal file, and extract the targets in it. The current code attempts to load all the targets into the module graph, to make sure that when a project is refactored the ancillary parts such as tests and benchmarks are refactored too, e.g. when renaming a function. The problem is that GHC is unable to load more than one main file. I am trying to decide on the best way of resolving this in terms of a user of HaRe, where it should 'just work' most of the time. The actual refactoring is done by calling the HaRe executable with command line arguments. Options that seem viable are 1. require the names of the target(s) to be loaded to be passed in as command line arguments. This means the IDE integration is going to have to provide a way of deciding the scope of the refactoring. 2. Create a config file that lives in the project directory and specifies the targets to be loaded 3. Try to build up a union of the module graph for all the targets, excluding all main modules. The problem with this is that it then becomes difficult to refactor a main module. 4. A different option, or blend of the above.e.g. load the union but specify the specific main module. Does anyone have any preferences in terms of this? Alan -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpmoresmau at gmail.com Tue Jan 14 10:25:52 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Tue, 14 Jan 2014 11:25:52 +0100 Subject: [Haskell-cafe] Target Selection in HaRe In-Reply-To: References: Message-ID: Can't you do the union of module graphs for all targets by adding the file names to the modules or something, so you could have several main modules using different files in a general graph? What I know is how we do renames in EclipseFP: we use the GHC API to generate usage information for each different targets then the data is actually stored in a DB, and the Java code uses this info to perform renames everywhere (across projects, even). Of course you don't want all that, but you should be able to decorate the module graph with file names and perform the union. JP On Tue, Jan 14, 2014 at 11:04 AM, AlanKim Zimmerman wrote: > The Haskell Refactorer now makes use of the GHC API to load and typecheck > the code to be refactored. > > It uses ghc-mod internally to identify a project cabal file, and extract > the targets in it. > > The current code attempts to load all the targets into the module graph, > to make sure that when a project is refactored the ancillary parts such as > tests and benchmarks are refactored too, e.g. when renaming a function. > > The problem is that GHC is unable to load more than one main file. > > I am trying to decide on the best way of resolving this in terms of a user > of HaRe, where it should 'just work' most of the time. The actual > refactoring is done by calling the HaRe executable with command line > arguments. > > Options that seem viable are > > 1. require the names of the target(s) to be loaded to be passed in as > command line arguments. > > This means the IDE integration is going to have to provide a way of > deciding the scope of the refactoring. > > 2. Create a config file that lives in the project directory and specifies > the targets to be loaded > > 3. Try to build up a union of the module graph for all the targets, > excluding all main modules. > > The problem with this is that it then becomes difficult to refactor a main > module. > > 4. A different option, or blend of the above.e.g. load the union but > specify the specific main module. > > > Does anyone have any preferences in terms of this? > > Alan > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmacristovao at gmail.com Tue Jan 14 10:26:41 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Tue, 14 Jan 2014 10:26:41 +0000 Subject: [Haskell-cafe] Future imports in GHC/Base In-Reply-To: <8738kr2eh3.fsf@gnu.org> References: <8738kr2eh3.fsf@gnu.org> Message-ID: Hi Herbert, I don't know how I could have missed it! Thanks, I will send a push request to merge this. 2014/1/14 Herbert Valerio Riedel > Hi, > > On 2014-01-13 at 12:47:58 +0100, Jo?o Crist?v?o wrote: > > I was wondering if there is any particular reason for Haskell/GHC not > > having a kind of "import from Future", similar to Python import > __future__, > > or, in a different take, stuff like modernizr for javascript. > > > > Was this done already? > > Have you seen > > http://hackage.haskell.org/package/base-compat > > ? > > Cheers, > hvr > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Tue Jan 14 10:31:26 2014 From: alan.zimm at gmail.com (AlanKim Zimmerman) Date: Tue, 14 Jan 2014 12:31:26 +0200 Subject: [Haskell-cafe] Target Selection in HaRe In-Reply-To: References: Message-ID: I'm trying to steer away from a database if I can avoid it. And also hoping to not have to store meta information outside the GHC AST to do a multi phase refactor, e.g. the usage information to know where a name was used for renaming. I think the union will work best, with some kind of selection of the current main to work with, or just store the additional info for the main modules. Alan On Jan 14, 2014 6:25 PM, "JP Moresmau" wrote: > Can't you do the union of module graphs for all targets by adding the file > names to the modules or something, so you could have several main modules > using different files in a general graph? > What I know is how we do renames in EclipseFP: we use the GHC API to > generate usage information for each different targets then the data is > actually stored in a DB, and the Java code uses this info to perform > renames everywhere (across projects, even). Of course you don't want all > that, but you should be able to decorate the module graph with file names > and perform the union. > > JP > > > On Tue, Jan 14, 2014 at 11:04 AM, AlanKim Zimmerman wrote: > >> The Haskell Refactorer now makes use of the GHC API to load and typecheck >> the code to be refactored. >> >> It uses ghc-mod internally to identify a project cabal file, and extract >> the targets in it. >> >> The current code attempts to load all the targets into the module graph, >> to make sure that when a project is refactored the ancillary parts such as >> tests and benchmarks are refactored too, e.g. when renaming a function. >> >> The problem is that GHC is unable to load more than one main file. >> >> I am trying to decide on the best way of resolving this in terms of a >> user of HaRe, where it should 'just work' most of the time. The actual >> refactoring is done by calling the HaRe executable with command line >> arguments. >> >> Options that seem viable are >> >> 1. require the names of the target(s) to be loaded to be passed in as >> command line arguments. >> >> This means the IDE integration is going to have to provide a way of >> deciding the scope of the refactoring. >> >> 2. Create a config file that lives in the project directory and specifies >> the targets to be loaded >> >> 3. Try to build up a union of the module graph for all the targets, >> excluding all main modules. >> >> The problem with this is that it then becomes difficult to refactor a >> main module. >> >> 4. A different option, or blend of the above.e.g. load the union but >> specify the specific main module. >> >> >> Does anyone have any preferences in terms of this? >> >> Alan >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > > -- > JP Moresmau > http://jpmoresmau.blogspot.com/ > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpmoresmau at gmail.com Tue Jan 14 10:43:29 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Tue, 14 Jan 2014 11:43:29 +0100 Subject: [Haskell-cafe] Target Selection in HaRe In-Reply-To: References: Message-ID: OK, but I don't really understand how you can do a rename with only "some" of the targets. You mean that if I rename a function used in the main module of two executables in one single project, the rename will only be effective in one executable, and the other one will stop compiling? That sounds sub-optimal to me. A lot of project now have several targets; executables, test-suites, benchmarks... JP On Tue, Jan 14, 2014 at 11:31 AM, AlanKim Zimmerman wrote: > I'm trying to steer away from a database if I can avoid it. And also > hoping to not have to store meta information outside the GHC AST to do a > multi phase refactor, e.g. the usage information to know where a name was > used for renaming. > > I think the union will work best, with some kind of selection of the > current main to work with, or just store the additional info for the main > modules. > > Alan > On Jan 14, 2014 6:25 PM, "JP Moresmau" wrote: > >> Can't you do the union of module graphs for all targets by adding the >> file names to the modules or something, so you could have several main >> modules using different files in a general graph? >> What I know is how we do renames in EclipseFP: we use the GHC API to >> generate usage information for each different targets then the data is >> actually stored in a DB, and the Java code uses this info to perform >> renames everywhere (across projects, even). Of course you don't want all >> that, but you should be able to decorate the module graph with file names >> and perform the union. >> >> JP >> >> >> On Tue, Jan 14, 2014 at 11:04 AM, AlanKim Zimmerman wrote: >> >>> The Haskell Refactorer now makes use of the GHC API to load and >>> typecheck the code to be refactored. >>> >>> It uses ghc-mod internally to identify a project cabal file, and extract >>> the targets in it. >>> >>> The current code attempts to load all the targets into the module graph, >>> to make sure that when a project is refactored the ancillary parts such as >>> tests and benchmarks are refactored too, e.g. when renaming a function. >>> >>> The problem is that GHC is unable to load more than one main file. >>> >>> I am trying to decide on the best way of resolving this in terms of a >>> user of HaRe, where it should 'just work' most of the time. The actual >>> refactoring is done by calling the HaRe executable with command line >>> arguments. >>> >>> Options that seem viable are >>> >>> 1. require the names of the target(s) to be loaded to be passed in as >>> command line arguments. >>> >>> This means the IDE integration is going to have to provide a way of >>> deciding the scope of the refactoring. >>> >>> 2. Create a config file that lives in the project directory and >>> specifies the targets to be loaded >>> >>> 3. Try to build up a union of the module graph for all the targets, >>> excluding all main modules. >>> >>> The problem with this is that it then becomes difficult to refactor a >>> main module. >>> >>> 4. A different option, or blend of the above.e.g. load the union but >>> specify the specific main module. >>> >>> >>> Does anyone have any preferences in terms of this? >>> >>> Alan >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> >> >> -- >> JP Moresmau >> http://jpmoresmau.blogspot.com/ >> > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpmoresmau at gmail.com Tue Jan 14 20:13:40 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Tue, 14 Jan 2014 21:13:40 +0100 Subject: [Haskell-cafe] GHC API: runStmt not taking into account reloaded module Message-ID: It's late here and I'm probably overlooking something stupid, so I'd like if somebody could put my nose on it... I'm using the GHC API to evaluate statements. I use runStmt to get a RunResult, lookupName to get the ID for the bound names, obtainTermFromId to get the term and showTerm to display it. So I can call a function from the loaded module with some parameters and get the result. Good! However, if I reload a module and I change the implementation of the function, runStmt still returns the old value! I know the reload worked because if I added new names, getNamesInScope returns the new names. What do I need to do to make sure the new function definitions are used? I've perused the source code of InteractiveEval and ghci but nothing stood out. I am calling setContext after load. Thanks a million! -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at orlitzky.com Tue Jan 14 22:25:21 2014 From: michael at orlitzky.com (Michael Orlitzky) Date: Tue, 14 Jan 2014 17:25:21 -0500 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> Message-ID: <52D5B951.6040102@orlitzky.com> On 01/14/2014 01:06 AM, Ivan Lazar Miljenovic wrote: > On 14 January 2014 16:48, Christian Marie wrote: >> I have defined a bunch of functions like this: >> >> -- | Move the fourth argument to the first place >> rotate4 :: (a -> b -> c -> d -> e) -> (d -> a -> b -> c -> e) >> >> -- | Reverse four arguments >> flip4 :: (a -> b -> c -> d -> e) -> (d -> c -> b -> a -> e) >> >> I decided to upload this as a library to hackage, as I personally find it >> useful, especially for writing FFI bindings. >> >> It seems like I can't be the first to write a library like this though, am I >> missing something obvious? Is this useful or stupid? Does it exist already? >> >> Full definition here: >> >> https://github.com/christian-marie/flippers/blob/master/src/Control/Flippers.hs > > Except for completeness, I don't see the point of rotate1 and flip1. > It could be nice if you're attempting something insane with e.g. template haskell and don't want n=1 to be a special case. From christian at ponies.io Tue Jan 14 23:30:15 2014 From: christian at ponies.io (Christian Marie) Date: Wed, 15 Jan 2014 10:30:15 +1100 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <52D4DFCA.8000703@gmail.com> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> Message-ID: <20140114233015.GA22859@cucumber.bridge.anchor.net.au> On Tue, Jan 14, 2014 at 04:57:14PM +1000, Tony Morris wrote: > Why not generalise to any functor? > let flip f a = fmap ($a) f I didn't think of that, I suppose. Now that I do, it seems to be a tradeoff between (arguably) less immediately obvious type signatures and something. I can't actually think of what that something is yet. Can you think of a real world use for a functor flip where normal flip wouldn't do? -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 836 bytes Desc: not available URL: From alex.solla at gmail.com Tue Jan 14 23:38:07 2014 From: alex.solla at gmail.com (Alexander Solla) Date: Tue, 14 Jan 2014 15:38:07 -0800 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <52D4DFCA.8000703@gmail.com> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> Message-ID: On Mon, Jan 13, 2014 at 10:57 PM, Tony Morris wrote: > On 14/01/14 15:48, Christian Marie wrote: > > I have defined a bunch of functions like this: > > -- | Move the fourth argument to the first place > rotate4 :: (a -> b -> c -> d -> e) -> (d -> a -> b -> c -> e) > > -- | Reverse four arguments > flip4 :: (a -> b -> c -> d -> e) -> (d -> c -> b -> a -> e) > > I decided to upload this as a library to hackage, as I personally find it > useful, especially for writing FFI bindings. > > It seems like I can't be the first to write a library like this though, am I > missing something obvious? Is this useful or stupid? Does it exist already? > > Full definition here: > https://github.com/christian-marie/flippers/blob/master/src/Control/Flippers.hs > > > > _______________________________________________ > Haskell-Cafe mailing listHaskell-Cafe at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe > > Why not generalise to any functor? > > let flip f a = fmap ($a) f > I don't see that operator as "flip-like", personally. It might behave as flip in the case of the function functor , but that intuition does not carry over to things like fmap ($a) [f, g, h] = [f a, g a, h a] I'd call it "funder", personally. -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Tue Jan 14 23:40:01 2014 From: jwlato at gmail.com (John Lato) Date: Tue, 14 Jan 2014 15:40:01 -0800 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <20140114233015.GA22859@cucumber.bridge.anchor.net.au> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> <20140114233015.GA22859@cucumber.bridge.anchor.net.au> Message-ID: On Tue, Jan 14, 2014 at 3:30 PM, Christian Marie wrote: > On Tue, Jan 14, 2014 at 04:57:14PM +1000, Tony Morris wrote: > > Why not generalise to any functor? > > let flip f a = fmap ($a) f > > I didn't think of that, I suppose. > > Now that I do, it seems to be a tradeoff between (arguably) less > immediately > obvious type signatures and something. > > I can't actually think of what that something is yet. Can you think of a > real > world use for a functor flip where normal flip wouldn't do? > I know I've written "fmap ($a) f" in the past, so I guess any of those would be a use case for a functor flip. On the other hand, it's only a few characters longer than flip, and arguably more clear, so I'm not convinced that generalizing flip is useful. YMMV. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rhymoid at gmail.com Tue Jan 14 23:42:16 2014 From: rhymoid at gmail.com (Stijn van Drongelen) Date: Wed, 15 Jan 2014 00:42:16 +0100 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <20140114233015.GA22859@cucumber.bridge.anchor.net.au> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> <20140114233015.GA22859@cucumber.bridge.anchor.net.au> Message-ID: On Wed, Jan 15, 2014 at 12:30 AM, Christian Marie wrote: > On Tue, Jan 14, 2014 at 04:57:14PM +1000, Tony Morris wrote: > > Why not generalise to any functor? > > let flip f a = fmap ($a) f > > I didn't think of that, I suppose. > > Now that I do, it seems to be a tradeoff between (arguably) less > immediately > obvious type signatures and something. > > I can't actually think of what that something is yet. Can you think of a > real > world use for a functor flip where normal flip wouldn't do? > > I think it's mostly a skeleton to use for generalizing flip. Right now, you have \f a -> fmap ($a) f :: Functor f => f (a -> b) -> a -> f b so if you take (f ~ (->) c), you have \f a -> fmap ($a) f :: (c -> a -> b) -> (a -> c -> b) For flips of higher arities, you would choose a different `f`, like (f ~ (->) d . (->) c): \f a -> fmap ($a) f :: (c -> d -> a -> b) -> (a -> c -> d -> b) -------------- next part -------------- An HTML attachment was scrubbed... URL: From dagitj at gmail.com Wed Jan 15 00:23:18 2014 From: dagitj at gmail.com (Jason Dagit) Date: Tue, 14 Jan 2014 16:23:18 -0800 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> <20140114233015.GA22859@cucumber.bridge.anchor.net.au> Message-ID: While I don't think the overall idea is good*, I do wonder if the explicit numbers in the names could be removed. Here are some approaches to writing N-ary zipWith that might give you inspiration: https://gist.github.com/dagit/6082516 https://gist.github.com/dagit/8428444 Both have links to the original sources. The first one depends on closed type families and the other one still uses numerals but they are just names for special functions that makes it all hold together. * I don't think we should encourage use of things like flip8 in 'real code' because it's very likely to make the code completely incomprehensible. I DO think it's a fun and interesting exercise to generalizing flip to N-ary. Jason -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Wed Jan 15 09:56:52 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 15 Jan 2014 09:56:52 +0000 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <52D4DFCA.8000703@gmail.com> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> Message-ID: <20140115095652.GO28182@weber> On Tue, Jan 14, 2014 at 04:57:14PM +1000, Tony Morris wrote: > Why not generalise to any functor? > > let flip f a = fmap ($a) f FYI, this is Control.Lens.?? http://hackage.haskell.org/package/lens-3.9.2/docs/src/Control-Lens-Combinators.html#%3F%3F Tom From mail at joachim-breitner.de Wed Jan 15 09:57:57 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Wed, 15 Jan 2014 09:57:57 +0000 Subject: [Haskell-cafe] mdo with multiple values Message-ID: <1389779877.2660.4.camel@kirk> Dear List, a little puzzle. Given a monad M with a MonadFix instance, and these two functions: act1 :: T -> M () act2 :: a -> M T I morally want to write this function: foo :: [a] -> M () foo = mdo mapM_ act1 xs xs <- mapM act2 return () Unfortunately, that will not work: mapM_ will force xs before any of it can be generated. But morally it should be possible, as the lists passed to mapM_ and mapM have the same, already known list. So here is my solution (which is a bit more general, because I happen to need some that in one place): mapFstMapSnd :: MonadFix m => [(a -> m (), m a)] -> m () mapFstMapSnd xs = const () `liftM` go xs (return []) where go [] cont = cont go ((f,s):xs) cont = mdo f v (v:vs) <- go xs $ do vs <- cont v <- s return (v:vs) return vs Using that, I can write foo = mapFstSnd . map (x -> (act1, act2 x)) Are there better solutions? Simpler ones? Or possibly ones that do not require a partial pattern? Hmm, and thinking while writing lets me come up with data FunSplit m where FunSplit :: forall m a . (a -> m ()) -> m a -> FunSplit m mapFstMapSnd :: forall m. MonadFix m => [FunSplit m] -> m () mapFstMapSnd xs = const () `liftM` go xs (return ()) where go :: [FunSplit m] -> m b -> m b go [] cont = cont go (FunSplit f s:xs) cont = mdo f v (v,vs) <- go xs $ do vs <- cont v <- s return (v,vs) return vs foo :: [SPut] -> SPut foo = mapFstMapSnd . map go where go x = FunSplit act1 (act2 x) Any suggestions for improvement? Thanks, Joachim -- Joachim Breitner e-Mail: mail at joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata at joachim-breitner.de -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 181 bytes Desc: This is a digitally signed message part URL: From tonymorris at gmail.com Wed Jan 15 10:48:51 2014 From: tonymorris at gmail.com (Tony Morris) Date: Wed, 15 Jan 2014 20:48:51 +1000 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: <20140115095652.GO28182@weber> References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> <20140115095652.GO28182@weber> Message-ID: <52D66793.20609@gmail.com> Indeed! I offered the question as a coaching exercise :) On 15/01/14 19:56, Tom Ellis wrote: > On Tue, Jan 14, 2014 at 04:57:14PM +1000, Tony Morris wrote: >> Why not generalise to any functor? >> >> let flip f a = fmap ($a) f > FYI, this is Control.Lens.?? > > http://hackage.haskell.org/package/lens-3.9.2/docs/src/Control-Lens-Combinators.html#%3F%3F > > Tom > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Tony Morris http://tmorris.net/ From barak at cs.nuim.ie Wed Jan 15 12:01:43 2014 From: barak at cs.nuim.ie (Barak A. Pearlmutter) Date: Wed, 15 Jan 2014 12:01:43 +0000 Subject: [Haskell-cafe] Postdocs / Research Programmer for Efficient First-Class Automatic Differentiation Message-ID: <874n55bgig.fsf@cs.nuim.ie> Postdocs / Research Programmer for Compositional Learning via Generalized Automatic Differentiation The goal of this project is to make a qualitative improvement in our ability to write sophisticated numeric code, by giving numeric programmers access to _fast_, _robust_, _general_, _accurate_ differentiation operators. To be technical: we are adding exact first-class derivative calculation operators (Automatic Differentiation or AD) to the lambda calculus, and embodying the combination in a production-quality fast system suitable for numeric computing in general, and compositional machine learning methods in particular. Our research prototype compilers generate object code competitive with the fastest current systems, which are based on FORTRAN. And the combined expressive power of first-class AD operators and function programming allows very succinct code for many machine learning algorithms, as well as for some algorithms in computer vision and signal processing. Specific sub-projects include: compiler and numeric programming environment construction; writing, simplifying, and generalising, machine learning and other numeric algorithms; and associated Type Theory/Lambda Calculus/PLT/Real Computation issues. TO THE PROGRAMMING LANGUAGE COMMUNITY, we seek to contribute a way to make numeric software faster, more robust, and easier to write. TO THE MACHINE LEARNING COMMUNITY, in addition to making it easier to write efficient numeric codes, we seek to contribute a system that embodies "compositionality", in that gradient optimisation can be automatically and efficiently performed on systems themselves consisting of many components, even when such components may internally take derivatives or perform optimisation. (Examples of this include, say, optimisation of the rules of a multi-player game to cause the players' actions to satisfy some desiderata, where the players themselves optimise their own strategies using simple models of their opponents which they optimise according to their opponents' observed behaviour.) To this end, we are seeking to fill three positions (postdoctoral or research programmer, or in exceptional cases graduate students) with interest and experience in at least one of: programming language theory, automatic differentiation, machine learning, numerics, mathematical logic. Informal announcement: http://www.bcl.hamilton.ie/~barak/ad-fp-positions.html Formal job postings on http://humanresources.nuim.ie/vacancies.shtml, in particular http://humanresources.nuim.ie/documents/JobSpecPostdoc2_Final.pdf and http://humanresources.nuim.ie/documents/JobSpecProgrammer_Final.pdf Inquiries to: -- Barak A. Pearlmutter Hamilton Institute & Dept Computer Science NUI Maynooth, Co. Kildare, Ireland From 0slemi0 at gmail.com Wed Jan 15 13:55:26 2014 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Wed, 15 Jan 2014 13:55:26 +0000 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: > I have been looking at DataKinds and GADTs, but I can't quite figure out if they actually help me here at all. You are on the right track. With DataKinds and GADTs you can create an index type for PenShape: data Shape = Circle | Rectangle | Arbitrary data PenShape s where PenCircle :: Float -> PenShape Circle PenRectangle :: Float -> Float -> PenShape Rectangle ArbitraryPen :: PenShape Arbitrary You can use this index 's' to restrict PenShape to a particular constructor, or none at all: data Stroke where Spot :: Point -> PenShape s -> Stroke -- any shape allowed Arc :: Point -> Point -> Point -> PenShape Circle -> Stroke -- only circle In the Spot case the type variable 's' will be existentially hidden, meaning any type can go there. The tricky part comes when you want to have a notion of "or" in the case of Line. We basically need decidable type equality for this. Let's assume we have a way of deciding whether two lifted Shape types are equal and we get back a lifted Bool. Now we can write a type level "or" function: type family Or (a :: Bool) (b :: Bool) :: Bool type instance Or False False = False type instance Or True b = True type instance Or a True = True Now the Line case in the GADT would look something like this: Line :: Or (s :== Circle) (s :== Rectangle) ~ True => -- circle or rectangle Point -> Point -> PenShape s -> Stroke where :== is our type equality predicate. You can write this by hand if you'd like but it's pretty tedious and really should be inferred by the compiler or some automated process. And indeed the 'singletons' library does just this (and more), all you need to do is wrap your Shape definition in some th: $(singletons [d|data Shape = Circle | Rectangle | Arbitrary deriving (Eq)|]) And voila you have a nice type safe datastructure:) A full module can be found here: http://lpaste.net/98527 On 13 January 2014 16:25, Daniil Frumin wrote: > I devised the following (unarguably verbose) solution using the > singletons [1] library > > {-# LANGUAGE DataKinds, TypeFamilies, MultiParamTypeClasses #-} > {-# LANGUAGE TemplateHaskell, GADTs, FlexibleContexts #-} > module Image where > import Data.Singletons > > type Point = (Float,Float) > > $(singletons [d| > data Shape' = Circle' | Rectangle' | Arbitrary' > deriving (Eq) > data Stroke' = Line' | Arc' | Spot' > deriving (Eq) > |]) > > > data PenShape shape where > Circle :: SingI Circle' => Float -> PenShape Circle' > Rectangle :: SingI Rectangle' => Float -> Float -> PenShape Rectangle' > ArbitraryPen :: PenShape Arbitrary' > > class AllowedStroke (a::Stroke') (b::Shape') where > > instance AllowedStroke Line' Circle' > instance AllowedStroke Line' Rectangle' > instance AllowedStroke Arc' Circle' > instance AllowedStroke Spot' Circle' > instance AllowedStroke Spot' Rectangle' > instance AllowedStroke Spot' Arbitrary' > > data Stroke where > Line :: AllowedStroke Line' a > => Point -> Point -> PenShape a -> Stroke > Arc :: AllowedStroke Arc' a > => Point -> Point -> Point -> PenShape a -> Stroke > Spot :: AllowedStroke Spot' a > => Point -> PenShape a -> Stroke > > {- > h> :t Line (1,1) (1,1) (Circle 3) > Line (1,1) (1,1) (Circle 3) :: Stroke > h> :t Line (1,1) (1,1) (Rectangle 3 3) > Line (1,1) (1,1) (Rectangle 3 3) :: Stroke > h> :t Line (1,1) (1,1) ArbitraryPen > > :1:1: > No instance for (AllowedStroke 'Line' 'Arbitrary') > arising from a use of `Line' > Possible fix: > add an instance declaration for (AllowedStroke 'Line' 'Arbitrary') > In the expression: Line (1, 1) (1, 1) ArbitraryPen > -} > > --- unfortunately this still gives non-exhaustive pattern match > --- warning :( > showStroke :: Stroke -> String > showStroke (Line _ _ (Circle _)) = "Line + Circle" > showStroke (Line _ _ (Rectangle _ _)) = "Line + Rect" > showStroke (Arc _ _ _ (Circle _)) = "Arc" > showStroke (Spot _ _) = "Spot" > > The shortcomings of this approach are the following: > - verbosity and repetition (eg: Shape' and Shape) > - still gives pattern matching warning ( I suspect that's because > typeclasses are open and there is really no way of determining whether > something is an 'AllowedStroke' or not) > > Feel free to improve the code and notify the list :) > > [1] http://hackage.haskell.org/package/singletons > > On Mon, Jan 13, 2014 at 7:38 AM, Luke Clifton wrote: > > Hi, > > > > I'm quite new to Haskell, and have been loving exploring it. I've always > > been a huge fan of languages that let me catch errors at compile time, > > finding dynamic languages like Python a nightmare to work in. I'm finding > > with Haskell I can take this compile time checking even further than most > > static languages and it has gotten me rather excited. So I was wondering > if > > there is a Haskell way of solving my problem. > > > > I'm trying to represent an image made up of a list of strokes. Strokes > are > > either lines, arcs or spots, and can be made using different pen shapes. > > > > data Image = Image [Stroke] > > > > data Stroke = Line Point Point PenShape > > | Arc Point Point Point PenShape > > | Spot Point PenShape > > > > data PenShape = Circle Float > > | Rectangle Float Float > > | ArbitraryPen -- Stuff (not relevant) > > > > And this is all great and works. > > > > But now I have a problem. I want to extend this such that Arc strokes are > > only allowed to have the Circle pen shape, and Lines are only allowed to > > have the Rectangle or Circle pen shapes. > > > > What is the best way of enforcing this in the type system. > > > > I could make more Strokes like LineCircle, LineRectangle, Arc, > PointCircle, > > PointRectangle, PointArbitrary and get rid of the PenShape type > altogether. > > But this doesn't really feel good to me (and seems like the amount of > work I > > have to do is bigger than it needs to be, especially if I added more > basic > > pen shapes). > > > > I thought about making the different PenShapes different types, using > > typeclasses and making Stroke an algebraic data type, but then my strokes > > would be of different types, and I wouldn't be able to have a list of > > strokes. > > > > I have been looking at DataKinds and GADTs, but I can't quite figure out > if > > they actually help me here at all. > > > > I'm sure there is a way to do this, I'm just not googling properly. > > > > What I want to write is... > > > > data Image = Image [Stroke] > > > > data Stroke = Line Point Point (Circle or Rectangle) > > | Arc Point Point Point Circle > > | Spot Point PenShape > > > > data PenShape = Circle Float > > | Rectangle Float Float > > | ArbitraryPen -- Stuff (not relevant) > > > > Regards, > > > > Luke > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > Sincerely yours, > -- Daniil > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Wed Jan 15 14:13:07 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Wed, 15 Jan 2014 18:13:07 +0400 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Oh, I didn't know that the singletons library provides the equality type family, that's nice On Wed, Jan 15, 2014 at 5:55 PM, Andras Slemmer <0slemi0 at gmail.com> wrote: >> I have been looking at DataKinds and GADTs, but I can't quite figure out >> if they actually help me here at all. > You are on the right track. With DataKinds and GADTs you can create an index > type for PenShape: > > > data Shape = Circle | Rectangle | Arbitrary > > data PenShape s where > PenCircle :: Float -> PenShape Circle > PenRectangle :: Float -> Float -> PenShape Rectangle > ArbitraryPen :: PenShape Arbitrary > > You can use this index 's' to restrict PenShape to a particular constructor, > or none at all: > > data Stroke where > Spot :: Point -> PenShape s -> Stroke -- any shape allowed > Arc :: Point -> Point -> Point -> PenShape Circle -> Stroke -- only > circle > > In the Spot case the type variable 's' will be existentially hidden, meaning > any type can go there. > > The tricky part comes when you want to have a notion of "or" in the case of > Line. We basically need decidable type equality for this. Let's assume we > have a way of deciding whether two lifted Shape types are equal and we get > back a lifted Bool. Now we can write a type level "or" function: > > type family Or (a :: Bool) (b :: Bool) :: Bool > type instance Or False False = False > type instance Or True b = True > type instance Or a True = True > > Now the Line case in the GADT would look something like this: > > Line :: Or (s :== Circle) (s :== Rectangle) ~ True => -- circle or > rectangle > Point -> Point -> PenShape s -> Stroke > > where :== is our type equality predicate. You can write this by hand if > you'd like but it's pretty tedious and really should be inferred by the > compiler or some automated process. And indeed the 'singletons' library does > just this (and more), all you need to do is wrap your Shape definition in > some th: > > $(singletons [d|data Shape = Circle | Rectangle | Arbitrary deriving (Eq)|]) > > And voila you have a nice type safe datastructure:) > > A full module can be found here: http://lpaste.net/98527 > > > On 13 January 2014 16:25, Daniil Frumin wrote: >> >> I devised the following (unarguably verbose) solution using the >> singletons [1] library >> >> {-# LANGUAGE DataKinds, TypeFamilies, MultiParamTypeClasses #-} >> {-# LANGUAGE TemplateHaskell, GADTs, FlexibleContexts #-} >> module Image where >> import Data.Singletons >> >> type Point = (Float,Float) >> >> $(singletons [d| >> data Shape' = Circle' | Rectangle' | Arbitrary' >> deriving (Eq) >> data Stroke' = Line' | Arc' | Spot' >> deriving (Eq) >> |]) >> >> >> data PenShape shape where >> Circle :: SingI Circle' => Float -> PenShape Circle' >> Rectangle :: SingI Rectangle' => Float -> Float -> PenShape Rectangle' >> ArbitraryPen :: PenShape Arbitrary' >> >> class AllowedStroke (a::Stroke') (b::Shape') where >> >> instance AllowedStroke Line' Circle' >> instance AllowedStroke Line' Rectangle' >> instance AllowedStroke Arc' Circle' >> instance AllowedStroke Spot' Circle' >> instance AllowedStroke Spot' Rectangle' >> instance AllowedStroke Spot' Arbitrary' >> >> data Stroke where >> Line :: AllowedStroke Line' a >> => Point -> Point -> PenShape a -> Stroke >> Arc :: AllowedStroke Arc' a >> => Point -> Point -> Point -> PenShape a -> Stroke >> Spot :: AllowedStroke Spot' a >> => Point -> PenShape a -> Stroke >> >> {- >> h> :t Line (1,1) (1,1) (Circle 3) >> Line (1,1) (1,1) (Circle 3) :: Stroke >> h> :t Line (1,1) (1,1) (Rectangle 3 3) >> Line (1,1) (1,1) (Rectangle 3 3) :: Stroke >> h> :t Line (1,1) (1,1) ArbitraryPen >> >> :1:1: >> No instance for (AllowedStroke 'Line' 'Arbitrary') >> arising from a use of `Line' >> Possible fix: >> add an instance declaration for (AllowedStroke 'Line' 'Arbitrary') >> In the expression: Line (1, 1) (1, 1) ArbitraryPen >> -} >> >> --- unfortunately this still gives non-exhaustive pattern match >> --- warning :( >> showStroke :: Stroke -> String >> showStroke (Line _ _ (Circle _)) = "Line + Circle" >> showStroke (Line _ _ (Rectangle _ _)) = "Line + Rect" >> showStroke (Arc _ _ _ (Circle _)) = "Arc" >> showStroke (Spot _ _) = "Spot" >> >> The shortcomings of this approach are the following: >> - verbosity and repetition (eg: Shape' and Shape) >> - still gives pattern matching warning ( I suspect that's because >> typeclasses are open and there is really no way of determining whether >> something is an 'AllowedStroke' or not) >> >> Feel free to improve the code and notify the list :) >> >> [1] http://hackage.haskell.org/package/singletons >> >> On Mon, Jan 13, 2014 at 7:38 AM, Luke Clifton wrote: >> > Hi, >> > >> > I'm quite new to Haskell, and have been loving exploring it. I've always >> > been a huge fan of languages that let me catch errors at compile time, >> > finding dynamic languages like Python a nightmare to work in. I'm >> > finding >> > with Haskell I can take this compile time checking even further than >> > most >> > static languages and it has gotten me rather excited. So I was wondering >> > if >> > there is a Haskell way of solving my problem. >> > >> > I'm trying to represent an image made up of a list of strokes. Strokes >> > are >> > either lines, arcs or spots, and can be made using different pen shapes. >> > >> > data Image = Image [Stroke] >> > >> > data Stroke = Line Point Point PenShape >> > | Arc Point Point Point PenShape >> > | Spot Point PenShape >> > >> > data PenShape = Circle Float >> > | Rectangle Float Float >> > | ArbitraryPen -- Stuff (not relevant) >> > >> > And this is all great and works. >> > >> > But now I have a problem. I want to extend this such that Arc strokes >> > are >> > only allowed to have the Circle pen shape, and Lines are only allowed to >> > have the Rectangle or Circle pen shapes. >> > >> > What is the best way of enforcing this in the type system. >> > >> > I could make more Strokes like LineCircle, LineRectangle, Arc, >> > PointCircle, >> > PointRectangle, PointArbitrary and get rid of the PenShape type >> > altogether. >> > But this doesn't really feel good to me (and seems like the amount of >> > work I >> > have to do is bigger than it needs to be, especially if I added more >> > basic >> > pen shapes). >> > >> > I thought about making the different PenShapes different types, using >> > typeclasses and making Stroke an algebraic data type, but then my >> > strokes >> > would be of different types, and I wouldn't be able to have a list of >> > strokes. >> > >> > I have been looking at DataKinds and GADTs, but I can't quite figure out >> > if >> > they actually help me here at all. >> > >> > I'm sure there is a way to do this, I'm just not googling properly. >> > >> > What I want to write is... >> > >> > data Image = Image [Stroke] >> > >> > data Stroke = Line Point Point (Circle or Rectangle) >> > | Arc Point Point Point Circle >> > | Spot Point PenShape >> > >> > data PenShape = Circle Float >> > | Rectangle Float Float >> > | ArbitraryPen -- Stuff (not relevant) >> > >> > Regards, >> > >> > Luke >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> >> >> >> -- >> Sincerely yours, >> -- Daniil >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Sincerely yours, -- Daniil From nicolas at incubaid.com Wed Jan 15 14:13:46 2014 From: nicolas at incubaid.com (Nicolas Trangez) Date: Wed, 15 Jan 2014 15:13:46 +0100 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: <1389795226.3116.1.camel@tau.nicolast.be> On Wed, 2014-01-15 at 13:55 +0000, Andras Slemmer wrote: > > I have been looking at DataKinds and GADTs, but I can't quite figure out > if they actually help me here at all. > You are on the right track. With DataKinds and GADTs you can create an > index type for PenShape: > > data Shape = Circle | Rectangle | Arbitrary > > data PenShape s where > PenCircle :: Float -> PenShape Circle > PenRectangle :: Float -> Float -> PenShape Rectangle > ArbitraryPen :: PenShape Arbitrary > > You can use this index 's' to restrict PenShape to a particular > constructor, or none at all: > > data Stroke where > Spot :: Point -> PenShape s -> Stroke -- any shape allowed > Arc :: Point -> Point -> Point -> PenShape Circle -> Stroke -- only > circle > > In the Spot case the type variable 's' will be existentially hidden, > meaning any type can go there. > > The tricky part comes when you want to have a notion of "or" in the case of > Line. We basically need decidable type equality for this. Let's assume we > have a way of deciding whether two lifted Shape types are equal and we get > back a lifted Bool. Now we can write a type level "or" function: > > type family Or (a :: Bool) (b :: Bool) :: Bool > type instance Or False False = False > type instance Or True b = True > type instance Or a True = True > > Now the Line case in the GADT would look something like this: > > Line :: Or (s :== Circle) (s :== Rectangle) ~ True => -- circle > or rectangle > Point -> Point -> PenShape s -> Stroke > > where :== is our type equality predicate. You can write this by hand if > you'd like but it's pretty tedious and really should be inferred by the > compiler or some automated process. And indeed the 'singletons' library > does just this (and more), all you need to do is wrap your Shape definition > in some th: > > $(singletons [d|data Shape = Circle | Rectangle | Arbitrary deriving (Eq)|]) > > And voila you have a nice type safe datastructure:) > > A full module can be found here: http://lpaste.net/98527 I never used the 'singletons' library (yet), but since you're using it already, can't what's provided by Data.Singletons.Bool (or Data.Singletons.Prelude) be used instead of a hand-rolled type-level bool? Nicolas From difrumin at gmail.com Wed Jan 15 14:19:17 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Wed, 15 Jan 2014 18:19:17 +0400 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: <1389795226.3116.1.camel@tau.nicolast.be> References: <1389795226.3116.1.camel@tau.nicolast.be> Message-ID: I think so, yes. Singleton library already provides Bool and (:||) type family (or) On Wed, Jan 15, 2014 at 6:13 PM, Nicolas Trangez wrote: > On Wed, 2014-01-15 at 13:55 +0000, Andras Slemmer wrote: >> > I have been looking at DataKinds and GADTs, but I can't quite figure out >> if they actually help me here at all. >> You are on the right track. With DataKinds and GADTs you can create an >> index type for PenShape: >> >> data Shape = Circle | Rectangle | Arbitrary >> >> data PenShape s where >> PenCircle :: Float -> PenShape Circle >> PenRectangle :: Float -> Float -> PenShape Rectangle >> ArbitraryPen :: PenShape Arbitrary >> >> You can use this index 's' to restrict PenShape to a particular >> constructor, or none at all: >> >> data Stroke where >> Spot :: Point -> PenShape s -> Stroke -- any shape allowed >> Arc :: Point -> Point -> Point -> PenShape Circle -> Stroke -- only >> circle >> >> In the Spot case the type variable 's' will be existentially hidden, >> meaning any type can go there. >> >> The tricky part comes when you want to have a notion of "or" in the case of >> Line. We basically need decidable type equality for this. Let's assume we >> have a way of deciding whether two lifted Shape types are equal and we get >> back a lifted Bool. Now we can write a type level "or" function: >> >> type family Or (a :: Bool) (b :: Bool) :: Bool >> type instance Or False False = False >> type instance Or True b = True >> type instance Or a True = True >> >> Now the Line case in the GADT would look something like this: >> >> Line :: Or (s :== Circle) (s :== Rectangle) ~ True => -- circle >> or rectangle >> Point -> Point -> PenShape s -> Stroke >> >> where :== is our type equality predicate. You can write this by hand if >> you'd like but it's pretty tedious and really should be inferred by the >> compiler or some automated process. And indeed the 'singletons' library >> does just this (and more), all you need to do is wrap your Shape definition >> in some th: >> >> $(singletons [d|data Shape = Circle | Rectangle | Arbitrary deriving (Eq)|]) >> >> And voila you have a nice type safe datastructure:) >> >> A full module can be found here: http://lpaste.net/98527 > > I never used the 'singletons' library (yet), but since you're using it > already, can't what's provided by Data.Singletons.Bool (or > Data.Singletons.Prelude) be used instead of a hand-rolled type-level > bool? > > Nicolas > -- Sincerely yours, -- Daniil From jake.mcarthur at gmail.com Wed Jan 15 14:25:33 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Wed, 15 Jan 2014 09:25:33 -0500 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: You can get some kind of subtyping out of type classes. Then it's just a matter of making a few different instances so you can do what you want with them. class Circle a where circle :: Float -> a class Rectangle a where rectangle :: Float -> Float -> a class (Circle a, Rectangle a) => PenShape a where arbitraryPen :: ... -> a data Stroke = forall p. (Circle p, Rectangle p) => Line Point Point p | forall p. Circle p => Arc Point Point Point p | forall p. PenShape p => Spot Point p - Jake Hi, I'm quite new to Haskell, and have been loving exploring it. I've always been a huge fan of languages that let me catch errors at compile time, finding dynamic languages like Python a nightmare to work in. I'm finding with Haskell I can take this compile time checking even further than most static languages and it has gotten me rather excited. So I was wondering if there is a Haskell way of solving my problem. I'm trying to represent an image made up of a list of strokes. Strokes are either lines, arcs or spots, and can be made using different pen shapes. data Image = Image [Stroke] data Stroke = Line Point Point PenShape | Arc Point Point Point PenShape | Spot Point PenShape data PenShape = Circle Float | Rectangle Float Float | ArbitraryPen -- Stuff (not relevant) And this is all great and works. But now I have a problem. I want to extend this such that Arc strokes are only allowed to have the Circle pen shape, and Lines are only allowed to have the Rectangle or Circle pen shapes. What is the best way of enforcing this in the type system. I could make more Strokes like LineCircle, LineRectangle, Arc, PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape type altogether. But this doesn't really feel good to me (and seems like the amount of work I have to do is bigger than it needs to be, especially if I added more basic pen shapes). I thought about making the different PenShapes different types, using typeclasses and making Stroke an algebraic data type, but then my strokes would be of different types, and I wouldn't be able to have a list of strokes. I have been looking at DataKinds and GADTs, but I can't quite figure out if they actually help me here at all. I'm sure there is a way to do this, I'm just not googling properly. What I want to write is... data Image = Image [Stroke] data Stroke = Line Point Point (Circle or Rectangle) | Arc Point Point Point Circle | Spot Point PenShape data PenShape = Circle Float | Rectangle Float Float | ArbitraryPen -- Stuff (not relevant) Regards, Luke _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From jake.mcarthur at gmail.com Wed Jan 15 14:26:19 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Wed, 15 Jan 2014 09:26:19 -0500 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Sorry, I used existential types but should have used universal types. On Jan 15, 2014 9:25 AM, "Jake McArthur" wrote: > You can get some kind of subtyping out of type classes. Then it's just a > matter of making a few different instances so you can do what you want with > them. > > class Circle a where > circle :: Float -> a > > class Rectangle a where > rectangle :: Float -> Float -> a > > class (Circle a, Rectangle a) => PenShape a where > arbitraryPen :: ... -> a > > data Stroke = forall p. (Circle p, Rectangle p) => Line Point Point p > | forall p. Circle p => Arc Point Point Point p > | forall p. PenShape p => Spot Point p > > - Jake > Hi, > > I'm quite new to Haskell, and have been loving exploring it. I've always > been a huge fan of languages that let me catch errors at compile time, > finding dynamic languages like Python a nightmare to work in. I'm finding > with Haskell I can take this compile time checking even further than most > static languages and it has gotten me rather excited. So I was wondering if > there is a Haskell way of solving my problem. > > I'm trying to represent an image made up of a list of strokes. Strokes are > either lines, arcs or spots, and can be made using different pen shapes. > > data Image = Image [Stroke] > > data Stroke = Line Point Point PenShape > | Arc Point Point Point PenShape > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > And this is all great and works. > > But now I have a problem. I want to extend this such that Arc strokes are > only allowed to have the Circle pen shape, and Lines are only allowed to > have the Rectangle or Circle pen shapes. > > What is the best way of enforcing this in the type system. > > I could make more Strokes like LineCircle, LineRectangle, Arc, > PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape > type altogether. But this doesn't really feel good to me (and seems like > the amount of work I have to do is bigger than it needs to be, especially > if I added more basic pen shapes). > > I thought about making the different PenShapes different types, using > typeclasses and making Stroke an algebraic data type, but then my strokes > would be of different types, and I wouldn't be able to have a list of > strokes. > > I have been looking at DataKinds and GADTs, but I can't quite figure out > if they actually help me here at all. > > I'm sure there is a way to do this, I'm just not googling properly. > > What I want to write is... > > data Image = Image [Stroke] > > data Stroke = Line Point Point (Circle or Rectangle) > | Arc Point Point Point Circle > | Spot Point PenShape > > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) > > Regards, > > Luke > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jake.mcarthur at gmail.com Wed Jan 15 14:29:24 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Wed, 15 Jan 2014 09:29:24 -0500 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: This is what it should have been. Also, sorry for segmenting my emails. data Stroke = Line Point Point (forall p. (Circle p, Rectangle p) => p) | Arc Point Point Point (forall p. Circle p => p) | Spot Point (forall p. PenShape p => p) On Jan 15, 2014 9:26 AM, "Jake McArthur" wrote: > Sorry, I used existential types but should have used universal types. > On Jan 15, 2014 9:25 AM, "Jake McArthur" wrote: > >> You can get some kind of subtyping out of type classes. Then it's just a >> matter of making a few different instances so you can do what you want with >> them. >> >> class Circle a where >> circle :: Float -> a >> >> class Rectangle a where >> rectangle :: Float -> Float -> a >> >> class (Circle a, Rectangle a) => PenShape a where >> arbitraryPen :: ... -> a >> >> data Stroke = forall p. (Circle p, Rectangle p) => Line Point Point p >> | forall p. Circle p => Arc Point Point Point p >> | forall p. PenShape p => Spot Point p >> >> - Jake >> Hi, >> >> I'm quite new to Haskell, and have been loving exploring it. I've always >> been a huge fan of languages that let me catch errors at compile time, >> finding dynamic languages like Python a nightmare to work in. I'm finding >> with Haskell I can take this compile time checking even further than most >> static languages and it has gotten me rather excited. So I was wondering if >> there is a Haskell way of solving my problem. >> >> I'm trying to represent an image made up of a list of strokes. Strokes >> are either lines, arcs or spots, and can be made using different pen shapes. >> >> data Image = Image [Stroke] >> >> data Stroke = Line Point Point PenShape >> | Arc Point Point Point PenShape >> | Spot Point PenShape >> >> data PenShape = Circle Float >> | Rectangle Float Float >> | ArbitraryPen -- Stuff (not relevant) >> >> And this is all great and works. >> >> But now I have a problem. I want to extend this such that Arc strokes are >> only allowed to have the Circle pen shape, and Lines are only allowed to >> have the Rectangle or Circle pen shapes. >> >> What is the best way of enforcing this in the type system. >> >> I could make more Strokes like LineCircle, LineRectangle, Arc, >> PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape >> type altogether. But this doesn't really feel good to me (and seems like >> the amount of work I have to do is bigger than it needs to be, especially >> if I added more basic pen shapes). >> >> I thought about making the different PenShapes different types, using >> typeclasses and making Stroke an algebraic data type, but then my strokes >> would be of different types, and I wouldn't be able to have a list of >> strokes. >> >> I have been looking at DataKinds and GADTs, but I can't quite figure out >> if they actually help me here at all. >> >> I'm sure there is a way to do this, I'm just not googling properly. >> >> What I want to write is... >> >> data Image = Image [Stroke] >> >> data Stroke = Line Point Point (Circle or Rectangle) >> | Arc Point Point Point Circle >> | Spot Point PenShape >> >> data PenShape = Circle Float >> | Rectangle Float Float >> | ArbitraryPen -- Stuff (not relevant) >> >> Regards, >> >> Luke >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From erochest at gmail.com Wed Jan 15 20:24:35 2014 From: erochest at gmail.com (Eric Rochester) Date: Wed, 15 Jan 2014 15:24:35 -0500 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 Message-ID: I'd like to announce the first release of castle ( http://hackage.haskell.org/package/castle and https://github.com/erochest/castle). From the README: > I really like having sandboxes baked into cabal-install(see Cabal > Sandboxes for > more information). > > I got tired of waiting for big packages like Yesodand > Lens to compile in project > after project that used them. However, I still didn't want to install them > in the user database. I wanted to maintain *some* sandboxing among a > group of projects that all share a common set of packages, but I wanted to > be able to switch from them or upgrade them easily. > > That's the itch I was trying to scratch with castle. > > It allows you to share one Cabal sandbox between multiple projects. This > keeps the package versions for all of these projects in line. It also means > that you don't have to constantly be re-installing everything, but you > still get the ability to blow away a set of packages without borking your > whole system. > This tool is still pretty rough around the edges, but I've been using it some, and it's to the point that more feedback would be helpful. Let me know what bugs and rough patches you find. Thanks, Eric -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Wed Jan 15 21:10:49 2014 From: jwlato at gmail.com (John Lato) Date: Wed, 15 Jan 2014 13:10:49 -0800 Subject: [Haskell-cafe] mdo with multiple values In-Reply-To: <1389779877.2660.4.camel@kirk> References: <1389779877.2660.4.camel@kirk> Message-ID: Hello Joachim, I don't really understand what you're doing here. There's the obvious mapM_ (act2 >=> act1) But presumably act1 performs some monadic action that doesn't depend on its input, and you need that to be performed before act2? To me, it feels like there's some sort of implicit coupling between act1 and act2, and you would be better off extracting that, perhaps by changing act1 to have the type act1 :: M T -> () . If that's not possible, your approach seems pretty simple to me. John L. On Jan 15, 2014 1:57 AM, "Joachim Breitner" wrote: > Dear List, > > a little puzzle. > > Given a monad M with a MonadFix instance, and these two functions: > act1 :: T -> M () > act2 :: a -> M T > > I morally want to write this function: > foo :: [a] -> M () > foo = mdo > mapM_ act1 xs > xs <- mapM act2 > return () > > Unfortunately, that will not work: mapM_ will force xs before any of it > can be generated. But morally it should be possible, as the lists passed > to mapM_ and mapM have the same, already known list. > > > So here is my solution (which is a bit more general, because I happen to > need some that in one place): > > mapFstMapSnd :: MonadFix m => [(a -> m (), m a)] -> m () > mapFstMapSnd xs = const () `liftM` go xs (return []) > where > go [] cont = cont > go ((f,s):xs) cont = mdo > f v > (v:vs) <- go xs $ do > vs <- cont > v <- s > return (v:vs) > return vs > > Using that, I can write > foo = mapFstSnd . map (x -> (act1, act2 x)) > > > Are there better solutions? Simpler ones? Or possibly ones that do not > require a partial pattern? > > > Hmm, and thinking while writing lets me come up with > > data FunSplit m where > FunSplit :: forall m a . (a -> m ()) -> m a -> FunSplit m > > mapFstMapSnd :: forall m. MonadFix m => [FunSplit m] -> m () > mapFstMapSnd xs = const () `liftM` go xs (return ()) > where > go :: [FunSplit m] -> m b -> m b > go [] cont = cont > go (FunSplit f s:xs) cont = mdo > f v > (v,vs) <- go xs $ do > vs <- cont > v <- s > return (v,vs) > return vs > > foo :: [SPut] -> SPut > foo = mapFstMapSnd . map go > where go x = FunSplit act1 (act2 x) > > Any suggestions for improvement? > > > Thanks, > Joachim > > > -- > Joachim Breitner > e-Mail: mail at joachim-breitner.de > Homepage: http://www.joachim-breitner.de > Jabber-ID: nomeata at joachim-breitner.de > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Wed Jan 15 23:24:05 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Wed, 15 Jan 2014 23:24:05 +0000 Subject: [Haskell-cafe] mdo with multiple values In-Reply-To: References: <1389779877.2660.4.camel@kirk> Message-ID: <1389828245.4552.9.camel@kirk> Dear John, the background is a binary format assembler, so you can think of the monad as the Put monad, only sufficiently lazy to admit a useful MonadFix instance. Then one can do nice things like mdo putWord32 offset putBS someMoreHeaderData ... offset <- getCurrentOffset putBS byteString1 where I conceptually use the offset before it is known. So what if I want to put two offsets, followed by two bytestrings? Easy: mdo putWord32 offset1 putWord32 offset2 putBS someMoreHeaderData ... offset1 <- getCurrentOffset putBS byteString1 offset2 <- getCurrentOffset putBS byteString2 Now I try to generalize that to a list of Bytestrings, and just from the looks of it, this is what you want to do: mdo mapM_ putWord32 offsets putBS someMoreHeaderData ... offsets <- forM byteStrings $ \b -> offset <- getCurrentOffset putBS b return offset but that will <>. Am Mittwoch, den 15.01.2014, 13:10 -0800 schrieb John Lato: > Hello Joachim, > I don't really understand what you're doing here. There's the obvious > > mapM_ (act2 >=> act1) > > But presumably act1 performs some monadic action that doesn't depend > on its input, and you need that to be performed before act2? Exactly, (act2 >=> act1) would write out the data in the wrong order. > To me, it feels like there's some sort of implicit coupling between > act1 and act2, and you would be better off extracting that, perhaps by > changing act1 to have the type act1 :: M T -> () . > > If that's not possible, your approach seems pretty simple to me. I don?t think its, possible with that signature, no... (It were if I were to interleave the calls to act1 and act2, instead of requiring first all act1 and then all act2, but then it would be trivial anyways.) Greetings, Joachi -- Joachim Breitner e-Mail: mail at joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata at joachim-breitner.de -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 181 bytes Desc: This is a digitally signed message part URL: From ivan.miljenovic at gmail.com Thu Jan 16 00:30:22 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 16 Jan 2014 11:30:22 +1100 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: On 16 January 2014 07:24, Eric Rochester wrote: > I'd like to announce the first release of castle > (http://hackage.haskell.org/package/castle and > https://github.com/erochest/castle). From the README: >> >> I really like having sandboxes baked into cabal-install (see Cabal >> Sandboxes for more information). >> >> I got tired of waiting for big packages like Yesod and Lens to compile in >> project after project that used them. However, I still didn't want to >> install them in the user database. I wanted to maintain some sandboxing >> among a group of projects that all share a common set of packages, but I >> wanted to be able to switch from them or upgrade them easily. >> >> That's the itch I was trying to scratch with castle. >> >> It allows you to share one Cabal sandbox between multiple projects. This >> keeps the package versions for all of these projects in line. It also means >> that you don't have to constantly be re-installing everything, but you still >> get the ability to blow away a set of packages without borking your whole >> system. > > > This tool is still pretty rough around the edges, but I've been using it > some, and it's to the point that more feedback would be helpful. Let me know > what bugs and rough patches you find. How does this differ from doing "cabal sandbox init --sandbox=../my-common-sandbox" for all these projects? -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From cma at bitemyapp.com Thu Jan 16 00:45:38 2014 From: cma at bitemyapp.com (Christopher Allen) Date: Wed, 15 Jan 2014 16:45:38 -0800 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: I typically do the same, fairly frequently, using a Makefile to handle configuring builds/cabal/whatever to all point to the same sandbox or pulling it from my environment variables. On Wed, Jan 15, 2014 at 4:30 PM, Ivan Lazar Miljenovic < ivan.miljenovic at gmail.com> wrote: > On 16 January 2014 07:24, Eric Rochester wrote: > > I'd like to announce the first release of castle > > (http://hackage.haskell.org/package/castle and > > https://github.com/erochest/castle). From the README: > >> > >> I really like having sandboxes baked into cabal-install (see Cabal > >> Sandboxes for more information). > >> > >> I got tired of waiting for big packages like Yesod and Lens to compile > in > >> project after project that used them. However, I still didn't want to > >> install them in the user database. I wanted to maintain some sandboxing > >> among a group of projects that all share a common set of packages, but I > >> wanted to be able to switch from them or upgrade them easily. > >> > >> That's the itch I was trying to scratch with castle. > >> > >> It allows you to share one Cabal sandbox between multiple projects. This > >> keeps the package versions for all of these projects in line. It also > means > >> that you don't have to constantly be re-installing everything, but you > still > >> get the ability to blow away a set of packages without borking your > whole > >> system. > > > > > > This tool is still pretty rough around the edges, but I've been using it > > some, and it's to the point that more feedback would be helpful. Let me > know > > what bugs and rough patches you find. > > How does this differ from doing "cabal sandbox init > --sandbox=../my-common-sandbox" for all these projects? > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From erochest at gmail.com Thu Jan 16 01:38:50 2014 From: erochest at gmail.com (Eric Rochester) Date: Wed, 15 Jan 2014 20:38:50 -0500 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: It doesn't differ at all. In fact, that's just what it does. It's just a management utility keeping all of the sandboxes in one place. Overkill? Certainly. On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" wrote: > On 16 January 2014 07:24, Eric Rochester wrote: > > I'd like to announce the first release of castle > > (http://hackage.haskell.org/package/castle and > > https://github.com/erochest/castle). From the README: > >> > >> I really like having sandboxes baked into cabal-install (see Cabal > >> Sandboxes for more information). > >> > >> I got tired of waiting for big packages like Yesod and Lens to compile > in > >> project after project that used them. However, I still didn't want to > >> install them in the user database. I wanted to maintain some sandboxing > >> among a group of projects that all share a common set of packages, but I > >> wanted to be able to switch from them or upgrade them easily. > >> > >> That's the itch I was trying to scratch with castle. > >> > >> It allows you to share one Cabal sandbox between multiple projects. This > >> keeps the package versions for all of these projects in line. It also > means > >> that you don't have to constantly be re-installing everything, but you > still > >> get the ability to blow away a set of packages without borking your > whole > >> system. > > > > > > This tool is still pretty rough around the edges, but I've been using it > > some, and it's to the point that more feedback would be helpful. Let me > know > > what bugs and rough patches you find. > > How does this differ from doing "cabal sandbox init > --sandbox=../my-common-sandbox" for all these projects? > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ltclifton at gmail.com Thu Jan 16 02:07:44 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Thu, 16 Jan 2014 10:07:44 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Well that works wonderfully for parts of the problem. listOfStrokes = [ Line point point (circle 5) , Line point point (rectangle 2 3) , Arc point point point (circle 2) , Spot point arbitraryPen , Spot point (circle 1) , Spot point (rectangle 1 1) ] *Tmp> :t listOfStrokes listOfStrokes :: [Stroke] But how can I extract the information about the PenShape from such a structure? I can't pattern match (unless there is some language extension I am missing). case Arc point point point (circle 1) of (Arc _ _ _ (circle r)) -> r :67:14: Parse error in pattern: circle This seems obvious to me because pattern matching works on data constructors (though I have often found that what I think is obvious is not always correct...). This would leave me to believe that, because there are no data constructors for Circle, Rectangle and PenShape that I couldn't pattern match on it. I tried to add some functions to the various classes to figure it out, but that didn't seem to take me anywhere. On Wed, Jan 15, 2014 at 10:29 PM, Jake McArthur wrote: > This is what it should have been. Also, sorry for segmenting my emails. > > data Stroke = Line Point Point (forall p. (Circle p, Rectangle p) => p) > | Arc Point Point Point (forall p. Circle p => p) > | Spot Point (forall p. PenShape p => p) > On Jan 15, 2014 9:26 AM, "Jake McArthur" wrote: > >> Sorry, I used existential types but should have used universal types. >> On Jan 15, 2014 9:25 AM, "Jake McArthur" wrote: >> >>> You can get some kind of subtyping out of type classes. Then it's just a >>> matter of making a few different instances so you can do what you want with >>> them. >>> >>> class Circle a where >>> circle :: Float -> a >>> >>> class Rectangle a where >>> rectangle :: Float -> Float -> a >>> >>> class (Circle a, Rectangle a) => PenShape a where >>> arbitraryPen :: ... -> a >>> >>> data Stroke = forall p. (Circle p, Rectangle p) => Line Point Point p >>> | forall p. Circle p => Arc Point Point Point p >>> | forall p. PenShape p => Spot Point p >>> >>> - Jake >>> Hi, >>> >>> I'm quite new to Haskell, and have been loving exploring it. I've always >>> been a huge fan of languages that let me catch errors at compile time, >>> finding dynamic languages like Python a nightmare to work in. I'm finding >>> with Haskell I can take this compile time checking even further than most >>> static languages and it has gotten me rather excited. So I was wondering if >>> there is a Haskell way of solving my problem. >>> >>> I'm trying to represent an image made up of a list of strokes. Strokes >>> are either lines, arcs or spots, and can be made using different pen shapes. >>> >>> data Image = Image [Stroke] >>> >>> data Stroke = Line Point Point PenShape >>> | Arc Point Point Point PenShape >>> | Spot Point PenShape >>> >>> data PenShape = Circle Float >>> | Rectangle Float Float >>> | ArbitraryPen -- Stuff (not relevant) >>> >>> And this is all great and works. >>> >>> But now I have a problem. I want to extend this such that Arc strokes >>> are only allowed to have the Circle pen shape, and Lines are only allowed >>> to have the Rectangle or Circle pen shapes. >>> >>> What is the best way of enforcing this in the type system. >>> >>> I could make more Strokes like LineCircle, LineRectangle, Arc, >>> PointCircle, PointRectangle, PointArbitrary and get rid of the PenShape >>> type altogether. But this doesn't really feel good to me (and seems like >>> the amount of work I have to do is bigger than it needs to be, especially >>> if I added more basic pen shapes). >>> >>> I thought about making the different PenShapes different types, using >>> typeclasses and making Stroke an algebraic data type, but then my strokes >>> would be of different types, and I wouldn't be able to have a list of >>> strokes. >>> >>> I have been looking at DataKinds and GADTs, but I can't quite figure out >>> if they actually help me here at all. >>> >>> I'm sure there is a way to do this, I'm just not googling properly. >>> >>> What I want to write is... >>> >>> data Image = Image [Stroke] >>> >>> data Stroke = Line Point Point (Circle or Rectangle) >>> | Arc Point Point Point Circle >>> | Spot Point PenShape >>> >>> data PenShape = Circle Float >>> | Rectangle Float Float >>> | ArbitraryPen -- Stuff (not relevant) >>> >>> Regards, >>> >>> Luke >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> -------------- next part -------------- An HTML attachment was scrubbed... URL: From ltclifton at gmail.com Thu Jan 16 02:36:40 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Thu, 16 Jan 2014 10:36:40 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: Message-ID: Thanks Andras and Daniil for pointing out the singletons package. I will need to look into this in more detail to fully understand what is going on. Seems I'm jumping into the deep end with this. Type families have move up in my reading list! On Wed, Jan 15, 2014 at 9:55 PM, Andras Slemmer <0slemi0 at gmail.com> wrote: > > I have been looking at DataKinds and GADTs, but I can't quite figure out > if they actually help me here at all. > You are on the right track. With DataKinds and GADTs you can create an > index type for PenShape: > > > data Shape = Circle | Rectangle | Arbitrary > > data PenShape s where > PenCircle :: Float -> PenShape Circle > PenRectangle :: Float -> Float -> PenShape Rectangle > ArbitraryPen :: PenShape Arbitrary > > You can use this index 's' to restrict PenShape to a particular > constructor, or none at all: > > data Stroke where > Spot :: Point -> PenShape s -> Stroke -- any shape allowed > Arc :: Point -> Point -> Point -> PenShape Circle -> Stroke -- only > circle > > In the Spot case the type variable 's' will be existentially hidden, > meaning any type can go there. > > The tricky part comes when you want to have a notion of "or" in the case > of Line. We basically need decidable type equality for this. Let's assume > we have a way of deciding whether two lifted Shape types are equal and we > get back a lifted Bool. Now we can write a type level "or" function: > > type family Or (a :: Bool) (b :: Bool) :: Bool > type instance Or False False = False > type instance Or True b = True > type instance Or a True = True > > Now the Line case in the GADT would look something like this: > > Line :: Or (s :== Circle) (s :== Rectangle) ~ True => -- circle > or rectangle > Point -> Point -> PenShape s -> Stroke > > where :== is our type equality predicate. You can write this by hand if > you'd like but it's pretty tedious and really should be inferred by the > compiler or some automated process. And indeed the 'singletons' library > does just this (and more), all you need to do is wrap your Shape definition > in some th: > > $(singletons [d|data Shape = Circle | Rectangle | Arbitrary deriving > (Eq)|]) > > And voila you have a nice type safe datastructure:) > > A full module can be found here: http://lpaste.net/98527 > > > On 13 January 2014 16:25, Daniil Frumin wrote: > >> I devised the following (unarguably verbose) solution using the >> singletons [1] library >> >> {-# LANGUAGE DataKinds, TypeFamilies, MultiParamTypeClasses #-} >> {-# LANGUAGE TemplateHaskell, GADTs, FlexibleContexts #-} >> module Image where >> import Data.Singletons >> >> type Point = (Float,Float) >> >> $(singletons [d| >> data Shape' = Circle' | Rectangle' | Arbitrary' >> deriving (Eq) >> data Stroke' = Line' | Arc' | Spot' >> deriving (Eq) >> |]) >> >> >> data PenShape shape where >> Circle :: SingI Circle' => Float -> PenShape Circle' >> Rectangle :: SingI Rectangle' => Float -> Float -> PenShape Rectangle' >> ArbitraryPen :: PenShape Arbitrary' >> >> class AllowedStroke (a::Stroke') (b::Shape') where >> >> instance AllowedStroke Line' Circle' >> instance AllowedStroke Line' Rectangle' >> instance AllowedStroke Arc' Circle' >> instance AllowedStroke Spot' Circle' >> instance AllowedStroke Spot' Rectangle' >> instance AllowedStroke Spot' Arbitrary' >> >> data Stroke where >> Line :: AllowedStroke Line' a >> => Point -> Point -> PenShape a -> Stroke >> Arc :: AllowedStroke Arc' a >> => Point -> Point -> Point -> PenShape a -> Stroke >> Spot :: AllowedStroke Spot' a >> => Point -> PenShape a -> Stroke >> >> {- >> h> :t Line (1,1) (1,1) (Circle 3) >> Line (1,1) (1,1) (Circle 3) :: Stroke >> h> :t Line (1,1) (1,1) (Rectangle 3 3) >> Line (1,1) (1,1) (Rectangle 3 3) :: Stroke >> h> :t Line (1,1) (1,1) ArbitraryPen >> >> :1:1: >> No instance for (AllowedStroke 'Line' 'Arbitrary') >> arising from a use of `Line' >> Possible fix: >> add an instance declaration for (AllowedStroke 'Line' 'Arbitrary') >> In the expression: Line (1, 1) (1, 1) ArbitraryPen >> -} >> >> --- unfortunately this still gives non-exhaustive pattern match >> --- warning :( >> showStroke :: Stroke -> String >> showStroke (Line _ _ (Circle _)) = "Line + Circle" >> showStroke (Line _ _ (Rectangle _ _)) = "Line + Rect" >> showStroke (Arc _ _ _ (Circle _)) = "Arc" >> showStroke (Spot _ _) = "Spot" >> >> The shortcomings of this approach are the following: >> - verbosity and repetition (eg: Shape' and Shape) >> - still gives pattern matching warning ( I suspect that's because >> typeclasses are open and there is really no way of determining whether >> something is an 'AllowedStroke' or not) >> >> Feel free to improve the code and notify the list :) >> >> [1] http://hackage.haskell.org/package/singletons >> >> On Mon, Jan 13, 2014 at 7:38 AM, Luke Clifton >> wrote: >> > Hi, >> > >> > I'm quite new to Haskell, and have been loving exploring it. I've always >> > been a huge fan of languages that let me catch errors at compile time, >> > finding dynamic languages like Python a nightmare to work in. I'm >> finding >> > with Haskell I can take this compile time checking even further than >> most >> > static languages and it has gotten me rather excited. So I was >> wondering if >> > there is a Haskell way of solving my problem. >> > >> > I'm trying to represent an image made up of a list of strokes. Strokes >> are >> > either lines, arcs or spots, and can be made using different pen shapes. >> > >> > data Image = Image [Stroke] >> > >> > data Stroke = Line Point Point PenShape >> > | Arc Point Point Point PenShape >> > | Spot Point PenShape >> > >> > data PenShape = Circle Float >> > | Rectangle Float Float >> > | ArbitraryPen -- Stuff (not relevant) >> > >> > And this is all great and works. >> > >> > But now I have a problem. I want to extend this such that Arc strokes >> are >> > only allowed to have the Circle pen shape, and Lines are only allowed to >> > have the Rectangle or Circle pen shapes. >> > >> > What is the best way of enforcing this in the type system. >> > >> > I could make more Strokes like LineCircle, LineRectangle, Arc, >> PointCircle, >> > PointRectangle, PointArbitrary and get rid of the PenShape type >> altogether. >> > But this doesn't really feel good to me (and seems like the amount of >> work I >> > have to do is bigger than it needs to be, especially if I added more >> basic >> > pen shapes). >> > >> > I thought about making the different PenShapes different types, using >> > typeclasses and making Stroke an algebraic data type, but then my >> strokes >> > would be of different types, and I wouldn't be able to have a list of >> > strokes. >> > >> > I have been looking at DataKinds and GADTs, but I can't quite figure >> out if >> > they actually help me here at all. >> > >> > I'm sure there is a way to do this, I'm just not googling properly. >> > >> > What I want to write is... >> > >> > data Image = Image [Stroke] >> > >> > data Stroke = Line Point Point (Circle or Rectangle) >> > | Arc Point Point Point Circle >> > | Spot Point PenShape >> > >> > data PenShape = Circle Float >> > | Rectangle Float Float >> > | ArbitraryPen -- Stuff (not relevant) >> > >> > Regards, >> > >> > Luke >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> >> >> >> -- >> Sincerely yours, >> -- Daniil >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From conrad at metadecks.org Thu Jan 16 02:47:37 2014 From: conrad at metadecks.org (Conrad Parker) Date: Thu, 16 Jan 2014 13:47:37 +1100 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: On 16 January 2014 12:38, Eric Rochester wrote: > It doesn't differ at all. In fact, that's just what it does. It's just a > management utility keeping all of the sandboxes in one place. > > Overkill? Certainly. > It doesn't sound like overkill to me -- cabal gives a mechanism for having sandboxes, but doesn't impose any policy about why you would use them. Is the point that you maintain multiple sandboxes, like a lens sandbox and a yesod sandbox; and this tool makes it easier to manage those? ie. you might maintain separate lens-3.9 and lens-3.10 sandboxes, and when compiling a new project that uses lens, choose the appropriate lens sandbox. Conrad. > On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" < > ivan.miljenovic at gmail.com> wrote: > >> On 16 January 2014 07:24, Eric Rochester wrote: >> > I'd like to announce the first release of castle >> > (http://hackage.haskell.org/package/castle and >> > https://github.com/erochest/castle). From the README: >> >> >> >> I really like having sandboxes baked into cabal-install (see Cabal >> >> Sandboxes for more information). >> >> >> >> I got tired of waiting for big packages like Yesod and Lens to compile >> in >> >> project after project that used them. However, I still didn't want to >> >> install them in the user database. I wanted to maintain some sandboxing >> >> among a group of projects that all share a common set of packages, but >> I >> >> wanted to be able to switch from them or upgrade them easily. >> >> >> >> That's the itch I was trying to scratch with castle. >> >> >> >> It allows you to share one Cabal sandbox between multiple projects. >> This >> >> keeps the package versions for all of these projects in line. It also >> means >> >> that you don't have to constantly be re-installing everything, but you >> still >> >> get the ability to blow away a set of packages without borking your >> whole >> >> system. >> > >> > >> > This tool is still pretty rough around the edges, but I've been using it >> > some, and it's to the point that more feedback would be helpful. Let me >> know >> > what bugs and rough patches you find. >> >> How does this differ from doing "cabal sandbox init >> --sandbox=../my-common-sandbox" for all these projects? >> >> -- >> Ivan Lazar Miljenovic >> Ivan.Miljenovic at gmail.com >> http://IvanMiljenovic.wordpress.com >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From erochest at gmail.com Thu Jan 16 03:31:02 2014 From: erochest at gmail.com (Eric Rochester) Date: Wed, 15 Jan 2014 22:31:02 -0500 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: That's one use case that I've used some. Another motivation has been to make it easier and faster to get started on a new project. I may want to do a relatively small web app or command-line utility. It shouldn't take long. But if I require any of a number of larger (but very useful) packages, then installing them into a new sandbox does take a while. This short-circuits that and lets me get started on the project itself almost immediately. After the project's going, I often find that I switch over to a sandbox in the project directory, but I can do that after I've moved on to another task. Basically it allows me to get started on a project very quickly while still having the benefits of sandboxes. On Wed, Jan 15, 2014 at 9:47 PM, Conrad Parker wrote: > > > On 16 January 2014 12:38, Eric Rochester wrote: > >> It doesn't differ at all. In fact, that's just what it does. It's just a >> management utility keeping all of the sandboxes in one place. >> >> Overkill? Certainly. >> > It doesn't sound like overkill to me -- cabal gives a mechanism for having > sandboxes, but doesn't impose any policy about why you would use them. > > Is the point that you maintain multiple sandboxes, like a lens sandbox and > a yesod sandbox; and this tool makes it easier to manage those? ie. you > might maintain separate lens-3.9 and lens-3.10 sandboxes, and when > compiling a new project that uses lens, choose the appropriate lens sandbox. > > Conrad. > > >> On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" < >> ivan.miljenovic at gmail.com> wrote: >> >>> On 16 January 2014 07:24, Eric Rochester wrote: >>> > I'd like to announce the first release of castle >>> > (http://hackage.haskell.org/package/castle and >>> > https://github.com/erochest/castle). From the README: >>> >> >>> >> I really like having sandboxes baked into cabal-install (see Cabal >>> >> Sandboxes for more information). >>> >> >>> >> I got tired of waiting for big packages like Yesod and Lens to >>> compile in >>> >> project after project that used them. However, I still didn't want to >>> >> install them in the user database. I wanted to maintain some >>> sandboxing >>> >> among a group of projects that all share a common set of packages, >>> but I >>> >> wanted to be able to switch from them or upgrade them easily. >>> >> >>> >> That's the itch I was trying to scratch with castle. >>> >> >>> >> It allows you to share one Cabal sandbox between multiple projects. >>> This >>> >> keeps the package versions for all of these projects in line. It also >>> means >>> >> that you don't have to constantly be re-installing everything, but >>> you still >>> >> get the ability to blow away a set of packages without borking your >>> whole >>> >> system. >>> > >>> > >>> > This tool is still pretty rough around the edges, but I've been using >>> it >>> > some, and it's to the point that more feedback would be helpful. Let >>> me know >>> > what bugs and rough patches you find. >>> >>> How does this differ from doing "cabal sandbox init >>> --sandbox=../my-common-sandbox" for all these projects? >>> >>> -- >>> Ivan Lazar Miljenovic >>> Ivan.Miljenovic at gmail.com >>> http://IvanMiljenovic.wordpress.com >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeremy at n-heptane.com Thu Jan 16 03:37:51 2014 From: jeremy at n-heptane.com (Jeremy Shaw) Date: Wed, 15 Jan 2014 21:37:51 -0600 Subject: [Haskell-cafe] Error management in Happstack In-Reply-To: References: Message-ID: Hello, Happstack uses monad-control. You can use catch from lifted-base to catch the exception. I have attached a simple demo. You can learn more about monad-control many places including here: https://www.fpcomplete.com/user/jwiegley/monad-control - jeremy On Mon, Jan 13, 2014 at 3:50 PM, Corentin Dupont wrote: > Hi Jeremy, all, > In Happstack when I throw an error, I obtain a blank page with "server > error: my message". > How can I decorate this page? > I'd like to have it look like the other pages of my website, and a "back to > login" link, for example. > > Thanks! > Corentin > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- A non-text attachment was scrubbed... Name: happstack-catch-error.hs Type: text/x-haskell Size: 437 bytes Desc: not available URL: From ivan.miljenovic at gmail.com Thu Jan 16 04:05:02 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 16 Jan 2014 15:05:02 +1100 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: On 16 January 2014 14:31, Eric Rochester wrote: > That's one use case that I've used some. > > Another motivation has been to make it easier and faster to get started on a > new project. I may want to do a relatively small web app or command-line > utility. It shouldn't take long. But if I require any of a number of larger > (but very useful) packages, then installing them into a new sandbox does > take a while. This short-circuits that and lets me get started on the > project itself almost immediately. > > After the project's going, I often find that I switch over to a sandbox in > the project directory, but I can do that after I've moved on to another > task. > > Basically it allows me to get started on a project very quickly while still > having the benefits of sandboxes. There's been a utility I've been thinking of since I started using sandboxes (but haven't had enough of a need to write myself as yet): to automatically do a "git pull", "darcs pull", etc. for dependencies if you're using "cabal sandbox add-source" whilst developing based upon packages from HEAD. Would you consider adding such functionality to castle? > > > > On Wed, Jan 15, 2014 at 9:47 PM, Conrad Parker wrote: >> >> >> >> On 16 January 2014 12:38, Eric Rochester wrote: >>> >>> It doesn't differ at all. In fact, that's just what it does. It's just a >>> management utility keeping all of the sandboxes in one place. >>> >>> Overkill? Certainly. >> >> It doesn't sound like overkill to me -- cabal gives a mechanism for having >> sandboxes, but doesn't impose any policy about why you would use them. >> >> Is the point that you maintain multiple sandboxes, like a lens sandbox and >> a yesod sandbox; and this tool makes it easier to manage those? ie. you >> might maintain separate lens-3.9 and lens-3.10 sandboxes, and when compiling >> a new project that uses lens, choose the appropriate lens sandbox. >> >> Conrad. >> >>> >>> On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" >>> wrote: >>>> >>>> On 16 January 2014 07:24, Eric Rochester wrote: >>>> > I'd like to announce the first release of castle >>>> > (http://hackage.haskell.org/package/castle and >>>> > https://github.com/erochest/castle). From the README: >>>> >> >>>> >> I really like having sandboxes baked into cabal-install (see Cabal >>>> >> Sandboxes for more information). >>>> >> >>>> >> I got tired of waiting for big packages like Yesod and Lens to >>>> >> compile in >>>> >> project after project that used them. However, I still didn't want to >>>> >> install them in the user database. I wanted to maintain some >>>> >> sandboxing >>>> >> among a group of projects that all share a common set of packages, >>>> >> but I >>>> >> wanted to be able to switch from them or upgrade them easily. >>>> >> >>>> >> That's the itch I was trying to scratch with castle. >>>> >> >>>> >> It allows you to share one Cabal sandbox between multiple projects. >>>> >> This >>>> >> keeps the package versions for all of these projects in line. It also >>>> >> means >>>> >> that you don't have to constantly be re-installing everything, but >>>> >> you still >>>> >> get the ability to blow away a set of packages without borking your >>>> >> whole >>>> >> system. >>>> > >>>> > >>>> > This tool is still pretty rough around the edges, but I've been using >>>> > it >>>> > some, and it's to the point that more feedback would be helpful. Let >>>> > me know >>>> > what bugs and rough patches you find. >>>> >>>> How does this differ from doing "cabal sandbox init >>>> --sandbox=../my-common-sandbox" for all these projects? >>>> >>>> -- >>>> Ivan Lazar Miljenovic >>>> Ivan.Miljenovic at gmail.com >>>> http://IvanMiljenovic.wordpress.com >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From oleg at okmij.org Thu Jan 16 04:19:48 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 16 Jan 2014 04:19:48 -0000 Subject: [Haskell-cafe] Restrict values in type Message-ID: <20140116041948.99010.qmail@www1.g3.pair.com> The problem you have posed calls for so-called open unions. Open unions come up all the time, and lots of solutions exists. Alas, they are all a bit ad hoc. At Haskell Symposium I was advocating designing a good solution once and for all. The paper that introduced monad transformers showed one implementation of open unions (of effects). The paper `data types a la carte' showed another (essentially the same, trying to deemphasize its use of overlapping instances). The Extensible effects paper has two more solutions, one with Typeable and one without. You can use OpenUnions from that paper if you install extensible-effects package. Using singletons is yet another, quite heavy-weight solution. I'd like to stress a much simpler solution, which requires no type equality or GADTs or bleeding edge. It is a tagless-final solution. In fact, it has been demonstrated already by Jake McArthur. I elaborate and show the whole code. Your original code defined PenShape as a data structure > data PenShape = Circle Float > | Rectangle Float Float > | ArbitraryPen -- Stuff (not relevant) I will define it as an expression in a very simple domain-specific language of pen shapes. > class CirclePen repr where > circle :: Float -> repr > -- other ways of constructing circles go here > > class RectPen repr where > rectangle :: Float -> Float -> repr > > class ArbitraryPen repr where > arbitrary :: () -> repr -- () stands for irrelevant stuff Here repr is the meaning of a pan shape in a particular interpretation. The same term can be interpreted in many ways (compare: a Haskell code can be loaded into GHCi, compiled with GHC or processed with Haddoc). One interpretation of pen shapes is to print them out nicely: data S = S{unS :: String} instance CirclePen S where circle x = S $ "circle pen of radius " ++ show x instance RectPen S where rectangle x y = S $ "rect pen " ++ show (x,y) instance ArbitraryPen S where arbitrary () = S $ "arbitrary pen" There probably will be other representations: defined only for specific sets of pens (rather than all of them), see below for an example. You ask how can you pattern-match on pen shapes. The answer is that in taggless-final style, you don't pattern-match. You interpret. Quite often the code becomes clearer. Enclosed is the complete code. For (far) more explanation of tagless-final, please see the first part of http://okmij.org/ftp/tagless-final/course/lecture.pdf {-# LANGUAGE RankNTypes #-} module Im where data Image = Image [Stroke] -- As a data structure {- data PenShape = Circle Float | Rectangle Float Float | ArbitraryPen -- Stuff (not relevant) -} -- As a term in a simple language of shapes class CirclePen repr where circle :: Float -> repr -- other ways of constructing circles go here class RectPen repr where rectangle :: Float -> Float -> repr class ArbitraryPen repr where arbitrary :: () -> repr -- () stands for irrelevant stuff -- Let's define a few interpretations of pens -- the Show interpretation, to print them -- All pens support this interpretation data S = S{unS :: String} instance CirclePen S where circle x = S $ "circle pen of radius " ++ show x instance RectPen S where rectangle x y = S $ "rect pen " ++ show (x,y) instance ArbitraryPen S where arbitrary () = S $ "arbitrary pen" -- Another interpretation: finite-dim pens. Only CirclePen and RectPen -- support it data FiniteDim = FiniteDim{unFD:: Float} instance CirclePen FiniteDim where circle x = FiniteDim x instance RectPen FiniteDim where rectangle x y = FiniteDim $ max x y {- data Stroke = Line Point Point PenShape | Arc Point Point Point PenShape | Spot Point PenShape -} type Point = (Float,Float) p0 = (0,0) p1 = (1,1) data Stroke = Line Point Point (forall repr. (CirclePen repr, RectPen repr) => repr) | Arc Point Point (forall repr. (CirclePen repr) => repr) | Spot Point (forall repr. (CirclePen repr, RectPen repr, ArbitraryPen repr) => repr) -- Let's make a an image im1 = Image [ Line p0 p1 (circle 10), Line p0 p1 (rectangle 1 2), -- The following will be a type error, as expected -- Arc p0 p1 (rectangle 1 2), Arc p0 p1 (circle 3), Spot p0 (rectangle 1 2), Spot p0 (arbitrary ()) ] -- If we add -- Line p0 p1 (arbitrary ()) -- we get a type error with an informative message {- Could not deduce (ArbitraryPen repr) arising from a use of `arbitrary' from the context (CirclePen repr, RectPen repr) bound by a type expected by the context: (CirclePen repr, RectPen repr) => repr -} -- Let's print the list of strokes show_strokes :: Image -> [String] show_strokes (Image l) = map f l where f (Line p1 p2 pensh) = unwords ["Line", show (p1,p2), unS pensh] f (Arc p1 p2 pensh) = unwords ["Arc", show (p1,p2), unS pensh] f (Spot p1 pensh) = unwords ["Spot", show p1, unS pensh] tshow = show_strokes im1 {- ["Line ((0.0,0.0),(1.0,1.0)) circle pen of radius 10.0", "Line ((0.0,0.0),(1.0,1.0)) rect pen (1.0,2.0)", "Arc ((0.0,0.0),(1.0,1.0)) circle pen of radius 3.0", "Spot (0.0,0.0) rect pen (1.0,2.0)","Spot (0.0,0.0) arbitrary pen"] -} From corentin.dupont at gmail.com Thu Jan 16 08:50:14 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 16 Jan 2014 09:50:14 +0100 Subject: [Haskell-cafe] Error management in Happstack In-Reply-To: References: Message-ID: Thanks, that's great! So if I understand, I have to create a template error page to host the errors? Cheers, Corentin On Thu, Jan 16, 2014 at 4:37 AM, Jeremy Shaw wrote: > Hello, > > Happstack uses monad-control. You can use catch from lifted-base to > catch the exception. I have attached a simple demo. > > You can learn more about monad-control many places including here: > > https://www.fpcomplete.com/user/jwiegley/monad-control > > - jeremy > > On Mon, Jan 13, 2014 at 3:50 PM, Corentin Dupont > wrote: > > Hi Jeremy, all, > > In Happstack when I throw an error, I obtain a blank page with "server > > error: my message". > > How can I decorate this page? > > I'd like to have it look like the other pages of my website, and a "back > to > > login" link, for example. > > > > Thanks! > > Corentin > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From apfelmus at quantentunnel.de Thu Jan 16 10:34:52 2014 From: apfelmus at quantentunnel.de (Heinrich Apfelmus) Date: Thu, 16 Jan 2014 11:34:52 +0100 Subject: [Haskell-cafe] mdo with multiple values In-Reply-To: <1389828245.4552.9.camel@kirk> References: <1389779877.2660.4.camel@kirk> <1389828245.4552.9.camel@kirk> Message-ID: Joachim Breitner wrote: > the background is a binary format assembler, so you can think of the > monad as the Put monad, only sufficiently lazy to admit a useful > MonadFix instance. Then one can do nice things like > > mdo > putWord32 offset > putBS someMoreHeaderData > ... > offset <- getCurrentOffset > putBS byteString1 > > where I conceptually use the offset before it is known. > > [..] > Now I try to generalize that to a list of Bytestrings, and just from the > looks of it, this is what you want to do: > > mdo > mapM_ putWord32 offsets > putBS someMoreHeaderData > ... > offsets <- forM byteStrings $ \b -> > offset <- getCurrentOffset > putBS b > return offset > > but that will <>. So, the overall idea is that we can reserve 32 bits for the offset and defer its calculation to later. In other words, putWord32 can "forward the file pointer" long before it actually writes the word. Now, what's the problem with the `offsets` list? I think it may actually work in some monads that have a good MonadFix instance, but often, the MonadFix instances tend to be poor. One noteable example of the latter is the IO monad, and I have found the following rule to be very useful: To use value recursion in the IO monad, make sure that the sequence of *computations* is always defined in advance, only the values that these computations operate on may be lazy. This rule is best explained with the problem at hand, by asking the following question: how many `putWord32` instructions does the following expression generate? mapM_ putWord32 offsets Clearly, it should be `length offsets` many, but the problem is that this number is not known until the spine of `offsets` has been calculated. Now, some monads may be able to do that, but the rule for IO is that the number of `putWord32` must be known before the later definition of `offsets` can yield a value different from _|_ at all. Now, if a recursive expression works in the IO monad, then it will work in any other monad as well. Fortunately, we do known the spine of `offsets` in advance: it has the same spine as `byteStrings`. The solution is to make that explicit in the code, by using a lazy `zip`: ... mapM_ putWord32 (offsets `spine` byteStrings) ... where spine :: [a] -> [void] -> [a] spine ~[] [] = [] spine ~(x:xs) (y:ys) = x : tag xs ys This code takes the spine of `byteStrings` and fills it with values from `offsets`. It may also be possible to get rid of the <> by defining the monad appropriately: one pass calculates all offsets, a second pass calculates the actual output. The spine of `offsets` does not depend on the offset calculation, so there is a good chance that this might work recursively. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com From mail at joachim-breitner.de Thu Jan 16 10:49:09 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Thu, 16 Jan 2014 10:49:09 +0000 Subject: [Haskell-cafe] mdo with multiple values In-Reply-To: References: <1389779877.2660.4.camel@kirk> <1389828245.4552.9.camel@kirk> Message-ID: <1389869349.2491.8.camel@kirk> Hi, Am Donnerstag, den 16.01.2014, 11:34 +0100 schrieb Heinrich Apfelmus: > Fortunately, we do known the spine of `offsets` in advance: it has the > same spine as `byteStrings`. The solution is to make that explicit in > the code, by using a lazy `zip`: > > ... > mapM_ putWord32 (offsets `spine` byteStrings) > ... > > where > spine :: [a] -> [void] -> [a] > spine ~[] [] = [] > spine ~(x:xs) (y:ys) = x : tag xs ys > > This code takes the spine of `byteStrings` and fills it with values from > `offsets`. I thought about something in that direction; but thanks for working it out. What I do not like about this solution is that it is not safe: As a programmer I have two make sure that offsets and byteStrings actually have the same length. Greetings, Joachim -- Joachim Breitner e-Mail: mail at joachim-breitner.de Homepage: http://www.joachim-breitner.de Jabber-ID: nomeata at joachim-breitner.de -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 181 bytes Desc: This is a digitally signed message part URL: From erochest at gmail.com Thu Jan 16 11:45:05 2014 From: erochest at gmail.com (Eric Rochester) Date: Thu, 16 Jan 2014 06:45:05 -0500 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: If the package lists a source repository, that shouldn't be too difficult. But would it be helpful to do that in a shared sandbox? I'm trying to think about when I use add-source, and I think that it's generally on a project-specific basis. But you have other uses cases, I'd be happy to consider it. Eric On Wed, Jan 15, 2014 at 11:05 PM, Ivan Lazar Miljenovic < ivan.miljenovic at gmail.com> wrote: > On 16 January 2014 14:31, Eric Rochester wrote: > > That's one use case that I've used some. > > > > Another motivation has been to make it easier and faster to get started > on a > > new project. I may want to do a relatively small web app or command-line > > utility. It shouldn't take long. But if I require any of a number of > larger > > (but very useful) packages, then installing them into a new sandbox does > > take a while. This short-circuits that and lets me get started on the > > project itself almost immediately. > > > > After the project's going, I often find that I switch over to a sandbox > in > > the project directory, but I can do that after I've moved on to another > > task. > > > > Basically it allows me to get started on a project very quickly while > still > > having the benefits of sandboxes. > > There's been a utility I've been thinking of since I started using > sandboxes (but haven't had enough of a need to write myself as yet): > to automatically do a "git pull", "darcs pull", etc. for dependencies > if you're using "cabal sandbox add-source" whilst developing based > upon packages from HEAD. > > Would you consider adding such functionality to castle? > > > > > > > > > On Wed, Jan 15, 2014 at 9:47 PM, Conrad Parker > wrote: > >> > >> > >> > >> On 16 January 2014 12:38, Eric Rochester wrote: > >>> > >>> It doesn't differ at all. In fact, that's just what it does. It's just > a > >>> management utility keeping all of the sandboxes in one place. > >>> > >>> Overkill? Certainly. > >> > >> It doesn't sound like overkill to me -- cabal gives a mechanism for > having > >> sandboxes, but doesn't impose any policy about why you would use them. > >> > >> Is the point that you maintain multiple sandboxes, like a lens sandbox > and > >> a yesod sandbox; and this tool makes it easier to manage those? ie. you > >> might maintain separate lens-3.9 and lens-3.10 sandboxes, and when > compiling > >> a new project that uses lens, choose the appropriate lens sandbox. > >> > >> Conrad. > >> > >>> > >>> On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" > >>> wrote: > >>>> > >>>> On 16 January 2014 07:24, Eric Rochester wrote: > >>>> > I'd like to announce the first release of castle > >>>> > (http://hackage.haskell.org/package/castle and > >>>> > https://github.com/erochest/castle). From the README: > >>>> >> > >>>> >> I really like having sandboxes baked into cabal-install (see Cabal > >>>> >> Sandboxes for more information). > >>>> >> > >>>> >> I got tired of waiting for big packages like Yesod and Lens to > >>>> >> compile in > >>>> >> project after project that used them. However, I still didn't want > to > >>>> >> install them in the user database. I wanted to maintain some > >>>> >> sandboxing > >>>> >> among a group of projects that all share a common set of packages, > >>>> >> but I > >>>> >> wanted to be able to switch from them or upgrade them easily. > >>>> >> > >>>> >> That's the itch I was trying to scratch with castle. > >>>> >> > >>>> >> It allows you to share one Cabal sandbox between multiple projects. > >>>> >> This > >>>> >> keeps the package versions for all of these projects in line. It > also > >>>> >> means > >>>> >> that you don't have to constantly be re-installing everything, but > >>>> >> you still > >>>> >> get the ability to blow away a set of packages without borking your > >>>> >> whole > >>>> >> system. > >>>> > > >>>> > > >>>> > This tool is still pretty rough around the edges, but I've been > using > >>>> > it > >>>> > some, and it's to the point that more feedback would be helpful. Let > >>>> > me know > >>>> > what bugs and rough patches you find. > >>>> > >>>> How does this differ from doing "cabal sandbox init > >>>> --sandbox=../my-common-sandbox" for all these projects? > >>>> > >>>> -- > >>>> Ivan Lazar Miljenovic > >>>> Ivan.Miljenovic at gmail.com > >>>> http://IvanMiljenovic.wordpress.com > >>> > >>> > >>> _______________________________________________ > >>> Haskell-Cafe mailing list > >>> Haskell-Cafe at haskell.org > >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >>> > >> > > > > > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Thu Jan 16 12:01:28 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 16 Jan 2014 23:01:28 +1100 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: On 16 January 2014 22:45, Eric Rochester wrote: > If the package lists a source repository, that shouldn't be too difficult. > > But would it be helpful to do that in a shared sandbox? I'm trying to think > about when I use add-source, and I think that it's generally on a > project-specific basis. > > But you have other uses cases, I'd be happy to consider it. The cases I can think of: 1) Benchmarking against various libraries (release versions could be used, but unless I'm doing something wrong with my usage of cabal-install, unless I change the lower bound it doesn't bring in newer versions of libraries unless you explicitly tell it to, so by tracking HEAD you can make sure you're always comparing against the latest library verions). 2) Working on interrelated projects amongst several people: you yourself might not be working on a library foo that someone else is developing, but you know you need to make sure your code works against the latest version (either to be ready for when it releases or because you need functionality that isn't in a release of foo yet). 3) Related to the previous point: you've tracked down a regression in a dependency of your project, and so you're tracking its source repo to help its developer track down the problem (admittedly this one is a bit tenuous: either upstream can use your code to test, or you can manually sync the few times upstream thinks they might have a fix and see if it works, rather than needing it automated). > > Eric > > > > On Wed, Jan 15, 2014 at 11:05 PM, Ivan Lazar Miljenovic > wrote: >> >> On 16 January 2014 14:31, Eric Rochester wrote: >> > That's one use case that I've used some. >> > >> > Another motivation has been to make it easier and faster to get started >> > on a >> > new project. I may want to do a relatively small web app or command-line >> > utility. It shouldn't take long. But if I require any of a number of >> > larger >> > (but very useful) packages, then installing them into a new sandbox does >> > take a while. This short-circuits that and lets me get started on the >> > project itself almost immediately. >> > >> > After the project's going, I often find that I switch over to a sandbox >> > in >> > the project directory, but I can do that after I've moved on to another >> > task. >> > >> > Basically it allows me to get started on a project very quickly while >> > still >> > having the benefits of sandboxes. >> >> There's been a utility I've been thinking of since I started using >> sandboxes (but haven't had enough of a need to write myself as yet): >> to automatically do a "git pull", "darcs pull", etc. for dependencies >> if you're using "cabal sandbox add-source" whilst developing based >> upon packages from HEAD. >> >> Would you consider adding such functionality to castle? >> >> > >> > >> > >> > On Wed, Jan 15, 2014 at 9:47 PM, Conrad Parker >> > wrote: >> >> >> >> >> >> >> >> On 16 January 2014 12:38, Eric Rochester wrote: >> >>> >> >>> It doesn't differ at all. In fact, that's just what it does. It's just >> >>> a >> >>> management utility keeping all of the sandboxes in one place. >> >>> >> >>> Overkill? Certainly. >> >> >> >> It doesn't sound like overkill to me -- cabal gives a mechanism for >> >> having >> >> sandboxes, but doesn't impose any policy about why you would use them. >> >> >> >> Is the point that you maintain multiple sandboxes, like a lens sandbox >> >> and >> >> a yesod sandbox; and this tool makes it easier to manage those? ie. you >> >> might maintain separate lens-3.9 and lens-3.10 sandboxes, and when >> >> compiling >> >> a new project that uses lens, choose the appropriate lens sandbox. >> >> >> >> Conrad. >> >> >> >>> >> >>> On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" >> >>> wrote: >> >>>> >> >>>> On 16 January 2014 07:24, Eric Rochester wrote: >> >>>> > I'd like to announce the first release of castle >> >>>> > (http://hackage.haskell.org/package/castle and >> >>>> > https://github.com/erochest/castle). From the README: >> >>>> >> >> >>>> >> I really like having sandboxes baked into cabal-install (see Cabal >> >>>> >> Sandboxes for more information). >> >>>> >> >> >>>> >> I got tired of waiting for big packages like Yesod and Lens to >> >>>> >> compile in >> >>>> >> project after project that used them. However, I still didn't want >> >>>> >> to >> >>>> >> install them in the user database. I wanted to maintain some >> >>>> >> sandboxing >> >>>> >> among a group of projects that all share a common set of packages, >> >>>> >> but I >> >>>> >> wanted to be able to switch from them or upgrade them easily. >> >>>> >> >> >>>> >> That's the itch I was trying to scratch with castle. >> >>>> >> >> >>>> >> It allows you to share one Cabal sandbox between multiple >> >>>> >> projects. >> >>>> >> This >> >>>> >> keeps the package versions for all of these projects in line. It >> >>>> >> also >> >>>> >> means >> >>>> >> that you don't have to constantly be re-installing everything, but >> >>>> >> you still >> >>>> >> get the ability to blow away a set of packages without borking >> >>>> >> your >> >>>> >> whole >> >>>> >> system. >> >>>> > >> >>>> > >> >>>> > This tool is still pretty rough around the edges, but I've been >> >>>> > using >> >>>> > it >> >>>> > some, and it's to the point that more feedback would be helpful. >> >>>> > Let >> >>>> > me know >> >>>> > what bugs and rough patches you find. >> >>>> >> >>>> How does this differ from doing "cabal sandbox init >> >>>> --sandbox=../my-common-sandbox" for all these projects? >> >>>> >> >>>> -- >> >>>> Ivan Lazar Miljenovic >> >>>> Ivan.Miljenovic at gmail.com >> >>>> http://IvanMiljenovic.wordpress.com >> >>> >> >>> >> >>> _______________________________________________ >> >>> Haskell-Cafe mailing list >> >>> Haskell-Cafe at haskell.org >> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >>> >> >> >> > >> >> >> >> -- >> Ivan Lazar Miljenovic >> Ivan.Miljenovic at gmail.com >> http://IvanMiljenovic.wordpress.com > > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From erochest at gmail.com Thu Jan 16 13:51:32 2014 From: erochest at gmail.com (Eric Rochester) Date: Thu, 16 Jan 2014 08:51:32 -0500 Subject: [Haskell-cafe] ANN: castle 0.1.0.0 In-Reply-To: References: Message-ID: Sounds fine. It may be next week, but I'll see if I can add an add-source command in. Eric On Thu, Jan 16, 2014 at 7:01 AM, Ivan Lazar Miljenovic < ivan.miljenovic at gmail.com> wrote: > On 16 January 2014 22:45, Eric Rochester wrote: > > If the package lists a source repository, that shouldn't be too > difficult. > > > > But would it be helpful to do that in a shared sandbox? I'm trying to > think > > about when I use add-source, and I think that it's generally on a > > project-specific basis. > > > > But you have other uses cases, I'd be happy to consider it. > > The cases I can think of: > > 1) Benchmarking against various libraries (release versions could be > used, but unless I'm doing something wrong with my usage of > cabal-install, unless I change the lower bound it doesn't bring in > newer versions of libraries unless you explicitly tell it to, so by > tracking HEAD you can make sure you're always comparing against the > latest library verions). > > 2) Working on interrelated projects amongst several people: you > yourself might not be working on a library foo that someone else is > developing, but you know you need to make sure your code works against > the latest version (either to be ready for when it releases or because > you need functionality that isn't in a release of foo yet). > > 3) Related to the previous point: you've tracked down a regression in > a dependency of your project, and so you're tracking its source repo > to help its developer track down the problem (admittedly this one is a > bit tenuous: either upstream can use your code to test, or you can > manually sync the few times upstream thinks they might have a fix and > see if it works, rather than needing it automated). > > > > > Eric > > > > > > > > On Wed, Jan 15, 2014 at 11:05 PM, Ivan Lazar Miljenovic > > wrote: > >> > >> On 16 January 2014 14:31, Eric Rochester wrote: > >> > That's one use case that I've used some. > >> > > >> > Another motivation has been to make it easier and faster to get > started > >> > on a > >> > new project. I may want to do a relatively small web app or > command-line > >> > utility. It shouldn't take long. But if I require any of a number of > >> > larger > >> > (but very useful) packages, then installing them into a new sandbox > does > >> > take a while. This short-circuits that and lets me get started on the > >> > project itself almost immediately. > >> > > >> > After the project's going, I often find that I switch over to a > sandbox > >> > in > >> > the project directory, but I can do that after I've moved on to > another > >> > task. > >> > > >> > Basically it allows me to get started on a project very quickly while > >> > still > >> > having the benefits of sandboxes. > >> > >> There's been a utility I've been thinking of since I started using > >> sandboxes (but haven't had enough of a need to write myself as yet): > >> to automatically do a "git pull", "darcs pull", etc. for dependencies > >> if you're using "cabal sandbox add-source" whilst developing based > >> upon packages from HEAD. > >> > >> Would you consider adding such functionality to castle? > >> > >> > > >> > > >> > > >> > On Wed, Jan 15, 2014 at 9:47 PM, Conrad Parker > >> > wrote: > >> >> > >> >> > >> >> > >> >> On 16 January 2014 12:38, Eric Rochester wrote: > >> >>> > >> >>> It doesn't differ at all. In fact, that's just what it does. It's > just > >> >>> a > >> >>> management utility keeping all of the sandboxes in one place. > >> >>> > >> >>> Overkill? Certainly. > >> >> > >> >> It doesn't sound like overkill to me -- cabal gives a mechanism for > >> >> having > >> >> sandboxes, but doesn't impose any policy about why you would use > them. > >> >> > >> >> Is the point that you maintain multiple sandboxes, like a lens > sandbox > >> >> and > >> >> a yesod sandbox; and this tool makes it easier to manage those? ie. > you > >> >> might maintain separate lens-3.9 and lens-3.10 sandboxes, and when > >> >> compiling > >> >> a new project that uses lens, choose the appropriate lens sandbox. > >> >> > >> >> Conrad. > >> >> > >> >>> > >> >>> On Jan 15, 2014 7:30 PM, "Ivan Lazar Miljenovic" > >> >>> wrote: > >> >>>> > >> >>>> On 16 January 2014 07:24, Eric Rochester > wrote: > >> >>>> > I'd like to announce the first release of castle > >> >>>> > (http://hackage.haskell.org/package/castle and > >> >>>> > https://github.com/erochest/castle). From the README: > >> >>>> >> > >> >>>> >> I really like having sandboxes baked into cabal-install (see > Cabal > >> >>>> >> Sandboxes for more information). > >> >>>> >> > >> >>>> >> I got tired of waiting for big packages like Yesod and Lens to > >> >>>> >> compile in > >> >>>> >> project after project that used them. However, I still didn't > want > >> >>>> >> to > >> >>>> >> install them in the user database. I wanted to maintain some > >> >>>> >> sandboxing > >> >>>> >> among a group of projects that all share a common set of > packages, > >> >>>> >> but I > >> >>>> >> wanted to be able to switch from them or upgrade them easily. > >> >>>> >> > >> >>>> >> That's the itch I was trying to scratch with castle. > >> >>>> >> > >> >>>> >> It allows you to share one Cabal sandbox between multiple > >> >>>> >> projects. > >> >>>> >> This > >> >>>> >> keeps the package versions for all of these projects in line. It > >> >>>> >> also > >> >>>> >> means > >> >>>> >> that you don't have to constantly be re-installing everything, > but > >> >>>> >> you still > >> >>>> >> get the ability to blow away a set of packages without borking > >> >>>> >> your > >> >>>> >> whole > >> >>>> >> system. > >> >>>> > > >> >>>> > > >> >>>> > This tool is still pretty rough around the edges, but I've been > >> >>>> > using > >> >>>> > it > >> >>>> > some, and it's to the point that more feedback would be helpful. > >> >>>> > Let > >> >>>> > me know > >> >>>> > what bugs and rough patches you find. > >> >>>> > >> >>>> How does this differ from doing "cabal sandbox init > >> >>>> --sandbox=../my-common-sandbox" for all these projects? > >> >>>> > >> >>>> -- > >> >>>> Ivan Lazar Miljenovic > >> >>>> Ivan.Miljenovic at gmail.com > >> >>>> http://IvanMiljenovic.wordpress.com > >> >>> > >> >>> > >> >>> _______________________________________________ > >> >>> Haskell-Cafe mailing list > >> >>> Haskell-Cafe at haskell.org > >> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> >>> > >> >> > >> > > >> > >> > >> > >> -- > >> Ivan Lazar Miljenovic > >> Ivan.Miljenovic at gmail.com > >> http://IvanMiljenovic.wordpress.com > > > > > > > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jan.stolarek at p.lodz.pl Thu Jan 16 13:52:11 2014 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Thu, 16 Jan 2014 14:52:11 +0100 Subject: [Haskell-cafe] Silencing 'cabal configure' warning Message-ID: <201401161452.11227.jan.stolarek@p.lodz.pl> Hi all, When running 'cabal configure' I get a warning that my package database is old: [killy at xerxes : /dane/projekty/singletons] cabal configure Warning: The package list for 'hackage.haskell.org' is 25 days old. Run 'cabal update' to get the latest list of available packages. Is there a way to silence this warning other than running 'cabal update'? I don't want to update my package database and getting a warning every time I configure a package is irritating. Janek From ltclifton at gmail.com Thu Jan 16 14:16:58 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Thu, 16 Jan 2014 22:16:58 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: <20140116041948.99010.qmail@www1.g3.pair.com> References: <20140116041948.99010.qmail@www1.g3.pair.com> Message-ID: Thanks, that really cleared up a few of the questions I had about Jake McArthurs' code as well. The link you provided was a good read and shed some more light on the situation. The only bit I don't quite understand is why the following code implies an "or" relation in the type constraint of repr. > data Stroke = > Line Point Point (forall repr. (CirclePen repr, RectPen repr) => repr) > | Arc Point Point (forall repr. (CirclePen repr) => repr) > | Spot Point (forall repr. > (CirclePen repr, RectPen repr, ArbitraryPen repr) => repr) To me this reads that repr should be both a CirclePen and a RectPen in order to satisfy the type constraint in the case of Line, but it seems that it is accepting a CirclePen or a RectPen (which is the desired behaviour, so I'm not complaining). -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Thu Jan 16 14:31:37 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Thu, 16 Jan 2014 18:31:37 +0400 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: <20140116041948.99010.qmail@www1.g3.pair.com> Message-ID: Ah, it is a little bit confusing. The type (forall repr. (CirclePen repr, RectPen repr) => repr) is inhabited by a _represtentation_ that can be constructed both by 'circle' and by 'rectangle'. So we can use any of those two functions to construct a value of that type. (Such type is FiniteDim for example). The Arc constructor, on the other hand, accepts only values of type (forall repr. (CirclePen repr) => repr). We don't know anything about the concrete representation type, we only know that we can construct it using 'circle'. Hth -dan On Thu, Jan 16, 2014 at 6:16 PM, Luke Clifton wrote: > Thanks, that really cleared up a few of the questions I had about Jake > McArthurs' code as well. The link you provided was a good read and shed some > more light on the situation. > > The only bit I don't quite understand is why the following code implies an > "or" relation in the type constraint of repr. > >> data Stroke = >> Line Point Point (forall repr. (CirclePen repr, RectPen repr) => repr) >> | Arc Point Point (forall repr. (CirclePen repr) => repr) >> | Spot Point (forall repr. >> (CirclePen repr, RectPen repr, ArbitraryPen repr) => repr) > > To me this reads that repr should be both a CirclePen and a RectPen in order > to satisfy the type constraint in the case of Line, but it seems that it is > accepting a CirclePen or a RectPen (which is the desired behaviour, so I'm > not complaining). > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sincerely yours, -- Daniil From ltclifton at gmail.com Thu Jan 16 14:55:59 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Thu, 16 Jan 2014 22:55:59 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: References: <20140116041948.99010.qmail@www1.g3.pair.com> Message-ID: > > > To me this reads that repr should be both a CirclePen and a RectPen in > order to satisfy the type constraint in the case of Line, but it seems that > it is accepting a CirclePen or a RectPen (which is the desired behaviour, > so I'm not complaining). > > Having thought about it, it _IS_ saying that repr is an instance of both CirclePen and RectPen, which is why I can call either circle or rectangle in that context. The called function then decides the type, rather than the calling function. PS: I got out of bed with this epiphany, so I may be incoherent and tired and not making any sense at all... -------------- next part -------------- An HTML attachment was scrubbed... URL: From tretriluxana.s at gmail.com Thu Jan 16 16:43:04 2014 From: tretriluxana.s at gmail.com (Sukit Tretriluxana) Date: Thu, 16 Jan 2014 08:43:04 -0800 Subject: [Haskell-cafe] Can't install yesod-platform due to vector package Message-ID: Hi all, I'm trying to install Yesod as suggested by this page. http://www.yesodweb.com/page/quickstart with the following command cabal update cabal install yesod-platform yesod-bin --max-backjumps=-1 --reorder-goals But I constantly get the following error. ... 136 warnings and 6 errors generated. Failed to install vector-0.10.9.1 cabal: Error: some packages failed to install: aeson-0.6.2.1 depends on vector-0.10.9.1 which failed to install. ... The error appears to be from the fact that cabal cannot install vector package. Any suggestion to fix the problem. I'm on Maverick, Xcode5, Haskell Platform 2013.2.0.0 64bit Thanks, Ed -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Jan 16 16:47:31 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 16 Jan 2014 11:47:31 -0500 Subject: [Haskell-cafe] Can't install yesod-platform due to vector package In-Reply-To: References: Message-ID: On Thu, Jan 16, 2014 at 11:43 AM, Sukit Tretriluxana < tretriluxana.s at gmail.com> wrote: > Any suggestion to fix the problem. I'm on Maverick, Xcode5, Haskell > Platform 2013.2.0.0 64bit > We would have to see the actual errors, as opposed to just how many errors occurred which is all that you have shown us. But, since you say you are on Mavericks with Xcode 5, have you applied the mandatory changes for Xcode 5 support? http://is.gd/H4sEub -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Thu Jan 16 17:30:12 2014 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 16 Jan 2014 19:30:12 +0200 Subject: [Haskell-cafe] Can't install yesod-platform due to vector package In-Reply-To: References: Message-ID: Can you include the full output from trying to install vector? cabal install vector-0.10.9.1 On Thu, Jan 16, 2014 at 6:43 PM, Sukit Tretriluxana < tretriluxana.s at gmail.com> wrote: > Hi all, > > I'm trying to install Yesod as suggested by this page. > > http://www.yesodweb.com/page/quickstart > > with the following command > > cabal update cabal install yesod-platform yesod-bin --max-backjumps=-1 > --reorder-goals > > But I constantly get the following error. > > ... > > 136 warnings and 6 errors generated. > > Failed to install vector-0.10.9.1 > > cabal: Error: some packages failed to install: > > aeson-0.6.2.1 depends on vector-0.10.9.1 which failed to install. > ... > > The error appears to be from the fact that cabal cannot install vector > package. > > Any suggestion to fix the problem. I'm on Maverick, Xcode5, Haskell > Platform 2013.2.0.0 64bit > > Thanks, > Ed > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmacristovao at gmail.com Thu Jan 16 17:57:39 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Thu, 16 Jan 2014 17:57:39 +0000 Subject: [Haskell-cafe] flip1 through flip9, useful? In-Reply-To: References: <20140114054823.GA8955@cucumber.bridge.anchor.net.au> <52D4DFCA.8000703@gmail.com> <20140114233015.GA22859@cucumber.bridge.anchor.net.au> Message-ID: > > For flips of higher arities, you would choose a different `f`, like (f ~ > (->) d . (->) c): > > \f a -> fmap ($a) f :: (c -> d -> a -> b) -> (a -> c -> d -> b) > Hi, Could you give a concrete example of this (for higher arities)? Thanks, Joao -------------- next part -------------- An HTML attachment was scrubbed... URL: From tretriluxana.s at gmail.com Thu Jan 16 19:06:13 2014 From: tretriluxana.s at gmail.com (Sukit Tretriluxana) Date: Thu, 16 Jan 2014 11:06:13 -0800 Subject: [Haskell-cafe] Can't install yesod-platform due to vector package In-Reply-To: References: Message-ID: Thanks both Brandon and Michael for your help. My bad. I wasn't aware of the small step to take after install Haskell Platform that Brandon pointed out. After done that, everything works just fine. Ed On Thu, Jan 16, 2014 at 9:30 AM, Michael Snoyman wrote: > Can you include the full output from trying to install vector? > > cabal install vector-0.10.9.1 > > > On Thu, Jan 16, 2014 at 6:43 PM, Sukit Tretriluxana < > tretriluxana.s at gmail.com> wrote: > >> Hi all, >> >> I'm trying to install Yesod as suggested by this page. >> >> http://www.yesodweb.com/page/quickstart >> >> with the following command >> >> cabal update cabal install yesod-platform yesod-bin --max-backjumps=-1 >> --reorder-goals >> >> But I constantly get the following error. >> >> ... >> >> 136 warnings and 6 errors generated. >> >> Failed to install vector-0.10.9.1 >> >> cabal: Error: some packages failed to install: >> >> aeson-0.6.2.1 depends on vector-0.10.9.1 which failed to install. >> ... >> >> The error appears to be from the fact that cabal cannot install vector >> package. >> >> Any suggestion to fix the problem. I'm on Maverick, Xcode5, Haskell >> Platform 2013.2.0.0 64bit >> >> Thanks, >> Ed >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Fri Jan 17 03:30:30 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 17 Jan 2014 03:30:30 -0000 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: Message-ID: <20140117033030.39076.qmail@www1.g3.pair.com> > The only bit I don't quite understand is why the following code implies an > "or" relation in the type constraint of repr. > > data Stroke = > > Line Point Point (forall repr. (CirclePen repr, RectPen repr) => repr) > > | Arc Point Point (forall repr. (CirclePen repr) => repr) > > | Spot Point (forall repr. > > (CirclePen repr, RectPen repr, ArbitraryPen repr) => repr) > To me this reads that repr should be both a CirclePen and a RectPen in > order to satisfy the type constraint in the case of Line, but it seems that > it is accepting a CirclePen or a RectPen (which is the desired behaviour, > so I'm not complaining). This point is indeed confusing. Perhaps yet another explanation might be helpful. Added to the already given, it might help reaching the critical mass. First, it seems that the dictionary passing implementation of type classes makes things clearer. This implementation realizes, informally, double arrow as a simple arrow. For example, the declaration > class CirclePen repr where > circle :: Float -> repr is translated to a dictionary declaration > data CirclePenDict repr = CirclePenDict{circle :: Float -> repr} and a bounded polymorphic function or value like > CirclePen repr => repr is realized as > CirclePenDict repr -> repr Double arrow turns simple arrow. Therefore, > data Stroke = > Line Point Point (forall repr. (CirclePen repr, RectPen repr) => repr) becomes > data Stroke = > Line Point Point (forall repr. > (CirclePenDict repr, RectPenDict repr) -> repr) We can make two different lines, with the circle pen shape: > -- Line p1 p2 (circle 10) > stroke1 = Line' p0 p1 (\(circledict, rectdict) -> circle circledict 10) or with the rectangular pen shape. > -- Line p1 p2 (circle 10 20) > stroke2 = Line' p0 p1 (\(circledict, rectdict) -> rectangle rectdict 10 20) Obviously we cannot make Lines with the Arbitrary pen shape since we will receive from the user only circledict and rectdict but no arbitrarypendict. Suppose we are communicating over a network. If I can send you _either_ a boolean or an integer, you have to be prepared to handle _both_. From a different point of view: if you send me the handler for a boolean _and_ the handler for an integer, it becomes my choice which one to invoke. (Incidentally, what I just described is a subset of session types for pi-calculus.) At this point de Morgan laws may spring to mind. Here is a related explanation of using open records to implement open unions. http://okmij.org/ftp/Haskell/generics.html#PolyVariant From ltclifton at gmail.com Fri Jan 17 04:06:08 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Fri, 17 Jan 2014 12:06:08 +0800 Subject: [Haskell-cafe] Restrict values in type In-Reply-To: <20140117033030.39076.qmail@www1.g3.pair.com> References: <20140117033030.39076.qmail@www1.g3.pair.com> Message-ID: > > First, it seems that the dictionary passing implementation of type > classes makes things clearer. This implementation realizes, > informally, double arrow as a simple arrow. > Thank you. This explanation really helped me and was precisely what I was missing. I find an understanding of how things are implemented is often required before I feel comfortable with something (and my search for an explanation like the one you gave provided no results). Regards, Luke -------------- next part -------------- An HTML attachment was scrubbed... URL: From simonyarde at me.com Fri Jan 17 10:39:55 2014 From: simonyarde at me.com (Simon Yarde) Date: Fri, 17 Jan 2014 10:39:55 +0000 Subject: [Haskell-cafe] Restrict values in type Message-ID: <92D98678-7562-4006-BE5A-0E13577D6E47@me.com> If it's not been mentioned, this tutorial regarding Type Families and the kinds of restrictions you mention might provide a few pointers: https://www.fpcomplete.com/school/to-infinity-and-beyond/pick-of-the-week/type-families-and-pokemon In general, I've found key concepts to hold in mind are 'exclusion of bad programs' mentioned in the paper Fun With Types: http://research.microsoft.com/en-us/um/people/simonpj/papers/assoc-types/fun-with-type-funs/typefun.pdf I'm sorry if any of this has been mentioned previous. I asked a related question yesterday about the relative merits of creating type restrictions using using newtypes (unions), which I agree seem unwieldy, and using multi-parameter-type-classes (and/or type families) to enable exclusion-of-bad-programms via instances. I'd be interested to follow along and see what you discover. Simon Yarde From lemming at henning-thielemann.de Fri Jan 17 16:07:06 2014 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Fri, 17 Jan 2014 17:07:06 +0100 Subject: [Haskell-cafe] ANN: pooled-io Message-ID: <52D9552A.2040908@henning-thielemann.de> I uploaded the package pooled-io to Hackage: https://hackage.haskell.org/package/pooled-io It is intended to perform parallelism in the IO monad. I needed it for computations that must write intermediate data to disk. The main task of the package is to make sure that no more than a maximum number of actions is run in parallel. There are three modules: For actions without monadic results, for actions with monadic results and for actions that depend on each others results. From robstewart57 at gmail.com Fri Jan 17 16:20:57 2014 From: robstewart57 at gmail.com (Rob Stewart) Date: Fri, 17 Jan 2014 16:20:57 +0000 Subject: [Haskell-cafe] ANN: pooled-io In-Reply-To: <52D9552A.2040908@henning-thielemann.de> References: <52D9552A.2040908@henning-thielemann.de> Message-ID: Hi, Looks interesting. Did you also consider implementing this throttled workpool of IO actions on top of the async library [1]? E.g. mapPool :: T.Traversable t => Int -> (a -> IO b) -> t a -> IO (t b) As in the following SO answer: http://stackoverflow.com/a/18898822/1526266 [1] - http://hackage.haskell.org/package/async -- Rob On 17 January 2014 16:07, Henning Thielemann wrote: > I uploaded the package pooled-io to Hackage: > https://hackage.haskell.org/package/pooled-io > > It is intended to perform parallelism in the IO monad. I needed it for > computations that must write intermediate data to disk. The main task of the > package is to make sure that no more than a maximum number of actions is run > in parallel. There are three modules: For actions without monadic results, > for actions with monadic results and for actions that depend on each others > results. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From schlepptop at henning-thielemann.de Fri Jan 17 17:22:39 2014 From: schlepptop at henning-thielemann.de (Henning Thielemann) Date: Fri, 17 Jan 2014 18:22:39 +0100 Subject: [Haskell-cafe] ANN: pooled-io In-Reply-To: References: <52D9552A.2040908@henning-thielemann.de> Message-ID: <52D966DF.5080701@henning-thielemann.de> Am 17.01.2014 17:20, schrieb Rob Stewart: > Looks interesting. Did you also consider implementing this throttled > workpool of IO actions on top of the async library [1]? What would be the advantages? > E.g. > mapPool :: T.Traversable t => Int -> (a -> IO b) -> t a -> IO (t b) > > As in the following SO answer: > http://stackoverflow.com/a/18898822/1526266 I have added an answer to this question. From trebla at vex.net Fri Jan 17 17:46:58 2014 From: trebla at vex.net (Albert Y. C. Lai) Date: Fri, 17 Jan 2014 12:46:58 -0500 Subject: [Haskell-cafe] Silencing 'cabal configure' warning In-Reply-To: <201401161452.11227.jan.stolarek@p.lodz.pl> References: <201401161452.11227.jan.stolarek@p.lodz.pl> Message-ID: <52D96C92.1090508@vex.net> On 14-01-16 08:52 AM, Jan Stolarek wrote: > When running 'cabal configure' I get a warning that my package database is old: [...] > Is there a way to silence this warning other than running 'cabal update'? I don't want to update > my package database and getting a warning every time I configure a package is irritating. Explore ~/.cabal/packages/hackage.haskell.org, find out of which files to fudge timestamps to fool cabal. From omeragacan at gmail.com Fri Jan 17 18:14:15 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Fri, 17 Jan 2014 20:14:15 +0200 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? Message-ID: Hi all, I recently got myself thinking about programming languages and their effects on programmers. I already knew that concept of "linguistic relativity" ( http://en.wikipedia.org/wiki/Linguistic_relativity ) and I was thinking that this may be relevant with programming too, although I don't have any concrete evidence. I was wondering if anyone else also find that idea of programming language's effect of the programmer interesting. Do we have any research on that kinds of things? Thanks, From douglas.mcclean at gmail.com Fri Jan 17 21:23:13 2014 From: douglas.mcclean at gmail.com (Douglas McClean) Date: Fri, 17 Jan 2014 16:23:13 -0500 Subject: [Haskell-cafe] Automatic differentiation and dimension types Message-ID: Has anyone explored the intersection between automatic differentiation and dimension types (like those in the dimensional package or along the lines of any of the approaches discussed at http://www.haskell.org/haskellwiki/Physical_units)? It's tricky because for ordinary automatic differentiation the types are all the same, but when dimensions get involved that isn't the case, you have to keep dividing by the dimension of the infinitesimal. -Doug McClean -------------- next part -------------- An HTML attachment was scrubbed... URL: From byorgey at seas.upenn.edu Fri Jan 17 21:57:19 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Fri, 17 Jan 2014 16:57:19 -0500 Subject: [Haskell-cafe] ANNOUNCE: Diagrams 1.0 Message-ID: <20140117215719.GA21107@seas.upenn.edu> The diagrams team is very pleased to announce the 1.0 release of diagrams [1], a framework and embedded domain-specific language for declarative drawing in Haskell. Check out the gallery [2] for some examples of what it can do. Diagrams can be used for a wide range of purposes, from data visualization [3] to illustration [4] to art [5], and diagrams code can be seamlessly embedded in blog posts [6], LaTeX documents [7], and Haddock documentation [8], making it easy to incorporate diagrams into your documents with minimal extra work. [1] http://projects.haskell.org/diagrams [2] http://projects.haskell.org/diagrams/gallery.html [3] http://idontgetoutmuch.wordpress.com/2013/10/23/parking-in-westminster-an-analysis-in-haskell/ [4] https://www.fpcomplete.com/user/edwardk/cellular-automata/part-1 [5] http://mathlesstraveled.com/2013/04/06/stars-of-the-minds-sky-with-diagrams/ [6] http://byorgey.wordpress.com/2012/08/28/creating-documents-with-embedded-diagrams/ [7] http://projects.haskell.org/diagrams/doc/latex.html [8] http://byorgey.wordpress.com/2013/03/23/introducing-diagrams-haddock/ What's new ---------- Brent recently gave a talk at the New York Haskell Users' Group [12] presenting the new release. You can find videos of the talk on vimeo: part 1 presents a basic introduction to the library [13], and part 2 talks about mathematical abstraction and DSL design [14]. The slides are also available [15]. [12] http://www.meetup.com/NY-Haskell/ [13] http://vimeo.com/84104226 [14] http://vimeo.com/84249042 [15] http://www.cis.upenn.edu/~byorgey/pub/13-11-25-nyhaskell-diagrams.pdf This release includes a number of significant new features and improvements. Highlights include: - Support for drawing arrows between given points or between diagrams, with many options for customization (tutorial [16], documentation [17], API [18]). [16] http://projects.haskell.org/diagrams/doc/arrow.html [17] http://projects.haskell.org/diagrams/doc/manual.html#arrows [18] http://projects.haskell.org/diagrams/haddock/Diagrams-TwoD-Arrow.html - A new framework for creating custom command-line-driven executables for diagram generation (tutorial [19], API [20]). [19] http://projects.haskell.org/diagrams/doc/cmdline.html [20] http://projects.haskell.org/diagrams/haddock/Diagrams-Backend-CmdLine.html - Offsets of trails and paths, i.e. compute the trail or path lying a constant distance from the given one (documentation [21], API [22]). [21] http://projects.haskell.org/diagrams/doc/manual.html#offsets-of-segments-trails-and-paths [22] http://projects.haskell.org/diagrams/haddock/Diagrams-TwoD-Offset.html - A new API, based on Metafont, for constructing cubic splines with control over things like tangents and "tension" (tutorial [23], API [24]). [23] http://projects.haskell.org/diagrams/doc/metafont.html [24] http://projects.haskell.org/diagrams/haddock/Diagrams-TwoD-Path-Metafont.html - Tangent and normal vectors of segments and trails (API [25]). [25] http://projects.haskell.org/diagrams/haddock/Diagrams-Tangent.html - Alignment can now be done by trace in addition to envelope (API [26]). [26] http://projects.haskell.org/diagrams/haddock/Diagrams-TwoD-Align.html - The lens [27] package is now used consistently for record fields throughout the library (documentation [28]). [27] http://hackage.haskell.org/package/lens [28] http://projects.haskell.org/diagrams/doc/manual.html#faking-optional-named-arguments - Across-the-board improvements in performance and size of generated files. See the release notes [29] for full details, and the migration guide [30] for help porting your diagrams 0.7 code to work with diagrams 1.0. [29] http://projects.haskell.org/diagrams/releases.html [30] http://www.haskell.org/haskellwiki/Diagrams/Dev/Migrate1.0 Try it out ---------- For the truly impatient: cabal install diagrams Diagrams is supported under GHC 7.4 and 7.6. To get started, read the quick start tutorial [31], which will introduce you to the fundamentals of the framework and provide links for further reading. For those who are less impatient and want to really dig in and use the power features, read the extensive user manual [32]. There is also a growing collection of tutorials [33] on specific topics. [31] http://projects.haskell.org/diagrams/doc/quickstart.html [32] http://projects.haskell.org/diagrams/doc/manual.html [33] http://projects.haskell.org/diagrams/documentation.html Get involved ------------ Diagrams has a friendly and growing community of users and developers. To connect with the community, subscribe to the project mailing list [34], and/or come hang out in the #diagrams IRC channel on freenode.org for help and discussion. Development continues stronger than ever, and there are a wide range of projects available for new contributors of all levels of Haskell skill. Make some diagrams. Fix some bugs [35]. Submit your cool examples for inclusion in the gallery [36] or your cool code for inclusion in the diagrams-contrib [37] package. [34] http://groups.google.com/group/diagrams-discuss [35] http://github.com/diagrams/ [36] http://projects.haskell.org/diagrams/gallery.html [37] http://hackage.haskell.org/package/diagrams%2Dcontrib Happy diagramming! Brought to you by the diagrams team: - Daniel Bergey - Jeff Rosenbluth - Ryan Yates - Brent Yorgey with contributions from: - Jan Bracker - Conal Elliott - Daniil Frumin - Sam Griffin - Niklas Haas - Peter Hall - Claude Heiland-Allen - Deepak Jois - John Lato - Felipe Lessa - Chris Mears - Ian Ross - Carlos Scheidegger - Vilhelm Sj?berg - Michael Sloan - Jim Snavely - Luite Stegeman - Kanchalai Suveepattananont - Michael Thompson - Scott Walck From corentin.dupont at gmail.com Sat Jan 18 02:03:12 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sat, 18 Jan 2014 03:03:12 +0100 Subject: [Haskell-cafe] Open researcher position at Create-Net Italy Message-ID: Dear Haskell-cafe, CREATE-NET, a research center located in Trento, Italy, is hiring one researcher on distributed system management. The responsibility of the candidate will be to contribute to the research topic of Energy Efficiency in the Cloud with particular focus on making cloud-running applications energy-aware. The techniques used will include Constraint Programming and Functional Programming to some extent. We offer competitive compensation and a stimulating work environment in the research and innovation sector. The scenic landscape of Italian Alps doesn't hurt either. If you are interested, please submit your application to careers at create-net.org (with me in copy). Details on the open position and ideal profile may be found on http://www.create-net.org/it/node/3197 Don't hesitate to contact me for more details! Cheers, Corentin Dupont CREATE-NET www.create-net.org www.corentindupont.info -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Sat Jan 18 08:57:39 2014 From: vogt.adam at gmail.com (adam vogt) Date: Sat, 18 Jan 2014 03:57:39 -0500 Subject: [Haskell-cafe] Automatic differentiation and dimension types In-Reply-To: References: Message-ID: Hi Douglas, Looks like it's pretty straightforward to use the "dimensional" and "ad" packages together: {-# LANGUAGE RankNTypes #-} import qualified Numeric.AD as AD import qualified Numeric.AD.Types as AD import Numeric.Units.Dimensional.Prelude import Numeric.Units.Dimensional import qualified Prelude as P diff :: (Div y x y', Num a) => (forall s. AD.Mode s => Dimensional v x (AD.AD s a) -> Dimensional v y (AD.AD s a)) -> Dimensional v x a -> Dimensional v y' a diff f z = Dimensional $ AD.diff (unD . f . Dimensional) (unD z) unD (Dimensional a) = a -- a dumb example ke velocity = velocity*velocity*(1*~kilo gram) main = print $ diff ke (3 *~ (metre/second)) -- prints 6.0 m kg s^-1 It might be nice to have a package that wraps up the rest of the functionality in "ad" (gradients, the different modes etc.). I'm not sure there are convenient vectors/matrices that can have each element with a different type (units). Regards, Adam On Fri, Jan 17, 2014 at 4:23 PM, Douglas McClean wrote: > Has anyone explored the intersection between automatic differentiation and > dimension types (like those in the dimensional package or along the lines of > any of the approaches discussed at > http://www.haskell.org/haskellwiki/Physical_units)? > > It's tricky because for ordinary automatic differentiation the types are all > the same, but when dimensions get involved that isn't the case, you have to > keep dividing by the dimension of the infinitesimal. > > -Doug McClean > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From malikov.d.y at gmail.com Sat Jan 18 11:11:51 2014 From: malikov.d.y at gmail.com (Dmitry Malikov) Date: Sat, 18 Jan 2014 15:11:51 +0400 Subject: [Haskell-cafe] Building ghc-7.6.3 under cygwin Message-ID: Trying to build 7.6.3-x86_64-unknown-linux under cygwin. $ ./configure checking for path to top of build tree... ./configure: line 2121: utils/ghc-pwd/dist-install/build/tmp/ghc-pwd: cannot execute binary file configure: error: cannot determine current directory Not sure it is a libgmp issue, because linking doesn't help: $ ln -s /usr/lib/libgmp.dll.a /usr/lib/libgmp.so.3 Any ideas what is going on and how to fix this? -------------- next part -------------- An HTML attachment was scrubbed... URL: From schlepptop at henning-thielemann.de Sat Jan 18 12:52:21 2014 From: schlepptop at henning-thielemann.de (Henning Thielemann) Date: Sat, 18 Jan 2014 13:52:21 +0100 Subject: [Haskell-cafe] [Haskell] ANNOUNCE: Diagrams 1.0 In-Reply-To: <52DA72C2.60904@henning-thielemann.de> References: <20140117215719.GA21107@seas.upenn.edu> <52DA72C2.60904@henning-thielemann.de> Message-ID: <52DA7905.6090305@henning-thielemann.de> Am 18.01.2014 13:25, schrieb Henning Thielemann: > When compiling I get: > > src/Diagrams/TwoD/Layout/Tree.hs:448:26: > No instance for (Default (ForceLayoutOpts R2)) > arising from a use of `def' > Possible fix: > add an instance declaration for (Default (ForceLayoutOpts R2)) > In the `_forceLayoutOpts' field of a record > In the expression: > FLTOpts > {_forceLayoutOpts = def, _edgeLen = sqrt 2, _springK = 0.05, > _staticK = 0.1} > In an equation for `def': > def > = FLTOpts > {_forceLayoutOpts = def, _edgeLen = sqrt 2, _springK = 0.05, > _staticK = 0.1} I guess this problem is best fixed by staying away from data-default, at all. I can't believe it is sensible to assign default values to arbitrary types. From mithrandi at mithrandi.net Sat Jan 18 15:18:20 2014 From: mithrandi at mithrandi.net (Tristan Seligmann) Date: Sat, 18 Jan 2014 17:18:20 +0200 Subject: [Haskell-cafe] Standard implementation of asynchronous helpers? Message-ID: I was wondering if a standard implementation of these helpers (or something similar) existed somewhere: startAsync :: IO a -> IO (MVar a) startAsync action = do var <- newEmptyMVar forkIO $ action >>= putMVar var return var wait :: MVar a -> IO a wait = readMVar I've found a few throwaway examples that implement something similar, and I can imagine some improvements already (I guess the MVar should be wrapped, for example, and some higher) but I was unable to find any released library that does something like this. Is it just too trivial for anyone to have bothered? -- mithrandi, i Ainil en-Balandor, a faer Ambar From mail at nh2.me Sat Jan 18 15:26:51 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Sat, 18 Jan 2014 15:26:51 +0000 Subject: [Haskell-cafe] Standard implementation of asynchronous helpers? In-Reply-To: References: Message-ID: <52DA9D3B.3050408@nh2.me> E.g. https://hackage.haskell.org/package/async ? On Sat 18 Jan 2014 15:18:20 GMT, Tristan Seligmann wrote: > I was wondering if a standard implementation of these helpers (or > something similar) existed somewhere: > > startAsync :: IO a -> IO (MVar a) > startAsync action = do > var <- newEmptyMVar > forkIO $ action >>= putMVar var > return var > > wait :: MVar a -> IO a > wait = readMVar > > I've found a few throwaway examples that implement something similar, > and I can imagine some improvements already (I guess the MVar should > be wrapped, for example, and some higher) but I was unable to find any > released library that does something like this. > > Is it just too trivial for anyone to have bothered? From mithrandi at mithrandi.net Sat Jan 18 15:32:19 2014 From: mithrandi at mithrandi.net (Tristan Seligmann) Date: Sat, 18 Jan 2014 17:32:19 +0200 Subject: [Haskell-cafe] Standard implementation of asynchronous helpers? In-Reply-To: <52DA9D3B.3050408@nh2.me> References: <52DA9D3B.3050408@nh2.me> Message-ID: On Sat, Jan 18, 2014 at 5:26 PM, Niklas Hamb?chen wrote: > E.g. https://hackage.haskell.org/package/async ? Uh, yes, that seems to be exactly what I was looking for! It's even named the obvious thing, I have no idea why I didn't find it when I was searching. -- mithrandi, i Ainil en-Balandor, a faer Ambar From schlepptop at henning-thielemann.de Sat Jan 18 17:30:29 2014 From: schlepptop at henning-thielemann.de (Henning Thielemann) Date: Sat, 18 Jan 2014 18:30:29 +0100 Subject: [Haskell-cafe] [Haskell] Just started working with Haskell. Need some help In-Reply-To: <8D0E2897644541B-1058-8B6C@webmail-d276.sysops.aol.com> References: <8D0E2897644541B-1058-8B6C@webmail-d276.sysops.aol.com> Message-ID: <52DABA35.9020100@henning-thielemann.de> moving to Haskell-Cafe ... Am 18.01.2014 18:25, schrieb Pyro Crane: > But, when I try to run a simple script, I keep getting the error : > "*Could not find module XXXXXX*".............. What precisely did you try? > And, now, I've come up against a module/package, which I am unable to > locate in Google. It's missing from my installation, and Google does > not know what it is, or where I can find it > > Is there any way to simply install ALL required packages??? I thought > I already did this, but obviously I missed something $ cabal install wantedpkg should install all dependencies of 'wantedpkg'. If it does not I am interested in how you tried to install 'wantedpkg'. From the.dead.shall.rise at gmail.com Sat Jan 18 19:20:23 2014 From: the.dead.shall.rise at gmail.com (Mikhail Glushenkov) Date: Sat, 18 Jan 2014 20:20:23 +0100 Subject: [Haskell-cafe] Building ghc-7.6.3 under cygwin In-Reply-To: References: Message-ID: Hi, On Sat, Jan 18, 2014 at 12:11 PM, Dmitry Malikov wrote: > Trying to build 7.6.3-x86_64-unknown-linux under cygwin. IIUC, building GHC under Cygwin is not really supported. -- () ascii ribbon campaign - against html e-mail /\ www.asciiribbon.org - against proprietary attachments From difrumin at gmail.com Sat Jan 18 20:10:47 2014 From: difrumin at gmail.com (Dan Frumin) Date: Sun, 19 Jan 2014 00:10:47 +0400 Subject: [Haskell-cafe] Standard implementation of asynchronous helpers? In-Reply-To: References: <52DA9D3B.3050408@nh2.me> Message-ID: Yeah it's a nice package, it got some good coverage in Simon's book about concurrency in Haskell > On 18 Jan 2014, at 19:32, Tristan Seligmann wrote: > >> On Sat, Jan 18, 2014 at 5:26 PM, Niklas Hamb?chen wrote: >> E.g. https://hackage.haskell.org/package/async ? > > Uh, yes, that seems to be exactly what I was looking for! It's even > named the obvious thing, I have no idea why I didn't find it when I > was searching. > -- > mithrandi, i Ainil en-Balandor, a faer Ambar > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From jmitdase at gmail.com Sat Jan 18 20:17:13 2014 From: jmitdase at gmail.com (Joey Eremondi) Date: Sat, 18 Jan 2014 12:17:13 -0800 (PST) Subject: [Haskell-cafe] Help with Binary Serialization Message-ID: <19536a0f-e74f-4d00-8adb-7b7507320eb4@googlegroups.com> I was wondering if somebody could talk me through the default derived format for binary serialization used, either by binary or by cereal. I'm trying to share data between Haskell and another function language (Elm) which also supports algebraic data types, so the conversion of data should be pretty trivial. I'd like to be able to just derive encode and decode in Haskell using either binary/cereal, and then write a parser for the same format in Elm. The trick is, I don't know what that format is. Is there any documentation on it, or if not, is anybody familiar enough with it that they could explain the format to me? Thanks! -------------- next part -------------- An HTML attachment was scrubbed... URL: From schlepptop at henning-thielemann.de Sat Jan 18 12:25:38 2014 From: schlepptop at henning-thielemann.de (Henning Thielemann) Date: Sat, 18 Jan 2014 13:25:38 +0100 Subject: [Haskell-cafe] [Haskell] ANNOUNCE: Diagrams 1.0 In-Reply-To: <20140117215719.GA21107@seas.upenn.edu> References: <20140117215719.GA21107@seas.upenn.edu> Message-ID: <52DA72C2.60904@henning-thielemann.de> Am 17.01.2014 22:57, schrieb Brent Yorgey: > The diagrams team is very pleased to announce the 1.0 release of > diagrams [1], a framework and embedded domain-specific language for > declarative drawing in Haskell. When compiling I get: src/Diagrams/TwoD/Layout/Tree.hs:448:26: No instance for (Default (ForceLayoutOpts R2)) arising from a use of `def' Possible fix: add an instance declaration for (Default (ForceLayoutOpts R2)) In the `_forceLayoutOpts' field of a record In the expression: FLTOpts {_forceLayoutOpts = def, _edgeLen = sqrt 2, _springK = 0.05, _staticK = 0.1} In an equation for `def': def = FLTOpts {_forceLayoutOpts = def, _edgeLen = sqrt 2, _springK = 0.05, _staticK = 0.1} From qdunkan at gmail.com Sun Jan 19 00:14:26 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Sat, 18 Jan 2014 16:14:26 -0800 Subject: [Haskell-cafe] evaluating CAFs at compile time Message-ID: So I have a large CAF which is expensive to generate. Theoretically it should be possible to totally evaluate at compile time, resulting in a bunch of constructor calls, ideally totally de-thunked and in the read-only segment of the binary. In the absence of a "eval at compile time" pragma, it seemed like TH should be able to do this, and searching haskell-cafe I turned up an old post by Wren where he is doing basically that, and eventually discovered the Lift class in http://hackage.haskell.org/package/template-haskell-2.8.0.0/docs/Language-Haskell-TH-Syntax.html However, if I understand Lift correctly (and not really understanding much of TH), you need to create instances for every type you wish to generate, which seems like it would be a pain. Even if they can be automatically derived, it would spread TH dependency gunk throughout the whole program. Is this true? Is there a library that does the equivalent of a "eval at compile time" pragma? (Wren's proposed QAF library seems to have never made it to hackage, but maybe given Lift and the proper instances it turns out to be trivial.) Would it be possible or desirable for an actual pragma that wouldn't introduce a TH dependency? Also, I assume it would produce a giant set of constructor applications which ghc would then optimize as well as it can... but it seems like that might not include full strictness, since even 'x = (4, undefined)' is obliged to not diverge as long as you don't look at the snd field, so even a large literal expression is actually unevaluated code if there are some non-strict data types in there. And... is it actually possible for ghc to do clever optimization with constant values, i.e. lay them out fully evaluated in read-only memory? I know that something like 'x = "abc" ++ "def"' will wind up as 'unpackCString# "abcdef"', but I'm curious what happens to more complicated data structures. Strictness seems to make a difference, e.g. with nonstrict fields the core has separate bindings for the contained values, while with strict ones the values get inlined directly into the consumer of the data type and the constructor is nowhere to be seen. But if the type is recursive (data X = X Int (Maybe X)), then we wind up with CAFs applying it, though they have lots of provocative flags that indicate ghc knows it's dealing with constructors: Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, ConLike=True, WorkFree=False, Expandable=True, Guidance=IF_ARGS [] 10 30}] I assume it still can't hoist the undefined to the entire expression though, because of non-strictness. I would think that if all data types are strict, then it could transform 'caf = X 42 (StrictJust (X 24 undefined))' to 'caf = undefined', but that doesn't seem to happen either. Tangentially, I've noticed that the 'unpackCString# "abcdef"' optimization is limited to String, replacing it with Text produces "abc" + giant wodge of code that is presumably appending "def" at runtime. I'm sure I've seen some discussions around here about wanting to optimize string literals to 'Text 0 len (giant chunk of binary data)', but I don't think they talked about possible compile time evaluation... presumably it could also solve that problem? From carter.schonwald at gmail.com Sun Jan 19 00:25:25 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 18 Jan 2014 19:25:25 -0500 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: evan, could you share a minimal example of the code that illustrates your problem? It may be that theres a) an alternative way to write it that that gives the perf characteristics you want b) it could be a good example for future ghc optimization efforts c) other -Carter On Sat, Jan 18, 2014 at 7:14 PM, Evan Laforge wrote: > So I have a large CAF which is expensive to generate. Theoretically > it should be possible to totally evaluate at compile time, resulting > in a bunch of constructor calls, ideally totally de-thunked and in the > read-only segment of the binary. > > In the absence of a "eval at compile time" pragma, it seemed like TH > should be able to do this, and searching haskell-cafe I turned up an > old post by Wren where he is doing basically that, and eventually > discovered the Lift class in > > http://hackage.haskell.org/package/template-haskell-2.8.0.0/docs/Language-Haskell-TH-Syntax.html > > However, if I understand Lift correctly (and not really understanding > much of TH), you need to create instances for every type you wish to > generate, which seems like it would be a pain. Even if they can be > automatically derived, it would spread TH dependency gunk throughout > the whole program. Is this true? Is there a library that does the > equivalent of a "eval at compile time" pragma? (Wren's proposed QAF > library seems to have never made it to hackage, but maybe given Lift > and the proper instances it turns out to be trivial.) Would it be > possible or desirable for an actual pragma that wouldn't introduce a > TH dependency? > > Also, I assume it would produce a giant set of constructor > applications which ghc would then optimize as well as it can... but > it seems like that might not include full strictness, since even 'x = > (4, undefined)' is obliged to not diverge as long as you don't look at > the snd field, so even a large literal expression is actually > unevaluated code if there are some non-strict data types in there. > > And... is it actually possible for ghc to do clever optimization with > constant values, i.e. lay them out fully evaluated in read-only > memory? I know that something like 'x = "abc" ++ "def"' will wind up > as 'unpackCString# "abcdef"', but I'm curious what happens to more > complicated data structures. Strictness seems to make a difference, > e.g. with nonstrict fields the core has separate bindings for the > contained values, while with strict ones the values get inlined > directly into the consumer of the data type and the constructor is > nowhere to be seen. But if the type is recursive (data X = X Int > (Maybe X)), then we wind up with CAFs applying it, though they have > lots of provocative flags that indicate ghc knows it's dealing with > constructors: > > Unf=Unf{Src=, TopLvl=True, Arity=0, Value=True, > ConLike=True, WorkFree=False, Expandable=True, > Guidance=IF_ARGS [] 10 30}] > > I assume it still can't hoist the undefined to the entire expression > though, because of non-strictness. I would think that if all data > types are strict, then it could transform 'caf = X 42 (StrictJust (X > 24 undefined))' to 'caf = undefined', but that doesn't seem to happen > either. > > Tangentially, I've noticed that the 'unpackCString# "abcdef"' > optimization is limited to String, replacing it with Text produces > "abc" + giant wodge of code that is presumably appending "def" at > runtime. I'm sure I've seen some discussions around here about > wanting to optimize string literals to 'Text 0 len (giant chunk of > binary data)', but I don't think they talked about possible compile > time evaluation... presumably it could also solve that problem? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Sun Jan 19 00:56:55 2014 From: vogt.adam at gmail.com (adam vogt) Date: Sat, 18 Jan 2014 19:56:55 -0500 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: On Sat, Jan 18, 2014 at 7:14 PM, Evan Laforge wrote: > However, if I understand Lift correctly (and not really understanding > much of TH), you need to create instances for every type you wish to > generate, which seems like it would be a pain. Even if they can be > automatically derived, it would spread TH dependency gunk throughout > the whole program. Is this true? Is there a library that does the > equivalent of a "eval at compile time" pragma? (Wren's proposed QAF > library seems to have never made it to hackage, but maybe given Lift > and the proper instances it turns out to be trivial.) Would it be > possible or desirable for an actual pragma that wouldn't introduce a > TH dependency? Hi Evan, Check out . Also, there is a of zeroTH here https://github.com/mgsloan/zeroth which works with a haskell-src-exts < 1.14. I'm not sure what benefit you'd get from a new mechanism (beside TH) to calculate things at compile-time. Won't it have to solve the same problems which are solved by TH already? How can those problems (generating haskell code, stage restriction) be solved without ending up with the same kind of complexity ("TH dependency gunk")? Regards, Adam From qdunkan at gmail.com Sun Jan 19 00:56:57 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Sat, 18 Jan 2014 16:56:57 -0800 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: On Sat, Jan 18, 2014 at 4:25 PM, Carter Schonwald wrote: > evan, could you share a minimal example of the code that illustrates your > problem? It may be that theres > a) an alternative way to write it that that gives the perf characteristics > you want > b) it could be a good example for future ghc optimization efforts > c) other Sure. As you might guess, there are lots of dependencies, but you don't have to care about them. A Patch has a bunch of fields, but the key part is Score.Attributes, which is a newtype over Set Text. All the attrs_* functions are just the obvious wrappers around set operations. 'strip_attr' tries to remove redundant attributes, but can only do so if that doesn't cause it to collide with an existing attribute set (which means it wasn't redundant after all). You'll notice it's naively implemented, since it does a linear search through all the other attributes. Given 41 instruments, 12 attrs to strip, and a typical instrument having 285 attrs, that winds up being something like 41 * 12 * 285^2, and takes about 0.39 CPU seconds to force with NFData. I appended a less naive version that replaces the linear search with a Set and it's faster (0.19, presumably ^2 becomes (* log 285)), but is uglier. So I did find an alternative way, but it's still fairly expensive, and it would be nice to be able to write the slow but pretty version and pay the cost at compile time. All the attributes data is coming from another module which is basically 1855 lines of CAFs. I could apply the attribute stripping by hand to that, but it would be error-prone and ugly and lots of work... that's the machine's job! patches :: [MidiInst.Patch] patches = [add_code hmap (make_patch inst category) | ((inst, hmap), category) <- instruments] where add_code hmap patch = (patch, code) where code = MidiInst.note_calls (note_calls hmap patch) make_patch :: VslInst.Instrument -> Text -> Instrument.Patch make_patch inst category = instrument_patch category (second strip (make_instrument inst)) where strip = uncurry zip . first strip_attrs . unzip strip_attrs :: [Score.Attributes] -> [Score.Attributes] strip_attrs attrs = foldr strip_attr attrs strip where strip = reverse [ VslInst.sus, VslInst.vib, VslInst.perf, VslInst.fast, VslInst.fa , VslInst.norm, VslInst.na, VslInst.legato, VslInst.v1, VslInst.art , VslInst.med, VslInst.short ] -- | Strip the given attr, but only if it wouldn't cause clashes. strip_attr :: Score.Attributes -> [Score.Attributes] -> [Score.Attributes] strip_attr attr all_attrs = map (strip_redundant attr) all_attrs where strip_redundant attr attrs | stripped `elem` all_attrs = attrs | otherwise = stripped where stripped = Score.attrs_diff attrs attr -- optimized version, applied via mapAccumL to thread the Set through each call: strip_attr :: Score.Attributes -> (Set.Set Score.Attributes, [Score.Attributes]) -> (Set.Set Score.Attributes, [Score.Attributes]) strip_attr attr (all_attrs_set, all_attrs) | any (`Score.attrs_contain` attr) all_attrs = List.mapAccumL strip_redundant all_attrs_set all_attrs | otherwise = (all_attrs_set, all_attrs) where strip_redundant attrs_set attrs | Set.member stripped attrs_set = (attrs_set, attrs) | otherwise = (Set.insert stripped attrs_set, stripped) where stripped = Score.attrs_diff attrs attr From winterkoninkje at gmail.com Sun Jan 19 01:01:36 2014 From: winterkoninkje at gmail.com (wren ng thornton) Date: Sat, 18 Jan 2014 20:01:36 -0500 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: On Sat, Jan 18, 2014 at 7:14 PM, Evan Laforge wrote: > (Wren's proposed QAF > library seems to have never made it to hackage, but maybe given Lift > and the proper instances it turns out to be trivial.) Yep, the Lift class does essentially the same thing, which is why I never published QAF -- Live well, ~wren From qdunkan at gmail.com Sun Jan 19 01:08:23 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Sat, 18 Jan 2014 17:08:23 -0800 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: On Sat, Jan 18, 2014 at 4:56 PM, adam vogt wrote: > Check out . Also, there > is a of zeroTH here https://github.com/mgsloan/zeroth which works with > a haskell-src-exts < 1.14. Thanks, I'll take a look. Though since I have my faster-but-uglier solution, at this point I'm mostly only theoretically interested, and hoping to learn something about compilers and optimization :) > I'm not sure what benefit you'd get from a new mechanism (beside TH) > to calculate things at compile-time. Won't it have to solve the same > problems which are solved by TH already? How can those problems > (generating haskell code, stage restriction) be solved without ending > up with the same kind of complexity ("TH dependency gunk")? Well, TH is much more powerful in that it can generate any expression at compile time. But in exchange, it slows down compilation a lot, introduces an order dependency in the source file, and causes complications for the build system (I don't remember exactly, but it came down to needing to find the .o files at compile time). I would think, in the handwaviest kind of way, that the compiler could compile a CAF, and then just evaluate it on the spot by just following all the code thunk pointers (similar to a deepseq), and then emit the raw data structure that comes out. Of course that assumes that there is a such thing as "raw" data, which is why I got all side tracked wondering about compile time optimization in general. I expect it's not like C where you would wind up with a nested bunch of structs you could just write directly to the .TEXT section of the binary and then mmap into place when the binary is run. Even in C you'd need to go fix up pointers. At which point it sounds like a dynamic loader :) From carter.schonwald at gmail.com Sun Jan 19 02:50:42 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 18 Jan 2014 21:50:42 -0500 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: You ask for something that ghc doesnt have yet, but perhaps could have at some point. (If I'm reading you right). Currently ghc doesn't have a way of doing what you want! Eg, I don't think there's even really support as yet for that sort of notion in the context of just boxed/unboxed/storable arrays. There's definitely a few example pieces of code here it'd be nice to express a read only lookup array that's fixed before run time for various bit fiddling etc algs. On Saturday, January 18, 2014, Evan Laforge wrote: > On Sat, Jan 18, 2014 at 4:56 PM, adam vogt > > wrote: > > Check out . Also, there > > is a of zeroTH here https://github.com/mgsloan/zeroth which works with > > a haskell-src-exts < 1.14. > > Thanks, I'll take a look. Though since I have my faster-but-uglier > solution, at this point I'm mostly only theoretically interested, and > hoping to learn something about compilers and optimization :) > > > I'm not sure what benefit you'd get from a new mechanism (beside TH) > > to calculate things at compile-time. Won't it have to solve the same > > problems which are solved by TH already? How can those problems > > (generating haskell code, stage restriction) be solved without ending > > up with the same kind of complexity ("TH dependency gunk")? > > Well, TH is much more powerful in that it can generate any expression > at compile time. But in exchange, it slows down compilation a lot, > introduces an order dependency in the source file, and causes > complications for the build system (I don't remember exactly, but it > came down to needing to find the .o files at compile time). I would > think, in the handwaviest kind of way, that the compiler could compile > a CAF, and then just evaluate it on the spot by just following all the > code thunk pointers (similar to a deepseq), and then emit the raw data > structure that comes out. Of course that assumes that there is a such > thing as "raw" data, which is why I got all side tracked wondering > about compile time optimization in general. I expect it's not like C > where you would wind up with a nested bunch of structs you could just > write directly to the .TEXT section of the binary and then mmap into > place when the binary is run. Even in C you'd need to go fix up > pointers. At which point it sounds like a dynamic loader :) > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jan 19 02:57:22 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 18 Jan 2014 21:57:22 -0500 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: Point being, I think your pointing to an idea other people are (also) interested in exploring for ghc, and that there's some interesting subltelties to it. On Saturday, January 18, 2014, Carter Schonwald wrote: > You ask for something that ghc doesnt have yet, but perhaps could have at > some point. (If I'm reading you right). Currently ghc doesn't have a way > of doing what you want! Eg, I don't think there's even really support as > yet for that sort of notion in the context of just boxed/unboxed/storable > arrays. > > There's definitely a few example pieces of code here it'd be nice to > express a read only lookup array that's fixed before run time for various > bit fiddling etc algs. > > On Saturday, January 18, 2014, Evan Laforge > > wrote: > >> On Sat, Jan 18, 2014 at 4:56 PM, adam vogt wrote: >> > Check out . Also, there >> > is a of zeroTH here https://github.com/mgsloan/zeroth which works with >> > a haskell-src-exts < 1.14. >> >> Thanks, I'll take a look. Though since I have my faster-but-uglier >> solution, at this point I'm mostly only theoretically interested, and >> hoping to learn something about compilers and optimization :) >> >> > I'm not sure what benefit you'd get from a new mechanism (beside TH) >> > to calculate things at compile-time. Won't it have to solve the same >> > problems which are solved by TH already? How can those problems >> > (generating haskell code, stage restriction) be solved without ending >> > up with the same kind of complexity ("TH dependency gunk")? >> >> Well, TH is much more powerful in that it can generate any expression >> at compile time. But in exchange, it slows down compilation a lot, >> introduces an order dependency in the source file, and causes >> complications for the build system (I don't remember exactly, but it >> came down to needing to find the .o files at compile time). I would >> think, in the handwaviest kind of way, that the compiler could compile >> a CAF, and then just evaluate it on the spot by just following all the >> code thunk pointers (similar to a deepseq), and then emit the raw data >> structure that comes out. Of course that assumes that there is a such >> thing as "raw" data, which is why I got all side tracked wondering >> about compile time optimization in general. I expect it's not like C >> where you would wind up with a nested bunch of structs you could just >> write directly to the .TEXT section of the binary and then mmap into >> place when the binary is run. Even in C you'd need to go fix up >> pointers. At which point it sounds like a dynamic loader :) >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From konn.jinro at gmail.com Sun Jan 19 05:30:37 2014 From: konn.jinro at gmail.com (Hiromi ISHII) Date: Sun, 19 Jan 2014 14:30:37 +0900 Subject: [Haskell-cafe] ANN: unsafely, Flexible access control for unsafe operations and instances Message-ID: <652F9AB3-178B-4295-92B8-E4057AA56F58@gmail.com> Yesterday, I uploaded the library `unsafely` to Hackage: http://hackage.haskell.org/package/unsafely This package provides you the functionality for access control for unsafe operations and instances. This purpose is somewhat similar to GHC's `NullaryTypeClasses`[^1] extension, but permits more flexible access control. With this package, you can tag functions and type-class instances as *unsafe* in type constraint. This library is useful when: * You want to restrict the access to *unsafe* operations by type constraint * You have to provide some *unsafe* type-instances for practical reasons. For example, when writing computer algebra system with type-classes, `Double` type doesn't even form a semi ring, but we need the instance `Semiring Double` if we want to combine the symbolic computations and the numerical methods. A simple example: ```haskell {-# LANGUAGE FlexibleContexts, FlexibleInstances, RankNTypes #-} {-# LANGUAGE UndecidableInstances #-} module Main where import Data.Constraint.Unsafely import Data.IORef import Data.Proxy import System.IO.Unsafe saferUnsafePerformIO :: Unsafely IO => IO a -> a saferUnsafePerformIO = unsafePerformIO global :: Unsafely IO => IORef Int global = saferUnsafePerformIO $ newIORef 0 unsafelyIO :: (Unsafely IO => a) -> a unsafelyIO = unsafely (Proxy :: Proxy IO) main :: IO () main = do unsafelyIO $ readIORef global -- | uncommenting following line causes type-error! -- readIORef global return () ``` For more detail, please read Haddock[^2]. [^1]: https://ghc.haskell.org/trac/ghc/ticket/7642 [^2]: http://hackage.haskell.org/package/unsafely-0.1.0.0.1/docs/Data-Constraint-Unsafely.html -- Hiromi ISHII konn.jinro at gmail.com From corentin.dupont at gmail.com Sun Jan 19 22:22:33 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sun, 19 Jan 2014 23:22:33 +0100 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: Hi, I've tried the make an instance of NFData for all types, although I have a problem with the GATD: *data MyGADT a where MyField :: b -> MyGADT (Maybe b)instance NFData a => NFData (MyGADT a) where rnf (MyField b) = (rnf b)* Gives me : Could not deduce (NFData b) arising from a use of `rnf' from the context (NFData a) Which I understand (that's because a ~ *Maybe b *and not* a ~ b *due to the declaration of *MyField b *being of type *MyGADT (Maybe b)*) *But I have no idea how to solve that??* *Thanks...* *Corentin* On Mon, Jan 13, 2014 at 1:10 AM, Brandon Allbery wrote: > On Sun, Jan 12, 2014 at 6:44 PM, Corentin Dupont < > corentin.dupont at gmail.com> wrote: > >> One question: >> Since it works with putStrLn, can I simulate the behaviour of putStrLn >> without actually... printing anything? As a workaround... >> > > Worst case, open a handle on /dev/null and hPutStr to it. > > I'd probably try to figure out how to write appropriate NFData instances, > though. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Jan 19 23:00:57 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 19 Jan 2014 18:00:57 -0500 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: Try *instance NFData a => NFData (MyGADT (Maybe a) )* On Sunday, January 19, 2014, Corentin Dupont wrote: > Hi, > I've tried the make an instance of NFData for all types, although I have a > problem with the GATD: > > > > > > > > *data MyGADT a where MyField :: b -> MyGADT (Maybe b) instance NFData a > => NFData (MyGADT a) where rnf (MyField b) = (rnf b)* > Gives me : > Could not deduce (NFData b) arising from a use of `rnf' > from the context (NFData a) > > Which I understand (that's because a ~ *Maybe b *and not* a ~ b *due to > the declaration of *MyField b *being of type *MyGADT (Maybe b)*) > > *But I have no idea how to solve that?? * > > *Thanks...* > > *Corentin* > > > > On Mon, Jan 13, 2014 at 1:10 AM, Brandon Allbery > > wrote: > >> On Sun, Jan 12, 2014 at 6:44 PM, Corentin Dupont < >> corentin.dupont at gmail.com > 'corentin.dupont at gmail.com');>> wrote: >> >>> One question: >>> Since it works with putStrLn, can I simulate the behaviour of putStrLn >>> without actually... printing anything? As a workaround... >>> >> >> Worst case, open a handle on /dev/null and hPutStr to it. >> >> I'd probably try to figure out how to write appropriate NFData instances, >> though. >> >> -- >> brandon s allbery kf8nh sine nomine >> associates >> allbery.b at gmail.com >> ballbery at sinenomine.net > 'ballbery at sinenomine.net');> >> unix, openafs, kerberos, infrastructure, xmonad >> http://sinenomine.net >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Sun Jan 19 23:16:02 2014 From: bob at redivi.com (Bob Ippolito) Date: Sun, 19 Jan 2014 15:16:02 -0800 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: For that to work, I believe you must enable FlexibleInstances and possibly also OverlappingInstances (depending on what the rest of the GADT looks like). On Sun, Jan 19, 2014 at 3:00 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Try > > *instance NFData a => NFData (MyGADT (Maybe a) )* > > > On Sunday, January 19, 2014, Corentin Dupont > wrote: > >> Hi, >> I've tried the make an instance of NFData for all types, although I have >> a problem with the GATD: >> >> >> >> >> >> >> >> *data MyGADT a where MyField :: b -> MyGADT (Maybe b) instance NFData a >> => NFData (MyGADT a) where rnf (MyField b) = (rnf b)* >> Gives me : >> Could not deduce (NFData b) arising from a use of `rnf' >> from the context (NFData a) >> >> Which I understand (that's because a ~ *Maybe b *and not* a ~ b *due to >> the declaration of *MyField b *being of type *MyGADT (Maybe b)*) >> >> *But I have no idea how to solve that?? * >> >> *Thanks...* >> >> *Corentin* >> >> >> >> On Mon, Jan 13, 2014 at 1:10 AM, Brandon Allbery wrote: >> >>> On Sun, Jan 12, 2014 at 6:44 PM, Corentin Dupont < >>> corentin.dupont at gmail.com> wrote: >>> >>>> One question: >>>> Since it works with putStrLn, can I simulate the behaviour of putStrLn >>>> without actually... printing anything? As a workaround... >>>> >>> >>> Worst case, open a handle on /dev/null and hPutStr to it. >>> >>> I'd probably try to figure out how to write appropriate NFData >>> instances, though. >>> >>> -- >>> brandon s allbery kf8nh sine nomine >>> associates >>> allbery.b at gmail.com >>> ballbery at sinenomine.net >>> unix, openafs, kerberos, infrastructure, xmonad >>> http://sinenomine.net >>> >> >> > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From chrisdone at gmail.com Mon Jan 20 11:41:45 2014 From: chrisdone at gmail.com (Christopher Done) Date: Mon, 20 Jan 2014 12:41:45 +0100 Subject: [Haskell-cafe] Combining databases from packages installed with cabal install In-Reply-To: References: Message-ID: This is awesome, thanks for sharing. Related issue: https://github.com/haskell/cabal/issues/395 I added --force-reinstalls --reinstall and ran time (for i in `ghc-pkg list | sed 's/ //' | grep '^[^(]' | grep -v ':'`; do hoogle-install $i; done) To generate hoogle entries for all my installed packages. On 21 August 2012 17:55, Marco T?lio Pimenta Gontijo wrote: > Hi. > > I'm configuring haddock via cabal install (see [0]) to build the > hoogle database. The database is being installed in > ~/.cabal/share/doc/$package-$version/html/$package.txt, but is not > being combined with the default database. That is, if right after the > installation I try to search with the hoogle command for some a > function, it will not work. I wrote the following script, which I > called cabal-install: > > #!/bin/sh > > set -e > set -x > > cabal \ > install \ > --enable-documentation \ > --enable-library-profiling \ > --haddock-hyperlink-source \ > --haddock-hoogle \ > --haddock-html \ > "$@" > > cd ~/.cabal/share/hoogle-4.2.13/databases/ > for file in ~/.cabal/share/doc/*/html/*.txt > do > hoo=`echo $file | sed 's/.txt$/.hoo/;s#.*/##'` > if [ ! -f $hoo ] > then > hoogle convert $file $hoo || true > hoogle combine default.hoo $hoo -o /tmp/cabal-install-$$.hoo > mv /tmp/cabal-install-$$.hoo default.hoo > fi > done > > Basically, it searches for .txt hoogle databases installed that were not > combined yet with the default database, and combines them. I think it > would be > good if this was the default behaviour of cabal install when called with > --haddock-hoogle. Is this a bug? > > Greetings. > > 0: http://hackage.haskell.org/trac/hackage/ticket/517 > > -- > marcot > http://marcot.eti.br/ > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Mon Jan 20 11:48:31 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Mon, 20 Jan 2014 12:48:31 +0100 Subject: [Haskell-cafe] Constraint on data type Message-ID: <52DD0D0F.90408@gmail.com> Hi Cafe, I have these typeclasses defined: class UA a where ... class RA a where ... and this data definition data (UA u, RA r) => AD u r = AD { ... } I have another data definition data ACT aur c = ACT { x :: aur, ... } but the type 'aur' should be restricted to (AD u r) only. (I would like to keep 'aur' as 1 parameter, not as data ACT u r c = ACT { x :: AD u r, ... } ) How can such constraint be defined? Best regards, vlatko From 0slemi0 at gmail.com Mon Jan 20 11:50:14 2014 From: 0slemi0 at gmail.com (Andras Slemmer) Date: Mon, 20 Jan 2014 11:50:14 +0000 Subject: [Haskell-cafe] different behaviours with or without putStrLn In-Reply-To: References: Message-ID: Off the top of my head i can think of two non-overlapping solution, both are ugly but maybe someone has an idea to make one nice: The first is to bake the constraint into the GADT: data MyGADT a where MyField :: NFData b => b -> MyGADT (Maybe b) instance NFData (MyGADT a) where rnf (MyField b) = rnf b This is bad because NFData should have nothing to do with the definition of the datastructure The second is to use implication constraints: import Data.Constraint data MyGADT a where MyField :: b -> MyGADT (Maybe b) newtype Constr a = Constr (forall b. (a ~ Maybe b) :- NFData b) class DConstr a where constr :: Constr a instance (NFData a) => DConstr (Maybe a) where constr = Constr (Sub Dict) instance (DConstr a) => NFData (MyGADT a) where rnf (MyField b) = case constr :: Constr a of Constr (Sub Dict) -> rnf b this is ugly because for every non-Maybe index you need to define an "absurd" instance of DConstr. e.g. for Int: instance DConstr Int where constr = Constr undefined -- should be (Constr (Sub !absurd!)) but there is no way to denote absurdity in Haskell On 19 January 2014 23:16, Bob Ippolito wrote: > For that to work, I believe you must enable FlexibleInstances and possibly > also OverlappingInstances (depending on what the rest of the GADT looks > like). > > > On Sun, Jan 19, 2014 at 3:00 PM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> Try >> >> *instance NFData a => NFData (MyGADT (Maybe a) )* >> >> >> On Sunday, January 19, 2014, Corentin Dupont >> wrote: >> >>> Hi, >>> I've tried the make an instance of NFData for all types, although I have >>> a problem with the GATD: >>> >>> >>> >>> >>> >>> >>> >>> *data MyGADT a where MyField :: b -> MyGADT (Maybe b) instance NFData >>> a => NFData (MyGADT a) where rnf (MyField b) = (rnf b)* >>> Gives me : >>> Could not deduce (NFData b) arising from a use of `rnf' >>> from the context (NFData a) >>> >>> Which I understand (that's because a ~ *Maybe b *and not* a ~ b *due to >>> the declaration of *MyField b *being of type *MyGADT (Maybe b)*) >>> >>> *But I have no idea how to solve that?? * >>> >>> *Thanks...* >>> >>> *Corentin* >>> >>> >>> >>> On Mon, Jan 13, 2014 at 1:10 AM, Brandon Allbery wrote: >>> >>>> On Sun, Jan 12, 2014 at 6:44 PM, Corentin Dupont < >>>> corentin.dupont at gmail.com> wrote: >>>> >>>>> One question: >>>>> Since it works with putStrLn, can I simulate the behaviour of putStrLn >>>>> without actually... printing anything? As a workaround... >>>>> >>>> >>>> Worst case, open a handle on /dev/null and hPutStr to it. >>>> >>>> I'd probably try to figure out how to write appropriate NFData >>>> instances, though. >>>> >>>> -- >>>> brandon s allbery kf8nh sine nomine >>>> associates >>>> allbery.b at gmail.com >>>> ballbery at sinenomine.net >>>> unix, openafs, kerberos, infrastructure, xmonad >>>> http://sinenomine.net >>>> >>> >>> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tim at blitzcode.net Mon Jan 20 12:54:40 2014 From: tim at blitzcode.net (Tim C. Schroeder) Date: Mon, 20 Jan 2014 13:54:40 +0100 Subject: [Haskell-cafe] Hacking GHC's Stack for Fun and Profit (featuring The Glorious Haskell Debugger v0.0.1 Pre-alpha) Message-ID: <10C9B4EE-AEBB-4DEC-8755-4242694E80AA@blitzcode.net> Hello, I have developed various profiling and debugging tools in the past, but haven't done any work in that direction for GHC compiled Haskell programs. I thought a good start might be to write a document detailing how the call stack works in GHC, and also write a basic debugger stack trace tool. Here: https://github.com/blitzcode/ghc-stack I hope this is helpful to people trying to pin down crashes, and people interested in working on debugging / profiling tools. I'd also really appreciate if somebody with more GHC / RTS knowledge than me would have a look and see if I got things right. Cheers, Tim From kiwamu at debian.or.jp Mon Jan 20 13:55:36 2014 From: kiwamu at debian.or.jp (Kiwamu Okabe) Date: Mon, 20 Jan 2014 22:55:36 +0900 Subject: [Haskell-cafe] [Help] Trying to rewrite the NetBSD kernel using Haskell language. Message-ID: Hi Haskell hackers, We start trying to rewrite NetBSD kernel using Haskell language. https://github.com/metasepi/netbsd-arafura-s1 But we find some problems. Could you have any ideas for them? ## Status * Trying rewrite AC''97 sound driver using Haskell * Before rewriting. (C language) https://github.com/metasepi/netbsd-arafura-s1/blob/d1b19c686de5573ef8a8342a38b18102476aa1d4/sys/dev/pci/auich.c#L917 * After rewriting. (Haskell language) https://github.com/metasepi/netbsd-arafura-s1/blob/d1b19c686de5573ef8a8342a38b18102476aa1d4/metasepi/sys/hssrc/Dev/Pci/Auich.hs#L7 * Have rewrited 2 functions, auich_open() and auich_close() * Not yet touch Haskell heap ## Problems Some time, C programmer writes following code. ~~~ static int auich_open(void *addr, int flags) { struct auich_softc *sc; sc = (struct auich_softc *)addr; mutex_spin_exit(&sc->sc_intr_lock); sc->codec_if->vtbl->lock(sc->codec_if); ~~~ Note the line "sc->codec_if->vtbl->lock(sc->codec_if);". It traces pointer tree regionally. Haskell's Strorable class is not good for the use case, because it copies the entire pointer tree! We avoid the problem using following messy code. https://github.com/metasepi/netbsd-arafura-s1/blob/d1b19c686de5573ef8a8342a38b18102476aa1d4/metasepi/sys/hssrc/Dev/Pci/Auich.hs#L28 ~~~ auichOpen :: Ptr AuichSoftc -> Int -> IO Int auichOpen sc flags = do mutexp <- p_AuichSoftc_sc_intr_lock sc codeif <- peek =<< p_AuichSoftc_codec_if sc lock <- peek =<< p_Ac97CodecIfVtbl_lock =<< peek =<< p_Ac97CodecIf_vtbl codeif mutexSpinExit mutexp call_Ac97CodecIfVtbl_lock lock codeif -- snip -- p_AuichSoftc_sc_intr_lock :: Ptr AuichSoftc -> IO (Ptr KmutexT) p_AuichSoftc_sc_intr_lock p = return $ plusPtr p offsetOf_AuichSoftc_sc_intr_lock p_AuichSoftc_codec_if :: Ptr AuichSoftc -> IO (Ptr (Ptr Ac97CodecIf)) p_AuichSoftc_codec_if p = return $ plusPtr p offsetOf_AuichSoftc_codec_if p_Ac97CodecIf_vtbl :: Ptr Ac97CodecIf -> IO (Ptr (Ptr Ac97CodecIfVtbl)) p_Ac97CodecIf_vtbl p = return $ plusPtr p offsetOf_Ac97CodecIf_vtbl p_Ac97CodecIfVtbl_lock :: Ptr Ac97CodecIfVtbl -> IO (Ptr (FunPtr Ac97CodecIfVtbl_lock)) p_Ac97CodecIfVtbl_lock p = return $ plusPtr p offsetOf_Ac97CodecIfVtbl_lock ~~~ Haskell world has the answer for it already? Best regards, -- Kiwamu Okabe From donn at avvanta.com Mon Jan 20 16:27:55 2014 From: donn at avvanta.com (Donn Cave) Date: Mon, 20 Jan 2014 08:27:55 -0800 (PST) Subject: [Haskell-cafe] [Help] Trying to rewrite the NetBSD kernel usingHaskell language. In-Reply-To: References: Message-ID: <20140120162755.081CD276C41@mail.avvanta.com> quoth Kiwamu Okabe>, ... > static int > auich_open(void *addr, int flags) > { > struct auich_softc *sc; > > sc = (struct auich_softc *)addr; > mutex_spin_exit(&sc->sc_intr_lock); > sc->codec_if->vtbl->lock(sc->codec_if); > ~~~ > > Note the line "sc->codec_if->vtbl->lock(sc->codec_if);". > It traces pointer tree regionally. > Haskell's Strorable class is not good for the use case, > because it copies the entire pointer tree! That suggests to me that you should change the class, so that its Storable instance doesn't need to dereference the pointers - that is, vtbl for example would be a Ptr type. Though that would not save you very much trouble in the present case. Are you using hsc2hs? Your example has a few things like "plusPtr p offsetOf_Ac97CodecIf_vtbl" - where do you get that offsetOf_? hsc2hs has a #peek macro that does this: p_Ac97CodecIf_vtbl p = (#peek struct ac97codecxzy, vtbl) p -- creates Haskell code p_Ac97CodecIf_vtbl p = ((\ hsc_ptr -> peekByteOff hsc_ptr 96) p Hope that may help a little! Donn From peter at colberg.org Tue Jan 21 01:54:13 2014 From: peter at colberg.org (Peter Colberg) Date: Mon, 20 Jan 2014 20:54:13 -0500 Subject: [Haskell-cafe] MissingH fails to compile Message-ID: <20140121015412.GA17131@pignolo.chem.utoronto.ca> Dear Haskell developers, I am trying to build a current version of git-annex, and stumble over a compilation failure of one of its dependencies, MissingH. I am using GHC 7.4.2 and Cabal 1.18.0.2, both bootstrapped on RHEL 5.x/6.x using a helper makefile [1] that has worked fine so far. The command to install git-annex is cabal install git-annex-5.20140108 --flags=-assistant --flags=-dbus --flags=-webapp --flags=-webdav --flags=-xmpp The build log for MissingH-1.2.0.2 is attached. I would be glad for any pointers on how to resolve this issue. Thanks, Peter [1] http://git.colberg.org/packages/plain/packages.mk -------------- next part -------------- Building MissingH-1.2.0.2... Preprocessing library MissingH-1.2.0.2... [ 1 of 47] Compiling System.Console.GetOpt.Utils ( src/System/Console/GetOpt/Utils.hs, dist/build/System/Console/GetOpt/Utils.o ) [ 2 of 47] Compiling System.Debian ( src/System/Debian.hs, dist/build/System/Debian.o ) src/System/Debian.hs:31:1: Warning: Module `System.Cmd' is deprecated: Use "System.Process" instead [ 3 of 47] Compiling System.IO.WindowsCompat ( src/System/IO/WindowsCompat.hs, dist/build/System/IO/WindowsCompat.o ) [ 4 of 47] Compiling System.Posix.Consts ( src/System/Posix/Consts.hs, dist/build/System/Posix/Consts.o ) [ 5 of 47] Compiling System.IO.StatCompat ( src/System/IO/StatCompat.hs, dist/build/System/IO/StatCompat.o ) [ 6 of 47] Compiling System.IO.PlafCompat ( src/System/IO/PlafCompat.hs, dist/build/System/IO/PlafCompat.o ) [ 7 of 47] Compiling Data.Compression.Inflate ( src/Data/Compression/Inflate.hs, dist/build/Data/Compression/Inflate.o ) [ 8 of 47] Compiling Data.Hash.MD5.Zord64_HARD ( src/Data/Hash/MD5/Zord64_HARD.lhs, dist/build/Data/Hash/MD5/Zord64_HARD.o ) src/Data/Hash/MD5/Zord64_HARD.lhs:17:12: Warning: No explicit method nor default method for `*' In the instance declaration for `Num Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:17:12: Warning: No explicit method nor default method for `abs' In the instance declaration for `Num Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:17:12: Warning: No explicit method nor default method for `signum' In the instance declaration for `Num Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:26:12: Warning: No explicit method nor default method for `xor' In the instance declaration for `Bits Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:26:12: Warning: No explicit method nor default method for `bitSize' In the instance declaration for `Bits Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:26:12: Warning: No explicit method nor default method for `isSigned' In the instance declaration for `Bits Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:43:12: Warning: No explicit method nor default method for `quotRem' In the instance declaration for `Integral Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:46:12: Warning: No explicit method nor default method for `toRational' In the instance declaration for `Real Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:47:12: Warning: No explicit method nor default method for `toEnum' In the instance declaration for `Enum Zord64' src/Data/Hash/MD5/Zord64_HARD.lhs:47:12: Warning: No explicit method nor default method for `fromEnum' In the instance declaration for `Enum Zord64' [ 9 of 47] Compiling Data.Hash.MD5 ( src/Data/Hash/MD5.lhs, dist/build/Data/Hash/MD5.o ) src/Data/Hash/MD5.lhs:114:12: Warning: No explicit method nor default method for `*' In the instance declaration for `Num ABCD' src/Data/Hash/MD5.lhs:114:12: Warning: No explicit method nor default method for `abs' In the instance declaration for `Num ABCD' src/Data/Hash/MD5.lhs:114:12: Warning: No explicit method nor default method for `signum' In the instance declaration for `Num ABCD' src/Data/Hash/MD5.lhs:114:12: Warning: No explicit method nor default method for `fromInteger' In the instance declaration for `Num ABCD' [10 of 47] Compiling Data.Hash.CRC32.GZip ( src/Data/Hash/CRC32/GZip.hs, dist/build/Data/Hash/CRC32/GZip.o ) [11 of 47] Compiling Data.Hash.CRC32.Posix ( src/Data/Hash/CRC32/Posix.hs, dist/build/Data/Hash/CRC32/Posix.o ) [12 of 47] Compiling Data.Bits.Utils ( src/Data/Bits/Utils.hs, dist/build/Data/Bits/Utils.o ) [13 of 47] Compiling System.FileArchive.GZip ( src/System/FileArchive/GZip.hs, dist/build/System/FileArchive/GZip.o ) [14 of 47] Compiling Data.Tuple.Utils ( src/Data/Tuple/Utils.hs, dist/build/Data/Tuple/Utils.o ) [15 of 47] Compiling Data.Maybe.Utils ( src/Data/Maybe/Utils.hs, dist/build/Data/Maybe/Utils.o ) [16 of 47] Compiling Data.Either.Utils ( src/Data/Either/Utils.hs, dist/build/Data/Either/Utils.o ) [17 of 47] Compiling Network.Utils ( src/Network/Utils.hs, dist/build/Network/Utils.o ) [18 of 47] Compiling Network.SocketServer ( src/Network/SocketServer.hs, dist/build/Network/SocketServer.o ) [19 of 47] Compiling System.Time.ParseDate ( src/System/Time/ParseDate.hs, dist/build/System/Time/ParseDate.o ) [20 of 47] Compiling System.Path.NameManip ( src/System/Path/NameManip.hs, dist/build/System/Path/NameManip.o ) [21 of 47] Compiling Data.Quantity ( src/Data/Quantity.hs, dist/build/Data/Quantity.o ) [22 of 47] Compiling System.Time.Utils ( src/System/Time/Utils.hs, dist/build/System/Time/Utils.o ) [23 of 47] Compiling Data.Progress.Tracker ( src/Data/Progress/Tracker.hs, dist/build/Data/Progress/Tracker.o ) [24 of 47] Compiling Data.BinPacking ( src/Data/BinPacking.hs, dist/build/Data/BinPacking.o ) [25 of 47] Compiling Data.CSV ( src/Data/CSV.hs, dist/build/Data/CSV.o ) [26 of 47] Compiling System.Cmd.Utils ( src/System/Cmd/Utils.hs, dist/build/System/Cmd/Utils.o ) src/System/Cmd/Utils.hs:328:23: Constructor `Terminated' should have 2 arguments, but has been given 1 In the pattern: Terminated sig In the pattern: Just (Terminated sig) In a case alternative: Just (Terminated sig) -> warnfail fp args $ "Terminated by signal " ++ show sig src/System/Cmd/Utils.hs:354:13: Constructor `Terminated' should have 2 arguments, but has been given 1 In the pattern: Terminated s In a case alternative: Terminated s -> cmdsignalled "safeSystem" command args s In a stmt of a 'do' block: case ec of { Exited ExitSuccess -> return () Exited (ExitFailure fc) -> cmdfailed "safeSystem" command args fc Terminated s -> cmdsignalled "safeSystem" command args s Stopped s -> cmdsignalled "safeSystem" command args s } From gmane at brianhv.org Tue Jan 21 03:44:16 2014 From: gmane at brianhv.org (Brian Victor) Date: Mon, 20 Jan 2014 22:44:16 -0500 Subject: [Haskell-cafe] ghc-mod list: cannot satisfy -package cairo Message-ID: I'm receiving an error from ghc-mod in my cabal sandbox: %./.cabal-sandbox/bin/ghc-mod list Dummy:0:0:Error:: cannot satisfy -package cairo (use -v for more information) The obvious potential problem is that cairo isn't installed. However, %cabal repl Preprocessing executable 'Notation' for Notation-0.1.0.0... GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help ... Prelude Main> import Graphics.Rendering.Cairo Prelude Graphics.Rendering.Cairo Main> My cabal file includes: build-depends: base >=4.6 && <4.7, mtl >=2.1 && <2.2, containers >=0.4 && <0.5, cairo >= 0.12 && <= 0.13 I'm on OSX 10.9.1. I had to point cairo to gcc-4.9 instead of clang to make it compile. Where else can I look for the problem? -- Brian From kolmodin at gmail.com Tue Jan 21 06:01:10 2014 From: kolmodin at gmail.com (Lennart Kolmodin) Date: Mon, 20 Jan 2014 22:01:10 -0800 (PST) Subject: [Haskell-cafe] Help with Binary Serialization In-Reply-To: References: <19536a0f-e74f-4d00-8adb-7b7507320eb4@googlegroups.com> Message-ID: <2d3179b5-c288-4838-8fc3-b8db708ad37a@googlegroups.com> Hi, the format is quite simple, and it's the same in both binary and cereal. For data types with only one constructor, only the values of the constructor are encoded - not the constructor itself. data Foo = Foo Int Int deriving (Generic) So Foo is encoded as if it was only the Ints without the Foo constructor. encode (Foo 1 2) = 0x 00000001 00000002 If there are multiple constructors a tag is encoded representing the constructor, and then the values of that constructor. The tag will use as many bytes as it needs to be to fit the tag. 2-255 constructors will use 1 byte, and so on. data Fruit = Apple Int | Orange Foo encode (Apple 3) = 0x 00 00000003 First byte is zero to represent the Apple constructor, then the Int. encode (Orange (Foo 4 5)) = 0x 01 00000004 00000005 First byte is 0x01 to represent the Orange constructor, then the Foo value which is just to subsequent Ints. The format will not change without warning, and has not changed since it was implemented. That said, the generic format is mostly meant for being written and read by the haskell app that defines the data types, as it's easy to break compatibility even within the same app. JSON is probably not a bad choice, try it out http://hackage.haskell.org/package/aeson-0.6.1.0/docs/Data-Aeson.html Hope it helps! Lennart On Monday, 20 January 2014 21:28:33 UTC+4, Joey Eremondi wrote: > > Makes sense. I've had trouble finding documentation on the format used by > aeson, any links to that? > On 2014-01-19 10:46 AM, "John Lato" > > wrote: > >> I think this approach will likely lead to problems later on. First, >> undocumented formats are liable to change without warning. Secondly, it's >> conceivable that the format could change due to changes in ghc's generics >> support, or internal (and hence unstable) data structures of some component >> type. >> >> Would it be possible to just define your own format instead, or use >> something like JSON that's already well-defined? >> >> On Jan 18, 2014 12:17 PM, "Joey Eremondi" > >> wrote: >> > >> > I was wondering if somebody could talk me through the default derived >> format for binary serialization used, either by binary or by cereal. >> > >> > I'm trying to share data between Haskell and another function language >> (Elm) which also supports algebraic data types, so the conversion of data >> should be pretty trivial. I'd like to be able to just derive encode and >> decode in Haskell using either binary/cereal, and then write a parser for >> the same format in Elm. The trick is, I don't know what that format is. >> > >> > Is there any documentation on it, or if not, is anybody familiar enough >> with it that they could explain the format to me? >> > >> > Thanks! >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskel... at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Tue Jan 21 06:09:12 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Tue, 21 Jan 2014 08:09:12 +0200 Subject: [Haskell-cafe] MissingH fails to compile In-Reply-To: <20140121015412.GA17131@pignolo.chem.utoronto.ca> References: <20140121015412.GA17131@pignolo.chem.utoronto.ca> Message-ID: <20140121060912.GA19019@sniper> Hi Peter, It looks like MissingH is not yet updated to work with the latest version of the unix library (CC'ing the maintainer of MissingH). Try adding --constraint 'unix < 2.7' to your cabal install command line. Roman * Peter Colberg [2014-01-20 20:54:13-0500] > src/System/Cmd/Utils.hs:328:23: > Constructor `Terminated' should have 2 arguments, but has been given 1 > In the pattern: Terminated sig > In the pattern: Just (Terminated sig) > In a case alternative: > Just (Terminated sig) > -> warnfail fp args $ "Terminated by signal " ++ show sig > > src/System/Cmd/Utils.hs:354:13: > Constructor `Terminated' should have 2 arguments, but has been given 1 > In the pattern: Terminated s > In a case alternative: > Terminated s -> cmdsignalled "safeSystem" command args s > In a stmt of a 'do' block: > case ec of { > Exited ExitSuccess -> return () > Exited (ExitFailure fc) -> cmdfailed "safeSystem" command args fc > Terminated s -> cmdsignalled "safeSystem" command args s > Stopped s -> cmdsignalled "safeSystem" command args s } -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From carlo at carlo-hamalainen.net Tue Jan 21 06:15:32 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Tue, 21 Jan 2014 07:15:32 +0100 Subject: [Haskell-cafe] ghc-mod list: cannot satisfy -package cairo In-Reply-To: References: Message-ID: <52DE1084.6070006@carlo-hamalainen.net> On 21/01/14 04:44, Brian Victor wrote: > I'm receiving an error from ghc-mod in my cabal sandbox: > > %./.cabal-sandbox/bin/ghc-mod list > Dummy:0:0:Error:: cannot satisfy -package cairo > (use -v for more information) > > The obvious potential problem is that cairo isn't installed. However, > > %cabal repl > Preprocessing executable 'Notation' for Notation-0.1.0.0... > GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help > ... > Prelude Main> import Graphics.Rendering.Cairo > Prelude Graphics.Rendering.Cairo Main> If you use ghci and point it to only the cabal sandbox, can you still import Graphics.Rendering.Cairo? For example: ghci -no-user-package-db -package-db .cabal-sandbox/x86_64-linux-ghc-7.6.3-packages.conf.d but change "x86_64-linux-ghc-7.6.3" to your appropriate architecture and ghc version. -- Carlo Hamalainen http://carlo-hamalainen.net From trupill at gmail.com Tue Jan 21 10:31:39 2014 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Tue, 21 Jan 2014 11:31:39 +0100 Subject: [Haskell-cafe] Associated patterns Message-ID: Dear haskell-cafe, I've read in Reddit that pattern synonyms have been merged in GHC HEAD [ http://www.reddit.com/r/haskell/comments/1vpaey/pattern_synonyms_merged_into_ghchead/ ]. I would like to know whether associated patterns, that is, patterns which come under the umbrella of a type class, have also been implemented. I think that associated patterns would fill the gap in difference of features between type classes and common data types. For plain data types, you can declare both functions and patterns (either via constructors or now via pattern synonyms). However, you can only declare functions (either term-level or type-level) in type classes. This means that the pattern match mechanism, very useful to get clear code, is not useful if you want to use type classes. Alejandro. -------------- next part -------------- An HTML attachment was scrubbed... URL: From kiwamu at debian.or.jp Tue Jan 21 11:04:50 2014 From: kiwamu at debian.or.jp (Kiwamu Okabe) Date: Tue, 21 Jan 2014 20:04:50 +0900 Subject: [Haskell-cafe] [Help] Trying to rewrite the NetBSD kernel usingHaskell language. In-Reply-To: <20140120162755.081CD276C41@mail.avvanta.com> References: <20140120162755.081CD276C41@mail.avvanta.com> Message-ID: Hi Donn, Do you know c2hs and GreenCard? I don't know the details of them. http://blog.ezyang.com/2010/06/the-haskell-preprocessor-hierarchy/ On Tue, Jan 21, 2014 at 1:27 AM, Donn Cave wrote: > That suggests to me that you should change the class, so that > its Storable instance doesn't need to dereference the pointers - > that is, vtbl for example would be a Ptr type. Though that would > not save you very much trouble in the present case. Yes. I will try to write the own Ptr type and Storable class. Thank's. > Are you using hsc2hs? Your example has a few things like "plusPtr > p offsetOf_Ac97CodecIf_vtbl" - where do you get that offsetOf_? > hsc2hs has a #peek macro that does this: > > p_Ac97CodecIf_vtbl p = (#peek struct ac97codecxzy, vtbl) p > -- creates Haskell code > p_Ac97CodecIf_vtbl p = ((\ hsc_ptr -> peekByteOff hsc_ptr 96) p Yes, I know it. I read Read World Haskell book. But there are two problems. First, jhc has own Foreign Primitives. http://ajhc.metasepi.org/manual.html#foreign-primitives The "const. C_CONSTANT" can embed a C expression in Haskell code. It understands C's macros (#define). Very powerful. Second, The hsc2hs is not good for cross compiling. If I miss to choose "--cc" option, I will watch funny BUG... Thank's, -- Kiwamu Okabe From gmane at brianhv.org Tue Jan 21 12:50:52 2014 From: gmane at brianhv.org (Brian Victor) Date: Tue, 21 Jan 2014 07:50:52 -0500 Subject: [Haskell-cafe] ghc-mod list: cannot satisfy -package cairo In-Reply-To: <52DE1084.6070006@carlo-hamalainen.net> References: <52DE1084.6070006@carlo-hamalainen.net> Message-ID: On 1/21/14, 1:15 AM, Carlo Hamalainen wrote: > On 21/01/14 04:44, Brian Victor wrote: >> I'm receiving an error from ghc-mod in my cabal sandbox: >> >> %./.cabal-sandbox/bin/ghc-mod list >> Dummy:0:0:Error:: cannot satisfy -package cairo >> (use -v for more information) >> >> The obvious potential problem is that cairo isn't installed. However, >> >> %cabal repl >> Preprocessing executable 'Notation' for Notation-0.1.0.0... >> GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help >> ... >> Prelude Main> import Graphics.Rendering.Cairo >> Prelude Graphics.Rendering.Cairo Main> > > If you use ghci and point it to only the cabal sandbox, can you still > import Graphics.Rendering.Cairo? For example: > > ghci -no-user-package-db -package-db > .cabal-sandbox/x86_64-linux-ghc-7.6.3-packages.conf.d > > but change "x86_64-linux-ghc-7.6.3" to your appropriate architecture and > ghc version. > Yes, I can. %ghci -no-user-package-db -package-db .cabal-sandbox/x86_64-osx-ghc-7.6.3-packages.conf.d GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Prelude> import Graphics.Rendering.Cairo Prelude Graphics.Rendering.Cairo> -- Brian From peter at colberg.org Tue Jan 21 15:20:51 2014 From: peter at colberg.org (Peter Colberg) Date: Tue, 21 Jan 2014 10:20:51 -0500 Subject: [Haskell-cafe] MissingH fails to compile In-Reply-To: <20140121060912.GA19019@sniper> References: <20140121015412.GA17131@pignolo.chem.utoronto.ca> <20140121060912.GA19019@sniper> Message-ID: <20140121152051.GA15009@alcyone> Hi Roman, On Tue, Jan 21, 2014 at 08:09:12AM +0200, Roman Cheplyaka wrote: > It looks like MissingH is not yet updated to work with the latest > version of the unix library (CC'ing the maintainer of MissingH). > > Try adding --constraint 'unix < 2.7' to your cabal install command line. Thank you, with that constraint MissingH compiles successfully :-). Peter From vogt.adam at gmail.com Tue Jan 21 15:34:59 2014 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 21 Jan 2014 10:34:59 -0500 Subject: [Haskell-cafe] Associated patterns In-Reply-To: References: Message-ID: Hi Alejandro, If your inspiration for "associated __" comes from the -XTypeFamilies, consider that you can take a working program, move all associated type/data families to top-level, and the program will still work. The only point of associating them with a class is to help prevent people from forgetting to write the type instance, and possibly to improve documentation. So maybe using a class method in the definition of a pattern synonym is close enough: {-# LANGUAGE ViewPatterns, PatternSynonyms #-} import qualified Data.Sequence as Seq class Listy t where listySplit :: t a -> Maybe (a, t a) listyUnsplit :: a -> t a -> t a instance Listy [] where listySplit (a:b) = Just (a,b) listySplit _ = Nothing listyUnsplit = (:) instance Listy Seq.Seq where listySplit (Seq.viewl -> a Seq.:< b) = Just (a,b) listySplit _ = Nothing listyUnsplit = (Seq.<|) pattern L x xs <- (listySplit -> Just (x,xs)) -- example sum1 :: (Listy t, Num a) => t a -> a sum1 (L x xs) = x + sum1 xs sum1 _ = 0 I don't see a way to make the expression `L x xs' stand for listyUnsplit. Maybe someone else can figure this out, or this is a forthcoming feature? -- Adam On Tue, Jan 21, 2014 at 5:31 AM, Alejandro Serrano Mena wrote: > Dear haskell-cafe, > I've read in Reddit that pattern synonyms have been merged in GHC HEAD > [http://www.reddit.com/r/haskell/comments/1vpaey/pattern_synonyms_merged_into_ghchead/]. > > I would like to know whether associated patterns, that is, patterns which > come under the umbrella of a type class, have also been implemented. > > I think that associated patterns would fill the gap in difference of > features between type classes and common data types. For plain data types, > you can declare both functions and patterns (either via constructors or now > via pattern synonyms). However, you can only declare functions (either > term-level or type-level) in type classes. This means that the pattern match > mechanism, very useful to get clear code, is not useful if you want to use > type classes. > > Alejandro. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From carter.schonwald at gmail.com Tue Jan 21 17:17:18 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 21 Jan 2014 12:17:18 -0500 Subject: [Haskell-cafe] Associated patterns In-Reply-To: References: Message-ID: It's been merged in, so you should build head and find out! (Seriously, we're very close to an official RC, if you use a unixy platform current head should look very similar to the official RC) On Tuesday, January 21, 2014, Alejandro Serrano Mena wrote: > Dear haskell-cafe, > I've read in Reddit that pattern synonyms have been merged in GHC HEAD [ > http://www.reddit.com/r/haskell/comments/1vpaey/pattern_synonyms_merged_into_ghchead/ > ]. > > I would like to know whether associated patterns, that is, patterns which > come under the umbrella of a type class, have also been implemented. > > I think that associated patterns would fill the gap in difference of > features between type classes and common data types. For plain data types, > you can declare both functions and patterns (either via constructors or now > via pattern synonyms). However, you can only declare functions (either > term-level or type-level) in type classes. This means that the pattern > match mechanism, very useful to get clear code, is not useful if you want > to use type classes. > > Alejandro. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From stuartallenmills at gmail.com Tue Jan 21 22:10:19 2014 From: stuartallenmills at gmail.com (Stuart Mills) Date: Tue, 21 Jan 2014 14:10:19 -0800 (PST) Subject: [Haskell-cafe] Help on simpleHttp in Network.HTTP.Conduit problem Message-ID: <6f5de711-e76d-4d72-823e-ca76ec45bae0@googlegroups.com> I copied and pasted some html parsing demo source from FP School. While the code works on the FP demo site (in the IDE), I get the following error on my Windows 7 64 bit: InternalIOException getAddrInfo: does not exist (error 10093). Thanks -------------- next part -------------- An HTML attachment was scrubbed... URL: From stuartallenmills at gmail.com Tue Jan 21 22:27:12 2014 From: stuartallenmills at gmail.com (Stuart Mills) Date: Tue, 21 Jan 2014 14:27:12 -0800 (PST) Subject: [Haskell-cafe] Any projected data for new Haskell Platform (2013.4? 2014.2?) Message-ID: Thanks -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Tue Jan 21 22:29:00 2014 From: trebla at vex.net (Albert Y. C. Lai) Date: Tue, 21 Jan 2014 17:29:00 -0500 Subject: [Haskell-cafe] Constraint on data type In-Reply-To: <52DD0D0F.90408@gmail.com> References: <52DD0D0F.90408@gmail.com> Message-ID: <52DEF4AC.4060406@vex.net> On 14-01-20 06:48 AM, Vlatko Basic wrote: > I have another data definition > > data ACT aur c = ACT { x :: aur, ... } > > but the type 'aur' should be restricted to (AD u r) only. > (I would like to keep 'aur' as 1 parameter, not as It is unnecessary to enforce your rule at the data declaration. It is sufficient and necessary to enforce it at relevant functions and values. For example: transform :: (UA u, RA r) => ACT (AD u r) Int -> ACT (AD u r) Bool From stuartallenmills at gmail.com Tue Jan 21 22:39:36 2014 From: stuartallenmills at gmail.com (Stuart Mills) Date: Tue, 21 Jan 2014 14:39:36 -0800 (PST) Subject: [Haskell-cafe] Help on simpleHttp in Network.HTTP.Conduit problem In-Reply-To: <6f5de711-e76d-4d72-823e-ca76ec45bae0@googlegroups.com> References: <6f5de711-e76d-4d72-823e-ca76ec45bae0@googlegroups.com> Message-ID: <67ce3b60-c1a9-4eb7-9aa9-e03b9dcc0677@googlegroups.com> Here is the source by the way: {-# LANGUAGE OverloadedStrings #-} import Network.HTTP.Conduit (simpleHttp) import qualified Data.Text as T import Text.HTML.DOM (parseLBS) import Text.XML.Cursor (Cursor, attributeIs, content, element, fromDocument, child, ($//), (&|), (&//), (>=>)) -- The URL we're going to search url = "http://www.bing.com/search?q=school+of+haskell" -- The data we're going to search for findNodes :: Cursor -> [Cursor] findNodes = element "span" >=> attributeIs "id" "count" >=> child -- Extract the data from each node in turn extractData = T.concat . content -- Process the list of data elements processData = putStrLn . T.unpack . T.concat cursorFor :: String -> IO Cursor cursorFor u = do page <- simpleHttp u return $ fromDocument $ parseLBS page -- test main = do cursor <- cursorFor url processData $ cursor $// findNodes &| extractData On Tuesday, January 21, 2014 2:10:19 PM UTC-8, Stuart Mills wrote: > > I copied and pasted some html parsing demo source from FP School. > > While the code works on the FP demo site (in the IDE), I get the following > error on my Windows 7 64 bit: > > InternalIOException getAddrInfo: does not exist (error 10093). > > Thanks > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Tue Jan 21 23:14:10 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 22 Jan 2014 01:14:10 +0200 Subject: [Haskell-cafe] Help on simpleHttp in Network.HTTP.Conduit problem In-Reply-To: <67ce3b60-c1a9-4eb7-9aa9-e03b9dcc0677@googlegroups.com> References: <6f5de711-e76d-4d72-823e-ca76ec45bae0@googlegroups.com> <67ce3b60-c1a9-4eb7-9aa9-e03b9dcc0677@googlegroups.com> Message-ID: <20140121231410.GA16325@sniper> It looks like you haven't initialized the networking subsystem. See http://hackage.haskell.org/package/network-2.4.2.2/docs/Network.html#g:2 * Stuart Mills [2014-01-21 14:39:36-0800] > Here is the source by the way: > {-# LANGUAGE OverloadedStrings #-} > > import Network.HTTP.Conduit (simpleHttp) > import qualified Data.Text as T > import Text.HTML.DOM (parseLBS) > import Text.XML.Cursor (Cursor, attributeIs, content, element, > fromDocument, child, > ($//), (&|), (&//), (>=>)) > > -- The URL we're going to search > url = "http://www.bing.com/search?q=school+of+haskell" > > -- The data we're going to search for > findNodes :: Cursor -> [Cursor] > findNodes = element "span" >=> attributeIs "id" "count" >=> child > > -- Extract the data from each node in turn > extractData = T.concat . content > > -- Process the list of data elements > processData = putStrLn . T.unpack . T.concat > > cursorFor :: String -> IO Cursor > cursorFor u = do > page <- simpleHttp u > return $ fromDocument $ parseLBS page > > -- test > main = do > cursor <- cursorFor url > processData $ cursor $// findNodes &| extractData > > > On Tuesday, January 21, 2014 2:10:19 PM UTC-8, Stuart Mills wrote: > > > > I copied and pasted some html parsing demo source from FP School. > > > > While the code works on the FP demo site (in the IDE), I get the following > > error on my Windows 7 64 bit: > > > > InternalIOException getAddrInfo: does not exist (error 10093). > > > > Thanks > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From mightybyte at gmail.com Wed Jan 22 01:24:30 2014 From: mightybyte at gmail.com (MightyByte) Date: Tue, 21 Jan 2014 20:24:30 -0500 Subject: [Haskell-cafe] ANNOUNCE: Hac NYC: Haskell Hackathon in NYC, April 4-6 Message-ID: Greetings, On behalf of the organizers, I am pleased to officially announce the first Hac NYC, a Haskell hackathon/get-together to be held April 4-6 in New York City. Space will be provided by Etsy on Saturday and Sunday. Details for Friday will be announced as they become finalized. We want to stress that everyone is welcome---you do not have to be a Haskell guru to attend! Helping hack on someone else's project could be a great way to increase your Haskell-fu. If you plan on coming, you must officially register by filling out our registration form [1]. Other details for travel, lodging, etc can be found on the Hac NYC wiki [2]. We're also looking for a few people interested in giving short (15-20 min.) talks, probably on Saturday afternoon. Anything of interest to the Haskell community is fair game---a project you've been working on, a paper, a quick tutorial. If you'd like to give a talk, add it on the wiki [3]. Hope to see you in April! -The Hac NYC Team [1] https://docs.google.com/forms/d/1taZtjgYozFNebLt1TR2VnKv-ovD2Yv5sOdSZzmi_xFo/viewform [2] http://www.haskell.org/haskellwiki/Hac_NYC [3] http://www.haskell.org/haskellwiki/Hac_NYC/Talks From ok at cs.otago.ac.nz Wed Jan 22 01:56:36 2014 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Wed, 22 Jan 2014 14:56:36 +1300 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> Message-ID: On 10/01/2014, at 8:36 PM, John Lato wrote: > An abstract String would also be better than our current situation because Data.List functions on Strings are just plain wrong anyway. Simple example: what should be the reverse of "This is two lines\r\nbecause Windows!\r\n"? It gets even more fun with unicode. Linear sequences of characters are a fundamentally broken data type no matter how you represent them in the computer. John Lato gave this link: http://msmvps.com/blogs/jon_skeet/archive/2009/11/02/omg-ponies-aka-humanity-epic-fail.aspx where in the course of making a valid point, the author made the mistake of writing "Les Mis\u0301erables" which should of course be "Les Mise\u0301rables". And when he wrote "Unicode has its own special line terminator character as well" he should have said "Unicode adds THREE more special characters": the Latin-1 Next Line character (U+0085), Line Separator (U+2028), and Paragraph Separator (U+2029). Just to add to the fun, \r, \n, \r\n, and \205 are line *terminators* while the other two are *separators*. Unicode is *insanely* complicated. It includes a set of *prefix* operators (the "Ideographic Description Characters") for describing *trees* of Chinese characters to be displayed in a single box, but a set of *postfix* operators for other things like accents and for saying "the FUEL PUMP U+26FD characte preceding should be in colour" [VS15 = "text style", VS16 = "emoji style", see http://www.unicode.org/L2/L2011/11438-emoji-var.pdf]. And just to complete the trifecta, there's a distfix operator base text annotation text . Oh, I didn't mention the *infix* operator "combining grapheme cluster". If there is _any_ sane way to reverse a Unicode string, which I rather doubt, it would be _horrible_ to implement it. And frankly, the use of lists here would *not* contribute materially to the difficulty. (For the record, I tried to implement a string reversal operation that made sense for Unicode, and very quickly became extremely bewildered.) From alfredo.dinapoli at gmail.com Wed Jan 22 08:40:20 2014 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Wed, 22 Jan 2014 08:40:20 +0000 Subject: [Haskell-cafe] Help on simpleHttp in Network.HTTP.Conduit problem In-Reply-To: <20140121231410.GA16325@sniper> References: <6f5de711-e76d-4d72-823e-ca76ec45bae0@googlegroups.com> <67ce3b60-c1a9-4eb7-9aa9-e03b9dcc0677@googlegroups.com> <20140121231410.GA16325@sniper> Message-ID: Hi Stuart, I was going to suggest the same as Roman, this is a "known problem" on Windows. But the good news is that withSocketsDo is implemented as "id" if you are on Unix, so you could still write multi platform programs without worrying about platforms and preprocessor flags. Hope this helps! Alfredo On 21 January 2014 23:14, Roman Cheplyaka wrote: > It looks like you haven't initialized the networking subsystem. See > http://hackage.haskell.org/package/network-2.4.2.2/docs/Network.html#g:2 > > * Stuart Mills [2014-01-21 14:39:36-0800] > > Here is the source by the way: > > {-# LANGUAGE OverloadedStrings #-} > > > > import Network.HTTP.Conduit (simpleHttp) > > import qualified Data.Text as T > > import Text.HTML.DOM (parseLBS) > > import Text.XML.Cursor (Cursor, attributeIs, content, element, > > fromDocument, child, > > ($//), (&|), (&//), (>=>)) > > > > -- The URL we're going to search > > url = "http://www.bing.com/search?q=school+of+haskell" > > > > -- The data we're going to search for > > findNodes :: Cursor -> [Cursor] > > findNodes = element "span" >=> attributeIs "id" "count" >=> child > > > > -- Extract the data from each node in turn > > extractData = T.concat . content > > > > -- Process the list of data elements > > processData = putStrLn . T.unpack . T.concat > > > > cursorFor :: String -> IO Cursor > > cursorFor u = do > > page <- simpleHttp u > > return $ fromDocument $ parseLBS page > > > > -- test > > main = do > > cursor <- cursorFor url > > processData $ cursor $// findNodes &| extractData > > > > > > On Tuesday, January 21, 2014 2:10:19 PM UTC-8, Stuart Mills wrote: > > > > > > I copied and pasted some html parsing demo source from FP School. > > > > > > While the code works on the FP demo site (in the IDE), I get the > following > > > error on my Windows 7 64 bit: > > > > > > InternalIOException getAddrInfo: does not exist (error 10093). > > > > > > Thanks > > > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at joachim-breitner.de Wed Jan 22 09:23:51 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Wed, 22 Jan 2014 09:23:51 +0000 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> Message-ID: <1390382631.2528.2.camel@kirk> Hi, Am Mittwoch, den 22.01.2014, 14:56 +1300 schrieb Richard A. O'Keefe: > If there is _any_ sane way to reverse a Unicode string, > which I rather doubt, > it would be _horrible_ to implement it. I suggest this: > reverse unicode_str = '\u202E' : unicode_str ?It works great! Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 181 bytes Desc: This is a digitally signed message part URL: From mystic.satvik at gmail.com Wed Jan 22 09:42:41 2014 From: mystic.satvik at gmail.com (satvik chauhan) Date: Wed, 22 Jan 2014 15:12:41 +0530 Subject: [Haskell-cafe] Haddock Constructor parameter documentation without record syntax Message-ID: Hi, Does anybody know how to document parameters of a constructor in haddock. The following code gives parse error on the second parameter while generating haddock documentation. ``` data Foo = Foo Int -- ^ First Int -- ^ Second ``` -Satvik -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander at plaimi.net Wed Jan 22 09:48:59 2014 From: alexander at plaimi.net (Alexander Berntsen) Date: Wed, 22 Jan 2014 10:48:59 +0100 Subject: [Haskell-cafe] Haddock Constructor parameter documentation without record syntax In-Reply-To: References: Message-ID: <52DF940B.7090501@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 22/01/14 10:42, satvik chauhan wrote: > data Foo = Foo Int -- ^ First > Int -- ^ Second I don't think you can do it that way. See [0]. [0] - -- Alexander alexander at plaimi.net http://plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlLflAsACgkQRtClrXBQc7VevgD+JBpm/PQkdUZ1v8EFgErIECWf 1Zjoyp/kSvnuYpJlPi4A/3/zVoumiAQYq8BI1lBo22r992cSkvrnOn7D57EZfJSr =KwN5 -----END PGP SIGNATURE----- From difrumin at gmail.com Wed Jan 22 10:04:48 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Wed, 22 Jan 2014 14:04:48 +0400 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <1390382631.2528.2.camel@kirk> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> <1390382631.2528.2.camel@kirk> Message-ID: Ha, this is a clever trick. Does it really work in all the cases? On Wed, Jan 22, 2014 at 1:23 PM, Joachim Breitner wrote: > Hi, > > Am Mittwoch, den 22.01.2014, 14:56 +1300 schrieb Richard A. O'Keefe: >> If there is _any_ sane way to reverse a Unicode string, >> which I rather doubt, >> it would be _horrible_ to implement it. > > I suggest this: > >> reverse unicode_str = '\u202E' : unicode_str > > It works great! > > Greetings, > Joachim > > > -- > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? http://www.joachim-breitner.de/ > Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C > Debian Developer: nomeata at debian.org > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Sincerely yours, -- Daniil From mail at joachim-breitner.de Wed Jan 22 10:07:15 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Wed, 22 Jan 2014 10:07:15 +0000 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> <1390382631.2528.2.camel@kirk> Message-ID: <1390385235.2528.3.camel@kirk> Hi, Am Mittwoch, den 22.01.2014, 14:04 +0400 schrieb Daniil Frumin: > Ha, this is a clever trick. Does it really work in all the cases? that depends on the unicode implementation of the client, of course. But in enough cases to annoy or confuse people. Greetings, Joachim -- Joachim ?nomeata? Breitner mail at joachim-breitner.de ? http://www.joachim-breitner.de/ Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C Debian Developer: nomeata at debian.org -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 181 bytes Desc: This is a digitally signed message part URL: From fuuzetsu at fuuzetsu.co.uk Wed Jan 22 10:25:40 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Wed, 22 Jan 2014 10:25:40 +0000 Subject: [Haskell-cafe] Haddock Constructor parameter documentation without record syntax In-Reply-To: <52DF940B.7090501@plaimi.net> References: <52DF940B.7090501@plaimi.net> Message-ID: <52DF9CA4.30605@fuuzetsu.co.uk> On 22/01/14 09:48, Alexander Berntsen wrote: > On 22/01/14 10:42, satvik chauhan wrote: >> data Foo = Foo Int -- ^ First >> Int -- ^ Second > I don't think you can do it that way. See [0]. > > [0] > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > I can confirm that you can not document constructors in this way. If you really need to, you can make it into a record and document each field. -- Mateusz K. From mystic.satvik at gmail.com Wed Jan 22 10:29:44 2014 From: mystic.satvik at gmail.com (satvik chauhan) Date: Wed, 22 Jan 2014 15:59:44 +0530 Subject: [Haskell-cafe] Haddock Constructor parameter documentation without record syntax In-Reply-To: <52DF9CA4.30605@fuuzetsu.co.uk> References: <52DF940B.7090501@plaimi.net> <52DF9CA4.30605@fuuzetsu.co.uk> Message-ID: Using the record is an option but it pollutes the namespace which I don't want to do. Any ideas why this is not possible? On Wed, Jan 22, 2014 at 3:55 PM, Mateusz Kowalczyk wrote: > On 22/01/14 09:48, Alexander Berntsen wrote: > > On 22/01/14 10:42, satvik chauhan wrote: > >> data Foo = Foo Int -- ^ First > >> Int -- ^ Second > > I don't think you can do it that way. See [0]. > > > > [0] > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > I can confirm that you can not document constructors in this way. If you > really need to, you can make it into a record and document each field. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- -------------------------------------------------------------------------------------------------- Satvik Chauhan Fourth Year Under Graduate Student Deptt. of Computer Science and Engineering Indian Institute of Technology Kanpur Kanpur-208016, INDIA Email: mystic.satvik at gmail.com , satvikc at iitk.ac.in -------------------------------------------------------------------------------------------------- -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Wed Jan 22 10:51:02 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Wed, 22 Jan 2014 10:51:02 +0000 Subject: [Haskell-cafe] Haddock Constructor parameter documentation without record syntax In-Reply-To: References: <52DF940B.7090501@plaimi.net> <52DF9CA4.30605@fuuzetsu.co.uk> Message-ID: <52DFA296.2030602@fuuzetsu.co.uk> On 22/01/14 10:29, satvik chauhan wrote: > Using the record is an option but it pollutes the namespace which I don't > want to do. > > Any ideas why this is not possible? > > > On Wed, Jan 22, 2014 at 3:55 PM, Mateusz Kowalczyk > wrote: > >> On 22/01/14 09:48, Alexander Berntsen wrote: >>> On 22/01/14 10:42, satvik chauhan wrote: >>>> data Foo = Foo Int -- ^ First >>>> Int -- ^ Second >>> I don't think you can do it that way. See [0]. >>> >>> [0] >> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> I can confirm that you can not document constructors in this way. If you >> really need to, you can make it into a record and document each field. >> >> -- >> Mateusz K. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > See http://trac.haskell.org/haddock/ticket/95 -- Mateusz K. From carlo at carlo-hamalainen.net Wed Jan 22 12:43:34 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Wed, 22 Jan 2014 13:43:34 +0100 Subject: [Haskell-cafe] Cabal version constraint seems to be ignored. Message-ID: <52DFBCF6.60801@carlo-hamalainen.net> Hi, I have two versions of Cabal, both are visible: $ ghc-pkg expose Cabal-1.16.0 $ ghc-pkg expose Cabal-1.18.1.2 I clone and build my package. Since I have GHC 7.6.3 it uses Cabal-1.16.0 (as specified in ghc-imported-from.cabal): $ git clone https://github.com/carlohamalainen/ghc-imported-from $ cd ghc-imported-from $ cabal install It looks like Cabal-1.16.0 was chosen, as expected: $ grep Cabal dist/build/autogen/cabal_macros.h /* DO NOT EDIT: This file is automatically generated by Cabal */ /* package Cabal-1.16.0 */ #define VERSION_Cabal "1.16.0" #define MIN_VERSION_Cabal(major1,major2,minor) (\ But my program doesn't run: $ ghc-imported-from src/Main.hs Main getArgs 11 11 --ghc-options --ghc-pkg-options GhcOptions [] GhcPkgOptions [] Language/Haskell/GhcImportedFrom.hs:132:54: Couldn't match expected type `Distribution.PackageDescription.BuildInfo' with actual type `Cabal-1.16.0:Distribution.PackageDescription.BuildInfo' In the fourth argument of `getGHCOptions', namely `binfo' In a stmt of a 'do' block: getGHCOptions [] c (fromJust $ cradleCabalDir c) binfo In the expression: do { c <- findCradle; pkgDesc <- GhcMonad.liftIO $ parseCabalFile $ fromJust $ cradleCabalFile c; let binfo = head $ cabalAllBuildInfo pkgDesc; getGHCOptions [] c (fromJust $ cradleCabalDir c) binfo } I'm surprised that the error didn't appear at compile time. I guess the first reference to Distribution.PackageDescription.BuildInfo is from Cabal-1.18.1.2? If I hide Cabal-1.18.1.2 then things work ok: $ ghc-pkg hide Cabal-1.18.1.2 $ cabal install $ ghc-imported-from .... (runs as expected) But I can't expect a user to know that they have to hide Cabal-1.18.1.2. Is this actually a GHC bug or have I stuffed up my ghc-imported-from.cabal file? Thanks, -- Carlo Hamalainen http://carlo-hamalainen.net From hutch-lists at recursive.ca Wed Jan 22 12:50:03 2014 From: hutch-lists at recursive.ca (Bob Hutchison) Date: Wed, 22 Jan 2014 07:50:03 -0500 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <1390385235.2528.3.camel@kirk> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> <1390382631.2528.2.camel@kirk> <1390385235.2528.3.camel@kirk> Message-ID: <230BF688-3BBD-492F-8B79-A9E5E05A9DF4@recursive.ca> For still more fun: http://www.explainxkcd.com/wiki/index.php/1137:_RTL Cheers, Bob On Jan 22, 2014, at 5:07 AM, Joachim Breitner wrote: > Hi, > > Am Mittwoch, den 22.01.2014, 14:04 +0400 schrieb Daniil Frumin: >> Ha, this is a clever trick. Does it really work in all the cases? > > that depends on the unicode implementation of the client, of course. But > in enough cases to annoy or confuse people. > > Greetings, > Joachim > > -- > Joachim ?nomeata? Breitner > mail at joachim-breitner.de ? http://www.joachim-breitner.de/ > Jabber: nomeata at joachim-breitner.de ? GPG-Key: 0x4743206C > Debian Developer: nomeata at debian.org > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From v.dijk.bas at gmail.com Wed Jan 22 16:49:54 2014 From: v.dijk.bas at gmail.com (Bas van Dijk) Date: Wed, 22 Jan 2014 17:49:54 +0100 Subject: [Haskell-cafe] ANN: ZuriHac 2014 Message-ID: Dear Haskellers, After a very successful ZuriHac 2013 we are delighted to announce ZuriHac 2014! When: Friday 6 June 2014 - Sunday 8 June 2014 Where: Erudify offices, Zurich, Switzerland ZuriHac is an international Haskell hackathon: a grassroots, collaborative coding festival with a simple focus, to build and improve Haskell libraries, tools, and infrastructure. This is a great opportunity to meet your fellow Haskellers in real life, find new contributors for your project, improve existing libraries and tools, or even start new ones! Registration ------------ If you wish to attend, please register by filling in this form: http://bit.ly/ZuriHac2014 Please note that we have a limited number of places -- first come, first served. Full details can be found on the wiki page: http://www.haskell.org/haskellwiki/ZuriHac2014 We look forward to seeing you there! -- The organisers of ZuriHac 2014 ZuriHac 2014 is sponsored by Erudify & Google From creswick at gmail.com Wed Jan 22 17:07:10 2014 From: creswick at gmail.com (Rogan Creswick) Date: Wed, 22 Jan 2014 09:07:10 -0800 Subject: [Haskell-cafe] Cabal version constraint seems to be ignored. In-Reply-To: <52DFBCF6.60801@carlo-hamalainen.net> References: <52DFBCF6.60801@carlo-hamalainen.net> Message-ID: On Wed, Jan 22, 2014 at 4:43 AM, Carlo Hamalainen < carlo at carlo-hamalainen.net> wrote: > If I hide Cabal-1.18.1.2 then things work ok: > > Does the behavior change if you build with a sandbox? (without hiding either Cabal via ghc-pkg?) If I had to hazard a guess, I'd say that the inability to specify dependencies for the build process are causing this problem, even though you're using build-type: simple; one cabal is used to set cabal-specific details in the cabal_macros.h file (which I'm assuming you're using somewhere in the source?) and another is picked based on the build-depends. That's just a guess, though... and if true, it's a wrinkle in the interactions between build-system dependencies and program build-time dependencies that I haven't run across before (even with Cabal-dev!). --Rogan > $ ghc-pkg hide Cabal-1.18.1.2 > $ cabal install > $ ghc-imported-from .... (runs as expected) > > But I can't expect a user to know that they have to hide Cabal-1.18.1.2. > > Is this actually a GHC bug or have I stuffed up my > ghc-imported-from.cabal file? > > Thanks, > > -- > Carlo Hamalainen > http://carlo-hamalainen.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carlo at carlo-hamalainen.net Wed Jan 22 18:52:12 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Wed, 22 Jan 2014 19:52:12 +0100 Subject: [Haskell-cafe] Cabal version constraint seems to be ignored. In-Reply-To: References: <52DFBCF6.60801@carlo-hamalainen.net> Message-ID: <52E0135C.8050402@carlo-hamalainen.net> On 22/01/14 18:07, Rogan Creswick wrote: > Does the behavior change if you build with a sandbox? (without hiding > either Cabal via ghc-pkg?) Yes, in particular: $ ghc-pkg expose Cabal-1.18.1.2 $ rm -fr .cabal-sandbox cabal.sandbox.config dist $ cabal sandbox init $ cabal install --dependencies-only $ cabal install $ .cabal-sandbox/bin/ghc-imported-from src/Main.hs Main getArgs 11 11 --ghc-options --ghc-pkg-options runs with no problems. I dug into this a bit more and I think it's a bug in my own code: the error that I quoted before was not the executable blowing up, instead it was runGhc exploding because I did not pass the right flags to the GHC API when I called "load LoadAllTargets". Stepping back, I can reproduce the error with plain ghci: $ ghci GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. Prelude> :l src/Main.hs [1 of 3] Compiling Language.Haskell.GhcImportedFrom.UtilsFromGhcMod ( Language/Haskell/GhcImportedFrom/UtilsFromGhcMod.hs, interpreted ) [2 of 3] Compiling Language.Haskell.GhcImportedFrom ( Language/Haskell/GhcImportedFrom.hs, interpreted ) Language/Haskell/GhcImportedFrom.hs:132:54: Couldn't match expected type `Distribution.PackageDescription.BuildInfo' with actual type `Cabal-1.16.0:Distribution.PackageDescription.BuildInfo' In the fourth argument of `getGHCOptions', namely `binfo' In a stmt of a 'do' block: getGHCOptions [] c (fromJust $ cradleCabalDir c) binfo In the expression: do { c <- findCradle; pkgDesc <- GhcMonad.liftIO $ parseCabalFile $ fromJust $ cradleCabalFile c; let binfo = head $ cabalAllBuildInfo pkgDesc; getGHCOptions [] c (fromJust $ cradleCabalDir c) binfo } Failed, modules loaded: Language.Haskell.GhcImportedFrom.UtilsFromGhcMod. whereas cabal repl works fine, because it parses the .cabal file and realises that it needs the earlier version of Cabal. Confirming this, if I use -package to specify the version of Cabal then it works fine: $ ghci -package Cabal-1.16.0 (all happy now) So I should look at how the latest Cabal (in particular "cabal repl") works out the right flags to pass to ghci, and incorporate that into my ghc-imported-from project. I see that the developer of ghc-mod has run into a similar issue recently: https://github.com/kazu-yamamoto/ghc-mod/issues/171 > If I had to hazard a guess, I'd say that the inability to specify > dependencies for the build process are causing this problem, even > though you're using build-type: simple; one cabal is used to set > cabal-specific details in the cabal_macros.h file (which I'm assuming > you're using somewhere in the source?) and another is picked based on > the build-depends. > > That's just a guess, though... and if true, it's a wrinkle in the > interactions between build-system dependencies and program build-time > dependencies that I haven't run across before (even with Cabal-dev!). Nope, it's a wrinkle in my understanding of Cabal/ghci/etc :) Thanks for the reply though, it helped me hunt down the problem. Cheers, -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From reilithion at gmail.com Wed Jan 22 21:37:26 2014 From: reilithion at gmail.com (Lucas Paul) Date: Wed, 22 Jan 2014 14:37:26 -0700 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? In-Reply-To: References: Message-ID: This is my take, as a CS undergraduate. I'm not sure if we can say that a programmer's language of choice determines the way they think about programming (the strong version of linguistic relativity for programming, as I see it). But I think it's fairly obvious that the language we choose to use to solve a problem affects how we think about the solution. That's basically the entire raison d'?tre for domain-specific languages (DSLs)! DSLs are popular (and becoming more so) precisely because the right choice of DSL can make expressing the solution to a particular kind of problem almost trivial. A poor choice can almost doom an endeavor. Imagine trying to query a database in assembly language. No SQL. It would at the very least require some mental gymnastics that a SELECT statement simply obviates. Similarly, functional programmers tend to think about maps and folds, while imperative programmers tend to think about loops and iterators. While they accomplish much the same thing, it's amazing to read code and see what different directions they often lead. (?mer, sorry for the double-response. I wish GMail defaulted to replying to the list. >_<) - Lucas On Fri, Jan 17, 2014 at 11:14 AM, ?mer Sinan A?acan wrote: > Hi all, > > I recently got myself thinking about programming languages and their > effects on programmers. I already knew that concept of "linguistic > relativity" ( http://en.wikipedia.org/wiki/Linguistic_relativity ) > and I was thinking that this may be relevant with programming too, > although I don't have any concrete evidence. I was wondering if anyone > else also find that idea of programming language's effect of the > programmer interesting. Do we have any research on that kinds of > things? > > Thanks, > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From keshav.kini at gmail.com Wed Jan 22 23:35:47 2014 From: keshav.kini at gmail.com (Keshav Kini) Date: Wed, 22 Jan 2014 15:35:47 -0800 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? References: Message-ID: <87d2jjpp2k.fsf@gmail.com> Lucas Paul writes: > This is my take, as a CS undergraduate. > > I'm not sure if we can say that a programmer's language of choice > determines the way they think about programming (the strong version of > linguistic relativity for programming, as I see it). But I think it's > fairly obvious that the language we choose to use to solve a problem > affects how we think about the solution. That's basically the entire > raison d'?tre for domain-specific languages (DSLs)! > > DSLs are popular (and becoming more so) precisely because the right > choice of DSL can make expressing the solution to a particular kind of > problem almost trivial. A poor choice can almost doom an endeavor. > Imagine trying to query a database in assembly language. No SQL. It > would at the very least require some mental gymnastics that a SELECT > statement simply obviates. I think this can be partially explained by noting that programming languages, and in particular the way that programmers use them, afford a capacity for essentially limitless amounts of abstraction, unlike human language and human communication. For example, I might easily have a magic library that does exactly what I want, with bindings for my programming language of choice, in which case I don't need to think about what to do, I just call the appropriate function. In human communication, while someone might have perfectly formulated exactly the idea I want to communicate, it is rarely sufficient for the purpose of communication to say "insert pages 204 through 356 of _Foobar_ by John Doe here" in the middle of a conversation :) -Keshav From allbery.b at gmail.com Thu Jan 23 00:28:09 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 22 Jan 2014 19:28:09 -0500 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? In-Reply-To: References: Message-ID: On Wed, Jan 22, 2014 at 4:37 PM, Lucas Paul wrote: > (?mer, sorry for the double-response. I wish GMail defaulted to > replying to the list. >_<) > > Settings > General > Default reply behavior -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From kc1956 at gmail.com Thu Jan 23 00:36:47 2014 From: kc1956 at gmail.com (KC) Date: Wed, 22 Jan 2014 16:36:47 -0800 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? In-Reply-To: References: Message-ID: I would say it is more the concepts one uses than the programming language that has an effect on the programmer. After learning one OOP language it is not that hard to pick up another OOP language BUT Functional programming concepts have such a wide array (pun intended) of expression that it was hard for university graduates to use another university's functional programming language; which was why Haskell came to be. :) Casey On Fri, Jan 17, 2014 at 10:14 AM, ?mer Sinan A?acan wrote: > Hi all, > > I recently got myself thinking about programming languages and their > effects on programmers. I already knew that concept of "linguistic > relativity" ( http://en.wikipedia.org/wiki/Linguistic_relativity ) > and I was thinking that this may be relevant with programming too, > although I don't have any concrete evidence. I was wondering if anyone > else also find that idea of programming language's effect of the > programmer interesting. Do we have any research on that kinds of > things? > > Thanks, > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- -- Regards, KC -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Thu Jan 23 02:16:16 2014 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Thu, 23 Jan 2014 15:16:16 +1300 Subject: [Haskell-cafe] Why Maybe exists if there is Either? In-Reply-To: <1390382631.2528.2.camel@kirk> References: <52CEB728.8040807@gmail.com> <52CEBEDF.5070908@artyom.me> <52CECFF6.4040007@gmail.com> <52CED39A.4060505@artyom.me> <52CF4CE3.2010502@artyom.me> <1390382631.2528.2.camel@kirk> Message-ID: On 22/01/2014, at 10:23 PM, Joachim Breitner wrote: > Am Mittwoch, den 22.01.2014, 14:56 +1300 schrieb Richard A. O'Keefe: >> If there is _any_ sane way to reverse a Unicode string, >> which I rather doubt, >> it would be _horrible_ to implement it. > > I suggest this: > >> reverse unicode_str = '\u202E' : unicode_str > > ?It works great! According to "Unicode Demystified", The Unicode bidirectional text layout algorithm (or "bi-di algorithm," as it is most commonly called) is possibly the most complicated and difficult-to- understand aspect of the Unicode standard. Considering the rest of Unicode, that says a LOT. This particular example using RIGHT-TO-LEFT OVERRIDE is a neat hack, but as a *general* way to reverse strings it's a FAIL: let s="\u202DIt's harder than you think." '\u202E' : s You will see no reversal in the output. Reverting to the original topic, Maybe and Either signify different things to human beings, and in the original libraries, the cost of having both was negligible compared with the benefits. Just recently I was revising some code in another language, where they had the equivalent of infinity = 99999.0 to serve as the initial value in a "search for the cheapest element and its cost" loop, and I suggested the equivalent of using Maybe (Cost, Item) instead, on the grounds that when you make up an "arbitrary" value it's a bad sign. In fact making this change led me to a deeper understanding of what the algorithm could do and a clarifying shift in its structure. (Amongst other things, the original code actually _relied_ on infinity + finite > infinity, which is not the way infinities are supposed to behave.) Representing Maybe as Either with an arbitrary value made up to be the "missing" value seems to me like just such a bad sign. From ok at cs.otago.ac.nz Thu Jan 23 02:52:54 2014 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Thu, 23 Jan 2014 15:52:54 +1300 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? In-Reply-To: References: Message-ID: On 23/01/2014, at 1:36 PM, KC wrote: > I would say it is more the concepts one uses than the programming language that has an effect on the programmer. > > After learning one OOP language it is not that hard to pick up another OOP language It's not clear to me that that's true. Consider: my first OO language was Smalltalk. - everything is an object - there is no pointer arithmetic - bounds checking is obligatory - integers are bounded - single inheritance - no static types - anonymous functions used *extensively* and nest - classes are objects - you can define a variable in a class that belongs to the *class* (not its instances) but such that its subclasses (not their instances) have their own copy; inherited methods work on the receiver's copy My third OO language was C++ - numbers are not objects - there is pointer arithmetic - bounds checking was not available - integers have machine-dependent bounds - multiple inheritance - statically typed - no anonymous functions and no function nesting - classes were not objects - class instance variables are not available At least half the design patterns in the Gang Of Four book either make no sense for or are trivial in Smalltalk. What C++ programmer would ever think of passing a class as a parameter to a function so it could create instances of different classes? What C++ programmer, finding _that_ couldn't be done, would next try to pass an object-creating function? Answer: a Smalltalk or Lisp programmer writing C++. What Smalltalk programmer, faced with let's say a parsing problem, would ever say "I'll define a combinator for that"? Answer: one who knows Haskell and is about to switch back to it. What I see here is that a programming language has *many* aspects and exposure to native style in several of them definitely enlarges what you find easy to _think_ of, whereas the one you are using right now affects what is _easy to express_ once thought of. One thing we're seeing is a lot of convergence: current Fortran is an OO language with modules _and_ good array-crunching support, there are C, C++, and Objective C compilers that support anonymous functions (and Java, we keep being told, will get them Real Soon Now), LINQ in C# was inspired by functional programming, ... Right now, there are just three surviving languages where I trust myself to do concurrent programming without stupid blunders that take ages to fix: Ada, Erlang, and Haskell. We still need *new* ideas. From mbrock at goula.sh Thu Jan 23 09:13:19 2014 From: mbrock at goula.sh (Mikael Brockman) Date: Thu, 23 Jan 2014 10:13:19 +0100 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? References: Message-ID: ?mer Sinan A?acan writes: > Hi all, > > I recently got myself thinking about programming languages and their > effects on programmers. I already knew that concept of "linguistic > relativity" ( http://en.wikipedia.org/wiki/Linguistic_relativity ) > and I was thinking that this may be relevant with programming too, > although I don't have any concrete evidence. I was wondering if anyone > else also find that idea of programming language's effect of the > programmer interesting. Do we have any research on that kinds of > things? The Stanford Encyclopedia of Philosophy has a pretty good page about the "linguistic relativity hypothesis." Here's a quote from Sapir in 1929 followed by some random thoughts of mine on your (very interesting) question: "Human beings do not live in the objective world alone, nor alone in the world of social activity as ordinarily understood, but are very much at the mercy of the particular language which has become the medium of expression for their society." I think our tendency to form communities (societies?) around programming languages is interesting in this context. Rubyists, Pythonistas, Schemers, hackathons, mailing lists & IRC, conferences, books, and so on. Without considering community, it seems hard to say even what a programming language is. Are "idioms" part of language, for example? In natural language, we can't judge fluency based on adherence to a formal grammar; we need to consider dialectal (even "sociolectal") competence, range of vocabulary, and so on. In programming, we are bound by formal grammars, but they still don't capture the whole thing. (That language and culture are hard to tease apart seems like a commonplace notion. I think it's one reason why the concept of "linguistic relativity" seems somehow vacuous or at least hard to pin down in a productive way. It's one of those "controversial" ideas, right? -- that nobody really knows what to do with, or whether it's even falsifiable, and so on.) So given that involvement with a programming language is to some extent inextricable from community involvement, I think we can look there for some interesting effects. When someone becomes interested in Haskell and later develops a taste for algebra and starts spending weekends reading abstract math textbooks, that's a pretty significant influence, right? There's an interesting meme in the Haskell world, which I think I first heard in a talk by Simon Peyton-Jones, that laziness -- though sometimes useful in itself -- is mostly a way to keep up a demand for pure semantics, which is what's really important. So that's a formal language feature consciously designed to influence our behavior as a community, to make sure we don't stray from the pure vision of our ancestors (so to speak). It's a kind of metaprogramming -- the language programs us! It'd be interesting to read stories and research about individuals or even groups who have for some reason switched from one primary programming language to another. What happened? There are a lot of applicable Dijkstra quotes. For example the classic: "It is practically impossible to teach good programming to students that have had a prior exposure to BASIC: as potential programmers they are mentally mutilated beyond hope of regeneration." Similar reasons are given for why university programs should begin with teaching a functional language, to instill certain good habits and values. Anyway, sorry for the longwindedness; I don't really have a thesis to drive, just writing down some thoughts. It's fun to think about the topic but it's so huge! -- Mikael Brockman (@mbrock) From simonyarde at me.com Thu Jan 23 13:46:53 2014 From: simonyarde at me.com (Simon Yarde) Date: Thu, 23 Jan 2014 13:46:53 +0000 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? In-Reply-To: <04986EB9-738A-449A-9DF1-D4351350B9FB@me.com> References: <87d2jjpp2k.fsf@gmail.com> <04986EB9-738A-449A-9DF1-D4351350B9FB@me.com> Message-ID: <97F8B129-7DD7-4EF4-8842-9313C5BA9132@me.com> > programming ... languages, and in particular the way that programmers use them, afford a > capacity for essentially limitless amounts of abstraction, unlike human > language and human communication. Au contraire! Humans use just such powerful abstractions in language, arts and sciences ? what we call humanity is built on no less. They're called *memes*. The only difference is that humans communicate on a foundation of shared experience that is a little more fuzzy and infinitely richer than the result of a data-base lookup. Simon Yarde On 22 Jan 2014, at 23:35, Keshav Kini wrote: > Lucas Paul writes: >> This is my take, as a CS undergraduate. >> >> I'm not sure if we can say that a programmer's language of choice >> determines the way they think about programming (the strong version of >> linguistic relativity for programming, as I see it). But I think it's >> fairly obvious that the language we choose to use to solve a problem >> affects how we think about the solution. That's basically the entire >> raison d'?tre for domain-specific languages (DSLs)! >> >> DSLs are popular (and becoming more so) precisely because the right >> choice of DSL can make expressing the solution to a particular kind of >> problem almost trivial. A poor choice can almost doom an endeavor. >> Imagine trying to query a database in assembly language. No SQL. It >> would at the very least require some mental gymnastics that a SELECT >> statement simply obviates. > > I think this can be partially explained by noting that programming > languages, and in particular the way that programmers use them, afford a > capacity for essentially limitless amounts of abstraction, unlike human > language and human communication. For example, I might easily have a > magic library that does exactly what I want, with bindings for my > programming language of choice, in which case I don't need to think > about what to do, I just call the appropriate function. In human > communication, while someone might have perfectly formulated exactly the > idea I want to communicate, it is rarely sufficient for the purpose of > communication to say "insert pages 204 through 356 of _Foobar_ by John > Doe here" in the middle of a conversation :) > > -Keshav > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mbrock at goula.sh Thu Jan 23 14:50:34 2014 From: mbrock at goula.sh (Mikael Brockman) Date: Thu, 23 Jan 2014 15:50:34 +0100 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? References: <87d2jjpp2k.fsf@gmail.com> <04986EB9-738A-449A-9DF1-D4351350B9FB@me.com> <97F8B129-7DD7-4EF4-8842-9313C5BA9132@me.com> Message-ID: Simon Yarde writes: >> programming ... languages, and in particular the way that programmers >> use them, afford a capacity for essentially limitless amounts of >> abstraction, unlike human language and human communication. > > Au contraire! Humans use just such powerful abstractions in language, > arts and sciences ? what we call humanity is built on no less. > They're called *memes*. > > The only difference is that humans communicate on a foundation of > shared experience that is a little more fuzzy and infinitely richer > than the result of a data-base lookup. Humanities people sometimes talk about "namedropping," like on a philosophy podcast[1] where one of the ground rules is No namedropping! Don't make arguments that hinge on something other than what we've agreed to read. Don't say, "You'd understand me if you'd only read *Capitalism is Fine, Now Shut Up*, by The Man." So just introducing a name (or even an ISBN number) isn't enough to establish an abstraction in the humanities -- you need to work for it, and new abstractions will probably remain fringey and unloved for a few years until they're accepted as part of normal discourse. There are similar issues in programming, like when introducing brand new abstract typeclasses, combinators, concepts, and so on. Even introducing a dependency on a 3rd party library can sometimes resemble a kind of "namedropping." But it's easier to get away with it in software! -- Mikael Brockman (@mbrock) [1]: The Partially Examined Life, http://www.partiallyexaminedlife.com/, have this rule, with a new bogus example at the start of each episode; the quoted one is from the episode on *The Gay Science*. From georg+haskell at schaathun.net Thu Jan 23 16:24:03 2014 From: georg+haskell at schaathun.net (Hans Georg Schaathun) Date: Thu, 23 Jan 2014 16:24:03 +0000 Subject: [Haskell-cafe] Sorting a Repa Array Message-ID: <20140123162403.GA27904@golay.schaathun.net> Hi, I am trying to parallellise genetic algorithms using haskell, but I get stuck at the stage where I need to sort the array of chromosomes based on their fitness. Using Repa, I am neither able to find a nice library implementation to sort an array, nor can I figure out how to generate a new array modifying only a few entries. I am not at a stage where I need to optimise execution time. It is still at the stage of learning exercise, wrt both to genetic algorithms, haskell, and splittable pseudo-random number generators. Thus, I would be grateful for both na?ve and clever suggestions :-) Except for the sorting stage, the problem seems to well suited for Repa, with a chain of operations which can be mapped on the array. I am also planning to explore accelerate later for GPU work, and Repa seems to be a better step on the way than most other alternatives. My arrays are 1-D boxed arrays BTW. The entries are tuples including an Unboxed Vector (and a Double on which the sort order is defined). Doing it as a 2-D Unboxed Array is further down on the agenda; I need more practice before I get my head around using slices correctly. So, any advice? Whether it involves conversion to a data type where a library sort routine is available, a library sort routine I have missed, or how to create new deferred arrays by updating selected entries in the input array so that I can implement sorting myself. TIA -- :-- Hans Georg From chaddai.fouche at gmail.com Thu Jan 23 16:59:55 2014 From: chaddai.fouche at gmail.com (=?UTF-8?B?Q2hhZGRhw68gRm91Y2jDqQ==?=) Date: Thu, 23 Jan 2014 17:59:55 +0100 Subject: [Haskell-cafe] Sorting a Repa Array In-Reply-To: <20140123162403.GA27904@golay.schaathun.net> References: <20140123162403.GA27904@golay.schaathun.net> Message-ID: Convert to a vector (that should be efficient since I understand that it is the underlying representation anyway), then use the sort algorithms available in the vector-algorithms package then convert back. You'll need to use modify to apply the sort (since it works on MVector). I don't think there's a simpler or better solution right now. -- Jeda? -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Jan 23 17:08:13 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 23 Jan 2014 12:08:13 -0500 Subject: [Haskell-cafe] Sorting a Repa Array In-Reply-To: References: <20140123162403.GA27904@golay.schaathun.net> Message-ID: Indeed! Repa and accelerate are really designed as a showcase for pushing the cutting edge of fusion based optimization. Sorting algorithms, fast matrix multiply, and other locality sensitive algorithms are precisely their weakest spot. To the point where you really shouldn't try to use them for such! I second the vector-algorithms recommendation. Be prepared for some large compile times, those sorting algs do a lot of Inlining to give you good perf. On Thursday, January 23, 2014, Chadda? Fouch? wrote: > Convert to a vector (that should be efficient since I understand that it > is the underlying representation anyway), then use the sort algorithms > available in the vector-algorithms package then convert back. You'll need > to use modify to apply the sort (since it works on MVector). > > I don't think there's a simpler or better solution right now. > -- > Jeda? > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From keshav.kini at gmail.com Thu Jan 23 17:34:52 2014 From: keshav.kini at gmail.com (Keshav Kini) Date: Thu, 23 Jan 2014 09:34:52 -0800 Subject: [Haskell-cafe] off-topic question: how well do you think linguistic relativity applies to PLs and programming? References: <87d2jjpp2k.fsf@gmail.com> <04986EB9-738A-449A-9DF1-D4351350B9FB@me.com> <97F8B129-7DD7-4EF4-8842-9313C5BA9132@me.com> Message-ID: <871tzyppoj.fsf@gmail.com> Mikael Brockman writes: > So just introducing a name (or even an ISBN number) isn't enough to > establish an abstraction in the humanities -- you need to work for it, > and new abstractions will probably remain fringey and unloved for a few > years until they're accepted as part of normal discourse. > > There are similar issues in programming, like when introducing brand new > abstract typeclasses, combinators, concepts, and so on. Even > introducing a dependency on a 3rd party library can sometimes resemble a > kind of "namedropping." But it's easier to get away with it in > software! Right, that's what I was talking about. Actually, not only is it easier to get away with it in software, it's the preferred option -- DRY is good and NIH is bad, etc. -Keshav From georg+haskell at schaathun.net Thu Jan 23 18:40:42 2014 From: georg+haskell at schaathun.net (Hans Georg Schaathun) Date: Thu, 23 Jan 2014 18:40:42 +0000 Subject: [Haskell-cafe] Sorting a Repa Array In-Reply-To: References: <20140123162403.GA27904@golay.schaathun.net> Message-ID: <20140123184042.GA5167@golay.schaathun.net> On Thu, Jan 23, 2014 at 05:59:55PM +0100, Chadda? Fouch? wrote: > Convert to a vector (that should be efficient since I understand that it is > the underlying representation anyway), then use the sort algorithms > available in the vector-algorithms package then convert back. You'll need > to use modify to apply the sort (since it works on MVector). Thanks a lot; I think I am starting to comprehend. I suppose this is the modify you mean: modify :: (forall s. MVector s a -> ST s ()) -> Vector a -> Vector a forall is a chapter of Haskell which I have not made it through, but with a concrete example which I need, I should manage tomorrow. Thanks again, to both responders. -- :-- Hans Georg From bos at serpentine.com Thu Jan 23 23:02:36 2014 From: bos at serpentine.com (Bryan O'Sullivan) Date: Thu, 23 Jan 2014 15:02:36 -0800 Subject: [Haskell-cafe] hpaste.org is expiring Message-ID: I've held the domain for a few years. I am not going to renew it. If you'd like to take it over, please let me know immediately and I'll send you an unlock code so you can transfer it. -------------- next part -------------- An HTML attachment was scrubbed... URL: From robstewart57 at gmail.com Thu Jan 23 23:12:41 2014 From: robstewart57 at gmail.com (Rob Stewart) Date: Thu, 23 Jan 2014 23:12:41 +0000 Subject: [Haskell-cafe] hpaste.org is expiring In-Reply-To: References: Message-ID: If no-one is able to pick up this domain, could hpaste be moved with the haskell.org infrastructure, i.e. hpaste.haskell.org ? On 23 January 2014 23:02, Bryan O'Sullivan wrote: > I've held the domain for a few years. I am not going to renew it. If you'd > like to take it over, please let me know immediately and I'll send you an > unlock code so you can transfer it. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From jeremy at n-heptane.com Fri Jan 24 00:04:25 2014 From: jeremy at n-heptane.com (Jeremy Shaw) Date: Thu, 23 Jan 2014 18:04:25 -0600 Subject: [Haskell-cafe] hpaste.org is expiring In-Reply-To: References: Message-ID: I'll take it. On Thu, Jan 23, 2014 at 5:02 PM, Bryan O'Sullivan wrote: > I've held the domain for a few years. I am not going to renew it. If you'd > like to take it over, please let me know immediately and I'll send you an > unlock code so you can transfer it. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From allbery.b at gmail.com Fri Jan 24 00:22:06 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 23 Jan 2014 19:22:06 -0500 Subject: [Haskell-cafe] hpaste.org is expiring In-Reply-To: References: Message-ID: On Thu, Jan 23, 2014 at 6:12 PM, Rob Stewart wrote: > If no-one is able to pick up this domain, could hpaste be moved with > the haskell.org infrastructure, i.e. hpaste.haskell.org ? I think you might be a little confused as to what is going on? The point is keeping a name alive that is widely linked so that those links don't break. hpaste,org is the old (and widely linked) name of what is currently lpaste.net. This serves more than the Haskell community; while it might make sense to have *a* name for it in the haskell.org namespace, it may not be appropriate for that to be the *only* name --- and in any case, that question would be applicable to lpaste.net, not hpaste.org. (And then we'd have the same problem anyway as there are existing links to lpaste.net that people would want to keep live.) [Semi-aside: apparently Central Michigan University tried at one point to claim that they should have the cmu.edu domain because they were more well known than Carnegie Mellon (the .edu registrar has procedures for this). Eventually someone pointed out to them just how many computer science links go to cmu.edu, and that they would be obligated to handle those links in some way that did not bring down on them the wrath of many, many people. Arbitrarily breaking links is a bad thing on the modern Internet.] -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From darthdeus at gmail.com Fri Jan 24 03:54:35 2014 From: darthdeus at gmail.com (Jakub Arnold) Date: Fri, 24 Jan 2014 04:54:35 +0100 Subject: [Haskell-cafe] How does one read complicated type signatures? Message-ID: Hello world, I?ve just started playing with the http-conduit package and started inspecting type signatures of some of the functions, and I stumbled upon many things that look like this *Main Network.HTTP.Conduit> :t withManager withManager :: (monad-control-0.3.2.2:Control.Monad.Trans.Control.MonadBaseControl IO m, transformers-0.3.0.0:Control.Monad.IO.Class.MonadIO m) => (Manager -> resourcet-0.4.10:Control.Monad.Trans.Resource.Internal.ResourceT m a) -> m a The question is ? how am I supposed to read these? It seems that they wrap around (maybe) 80 characters, which makes them unreadable ? and the package prefixes also don?t really help. I?d like to point out here that I?m really a noob without any practical experience in Haskell, I?ve just read a few books. So I don?t have a problem understanding the concepts, but more and more often I find myself struggling just to read the type signature correctly Thanks for any tips, Jakub -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Jan 24 04:12:23 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 23 Jan 2014 23:12:23 -0500 Subject: [Haskell-cafe] How does one read complicated type signatures? In-Reply-To: References: Message-ID: On Thu, Jan 23, 2014 at 10:54 PM, Jakub Arnold wrote: > *Main Network.HTTP.Conduit> :t withManager > withManager > :: (monad-control-0.3.2.2:Control.Monad.Trans.Control.MonadBaseControl > IO m, > transformers-0.3.0.0:Control.Monad.IO.Class.MonadIO m) => > (Manager > -> resourcet-0.4.10:Control.Monad.Trans.Resource.Internal.ResourceT > m a) > -> m a > > The question is ? how am I supposed to read these? It seems that they wrap > around (maybe) 80 characters, which makes them unreadable ? and the package > prefixes also don?t really help. > Import the modules named (usually ignoring any "Internal" or "Class" part), and their names will shorten. Since the names aren't in scope in ghci, it's being specific about where it found them. (MonadBaseControl IO m, MonadIO m) => (Manager ResourceT m a) -> m a should be what you see with Control.Monad.Trans.Control, Control.Monad.Trans (because I happen to know the "public" export of MonadIO is there), and Control.Monad.Trans.Resource in scope. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From bos at serpentine.com Fri Jan 24 04:58:36 2014 From: bos at serpentine.com (Bryan O'Sullivan) Date: Thu, 23 Jan 2014 20:58:36 -0800 Subject: [Haskell-cafe] hpaste.org is expiring In-Reply-To: References: Message-ID: On Thu, Jan 23, 2014 at 4:04 PM, Jeremy Shaw wrote: > I'll take it. > Thanks, Jeremy - I just sent the transfer code to you privately. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rob at mars.org Fri Jan 24 06:33:34 2014 From: rob at mars.org (Rob Leslie) Date: Thu, 23 Jan 2014 22:33:34 -0800 Subject: [Haskell-cafe] Arithmetic overflow Message-ID: <32CC1E5D-7CAB-4F19-BA44-F52859F18B96@mars.org> Greetings, I have a question about arithmetic overflow in Haskell -- actually, probably specifically in GHC. It?s my understanding from the Haskell 2010 Language Report that ?The results of exceptional conditions (such as overflow or underflow) on the fixed-precision numeric types [e.g. Int] are undefined; an implementation may choose error (?, semantically), a truncated value, or a special value such as infinity, indefinite, etc.? In the documentation for Data.Int from the current release of the Haskell Platform, I read that ?All arithmetic is performed modulo 2^n, where n is the number of bits in the type.? However, there seems to be at least one exception to this promise, namely: ?> (minBound :: Int) `quot` (-1) *** Exception: arithmetic overflow Is this a bug? More specifically, is it intended to be safe to rely on the modulo arithmetic behavior of GHC in spite of the Language Report? And if so, should the above witnessed behavior still be expected? Thanks, -- Rob Leslie rob at mars.org From jpmoresmau at gmail.com Fri Jan 24 15:38:02 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Fri, 24 Jan 2014 16:38:02 +0100 Subject: [Haskell-cafe] Why is the Show instance of Text not used by showTerm? Message-ID: Hello cafe, I'm continuing my adventures with the GHC API. I'm following the code given at http://www.haskell.org/haskellwiki/GHC/As_a_library#Running_interactive_statementsto run statements like in GHCi, but the behavior sometimes puzzles me. If I load a simple module: module Test where import qualified Data.Text as T And then run the statement T.pack \"test\", I expect to see "test" back. But I get Data.Text.Internal.Text _ 0 4. If I run "show $ T.Pack \"test\"" I get the expected result. Text _ 0 4 seems to be the output of the showText debugging function in Data.Text, that I don't see used in the Show instance. And looking at the GHC code (Debugger.hs) it does perform a show of the expression given. Why doesn't it work? What subtlety am I missing? Thanks! JP -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From erkokl at gmail.com Fri Jan 24 16:42:44 2014 From: erkokl at gmail.com (Levent Erkok) Date: Fri, 24 Jan 2014 08:42:44 -0800 Subject: [Haskell-cafe] Arithmetic overflow In-Reply-To: <32CC1E5D-7CAB-4F19-BA44-F52859F18B96@mars.org> References: <32CC1E5D-7CAB-4F19-BA44-F52859F18B96@mars.org> Message-ID: I think this is a bug. It also seems to impact explicitly sized types: Prelude Data.Int> (minBound::Int8) `quot` (-1) *** Exception: arithmetic overflow Prelude Data.Int> (minBound::Int16) `quot` (-1) *** Exception: arithmetic overflow You should definitely report it. I think there's a pending release of GHC, so they might be able to fix it shortly. -Levent. On Thu, Jan 23, 2014 at 10:33 PM, Rob Leslie wrote: > Greetings, > > I have a question about arithmetic overflow in Haskell -- actually, > probably specifically in GHC. > > It?s my understanding from the Haskell 2010 Language Report that ?The > results of exceptional conditions (such as overflow or underflow) on the > fixed-precision numeric types [e.g. Int] are undefined; an implementation > may choose error (?, semantically), a truncated value, or a special value > such as infinity, indefinite, etc.? > > In the documentation for Data.Int from the current release of the Haskell > Platform, I read that ?All arithmetic is performed modulo 2^n, where n is > the number of bits in the type.? > > However, there seems to be at least one exception to this promise, namely: > > ?> (minBound :: Int) `quot` (-1) > *** Exception: arithmetic overflow > > Is this a bug? > > More specifically, is it intended to be safe to rely on the modulo > arithmetic behavior of GHC in spite of the Language Report? And if so, > should the above witnessed behavior still be expected? > > Thanks, > > -- > Rob Leslie > rob at mars.org > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpmoresmau at gmail.com Fri Jan 24 18:09:12 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Fri, 24 Jan 2014 19:09:12 +0100 Subject: [Haskell-cafe] Why is the Show instance of Text not used by showTerm? In-Reply-To: <1390583545.13983.74916317.79EE9636@webmail.messagingengine.com> References: <1390583545.13983.74916317.79EE9636@webmail.messagingengine.com> Message-ID: Karl, thanks, but the flag is set to True... And setting it to False doesn't change the output. I'll continue my investigations! JP On Fri, Jan 24, 2014 at 6:12 PM, Karl Voelker wrote: > On Fri, Jan 24, 2014, at 07:38 AM, JP Moresmau wrote: > > Hello cafe, I'm continuing my adventures with the GHC API. I'm following > the code given at > http://www.haskell.org/haskellwiki/GHC/As_a_library#Running_interactive_statementsto run statements like in GHCi, but the behavior sometimes puzzles me. > > If I load a simple module: > > module Test where > import qualified Data.Text as T > > And then run the statement T.pack \"test\", I expect to see "test" back. > But I get Data.Text.Internal.Text _ 0 4. If I run "show $ T.Pack \"test\"" > I get the expected result. Text _ 0 4 seems to be the output of the > showText debugging function in Data.Text, that I don't see used in the Show > instance. And looking at the GHC code (Debugger.hs) it does perform a show > of the expression given. Why doesn't it work? What subtlety am I missing? > > > The example you linked to calls showTerm ( > http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/src/Debugger.html#showTerm) > which seems to have two different paths depending on the > Opt_PrintEvldWithShow dynflag. One path appears to use show, and the other > does not. > > -Karl > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpmoresmau at gmail.com Fri Jan 24 18:32:27 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Fri, 24 Jan 2014 19:32:27 +0100 Subject: [Haskell-cafe] Why is the Show instance of Text not used by showTerm? In-Reply-To: References: <1390583545.13983.74916317.79EE9636@webmail.messagingengine.com> Message-ID: OK, all simply, show is not called if the term is considered not fully evaluated, which seems to be my case. So I'll need to write my own showTerm or maybe pprintClosureCommand, returning a String instead of just writing to standard out. Bypassing the isFullEvaluatedTerm condition gives me the expected result. Thanks, JP On Fri, Jan 24, 2014 at 7:09 PM, JP Moresmau wrote: > Karl, thanks, but the flag is set to True... And setting it to False > doesn't change the output. I'll continue my investigations! > > JP > > > On Fri, Jan 24, 2014 at 6:12 PM, Karl Voelker wrote: > >> On Fri, Jan 24, 2014, at 07:38 AM, JP Moresmau wrote: >> >> Hello cafe, I'm continuing my adventures with the GHC API. I'm following >> the code given at >> http://www.haskell.org/haskellwiki/GHC/As_a_library#Running_interactive_statementsto run statements like in GHCi, but the behavior sometimes puzzles me. >> >> If I load a simple module: >> >> module Test where >> import qualified Data.Text as T >> >> And then run the statement T.pack \"test\", I expect to see "test" back. >> But I get Data.Text.Internal.Text _ 0 4. If I run "show $ T.Pack \"test\"" >> I get the expected result. Text _ 0 4 seems to be the output of the >> showText debugging function in Data.Text, that I don't see used in the Show >> instance. And looking at the GHC code (Debugger.hs) it does perform a show >> of the expression given. Why doesn't it work? What subtlety am I missing? >> >> >> The example you linked to calls showTerm ( >> http://www.haskell.org/ghc/docs/latest/html/libraries/ghc/src/Debugger.html#showTerm) >> which seems to have two different paths depending on the >> Opt_PrintEvldWithShow dynflag. One path appears to use show, and the other >> does not. >> >> -Karl >> > > > > -- > JP Moresmau > http://jpmoresmau.blogspot.com/ > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From rob at mars.org Fri Jan 24 22:55:07 2014 From: rob at mars.org (Rob Leslie) Date: Fri, 24 Jan 2014 14:55:07 -0800 Subject: [Haskell-cafe] Arithmetic overflow In-Reply-To: References: <32CC1E5D-7CAB-4F19-BA44-F52859F18B96@mars.org> Message-ID: <862BC6CD-13E5-4C51-8EA6-29F363164C71@mars.org> On Jan 24, 2014, at 8:42 AM, Levent Erkok wrote: > On Thu, Jan 23, 2014 at 10:33 PM, Rob Leslie wrote: > >> ?> (minBound :: Int) `quot` (-1) >> *** Exception: arithmetic overflow >> >> Is this a bug? > > I think this is a bug. It also seems to impact explicitly sized types: > > Prelude Data.Int> (minBound::Int8) `quot` (-1) > *** Exception: arithmetic overflow > Prelude Data.Int> (minBound::Int16) `quot` (-1) > *** Exception: arithmetic overflow > > You should definitely report it. I think there?s a pending release of GHC, so they might be able to fix it shortly. Thanks for the feedback; I went ahead and created a ticket: https://ghc.haskell.org/trac/ghc/ticket/8695 Cheers, -- Rob Leslie rob at mars.org From lukexipd at gmail.com Sun Jan 26 10:23:10 2014 From: lukexipd at gmail.com (Luke Iannini) Date: Sun, 26 Jan 2014 02:23:10 -0800 Subject: [Haskell-cafe] GHC iOS ARMv7/ARMv7s fat support completed Message-ID: Hi folks, Happy to report that I've finished an approach to armv7/armv7s fat compilation, just in time for 7.8's imminent release. You'll find the necessary scripts here: https://github.com/ghc-ios/ghc-ios-scripts and the latest instructions for building GHC for iOS usage here: https://ghc.haskell.org/trac/ghc/wiki/Building/CrossCompiling/iOS I've also added support for a perf-cross BuildFlavour, which will give a higher-performance and profiling-ready build that matches what we'll be putting together as the official 7.8 GHC iOS binaries: https://ghc.haskell.org/trac/ghc/ticket/8700 Cheers Luke -------------- next part -------------- An HTML attachment was scrubbed... URL: From efsubenovex at gmail.com Sun Jan 26 18:33:02 2014 From: efsubenovex at gmail.com (Schell Scivally) Date: Sun, 26 Jan 2014 10:33:02 -0800 Subject: [Haskell-cafe] [Haskell-iPhone] GHC iOS ARMv7/ARMv7s fat support completed In-Reply-To: References: Message-ID: Awesome! I'll be spinning this up soon. On Sun, Jan 26, 2014 at 2:23 AM, Luke Iannini wrote: > Hi folks, > > Happy to report that I've finished an approach to armv7/armv7s fat > compilation, just in time for 7.8's imminent release. > > You'll find the necessary scripts here: > https://github.com/ghc-ios/ghc-ios-scripts > > and the latest instructions for building GHC for iOS usage here: > https://ghc.haskell.org/trac/ghc/wiki/Building/CrossCompiling/iOS > > I've also added support for a perf-cross BuildFlavour, which will give a > higher-performance and profiling-ready build that matches what we'll be > putting together as the official 7.8 GHC iOS binaries: > https://ghc.haskell.org/trac/ghc/ticket/8700 > > Cheers > Luke > > _______________________________________________ > iPhone mailing list > iPhone at haskell.org > http://www.haskell.org/mailman/listinfo/iphone > > -- Schell Scivally http://blog.efnx.com http://github.com/schell http://twitter.com/schellsan -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Sun Jan 26 19:16:57 2014 From: trebla at vex.net (Albert Y. C. Lai) Date: Sun, 26 Jan 2014 14:16:57 -0500 Subject: [Haskell-cafe] Cabal version constraint seems to be ignored. In-Reply-To: <52DFBCF6.60801@carlo-hamalainen.net> References: <52DFBCF6.60801@carlo-hamalainen.net> Message-ID: <52E55F29.4040301@vex.net> On 14-01-22 07:43 AM, Carlo Hamalainen wrote: > I have two versions of Cabal, both are visible: > > $ ghc-pkg expose Cabal-1.16.0 > $ ghc-pkg expose Cabal-1.18.1.2 > > I clone and build my package. Since I have GHC 7.6.3 it uses > Cabal-1.16.0 (as specified in ghc-imported-from.cabal): > But my program doesn't run: > But I can't expect a user to know that they have to hide Cabal-1.18.1.2. It seems that you are using GHC API. Then your program starts a GHC session, which is not unlike an average ghci session, in particular: A. It will load and link libraries afresh during run time. This is independent of whatever your executable is linked with. B. And the default choice of libraries is, clearly: the newest unhidden version. Therefore, when your GHC session also has to work with compiled code built against older versions, there will be incompatibilities. What do you tell your users? I don't know. This is just one tip of a problem so widespread and entrenched, you cannot solve it alone. I cannot solve it alone, unless I am Imperator for Life. The problem is cultural and due to opinion leaders. The problem is: believing that multiple versions co-exist happily. Opinion leaders themselves do not run into troubles because they are cabal experts and they always tread cunningly through the jungle of multiple versions. That is what's wrong with opinion leaders. They are so expert that their ways are unsuitable for the rest of us. For the rest of us, cabal-install would be much better off defaulting to disallowing multiple versions in the first place. (It could provide overriding options to the experts.) In the particular case of the library Cabal 1.16 vs 1.18, Duncun Coutts explicitly said in IRC freenode #haskell that their co-existence is pretty harmless. Let your trouble be a lesson against that leader opinion. And let ghc-mod's trouble be another. P.S. cabal-install goes out of its way to dictate library versions to ghc. It begins with -hide-all-packages, then it recites, one by one, -package base-4.1.0.0, -package Cabal-1.16.0, -package text-0.11.3.1,... Are you going to bother to do the same? From qdunkan at gmail.com Mon Jan 27 02:14:51 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Sun, 26 Jan 2014 18:14:51 -0800 Subject: [Haskell-cafe] evaluating CAFs at compile time In-Reply-To: References: Message-ID: On Sat, Jan 18, 2014 at 6:57 PM, Carter Schonwald wrote: > Point being, I think your pointing to an idea other people are (also) > interested in exploring for ghc, and that there's some interesting > subltelties to it. I was actually kind of hoping someone would point out some of those subtleties. I figure there must be some since I don't know of any compiler other than the common lisp ones that implements something like this. Another thing that it could be useful for is that when declaring data it's sometimes convenient to declare data structures separately and then stitch them together, e.g. xs = makeXs [("name1", a), ("name2", b), ...] -- makeXs uses list order to infer things ys = makeYs [('x', ..., "name2"), ('y', ..., "name1")] -- same for makeYs things = do (c, ..., name) <- ys let x = fromMaybe (error "ack") $ lookup name xs return $ Thing name c x ... Not only would compile time evaluation eliminate some startup overhead, it could enforce at compile time that the names match up, along with other invariants in literal data, such as uniqueness, or that your keymap doesn't have any collisions, or whatever. From qdunkan at gmail.com Mon Jan 27 04:59:18 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Sun, 26 Jan 2014 20:59:18 -0800 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: <52D34359.3050401@fuuzetsu.co.uk> References: <52D34359.3050401@fuuzetsu.co.uk> Message-ID: On Sun, Jan 12, 2014 at 5:37 PM, Mateusz Kowalczyk wrote: > * Bold markup added. The syntax is two underscores around what you want > bold. Note, we still do not support multi-line markup. It's possible but > it's a design choice not to support it. This is all great, but I have a concern about this one. Do we really need more than one kind of emphasis? Actually, mostly what I don't like is the / markup, because slashes are common, e.g. URLs and paths, and it's a pain to escape them all the time. Messed up formatting due to forgetting a backslash is very common in my docs, and I've even seen it in GHC docs as well. I would prefer to swap /s for *s because *s seem less common, but of course that would break stuff. And I'm sure there are people out there who like using /s for emphasis, so we don't need to repaint that bikeshed. But at least we can avoid adding even more special characters you need to remember to escape. And bold emphasis seems like it's redundant with italics emphasis. From guthrie at mum.edu Mon Jan 27 05:07:14 2014 From: guthrie at mum.edu (Gregory Guthrie) Date: Sun, 26 Jan 2014 23:07:14 -0600 Subject: [Haskell-cafe] hoogle - find functions as arrows? Message-ID: <08EF9DA445C4B5439C4733E1F35705BA0338A94AD996@MAIL.cs.mum.edu> I was surprised that a Hoogle search for: (a -> b) -> (a -> c) -> a -> (b, c) No results found Didn't find this: (&&&) :: Arrow a => a b c -> a b c' -> a b (c, c') Since functions are arrows; yes? I suppose I can see why it might not, but it seems that it would be nice if it did. -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Mon Jan 27 05:10:54 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 27 Jan 2014 05:10:54 +0000 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: References: <52D34359.3050401@fuuzetsu.co.uk> Message-ID: <52E5EA5E.2070400@fuuzetsu.co.uk> On 27/01/14 04:59, Evan Laforge wrote: > On Sun, Jan 12, 2014 at 5:37 PM, Mateusz Kowalczyk > wrote: >> * Bold markup added. The syntax is two underscores around what you want >> bold. Note, we still do not support multi-line markup. It's possible but >> it's a design choice not to support it. > > This is all great, but I have a concern about this one. Do we really > need more than one kind of emphasis? > > Actually, mostly what I don't like is the / markup, because slashes > are common, e.g. URLs and paths, and it's a pain to escape them all > the time. Messed up formatting due to forgetting a backslash is very > common in my docs, and I've even seen it in GHC docs as well. This is an existing markup and we won't change it because every piece of documentation using it will break. I have seen plenty of documentation with ugly markup because someone forgot to escape something but it is unavoidable. I agree that ?/? might not be the best character but it's as good as any other for this purpose. If it was something else, people would complain about that instead. > I would prefer to swap /s for *s because *s seem less common, but of > course that would break stuff. And I'm sure there are people out > there who like using /s for emphasis, so we don't need to repaint that > bikeshed. But at least we can avoid adding even more special > characters you need to remember to escape. If it was ?*? then we'd have to remember that instead (and ?*? is also a very common character). The reason I picked two underscores for bold is precisely because it's not that common. > And bold emphasis seems like it's redundant with italics emphasis. You're free to not use it. A lot of people wanted bold (including myself). It looks different, it's a different kind of emphasis, why not include it? I don't understand your point of view on this. Are you not against different kinds of lists? I mean, all of them enumerate things so why bother with 3 different kinds, right? It is also now a bit late for this post, documentation and tests have been written and it's all done and dusted, just waiting for the imminent 7.8 release. There was plenty of time for input. If you have a pressing reason why bold shouldn't be included, file a Haddock ticket. -- Mateusz K. From qdunkan at gmail.com Mon Jan 27 05:24:09 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Sun, 26 Jan 2014 21:24:09 -0800 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: <52E5EA5E.2070400@fuuzetsu.co.uk> References: <52D34359.3050401@fuuzetsu.co.uk> <52E5EA5E.2070400@fuuzetsu.co.uk> Message-ID: On Sun, Jan 26, 2014 at 9:10 PM, Mateusz Kowalczyk wrote: > You're free to not use it. A lot of people wanted bold (including > myself). It looks different, it's a different kind of emphasis, why > not include it? I don't understand your point of view on this. Are you > not against different kinds of lists? I mean, all of them enumerate > things so why bother with 3 different kinds, right? Well, every bit of markup added is permanent, and it's one more thing to remember to escape. Redundant kinds of lists aren't so bad because they're not taking up a whole character, but yes if it were just me I would only have one kind of list. Anyway, I missed that it's double underscore, not *s. In that case, it won't be a burden so I'm not worried. Concern withdrawn! From fuuzetsu at fuuzetsu.co.uk Mon Jan 27 05:31:37 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 27 Jan 2014 05:31:37 +0000 Subject: [Haskell-cafe] Haddock changes pushed upstream In-Reply-To: References: <52D34359.3050401@fuuzetsu.co.uk> <52E5EA5E.2070400@fuuzetsu.co.uk> Message-ID: <52E5EF39.3060105@fuuzetsu.co.uk> On 27/01/14 05:24, Evan Laforge wrote: > On Sun, Jan 26, 2014 at 9:10 PM, Mateusz Kowalczyk > wrote: >> You're free to not use it. A lot of people wanted bold (including >> myself). It looks different, it's a different kind of emphasis, why >> not include it? I don't understand your point of view on this. Are you >> not against different kinds of lists? I mean, all of them enumerate >> things so why bother with 3 different kinds, right? > > Well, every bit of markup added is permanent, and it's one more thing > to remember to escape. Redundant kinds of lists aren't so bad because > they're not taking up a whole character, but yes if it were just me I > would only have one kind of list. Anyway, I missed that it's double > underscore, not *s. In that case, it won't be a burden so I'm not > worried. Concern withdrawn! > Oh, great. You actually reminded me the real reason why ?*? is not bold: we already use ?*? for unordered lists and it'd be impossible to tell which one you want at the beginning of a paragraph. -- Mateusz K. From ian at skybluetrades.net Mon Jan 27 06:31:04 2014 From: ian at skybluetrades.net (Ian Ross) Date: Mon, 27 Jan 2014 07:31:04 +0100 Subject: [Haskell-cafe] [ANN]: arb-fft 0.1, Fast Fourier transform library Message-ID: Dear Cafe, I'm happy to announce the first release of arb-fft, a pure Haskell FFT implementation for arbitrary length vectors: http://hackage.haskell.org/package/arb-fft This is probably more of pedagogical interest than anything else, since there's a long series of blog articles describing the development of the package, indexed at http://skybluetrades.net/haskell-fft-index.html The package has some interesting features beyond the usual "textbook" powers-of-two FFT algorithm. In particular, it uses a mixed-radix decomposition of composite input lengths, uses Rader's algorithm for large prime factors and has an empirical benchmarking scheme using Criterion for FFT plan selection. The performance of arb-fft is within a factor of 10 of FFTW for most input sizes, which isn't too bad for a pure Haskell with only a relatively limited amount of work done on optimisation. Commentary is very welcome, as are offers to help with any of the tasks listed in the last blog article: http://skybluetrades.net/blog/posts/2014/01/27/data-analysis-fft-14.html Hackage: http://hackage.haskell.org/package/arb-fft GitHub: https://github.com/ian-ross/arb-fft Blog article index: http://skybluetrades.net/haskell-fft-index.html -- Ian Ross Tel: +43(0)6804451378 ian at skybluetrades.net www.skybluetrades.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From sean at functionaljobs.com Mon Jan 27 07:00:03 2014 From: sean at functionaljobs.com (Functional Jobs) Date: Mon, 27 Jan 2014 02:00:03 -0500 Subject: [Haskell-cafe] New Functional Programming Job Opportunities Message-ID: <52e603fa23c86@functionaljobs.com> Here are some functional programming job opportunities that were posted recently: Haskell Developer at Zalora http://functionaljobs.com/jobs/8678-haskell-developer-at-zalora Cheers, Sean Murphy FunctionalJobs.com From dhelta.diaz at gmail.com Mon Jan 27 12:36:18 2014 From: dhelta.diaz at gmail.com (=?UTF-8?Q?Daniel_D=C3=ADaz_Casanueva?=) Date: Mon, 27 Jan 2014 13:36:18 +0100 Subject: [Haskell-cafe] [ANN]: arb-fft 0.1, Fast Fourier transform library In-Reply-To: References: Message-ID: Thank you!! I have been a long time waiting for something like this. I have been using FFTW, but I wanted a Haskell solution. On Mon, Jan 27, 2014 at 7:31 AM, Ian Ross wrote: > Dear Cafe, > > I'm happy to announce the first release of arb-fft, a pure Haskell FFT > implementation for arbitrary length vectors: > http://hackage.haskell.org/package/arb-fft > > This is probably more of pedagogical interest than anything else, since > there's a long series of blog articles describing the development of the > package, indexed at http://skybluetrades.net/haskell-fft-index.html > > The package has some interesting features beyond the usual "textbook" > powers-of-two FFT algorithm. In particular, it uses a mixed-radix > decomposition of composite input lengths, uses Rader's algorithm for large > prime factors and has an empirical benchmarking scheme using Criterion for > FFT plan selection. > > The performance of arb-fft is within a factor of 10 of FFTW for most input > sizes, which isn't too bad for a pure Haskell with only a relatively > limited amount of work done on optimisation. > > Commentary is very welcome, as are offers to help with any of the tasks > listed in the last blog article: > http://skybluetrades.net/blog/posts/2014/01/27/data-analysis-fft-14.html > > > Hackage: http://hackage.haskell.org/package/arb-fft > GitHub: https://github.com/ian-ross/arb-fft > Blog article index: http://skybluetrades.net/haskell-fft-index.html > > -- > Ian Ross Tel: +43(0)6804451378 ian at skybluetrades.net > www.skybluetrades.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Mon Jan 27 20:09:34 2014 From: alan.zimm at gmail.com (AlanKim Zimmerman) Date: Mon, 27 Jan 2014 22:09:34 +0200 Subject: [Haskell-cafe] Target Selection in HaRe In-Reply-To: References: Message-ID: Some feedback HaRe 0.7.1.1 now loads each of the targets in the cabal file in turn, and stores the module graph for each. When the clients of a module are requested for a refactoring it takes the union of all modules in the reachability graph, making sure to treat each Main module as distinct. So renaming a function in a library will rename it in the executables, tests, and benchmarks too. Alan On Tue, Jan 14, 2014 at 12:43 PM, JP Moresmau wrote: > OK, but I don't really understand how you can do a rename with only "some" > of the targets. You mean that if I rename a function used in the main > module of two executables in one single project, the rename will only be > effective in one executable, and the other one will stop compiling? That > sounds sub-optimal to me. A lot of project now have several targets; > executables, test-suites, benchmarks... > > JP > > > On Tue, Jan 14, 2014 at 11:31 AM, AlanKim Zimmerman wrote: > >> I'm trying to steer away from a database if I can avoid it. And also >> hoping to not have to store meta information outside the GHC AST to do a >> multi phase refactor, e.g. the usage information to know where a name was >> used for renaming. >> >> I think the union will work best, with some kind of selection of the >> current main to work with, or just store the additional info for the main >> modules. >> >> Alan >> On Jan 14, 2014 6:25 PM, "JP Moresmau" wrote: >> >>> Can't you do the union of module graphs for all targets by adding the >>> file names to the modules or something, so you could have several main >>> modules using different files in a general graph? >>> What I know is how we do renames in EclipseFP: we use the GHC API to >>> generate usage information for each different targets then the data is >>> actually stored in a DB, and the Java code uses this info to perform >>> renames everywhere (across projects, even). Of course you don't want all >>> that, but you should be able to decorate the module graph with file names >>> and perform the union. >>> >>> JP >>> >>> >>> On Tue, Jan 14, 2014 at 11:04 AM, AlanKim Zimmerman >> > wrote: >>> >>>> The Haskell Refactorer now makes use of the GHC API to load and >>>> typecheck the code to be refactored. >>>> >>>> It uses ghc-mod internally to identify a project cabal file, and >>>> extract the targets in it. >>>> >>>> The current code attempts to load all the targets into the module >>>> graph, to make sure that when a project is refactored the ancillary parts >>>> such as tests and benchmarks are refactored too, e.g. when renaming a >>>> function. >>>> >>>> The problem is that GHC is unable to load more than one main file. >>>> >>>> I am trying to decide on the best way of resolving this in terms of a >>>> user of HaRe, where it should 'just work' most of the time. The actual >>>> refactoring is done by calling the HaRe executable with command line >>>> arguments. >>>> >>>> Options that seem viable are >>>> >>>> 1. require the names of the target(s) to be loaded to be passed in as >>>> command line arguments. >>>> >>>> This means the IDE integration is going to have to provide a way of >>>> deciding the scope of the refactoring. >>>> >>>> 2. Create a config file that lives in the project directory and >>>> specifies the targets to be loaded >>>> >>>> 3. Try to build up a union of the module graph for all the targets, >>>> excluding all main modules. >>>> >>>> The problem with this is that it then becomes difficult to refactor a >>>> main module. >>>> >>>> 4. A different option, or blend of the above.e.g. load the union but >>>> specify the specific main module. >>>> >>>> >>>> Does anyone have any preferences in terms of this? >>>> >>>> Alan >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>>> >>> >>> >>> -- >>> JP Moresmau >>> http://jpmoresmau.blogspot.com/ >>> >> > > > -- > JP Moresmau > http://jpmoresmau.blogspot.com/ > -------------- next part -------------- An HTML attachment was scrubbed... URL: From althainz at gmail.com Mon Jan 27 21:54:50 2014 From: althainz at gmail.com (Peter Althainz) Date: Mon, 27 Jan 2014 22:54:50 +0100 Subject: [Haskell-cafe] Announcement - HGamer3D release candidate 0.3.0 Message-ID: Dear All, I'm happy to announce HGamer3D, version 0.3.0 as a release candidate on Github. Please look here: http://www.hgamer3d.org and https://github.com/urs-of-the-backwoods/HGamer3D . The new version features: - Linux ! (in addition to Windows) - HBind tool to generate and administrate bindings Of course I would be largely interested in feedback for the final release of 0.3.0. Best regards Peter Althainz -------------- next part -------------- An HTML attachment was scrubbed... URL: From winterkoninkje at gmail.com Mon Jan 27 22:16:54 2014 From: winterkoninkje at gmail.com (wren ng thornton) Date: Mon, 27 Jan 2014 17:16:54 -0500 Subject: [Haskell-cafe] [ANN]: arb-fft 0.1, Fast Fourier transform library In-Reply-To: References: Message-ID: On Mon, Jan 27, 2014 at 1:31 AM, Ian Ross wrote: > I'm happy to announce the first release of arb-fft, a pure Haskell FFT > implementation for arbitrary length vectors: > http://hackage.haskell.org/package/arb-fft > > This is probably more of pedagogical interest than anything else, since > there's a long series of blog articles describing the development of the > package, indexed at http://skybluetrades.net/haskell-fft-index.html > > The package has some interesting features beyond the usual "textbook" > powers-of-two FFT algorithm. In particular, it uses a mixed-radix > decomposition of composite input lengths, uses Rader's algorithm for large > prime factors and has an empirical benchmarking scheme using Criterion for > FFT plan selection. > > The performance of arb-fft is within a factor of 10 of FFTW for most input > sizes, which isn't too bad for a pure Haskell with only a relatively limited > amount of work done on optimisation. > > Commentary is very welcome, as are offers to help with any of the tasks > listed in the last blog article: > http://skybluetrades.net/blog/posts/2014/01/27/data-analysis-fft-14.html > > Hackage: http://hackage.haskell.org/package/arb-fft > GitHub: https://github.com/ian-ross/arb-fft > Blog article index: http://skybluetrades.net/haskell-fft-index.html Thanks, I've noticed the posts but hadn't had time to devote to them last semester. Now that I'm more free, I look forward to digging into them and, mayhaps, offering some optimization patches. -- Live well, ~wren From andrew at operationaldynamics.com Mon Jan 27 23:06:04 2014 From: andrew at operationaldynamics.com (Andrew Cowie) Date: Tue, 28 Jan 2014 10:06:04 +1100 Subject: [Haskell-cafe] Builder vs Builder Message-ID: <1390863964.18469.4.camel@nervous-energy> Does anyone know whether blaze-builder is deprecated in favour of bytestring's new Builder module, or are they the same, or... I know Simon is the evil wizard cackling in his dank lair in both cases, and I do remember him saying he was trying to get his work "upstream" into bytestring, but I haven't heard anyone suggesting we should be using Data.ByteString.Lazy.Builder instead of Blaze.ByteString.Builder I can only imagine the integration with the allocation routines is much better now that it's in bytestring, but on the other hand it's hard to upgrade bytestring ? it being so low in the stack ? so perhaps the original blaze remains the right choice from a bugfix and stability perspective. Thoughts? AfC Sydney From johan.tibell at gmail.com Tue Jan 28 07:21:01 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 27 Jan 2014 23:21:01 -0800 Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: <1390863964.18469.4.camel@nervous-energy> References: <1390863964.18469.4.camel@nervous-energy> Message-ID: Simon's work have made it into bytestring, so you should use that one if you can. On Mon, Jan 27, 2014 at 3:06 PM, Andrew Cowie < andrew at operationaldynamics.com> wrote: > Does anyone know whether blaze-builder is deprecated in favour of > bytestring's new Builder module, or are they the same, or... > > I know Simon is the evil wizard cackling in his dank lair in both cases, > and I do remember him saying he was trying to get his work "upstream" > into bytestring, but I haven't heard anyone suggesting we should be > using Data.ByteString.Lazy.Builder instead of Blaze.ByteString.Builder > > I can only imagine the integration with the allocation routines is much > better now that it's in bytestring, but on the other hand it's hard to > upgrade bytestring -- it being so low in the stack -- so perhaps the > original blaze remains the right choice from a bugfix and stability > perspective. > > Thoughts? > > AfC > Sydney > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kazu at iij.ad.jp Tue Jan 28 07:41:34 2014 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Tue, 28 Jan 2014 16:41:34 +0900 (JST) Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: <1390863964.18469.4.camel@nervous-energy> References: <1390863964.18469.4.camel@nervous-energy> Message-ID: <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Hi Andrew, > Does anyone know whether blaze-builder is deprecated in favour of > bytestring's new Builder module, or are they the same, or... Recently I supported both blaze-builder and bytestring's Builder in "fast-logger". So, I would like to share my experience. bytestring is tightly bound to GHC's version. GHC version 7.6.x is shipped with bytestring 0.10.0.2 while GHC version 7.8.x will be shipped with bytestring 0.10.4.0. To my impression, bytestring's APIs are stable and good enough in bytestring 0.10.4.0. For instance, while bytestring 0.10.4.0 provides Data.ByteString.Builder and .Extra, bytestring 0.10.0.2 does not. (Please don't confuse them with Data.ByteString.Lazy.Builder.) So, I think switching blaze-builder to bytestring's Builder is too early at this moment. But if you are interested, you can get ready for bytestring's Builder. You can use the following C's macro: #if MIN_VERSION_bytestring(0,10,4) For more information, please see the source of fast-logger. --Kazu From greg at gregorycollins.net Tue Jan 28 08:30:38 2014 From: greg at gregorycollins.net (Gregory Collins) Date: Tue, 28 Jan 2014 09:30:38 +0100 Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: <20140128.164134.1204768223271068591.kazu@iij.ad.jp> References: <1390863964.18469.4.camel@nervous-energy> <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: If you want to try to support the last two or three haskell platform versions, you're committing to supporting GHC 7.4.x and bytestring 0.9.2.1 still. Debian stable still has 7.4.1. Plus there are one or two things that are in blaze-builder that people use that didn't make it into bytestring. So I agree with Kazu, I'm not ready to switch to bytestring builder yet --- especially since 0.10.0.2 was kind of botched. I don't like preprocessor tricks here. If the public haddock docs on Hackage are built on a new machine but the user's machine is old, confusion is sure to result. You're forcing your downstream users to put in all of the same #ifdefs you used, too. Sad though it may be I think we just have to wait a year until everyone's on a capable version of bytestring, then deprecate blaze-builder and make the switch as quickly as possible. G On Tue, Jan 28, 2014 at 8:41 AM, Kazu Yamamoto wrote: > Hi Andrew, > > > Does anyone know whether blaze-builder is deprecated in favour of > > bytestring's new Builder module, or are they the same, or... > > Recently I supported both blaze-builder and bytestring's Builder in > "fast-logger". So, I would like to share my experience. > > bytestring is tightly bound to GHC's version. GHC version 7.6.x is > shipped with bytestring 0.10.0.2 while GHC version 7.8.x will be > shipped with bytestring 0.10.4.0. > > To my impression, bytestring's APIs are stable and good enough in > bytestring 0.10.4.0. For instance, while bytestring 0.10.4.0 provides > Data.ByteString.Builder and .Extra, bytestring 0.10.0.2 does not. > (Please don't confuse them with Data.ByteString.Lazy.Builder.) > > So, I think switching blaze-builder to bytestring's Builder is too > early at this moment. But if you are interested, you can get ready for > bytestring's Builder. You can use the following C's macro: > > #if MIN_VERSION_bytestring(0,10,4) > > For more information, please see the source of fast-logger. > > --Kazu > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Gregory Collins -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Tue Jan 28 08:34:47 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Tue, 28 Jan 2014 09:34:47 +0100 Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: References: <1390863964.18469.4.camel@nervous-energy> <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: I've never had any problems installing newer bytestring versions. Unless you're using the GHC API, what is the problem? Regards, Erik On Tue, Jan 28, 2014 at 9:30 AM, Gregory Collins wrote: > If you want to try to support the last two or three haskell platform > versions, you're committing to supporting GHC 7.4.x and bytestring 0.9.2.1 > still. Debian stable still has 7.4.1. Plus there are one or two things that > are in blaze-builder that people use that didn't make it into bytestring. So > I agree with Kazu, I'm not ready to switch to bytestring builder yet --- > especially since 0.10.0.2 was kind of botched. > > I don't like preprocessor tricks here. If the public haddock docs on Hackage > are built on a new machine but the user's machine is old, confusion is sure > to result. You're forcing your downstream users to put in all of the same > #ifdefs you used, too. > > Sad though it may be I think we just have to wait a year until everyone's on > a capable version of bytestring, then deprecate blaze-builder and make the > switch as quickly as possible. > > G > > > On Tue, Jan 28, 2014 at 8:41 AM, Kazu Yamamoto wrote: >> >> Hi Andrew, >> >> > Does anyone know whether blaze-builder is deprecated in favour of >> > bytestring's new Builder module, or are they the same, or... >> >> Recently I supported both blaze-builder and bytestring's Builder in >> "fast-logger". So, I would like to share my experience. >> >> bytestring is tightly bound to GHC's version. GHC version 7.6.x is >> shipped with bytestring 0.10.0.2 while GHC version 7.8.x will be >> shipped with bytestring 0.10.4.0. >> >> To my impression, bytestring's APIs are stable and good enough in >> bytestring 0.10.4.0. For instance, while bytestring 0.10.4.0 provides >> Data.ByteString.Builder and .Extra, bytestring 0.10.0.2 does not. >> (Please don't confuse them with Data.ByteString.Lazy.Builder.) >> >> So, I think switching blaze-builder to bytestring's Builder is too >> early at this moment. But if you are interested, you can get ready for >> bytestring's Builder. You can use the following C's macro: >> >> #if MIN_VERSION_bytestring(0,10,4) >> >> For more information, please see the source of fast-logger. >> >> --Kazu >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > -- > Gregory Collins > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From kazu at iij.ad.jp Tue Jan 28 08:41:08 2014 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Tue, 28 Jan 2014 17:41:08 +0900 (JST) Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: References: <1390863964.18469.4.camel@nervous-energy> <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: <20140128.174108.817801888584162815.kazu@iij.ad.jp> Greg, > I don't like preprocessor tricks here. If the public haddock docs on > Hackage are built on a new machine but the user's machine is old, confusion > is sure to result. You're forcing your downstream users to put in all of > the same #ifdefs you used, too. In the case of fast-logger, Builder is hidden in an abstract data type. I hope that users of fast-logger would not be confused. --Kazu From kazu at iij.ad.jp Tue Jan 28 08:42:53 2014 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Tue, 28 Jan 2014 17:42:53 +0900 (JST) Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: References: <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: <20140128.174253.810715653055503999.kazu@iij.ad.jp> Erik, > I've never had any problems installing newer bytestring versions. > Unless you're using the GHC API, what is the problem? I don't remember in detail. But when I installed the new bytestring to the current HP, I hit upon many dep hells. So, I gave up and uninstalled the new bytestring. --Kazu From ian at skybluetrades.net Tue Jan 28 10:10:28 2014 From: ian at skybluetrades.net (Ian Ross) Date: Tue, 28 Jan 2014 11:10:28 +0100 Subject: [Haskell-cafe] To LLVM or not to LLVM... Message-ID: A package I just released (arb-fft) gets about a 17% performance boost from using GHC's LLVM backend (on my machine at least). That seems a big enough gain that I put "-fllvm" into the ghc-options field in the Cabal file for the package. Unfortunately, that means the package won't install unless you have the LLVM tools installed. What's the best thing to do? Use the native code generator by default and add a Cabal flag to install using LLVM? Just take the "-fllvm" out and add a note to the Cabal file description to tell people to install using LLVM if they have it? A quick survey of packages on Hackage reveals only very few instances where the "-fllvm" flag appears in Cabal files, which makes me suspect that I'm doing it wrong. -- Ian Ross Tel: +43(0)6804451378 ian at skybluetrades.net www.skybluetrades.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From hoerdegen at funktional.info Tue Jan 28 10:52:47 2014 From: hoerdegen at funktional.info (=?ISO-8859-15?Q?Heinrich_H=F6rdegen?=) Date: Tue, 28 Jan 2014 11:52:47 +0100 Subject: [Haskell-cafe] Munich Haskell Meeting Message-ID: <52E78BFF.6000402@funktional.info> Dear all, I hope that you had good start into 2014. Munich's Haskell enthusiasts (or other declarative languages) meet for their first get-together in 2014 on Thu, 30th of January at 19h30 at Cafe Puck. If you plan to join, please go here and hit the button: http://www.haskell-munich.de/dates With my best wishes for this year, Heinrich From corentin.dupont at gmail.com Tue Jan 28 11:03:23 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Tue, 28 Jan 2014 12:03:23 +0100 Subject: [Haskell-cafe] manage effects in a DSL Message-ID: Hi Haskell-Caf?ists! I have a small DSL for a game. Some instructions have effects (change the game state), some not. -> In short, my question is: how can I semantically separate instructions with effect from the others? i.e. how can I mark down and track those effects? Here is a simplified version of the DSL I use. First some boilerplate: > {-# LANGUAGE GADTs #-} > import Control.Monad > import Control.Monad.State > import Control.Monad.Free This is the DSL: > data Exp a where > ReadAccount :: Exp Int > WriteAccount :: Exp Int -> Exp () > SetVictory :: Exp Bool -> Exp () > OnTimer :: Exp () -> Exp () > Return :: a -> Exp a > Bind :: Exp a -> (a -> Exp b) -> Exp b It can read and write to an account (belonging to the state of the game), set a victory condition, and trigger some event every minute. > instance Monad Exp where > return = Return > (>>=) = Bind > instance Functor Exp where > fmap f e = Bind e $ Return . f With that you can write: > victoryRule :: Exp () > victoryRule = SetVictory $ do > m <- ReadAccount > return (m > 100) "victoryRule" sets the victory condition to be: "if there is more than 100 gold in the account, you win." This is the game state: > data Game = Game { bankAccount :: Int, > victory :: Exp Bool, > timerEvent :: Exp ()} The evaluation of "Exp" can be: > eval :: Exp a -> State Game a > eval (SetVictory v) = modify (\g -> g{victory = v}) > eval ReadAccount = get >>= return . bankAccount > eval _ = undefined -- etc. If you evaluate "victoryRule", you change the Game state by setting the victory field. Then, each time you will evaluate the victory field, you will know if you won or not (depending on your account...). This is all well and good, but imagine if you write: > victoryRule' :: Exp () > victoryRule' = SetVictory $ do > m <- ReadAccount > WriteAccount (return $ m + 1) > return (m > 100) Ho no! Now each time a player is refreshing his screen (on the web interface), the victory condition is re-evaluated to be displayed again, and the bank account is increased by 1! This is not what we want. We should allow only effect-less (pure) instructions in the victory field, like readAccount, but not WriteAccount. How would you do that? I tried with the Free monad to delimit those effects. I re-write each primitives, marking them with the special type "Effect", when needed. > type Effect = Free Exp > -- readAccount remain the same: it has no effect > readAccount :: Exp Int > readAccount = ReadAccount > --writeAccount is marked as having an effect > writeAccount :: Exp Int -> Effect (Exp ()) > writeAccount ei = Pure $ WriteAccount ei > --onTimer is able to trigger an effect every minute > onTimer :: Effect (Exp ()) -> Effect (Exp ()) > onTimer e = Pure $ OnTimer $ iter join e > --victoryRule can be re-written like this, note that effects are rejected now > victoryRule'' :: Effect (Exp ()) > victoryRule'' = Pure $ SetVictory $ do > m <- readAccount > --writeAccount (return $ m + 1) --will be rejected at compile time (good)! > return (m > 100) > --increase my bank account by 1 every minute > myTimer :: Effect (Exp ()) > myTimer = onTimer $ do > m <- lift readAccount > writeAccount (return $ m + 1) I don't know if I got it right at all... How does it sound? It only bothers me that in this context "Pure" really means "Impure" :) Do you think of any other solution? Cheers, Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From carette at mcmaster.ca Tue Jan 28 12:29:51 2014 From: carette at mcmaster.ca (Jacques Carette) Date: Tue, 28 Jan 2014 07:29:51 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: Message-ID: <52E7A2BF.40800@mcmaster.ca> The simplest way would be to add a phantom type parameter to Exp, i.e. data Exp e a where The 'e' variable would be used to track (and propagate) effects. It is then up to you to design your 'effect system' as you wish. Jacques On 2014-01-28 6:03 AM, Corentin Dupont wrote: > -> In short, my question is: how can I semantically separate > instructions with effect from the others? i.e. how can I mark down and > track those effects? > This is the DSL: > > > data Exp a where > > ReadAccount :: Exp Int > > WriteAccount :: Exp Int -> Exp () > > SetVictory :: Exp Bool -> Exp () > > OnTimer :: Exp () -> Exp () > > Return :: a -> Exp a > > Bind :: Exp a -> (a -> Exp b) -> Exp b > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simons at cryp.to Tue Jan 28 14:07:03 2014 From: simons at cryp.to (Peter Simons) Date: Tue, 28 Jan 2014 15:07:03 +0100 Subject: [Haskell-cafe] To LLVM or not to LLVM... References: Message-ID: <87d2jc42uw.fsf@write-only.cryp.to> Hi Ian, > What's the best thing to do? Use the native code generator by default > and add a Cabal flag to install using LLVM? I would assume that everybody who wants to compile your package with LLVM can simply configure the build with "--ghc-option=-fllvm", no? A Cabal flag for the same purpose might make sense, IMHO, if there are other build parameters that change when compiling with LLVM (like CPP defines, etc.), but it's my understanding that this is not the case? Take care, Peter From corentin.dupont at gmail.com Tue Jan 28 14:29:27 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Tue, 28 Jan 2014 15:29:27 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: <52E7A2BF.40800@mcmaster.ca> References: <52E7A2BF.40800@mcmaster.ca> Message-ID: Hi Jacques, I thought about that, but I wasn't able to push it further. It would look like that: > data Effect = Effect > data Exp e a where > ReadAccount :: Exp () Int > WriteAccount :: Exp () Int -> Exp Effect () > SetVictory :: Exp () Bool -> Exp Effect () > OnTimer :: Exp Effect () -> Exp Effect () Is that right? Should Exp () and Exp Effect belong to two different monads? I was thinking of monad transformers to bridge between the two... On Tue, Jan 28, 2014 at 1:29 PM, Jacques Carette wrote: > The simplest way would be to add a phantom type parameter to Exp, i.e. > data Exp e a where > > The 'e' variable would be used to track (and propagate) effects. It is > then up to you to design your 'effect system' as you wish. > > Jacques > > > On 2014-01-28 6:03 AM, Corentin Dupont wrote: > > -> In short, my question is: how can I semantically separate > instructions with effect from the others? i.e. how can I mark down and > track those effects? > > > This is the DSL: > > > data Exp a where > > ReadAccount :: Exp Int > > WriteAccount :: Exp Int -> Exp () > > SetVictory :: Exp Bool -> Exp () > > OnTimer :: Exp () -> Exp () > > Return :: a -> Exp a > > Bind :: Exp a -> (a -> Exp b) -> Exp b > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jake.mcarthur at gmail.com Tue Jan 28 14:53:29 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Tue, 28 Jan 2014 09:53:29 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: Message-ID: You can use type classes and polymorphism to get the restrictions you want. class Monad m => ReadExp m where readAccount :: m Int onTimer :: m () -> m () class ReadExp m => WriteExp m where writeAccount :: Int -> m () setVistory :: Bool -> m () instance ReadExp Exp ... instance WriteExp exp ... -- works fine victoryRule :: ReadExp m => m () ... -- ends up being a type error for the implementation you gave victoryRule' :: ReadExp m => m () ... And nicely, you can still use both of them in more general computations that also need write access. On Tue, Jan 28, 2014 at 6:03 AM, Corentin Dupont wrote: > Hi Haskell-Caf?ists! > I have a small DSL for a game. Some instructions have effects (change the > game state), some not. > -> In short, my question is: how can I semantically separate instructions > with effect from the others? i.e. how can I mark down and track those > effects? > > Here is a simplified version of the DSL I use. > First some boilerplate: > > > {-# LANGUAGE GADTs #-} > > import Control.Monad > > import Control.Monad.State > > import Control.Monad.Free > > This is the DSL: > > > data Exp a where > > ReadAccount :: Exp Int > > WriteAccount :: Exp Int -> Exp () > > SetVictory :: Exp Bool -> Exp () > > OnTimer :: Exp () -> Exp () > > Return :: a -> Exp a > > Bind :: Exp a -> (a -> Exp b) -> Exp b > > It can read and write to an account (belonging to the state of the game), > set a victory condition, and trigger some event every minute. > > > instance Monad Exp where > > return = Return > > (>>=) = Bind > > > instance Functor Exp where > > fmap f e = Bind e $ Return . f > > With that you can write: > > > victoryRule :: Exp () > > victoryRule = SetVictory $ do > > m <- ReadAccount > > return (m > 100) > > "victoryRule" sets the victory condition to be: "if there is more than 100 > gold in the account, you win." > > This is the game state: > > > data Game = Game { bankAccount :: Int, > > victory :: Exp Bool, > > timerEvent :: Exp ()} > > The evaluation of "Exp" can be: > > > eval :: Exp a -> State Game a > > eval (SetVictory v) = modify (\g -> g{victory = v}) > > eval ReadAccount = get >>= return . bankAccount > > eval _ = undefined -- etc. > > If you evaluate "victoryRule", you change the Game state by setting the > victory field. Then, each time you will evaluate the victory field, you > will know if you won or not (depending on your account...). > This is all well and good, but imagine if you write: > > > victoryRule' :: Exp () > > victoryRule' = SetVictory $ do > > m <- ReadAccount > > WriteAccount (return $ m + 1) > > return (m > 100) > > Ho no! Now each time a player is refreshing his screen (on the web > interface), the victory condition is re-evaluated to be displayed again, > and the bank account is increased by 1! > This is not what we want. We should allow only effect-less (pure) > instructions in the victory field, like readAccount, but not WriteAccount. > > How would you do that? > > I tried with the Free monad to delimit those effects. > I re-write each primitives, marking them with the special type "Effect", > when needed. > > > type Effect = Free Exp > > > -- readAccount remain the same: it has no effect > > readAccount :: Exp Int > > readAccount = ReadAccount > > > --writeAccount is marked as having an effect > > writeAccount :: Exp Int -> Effect (Exp ()) > > writeAccount ei = Pure $ WriteAccount ei > > > --onTimer is able to trigger an effect every minute > > onTimer :: Effect (Exp ()) -> Effect (Exp ()) > > onTimer e = Pure $ OnTimer $ iter join e > > > --victoryRule can be re-written like this, note that effects are > rejected now > > victoryRule'' :: Effect (Exp ()) > > victoryRule'' = Pure $ SetVictory $ do > > m <- readAccount > > --writeAccount (return $ m + 1) --will be rejected at compile time > (good)! > > return (m > 100) > > > --increase my bank account by 1 every minute > > myTimer :: Effect (Exp ()) > > myTimer = onTimer $ do > > m <- lift readAccount > > writeAccount (return $ m + 1) > > I don't know if I got it right at all... How does it sound? > It only bothers me that in this context "Pure" really means "Impure" :) > Do you think of any other solution? > > Cheers, > Corentin > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Tue Jan 28 15:01:49 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Tue, 28 Jan 2014 16:01:49 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: Message-ID: That's nice! I will experiment with that... On Tue, Jan 28, 2014 at 3:53 PM, Jake McArthur wrote: > You can use type classes and polymorphism to get the restrictions you want. > > class Monad m => ReadExp m where > readAccount :: m Int > onTimer :: m () -> m () > > class ReadExp m => WriteExp m where > writeAccount :: Int -> m () > setVistory :: Bool -> m () > > instance ReadExp Exp ... > > instance WriteExp exp ... > > -- works fine > victoryRule :: ReadExp m => m () > ... > > -- ends up being a type error for the implementation you gave > victoryRule' :: ReadExp m => m () > ... > > And nicely, you can still use both of them in more general computations > that also need write access. > > On Tue, Jan 28, 2014 at 6:03 AM, Corentin Dupont < > corentin.dupont at gmail.com> wrote: > >> Hi Haskell-Caf?ists! >> I have a small DSL for a game. Some instructions have effects (change the >> game state), some not. >> -> In short, my question is: how can I semantically separate instructions >> with effect from the others? i.e. how can I mark down and track those >> effects? >> >> Here is a simplified version of the DSL I use. >> First some boilerplate: >> >> > {-# LANGUAGE GADTs #-} >> > import Control.Monad >> > import Control.Monad.State >> > import Control.Monad.Free >> >> This is the DSL: >> >> > data Exp a where >> > ReadAccount :: Exp Int >> > WriteAccount :: Exp Int -> Exp () >> > SetVictory :: Exp Bool -> Exp () >> > OnTimer :: Exp () -> Exp () >> > Return :: a -> Exp a >> > Bind :: Exp a -> (a -> Exp b) -> Exp b >> >> It can read and write to an account (belonging to the state of the game), >> set a victory condition, and trigger some event every minute. >> >> > instance Monad Exp where >> > return = Return >> > (>>=) = Bind >> >> > instance Functor Exp where >> > fmap f e = Bind e $ Return . f >> >> With that you can write: >> >> > victoryRule :: Exp () >> > victoryRule = SetVictory $ do >> > m <- ReadAccount >> > return (m > 100) >> >> "victoryRule" sets the victory condition to be: "if there is more than >> 100 gold in the account, you win." >> >> This is the game state: >> >> > data Game = Game { bankAccount :: Int, >> > victory :: Exp Bool, >> > timerEvent :: Exp ()} >> >> The evaluation of "Exp" can be: >> >> > eval :: Exp a -> State Game a >> > eval (SetVictory v) = modify (\g -> g{victory = v}) >> > eval ReadAccount = get >>= return . bankAccount >> > eval _ = undefined -- etc. >> >> If you evaluate "victoryRule", you change the Game state by setting the >> victory field. Then, each time you will evaluate the victory field, you >> will know if you won or not (depending on your account...). >> This is all well and good, but imagine if you write: >> >> > victoryRule' :: Exp () >> > victoryRule' = SetVictory $ do >> > m <- ReadAccount >> > WriteAccount (return $ m + 1) >> > return (m > 100) >> >> Ho no! Now each time a player is refreshing his screen (on the web >> interface), the victory condition is re-evaluated to be displayed again, >> and the bank account is increased by 1! >> This is not what we want. We should allow only effect-less (pure) >> instructions in the victory field, like readAccount, but not WriteAccount. >> >> How would you do that? >> >> I tried with the Free monad to delimit those effects. >> I re-write each primitives, marking them with the special type "Effect", >> when needed. >> >> > type Effect = Free Exp >> >> > -- readAccount remain the same: it has no effect >> > readAccount :: Exp Int >> > readAccount = ReadAccount >> >> > --writeAccount is marked as having an effect >> > writeAccount :: Exp Int -> Effect (Exp ()) >> > writeAccount ei = Pure $ WriteAccount ei >> >> > --onTimer is able to trigger an effect every minute >> > onTimer :: Effect (Exp ()) -> Effect (Exp ()) >> > onTimer e = Pure $ OnTimer $ iter join e >> >> > --victoryRule can be re-written like this, note that effects are >> rejected now >> > victoryRule'' :: Effect (Exp ()) >> > victoryRule'' = Pure $ SetVictory $ do >> > m <- readAccount >> > --writeAccount (return $ m + 1) --will be rejected at compile time >> (good)! >> > return (m > 100) >> >> > --increase my bank account by 1 every minute >> > myTimer :: Effect (Exp ()) >> > myTimer = onTimer $ do >> > m <- lift readAccount >> > writeAccount (return $ m + 1) >> >> I don't know if I got it right at all... How does it sound? >> It only bothers me that in this context "Pure" really means "Impure" :) >> Do you think of any other solution? >> >> Cheers, >> Corentin >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lindsey at composition.al Tue Jan 28 15:53:10 2014 From: lindsey at composition.al (Lindsey Kuper) Date: Tue, 28 Jan 2014 07:53:10 -0800 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: Message-ID: On Tue, Jan 28, 2014 at 3:03 AM, Corentin Dupont wrote: > Hi Haskell-Caf?ists! > I have a small DSL for a game. Some instructions have effects (change the > game state), some not. > -> In short, my question is: how can I semantically separate instructions > with effect from the others? i.e. how can I mark down and track those > effects? Hi, Corentin, This is very much like what we did in our work on adding fine-grained effect specification to the Par monad in the LVish library (http://hackage.haskell.org/package/lvish). Just as Jacques suggested up-thread, we did it by adding an extra phantom type parameter to the monad which we call the "determinism level". At its simplest, there are only two of these levels, Det and QuasiDet, for deterministic and quasi-deterministic: data Determinism = Det | QuasiDet and the first parameter passed to the Par type constructor is of kind Determinism (we have to turn on the DataKinds extension for this). Doing so allows the static type of a Par computation to reflect its determinism or quasi-determinism guarantee. (The effects you can perform in deterministic computations are a subset of the ones you can do in quasi-deterministic computations.) The beginning of section 6 of our POPL paper on LVish (http://www.cs.indiana.edu/~lkuper/papers/lvish-popl14.pdf) discusses this feature. In more recent work, we've extended this to allow a more fine-grained menu of effects to choose from, to the point where we've begun calling it an "effect level" rather than merely "determinism level". Good luck with it! Lately I have gotten a lot of mileage out of thinking of monads as embedded DSLs. Projects like yours really put that analogy to use. :) Lindsey From ian at skybluetrades.net Tue Jan 28 15:56:56 2014 From: ian at skybluetrades.net (Ian Ross) Date: Tue, 28 Jan 2014 16:56:56 +0100 Subject: [Haskell-cafe] To LLVM or not to LLVM... In-Reply-To: <87d2jc42uw.fsf@write-only.cryp.to> References: <87d2jc42uw.fsf@write-only.cryp.to> Message-ID: Hi Peter, > I would assume that everybody who wants to compile your package with > LLVM can simply configure the build with "--ghc-option=-fllvm", no? > Absolutely, yes. I was just wondering about it as a matter of policy, particularly in terms of reverse dependencies (not that this package has any yet). If you install package A that depends on package B and package B gets a big performance boost from LLVM, things are fine if you install package B yourself and tell Cabal to build it with LLVM, but if Cabal installs it automatically as a dependency of package A, then it won't get built with LLVM (unless you install package A with that option too, but then you end up pushing the responsibility to handle package B's peculiarities upstream to its reverse dependencies). > A Cabal flag for the same purpose might make sense, IMHO, if there are > other build parameters that change when compiling with LLVM (like CPP > defines, etc.), but it's my understanding that this is not the case? > Right. I think I'll add a Cabal flag and worry about the reverse dependencies issue if the package ever has any! Cheers, Ian. -- Ian Ross Tel: +43(0)6804451378 ian at skybluetrades.net www.skybluetrades.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From sacha404 at gmail.com Tue Jan 28 18:08:14 2014 From: sacha404 at gmail.com (Sacha Sokoloski) Date: Tue, 28 Jan 2014 19:08:14 +0100 Subject: [Haskell-cafe] Lazy MWC Random? Message-ID: <52E7F20E.6090205@gmail.com> Dear Haskellers, I'm in a situation where I'd like to generate an infinite list of random elements (basically, I'm simulating stochastic systems). I feel like MWC Random is the fastest RNG available, but when I try to pull the infinite list out of RandST, it obviously doesn't halt, because ST is strict. Someone posted a way around this in this stack overflow thread: https://stackoverflow.com/questions/16248600/parallel-computations-with-fast-randomness-and-purity Which would fix my problem. My question is though, why isn't ST.Lazy included as a PrimMonad instance anyway? The best answer I can come up with is that, since evaluating the Generator is time dependent, it's best to make it strict to make sure that one's program isn't tapping into /dev/random at arbitrary times. In this way the best stackoverflow solution is quite good. It requires one to strictly generate a Seed (since that's the only way to do it), but then converts the ST Monad to the Lazy version to Lazify everything else. However, my understanding of PrimMonad is simply that it's a class of low level monads i.e. IO and ST, so if there's some deeper reason to this, it's beyond me. Another question that I'm puzzling over: In the stack overflow solution, they also make an effort to only have to generate the seed a single time. Is this important performance wise? What I suppose this must hinge upon, is whether in saving an ST s Gen to a Seed, the conversion from an immutable to mutable array requires a copy or not. Is that the full extent of the complexity of this? Is the stackoverflow solution ultimately the most efficient? Is using MWC Random to generate infinite lists and efficient solution anyway? Thanks for any insight, - Sacha Sokoloski From vlatko.basic at gmail.com Tue Jan 28 18:37:55 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Tue, 28 Jan 2014 19:37:55 +0100 Subject: [Haskell-cafe] How to pass a polymorphic function in a record? In-Reply-To: <52e603fa23c86@functionaljobs.com> References: <52e603fa23c86@functionaljobs.com> Message-ID: <52E7F903.3010100@gmail.com> Hello Cafe, I'm playing with Persistent and have modules that I'd like to use on several backends. This is simplified situation. In shared module: sqliteRun, postgresRun :: Text -> Int -> (ConnectionPool -> IO a) -> IO a sqliteRun = withSqlitePool postgresRun conStr = withPostgresqlPool (encodeUtf8 conStr) sqlRun :: Text -> Int -> SqlPersistM a -> IO a sqlRun conStr poolSize = postgresRun conStr poolSize . runSqlPersistMPool --sqlRun conStr poolSize = sqliteRun conStr poolSize . runSqlPersistMPool All works well if either 'sqlRun' above is commented/uncommented: In one of modules: data ThingCfg = ThingCfg { thingDb :: Text } listThings :: ThingCfg -> IO [Thing] listThings db = sqlRun (thingDb db) $ selectList ... findThing :: ThingId -> ThingCfg -> IO (Maybe Thing) findThing uid db = sqlRun (thingDb db) $ getBy ... On call site simply: let tdb = ThingCfg "test" ts <- listThings tdb I would like to specify 'sqliteRun' or 'postgresRun' function as (some) parameter on the call site, but do not know how. Something of imaginary solution: data ThingCfg = ThingCfg { thingDb :: Text, thingRun :: SqlPersistM a -> IO a } On call site: let tdb = ThingCfg "test" sqliteRun ts <- listThings tdb I want to keep it as an init param because there are other backends (class instances) that are not Persistent, so the use of 'sqlRun' on call site is not an option. What would be the best/correct way(s) to achieve that? Best regards, Vlatko From vogt.adam at gmail.com Tue Jan 28 20:47:45 2014 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 28 Jan 2014 15:47:45 -0500 Subject: [Haskell-cafe] How to pass a polymorphic function in a record? In-Reply-To: <52E7F903.3010100@gmail.com> References: <52e603fa23c86@functionaljobs.com> <52E7F903.3010100@gmail.com> Message-ID: Hi Vlatko, Did you consider: {-# LANGUAGE RankNTypes #-} data ThingCfg m = ThingCfg { thingDb :: Text, thingRun_ :: forall a. Text -> m a -> IO a } thingRun (ThingCfg db f) = f db Maybe the `m' above should be SqlPersistM, if all your other backends use that type. -- Adam On Tue, Jan 28, 2014 at 1:37 PM, Vlatko Basic wrote: > Hello Cafe, > > I'm playing with Persistent and have modules that I'd like to use on > several backends. This is simplified situation. > > In shared module: > > sqliteRun, postgresRun :: Text -> Int -> (ConnectionPool -> IO a) -> IO a > sqliteRun = withSqlitePool > postgresRun conStr = withPostgresqlPool (encodeUtf8 conStr) > > sqlRun :: Text -> Int -> SqlPersistM a -> IO a > sqlRun conStr poolSize = postgresRun conStr poolSize . runSqlPersistMPool > --sqlRun conStr poolSize = sqliteRun conStr poolSize . runSqlPersistMPool > > All works well if either 'sqlRun' above is commented/uncommented: > > > In one of modules: > > data ThingCfg = ThingCfg { thingDb :: Text } > > listThings :: ThingCfg -> IO [Thing] > listThings db = sqlRun (thingDb db) $ selectList ... > > findThing :: ThingId -> ThingCfg -> IO (Maybe Thing) > findThing uid db = sqlRun (thingDb db) $ getBy ... > > > > On call site simply: > let tdb = ThingCfg "test" > ts <- listThings tdb > > > I would like to specify 'sqliteRun' or 'postgresRun' function as (some) > parameter on the call site, but do not know how. > Something of imaginary solution: > > data ThingCfg = ThingCfg { > thingDb :: Text, > thingRun :: SqlPersistM a -> IO a > } > > On call site: > let tdb = ThingCfg "test" sqliteRun > ts <- listThings tdb > > I want to keep it as an init param because there are other backends (class > instances) that are not Persistent, so the use of 'sqlRun' on call site is > not an option. > > > What would be the best/correct way(s) to achieve that? > > > Best regards, > Vlatko > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From andrew at operationaldynamics.com Tue Jan 28 23:12:52 2014 From: andrew at operationaldynamics.com (Andrew Cowie) Date: Wed, 29 Jan 2014 10:12:52 +1100 Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: References: <1390863964.18469.4.camel@nervous-energy> <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: <1390950772.4927.3.camel@nervous-energy.bridge.anchor.net.au> On Tue, 2014-01-28 at 09:34 +0100, Erik Hesselink wrote: > I've never had any problems installing newer bytestring versions. > Unless you're using the GHC API, what is the problem? Yeah, as Kazu said, right after installing the current **bytestring** cabal announced it would be downgrading it back to 0.10.0.2. Bit of a waste of my Saturday that. I think it was **text** but no need to point fingers, really; the end result was Cabal being quite uncompromising about it. AfC Sydney From genial at alva.ro Wed Jan 29 02:25:31 2014 From: genial at alva.ro (Alvaro J. Genial) Date: Tue, 28 Jan 2014 21:25:31 -0500 Subject: [Haskell-cafe] Generalized null / zero Message-ID: 1. Is there a more general version of `null`? (e.g. for a Monad, Functor, Applicative, Traversable or the like.) The closest I can come up with is, in decreasing clunkiness: zero :: (MonadPlus m, Eq (m a)) => m a -> Bool zero = m == mzero zero :: (Alternative f, Eq (f a)) => f a -> Bool zero = m == empty zero :: (Monoid m, Eq m) => m -> Bool zero = m == mempty Though requiring Eq seems ugly and unnecessary, in theory. 2. In that vein, is there an existing function for "a value or a default if it's zero"? E.g.: orElse :: (Monoid m) => m -> m -> m a `orElse` b = if zero a then b else a Thank you, Alvaro http://alva.ro -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Wed Jan 29 02:40:48 2014 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 28 Jan 2014 21:40:48 -0500 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: References: Message-ID: Hi Alvaro, 1. null . toList :: Foldable t => t a -> Bool 2. mappend, mplus, <|> are supposed to drop arguments that are mempty, mzero, empty respectively. There's no requirement to prefer the first argument, but that's what the MonadPlus Maybe instance does at least. -- Adam -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Wed Jan 29 03:34:04 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 29 Jan 2014 03:34:04 -0000 Subject: [Haskell-cafe] manage effects in a DSL Message-ID: <20140129033404.76144.qmail@www1.g3.pair.com> Lindsey Kuper wrote: > Lately I have gotten a lot of mileage out of thinking of monads as > embedded DSLs. This is in fact how Moggi suggested to view monads. I strongly suggest the remarkable paper Eugenio Moggi and Sonia Fagorzi A Monadic Multi-stage Metalanguage FOSSACS2003, pp. 358--374 http://www.disi.unige.it/person/MoggiE/ftp/fossacs03.pdf Here are two most salient quotations: An important principle of Haskell [PHA+ 97] is that pure functional evaluation (and all the optimization techniques that come with it) should not be corrupted by the addition of computational effects. In Haskell this separation has been achieved through the use of monads (like monadic IO and monadic state). When describing MMML we adopt this principle not only at the level of types, but also at the level of the operational semantics. In fact, we distinguish between simplification (described by local rewrite rules) and computation (that may cause side-effects). ... We outline a general pattern for specifying the operational semantics of monadic metalanguages, which distinguishes between transparent simplification and programmable computation. This is possible because in a monadic metalanguage there is a clear distinction between term-constructors for building terms of computational types, and the other term-constructors that are computationally irrelevant. For computationally relevant term-constructors we give an operational semantics that ensures the correct sequencing of computational effects, e.g. by adopting some well-established technique for specifying the operational semantics of programming languages (see [WF94]), while for computationally irrelevant term-constructors it suffices to give local simplification rules, that can be applied non-deterministically (because they are semantic preserving). I should point out a large design space of the embedded effectful DSL. First of all, an embedded DSL does not have to be monadic. Monad essentially corresponds to the let-form in embedded DSL: let_ :: Exp a -> (a -> Exp b) -> Exp b If we are implementing an offline DSL compiler, such a let_ form is inappropriate since it presupposes the interleaving of compilation and code generation. Indeed, according to the type of let_, the code for the body of let_ may differ depending on the result of Exp a (that is, the result of compiling and then running Exp a). Normally, we first generate code, _then_ we compile it and then we run it. Therefore, many DSLs will not have let_ form. Rather, they will have app :: Exp (a -> b) -> Exp a -> Exp b That is, DSL is an applicative rather than monadic. DSL may be even simpler, see for example, Sec 3.4 of http://research.microsoft.com/en-us/um/people/simonpj/papers/assoc-types/fun-with-type-funs/typefun.pdf for a simple DSL of communicating processes, which is not even applicative. (Its realization in Haskell may use monads, but this is an implementation detail. The full power of the implementation language is not exposed to the DSL programmer.) If the DSL is effectful, we may annotate the Exp type with a set of effects that an expression may perform. The most familiar example is the continuation monad Cont r a, which is annotated with the answer-type r. If Cont r a is polymorphic over r, the computation is pure. The type Cont Int a describes an impure computation, which may abort with an Int value, for example. If we continue on this road we quickly come to extensible-effects. It may happen that one annotation is not enough: we need two, to describe the (type)state of the computation before and after an operation. The simplest example is locking, with the type state showing the state of the lock (acquired or released). See Sec 5.2 Tracking state and control in a parameterised monad in the above typefun paper. The computational structure in question is not a monad -- it is more general than that. To summarize: the design space is large. The relevant computational structure is not necessary a monad: it could be less powerful or more powerful. One should resist jumping on the bandwagon of monads or free monads, which are so (over)hyped these days. It's best to first decide what sort of programs a DSL programmer should be able to write. The computational structure (monad or something else) will be clearer then. From michael at snoyman.com Wed Jan 29 06:46:12 2014 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 29 Jan 2014 08:46:12 +0200 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: References: Message-ID: On Wed, Jan 29, 2014 at 4:25 AM, Alvaro J. Genial wrote: > 1. Is there a more general version of `null`? (e.g. for a Monad, Functor, > Applicative, Traversable or the like.) The closest I can come up with is, > in decreasing clunkiness: > > zero :: (MonadPlus m, Eq (m a)) => m a -> Bool > zero = m == mzero > > zero :: (Alternative f, Eq (f a)) => f a -> Bool > zero = m == empty > > zero :: (Monoid m, Eq m) => m -> Bool > zero = m == mempty > > Though requiring Eq seems ugly and unnecessary, in theory. > > You can try out onull[1], which will work on any MonoFoldable. That allows it to work with classical Foldable instances (like a list or Maybe), but also monomorphic containers like ByteString or Text. [1] http://hackage.haskell.org/package/mono-traversable-0.2.0.0/docs/Data-MonoTraversable.html#v:onull > 2. In that vein, is there an existing function for "a value or a default > if it's zero"? E.g.: > > orElse :: (Monoid m) => m -> m -> m > a `orElse` b = if zero a then b else a > > Thank you, > > Alvaro > http://alva.ro > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at eax.me Wed Jan 29 07:32:26 2014 From: mail at eax.me (Alexander Alexeev) Date: Wed, 29 Jan 2014 11:32:26 +0400 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? Message-ID: <20140129113226.1d8d230d@portege> Hello! Lets consider the following code: import Control.Concurrent import Control.Concurrent.STM import System.IO.Unsafe (unsafePerformIO) {-# NOINLINE counter #-} counter :: TVar Int counter = unsafePerformIO $ newTVarIO 0 incCounter :: IO Int incCounter = do r <- atomically $ do t <- readTVar counter let t' = t + 1 writeTVar counter t' return t' return r main :: IO () main = do n1 <- incCounter print n1 n2 <- incCounter print n2 n3 <- incCounter print n3 This program prints: 1 2 3 So we have a "global variable". Do I right understand that newTVarIO creates TVar and RTS memoizes it since 'counter' function is pure? If it's true, could it happen that under some circumstances memoized value will be deleted from memory? Or Haskell keeps all memoized values forever? Another issue which I'm afraid of --- would the given code be safe in multithread application? For example, is it possible to encounter a race condition if two threads will try to create a new counter in the same time? Is there any other problems which should be taken in account? -- Best regards, Alexander Alexeev http://eax.me/ From greg at gregorycollins.net Wed Jan 29 07:56:04 2014 From: greg at gregorycollins.net (Gregory Collins) Date: Wed, 29 Jan 2014 08:56:04 +0100 Subject: [Haskell-cafe] Lazy MWC Random? In-Reply-To: <52E7F20E.6090205@gmail.com> References: <52E7F20E.6090205@gmail.com> Message-ID: Try using unsafeInterleaveST?. On Tue, Jan 28, 2014 at 7:08 PM, Sacha Sokoloski wrote: > Dear Haskellers, > > I'm in a situation where I'd like to generate an infinite list of random > elements (basically, I'm simulating stochastic systems). I feel like MWC > Random is the fastest RNG available, but when I try to pull the infinite > list out of RandST, it obviously doesn't halt, because ST is strict. > Someone posted a way around this in this stack overflow thread: > > https://stackoverflow.com/questions/16248600/parallel- > computations-with-fast-randomness-and-purity > > Which would fix my problem. My question is though, why isn't ST.Lazy > included as a PrimMonad instance anyway? The best answer I can come up with > is that, since evaluating the Generator is time dependent, it's best to > make it strict to make sure that one's program isn't tapping into > /dev/random at arbitrary times. > > In this way the best stackoverflow solution is quite good. It requires one > to strictly generate a Seed (since that's the only way to do it), but then > converts the ST Monad to the Lazy version to Lazify everything else. > However, my understanding of PrimMonad is simply that it's a class of low > level monads i.e. IO and ST, so if there's some deeper reason to this, it's > beyond me. > > Another question that I'm puzzling over: In the stack overflow solution, > they also make an effort to only have to generate the seed a single time. > Is this important performance wise? What I suppose this must hinge upon, is > whether in saving an ST s Gen to a Seed, the conversion from an immutable > to mutable array requires a copy or not. Is that the full extent of the > complexity of this? Is the stackoverflow solution ultimately the most > efficient? Is using MWC Random to generate infinite lists and efficient > solution anyway? > > Thanks for any insight, > > - Sacha Sokoloski > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Gregory Collins -------------- next part -------------- An HTML attachment was scrubbed... URL: From greg at gregorycollins.net Wed Jan 29 08:02:46 2014 From: greg at gregorycollins.net (Gregory Collins) Date: Wed, 29 Jan 2014 09:02:46 +0100 Subject: [Haskell-cafe] Lazy MWC Random? In-Reply-To: References: <52E7F20E.6090205@gmail.com> Message-ID: Apologies, I see the stackoverflow link already does that. The first reply on that thread is right that you'd have issues with that approach anyways for thread safety reasons -- so you'll need a lock, and you'll have to test what that does to performance. On Wed, Jan 29, 2014 at 8:56 AM, Gregory Collins wrote: > Try using unsafeInterleaveST?. > > > On Tue, Jan 28, 2014 at 7:08 PM, Sacha Sokoloski wrote: > >> Dear Haskellers, >> >> I'm in a situation where I'd like to generate an infinite list of random >> elements (basically, I'm simulating stochastic systems). I feel like MWC >> Random is the fastest RNG available, but when I try to pull the infinite >> list out of RandST, it obviously doesn't halt, because ST is strict. >> Someone posted a way around this in this stack overflow thread: >> >> https://stackoverflow.com/questions/16248600/parallel- >> computations-with-fast-randomness-and-purity >> >> Which would fix my problem. My question is though, why isn't ST.Lazy >> included as a PrimMonad instance anyway? The best answer I can come up with >> is that, since evaluating the Generator is time dependent, it's best to >> make it strict to make sure that one's program isn't tapping into >> /dev/random at arbitrary times. >> >> In this way the best stackoverflow solution is quite good. It requires >> one to strictly generate a Seed (since that's the only way to do it), but >> then converts the ST Monad to the Lazy version to Lazify everything else. >> However, my understanding of PrimMonad is simply that it's a class of low >> level monads i.e. IO and ST, so if there's some deeper reason to this, it's >> beyond me. >> >> Another question that I'm puzzling over: In the stack overflow solution, >> they also make an effort to only have to generate the seed a single time. >> Is this important performance wise? What I suppose this must hinge upon, is >> whether in saving an ST s Gen to a Seed, the conversion from an immutable >> to mutable array requires a copy or not. Is that the full extent of the >> complexity of this? Is the stackoverflow solution ultimately the most >> efficient? Is using MWC Random to generate infinite lists and efficient >> solution anyway? >> >> Thanks for any insight, >> >> - Sacha Sokoloski >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > -- > Gregory Collins > -- Gregory Collins -------------- next part -------------- An HTML attachment was scrubbed... URL: From nda at informatik.uni-kiel.de Wed Jan 29 08:44:28 2014 From: nda at informatik.uni-kiel.de (Nikita Danilenko) Date: Wed, 29 Jan 2014 09:44:28 +0100 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: References: Message-ID: <52E8BF6C.7050908@informatik.uni-kiel.de> An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: 0x76C229F0.asc Type: application/pgp-keys Size: 8170 bytes Desc: not available URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 901 bytes Desc: OpenPGP digital signature URL: From apfelmus at quantentunnel.de Wed Jan 29 09:55:19 2014 From: apfelmus at quantentunnel.de (Heinrich Apfelmus) Date: Wed, 29 Jan 2014 10:55:19 +0100 Subject: [Haskell-cafe] To LLVM or not to LLVM... In-Reply-To: References: <87d2jc42uw.fsf@write-only.cryp.to> Message-ID: Ian Ross wrote: >> A Cabal flag for the same purpose might make sense, IMHO, if there are >> other build parameters that change when compiling with LLVM (like CPP >> defines, etc.), but it's my understanding that this is not the case? >> > > Right. I think I'll add a Cabal flag and worry about the reverse > dependencies issue if the package ever has any! You can specify a cabal flag to be switched on by default. Cabal will then switch off the flag automatically if it cannot satisfy the constraints. So, if you can add a dependency on the LLVM tools in the "extra-libraries" field or elsewhere, you can use this automatic flag assignment to compile the LLVM version for people who already have the LLVM tools installed. (Note that last time I checked, cabal will not try to download new packages in order to fulfill the constraints, though.) Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com From ian at skybluetrades.net Wed Jan 29 09:58:49 2014 From: ian at skybluetrades.net (Ian Ross) Date: Wed, 29 Jan 2014 10:58:49 +0100 Subject: [Haskell-cafe] To LLVM or not to LLVM... In-Reply-To: References: <87d2jc42uw.fsf@write-only.cryp.to> Message-ID: Thanks Heinrich! That sounds like the ideal solution. I'll do that. On 29 January 2014 10:55, Heinrich Apfelmus wrote: > Ian Ross wrote: > >> A Cabal flag for the same purpose might make sense, IMHO, if there are >>> other build parameters that change when compiling with LLVM (like CPP >>> defines, etc.), but it's my understanding that this is not the case? >>> >>> >> Right. I think I'll add a Cabal flag and worry about the reverse >> dependencies issue if the package ever has any! >> > > You can specify a cabal flag to be switched on by default. Cabal will then > switch off the flag automatically if it cannot satisfy the constraints. > > So, if you can add a dependency on the LLVM tools in the "extra-libraries" > field or elsewhere, you can use this automatic flag assignment to compile > the LLVM version for people who already have the LLVM tools installed. > > (Note that last time I checked, cabal will not try to download new > packages in order to fulfill the constraints, though.) > > > Best regards, > Heinrich Apfelmus > > -- > http://apfelmus.nfshost.com > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Ian Ross Tel: +43(0)6804451378 ian at skybluetrades.net www.skybluetrades.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmacristovao at gmail.com Wed Jan 29 10:13:31 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Wed, 29 Jan 2014 10:13:31 +0000 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: <52E8BF6C.7050908@informatik.uni-kiel.de> References: <52E8BF6C.7050908@informatik.uni-kiel.de> Message-ID: Hi Alvaro, Not long ago I faced the same question, and ended up developing a very simplistic library IsNull: https://github.com/jcristovao/IsNull To be honest, its a very stripped down version of Mono-traversable referenced by Michael, which I highly recomend, but in my case specialized to provide some extra functions, namely nested null: isNullN (Just "abc") == False isNullN (Just "" ) == True isNullN (Nothing ) == True Now, a small note regarding: zero :: (Monoid m, Eq m) => m -> Bool zero = m == mempty This is dangerous. For example: -- | Monoid under multiplication. newtype Product a = Product { getProduct :: a } deriving (Eq, Ord, Read, Show, Bounded) instance Num a => Monoid (Product a) where mempty = Product 1 Product x `mappend` Product y = Product (x * y) This leads to: zero (Product 1) = True. Is this what you wanted? I had this in my library at first, and ended up removing it, because it might not always be what is expected. Cheers, Joao 2014/1/29 Nikita Danilenko : > Hi Alvaro, > > as for your second question > > > 2. In that vein, is there an existing function for "a value or a default if > it's zero"? E.g.: > > orElse :: (Monoid m) => m -> m -> m > a `orElse` b = if zero a then b else a > > > There is the function orElse from the syb package [1] that works on (Maybe > a) values. It can be considered a particular instance of the above with > mempty = Nothing. > > Alternatively, the function fromMaybe from Data.Maybe [2] provides a similar > functionality, but with the heterogeneous type > > fromMaybe :: a -> Maybe a -> a > > Essentially, in both cases the zero predicate is specialised to a pattern > matching for Nothing, which doesn't require an Eq instance. Also, there is > no need for a mappend function, which may be more convenient. > > Best regards, > > Nikita > > [1] > http://hackage.haskell.org/package/syb-0.4.1/docs/Data-Generics-Aliases.html#v:orElse > > [2] > http://hackage.haskell.org/package/base-4.6.0.1/docs/Data-Maybe.html#v:fromMaybe > > > On 29/01/14 07:46, Michael Snoyman wrote: > > > > > On Wed, Jan 29, 2014 at 4:25 AM, Alvaro J. Genial wrote: >> >> 1. Is there a more general version of `null`? (e.g. for a Monad, Functor, >> Applicative, Traversable or the like.) The closest I can come up with is, in >> decreasing clunkiness: >> >> zero :: (MonadPlus m, Eq (m a)) => m a -> Bool >> zero = m == mzero >> >> zero :: (Alternative f, Eq (f a)) => f a -> Bool >> zero = m == empty >> >> zero :: (Monoid m, Eq m) => m -> Bool >> zero = m == mempty >> >> Though requiring Eq seems ugly and unnecessary, in theory. >> > > You can try out onull[1], which will work on any MonoFoldable. That allows > it to work with classical Foldable instances (like a list or Maybe), but > also monomorphic containers like ByteString or Text. > > [1] > http://hackage.haskell.org/package/mono-traversable-0.2.0.0/docs/Data-MonoTraversable.html#v:onull > >> >> 2. In that vein, is there an existing function for "a value or a default >> if it's zero"? E.g.: >> >> orElse :: (Monoid m) => m -> m -> m >> a `orElse` b = if zero a then b else a >> >> Thank you, >> >> Alvaro >> http://alva.ro >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -- > Dipl.-Math. Nikita Danilenko > Research group: > Computer Aided Program Development > Kiel University > Olshausenstr. 40, D-24098 Kiel > Phone: +49 431 880 7275 > URL: https://www.informatik.uni-kiel.de/index.php?id=nikita > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From haskell at nand.wakku.to Wed Jan 29 11:20:43 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Wed, 29 Jan 2014 12:20:43 +0100 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: References: Message-ID: <20140129122043.GA8876@nanodesu.talocan.mine.nu> On Tue, 28 Jan 2014 21:25:31 -0500, "Alvaro J. Genial" wrote: > 1. Is there a more general version of `null`? (e.g. for a Monad, Functor, > Applicative, Traversable or the like.) The closest I can come up with is, > in decreasing clunkiness: Lens can do this via the ?hasn't? function for any Fold. You can get some free generalization out of it via ?hasn't each?, which works for every instance of Each (includes most Foldable containers along with ByteString, Text, and similar). > 2. In that vein, is there an existing function for "a value or a > default if > it's zero"? E.g.: This abstraction looks a lot like what you'd want out of Alternative, though admittedly that one is specialized to (* -> *). From svenpanne at gmail.com Wed Jan 29 12:08:00 2014 From: svenpanne at gmail.com (Sven Panne) Date: Wed, 29 Jan 2014 13:08:00 +0100 Subject: [Haskell-cafe] ANNOUNCE: GLUT 2.5.1.0 Message-ID: A new version of the GLUT package is available on Hackage, with the following new features: * Added support for left/right SHIFT/CTRL/ALT special keys. * Added skipStaleMotionEvents state flag, making it possible to skip all but the last motion event. * Added leaveFullScreen call. * Added support for position, application life cycle and multi-touch window callbacks. * Various object drawing improvements: * Added teacup and teaspoon objects, so we support the full Newell tea set now. * Added geometryVisualizeNormals state flag. * Added support for drawing objects via VBOs: vertexAttribCoord3, vertexAttribNormal, and vertexAttribTexCoord2. * Added support for menu fonts via new constructor MenuWithFont. Apart from glutInitErrorFunc and glutInitWarningFunc, which are not extremely useful IMHO, all freeglut features are now exposed on the Haskell side. Cheers, S. From fryguybob at gmail.com Wed Jan 29 14:16:16 2014 From: fryguybob at gmail.com (Ryan Yates) Date: Wed, 29 Jan 2014 09:16:16 -0500 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? In-Reply-To: <20140129113226.1d8d230d@portege> References: <20140129113226.1d8d230d@portege> Message-ID: I believe you are safe to do this for now with GHC. There is some relevant discussion here [1]. [1]: http://www.haskell.org/haskellwiki/Top_level_mutable_state Note that doing: {-# NOINLINE counter #-} counter :: TVar Int counter = unsafePerformIO $ atomically $ newTVar 0 Is not safe [2]. [2]: http://hackage.haskell.org/package/stm-2.4.2/docs/Control-Concurrent-STM-TVar.html#v:newTVarIO Ryan On Wed, Jan 29, 2014 at 2:32 AM, Alexander Alexeev wrote: > Hello! > > Lets consider the following code: > > import Control.Concurrent > import Control.Concurrent.STM > import System.IO.Unsafe (unsafePerformIO) > > {-# NOINLINE counter #-} > counter :: TVar Int > counter = unsafePerformIO $ newTVarIO 0 > > incCounter :: IO Int > incCounter = do > r <- atomically $ do > t <- readTVar counter > let t' = t + 1 > writeTVar counter t' > return t' > return r > > main :: IO () > main = do > n1 <- incCounter > print n1 > n2 <- incCounter > print n2 > n3 <- incCounter > print n3 > > This program prints: > > 1 > 2 > 3 > > So we have a "global variable". Do I right understand that newTVarIO > creates TVar and RTS memoizes it since 'counter' function is pure? If > it's true, could it happen that under some circumstances memoized value > will be deleted from memory? Or Haskell keeps all memoized values > forever? > > Another issue which I'm afraid of --- would the given code be safe in > multithread application? For example, is it possible to encounter a > race condition if two threads will try to create a new counter in the > same time? > > Is there any other problems which should be taken in account? > > -- > Best regards, > Alexander Alexeev > http://eax.me/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Wed Jan 29 14:53:48 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Wed, 29 Jan 2014 16:53:48 +0200 Subject: [Haskell-cafe] ANNOUNCE: GLUT 2.5.1.0 In-Reply-To: References: Message-ID: Great work, Sven. Thanks! 2014-01-29 Sven Panne : > A new version of the GLUT package is available on Hackage, with the > following new features: > > * Added support for left/right SHIFT/CTRL/ALT special keys. > * Added skipStaleMotionEvents state flag, making it possible to > skip all but the last motion event. > * Added leaveFullScreen call. > * Added support for position, application life cycle and > multi-touch window callbacks. > * Various object drawing improvements: > * Added teacup and teaspoon objects, so we support the full > Newell tea set now. > * Added geometryVisualizeNormals state flag. > * Added support for drawing objects via VBOs: > vertexAttribCoord3, vertexAttribNormal, and vertexAttribTexCoord2. > * Added support for menu fonts via new constructor MenuWithFont. > > Apart from glutInitErrorFunc and glutInitWarningFunc, which are not > extremely useful IMHO, all freeglut features are now exposed on the > Haskell side. > > Cheers, > S. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From omeragacan at gmail.com Wed Jan 29 15:03:23 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Wed, 29 Jan 2014 17:03:23 +0200 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? In-Reply-To: <20140129113226.1d8d230d@portege> References: <20140129113226.1d8d230d@portege> Message-ID: I was also wondering a similar thing. I'm writing FFI for a C library. Library has a function like: int pollEvent(EventType* event); Instead of malloc'ing a new EventType in a FFI call for this functions: pollEvent :: IO Event pollEvent = do ev <- malloc ret <- cPollEvent ev -- check if ret is 0 etc. peek ev I was wondering if something like this is also safe: eventObj_ :: Ptr Event eventObj_ = unsafePerformIO malloc pollEvent :: IO Event pollEvent = do ret <- cPollEvent eventObj_ -- check if ret is 0 etc. peek eventObj_ This is one malloc cheaper for every call, and differences are not visible from user side. Still, I did not use this in my FFI bindings because I was not sure how safe is this approach. Any ideas on this? --- ?mer Sinan A?acan http://osa1.net From vlatko.basic at gmail.com Wed Jan 29 15:26:35 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Wed, 29 Jan 2014 16:26:35 +0100 Subject: [Haskell-cafe] How to pass a polymorphic function in a record? In-Reply-To: References: <52e603fa23c86@functionaljobs.com> <52E7F903.3010100@gmail.com> Message-ID: <52E91DAB.9030109@gmail.com> An HTML attachment was scrubbed... URL: From alexey.skladnoy at gmail.com Wed Jan 29 15:48:41 2014 From: alexey.skladnoy at gmail.com (Aleksey Khudyakov) Date: Wed, 29 Jan 2014 19:48:41 +0400 Subject: [Haskell-cafe] Lazy MWC Random? In-Reply-To: <52E7F20E.6090205@gmail.com> References: <52E7F20E.6090205@gmail.com> Message-ID: <52E922D9.109@gmail.com> On 01/28/2014 10:08 PM, Sacha Sokoloski wrote: > Dear Haskellers, > > I'm in a situation where I'd like to generate an infinite list of random > elements (basically, I'm simulating stochastic systems). I feel like MWC > Random is the fastest RNG available, but when I try to pull the infinite > list out of RandST, it obviously doesn't halt, because ST is strict. > Someone posted a way around this in this stack overflow thread: > > https://stackoverflow.com/questions/16248600/parallel-computations-with-fast-randomness-and-purity > > > Which would fix my problem. My question is though, why isn't ST.Lazy > included as a PrimMonad instance anyway? The best answer I can come up > with is that, since evaluating the Generator is time dependent, it's > best to make it strict to make sure that one's program isn't tapping > into /dev/random at arbitrary times. > > In this way the best stackoverflow solution is quite good. It requires > one to strictly generate a Seed (since that's the only way to do it), > but then converts the ST Monad to the Lazy version to Lazify everything > else. However, my understanding of PrimMonad is simply that it's a class > of low level monads i.e. IO and ST, so if there's some deeper reason to > this, it's beyond me. > Definition of PrimMonad is basically monad which is isomorphic to strict ST/IO. It's possible to define instance for lazy ST but I'm not sure how well will it interact with lazyness. > Another question that I'm puzzling over: In the stack overflow solution, > they also make an effort to only have to generate the seed a single > time. Is this important performance wise? What I suppose this must hinge > upon, is whether in saving an ST s Gen to a Seed, the conversion from an > immutable to mutable array requires a copy or not. Is that the full > extent of the complexity of this? Is the stackoverflow solution > ultimately the most efficient? Is using MWC Random to generate infinite > lists and efficient solution anyway? > Conversions between Gen and Seed require copying a generator state. Internally Gen is 258 element array of Word32. So to get good performance one want to create Gen once and then modify it in place. To understand whether SO solution is efficient you ned to benchmark it. From fryguybob at gmail.com Wed Jan 29 15:58:18 2014 From: fryguybob at gmail.com (Ryan Yates) Date: Wed, 29 Jan 2014 10:58:18 -0500 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? In-Reply-To: References: <20140129113226.1d8d230d@portege> Message-ID: You would need the NOINLINE pragma: {-# NOINLINE eventObj_ #-} eventObj_ :: Ptr Event eventObj_ = unsafePerformIO malloc I would avoid this sort of global state in general. It isn't clear that this will give an improvement in performance and what could otherwise possible be a thread safe API is no longer thread safe. Global TVars and MVars are much more compelling as they are thread safe and represent some global synchronization in your program. On Wed, Jan 29, 2014 at 10:03 AM, ?mer Sinan A?acan wrote: > I was also wondering a similar thing. I'm writing FFI for a C library. > Library has a function like: > > int pollEvent(EventType* event); > > Instead of malloc'ing a new EventType in a FFI call for this functions: > > pollEvent :: IO Event > pollEvent = do > ev <- malloc > ret <- cPollEvent ev > -- check if ret is 0 etc. > peek ev > > I was wondering if something like this is also safe: > > eventObj_ :: Ptr Event > eventObj_ = unsafePerformIO malloc > > pollEvent :: IO Event > pollEvent = do > ret <- cPollEvent eventObj_ > -- check if ret is 0 etc. > peek eventObj_ > > This is one malloc cheaper for every call, and differences are not > visible from user side. Still, I did not use this in my FFI bindings > because I was not sure how safe is this approach. Any ideas on this? > > > --- > ?mer Sinan A?acan > http://osa1.net > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Wed Jan 29 18:09:42 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Wed, 29 Jan 2014 20:09:42 +0200 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? In-Reply-To: References: <20140129113226.1d8d230d@portege> Message-ID: > You would need the NOINLINE pragma Ahh, right. Thanks for reminding. > It isn't clear that > this will give an improvement in performance Why is that? I think it's clear since I'm eliminating malloc calls. (though one may claim that malloc calls are so cheap it's not even measurable) > and what could otherwise > possible be a thread safe API is no longer thread safe. This is a fair point. Though in my case I don't think this is the case because this API is already not thread safe, because of the C API and not Haskell bindings. --- ?mer Sinan A?acan http://osa1.net From allbery.b at gmail.com Wed Jan 29 18:17:30 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 29 Jan 2014 13:17:30 -0500 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? In-Reply-To: References: <20140129113226.1d8d230d@portege> Message-ID: On Wed, Jan 29, 2014 at 1:09 PM, ?mer Sinan A?acan wrote: > > > It isn't clear that > > this will give an improvement in performance > > Why is that? I think it's clear since I'm eliminating malloc calls. > (though one may claim that malloc calls are so cheap it's not even > measurable) > (1) it's not really malloc since it's being garbage collected when out of scope (2) given that there is a lot of allocation anyway and anything allocated as ephemerally as this use case is very common and very highly optimized, it's not really worth it -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From holmisen at gmail.com Thu Jan 30 12:24:24 2014 From: holmisen at gmail.com (Johan Holmquist) Date: Thu, 30 Jan 2014 13:24:24 +0100 Subject: [Haskell-cafe] Is it safe to create global variables using unsafePerformIO? In-Reply-To: References: <20140129113226.1d8d230d@portege> Message-ID: You might be interested in http://hackage.haskell.org/package/global-variables for this. Cheers Johan On Jan 29, 2014 7:17 PM, "Brandon Allbery" wrote: > On Wed, Jan 29, 2014 at 1:09 PM, ?mer Sinan A?acan wrote: > >> >> > It isn't clear that >> > this will give an improvement in performance >> >> Why is that? I think it's clear since I'm eliminating malloc calls. >> (though one may claim that malloc calls are so cheap it's not even >> measurable) >> > > (1) it's not really malloc since it's being garbage collected when out of > scope > > (2) given that there is a lot of allocation anyway and anything allocated > as ephemerally as this use case is very common and very highly optimized, > it's not really worth it > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From aseipp at pobox.com Thu Jan 30 13:26:49 2014 From: aseipp at pobox.com (Austin Seipp) Date: Thu, 30 Jan 2014 07:26:49 -0600 Subject: [Haskell-cafe] [Haskell-iPhone] GHC iOS ARMv7/ARMv7s fat support completed In-Reply-To: References: Message-ID: Hi Luke, Thanks, I have merged your patch. I also pushed a change to fix the use of __thread on iOS (since it's unsupported.) Hopefully HEAD is working well now. (And as a reminder for #8700 - if you don't set the ticket to 'patch' status, it's really unlikely I'm going to see it any time soon.) On Sun, Jan 26, 2014 at 12:33 PM, Schell Scivally wrote: > Awesome! I'll be spinning this up soon. > > On Sun, Jan 26, 2014 at 2:23 AM, Luke Iannini wrote: >> >> Hi folks, >> >> Happy to report that I've finished an approach to armv7/armv7s fat >> compilation, just in time for 7.8's imminent release. >> >> You'll find the necessary scripts here: >> https://github.com/ghc-ios/ghc-ios-scripts >> >> and the latest instructions for building GHC for iOS usage here: >> https://ghc.haskell.org/trac/ghc/wiki/Building/CrossCompiling/iOS >> >> I've also added support for a perf-cross BuildFlavour, which will give a >> higher-performance and profiling-ready build that matches what we'll be >> putting together as the official 7.8 GHC iOS binaries: >> https://ghc.haskell.org/trac/ghc/ticket/8700 >> >> Cheers >> Luke >> >> _______________________________________________ >> iPhone mailing list >> iPhone at haskell.org >> http://www.haskell.org/mailman/listinfo/iphone >> > > > > -- > Schell Scivally > http://blog.efnx.com > http://github.com/schell > http://twitter.com/schellsan > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Regards, Austin - PGP: 4096R/0x91384671 From waldmann at imn.htwk-leipzig.de Thu Jan 30 15:01:36 2014 From: waldmann at imn.htwk-leipzig.de (Johannes Waldmann) Date: Thu, 30 Jan 2014 15:01:36 +0000 (UTC) Subject: [Haskell-cafe] Builder vs Builder References: <1390863964.18469.4.camel@nervous-energy> <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: Erik Hesselink gmail.com> writes: > I've never had any problems installing newer bytestring versions. > Unless you're using the GHC API, what is the problem? Template Haskell. (I guess this counts as "using the GHC API" somehow. But even if you are not, one of your dependencies may be doing it.) See http://www.haskell.org/pipermail/ghc-devs/2014-January/003835.html - J.W. From hesselink at gmail.com Thu Jan 30 15:11:21 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 30 Jan 2014 16:11:21 +0100 Subject: [Haskell-cafe] Builder vs Builder In-Reply-To: References: <1390863964.18469.4.camel@nervous-energy> <20140128.164134.1204768223271068591.kazu@iij.ad.jp> Message-ID: On Thu, Jan 30, 2014 at 4:01 PM, Johannes Waldmann wrote: > Erik Hesselink gmail.com> writes: > >> I've never had any problems installing newer bytestring versions. >> Unless you're using the GHC API, what is the problem? > > Template Haskell. > > (I guess this counts as "using the GHC API" somehow. > But even if you are not, one of your dependencies may be doing it.) > > See http://www.haskell.org/pipermail/ghc-devs/2014-January/003835.html Template haskell doesn't depend on bytestring, and bytestring doesn't depend on template-haskell, so I don't see how that situation applies. Erik From roma at ro-che.info Thu Jan 30 16:30:55 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 30 Jan 2014 18:30:55 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights Message-ID: <20140130163055.GA19868@sniper> In the recent past I took over two unmaintained packages: bert and ansi-terminal. I don't mind spending a bit of time to keep our ecosystem from bitrotting. However, both times I had to go through an irritating procedure of contacting hackage admins, asking them to grant me upload rights, explaining why the maintainers can't do that themselves and why I think the packages are abandoned. Instead of a feeling that I'm doing something good and useful, I have a feeling that I'm bothering people with my own problems. It also adds unnecessary latency to my work. So from now on I'll simply fork the packages I need to fix. Others are of course welcome to use my forks. (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, and whose maintainer hasn't responded. My fork is at http://hackage.haskell.org/package/regex-tdfa-rc .) Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From cgaebel at uwaterloo.ca Thu Jan 30 16:40:12 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Thu, 30 Jan 2014 11:40:12 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140130163055.GA19868@sniper> References: <20140130163055.GA19868@sniper> Message-ID: How does the process of taking over maintenance add latency to your work? 1) Check out broken version of package. 2) Fix locally, bump version number locally. 3) cabal sandbox add-source ../fixed-package in any package that needs the fixed version. 4) Email hackage admins for upload rights. 5) Continue working on your actual project. 6) Receive upload privileges one day. 7) Upload fixed package. As far as I can tell, the only real latency cost here is that paid to fix the broken version. Regards, - Clark On Thu, Jan 30, 2014 at 11:30 AM, Roman Cheplyaka wrote: > In the recent past I took over two unmaintained packages: bert and > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > from bitrotting. > > However, both times I had to go through an irritating procedure of > contacting hackage admins, asking them to grant me upload rights, > explaining why the maintainers can't do that themselves and why I think > the packages are abandoned. > > Instead of a feeling that I'm doing something good and useful, I have > a feeling that I'm bothering people with my own problems. It also adds > unnecessary latency to my work. > > So from now on I'll simply fork the packages I need to fix. > > Others are of course welcome to use my forks. > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > and whose maintainer hasn't responded. My fork is at > http://hackage.haskell.org/package/regex-tdfa-rc .) > > Roman > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From bgamari.foss at gmail.com Thu Jan 30 16:49:37 2014 From: bgamari.foss at gmail.com (Ben Gamari) Date: Thu, 30 Jan 2014 11:49:37 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140130163055.GA19868@sniper> References: <20140130163055.GA19868@sniper> Message-ID: <878utxfm8u.fsf@gmail.com> Roman Cheplyaka writes: > In the recent past I took over two unmaintained packages: bert and > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > from bitrotting. > > However, both times I had to go through an irritating procedure of > contacting hackage admins, asking them to grant me upload rights, > explaining why the maintainers can't do that themselves and why I think > the packages are abandoned. > > Instead of a feeling that I'm doing something good and useful, I have > a feeling that I'm bothering people with my own problems. It also adds > unnecessary latency to my work. > > So from now on I'll simply fork the packages I need to fix. > > Others are of course welcome to use my forks. > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > and whose maintainer hasn't responded. My fork is at > http://hackage.haskell.org/package/regex-tdfa-rc .) > I have also tried to upstream GHC 7.8 fixes to this package to no avail. However, the maintainer did inform me that the darcs repository is here[1]. It would be great if someone (it could be me, Roman, or anyone else interested) would take over the regex-tdfa package itself. While the forking idea certainly eliminates a lot of effort for the fork-er, it would be nice if the original point in the namespace were inhabited by an actively maintained package. I feel like an explosion of forks gives a not-so-great impression of the Haskell community and makes it even harder for beginners to find the right packages to depend upon. Concerning the friction imposed by the package take-over process, I agree that it is rather onerous. In my opinion the protocol is a bit too thorough for its own good. Cheers, - Ben [1] http://code.haskell.org/regex-tdfa/ -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 489 bytes Desc: not available URL: From ky3 at atamo.com Thu Jan 30 16:50:40 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Thu, 30 Jan 2014 23:50:40 +0700 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> Message-ID: On Thu, Jan 30, 2014 at 11:40 PM, Clark Gaebel wrote: > How does the process of taking over maintenance add latency to your work? > > ... > 4) Email hackage admins for upload rights. Emails are hard. There's a massive cost in the context switch from coding to writing a justification as to why someone other than maintainer gets upload rights. At least that's what I gleaned from Roman's email. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From bgamari.foss at gmail.com Thu Jan 30 16:53:56 2014 From: bgamari.foss at gmail.com (Ben Gamari) Date: Thu, 30 Jan 2014 11:53:56 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> Message-ID: <8761p1fm1n.fsf@gmail.com> Clark Gaebel writes: > How does the process of taking over maintenance add latency to your work? > > 1) Check out broken version of package. > 2) Fix locally, bump version number locally. > 3) cabal sandbox add-source ../fixed-package in any package that needs the > fixed version. > 4) Email hackage admins for upload rights. > 5) Continue working on your actual project. > 6) Receive upload privileges one day. > 7) Upload fixed package. > > As far as I can tell, the only real latency cost here is that paid to fix > the broken version. > In my experience, step 4 involved several round trips between a number of different people. Admittedly, this is in part because it's easy to forget about the broken package after you have fixed it locally. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 489 bytes Desc: not available URL: From carter.schonwald at gmail.com Thu Jan 30 17:01:53 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 30 Jan 2014 12:01:53 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <8761p1fm1n.fsf@gmail.com> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> Message-ID: I HAVE A SOLUTION for anyone who asks me, I will help manage the "this isn't maintained, i wanna take over maintership" pestering emails that need to happen. that said, you'll still need to email me to ask me to do that, or pester me on IRC as applicable. (which may take just as much time as "hey i'd like to take over maintainership of X on hackage please" sent to the libraries list) Point being, if someone finds the prospect of doing the pestering needed to do the process overwhelming, ask me nicely, and i'll try to help push it along (while keeping them in CC and such, though they of course will have to chime in at some point) should this thread also touch on the the libraries mailing list? ccing it just in case :) point being, we need to have a responsive, *responsible* way of quickly resolving these things that easy to do. time for comments: 2 weeks -Carter On Thu, Jan 30, 2014 at 11:53 AM, Ben Gamari wrote: > Clark Gaebel writes: > > > How does the process of taking over maintenance add latency to your work? > > > > 1) Check out broken version of package. > > 2) Fix locally, bump version number locally. > > 3) cabal sandbox add-source ../fixed-package in any package that needs > the > > fixed version. > > 4) Email hackage admins for upload rights. > > 5) Continue working on your actual project. > > 6) Receive upload privileges one day. > > 7) Upload fixed package. > > > > As far as I can tell, the only real latency cost here is that paid to fix > > the broken version. > > > In my experience, step 4 involved several round trips between a number > of different people. Admittedly, this is in part because it's easy to > forget about the broken package after you have fixed it locally. > > Cheers, > > - Ben > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Thu Jan 30 17:07:43 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 30 Jan 2014 19:07:43 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> Message-ID: <20140130170743.GA22400@sniper> Because I can't release my package (which depends on the fixed version) immediately. Also, all sorts of psychological reasons (as Kim-Ee Yeoh said) ? context switches, open loops etc. It's much better to just upload the package and be done with it. Roman * Clark Gaebel [2014-01-30 11:40:12-0500] > How does the process of taking over maintenance add latency to your work? > > 1) Check out broken version of package. > 2) Fix locally, bump version number locally. > 3) cabal sandbox add-source ../fixed-package in any package that needs the > fixed version. > 4) Email hackage admins for upload rights. > 5) Continue working on your actual project. > 6) Receive upload privileges one day. > 7) Upload fixed package. > > As far as I can tell, the only real latency cost here is that paid to fix > the broken version. > > Regards, > - Clark > > > On Thu, Jan 30, 2014 at 11:30 AM, Roman Cheplyaka wrote: > > > In the recent past I took over two unmaintained packages: bert and > > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > > from bitrotting. > > > > However, both times I had to go through an irritating procedure of > > contacting hackage admins, asking them to grant me upload rights, > > explaining why the maintainers can't do that themselves and why I think > > the packages are abandoned. > > > > Instead of a feeling that I'm doing something good and useful, I have > > a feeling that I'm bothering people with my own problems. It also adds > > unnecessary latency to my work. > > > > So from now on I'll simply fork the packages I need to fix. > > > > Others are of course welcome to use my forks. > > > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > > and whose maintainer hasn't responded. My fork is at > > http://hackage.haskell.org/package/regex-tdfa-rc .) > > > > Roman > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From roma at ro-che.info Thu Jan 30 17:29:35 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 30 Jan 2014 19:29:35 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <878utxfm8u.fsf@gmail.com> References: <20140130163055.GA19868@sniper> <878utxfm8u.fsf@gmail.com> Message-ID: <20140130172935.GA23492@sniper> * Ben Gamari [2014-01-30 11:49:37-0500] > Roman Cheplyaka writes: > > > In the recent past I took over two unmaintained packages: bert and > > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > > from bitrotting. > > > > However, both times I had to go through an irritating procedure of > > contacting hackage admins, asking them to grant me upload rights, > > explaining why the maintainers can't do that themselves and why I think > > the packages are abandoned. > > > > Instead of a feeling that I'm doing something good and useful, I have > > a feeling that I'm bothering people with my own problems. It also adds > > unnecessary latency to my work. > > > > So from now on I'll simply fork the packages I need to fix. > > > > Others are of course welcome to use my forks. > > > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > > and whose maintainer hasn't responded. My fork is at > > http://hackage.haskell.org/package/regex-tdfa-rc .) > > > I have also tried to upstream GHC 7.8 fixes to this package to no > avail. However, the maintainer did inform me that the darcs repository > is here[1]. > > It would be great if someone (it could be me, Roman, or anyone else > interested) would take over the regex-tdfa package itself. While the > forking idea certainly eliminates a lot of effort for the fork-er, it > would be nice if the original point in the namespace were inhabited by > an actively maintained package. I feel like an explosion of forks gives > a not-so-great impression of the Haskell community and makes it even > harder for beginners to find the right packages to depend upon. > > Concerning the friction imposed by the package take-over process, I > agree that it is rather onerous. In my opinion the protocol is a bit > too thorough for its own good. > > Cheers, > > - Ben > > > [1] http://code.haskell.org/regex-tdfa/ Here's my git repo (imported from that repository + my patches): https://github.com/feuerbach/regex-tdfa-rc If anyone eventually takes over, feel free to use it (the renaming commits are easy to strip). Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From michael at snoyman.com Thu Jan 30 17:33:21 2014 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 30 Jan 2014 19:33:21 +0200 Subject: [Haskell-cafe] Naming scheme for partial functions Message-ID: Greg Weber and I have been discussing some changes to mono-traversable[1]. One of the modules we provide is Data.NonNull, which provides total versions of functions like `last`. A change we're looking at would require having a partial version of `last` defined in a separate typeclass (IsSequence), which would allowing for more optimized implementations of the total `last` function for datatypes which support it (e.g., strict ByteStrings). But what should we name it? I'm sure everyone's familiar with the `unsafe` naming convention, but that's not appropriate here: standard usage shows `unsafe` meaning a function which can cause a segfault. I initially named it `partialLast`, but partial can also imply partial function application. Greg brought up the idea of suffixing the function with something like `Throws` or `Errors`, which I think I'm a bit partial to myself[2]. So my questions are: * Is there some already used naming scheme out there for partial functions which I've missed? * Do people have any ideas to throw into the mix? Michael [1] https://github.com/snoyberg/mono-traversable/pull/21 [2] Pardon the pun. -------------- next part -------------- An HTML attachment was scrubbed... URL: From atzeus at gmail.com Thu Jan 30 17:36:45 2014 From: atzeus at gmail.com (Atze van der Ploeg) Date: Thu, 30 Jan 2014 18:36:45 +0100 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: unprovenLast ? On Jan 30, 2014 6:33 PM, "Michael Snoyman" wrote: > Greg Weber and I have been discussing some changes to mono-traversable[1]. > One of the modules we provide is Data.NonNull, which provides total > versions of functions like `last`. A change we're looking at would require > having a partial version of `last` defined in a separate typeclass > (IsSequence), which would allowing for more optimized implementations of > the total `last` function for datatypes which support it (e.g., strict > ByteStrings). > > But what should we name it? I'm sure everyone's familiar with the `unsafe` > naming convention, but that's not appropriate here: standard usage shows > `unsafe` meaning a function which can cause a segfault. > > I initially named it `partialLast`, but partial can also imply partial > function application. Greg brought up the idea of suffixing the function > with something like `Throws` or `Errors`, which I think I'm a bit partial > to myself[2]. > > So my questions are: > > * Is there some already used naming scheme out there for partial functions > which I've missed? > * Do people have any ideas to throw into the mix? > > Michael > > [1] https://github.com/snoyberg/mono-traversable/pull/21 > [2] Pardon the pun. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johan.tibell at gmail.com Thu Jan 30 17:56:27 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Thu, 30 Jan 2014 09:56:27 -0800 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140130163055.GA19868@sniper> References: <20140130163055.GA19868@sniper> Message-ID: Generally we (the Hackage admins) ask you to do the following before asking us to take over a package. Maintainer unreachable: 1. Try to contact the maintainer. Give him/her reasonable time to respond. 2. State your intention to take over the package in a public forum (e.g. haskell-cafe/libraries list). CC maintainer. 3. Wait a while. 4. Send us an email, with a link to the public email thread. 5. We will grant you maintenance rights. Maintainer reachable: Option 1 (preferred): 1. Original maintainer gives you access at http://hackage.haskell.org/package//maintainers/ Option 2: 1. Email us, with the maintainer CCed. 2. Maintainer replies to email saying it's OK. 3. We grant access. -- Johan On Thu, Jan 30, 2014 at 8:30 AM, Roman Cheplyaka wrote: > In the recent past I took over two unmaintained packages: bert and > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > from bitrotting. > > However, both times I had to go through an irritating procedure of > contacting hackage admins, asking them to grant me upload rights, > explaining why the maintainers can't do that themselves and why I think > the packages are abandoned. > > Instead of a feeling that I'm doing something good and useful, I have > a feeling that I'm bothering people with my own problems. It also adds > unnecessary latency to my work. > > So from now on I'll simply fork the packages I need to fix. > > Others are of course welcome to use my forks. > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > and whose maintainer hasn't responded. My fork is at > http://hackage.haskell.org/package/regex-tdfa-rc .) > > Roman > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From christianlaustsen at gmail.com Thu Jan 30 18:01:51 2014 From: christianlaustsen at gmail.com (Christian Laustsen) Date: Thu, 30 Jan 2014 19:01:51 +0100 Subject: [Haskell-cafe] Deprecating bytestring version 0.10.2.0 Message-ID: Hi everyone, Following some problems I experienced with Network.HTTP.Client.TLS, I found out the problem was specific to bytestring library version 0.10.2.0 and most likely fixed with this commit https://github.com/haskell/bytestring/commit/86df1f17b2332940df69f484182c5c2cdd4c5bec . The default version shipped with GHC 7.6.3 (0.10.0.2) works fine, and the version after 0.10.2.0 (that is, version 0.10.4.0) also works. It was suggested that I mention on here that I think we should deprecate the 0.10.2.0 version of bytestring specifically, since that is the one that introduces the problem, and there can be problems with having to specify specific versions of bytestring as a dependency when compiling across GHC versions. -- Christian // Tehnix -------------- next part -------------- An HTML attachment was scrubbed... URL: From gershomb at gmail.com Thu Jan 30 18:11:30 2014 From: gershomb at gmail.com (Gershom Bazerman) Date: Thu, 30 Jan 2014 13:11:30 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <8761p1fm1n.fsf@gmail.com> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> Message-ID: <52EA95D2.40400@gmail.com> (ccing hackage admin alias directly, just to make sure the right people are seeing all the emails) I think there are two _different_ issues we've been conflating under "taking over a package". 1) A package is genuinely unmaintained and it should be taken over by someone else, and someone steps up. This is fine to take some time, in my book. Our current process, as described by Johan Tibell, is reasonable. It _should_ be easily accessible from the hackage homepage, _and_ it should be on the haskell wiki. Perhaps the homepage could link to a hackage FAQ on the wiki? Volunteers on any of this? 2) A package needs patching to work with the latest deps, and the maintainer is unreachable, then we just want to upload a fixed version soon. But who knows, maybe we don't want to take it over for good. Maybe the maintainer is just on a monthlong vacation on a small island chain. Maybe they're sick, or busy at work. This is the sticking point. So maybe we could have a different policy on the latter. There are people like Roman, Ben, others, who I feel like I sort of "know" from their presence in the community, whether or not I've met them personally. I'd feel comfortable letting trusted community members not "take over" packages entirely without process, but use a more relaxed process simply to upload simple patches for compatibility, etc. Is there some way that we could create a "two process" approach -- one for taking over a package, and a more relaxed one for trusted individuals to fix things up easily? --Gershom On 1/30/14, 11:53 AM, Ben Gamari wrote: > Clark Gaebel writes: > >> How does the process of taking over maintenance add latency to your work? >> >> 1) Check out broken version of package. >> 2) Fix locally, bump version number locally. >> 3) cabal sandbox add-source ../fixed-package in any package that needs the >> fixed version. >> 4) Email hackage admins for upload rights. >> 5) Continue working on your actual project. >> 6) Receive upload privileges one day. >> 7) Upload fixed package. >> >> As far as I can tell, the only real latency cost here is that paid to fix >> the broken version. >> > In my experience, step 4 involved several round trips between a number > of different people. Admittedly, this is in part because it's easy to > forget about the broken package after you have fixed it locally. > > Cheers, > > - Ben > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Thu Jan 30 18:30:33 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 30 Jan 2014 19:30:33 +0100 Subject: [Haskell-cafe] Deprecating bytestring version 0.10.2.0 In-Reply-To: References: Message-ID: See also https://github.com/snoyberg/http-conduit/issues/145 Erik On Thursday, January 30, 2014, Christian Laustsen < christianlaustsen at gmail.com> wrote: > Hi everyone, > > Following some problems I experienced with Network.HTTP.Client.TLS, I > found out the problem was specific to bytestring library version 0.10.2.0 > and most likely fixed with this commit > https://github.com/haskell/bytestring/commit/86df1f17b2332940df69f484182c5c2cdd4c5bec > . > > The default version shipped with GHC 7.6.3 (0.10.0.2) works fine, and the > version after 0.10.2.0 (that is, version 0.10.4.0) also works. > > It was suggested that I mention on here that I think we should deprecate > the 0.10.2.0 version of bytestring specifically, since that is the one that > introduces the problem, and there can be problems with having to specify > specific versions of bytestring as a dependency when compiling across GHC > versions. > > -- > Christian // Tehnix > -------------- next part -------------- An HTML attachment was scrubbed... URL: From duncan at well-typed.com Thu Jan 30 18:39:37 2014 From: duncan at well-typed.com (Duncan Coutts) Date: Thu, 30 Jan 2014 18:39:37 +0000 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <52EA95D2.40400@gmail.com> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> Message-ID: <1391107177.17028.21.camel@dunky.localdomain> On Thu, 2014-01-30 at 13:11 -0500, Gershom Bazerman wrote: > (ccing hackage admin alias directly, just to make sure the right people > are seeing all the emails) > > I think there are two _different_ issues we've been conflating under > "taking over a package". > > 1) A package is genuinely unmaintained and it should be taken over by > someone else, and someone steps up. This is fine to take some time, in > my book. Our current process, as described by Johan Tibell, is > reasonable. It _should_ be easily accessible from the hackage homepage, > _and_ it should be on the haskell wiki. Perhaps the homepage could link > to a hackage FAQ on the wiki? Volunteers on any of this? Right, Johan described our policy, and indeed that should be documented in obvious places. > 2) A package needs patching to work with the latest deps, and the > maintainer is unreachable, then we just want to upload a fixed version > soon. But who knows, maybe we don't want to take it over for good. Maybe > the maintainer is just on a monthlong vacation on a small island chain. > Maybe they're sick, or busy at work. This is the sticking point. > > So maybe we could have a different policy on the latter. There are > people like Roman, Ben, others, who I feel like I sort of "know" from > their presence in the community, whether or not I've met them > personally. I'd feel comfortable letting trusted community members not > "take over" packages entirely without process, but use a more relaxed > process simply to upload simple patches for compatibility, etc. > > Is there some way that we could create a "two process" approach -- one > for taking over a package, and a more relaxed one for trusted > individuals to fix things up easily? So this one is easy so long as the maintainer (or one of the maintainers) is reachable, because then a maintainer can spend 30 seconds to add the person volunteering to make the fix to the maintainer group for the package. If the maintainer(s) is/are unreachable then that's a hard call. They have not pre-approved (which they can do by adding some trusted person to the maintainer group) and they are not in a position to approve or not in the short term as they are unreachable. In general we like to give authors/maintainers strong control over their packages. I should note that a maintainer could pre-approve some helper to whom they can delegate the decision. For example, suppose volunteered to be a person of good taste who would review cases where the package needs fixing in simple ways but the maintainer is away. That person does not have to be the one who develops the fix or even necessarily the person who uploads it. What the maintainer would need to do is to add that volunteer of good taste to the maintainer group, and then that volunteer now has all the same rights as the "real" maintainer and so can upload the fixed package themselves or even add the person who did the fix to the maintainer group too (different maintainers and fixers might agree different policies here). But otherwise, in general I think we do not want to force maintainers to accept "fixes" from other developers without any kind of pre-approval. So the worst case of there being no pre-approved helper and the maintainer uncontactable in the short term would simply remain. On the other hand we can certainly encourage and ease setting up pre-approval with volunteers, especially for important packages. Or just encourage people to add secondary/backup maintainers to their packages. A little bit of planning will avoid the angst. -- Duncan Coutts, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From michael at orlitzky.com Thu Jan 30 18:47:29 2014 From: michael at orlitzky.com (Michael Orlitzky) Date: Thu, 30 Jan 2014 13:47:29 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <1391107177.17028.21.camel@dunky.localdomain> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> Message-ID: <52EA9E41.9010704@orlitzky.com> On 01/30/2014 01:39 PM, Duncan Coutts wrote: > > I should note that a maintainer could pre-approve some helper to whom > they can delegate the decision. For example, suppose volunteered to be a > person of good taste who would review cases where the package needs > fixing in simple ways but the maintainer is away. That person does not > have to be the one who develops the fix or even necessarily the person > who uploads it. What the maintainer would need to do is to add that > volunteer of good taste to the maintainer group, and then that volunteer > now has all the same rights as the "real" maintainer and so can upload > the fixed package themselves or even add the person who did the fix to > the maintainer group too (different maintainers and fixers might agree > different policies here). I don't suppose there's any support for groups in hackage2? I don't know anyone in particular that I'd want to pre-delegate this responsibility to, but I would be fine with e.g. delegating it to "the hackage team" (who I already implicitly trust). They could then make the decision on my behalf, using something like Gershom's "I feel like I can trust this guy" criteria. From fuuzetsu at fuuzetsu.co.uk Thu Jan 30 18:57:31 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 30 Jan 2014 18:57:31 +0000 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <52EA9E41.9010704@orlitzky.com> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> <52EA9E41.9010704@orlitzky.com> Message-ID: <52EAA09B.5030307@fuuzetsu.co.uk> On 30/01/14 18:47, Michael Orlitzky wrote: > On 01/30/2014 01:39 PM, Duncan Coutts wrote: >> >> I should note that a maintainer could pre-approve some helper to whom >> they can delegate the decision. For example, suppose volunteered to be a >> person of good taste who would review cases where the package needs >> fixing in simple ways but the maintainer is away. That person does not >> have to be the one who develops the fix or even necessarily the person >> who uploads it. What the maintainer would need to do is to add that >> volunteer of good taste to the maintainer group, and then that volunteer >> now has all the same rights as the "real" maintainer and so can upload >> the fixed package themselves or even add the person who did the fix to >> the maintainer group too (different maintainers and fixers might agree >> different policies here). > > I don't suppose there's any support for groups in hackage2? I don't know > anyone in particular that I'd want to pre-delegate this responsibility > to, but I would be fine with e.g. delegating it to "the hackage team" > (who I already implicitly trust). > > They could then make the decision on my behalf, using something like > Gershom's "I feel like I can trust this guy" criteria. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Is [1] what you're after? It was unused until recently as far as I know. [1]: https://hackage.haskell.org/packages/trustees/ -- Mateusz K. From michael at orlitzky.com Thu Jan 30 19:22:01 2014 From: michael at orlitzky.com (Michael Orlitzky) Date: Thu, 30 Jan 2014 14:22:01 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <52EAA09B.5030307@fuuzetsu.co.uk> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> <52EA9E41.9010704@orlitzky.com> <52EAA09B.5030307@fuuzetsu.co.uk> Message-ID: <52EAA659.8060907@orlitzky.com> On 01/30/2014 01:57 PM, Mateusz Kowalczyk wrote: > > Is [1] what you're after? It was unused until recently as far as I know. > > [1]: https://hackage.haskell.org/packages/trustees/ > Sort of; I was wondering if there was a way to add "trustees" as a maintainer so that they know they can fix my packages without having to track me down first. From hesselink at gmail.com Thu Jan 30 19:23:02 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 30 Jan 2014 20:23:02 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <1391107177.17028.21.camel@dunky.localdomain> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> Message-ID: As one of the hackage admins, I should probably weigh in here too. First, let's not forget that one of the big new features of the new hackage was the addition of proper permission checks for uploading new versions of packages. Previously, anyone could upload any package, which is a huge security risk for one, and also violates the expectations of package owners as well. So I think this feature is a good one. Second, there are a lot of abandoned packages. It is good for the community if people take over maintenance of these, so the process for doing this should be as smooth as possible. Note that these two things are at odds. So we have to find a balance. Johan already mentioned the process we use, although we recently discussed changing it a bit so that the hackage admins would email the maintainer instead of the user wanting to take over. This is because of a recent mishap where a package was taken over because the maintainer missed the initial email (and haskell-cafe message). I agree that this process is suboptimal, at least for some scenarios. It's a lot of work for both the user and the hackage admins. Also, it's unclear to me how long the wait periods have to be. The distinction between actually taking over maintainership and just doing some small fixes seems to be a good one, though it's not exactly clear where to draw the line. Fixing compilation issues on newer GHCs and relaxing dependencies seems ok to me, though. There is support for trustees on the new hackage, as other's mentioned. These can maintain any package. Perhaps this would be a good time to recruit a few of them? Regards, Erik On Thu, Jan 30, 2014 at 7:39 PM, Duncan Coutts wrote: > On Thu, 2014-01-30 at 13:11 -0500, Gershom Bazerman wrote: >> (ccing hackage admin alias directly, just to make sure the right people >> are seeing all the emails) >> >> I think there are two _different_ issues we've been conflating under >> "taking over a package". >> >> 1) A package is genuinely unmaintained and it should be taken over by >> someone else, and someone steps up. This is fine to take some time, in >> my book. Our current process, as described by Johan Tibell, is >> reasonable. It _should_ be easily accessible from the hackage homepage, >> _and_ it should be on the haskell wiki. Perhaps the homepage could link >> to a hackage FAQ on the wiki? Volunteers on any of this? > > Right, Johan described our policy, and indeed that should be documented > in obvious places. > >> 2) A package needs patching to work with the latest deps, and the >> maintainer is unreachable, then we just want to upload a fixed version >> soon. But who knows, maybe we don't want to take it over for good. Maybe >> the maintainer is just on a monthlong vacation on a small island chain. >> Maybe they're sick, or busy at work. This is the sticking point. >> >> So maybe we could have a different policy on the latter. There are >> people like Roman, Ben, others, who I feel like I sort of "know" from >> their presence in the community, whether or not I've met them >> personally. I'd feel comfortable letting trusted community members not >> "take over" packages entirely without process, but use a more relaxed >> process simply to upload simple patches for compatibility, etc. >> >> Is there some way that we could create a "two process" approach -- one >> for taking over a package, and a more relaxed one for trusted >> individuals to fix things up easily? > > So this one is easy so long as the maintainer (or one of the > maintainers) is reachable, because then a maintainer can spend 30 > seconds to add the person volunteering to make the fix to the maintainer > group for the package. > > If the maintainer(s) is/are unreachable then that's a hard call. They > have not pre-approved (which they can do by adding some trusted person > to the maintainer group) and they are not in a position to approve or > not in the short term as they are unreachable. In general we like to > give authors/maintainers strong control over their packages. > > I should note that a maintainer could pre-approve some helper to whom > they can delegate the decision. For example, suppose volunteered to be a > person of good taste who would review cases where the package needs > fixing in simple ways but the maintainer is away. That person does not > have to be the one who develops the fix or even necessarily the person > who uploads it. What the maintainer would need to do is to add that > volunteer of good taste to the maintainer group, and then that volunteer > now has all the same rights as the "real" maintainer and so can upload > the fixed package themselves or even add the person who did the fix to > the maintainer group too (different maintainers and fixers might agree > different policies here). > > But otherwise, in general I think we do not want to force maintainers to > accept "fixes" from other developers without any kind of pre-approval. > So the worst case of there being no pre-approved helper and the > maintainer uncontactable in the short term would simply remain. > > On the other hand we can certainly encourage and ease setting up > pre-approval with volunteers, especially for important packages. Or just > encourage people to add secondary/backup maintainers to their packages. > > A little bit of planning will avoid the angst. > > -- > Duncan Coutts, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > From malcolm.wallace at me.com Thu Jan 30 19:34:16 2014 From: malcolm.wallace at me.com (Malcolm Wallace) Date: Thu, 30 Jan 2014 19:34:16 +0000 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> Message-ID: <482B394E-2D7D-4733-804B-5E343C2E7EF4@me.com> > On 30 Jan 2014, at 19:23, Erik Hesselink wrote: > > h it's not exactly clear > where to draw the line. Fixing compilation issues on newer GHCs and > relaxing dependencies seems ok to me, though. It seems to me that the fundamental problem is that new releases of ghc break too many things, and the PVP encourages authors to set dependency bounds that are too tight. If we could solve those things, maintenance would be much less of a burden. Regards, Malcolm From hesselink at gmail.com Thu Jan 30 19:39:06 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 30 Jan 2014 20:39:06 +0100 Subject: [Haskell-cafe] liboleg In-Reply-To: <87zjn87yxo.fsf@chaos.shergill.su> References: <874n5gaazx.fsf@chaos.shergill.su> <87zjn87yxo.fsf@chaos.shergill.su> Message-ID: On Tue, Jan 7, 2014 at 1:34 PM, Suhail Shergill wrote: > Erik Hesselink writes: > >> In cases where the maintainer is unresposive/unavailable, we (hackage admins) >> can do it, but that doesn't seem to be the case here. > > though don did grant me permission via email, i never heard back from him when i > asked him to add me to the maintainers group (i verified by trying to log in to > ). should i be able to > access that area *before* i upload a copy of liboleg, or only afterwards? i'm > cc-ing don to this thread as well. > > since this will be the first time i'll be maintaining a package on hackage it's > possible i'm making some fundamental mistake; if so please do correct me (and > excuse my bumbling ways). Oleg, Don: could you either: 1) Add Suhail to the maintainers for liboleg. This is the best option, since us having to do this for every package doesn't scale. 2) Tell us it's ok, but you don't want to/can't add Suhail. In that case we'll do it. Suhail, you should be able to access that area once you are a maintainer, before you upload the package. Regards, Erik From marco-oweber at gmx.de Thu Jan 30 19:40:56 2014 From: marco-oweber at gmx.de (Marc Weber) Date: Thu, 30 Jan 2014 20:40:56 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <1391107177.17028.21.camel@dunky.localdomain> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> Message-ID: <1391110546-sup-740@nixos> I feel Duncan Coutts is right. Just fixing deps could be done by anyone. Bigger changes (design choices) about more complicated packages should be done on forks till the maintainer replies or failed doing so for some time. However live must go on in such case, too. Thus forking seems to be the best way to continue. Then it should be possible to signal that there is an alternative upstream for that possibly unmaintained package. Maybe a cabal field such as improves-uppon: other-package If the maintainer replies it can be deprecated and upstream can be merged easily. There are different approaches, too. Eg github/bitbucket support teams/organizations. Eg the haskell community could just start a such a team which implies that all packages hosted there may be updated be the community as well (unless there are special notes in the .cabal file/readme). Its not only about putting updated packages on hackage, also about knowing where current upstream is (if others want to join its easy to miss such a fork) - with a community bitbucket the new version could just be a new branch .. How well such works in the real world - no idea. In the Vim community there are severall packages whose maintainers changed and where 2 to 3 people fix some small bugs occasionally. Marc Weber From corentin.dupont at gmail.com Thu Jan 30 19:53:40 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 30 Jan 2014 20:53:40 +0100 Subject: [Haskell-cafe] Fwd: manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Oleg: Very interresting, thanks. I have some questions: - What do you mean by "The type Cont Int a describes an impure computation, which may abort with an Int value, for example". Aborting with an Int value is akin to exceptions? - for me it's not clear when to choose an "applicative" or a "monadic" DSL? Betsides, what's the rational behind the name "let_" (never seen it before)? Linsey, Jacques: Thanks for the pointer! I learned about data kinds. I tried to apply your suggestions to add a phantom type parameter to Exp. I came up to (I dropped the Free monad idea, which seems unrelated to the problem): > data Eff = Effect | NoEffect > -- first type parameter is used to track effects > data Exp :: Eff -> * -> * where > ReadAccount :: Exp r Int --ReadAccount can be used in whatever monad (with or without effect) > WriteAccount :: Exp NoEffect Int -> Exp Effect () --WriteAccount takes an effect-less expression, and returns an effectfull expression > SetVictory :: Exp NoEffect Bool -> Exp Effect () -- same for SetVictory > OnTimer :: Exp Effect () -> Exp Effect () --OnTime can program whatever expression to be triggered every minutes, in particular effectful ones > Return :: a -> Exp r a > Bind :: Exp r a -> (a -> Exp r b) -> Exp r b This is the (simplified) game state: > data Game = Game { bankAccount :: Int, > victory :: Exp NoEffect Bool, > timerEvent :: Exp Effect ()} > -- victory when account > 100 > victoryRule' :: Exp Effect () > victoryRule' = SetVictory $ do > m <- readAccount > --WriteAccount (return $ m + 1) --won't compile (good) > return (m > 100) > --increase my bank account by 1 every minute > myTimer :: Exp Effect () > myTimer = OnTimer $ do > m <- readAccount > writeAccount (return $ m + 1) Do you have a better name suggestion for Eff? Other pointers where this idiom is realised?? Thanks!! Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From mle+hs at mega-nerd.com Thu Jan 30 22:22:36 2014 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Fri, 31 Jan 2014 09:22:36 +1100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140130163055.GA19868@sniper> References: <20140130163055.GA19868@sniper> Message-ID: <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> Roman Cheplyaka wrote: > In the recent past I took over two unmaintained packages: bert and > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > from bitrotting. > > However, both times I had to go through an irritating procedure of > contacting hackage admins, asking them to grant me upload rights, > explaining why the maintainers can't do that themselves and why I think > the packages are abandoned. > > Instead of a feeling that I'm doing something good and useful, I have > a feeling that I'm bothering people with my own problems. It also adds > unnecessary latency to my work. > > So from now on I'll simply fork the packages I need to fix. > > Others are of course welcome to use my forks. > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > and whose maintainer hasn't responded. My fork is at > http://hackage.haskell.org/package/regex-tdfa-rc .) Roman, I really can understand why you did this; I am frustrated by some of the same issues. However, I think if any significant number of people did this, the results could easily be disasterous. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From carter.schonwald at gmail.com Thu Jan 30 22:26:34 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 30 Jan 2014 17:26:34 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> Message-ID: i second erik's sentiment. On Thu, Jan 30, 2014 at 5:22 PM, Erik de Castro Lopo wrote: > Roman Cheplyaka wrote: > > > In the recent past I took over two unmaintained packages: bert and > > ansi-terminal. I don't mind spending a bit of time to keep our ecosystem > > from bitrotting. > > > > However, both times I had to go through an irritating procedure of > > contacting hackage admins, asking them to grant me upload rights, > > explaining why the maintainers can't do that themselves and why I think > > the packages are abandoned. > > > > Instead of a feeling that I'm doing something good and useful, I have > > a feeling that I'm bothering people with my own problems. It also adds > > unnecessary latency to my work. > > > > So from now on I'll simply fork the packages I need to fix. > > > > Others are of course welcome to use my forks. > > > > (This email was prompted by regex-tdfa which doesn't build on GHC 7.8, > > and whose maintainer hasn't responded. My fork is at > > http://hackage.haskell.org/package/regex-tdfa-rc .) > > Roman, > > I really can understand why you did this; I am frustrated by some of > the same issues. However, I think if any significant number of people > did this, the results could easily be disasterous. > > Erik > -- > ---------------------------------------------------------------------- > Erik de Castro Lopo > http://www.mega-nerd.com/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Fri Jan 31 02:15:30 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Fri, 31 Jan 2014 04:15:30 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> Message-ID: <20140131021530.GA25143@sniper> * Erik de Castro Lopo [2014-01-31 09:22:36+1100] > I really can understand why you did this; I am frustrated by some of > the same issues. However, I think if any significant number of people > did this, the results could easily be disasterous. Agreed. Maybe we need those disasterous results to realize that the current process is bad and come up with a better one. Or maybe it's just me, and everyone else is happy (enough) with the process, so nothing will happen. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From evan at theunixman.com Fri Jan 31 06:11:52 2014 From: evan at theunixman.com (Evan Cofsky) Date: Fri, 31 Jan 2014 06:11:52 +0000 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131021530.GA25143@sniper> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: <20140131061151.GL60654@serenity.tunixman.com> Hello, As you all know I'm new to Haskell, but not at all new to software communities or computer security. The Haskell community is maturing, and as part of that we will have to be able to ensure that social engineering attacks against our core infrastructure, such as the canonical package repository, are not trivial to pull off successfully. There are several instances just in the past week that have been making the rounds of basic impersonation attacks having disastrous consequences because people were quite willing to trust complete strangers, and of course we all know about the various problems faced by the Node and the Ruby communities and their package management systems, which were fully automated. I put a lot more faith into Haskell programs, probably naively so, but as people, though, we have to at least maintain a certain amount of healthy skepticism when it comes to responding to requests to take over projects, and without a doubt along with that skepticism comes friction and process. But these are absolutely essential to having a trustworthy resource in Hackage, and I think that far outweighs the ficticious freedoms offered by management by handshake and a smile, especially for such an important community resource. -- Evan Cofsky -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 228 bytes Desc: not available URL: From oleg at okmij.org Fri Jan 31 08:24:50 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 31 Jan 2014 08:24:50 -0000 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: Message-ID: <20140131082450.70346.qmail@www1.g3.pair.com> > - What do you mean by "The type Cont Int a describes an impure computation, > which may abort with an Int value, for example". > Aborting with an Int value is akin to exceptions? I see that using Cont monad wasn't a good idea. The point can be made simply, with an Error monad or applicative. Here is a simple function to multiply a list of integers: > muls :: [Integer] -> Either e Integer > muls [] = pure 1 > muls (h:t) = (h*) <$> muls t We give the signature (which the compiler accepts) with the polymorphic return type Either e Integer, fully polymorphic over e. Therefore, muls throws no exceptions. Here is a bit more optimized function, which stops all multiplications once zero is encountered. > mulse :: [Integer] -> Either Integer Integer > mulse [] = pure 1 > mulse (0:t) = Left 0 > mulse (h:t) = (h*) <$> mulse t We cannot make the return type (Either e Integer), it must be (Either Integer Integer). The function can indeed throw an exception. If we handle the exception > muls' :: [Integer] -> Either e Integer > muls' l = either pure pure $ mulse l the effect is encapsulated and the type is polymorphic again. > - for me it's not clear when to choose an "applicative" or a "monadic" DSL? > Betsides, what's the rational behind the name "let_" (never seen it before)? The first rule of thumb is to use the simplest structure that does the job. Another good rule is to distinguish the DSL from its implementation. For example, the DSL below http://okmij.org/ftp/tagless-final/index.html#call-by-any has no monads. It is a simple lambda-calculus with constants. Its implementation in Haskell, the embedding, does use monads, sometimes quite specific monads (e.g., IO, to print the trace of evaluation). But these monads are not exposed to the DSL programmer. That article also shows off let_. > data Eff = Effect | NoEffect > -- first type parameter is used to track effects > data Exp :: Eff -> * -> * where > ReadAccount :: Exp r Int --ReadAccount can be used in whatever > monad (with or without effect) > WriteAccount :: Exp NoEffect Int -> Exp Effect () --WriteAccount > takes an effect-less expression, and returns an effectfull expression This is exactly what I had in mind (and probably Jacques as well). > Other pointers where this idiom is realised?? Lots of places; ST monad comes to mind, and the Region monad. This trick is often used to track, for example, information flow security (the label then reflects the sensitivity level of data processed by the computation, Low or High). See, for example, http://www.cse.chalmers.se/~russo/seclib.htm http://www.scs.stanford.edu/~deian/pubs/stefan:2011:flexible-slides.pdf or just search for information flow control or information flow security in Haskell. Edward Yang has a lot to say on this topic. From P.Achten at cs.ru.nl Fri Jan 31 08:49:37 2014 From: P.Achten at cs.ru.nl (Peter Achten) Date: Fri, 31 Jan 2014 09:49:37 +0100 Subject: [Haskell-cafe] TFP 2014 - 2nd call for papers Message-ID: <52EB63A1.2070602@cs.ru.nl> --------------------------------- 2ND C A L L F O R P A P E R S --------------------------------- ======== TFP 2014 =========== 15th Symposium on Trends in Functional Programming May 26-28, 2014 Utrecht University Soesterberg, The Netherlands http://www.cs.uu.nl/wiki/TFP2014/WebHome *** Submission for TFP 2014 is now open: please direct your browser to *** http://www.cs.uu.nl/wiki/TFP2014/PaperSubmission The symposium on Trends in Functional Programming (TFP) is an international forum for researchers with interests in all aspects of functional programming, taking a broad view of current and future trends in the area. It aspires to be a lively environment for presenting the latest research results, and other contributions (see below), described in draft papers submitted prior to the symposium. A formal post-symposium refereeing process then selects a subset of the articles presented at the symposium and submitted for formal publication. Selected revised papers will be published as a Springer Lecture Notes in Computer Science (LNCS) volume. TFP 2014 will be the main event of a pair of functional programming events. The other is the International Workshop on Trends in Functional Programming in Education (TFPIE). TFPIE will take place on May 25th. Its website is located at http://www.cs.uwyo.edu/~jlc/tfpie14/ The TFP symposium is the heir of the successful series of Scottish Functional Programming Workshops. Previous TFP symposia were held in Edinburgh (Scotland) in 2003, in Munich (Germany) in 2004, in Tallinn (Estonia) in 2005, in Nottingham (UK) in 2006, in New York (USA) in 2007, in Nijmegen (The Netherlands) in 2008, in Komarno (Slovakia) in 2009, in Oklahoma (USA) in 2010, in Madrid (Spain) in 2011, St. Andrews (UK) in 2012 and Provo (Utah, USA) in 2013. For further general information about TFP please see the TFP homepage. INVITED SPEAKERS TFP is pleased to announce talks by the following two invited speakers: John Hughes of Chalmers, Goteborg, Sweden, is well-known as author of Why Functional Programming Matters, and as one of the designers of QuickCheck (together with Koen Claessen); the paper on QuickCheck won the ICFP Most Influential Paper Award in 2010. Currently he divides his time between his professorship and Quviq, a company that performs property-based testing of software with a tool implemented in Erlang. Dr. Geoffrey Mainland received his PhD from Harvard University where he was advised by Greg Morrisett and Matt Welsh. After a two year postdoc with the Programming Principles and Tools group at Microsoft Research Cambridge, he is now an assistant professor at Drexel University. His research focuses on high-level programming language and runtime support for non-general purpose computation. SCOPE The symposium recognizes that new trends may arise through various routes. As part of the Symposium's focus on trends we therefore identify the following five article categories. High-quality articles are solicited in any of these categories: Research Articles: leading-edge, previously unpublished research work Position Articles: on what new trends should or should not be Project Articles: descriptions of recently started new projects Evaluation Articles: what lessons can be drawn from a finished project Overview Articles: summarizing work with respect to a trendy subject Articles must be original and not submitted for simultaneous publication to any other forum. They may consider any aspect of functional programming: theoretical, implementation-oriented, or more experience-oriented. Applications of functional programming techniques to other languages are also within the scope of the symposium. Topics suitable for the symposium include: Functional programming and multicore/manycore computing Functional programming in the cloud High performance functional computing Extra-functional (behavioural) properties of functional programs Dependently typed functional programming Validation and verification of functional programs Using functional techniques to reason about imperative/object-oriented programs Debugging for functional languages Functional programming in different application areas: security, mobility, telecommunications applications, embedded systems, global computing, grids, etc. Interoperability with imperative programming languages Novel memory management techniques Program analysis and transformation techniques Empirical performance studies Abstract/virtual machines and compilers for functional languages (Embedded) domain specific languages New implementation strategies Any new emerging trend in the functional programming area If you are in doubt on whether your article is within the scope of TFP, please contact the TFP 2014 program chair, Jurriaan Hage at J.Hage at uu.nl. BEST PAPER AWARDS To reward excellent contributions, TFP awards a prize for the best paper accepted for the formal proceedings. TFP traditionally pays special attention to research students, acknowledging that students are almost by definition part of new subject trends. A student paper is one for which the authors state that the paper is mainly the work of students, the students are listed as first authors, and a student would present the paper. A prize for the best student paper is awarded each year. In both cases, it is the PC of TFP that awards the prize. In case the best paper happens to be a student paper, that paper will then receive both prizes. SPONSORS TFP is financially supported by NWO (Netherlands Organisation for Scientific Research), Well-Typed and Erlang Solutions. PAPER SUBMISSIONS Acceptance of articles for presentation at the symposium is based on a lightweight peer review process of extended abstracts (4 to 10 pages in length) or full papers (16 pages). The submission must clearly indicate which category it belongs to: research, position, project, evaluation, or overview paper. It should also indicate whether the main author or authors are research students. In the case of a FULL STUDENT paper, the draft paper will receive additional feedback by one of the PC members shortly after the symposium has taken place. We use EasyChair for the refereeing process. IMPORTANT DATES Submission of draft papers: March 17, 2014 Notification: March 24, 2014 Registration: April 7, 2014 TFP Symposium: May 26-28, 2014 Student papers feedback: June 9th, 2014 Submission for formal review: July 1st, 2014 Notification of acceptance: September 8th, 2014 Camera ready paper: October 8th, 2014 PROGRAM COMMITTEE Peter Achten Radboud University Nijmegen Emil Axelsson Chalmers Lucilia Camarao de Figueiredo Universidade Federal de Ouro Preto Laura Castro University of A Coruna Frank Huch Christian-Albrechts-University of Kiel Matthew Fluet Rochester Institute of Technology Jurriaan Hage (chair) University of Utrecht Yukiyoshi Kameyama University of Tsukuba Andrew Kennedy Microsoft Research Tamas Kozsik Eotvos Lorand University Ben Lippmeier University of New South Wales Luc Maranget INRIA Jay McCarthy (co-chair) Brigham Young University Marco T. Morazan Seton Hall University Ricardo Pena Universidad Complutense de Madrid Alexey Rodriguez LiquidM Sven-Bodo Scholz Heriot-Watt University Manuel Serrano INRIA Sophia Antipolis Simon Thompson University of Kent Tarmo Uustalu Inst of Cybernetics David Van Horn University of Maryland Janis Voigtlaender University of Bonn From hesselink at gmail.com Fri Jan 31 09:04:33 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 31 Jan 2014 10:04:33 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131021530.GA25143@sniper> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka wrote: > * Erik de Castro Lopo [2014-01-31 09:22:36+1100] >> I really can understand why you did this; I am frustrated by some of >> the same issues. However, I think if any significant number of people >> did this, the results could easily be disasterous. > > Agreed. Maybe we need those disasterous results to realize that the > current process is bad and come up with a better one. Or maybe it's just > me, and everyone else is happy (enough) with the process, so nothing > will happen. That's a rather fatalist attitude, and also one that is not warranted given the replies in this thread. Let me try to be more constructive instead: I propose to make the trustees group able to upload any package, with the understanding that they only do so to make packages where the maintainer is unreachable compile on more compilers or with more versions of dependencies. The newly uploaded version should have a public repository of the forked source available and listed in the cabal file. The process would then be: * User fixes a package, emails the maintainer. * No response: User emails trustees. * Trustees check the above conditions, and upload the new version. This is more lightweight that the process to take over maintainership, and it can be, because we're not trusting a random user with a random package. Instead, we're only trusting a fixed set of maintainers and a small, publicly visible change. Because of this, the waiting times for non-responsiveness can probably also be shorter than in the maintainer take-over process. Would this alleviate the frustration, while at the same time maintaining enough security and sense of package ownership? Regards, Erik From carlo at carlo-hamalainen.net Fri Jan 31 09:26:05 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Fri, 31 Jan 2014 10:26:05 +0100 Subject: [Haskell-cafe] Cabal version constraint seems to be ignored. In-Reply-To: <52E55F29.4040301@vex.net> References: <52DFBCF6.60801@carlo-hamalainen.net> <52E55F29.4040301@vex.net> Message-ID: <52EB6C2D.5040607@carlo-hamalainen.net> On 26/01/14 20:16, Albert Y. C. Lai wrote: > It seems that you are using GHC API. Then your program starts a GHC > session, which is not unlike an average ghci session, in particular: > > A. It will load and link libraries afresh during run time. This is > independent of whatever your executable is linked with. > > B. And the default choice of libraries is, clearly: the newest > unhidden version. > > Therefore, when your GHC session also has to work with compiled code > built against older versions, there will be incompatibilities. Ah, I see. > What do you tell your users? In my testing, using cabal sandboxes seems to work, but that's not really a full solution. > P.S. cabal-install goes out of its way to dictate library versions to > ghc. It begins with -hide-all-packages, then it recites, one by one, > -package base-4.1.0.0, -package Cabal-1.16.0, -package > text-0.11.3.1,... Are you going to bother to do the same? I did add some functionality like this recently: https://github.com/carlohamalainen/ghc-imported-from/commit/e1a212000a73372f84aecd307d9d794c87768e93#diff-d2ce8e34838af0511940565d8c9d7addR108 (around line 108) which is just using ghc-mod's API to do so. But I still run into the original problem that I had before, at least when not using a sandbox. I'm not sure what to do from here. -- Carlo Hamalainen http://carlo-hamalainen.net From roma at ro-che.info Fri Jan 31 11:02:08 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Fri, 31 Jan 2014 13:02:08 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131061151.GL60654@serenity.tunixman.com> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> Message-ID: <20140131110208.GA26266@sniper> So let's talk about security. The current process protects against malicious parties rather poorly. It protects against malicious takeover of a maintained package, but an adversary could presumably find an unmaintained or semi-maintained yet popular package (such as ansi-terminal) to pull off an attack. The process does protect against *targeted* malicious takeover (i.e. an adversary wants to inject malicious code in exactly the (maintained) package K, and not just any moderately popular (but unmaintained) package L). But that is not enough. So security and trust have to be enforced by a different mechanism anyway. Roman * Evan Cofsky [2014-01-31 06:11:52+0000] > Hello, > > As you all know I'm new to Haskell, but not at all new to software > communities or computer security. The Haskell community is maturing, > and as part of that we will have to be able to ensure that social > engineering attacks against our core infrastructure, such as the > canonical package repository, are not trivial to pull off > successfully. > > There are several instances just in the past week that have been > making the rounds of basic impersonation attacks having disastrous > consequences because people were quite willing to trust complete > strangers, and of course we all know about the various problems faced > by the Node and the Ruby communities and their package management > systems, which were fully automated. > > I put a lot more faith into Haskell programs, probably naively so, but > as people, though, we have to at least maintain a certain amount of > healthy skepticism when it comes to responding to requests to take > over projects, and without a doubt along with that skepticism comes > friction and process. But these are absolutely essential to having a > trustworthy resource in Hackage, and I think that far outweighs the > ficticious freedoms offered by management by handshake and a smile, > especially for such an important community resource. > > -- > Evan Cofsky -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From roma at ro-che.info Fri Jan 31 11:16:49 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Fri, 31 Jan 2014 13:16:49 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: <20140131111649.GB26266@sniper> * Erik Hesselink [2014-01-31 10:04:33+0100] > I propose to make the trustees group able to upload any package, with > the understanding that they only do so to make packages where the > maintainer is unreachable compile on more compilers or with more > versions of dependencies. The newly uploaded version should have a > public repository of the forked source available and listed in the > cabal file. The process would then be: > > * User fixes a package, emails the maintainer. > * No response: User emails trustees. > * Trustees check the above conditions, and upload the new version. > > This is more lightweight that the process to take over maintainership, > and it can be, because we're not trusting a random user with a random > package. Instead, we're only trusting a fixed set of maintainers and a > small, publicly visible change. Because of this, the waiting times for > non-responsiveness can probably also be shorter than in the maintainer > take-over process. > > Would this alleviate the frustration, while at the same time > maintaining enough security and sense of package ownership? It could. Let's implement it and see how it goes. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From daniel.trstenjak at gmail.com Fri Jan 31 11:27:15 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Fri, 31 Jan 2014 12:27:15 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: <20140131112715.GA26213@machine> Hi Erik, > * No response: User emails trustees. It would be nice to have a dedicated button on each hackage package page for this. The page opened by the button would allow the uploading of the modified package which would be send by email to the maintainer and the trustees. If the maintainer wouldn't respond in a certain amount of time, then the trustees can take their actions. Greetings, Daniel From hesselink at gmail.com Fri Jan 31 11:45:56 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 31 Jan 2014 12:45:56 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131110208.GA26266@sniper> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> Message-ID: Security is never binary, and just because we're not guarding against all scenarios, doesn't mean we shouldn't guard against any. Again, do you have any suggestions to make things better? Regards, Erik On Fri, Jan 31, 2014 at 12:02 PM, Roman Cheplyaka wrote: > So let's talk about security. > > The current process protects against malicious parties rather poorly. > It protects against malicious takeover of a maintained package, but an > adversary could presumably find an unmaintained or semi-maintained yet > popular package (such as ansi-terminal) to pull off an attack. > > The process does protect against *targeted* malicious takeover (i.e. an > adversary wants to inject malicious code in exactly the (maintained) > package K, and not just any moderately popular (but unmaintained) > package L). But that is not enough. So security and trust have to be > enforced by a different mechanism anyway. > > Roman > > * Evan Cofsky [2014-01-31 06:11:52+0000] >> Hello, >> >> As you all know I'm new to Haskell, but not at all new to software >> communities or computer security. The Haskell community is maturing, >> and as part of that we will have to be able to ensure that social >> engineering attacks against our core infrastructure, such as the >> canonical package repository, are not trivial to pull off >> successfully. >> >> There are several instances just in the past week that have been >> making the rounds of basic impersonation attacks having disastrous >> consequences because people were quite willing to trust complete >> strangers, and of course we all know about the various problems faced >> by the Node and the Ruby communities and their package management >> systems, which were fully automated. >> >> I put a lot more faith into Haskell programs, probably naively so, but >> as people, though, we have to at least maintain a certain amount of >> healthy skepticism when it comes to responding to requests to take >> over projects, and without a doubt along with that skepticism comes >> friction and process. But these are absolutely essential to having a >> trustworthy resource in Hackage, and I think that far outweighs the >> ficticious freedoms offered by management by handshake and a smile, >> especially for such an important community resource. >> >> -- >> Evan Cofsky > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From roma at ro-che.info Fri Jan 31 12:12:33 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Fri, 31 Jan 2014 14:12:33 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> Message-ID: <20140131121233.GA27525@sniper> * Erik Hesselink [2014-01-31 12:45:56+0100] > Security is never binary, and just because we're not guarding against > all scenarios, doesn't mean we shouldn't guard against any. It doesn't. It means, however, that we should at least ask ourselves whether it's worth what we pay for it. And whether we can get better for less. > Again, do you have any suggestions to make things better? Here I merely want people to realize that there is a problem. How to solve it is a whole new discussion. > On Fri, Jan 31, 2014 at 12:02 PM, Roman Cheplyaka wrote: > > So let's talk about security. > > > > The current process protects against malicious parties rather poorly. > > It protects against malicious takeover of a maintained package, but an > > adversary could presumably find an unmaintained or semi-maintained yet > > popular package (such as ansi-terminal) to pull off an attack. > > > > The process does protect against *targeted* malicious takeover (i.e. an > > adversary wants to inject malicious code in exactly the (maintained) > > package K, and not just any moderately popular (but unmaintained) > > package L). But that is not enough. So security and trust have to be > > enforced by a different mechanism anyway. > > > > Roman > > > > * Evan Cofsky [2014-01-31 06:11:52+0000] > >> Hello, > >> > >> As you all know I'm new to Haskell, but not at all new to software > >> communities or computer security. The Haskell community is maturing, > >> and as part of that we will have to be able to ensure that social > >> engineering attacks against our core infrastructure, such as the > >> canonical package repository, are not trivial to pull off > >> successfully. > >> > >> There are several instances just in the past week that have been > >> making the rounds of basic impersonation attacks having disastrous > >> consequences because people were quite willing to trust complete > >> strangers, and of course we all know about the various problems faced > >> by the Node and the Ruby communities and their package management > >> systems, which were fully automated. > >> > >> I put a lot more faith into Haskell programs, probably naively so, but > >> as people, though, we have to at least maintain a certain amount of > >> healthy skepticism when it comes to responding to requests to take > >> over projects, and without a doubt along with that skepticism comes > >> friction and process. But these are absolutely essential to having a > >> trustworthy resource in Hackage, and I think that far outweighs the > >> ficticious freedoms offered by management by handshake and a smile, > >> especially for such an important community resource. > >> > >> -- > >> Evan Cofsky > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From alexander at plaimi.net Fri Jan 31 12:19:22 2014 From: alexander at plaimi.net (Alexander Berntsen) Date: Fri, 31 Jan 2014 13:19:22 +0100 Subject: [Haskell-cafe] What game libraries should I use? Message-ID: <52EB94CA.9060604@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 I need: - -2D graphics (preferably with simple shapes available) - -menus (I can make menus myself with shapes though) - -simple audio - -fonts (better than Gloss at least) - -keyboard input - -networking (simple direct connections between two computers) I need to be able to express my game system as declaratively as possible[0]. If the library is based on SDL/OpenGL, that would be nice[1]. This is, however, not necessary. What game libraries are the most mature and adequate for this? The only library I have used previously with Haskell is Gloss. I am not experienced in FRP, though I have read about and somewhat groked the point. I am willing to learn an FRP library. [0] I am writing it as part of a thesis in which I will look at the modularity and expressiveness of purely functional programming compared to object-oriented programming. Writing code that is technically purely functional, but in practice looks like imperative code, is sub-optimal. [1] For the thesis I am writing, I am implementing a C++ version of the same game. This will probably use SDL 2.0 and OpenGL bindings. If the Haskell version could use libraries based on that, this would make it easier for me to write my thesis. I.e., I would not have to spend time justifying that the modularity and expressiveness I am investigating is due to the chosen languages and programming paradigms, and not the libraries I use. - -- Alexander alexander at plaimi.net http://plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlLrlMoACgkQRtClrXBQc7VkiAEAnEbfjiSLovcXttmjpdD5OSFI uEMBVBJdWonY9ZMPIc8BAIAQn+YMRvGILgb8WmuB9oTWJDVZfqDMyB47qzjyfimO =YGLW -----END PGP SIGNATURE----- From hesselink at gmail.com Fri Jan 31 12:22:32 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 31 Jan 2014 13:22:32 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131121233.GA27525@sniper> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> <20140131121233.GA27525@sniper> Message-ID: On Fri, Jan 31, 2014 at 1:12 PM, Roman Cheplyaka wrote: >> Again, do you have any suggestions to make things better? > > Here I merely want people to realize that there is a problem. How to > solve it is a whole new discussion. I think plenty of people (including me) have already agreed that there is a problem. So I don't understand the point of your message about security, then. Erik From gergely at risko.hu Fri Jan 31 12:55:02 2014 From: gergely at risko.hu (Gergely Risko) Date: Fri, 31 Jan 2014 13:55:02 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: <8761p0wbtl.fsf@gergely.risko.hu> On Fri, 31 Jan 2014 10:04:33 +0100, Erik Hesselink writes: > * User fixes a package, emails the maintainer. > * No response: User emails trustees. > * Trustees check the above conditions, and upload the new version. * Attacker "fixes the package", emails the maintainer with a typo in the email address (if the package is really unmaintained and the maintainer is unreachable this typo trick is not even necessary) * No response: attacker emails trustees * Attacker provides a github repository where the last commit is nice, but the attack is in previous commits that are converted from darcs to git(hub) Of course I'd never attack my beloved Haskell community, but I also don't believe in snake-oil processes. Gergely From hesselink at gmail.com Fri Jan 31 13:21:10 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 31 Jan 2014 14:21:10 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <8761p0wbtl.fsf@gergely.risko.hu> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <8761p0wbtl.fsf@gergely.risko.hu> Message-ID: On Fri, Jan 31, 2014 at 1:55 PM, Gergely Risko wrote: > On Fri, 31 Jan 2014 10:04:33 +0100, Erik Hesselink writes: > >> * User fixes a package, emails the maintainer. >> * No response: User emails trustees. >> * Trustees check the above conditions, and upload the new version. > > * Attacker "fixes the package", emails the maintainer with a typo in the > email address (if the package is really unmaintained and the > maintainer is unreachable this typo trick is not even necessary) > * No response: attacker emails trustees > * Attacker provides a github repository where the last commit is nice, > but the attack is in previous commits that are converted from darcs to > git(hub) Yes, if there's no original repo to compare against, you can probably fake a lot of stuff. I cannot see how to easily guard against this, without making the process more cumbersome. Perhaps it was wrong of me to mention security at all. But having the concept of maintainers (and thus *some* process for changing these) still makes a lot of sense to me with regard to 'ownership' of a package. Should we abolish that and go back to the situation of no ownership/maintainership checks? Or should we skip checking the source code? Regards, Erik From simon at banquise.net Fri Jan 31 13:29:58 2014 From: simon at banquise.net (Simon Marechal) Date: Fri, 31 Jan 2014 14:29:58 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <8761p0wbtl.fsf@gergely.risko.hu> Message-ID: <52EBA556.2010907@banquise.net> On 01/31/2014 02:21 PM, Erik Hesselink wrote: > Yes, if there's no original repo to compare against, you can probably > fake a lot of stuff. I cannot see how to easily guard against this, Maybe have people provide a diff against the latest version instead of a repo/tarball ? That is easy to generate, review, and apply. From gergely at risko.hu Fri Jan 31 13:43:42 2014 From: gergely at risko.hu (Gergely Risko) Date: Fri, 31 Jan 2014 14:43:42 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <8761p0wbtl.fsf@gergely.risko.hu> Message-ID: <871tzow9kh.fsf@gergely.risko.hu> On Fri, 31 Jan 2014 14:21:10 +0100, Erik Hesselink writes: > On Fri, Jan 31, 2014 at 1:55 PM, Gergely Risko wrote: >> On Fri, 31 Jan 2014 10:04:33 +0100, Erik Hesselink writes: >> >>> * User fixes a package, emails the maintainer. >>> * No response: User emails trustees. >>> * Trustees check the above conditions, and upload the new version. >> >> * Attacker "fixes the package", emails the maintainer with a typo in the >> email address (if the package is really unmaintained and the >> maintainer is unreachable this typo trick is not even necessary) >> * No response: attacker emails trustees >> * Attacker provides a github repository where the last commit is nice, >> but the attack is in previous commits that are converted from darcs to >> git(hub) > > Yes, if there's no original repo to compare against, you can probably > fake a lot of stuff. I cannot see how to easily guard against this, > without making the process more cumbersome. Perhaps it was wrong of me > to mention security at all. But having the concept of maintainers (and > thus *some* process for changing these) still makes a lot of sense to > me with regard to 'ownership' of a package. Should we abolish that and > go back to the situation of no ownership/maintainership checks? Or > should we skip checking the source code? My point was that social engineering and security is *hard*, *very hard*. Let me point out that stealing email addresses is also quite easy if the owner doesn't think that his email is of very high importance. So even if you mail the correct address, maybe the attacker will just circumvent the email for the time period needed. So yes, I agree that 'ownership' is a good thing, but security is hard. If someone wants to attack someone else through hackage, it's an easy task. Easy previously, bit harder now (but still easy). On the other hand, the new process is totally demotivating and counterproductive for the startup nature of Hackage and the Haskell community. I'd vote for the following: - anyone can upload anything, - but the libraries mailing list _AND_ the previous uploaders and previous maintainers/authors gets an email notification, - that email contains a hackage admin emergency email address for security issues or hostile takeovers (we will never receive any email there), - maintainers can opt-out from the "anyone can upload anything" process for their own packages (so we can have important packages like lens), but they have to be active at least by clicking a confirmation url in an email every 3 months or uploading new versions. If you operate an organization with security needs and you download directly from Hackage, you're doomed anyways. Gergely From fuuzetsu at fuuzetsu.co.uk Fri Jan 31 14:11:34 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Fri, 31 Jan 2014 14:11:34 +0000 Subject: [Haskell-cafe] What game libraries should I use? In-Reply-To: <52EB94CA.9060604@plaimi.net> References: <52EB94CA.9060604@plaimi.net> Message-ID: <52EBAF16.9070407@fuuzetsu.co.uk> On 31/01/14 12:19, Alexander Berntsen wrote: > I need: > -2D graphics (preferably with simple shapes available) > -menus (I can make menus myself with shapes though) > -simple audio > -fonts (better than Gloss at least) > -keyboard input > -networking (simple direct connections between two computers) > > I need to be able to express my game system as declaratively as > possible[0]. > > If the library is based on SDL/OpenGL, that would be nice[1]. This is, > however, not necessary. > > What game libraries are the most mature and adequate for this? The > only library I have used previously with Haskell is Gloss. I am not > experienced in FRP, though I have read about and somewhat groked the > point. I am willing to learn an FRP library. > > > [0] I am writing it as part of a thesis in which I will look at the > modularity and expressiveness of purely functional programming > compared to object-oriented programming. Writing code that is > technically purely functional, but in practice looks like imperative > code, is sub-optimal. > [1] For the thesis I am writing, I am implementing a C++ version of > the same game. This will probably use SDL 2.0 and OpenGL bindings. If > the Haskell version could use libraries based on that, this would make > it easier for me to write my thesis. I.e., I would not have to spend > time justifying that the modularity and expressiveness I am > investigating is due to the chosen languages and programming > paradigms, and not the libraries I use. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > I don't have an answer for you but your requirement of ?as declarative as possible? clashes with ?SDL/OpenGL?. -- Mateusz K. From allbery.b at gmail.com Fri Jan 31 14:28:43 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 31 Jan 2014 09:28:43 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> <20140131121233.GA27525@sniper> Message-ID: On Fri, Jan 31, 2014 at 7:22 AM, Erik Hesselink wrote: > On Fri, Jan 31, 2014 at 1:12 PM, Roman Cheplyaka wrote: > >> Again, do you have any suggestions to make things better? > > > > Here I merely want people to realize that there is a problem. How to > > solve it is a whole new discussion. > > I think plenty of people (including me) have already agreed that there > is a problem. So I don't understand the point of your message about > security, then. > It was a response to Evan Coskey, who introduced a bit of a diversion. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander at plaimi.net Fri Jan 31 14:38:47 2014 From: alexander at plaimi.net (Alexander Berntsen) Date: Fri, 31 Jan 2014 15:38:47 +0100 Subject: [Haskell-cafe] What game libraries should I use? In-Reply-To: <52EBAF16.9070407@fuuzetsu.co.uk> References: <52EB94CA.9060604@plaimi.net> <52EBAF16.9070407@fuuzetsu.co.uk> Message-ID: <52EBB577.5050200@plaimi.net> -----BEGIN PGP SIGNED MESSAGE----- Hash: SHA256 On 31/01/14 15:11, Mateusz Kowalczyk wrote: > I don't have an answer for you but your requirement of ?as > declarative as possible? clashes with ?SDL/OpenGL?. Gloss is on top of OpenGL, and it lets me express myself in a declarative manner. See [0] for an example. [0] . - -- Alexander alexander at plaimi.net http://plaimi.net/~alexander -----BEGIN PGP SIGNATURE----- Version: GnuPG v2.0.22 (GNU/Linux) Comment: Using GnuPG with Thunderbird - http://www.enigmail.net/ iF4EAREIAAYFAlLrtXcACgkQRtClrXBQc7UJgAD+P5JmzyA4h89yhwdWxi2TDulc d2PUZC1dRfXxwNzoH+IA/3HkRqEL4efL7KrjENBXaAJDI4SeesDPIjDmRWGhCTb3 =tG7H -----END PGP SIGNATURE----- From evan at theunixman.com Fri Jan 31 16:10:57 2014 From: evan at theunixman.com (Evan Cofsky) Date: Fri, 31 Jan 2014 16:10:57 +0000 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> <20140131121233.GA27525@sniper> Message-ID: <20140131161056.GM60654@serenity.tunixman.com> Well sorry to have introduced a diversion to you boys talking about your adorable little package management system with all your pretend discussions of how to make it easy to hijack packages because security is hard we just want to write code. I'll leave you kids alone. I've got better things to do than watch yet another software community make the exact same mistakes as every other bad community before it because somehow this time it'll be different. Enjoy your little toy package system kids. On 31/01/2014 09:28, Brandon Allbery wrote: > On Fri, Jan 31, 2014 at 7:22 AM, Erik Hesselink wrote: > > > On Fri, Jan 31, 2014 at 1:12 PM, Roman Cheplyaka wrote: > > >> Again, do you have any suggestions to make things better? > > > > > > Here I merely want people to realize that there is a problem. How to > > > solve it is a whole new discussion. > > > > I think plenty of people (including me) have already agreed that there > > is a problem. So I don't understand the point of your message about > > security, then. > > > > It was a response to Evan Coskey, who introduced a bit of a diversion. > > -- > brandon s allbery kf8nh sine nomine associates > allbery.b at gmail.com ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Evan Cofsky -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 228 bytes Desc: not available URL: From carter.schonwald at gmail.com Fri Jan 31 16:12:02 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 11:12:02 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> <20140131121233.GA27525@sniper> Message-ID: People are missing a key point: hackage packages are append only. Any upload will not override any prior version, and a bad new version is quite easy to deprecate. I'm not sure I'm comfortable with the idea of trustees having super upload powers by default (Speaking as the only person with trustee but not admin powers). Ie Id want a "trustee" upload to be a distinguished API thst I couldn't trip using cabal upload and if such a hypothetical power existed, I'd probably solicit feedback from a few folks by emailing the libraries list and testing any such upload locally. That aside: why isn't anyone helping work on hackage-server? We really need a few Heros to help work on hackage server. Otherwise it's kinda moot! :-) On Friday, January 31, 2014, Brandon Allbery wrote: > On Fri, Jan 31, 2014 at 7:22 AM, Erik Hesselink > > wrote: > >> On Fri, Jan 31, 2014 at 1:12 PM, Roman Cheplyaka > >> wrote: >> >> Again, do you have any suggestions to make things better? >> > >> > Here I merely want people to realize that there is a problem. How to >> > solve it is a whole new discussion. >> >> I think plenty of people (including me) have already agreed that there >> is a problem. So I don't understand the point of your message about >> security, then. >> > > It was a response to Evan Coskey, who introduced a bit of a diversion. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Fri Jan 31 16:13:30 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 31 Jan 2014 11:13:30 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140131161056.GM60654@serenity.tunixman.com> References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> <20140131121233.GA27525@sniper> <20140131161056.GM60654@serenity.tunixman.com> Message-ID: On Fri, Jan 31, 2014 at 11:10 AM, Evan Cofsky wrote: > Well sorry to have introduced a diversion to you boys talking about > Someone who has managed to conflate confusion with disinterest, and has an attitude problem on top of it, perhaps needs to be spanked. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Jan 31 16:29:29 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 11:29:29 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <20140131061151.GL60654@serenity.tunixman.com> <20140131110208.GA26266@sniper> <20140131121233.GA27525@sniper> <20140131161056.GM60654@serenity.tunixman.com> Message-ID: Brandon. Don't be an asshole. Seriously. Name calling is really inappropriate and should never happen on this list. Evan, could you please walk us through an example step by step social engineering issue? The current model requires any commandeering to be loud and visible, and I do agree that I'm uncomfortable with a proposal that makes me a single point of failure. On Friday, January 31, 2014, Brandon Allbery wrote: > On Fri, Jan 31, 2014 at 11:10 AM, Evan Cofsky > > wrote: > >> Well sorry to have introduced a diversion to you boys talking about >> > > Someone who has managed to conflate confusion with disinterest, and has an > attitude problem on top of it, perhaps needs to be spanked. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Fri Jan 31 16:34:19 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Fri, 31 Jan 2014 20:34:19 +0400 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: I think the proposed approach is only reasonable. However, I would like to stress that in any case it would be better to make sure that we give the maintainer enough time to respond, e.g.: if the maintainer is unreachable for a couple of weeks at least On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink wrote: > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka wrote: >> * Erik de Castro Lopo [2014-01-31 09:22:36+1100] >>> I really can understand why you did this; I am frustrated by some of >>> the same issues. However, I think if any significant number of people >>> did this, the results could easily be disasterous. >> >> Agreed. Maybe we need those disasterous results to realize that the >> current process is bad and come up with a better one. Or maybe it's just >> me, and everyone else is happy (enough) with the process, so nothing >> will happen. > > That's a rather fatalist attitude, and also one that is not warranted > given the replies in this thread. Let me try to be more constructive > instead: > > I propose to make the trustees group able to upload any package, with > the understanding that they only do so to make packages where the > maintainer is unreachable compile on more compilers or with more > versions of dependencies. The newly uploaded version should have a > public repository of the forked source available and listed in the > cabal file. The process would then be: > > * User fixes a package, emails the maintainer. > * No response: User emails trustees. > * Trustees check the above conditions, and upload the new version. > > This is more lightweight that the process to take over maintainership, > and it can be, because we're not trusting a random user with a random > package. Instead, we're only trusting a fixed set of maintainers and a > small, publicly visible change. Because of this, the waiting times for > non-responsiveness can probably also be shorter than in the maintainer > take-over process. > > Would this alleviate the frustration, while at the same time > maintaining enough security and sense of package ownership? > > Regards, > > Erik > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sincerely yours, -- Daniil From difrumin at gmail.com Fri Jan 31 16:39:02 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Fri, 31 Jan 2014 20:39:02 +0400 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> <8761p0wbtl.fsf@gergely.risko.hu> Message-ID: On Fri, Jan 31, 2014 at 5:21 PM, Erik Hesselink wrote: > On Fri, Jan 31, 2014 at 1:55 PM, Gergely Risko wrote: >> On Fri, 31 Jan 2014 10:04:33 +0100, Erik Hesselink writes: >> >>> * User fixes a package, emails the maintainer. >>> * No response: User emails trustees. >>> * Trustees check the above conditions, and upload the new version. >> >> * Attacker "fixes the package", emails the maintainer with a typo in the >> email address (if the package is really unmaintained and the >> maintainer is unreachable this typo trick is not even necessary) >> * No response: attacker emails trustees >> * Attacker provides a github repository where the last commit is nice, >> but the attack is in previous commits that are converted from darcs to >> git(hub) > > Yes, if there's no original repo to compare against, you can probably > fake a lot of stuff. I cannot see how to easily guard against this, > without making the process more cumbersome. Well, surely we can (and should!) compare the given "new" repository with the latest hackage version. Comparing against the canonical repository can lead to problems if the canonical repository contains commits that have not been released to Hackage but which introduce breaking changes, for example. > Perhaps it was wrong of me > to mention security at all. But having the concept of maintainers (and > thus *some* process for changing these) still makes a lot of sense to > me with regard to 'ownership' of a package. Should we abolish that and > go back to the situation of no ownership/maintainership checks? Or > should we skip checking the source code? > > Regards, > > Erik > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Sincerely yours, -- Daniil From cgaebel at uwaterloo.ca Fri Jan 31 16:39:54 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Fri, 31 Jan 2014 11:39:54 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: We could actually partially automate this: 1) Package maintainership switch is submitted online, with a new replacement package, and perhaps a message. 2) An email is sent to the maintainer with a link to either: - delete the replacement package - allow one-time upload - permanently add the uploader as a maintainer - permanently switch maintaners to the uploader 3) While the package is in this limbo state waiting for a response from the maintainer, put a link to the package at the bottom of the hackage page in a new "suggested replacements" section. In this section, each candidate replacement package is listed, along with its message and how long it's been waiting. 4) After a bikeshed-long amount of time with no response from the maintainer (I'll suggest 1 month), the package is automatically updated to the suggested version and the package uploader is added as a maintainer. On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin wrote: > I think the proposed approach is only reasonable. However, I would > like to stress that in any case it would be better to make sure that > we give the maintainer enough time to respond, e.g.: if the maintainer > is unreachable for a couple of weeks at least > > On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink > wrote: > > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka > wrote: > >> * Erik de Castro Lopo [2014-01-31 09:22:36+1100] > >>> I really can understand why you did this; I am frustrated by some of > >>> the same issues. However, I think if any significant number of people > >>> did this, the results could easily be disasterous. > >> > >> Agreed. Maybe we need those disasterous results to realize that the > >> current process is bad and come up with a better one. Or maybe it's just > >> me, and everyone else is happy (enough) with the process, so nothing > >> will happen. > > > > That's a rather fatalist attitude, and also one that is not warranted > > given the replies in this thread. Let me try to be more constructive > > instead: > > > > I propose to make the trustees group able to upload any package, with > > the understanding that they only do so to make packages where the > > maintainer is unreachable compile on more compilers or with more > > versions of dependencies. The newly uploaded version should have a > > public repository of the forked source available and listed in the > > cabal file. The process would then be: > > > > * User fixes a package, emails the maintainer. > > * No response: User emails trustees. > > * Trustees check the above conditions, and upload the new version. > > > > This is more lightweight that the process to take over maintainership, > > and it can be, because we're not trusting a random user with a random > > package. Instead, we're only trusting a fixed set of maintainers and a > > small, publicly visible change. Because of this, the waiting times for > > non-responsiveness can probably also be shorter than in the maintainer > > take-over process. > > > > Would this alleviate the frustration, while at the same time > > maintaining enough security and sense of package ownership? > > > > Regards, > > > > Erik > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -- > Sincerely yours, > -- Daniil > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Jan 31 16:44:37 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 11:44:37 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: Problem: no one is really actively working on hackage-server. Are you volunteering? :-) On Friday, January 31, 2014, Clark Gaebel wrote: > We could actually partially automate this: > > 1) Package maintainership switch is submitted online, with a new > replacement package, and perhaps a message. > 2) An email is sent to the maintainer with a link to either: > - delete the replacement package > - allow one-time upload > - permanently add the uploader as a maintainer > - permanently switch maintaners to the uploader > 3) While the package is in this limbo state waiting for a response from > the maintainer, put a link to the package at the bottom of the hackage page > in a new "suggested replacements" section. In this section, each candidate > replacement package is listed, along with its message and how long it's > been waiting. > 4) After a bikeshed-long amount of time with no response from the > maintainer (I'll suggest 1 month), the package is automatically updated to > the suggested version and the package uploader is added as a maintainer. > > > On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin > > wrote: > >> I think the proposed approach is only reasonable. However, I would >> like to stress that in any case it would be better to make sure that >> we give the maintainer enough time to respond, e.g.: if the maintainer >> is unreachable for a couple of weeks at least >> >> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink > >> wrote: >> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka > >> wrote: >> >> * Erik de Castro Lopo > >> [2014-01-31 09:22:36+1100] >> >>> I really can understand why you did this; I am frustrated by some of >> >>> the same issues. However, I think if any significant number of people >> >>> did this, the results could easily be disasterous. >> >> >> >> Agreed. Maybe we need those disasterous results to realize that the >> >> current process is bad and come up with a better one. Or maybe it's >> just >> >> me, and everyone else is happy (enough) with the process, so nothing >> >> will happen. >> > >> > That's a rather fatalist attitude, and also one that is not warranted >> > given the replies in this thread. Let me try to be more constructive >> > instead: >> > >> > I propose to make the trustees group able to upload any package, with >> > the understanding that they only do so to make packages where the >> > maintainer is unreachable compile on more compilers or with more >> > versions of dependencies. The newly uploaded version should have a >> > public repository of the forked source available and listed in the >> > cabal file. The process would then be: >> > >> > * User fixes a package, emails the maintainer. >> > * No response: User emails trustees. >> > * Trustees check the above conditions, and upload the new version. >> > >> > This is more lightweight that the process to take over maintainership, >> > and it can be, because we're not trusting a random user with a random >> > package. Instead, we're only trusting a fixed set of maintainers and a >> > small, publicly visible change. Because of this, the waiting times for >> > non-responsiveness can probably also be shorter than in the maintainer >> > take-over process. >> > >> > Would this alleviate the frustration, while at the same time >> > maintaining enough security and sense of package ownership? >> > >> > Regards, >> > >> > Erik >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> >> -- >> Sincerely yours, >> -- Daniil >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From cgaebel at uwaterloo.ca Fri Jan 31 16:52:50 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Fri, 31 Jan 2014 11:52:50 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: Fair point. I wish I could, but the soonest I could start checking it out is in ~3 months. - Clark On Fri, Jan 31, 2014 at 11:44 AM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Problem: no one is really actively working on hackage-server. Are you > volunteering? :-) > > > On Friday, January 31, 2014, Clark Gaebel wrote: > >> We could actually partially automate this: >> >> 1) Package maintainership switch is submitted online, with a new >> replacement package, and perhaps a message. >> 2) An email is sent to the maintainer with a link to either: >> - delete the replacement package >> - allow one-time upload >> - permanently add the uploader as a maintainer >> - permanently switch maintaners to the uploader >> 3) While the package is in this limbo state waiting for a response from >> the maintainer, put a link to the package at the bottom of the hackage page >> in a new "suggested replacements" section. In this section, each candidate >> replacement package is listed, along with its message and how long it's >> been waiting. >> 4) After a bikeshed-long amount of time with no response from the >> maintainer (I'll suggest 1 month), the package is automatically updated to >> the suggested version and the package uploader is added as a maintainer. >> >> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin wrote: >> >>> I think the proposed approach is only reasonable. However, I would >>> like to stress that in any case it would be better to make sure that >>> we give the maintainer enough time to respond, e.g.: if the maintainer >>> is unreachable for a couple of weeks at least >>> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink >>> wrote: >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka >>> wrote: >>> >> * Erik de Castro Lopo [2014-01-31 >>> 09:22:36+1100] >>> >>> I really can understand why you did this; I am frustrated by some of >>> >>> the same issues. However, I think if any significant number of people >>> >>> did this, the results could easily be disasterous. >>> >> >>> >> Agreed. Maybe we need those disasterous results to realize that the >>> >> current process is bad and come up with a better one. Or maybe it's >>> just >>> >> me, and everyone else is happy (enough) with the process, so nothing >>> >> will happen. >>> > >>> > That's a rather fatalist attitude, and also one that is not warranted >>> > given the replies in this thread. Let me try to be more constructive >>> > instead: >>> > >>> > I propose to make the trustees group able to upload any package, with >>> > the understanding that they only do so to make packages where the >>> > maintainer is unreachable compile on more compilers or with more >>> > versions of dependencies. The newly uploaded version should have a >>> > public repository of the forked source available and listed in the >>> > cabal file. The process would then be: >>> > >>> > * User fixes a package, emails the maintainer. >>> > * No response: User emails trustees. >>> > * Trustees check the above conditions, and upload the new version. >>> > >>> > This is more lightweight that the process to take over maintainership, >>> > and it can be, because we're not trusting a random user with a random >>> > package. Instead, we're only trusting a fixed set of maintainers and a >>> > small, publicly visible change. Because of this, the waiting times for >>> > non-responsiveness can probably also be shorter than in the maintainer >>> > take-over process. >>> > >>> > Would this alleviate the frustration, while at the same time >>> > maintaining enough security and sense of package ownership? >>> > >>> > Regards, >>> > >>> > Erik >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > Haskell-Cafe at haskell.org >>> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >>> >>> -- >>> Sincerely yours, >>> -- Daniil >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> >> >> -- >> Clark. >> >> Key ID : 0x78099922 >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 >> > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Jan 31 17:05:55 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 12:05:55 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: Ill check in 3 months then :-) Everyone here has a lot of different ideas bout how to improve hackage (some of which may admittedly be at odds with others). But unless there's some associated commitment to work on hackage server by some volunteers who have the time and care to help out, not is going to happen. Any volunteers? :-) On Friday, January 31, 2014, Clark Gaebel wrote: > Fair point. > > I wish I could, but the soonest I could start checking it out is in ~3 > months. > > - Clark > > > On Fri, Jan 31, 2014 at 11:44 AM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > > Problem: no one is really actively working on hackage-server. Are you > volunteering? :-) > > > On Friday, January 31, 2014, Clark Gaebel wrote: > > We could actually partially automate this: > > 1) Package maintainership switch is submitted online, with a new > replacement package, and perhaps a message. > 2) An email is sent to the maintainer with a link to either: > - delete the replacement package > - allow one-time upload > - permanently add the uploader as a maintainer > - permanently switch maintaners to the uploader > 3) While the package is in this limbo state waiting for a response from > the maintainer, put a link to the package at the bottom of the hackage page > in a new "suggested replacements" section. In this section, each candidate > replacement package is listed, along with its message and how long it's > been waiting. > 4) After a bikeshed-long amount of time with no response from the > maintainer (I'll suggest 1 month), the package is automatically updated to > the suggested version and the package uploader is added as a maintainer. > > > On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin wrote: > > I think the proposed approach is only reasonable. However, I would > like to stress that in any case it would be better to make sure that > we give the maintainer enough time to respond, e.g.: if the maintainer > is unreachable for a couple of weeks at least > > On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink > wrote: > > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka > wrote: > >> * Erik de Castro Lopo [2014-01-31 09:22:36+1100] > >>> I really can understand why you did this; I am frustrated by some of > >>> the same issues. However, I think if any significant number of people > >>> did this, the results could easily be disasterous. > >> > >> Agreed. Maybe we need those disasterous results to realize that the > >> current process is bad and come up with a better one. Or maybe it's just > >> me, and everyone else is happy (enough) with the process, so nothing > >> will happen. > > > > That's a rather fatalist attitude, and also one that is not warranted > > given the replies in this thread. Let me try to be more constructive > > instead: > > > > I propose to make the trustees group able to upload any package, with > > the understanding that they only do so to make packages where the > > maintainer is unreachable compile on more compilers or with more > > versions of dependencies. The newly uploaded version should have a > > public repository of the forked source available and listed in the > > cabal file. The process would then be: > > > > * User fixes a package, emails the maintainer. > > * No response: User emails trustees. > > * Trustees check the above conditions, and upload the new version. > > > > This is more lightweight that the process to take over maintainership, > > and it can be, because we're not trusting a random user with a random > > package. Instead, we're only trusting a fixed set of maintainers and a > > small, publicly visible change. Because of this, the waiting times for > > non-responsiveness can probably also be shorter than in the maintainer > > take-over process. > > > > Would this allevi > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Fri Jan 31 17:06:28 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Fri, 31 Jan 2014 21:06:28 +0400 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: I have a problem with the 4th step. What if maintainer is unreachable, but the updated version of the package is broken/breaking ever dependency? What if there are several replacements awaiting? I personally think that problem we are facing is not technical, but a social one. Call me old fashioned, but I prefer trustees to the automatic mechanism. I understand that Roman may have been really irritated by the whole process - but on the other hand, do we really need/want the process of overtaking packages to be easy? I strongly align with Gershom's position. We should make the process more transparent and visible. In order to put my money where my mouth is, I created a wiki page that (hopefully) describes the process of taking over a package: http://www.haskell.org/haskellwiki/Taking_over_a_package You are strongly encouraged to edit that page and give more details (especially given my far from perfect English) Maybe it is a good idea to have links to that wiki article on every package page on Hackage? On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald wrote: > Problem: no one is really actively working on hackage-server. Are you > volunteering? :-) > > > On Friday, January 31, 2014, Clark Gaebel wrote: >> >> We could actually partially automate this: >> >> 1) Package maintainership switch is submitted online, with a new >> replacement package, and perhaps a message. >> 2) An email is sent to the maintainer with a link to either: >> - delete the replacement package >> - allow one-time upload >> - permanently add the uploader as a maintainer >> - permanently switch maintaners to the uploader >> 3) While the package is in this limbo state waiting for a response from >> the maintainer, put a link to the package at the bottom of the hackage page >> in a new "suggested replacements" section. In this section, each candidate >> replacement package is listed, along with its message and how long it's been >> waiting. >> 4) After a bikeshed-long amount of time with no response from the >> maintainer (I'll suggest 1 month), the package is automatically updated to >> the suggested version and the package uploader is added as a maintainer. >> >> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin >> wrote: >>> >>> I think the proposed approach is only reasonable. However, I would >>> like to stress that in any case it would be better to make sure that >>> we give the maintainer enough time to respond, e.g.: if the maintainer >>> is unreachable for a couple of weeks at least >>> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink >>> wrote: >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka >>> > wrote: >>> >> * Erik de Castro Lopo [2014-01-31 >>> >> 09:22:36+1100] >>> >>> I really can understand why you did this; I am frustrated by some of >>> >>> the same issues. However, I think if any significant number of people >>> >>> did this, the results could easily be disasterous. >>> >> >>> >> Agreed. Maybe we need those disasterous results to realize that the >>> >> current process is bad and come up with a better one. Or maybe it's >>> >> just >>> >> me, and everyone else is happy (enough) with the process, so nothing >>> >> will happen. >>> > >>> > That's a rather fatalist attitude, and also one that is not warranted >>> > given the replies in this thread. Let me try to be more constructive >>> > instead: >>> > >>> > I propose to make the trustees group able to upload any package, with >>> > the understanding that they only do so to make packages where the >>> > maintainer is unreachable compile on more compilers or with more >>> > versions of dependencies. The newly uploaded version should have a >>> > public repository of the forked source available and listed in the >>> > cabal file. The process would then be: >>> > >>> > * User fixes a package, emails the maintainer. >>> > * No response: User emails trustees. >>> > * Trustees check the above conditions, and upload the new version. >>> > >>> > This is more lightweight that the process to take over maintainership, >>> > and it can be, because we're not trusting a random user with a random >>> > package. Instead, we're only trusting a fixed set of maintainers and a >>> > small, publicly visible change. Because of this, the waiting times for >>> > non-responsiveness can probably also be shorter than in the maintainer >>> > take-over process. >>> > >>> > Would this alleviate the frustration, while at the same time >>> > maintaining enough security and sense of package ownership? >>> > >>> > Regards, >>> > >>> > Erik >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > Haskell-Cafe at haskell.org >>> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >>> >>> -- >>> Sincerely yours, >>> -- Daniil >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> >> >> -- >> Clark. >> >> Key ID : 0x78099922 >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -- Sincerely yours, -- Daniil From carter.schonwald at gmail.com Fri Jan 31 17:09:38 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 12:09:38 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: Agreed. It should not be automatic. There should be lots of human visible interaction publicly going on. On Friday, January 31, 2014, Daniil Frumin wrote: > I have a problem with the 4th step. What if maintainer is unreachable, > but the updated version of the package is broken/breaking ever > dependency? What if there are several replacements awaiting? > > I personally think that problem we are facing is not technical, but a > social one. Call me old fashioned, but I prefer trustees to the > automatic mechanism. > > I understand that Roman may have been really irritated by the whole > process - but on the other hand, do we really need/want the process of > overtaking packages to be easy? I strongly align with Gershom's > position. We should make the process more transparent and visible. In > order to put my money where my mouth is, I created a wiki page that > (hopefully) describes the process of taking over a package: > http://www.haskell.org/haskellwiki/Taking_over_a_package > You are strongly encouraged to edit that page and give more details > (especially given my far from perfect English) > > Maybe it is a good idea to have links to that wiki article on every > package page on Hackage? > > On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald > wrote: > > Problem: no one is really actively working on hackage-server. Are you > > volunteering? :-) > > > > > > On Friday, January 31, 2014, Clark Gaebel wrote: > >> > >> We could actually partially automate this: > >> > >> 1) Package maintainership switch is submitted online, with a new > >> replacement package, and perhaps a message. > >> 2) An email is sent to the maintainer with a link to either: > >> - delete the replacement package > >> - allow one-time upload > >> - permanently add the uploader as a maintainer > >> - permanently switch maintaners to the uploader > >> 3) While the package is in this limbo state waiting for a response from > >> the maintainer, put a link to the package at the bottom of the hackage > page > >> in a new "suggested replacements" section. In this section, each > candidate > >> replacement package is listed, along with its message and how long it's > been > >> waiting. > >> 4) After a bikeshed-long amount of time with no response from the > >> maintainer (I'll suggest 1 month), the package is automatically updated > to > >> the suggested version and the package uploader is added as a maintainer. > >> > >> > >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin > >> wrote: > >>> > >>> I think the proposed approach is only reasonable. However, I would > >>> like to stress that in any case it would be better to make sure that > >>> we give the maintainer enough time to respond, e.g.: if the maintainer > >>> is unreachable for a couple of weeks at least > >>> > >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink > >>> wrote: > >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka > >>> > wrote: > >>> >> * Erik de Castro Lopo [2014-01-31 > >>> >> 09:22:36+1100] > >>> >>> I really can understand why you did this; I am frustrated by some > of > >>> >>> the same issues. However, I think if any significant number of > people > >>> >>> did this, the results could easily be disasterous. > >>> >> > >>> >> Agreed. Maybe we need those disasterous results to realize that the > >>> >> current process is bad and come up with a better one. Or maybe it's > >>> >> just > >>> >> me, and everyone else is happy (enough) with the process, so nothing > >>> >> will happen. > >>> > > >>> > That's a rather fatalist attitude, and also one that is not warranted > >>> > given the replies in this thread. Let me try to be more constructive > >>> > instead: > >>> > > >>> > I propose to make the trustees group able to upload any package, with > >>> > the understanding that they only do so to make packages where the > >>> > maintainer is unreachable compile on more compilers or with more > >>> > versions of dependencies. The newly uploaded version should have a > >>> > public repository of the forked source available and listed in the > >>> > cabal file. The process would then be: > >>> > > >>> > * User fixes a package, emails the maintainer. > >>> > * No response: User emails trustees. > >>> > * Trustees check the above conditions, and upload the new version. > >>> > > >>> > This is more lightweight that the process to take over > maintainership, > >>> > and it can be, because we're not trusting a random user with a random > >>> > package. Instead, we're only trusting a fixed set of maintainers and > a > >>> > small, publicly visible change. Because of this, the waiting times > for > >>> > non-respo -------------- next part -------------- An HTML attachment was scrubbed... URL: From cgaebel at uwaterloo.ca Fri Jan 31 17:45:16 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Fri, 31 Jan 2014 12:45:16 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: There could be an email made to the relevant mailing lists during a takeover attempt. That way we get human visibility, human "veto power" if the email goes to libraries@, and automation when there are no objections. On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > Agreed. It should not be automatic. There should be lots of human > visible interaction publicly going on. > > > On Friday, January 31, 2014, Daniil Frumin wrote: > >> I have a problem with the 4th step. What if maintainer is unreachable, >> but the updated version of the package is broken/breaking ever >> dependency? What if there are several replacements awaiting? >> >> I personally think that problem we are facing is not technical, but a >> social one. Call me old fashioned, but I prefer trustees to the >> automatic mechanism. >> >> I understand that Roman may have been really irritated by the whole >> process - but on the other hand, do we really need/want the process of >> overtaking packages to be easy? I strongly align with Gershom's >> position. We should make the process more transparent and visible. In >> order to put my money where my mouth is, I created a wiki page that >> (hopefully) describes the process of taking over a package: >> http://www.haskell.org/haskellwiki/Taking_over_a_package >> You are strongly encouraged to edit that page and give more details >> (especially given my far from perfect English) >> >> Maybe it is a good idea to have links to that wiki article on every >> package page on Hackage? >> >> On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald >> wrote: >> > Problem: no one is really actively working on hackage-server. Are you >> > volunteering? :-) >> > >> > >> > On Friday, January 31, 2014, Clark Gaebel wrote: >> >> >> >> We could actually partially automate this: >> >> >> >> 1) Package maintainership switch is submitted online, with a new >> >> replacement package, and perhaps a message. >> >> 2) An email is sent to the maintainer with a link to either: >> >> - delete the replacement package >> >> - allow one-time upload >> >> - permanently add the uploader as a maintainer >> >> - permanently switch maintaners to the uploader >> >> 3) While the package is in this limbo state waiting for a response from >> >> the maintainer, put a link to the package at the bottom of the hackage >> page >> >> in a new "suggested replacements" section. In this section, each >> candidate >> >> replacement package is listed, along with its message and how long >> it's been >> >> waiting. >> >> 4) After a bikeshed-long amount of time with no response from the >> >> maintainer (I'll suggest 1 month), the package is automatically >> updated to >> >> the suggested version and the package uploader is added as a >> maintainer. >> >> >> >> >> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin >> >> wrote: >> >>> >> >>> I think the proposed approach is only reasonable. However, I would >> >>> like to stress that in any case it would be better to make sure that >> >>> we give the maintainer enough time to respond, e.g.: if the maintainer >> >>> is unreachable for a couple of weeks at least >> >>> >> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink >> >>> wrote: >> >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka >> >>> > wrote: >> >>> >> * Erik de Castro Lopo [2014-01-31 >> >>> >> 09:22:36+1100] >> >>> >>> I really can understand why you did this; I am frustrated by some >> of >> >>> >>> the same issues. However, I think if any significant number of >> people >> >>> >>> did this, the results could easily be disasterous. >> >>> >> >> >>> >> Agreed. Maybe we need those disasterous results to realize that the >> >>> >> current process is bad and come up with a better one. Or maybe it's >> >>> >> just >> >>> >> me, and everyone else is happy (enough) with the process, so >> nothing >> >>> >> will happen. >> >>> > >> >>> > That's a rather fatalist attitude, and also one that is not >> warranted >> >>> > given the replies in this thread. Let me try to be more constructive >> >>> > instead: >> >>> > >> >>> > I propose to make the trustees group able to upload any package, >> with >> >>> > the understanding that they only do so to make packages where the >> >>> > maintainer is unreachable compile on more compilers or with more >> >>> > versions of dependencies. The newly uploaded version should have a >> >>> > public repository of the forked source available and listed in the >> >>> > cabal file. The process would then be: >> >>> > >> >>> > * User fixes a package, emails the maintainer. >> >>> > * No response: User emails trustees. >> >>> > * Trustees check the above conditions, and upload the new version. >> >>> > >> >>> > This is more lightweight that the process to take over >> maintainership, >> >>> > and it can be, because we're not trusting a random user with a >> random >> >>> > package. Instead, we're only trusting a fixed set of maintainers >> and a >> >>> > small, publicly visible change. Because of this, the waiting times >> for >> >>> > non-respo > > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From hans at hanshoglund.se Fri Jan 31 17:56:00 2014 From: hans at hanshoglund.se (=?iso-8859-1?Q?Hans_H=F6glund?=) Date: Fri, 31 Jan 2014 18:56:00 +0100 Subject: [Haskell-cafe] Dispatch a type-function on the existence (or not) of instances? Message-ID: <31962063-6BA2-4C33-89C3-0641D1082FE4@hanshoglund.se> Dear all, I have been curious about the ability to detect the presence of a certain instance (ClassFoo TypeBar) in the type system. Specifically, is it possible to "dispatch" a type on the existence (or not) of such an instance. For example given two functions: withInstance :: (ClassFoo TypeBar) => TypeIfInstanceExists withoutInstance :: TypeIfInstanceDoesNotExists I would be able to consolidate them into something like this: withOrWithoutInstance :: (r ~ InstanceExists ClassFoo TypeBar, a ~ If r TypeIfInstanceExists TypeIfInstanceDoesNotExists) => a I guess what I need is: 1) A type-level "if". 2) The possibility of "converting" a constraint into a type-level bool. I am sure (1) is possible but have no idea about (2). Anyone? Best regards, Hans From carter.schonwald at gmail.com Fri Jan 31 18:03:16 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 13:03:16 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: How would the automation work? Automation in trust models is very very fiddly to get right. Like really hard. Like a research problem with reality consequences hard. At the end of the day, it's a people problem. The best we can do is come up with a very audit able, publicly visible process that makes everything easy for 3rd partiies to audit. And prevents / catches any abuse before it does something like break vector or ByteString. On Friday, January 31, 2014, Clark Gaebel wrote: > There could be an email made to the relevant mailing lists during a > takeover attempt. That way we get human visibility, human "veto power" if > the email goes to libraries@, and automation when there are no objections. > > > On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > > Agreed. It should not be automatic. There should be lots of human > visible interaction publicly going on. > > > On Friday, January 31, 2014, Daniil Frumin wrote: > > I have a problem with the 4th step. What if maintainer is unreachable, > but the updated version of the package is broken/breaking ever > dependency? What if there are several replacements awaiting? > > I personally think that problem we are facing is not technical, but a > social one. Call me old fashioned, but I prefer trustees to the > automatic mechanism. > > I understand that Roman may have been really irritated by the whole > process - but on the other hand, do we really need/want the process of > overtaking packages to be easy? I strongly align with Gershom's > position. We should make the process more transparent and visible. In > order to put my money where my mouth is, I created a wiki page that > (hopefully) describes the process of taking over a package: > http://www.haskell.org/haskellwiki/Taking_over_a_package > You are strongly encouraged to edit that page and give more details > (especially given my far from perfect English) > > Maybe it is a good idea to have links to that wiki article on every > package page on Hackage? > > On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald > wrote: > > Problem: no one is really actively working on hackage-server. Are you > > volunteering? :-) > > > > > > On Friday, January 31, 2014, Clark Gaebel wrote: > >> > >> We could actually partially automate this: > >> > >> 1) Package maintainership switch is submitted online, with a new > >> replacement package, and perhaps a message. > >> 2) An email is sent to the maintainer with a link to either: > >> - delete the replacement package > >> - allow one-time upload > >> - permanently add the uploader as a maintainer > >> - permanently switch maintaners to the uploader > >> 3) While the package is in this limbo state waiting for a response from > >> the maintainer, put a link to the package at the bottom of the hackage > page > >> in a new "suggested replacements" section. In this section, each > candidate > >> replacement package is listed, along with its message and how long it's > been > >> waiting. > >> 4) After a bikeshed-long amount of time with no response from the > >> maintainer (I'll suggest 1 month), the package is automatically updated > to > >> the suggested version and the package uploader is added as a maintainer. > >> > >> > >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin > >> wrote: > >>> > >>> I think the proposed approach is only reasonable. However, I would > >>> like to stress that in any case it would be better to make sure that > >>> we give the maintainer enough time to respond, e.g.: if the maintainer > >>> is unreachable for a couple of weeks at least > >>> > >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink > >>> wrote: > >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka > >>> > wrote: > >>> >> * Erik de Castro Lopo [2014-01-31 > >>> >> 09:22:36+1100] > >>> >>> I really can understand why you did this; I am frustrated by some > of > >>> >>> the same issues. However, I think if any significant number of > people > >>> >>> did this, the results could easily be disasterous. > >>> >> > >>> >> Agreed. Maybe we need those disasterous results to realize that the > >>> >> current process is bad and come up with a better one. Or maybe it's > >>> >> just > >>> >> me, and everyone else is happy (enough) with the process, so nothing > >>> >> will happen. > >>> > > >>> > That's a rather fatalist attitude, and als > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From cgaebel at uwaterloo.ca Fri Jan 31 18:05:53 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Fri, 31 Jan 2014 13:05:53 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: The automation could just be "new package version + new maintainer added in 30 days if no one manually stops it". Takeovers should be easy to stop for both existing library maintainers and any core "trusted" members of the community. On Fri, Jan 31, 2014 at 1:03 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > How would the automation work? Automation in trust models is very very > fiddly to get right. Like really hard. Like a research problem with > reality consequences hard. > > At the end of the day, it's a people problem. The best we can do is come > up with a very audit able, publicly visible process that makes everything > easy for 3rd partiies to audit. And prevents / catches any abuse before it > does something like break vector or ByteString. > > > > On Friday, January 31, 2014, Clark Gaebel wrote: > >> There could be an email made to the relevant mailing lists during a >> takeover attempt. That way we get human visibility, human "veto power" if >> the email goes to libraries@, and automation when there are no >> objections. >> >> >> On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >> Agreed. It should not be automatic. There should be lots of human >> visible interaction publicly going on. >> >> >> On Friday, January 31, 2014, Daniil Frumin wrote: >> >> I have a problem with the 4th step. What if maintainer is unreachable, >> but the updated version of the package is broken/breaking ever >> dependency? What if there are several replacements awaiting? >> >> I personally think that problem we are facing is not technical, but a >> social one. Call me old fashioned, but I prefer trustees to the >> automatic mechanism. >> >> I understand that Roman may have been really irritated by the whole >> process - but on the other hand, do we really need/want the process of >> overtaking packages to be easy? I strongly align with Gershom's >> position. We should make the process more transparent and visible. In >> order to put my money where my mouth is, I created a wiki page that >> (hopefully) describes the process of taking over a package: >> http://www.haskell.org/haskellwiki/Taking_over_a_package >> You are strongly encouraged to edit that page and give more details >> (especially given my far from perfect English) >> >> Maybe it is a good idea to have links to that wiki article on every >> package page on Hackage? >> >> On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald >> wrote: >> > Problem: no one is really actively working on hackage-server. Are you >> > volunteering? :-) >> > >> > >> > On Friday, January 31, 2014, Clark Gaebel wrote: >> >> >> >> We could actually partially automate this: >> >> >> >> 1) Package maintainership switch is submitted online, with a new >> >> replacement package, and perhaps a message. >> >> 2) An email is sent to the maintainer with a link to either: >> >> - delete the replacement package >> >> - allow one-time upload >> >> - permanently add the uploader as a maintainer >> >> - permanently switch maintaners to the uploader >> >> 3) While the package is in this limbo state waiting for a response from >> >> the maintainer, put a link to the package at the bottom of the hackage >> page >> >> in a new "suggested replacements" section. In this section, each >> candidate >> >> replacement package is listed, along with its message and how long >> it's been >> >> waiting. >> >> 4) After a bikeshed-long amount of time with no response from the >> >> maintainer (I'll suggest 1 month), the package is automatically >> updated to >> >> the suggested version and the package uploader is added as a >> maintainer. >> >> >> >> >> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin >> >> wrote: >> >>> >> >>> I think the proposed approach is only reasonable. However, I would >> >>> like to stress that in any case it would be better to make sure that >> >>> we give the maintainer enough time to respond, e.g.: if the maintainer >> >>> is unreachable for a couple of weeks at least >> >>> >> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink >> >>> wrote: >> >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka >> >>> > wrote: >> >>> >> * Erik de Castro Lopo [2014-01-31 >> >>> >> 09:22:36+1100] >> >>> >>> I really can understand why you did this; I am frustrated by some >> of >> >>> >>> the same issues. However, I think if any significant number of >> people >> >>> >>> did this, the results could easily be disasterous. >> >>> >> >> >>> >> Agreed. Maybe we need those disasterous results to realize that the >> >>> >> current process is bad and come up with a better one. Or maybe it's >> >>> >> just >> >>> >> me, and everyone else is happy (enough) with the process, so >> nothing >> >>> >> will happen. >> >>> > >> >>> > That's a rather fatalist attitude, and als >> >> -- >> Clark. >> >> Key ID : 0x78099922 >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 >> > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From difrumin at gmail.com Fri Jan 31 18:10:17 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Fri, 31 Jan 2014 22:10:17 +0400 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: On Fri, Jan 31, 2014 at 10:05 PM, Clark Gaebel wrote: > The automation could just be "new package version + new maintainer added in > 30 days if no one manually stops it". > > Takeovers should be easy to stop for both existing library maintainers and > any core "trusted" members of the community. Rights, that's why we have hackage trustees. They can easily overwrite/update any package (if I understand the process correctly). Complete takeover of a package should *not* be easy, we must give the maintainers a good sense of ownership. > > > On Fri, Jan 31, 2014 at 1:03 PM, Carter Schonwald > wrote: >> >> How would the automation work? Automation in trust models is very very >> fiddly to get right. Like really hard. Like a research problem with >> reality consequences hard. >> >> At the end of the day, it's a people problem. The best we can do is come >> up with a very audit able, publicly visible process that makes everything >> easy for 3rd partiies to audit. And prevents / catches any abuse before it >> does something like break vector or ByteString. >> >> >> >> On Friday, January 31, 2014, Clark Gaebel wrote: >>> >>> There could be an email made to the relevant mailing lists during a >>> takeover attempt. That way we get human visibility, human "veto power" if >>> the email goes to libraries@, and automation when there are no objections. >>> >>> >>> On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald >>> wrote: >>> >>> Agreed. It should not be automatic. There should be lots of human >>> visible interaction publicly going on. >>> >>> >>> On Friday, January 31, 2014, Daniil Frumin wrote: >>> >>> I have a problem with the 4th step. What if maintainer is unreachable, >>> but the updated version of the package is broken/breaking ever >>> dependency? What if there are several replacements awaiting? >>> >>> I personally think that problem we are facing is not technical, but a >>> social one. Call me old fashioned, but I prefer trustees to the >>> automatic mechanism. >>> >>> I understand that Roman may have been really irritated by the whole >>> process - but on the other hand, do we really need/want the process of >>> overtaking packages to be easy? I strongly align with Gershom's >>> position. We should make the process more transparent and visible. In >>> order to put my money where my mouth is, I created a wiki page that >>> (hopefully) describes the process of taking over a package: >>> http://www.haskell.org/haskellwiki/Taking_over_a_package >>> You are strongly encouraged to edit that page and give more details >>> (especially given my far from perfect English) >>> >>> Maybe it is a good idea to have links to that wiki article on every >>> package page on Hackage? >>> >>> On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald >>> wrote: >>> > Problem: no one is really actively working on hackage-server. Are you >>> > volunteering? :-) >>> > >>> > >>> > On Friday, January 31, 2014, Clark Gaebel wrote: >>> >> >>> >> We could actually partially automate this: >>> >> >>> >> 1) Package maintainership switch is submitted online, with a new >>> >> replacement package, and perhaps a message. >>> >> 2) An email is sent to the maintainer with a link to either: >>> >> - delete the replacement package >>> >> - allow one-time upload >>> >> - permanently add the uploader as a maintainer >>> >> - permanently switch maintaners to the uploader >>> >> 3) While the package is in this limbo state waiting for a response >>> >> from >>> >> the maintainer, put a link to the package at the bottom of the hackage >>> >> page >>> >> in a new "suggested replacements" section. In this section, each >>> >> candidate >>> >> replacement package is listed, along with its message and how long >>> >> it's been >>> >> waiting. >>> >> 4) After a bikeshed-long amount of time with no response from the >>> >> maintainer (I'll suggest 1 month), the package is automatically >>> >> updated to >>> >> the suggested version and the package uploader is added as a >>> >> maintainer. >>> >> >>> >> >>> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin >>> >> wrote: >>> >>> >>> >>> I think the proposed approach is only reasonable. However, I would >>> >>> like to stress that in any case it would be better to make sure that >>> >>> we give the maintainer enough time to respond, e.g.: if the >>> >>> maintainer >>> >>> is unreachable for a couple of weeks at least >>> >>> >>> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink >>> >>> wrote: >>> >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka >>> >>> > wrote: >>> >>> >> * Erik de Castro Lopo [2014-01-31 >>> >>> >> 09:22:36+1100] >>> >>> >>> I really can understand why you did this; I am frustrated by some >>> >>> >>> of >>> >>> >>> the same issues. However, I think if any significant number of >>> >>> >>> people >>> >>> >>> did this, the results could easily be disasterous. >>> >>> >> >>> >>> >> Agreed. Maybe we need those disasterous results to realize that >>> >>> >> the >>> >>> >> current process is bad and come up with a better one. Or maybe >>> >>> >> it's >>> >>> >> just >>> >>> >> me, and everyone else is happy (enough) with the process, so >>> >>> >> nothing >>> >>> >> will happen. >>> >>> > >>> >>> > That's a rather fatalist attitude, and als >>> >>> -- >>> Clark. >>> >>> Key ID : 0x78099922 >>> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -- Sincerely yours, -- Daniil From carter.schonwald at gmail.com Fri Jan 31 18:14:45 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 13:14:45 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: Yes. It should be perhaps even require two trustees / admins / whatever if we are actually serious about making things proof against social engineering. Or something. Nb: hackage admins have the super powers. I'm just a trustee. Which just means I can delete bad doc builds to force em to rebuild. On Friday, January 31, 2014, Daniil Frumin wrote: > On Fri, Jan 31, 2014 at 10:05 PM, Clark Gaebel > > wrote: > > The automation could just be "new package version + new maintainer added > in > > 30 days if no one manually stops it". > > > > Takeovers should be easy to stop for both existing library maintainers > and > > any core "trusted" members of the community. > > Rights, that's why we have hackage trustees. They can easily > overwrite/update any package (if I understand the process correctly). > Complete takeover of a package should *not* be easy, we must give the > maintainers a good sense of ownership. > > > > > > > On Fri, Jan 31, 2014 at 1:03 PM, Carter Schonwald > > wrote: > >> > >> How would the automation work? Automation in trust models is very very > >> fiddly to get right. Like really hard. Like a research problem with > >> reality consequences hard. > >> > >> At the end of the day, it's a people problem. The best we can do is > come > >> up with a very audit able, publicly visible process that makes > everything > >> easy for 3rd partiies to audit. And prevents / catches any abuse > before it > >> does something like break vector or ByteString. > >> > >> > >> > >> On Friday, January 31, 2014, Clark Gaebel wrote: > >>> > >>> There could be an email made to the relevant mailing lists during a > >>> takeover attempt. That way we get human visibility, human "veto power" > if > >>> the email goes to libraries@, and automation when there are no > objections. > >>> > >>> > >>> On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald > >>> wrote: > >>> > >>> Agreed. It should not be automatic. There should be lots of human > >>> visible interaction publicly going on. > >>> > >>> > >>> On Friday, January 31, 2014, Daniil Frumin wrote: > >>> > >>> I have a problem with the 4th step. What if maintainer is unreachable, > >>> but the updated version of the package is broken/breaking ever > >>> dependency? What if there are several replacements awaiting? > >>> > >>> I personally think that problem we are facing is not technical, but a > >>> social one. Call me old fashioned, but I prefer trustees to the > >>> automatic mechanism. > >>> > >>> I understand that Roman may have been really irritated by the whole > >>> process - but on the other hand, do we really need/want the process of > >>> overtaking packages to be easy? I strongly align with Gershom's > >>> position. We should make the process more transparent and visible. In > >>> order to put my money where my mouth is, I created a wiki page that > >>> (hopefully) describes the process of taking over a package: > >>> http://www.haskell.org/haskellwiki/Taking_over_a_package > >>> You are strongly encouraged to edit that page and give more details > >>> (especially given my far from perfect English) > >>> > >>> Maybe it is a good idea to have links to that wiki article on every > >>> package page on Hackage? > >>> > >>> On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald > >>> wrote: > >>> > Problem: no one is really actively working on hackage-server. Are > you > >>> > volunteering? :-) > >>> > > >>> > > >>> > On Friday, January 31, 2014, Clark Gaebel > wrote: > >>> >> > >>> >> We could actually partially automate this: > >>> >> > >>> >> 1) Package maintainership switch is submitted online, with a new > >>> >> replacement package, and perhaps a message. > >>> >> 2) An email is sent to the maintainer with a link to either: > >>> >> - delete the replacement package > >>> >> - allow one-time upload > >>> >> - permanently add the uploader as a maintainer > >>> >> - permanently switch maintaners to the uploader > >>> >> 3) While the package is in this limbo state waiting for a response > >>> >> from > >>> >> the maintainer, put a link to the package at the bottom of the > hackage > >>> >> pag-- > Sincerely yours, > -- Daniil > -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon at joyful.com Fri Jan 31 18:52:07 2014 From: simon at joyful.com (Simon Michael) Date: Fri, 31 Jan 2014 10:52:07 -0800 Subject: [Haskell-cafe] What game libraries should I use? In-Reply-To: <52EB94CA.9060604@plaimi.net> References: <52EB94CA.9060604@plaimi.net> Message-ID: FunGEn (http://joyful.com/fungen) is (amazingly) still the most mature/complete Haskell games library as far as I know. I'm curious to know if you agree, or if I'm wrong. From carter.schonwald at gmail.com Fri Jan 31 19:04:21 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 14:04:21 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: automation ... isn't flexible. the moment theres an automatic path, a lot of non social engineering approaches to break any hackage trust model On Fri, Jan 31, 2014 at 12:45 PM, Clark Gaebel wrote: > There could be an email made to the relevant mailing lists during a > takeover attempt. That way we get human visibility, human "veto power" if > the email goes to libraries@, and automation when there are no objections. > > > On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald < > carter.schonwald at gmail.com> wrote: > >> Agreed. It should not be automatic. There should be lots of human >> visible interaction publicly going on. >> >> >> On Friday, January 31, 2014, Daniil Frumin wrote: >> >>> I have a problem with the 4th step. What if maintainer is unreachable, >>> but the updated version of the package is broken/breaking ever >>> dependency? What if there are several replacements awaiting? >>> >>> I personally think that problem we are facing is not technical, but a >>> social one. Call me old fashioned, but I prefer trustees to the >>> automatic mechanism. >>> >>> I understand that Roman may have been really irritated by the whole >>> process - but on the other hand, do we really need/want the process of >>> overtaking packages to be easy? I strongly align with Gershom's >>> position. We should make the process more transparent and visible. In >>> order to put my money where my mouth is, I created a wiki page that >>> (hopefully) describes the process of taking over a package: >>> http://www.haskell.org/haskellwiki/Taking_over_a_package >>> You are strongly encouraged to edit that page and give more details >>> (especially given my far from perfect English) >>> >>> Maybe it is a good idea to have links to that wiki article on every >>> package page on Hackage? >>> >>> On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald >>> wrote: >>> > Problem: no one is really actively working on hackage-server. Are you >>> > volunteering? :-) >>> > >>> > >>> > On Friday, January 31, 2014, Clark Gaebel >>> wrote: >>> >> >>> >> We could actually partially automate this: >>> >> >>> >> 1) Package maintainership switch is submitted online, with a new >>> >> replacement package, and perhaps a message. >>> >> 2) An email is sent to the maintainer with a link to either: >>> >> - delete the replacement package >>> >> - allow one-time upload >>> >> - permanently add the uploader as a maintainer >>> >> - permanently switch maintaners to the uploader >>> >> 3) While the package is in this limbo state waiting for a response >>> from >>> >> the maintainer, put a link to the package at the bottom of the >>> hackage page >>> >> in a new "suggested replacements" section. In this section, each >>> candidate >>> >> replacement package is listed, along with its message and how long >>> it's been >>> >> waiting. >>> >> 4) After a bikeshed-long amount of time with no response from the >>> >> maintainer (I'll suggest 1 month), the package is automatically >>> updated to >>> >> the suggested version and the package uploader is added as a >>> maintainer. >>> >> >>> >> >>> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin >>> >> wrote: >>> >>> >>> >>> I think the proposed approach is only reasonable. However, I would >>> >>> like to stress that in any case it would be better to make sure that >>> >>> we give the maintainer enough time to respond, e.g.: if the >>> maintainer >>> >>> is unreachable for a couple of weeks at least >>> >>> >>> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink >> > >>> >>> wrote: >>> >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka >> > >>> >>> > wrote: >>> >>> >> * Erik de Castro Lopo [2014-01-31 >>> >>> >> 09:22:36+1100] >>> >>> >>> I really can understand why you did this; I am frustrated by >>> some of >>> >>> >>> the same issues. However, I think if any significant number of >>> people >>> >>> >>> did this, the results could easily be disasterous. >>> >>> >> >>> >>> >> Agreed. Maybe we need those disasterous results to realize that >>> the >>> >>> >> current process is bad and come up with a better one. Or maybe >>> it's >>> >>> >> just >>> >>> >> me, and everyone else is happy (enough) with the process, so >>> nothing >>> >>> >> will happen. >>> >>> > >>> >>> > That's a rather fatalist attitude, and also one that is not >>> warranted >>> >>> > given the replies in this thread. Let me try to be more >>> constructive >>> >>> > instead: >>> >>> > >>> >>> > I propose to make the trustees group able to upload any package, >>> with >>> >>> > the understanding that they only do so to make packages where the >>> >>> > maintainer is unreachable compile on more compilers or with more >>> >>> > versions of dependencies. The newly uploaded version should have a >>> >>> > public repository of the forked source available and listed in the >>> >>> > cabal file. The process would then be: >>> >>> > >>> >>> > * User fixes a package, emails the maintainer. >>> >>> > * No response: User emails trustees. >>> >>> > * Trustees check the above conditions, and upload the new version. >>> >>> > >>> >>> > This is more lightweight that the process to take over >>> maintainership, >>> >>> > and it can be, because we're not trusting a random user with a >>> random >>> >>> > package. Instead, we're only trusting a fixed set of maintainers >>> and a >>> >>> > small, publicly visible change. Because of this, the waiting times >>> for >>> >>> > non-respo >> >> > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From cgaebel at uwaterloo.ca Fri Jan 31 19:07:13 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Fri, 31 Jan 2014 14:07:13 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <20140131092236.2a160a4491766b99a0d1705a@mega-nerd.com> <20140131021530.GA25143@sniper> Message-ID: Fair enough. I'm also not sure the Haskell community has a resident security expert, so it would likely be bad security at best. - Clark On Fri, Jan 31, 2014 at 2:04 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > automation ... isn't flexible. the moment theres an automatic path, a lot > of non social engineering approaches to break any hackage trust model > > > On Fri, Jan 31, 2014 at 12:45 PM, Clark Gaebel wrote: > >> There could be an email made to the relevant mailing lists during a >> takeover attempt. That way we get human visibility, human "veto power" if >> the email goes to libraries@, and automation when there are no >> objections. >> >> >> On Fri, Jan 31, 2014 at 12:09 PM, Carter Schonwald < >> carter.schonwald at gmail.com> wrote: >> >>> Agreed. It should not be automatic. There should be lots of human >>> visible interaction publicly going on. >>> >>> >>> On Friday, January 31, 2014, Daniil Frumin wrote: >>> >>>> I have a problem with the 4th step. What if maintainer is unreachable, >>>> but the updated version of the package is broken/breaking ever >>>> dependency? What if there are several replacements awaiting? >>>> >>>> I personally think that problem we are facing is not technical, but a >>>> social one. Call me old fashioned, but I prefer trustees to the >>>> automatic mechanism. >>>> >>>> I understand that Roman may have been really irritated by the whole >>>> process - but on the other hand, do we really need/want the process of >>>> overtaking packages to be easy? I strongly align with Gershom's >>>> position. We should make the process more transparent and visible. In >>>> order to put my money where my mouth is, I created a wiki page that >>>> (hopefully) describes the process of taking over a package: >>>> http://www.haskell.org/haskellwiki/Taking_over_a_package >>>> You are strongly encouraged to edit that page and give more details >>>> (especially given my far from perfect English) >>>> >>>> Maybe it is a good idea to have links to that wiki article on every >>>> package page on Hackage? >>>> >>>> On Fri, Jan 31, 2014 at 8:44 PM, Carter Schonwald >>>> wrote: >>>> > Problem: no one is really actively working on hackage-server. Are you >>>> > volunteering? :-) >>>> > >>>> > >>>> > On Friday, January 31, 2014, Clark Gaebel >>>> wrote: >>>> >> >>>> >> We could actually partially automate this: >>>> >> >>>> >> 1) Package maintainership switch is submitted online, with a new >>>> >> replacement package, and perhaps a message. >>>> >> 2) An email is sent to the maintainer with a link to either: >>>> >> - delete the replacement package >>>> >> - allow one-time upload >>>> >> - permanently add the uploader as a maintainer >>>> >> - permanently switch maintaners to the uploader >>>> >> 3) While the package is in this limbo state waiting for a response >>>> from >>>> >> the maintainer, put a link to the package at the bottom of the >>>> hackage page >>>> >> in a new "suggested replacements" section. In this section, each >>>> candidate >>>> >> replacement package is listed, along with its message and how long >>>> it's been >>>> >> waiting. >>>> >> 4) After a bikeshed-long amount of time with no response from the >>>> >> maintainer (I'll suggest 1 month), the package is automatically >>>> updated to >>>> >> the suggested version and the package uploader is added as a >>>> maintainer. >>>> >> >>>> >> >>>> >> On Fri, Jan 31, 2014 at 11:34 AM, Daniil Frumin >>>> >> wrote: >>>> >>> >>>> >>> I think the proposed approach is only reasonable. However, I would >>>> >>> like to stress that in any case it would be better to make sure that >>>> >>> we give the maintainer enough time to respond, e.g.: if the >>>> maintainer >>>> >>> is unreachable for a couple of weeks at least >>>> >>> >>>> >>> On Fri, Jan 31, 2014 at 1:04 PM, Erik Hesselink < >>>> hesselink at gmail.com> >>>> >>> wrote: >>>> >>> > On Fri, Jan 31, 2014 at 3:15 AM, Roman Cheplyaka < >>>> roma at ro-che.info> >>>> >>> > wrote: >>>> >>> >> * Erik de Castro Lopo [2014-01-31 >>>> >>> >> 09:22:36+1100] >>>> >>> >>> I really can understand why you did this; I am frustrated by >>>> some of >>>> >>> >>> the same issues. However, I think if any significant number of >>>> people >>>> >>> >>> did this, the results could easily be disasterous. >>>> >>> >> >>>> >>> >> Agreed. Maybe we need those disasterous results to realize that >>>> the >>>> >>> >> current process is bad and come up with a better one. Or maybe >>>> it's >>>> >>> >> just >>>> >>> >> me, and everyone else is happy (enough) with the process, so >>>> nothing >>>> >>> >> will happen. >>>> >>> > >>>> >>> > That's a rather fatalist attitude, and also one that is not >>>> warranted >>>> >>> > given the replies in this thread. Let me try to be more >>>> constructive >>>> >>> > instead: >>>> >>> > >>>> >>> > I propose to make the trustees group able to upload any package, >>>> with >>>> >>> > the understanding that they only do so to make packages where the >>>> >>> > maintainer is unreachable compile on more compilers or with more >>>> >>> > versions of dependencies. The newly uploaded version should have a >>>> >>> > public repository of the forked source available and listed in the >>>> >>> > cabal file. The process would then be: >>>> >>> > >>>> >>> > * User fixes a package, emails the maintainer. >>>> >>> > * No response: User emails trustees. >>>> >>> > * Trustees check the above conditions, and upload the new version. >>>> >>> > >>>> >>> > This is more lightweight that the process to take over >>>> maintainership, >>>> >>> > and it can be, because we're not trusting a random user with a >>>> random >>>> >>> > package. Instead, we're only trusting a fixed set of maintainers >>>> and a >>>> >>> > small, publicly visible change. Because of this, the waiting >>>> times for >>>> >>> > non-respo >>> >>> >> >> >> -- >> Clark. >> >> Key ID : 0x78099922 >> Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 >> > > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From duncan at well-typed.com Fri Jan 31 21:15:58 2014 From: duncan at well-typed.com (Duncan Coutts) Date: Fri, 31 Jan 2014 21:15:58 +0000 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> Message-ID: <1391202958.17028.80.camel@dunky.localdomain> On Thu, 2014-01-30 at 20:23 +0100, Erik Hesselink wrote: > There is support for trustees on the new hackage, as other's > mentioned. These can maintain any package. Perhaps this would be a > good time to recruit a few of them? I should point out that trustees cannot upload new package tarballs. They can upload docs and will be able to tweak .cabal metadata (when that feature is fixed) but we drew the line at source code changes. -- Duncan Coutts, Haskell Consultant Well-Typed LLP, http://www.well-typed.com/ From carter.schonwald at gmail.com Fri Jan 31 21:17:18 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 31 Jan 2014 16:17:18 -0500 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <1391202958.17028.80.camel@dunky.localdomain> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> <1391202958.17028.80.camel@dunky.localdomain> Message-ID: and I"m glad I don't have such powers, thats too much responsibility. Its admins who have the real powers :) On Fri, Jan 31, 2014 at 4:15 PM, Duncan Coutts wrote: > On Thu, 2014-01-30 at 20:23 +0100, Erik Hesselink wrote: > > > There is support for trustees on the new hackage, as other's > > mentioned. These can maintain any package. Perhaps this would be a > > good time to recruit a few of them? > > I should point out that trustees cannot upload new package tarballs. > They can upload docs and will be able to tweak .cabal metadata (when > that feature is fixed) but we drew the line at source code changes. > > -- > Duncan Coutts, Haskell Consultant > Well-Typed LLP, http://www.well-typed.com/ > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hesselink at gmail.com Fri Jan 31 21:36:35 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Fri, 31 Jan 2014 22:36:35 +0100 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <1391202958.17028.80.camel@dunky.localdomain> References: <20140130163055.GA19868@sniper> <8761p1fm1n.fsf@gmail.com> <52EA95D2.40400@gmail.com> <1391107177.17028.21.camel@dunky.localdomain> <1391202958.17028.80.camel@dunky.localdomain> Message-ID: On Friday, January 31, 2014, Duncan Coutts wrote: > On Thu, 2014-01-30 at 20:23 +0100, Erik Hesselink wrote: > > > There is support for trustees on the new hackage, as other's > > mentioned. These can maintain any package. Perhaps this would be a > > good time to recruit a few of them? > > I should point out that trustees cannot upload new package tarballs. > They can upload docs and will be able to tweak .cabal metadata (when > that feature is fixed) but we drew the line at source code changes. > True, but that can be changed if people think it's a good idea. It seems they don't, currently, but I have a patch in case they do ;) Erik -------------- next part -------------- An HTML attachment was scrubbed... URL: