From haskell-cafe at maartenfaddegon.nl Sat Feb 1 12:11:13 2014 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Sat, 01 Feb 2014 12:11:13 +0000 Subject: [Haskell-cafe] Mixing own and derived instances with Generic Deriving Mechanism Message-ID: <52ECE461.8080303@maartenfaddegon.nl> Dear Pedro, Cafe, Thanks again for helping me out last December. I have been playing a bit more with deriving show and now ran into an interesting problem mixing my own instances with derived instances. Hope you can enlighten me there! > {-# LANGUAGE DeriveGeneric #-} > module Test where > import GHC.Generics > import Generics.Deriving.Show The Generic Deriving Mechanism adds the keyword 'default' to class definitions. With this keyword we can define a type-generic definition of that method when not given. For example, if we define our own MyData type, we can derive the GShow methods: > data MyData = MyData MyFancyType deriving Generic > instance GShow MyData We can also still give our own definition, for example if we want values of the MyFancyType to always be shown as the same string: > data MyFancyType = MyFancy1 | MyFancy2 deriving Generic > instance GShow MyFancyType where > gshow _ = "Fancy!" There is something strange here though: when we use gshow directly on a MyFancyType value our own instance definition is used, evaluating as expected to "Fancy!". > ex1 = gshow MyFancy1 But as soon as we are inside a derived method, we will continue using derived instances even though we defined our own. The example below evaluates to "MyData MyFancy1", rather than "MyData Fancy!": > ex2 = gshow (MyData MyFancy1) The default methods of GShow are defined in terms of methods from GShow' which operate on the type-representation. From this representation I do not see a way to recover the information that a type has a GShow instance. Am I correct (I hope not :) or is there a way out? Cheers, Maarten Faddegon From alfredo.dinapoli at gmail.com Sat Feb 1 12:11:09 2014 From: alfredo.dinapoli at gmail.com (Alfredo Di Napoli) Date: Sat, 1 Feb 2014 12:11:09 +0000 Subject: [Haskell-cafe] What game libraries should I use? In-Reply-To: References: <52EB94CA.9060604@plaimi.net> Message-ID: The Haskell bindings to SFML might be of your interest: https://github.com/SFML-haskell/SFML A. On 31 January 2014 18:52, Simon Michael wrote: > 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. > > > _______________________________________________ > 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 Sat Feb 1 15:55:09 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sat, 1 Feb 2014 16:55:09 +0100 Subject: [Haskell-cafe] DSLs and heterogeous lists Message-ID: Hi again, I have a game in which the user can create/write/read variables, using a small DSL. The type of the variable created can be whatever chooses the user, so I'm using existential types to store those variables in a heterogeneous list. This works fine, but the problem is that the "Typeable" class tag leaks into the DSL... The question is, how to get rid of it? > This is literate Haskell > {-# LANGUAGE GADTs, ScopedTypeVariables #-} > module DSLClass where > import Control.Monad > import Control.Monad.State > import Data.Typeable > This is the (simplified) DSL. With it you can read a variable stored in the game state (creation/writing is not shown). How can we get rid of the "Typeable a" in the ReadFirstVar constructor? > -- first type parameter is used to track effects > data Exp a where > ReadFirstVar :: (Typeable a) => Exp a <----- Ugly > Return :: a -> Exp a > Bind :: Exp a -> (a -> Exp b) -> Exp b This is the definition of a variable. The type is unknow, so I use existantial types. > data Var = forall a . (Typeable a) => Var { v :: a} This game state. It holds the heterogenous list. > data Game = Game { variables :: [Var]} The evaluation of "Exp" can be: > eval :: Exp a -> State Game a > eval ReadFirstVar = do > (Game ((Var v):vs)) <- get > case cast v of > Just val -> return val > Nothing -> error "no cast" > eval (Bind exp f) = do > a <- eval exp > eval (f a) As you can see, I'm obliged to cast the variable type to match it with the expression's type. Is that the right place to do it? Thanks!! Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From blamario at acanac.net Sat Feb 1 17:08:31 2014 From: blamario at acanac.net (=?UTF-8?B?TWFyaW8gQmxhxb5ldmnEhw==?=) Date: Sat, 01 Feb 2014 12:08:31 -0500 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: References: Message-ID: <52ED2A0F.9030305@acanac.net> On 01/28/14 21:25, Alvaro J. Genial wrote: > 1. Is there a more general version of `null`? (e.g. for a Monad, > Functor, Applicative, Traversable or the like.) There is the MonoidNull class from my monoid-subclasses library. It comes with plenty of standard instances. http://hackage.haskell.org/package/monoid-subclasses-0.3.5/docs/Data-Monoid-Null.html From eir at cis.upenn.edu Sat Feb 1 18:02:16 2014 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 1 Feb 2014 13:02:16 -0500 Subject: [Haskell-cafe] DSLs and heterogeous lists In-Reply-To: References: Message-ID: <930C302F-8637-4A64-8D44-87E568D6DB8F@cis.upenn.edu> This seems reasonable to me. What's ugly about it? As I see it, casting really is necessary, because there's no way to know whether the type of the head variable in the list is correct without it. Richard On Feb 1, 2014, at 10:55 AM, Corentin Dupont wrote: > Hi again, > I have a game in which the user can create/write/read variables, using a small DSL. The type of the variable created can be whatever chooses the user, so I'm using existential types to store those variables in a heterogeneous list. > This works fine, but the problem is that the "Typeable" class tag leaks into the DSL... The question is, how to get rid of it? > > > This is literate Haskell > > {-# LANGUAGE GADTs, ScopedTypeVariables #-} > > module DSLClass where > > import Control.Monad > > import Control.Monad.State > > import Data.Typeable > > > > This is the (simplified) DSL. With it you can read a variable stored in the game state (creation/writing is not shown). > How can we get rid of the "Typeable a" in the ReadFirstVar constructor? > > > -- first type parameter is used to track effects > > data Exp a where > > ReadFirstVar :: (Typeable a) => Exp a <----- Ugly > > Return :: a -> Exp a > > Bind :: Exp a -> (a -> Exp b) -> Exp b > > This is the definition of a variable. The type is unknow, so I use existantial types. > > > data Var = forall a . (Typeable a) => Var { v :: a} > > This game state. It holds the heterogenous list. > > > data Game = Game { variables :: [Var]} > > The evaluation of "Exp" can be: > > > eval :: Exp a -> State Game a > > eval ReadFirstVar = do > > (Game ((Var v):vs)) <- get > > case cast v of > > Just val -> return val > > Nothing -> error "no cast" > > eval (Bind exp f) = do > > a <- eval exp > > eval (f a) > > > As you can see, I'm obliged to cast the variable type to match it with the expression's type. Is that the right place to do it? > > 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 eir at cis.upenn.edu Sat Feb 1 18:21:12 2014 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 1 Feb 2014 13:21:12 -0500 Subject: [Haskell-cafe] Dispatch a type-function on the existence (or not) of instances? In-Reply-To: <31962063-6BA2-4C33-89C3-0641D1082FE4@hanshoglund.se> References: <31962063-6BA2-4C33-89C3-0641D1082FE4@hanshoglund.se> Message-ID: <67C7D749-C92D-405F-8A0F-A701AF600EB5@cis.upenn.edu> I am sure that "2) The possibility of "converting" a constraint into a type-level bool." is *not* possible. And, it really shouldn't be possible. The problem has to do with modules. Suppose we have: > module A where > data Foo > type Magic -- invented syntax: > | Show Foo = Int > | otherwise = Bool > module B where > import A > instance Show Foo > bar :: Magic > bar = 3 > module C where > import A > quux :: Magic -- no (Show Foo) here! > quux = False > module D where > import B > import C > hasSameType :: a -> a -> () > hasSameType _ _ = () > unit :: () > unit = hasSameType bar quux Does that last line of D type-check? `bar` and `quux` are both declared to have the same type. But, of course, they don't have the same type! Yuck. Thus, `Magic` cannot exist. In my own work, I've often wanted something like Magic, but I've learned that whenever I start wanting Magic, what I really want is a very different design. If you really, really want Magic and just can't live without it though, you might consider using Template Haskell. TH code can query the database of available instances and branch on the existence of an instance. See `reifyInstances`. TH can't cause the problem I described above, because the equivalent using TH would give `bar` and `quux` different types at compile time, because the TH code is fully evaluated, unlike something like `Magic` which might not be. I hope this helps! Richard On Jan 31, 2014, at 12:56 PM, Hans H?glund wrote: > 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 > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From corentin.dupont at gmail.com Sat Feb 1 18:51:42 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sat, 1 Feb 2014 19:51:42 +0100 Subject: [Haskell-cafe] DSLs and heterogeous lists In-Reply-To: <930C302F-8637-4A64-8D44-87E568D6DB8F@cis.upenn.edu> References: <930C302F-8637-4A64-8D44-87E568D6DB8F@cis.upenn.edu> Message-ID: Ugly, maybe not, but I read somewhere that the class restriction should be on the functions definitions than in the datatype definition... That is, the datatype is usually defined without class restriction, instead the necessary class restriction is added latter on in the functions signatures that work on that datatype. On Sat, Feb 1, 2014 at 7:02 PM, Richard Eisenberg wrote: > This seems reasonable to me. What's ugly about it? As I see it, casting > really is necessary, because there's no way to know whether the type of the > head variable in the list is correct without it. > > Richard > > On Feb 1, 2014, at 10:55 AM, Corentin Dupont > wrote: > > Hi again, > I have a game in which the user can create/write/read variables, using a > small DSL. The type of the variable created can be whatever chooses the > user, so I'm using existential types to store those variables in a > heterogeneous list. > This works fine, but the problem is that the "Typeable" class tag leaks > into the DSL... The question is, how to get rid of it? > > > This is literate Haskell > > {-# LANGUAGE GADTs, ScopedTypeVariables #-} > > module DSLClass where > > import Control.Monad > > import Control.Monad.State > > import Data.Typeable > > > > This is the (simplified) DSL. With it you can read a variable stored in > the game state (creation/writing is not shown). > How can we get rid of the "Typeable a" in the ReadFirstVar constructor? > > > -- first type parameter is used to track effects > > data Exp a where > > ReadFirstVar :: (Typeable a) => Exp a <----- Ugly > > Return :: a -> Exp a > > Bind :: Exp a -> (a -> Exp b) -> Exp b > > This is the definition of a variable. The type is unknow, so I use > existantial types. > > > data Var = forall a . (Typeable a) => Var { v :: a} > > This game state. It holds the heterogenous list. > > > data Game = Game { variables :: [Var]} > > The evaluation of "Exp" can be: > > > eval :: Exp a -> State Game a > > eval ReadFirstVar = do > > (Game ((Var v):vs)) <- get > > case cast v of > > Just val -> return val > > Nothing -> error "no cast" > > eval (Bind exp f) = do > > a <- eval exp > > eval (f a) > > > As you can see, I'm obliged to cast the variable type to match it with the > expression's type. Is that the right place to do it? > > 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 eir at cis.upenn.edu Sat Feb 1 19:09:57 2014 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 1 Feb 2014 14:09:57 -0500 Subject: [Haskell-cafe] DSLs and heterogeous lists In-Reply-To: References: <930C302F-8637-4A64-8D44-87E568D6DB8F@cis.upenn.edu> Message-ID: There are three (relevant) places a constraint could go: data Typeable a => Exp a = ... -- (1) data Exp a where ReadFirstVar :: Typeable a => Exp a -- (2) eval :: Typeable a => Exp a -> ... -- (3) You're currently doing (2). When people talk about not putting constraints on datatypes, I imagine they're talking about (1), which is indeed a bad idea. Using (1) essentially buys you nothing -- you would still still a constraint like (3) to work with the type declared in (1). So, the real choice is between (2) and (3). Each of these has its advantages. (2) essentially says that the data stored by the ReadFirstVar constructor is the type of the expression. (3) essentially says that any caller of `eval` also has to pass in the desired type for the expression. Without seeing more code, it's hard to know what's better in your scenario. But, my bottom line is that the advice you've read probably pertains to (1), not (2) -- it's not saying that what you've done is bad. Richard On Feb 1, 2014, at 1:51 PM, Corentin Dupont wrote: > Ugly, maybe not, but I read somewhere that the class restriction should be on the functions definitions than in the datatype definition... That is, the datatype is usually defined without class restriction, instead the necessary class restriction is added latter on in the functions signatures that work on that datatype. > > > On Sat, Feb 1, 2014 at 7:02 PM, Richard Eisenberg wrote: > This seems reasonable to me. What's ugly about it? As I see it, casting really is necessary, because there's no way to know whether the type of the head variable in the list is correct without it. > > Richard > > On Feb 1, 2014, at 10:55 AM, Corentin Dupont wrote: > >> Hi again, >> I have a game in which the user can create/write/read variables, using a small DSL. The type of the variable created can be whatever chooses the user, so I'm using existential types to store those variables in a heterogeneous list. >> This works fine, but the problem is that the "Typeable" class tag leaks into the DSL... The question is, how to get rid of it? >> >> > This is literate Haskell >> > {-# LANGUAGE GADTs, ScopedTypeVariables #-} >> > module DSLClass where >> > import Control.Monad >> > import Control.Monad.State >> > import Data.Typeable >> > >> >> This is the (simplified) DSL. With it you can read a variable stored in the game state (creation/writing is not shown). >> How can we get rid of the "Typeable a" in the ReadFirstVar constructor? >> >> > -- first type parameter is used to track effects >> > data Exp a where >> > ReadFirstVar :: (Typeable a) => Exp a <----- Ugly >> > Return :: a -> Exp a >> > Bind :: Exp a -> (a -> Exp b) -> Exp b >> >> This is the definition of a variable. The type is unknow, so I use existantial types. >> >> > data Var = forall a . (Typeable a) => Var { v :: a} >> >> This game state. It holds the heterogenous list. >> >> > data Game = Game { variables :: [Var]} >> >> The evaluation of "Exp" can be: >> >> > eval :: Exp a -> State Game a >> > eval ReadFirstVar = do >> > (Game ((Var v):vs)) <- get >> > case cast v of >> > Just val -> return val >> > Nothing -> error "no cast" >> > eval (Bind exp f) = do >> > a <- eval exp >> > eval (f a) >> >> >> As you can see, I'm obliged to cast the variable type to match it with the expression's type. Is that the right place to do it? >> >> 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 hjgtuyl at chello.nl Sat Feb 1 20:54:59 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Sat, 01 Feb 2014 21:54:59 +0100 Subject: [Haskell-cafe] Castle: Permission denied Message-ID: L.S., I am trying to install castle, but I get the following messages: Downloading castle-0.1.0.0... Configuring castle-0.1.0.0... realgcc.exe: ./specs: Permission denied What can I do about this? I am running Windows XP, Haskell Platform 2013.2.0.0 Regards, Henk-Jan van Tuyl -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From allbery.b at gmail.com Sat Feb 1 21:15:56 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 1 Feb 2014 16:15:56 -0500 Subject: [Haskell-cafe] Castle: Permission denied In-Reply-To: References: Message-ID: On Sat, Feb 1, 2014 at 3:54 PM, Henk-Jan van Tuyl wrote: > I am trying to install castle, but I get the following messages: > Downloading castle-0.1.0.0... > Configuring castle-0.1.0.0... > realgcc.exe: ./specs: Permission denied > What can I do about this? > That sounds like something is wrong with the permissions on your gcc installation. -- 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 erochest at gmail.com Sun Feb 2 02:44:06 2014 From: erochest at gmail.com (Eric Rochester) Date: Sat, 1 Feb 2014 21:44:06 -0500 Subject: [Haskell-cafe] Castle: Permission denied In-Reply-To: References: Message-ID: Thanks for opening the issue for this. I'll try to take a look on Monday when I will have access to a Windows box, but in the meantime, I agree that it sounds as if there are permissions problems with GCC. Eric On Feb 1, 2014 3:55 PM, "Henk-Jan van Tuyl" wrote: > > L.S., > > I am trying to install castle, but I get the following messages: > Downloading castle-0.1.0.0... > Configuring castle-0.1.0.0... > realgcc.exe: ./specs: Permission denied > What can I do about this? > > I am running Windows XP, Haskell Platform 2013.2.0.0 > > Regards, > Henk-Jan van Tuyl > > > -- > Folding at home > What if you could share your unused computer power to help find a cure? In > just 5 minutes you can join the world's biggest networked computer and get > us closer sooner. Watch the video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > _______________________________________________ > 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 jpm at cs.uu.nl Sun Feb 2 16:02:31 2014 From: jpm at cs.uu.nl (=?ISO-8859-1?Q?Jos=E9_Pedro_Magalh=E3es?=) Date: Sun, 2 Feb 2014 16:02:31 +0000 Subject: [Haskell-cafe] Mixing own and derived instances with Generic Deriving Mechanism In-Reply-To: <52ECE461.8080303@maartenfaddegon.nl> References: <52ECE461.8080303@maartenfaddegon.nl> Message-ID: Hi Maarten, The problem here is that your instance of GShow MyFancyType defines gshow, but the function that is defined generically is actually gshowsPrec, with the others being given defaults. For this to work as you'd expect it to, you have to define gshowsPrec in the instance GShow MyFancyType. This is a bit unfortunate, but because gshowsPrec has a generic default, it cannot have the usual default (like showsPrec does). Cheers, Pedro On Sat, Feb 1, 2014 at 12:11 PM, Maarten Faddegon < haskell-cafe at maartenfaddegon.nl> wrote: > Dear Pedro, Cafe, > > Thanks again for helping me out last December. I have been > playing a bit more with deriving show and now ran into an > interesting problem mixing my own instances with derived > instances. Hope you can enlighten me there! > > > {-# LANGUAGE DeriveGeneric #-} > > module Test where > > import GHC.Generics > > import Generics.Deriving.Show > > The Generic Deriving Mechanism adds the keyword 'default' to > class definitions. With this keyword we can define a > type-generic definition of that method when not given. For > example, if we define our own MyData type, we can derive the > GShow methods: > > > data MyData = MyData MyFancyType deriving Generic > > instance GShow MyData > > We can also still give our own definition, for example if we want > values of the MyFancyType to always be shown as the same string: > > > data MyFancyType = MyFancy1 | MyFancy2 deriving Generic > > instance GShow MyFancyType where > > gshow _ = "Fancy!" > > There is something strange here though: when we use gshow > directly on a MyFancyType value our own instance definition is > used, evaluating as expected to "Fancy!". > > > ex1 = gshow MyFancy1 > > But as soon as we are inside a derived method, we will continue > using derived instances even though we defined our own. The > example below evaluates to "MyData MyFancy1", rather than "MyData > Fancy!": > > > ex2 = gshow (MyData MyFancy1) > > The default methods of GShow are defined in terms of methods from > GShow' which operate on the type-representation. From this > representation I do not see a way to recover the information > that a type has a GShow instance. Am I correct (I hope not :) or > is there a way out? > > Cheers, > > Maarten Faddegon > -------------- next part -------------- An HTML attachment was scrubbed... URL: From trupill at gmail.com Sun Feb 2 16:49:14 2014 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Sun, 2 Feb 2014 17:49:14 +0100 Subject: [Haskell-cafe] New book: "Beginning Haskell" Message-ID: [Disclaimer: I'm the author of the book] Dear Haskell-cafe, I would like to introduce a new book discussing our favourite language from beginner into upper intermediate level: "Beginning Haskell". The book starts assuming zero knowledge about functional programming and builds step by step to get into the realm of web applications, type-level programming, domain specific languages, distributed computing, unit testing and much more! You can look at the Table of Contents in Amazon [ http://www.amazon.com/Beginning-Haskell-A-Project-Based-Approach/dp/1430262508/ ]. The book revolves around the idea of a Time Machine Store: in each part some functionality is developed. The first part serves as an introduction and how to model the data with Haskell data types and functions; part 2 discusses many concepts around monads while developing two data-mining algorithms; in the third part storing and interfacing with clients serves as an excuse to introduce input/output, database access and web applications; part 4 is devoted to discussing domain specific libraries for describing offers; and the last part discusses testing and other engineering issues. All the "classical" topics in Haskell are discussed: higher-order functions, type classes -- functors, applicatives, monads --, laziness. The focus also lies on libraries use in modern Haskell daily programming, such as lenses, streaming data libraries, functional dependencies and type families, Software Transactional Memory and Cloud Haskell. One topic that is cross-cutting through the book is how to manage projects with Cabal or EclipseFP: initializing a new package, declaring dependencies, building and integrating tests. The book tries thus to offer a comprehensive view of the Haskell ecosystem, not only of the Haskell programming language. The book is published by Apress [http://www.apress.com/9781430262503] and available as paperback and electronic format. If somebody would like to make a review for some FP or programming-related magazine (such as The Monad Reader) or assess its possibilities for use in classroom, please drop me a line. Hope you like it! :) -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Sun Feb 2 19:42:03 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sun, 2 Feb 2014 20:42:03 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Building up on the exemple below, I have a problem with mixing effectful/effectless computations. For example, this would not compile: > noEff :: Exp NoEffect () > noEff = return () > hasEffect :: Exp Effect () > hasEffect = do > noEff <--- won't compile > return () But it should: you should be able to run an effectless monad in an effectful one. How to encode this semantic? I know you can replace the type signature of noEff by: > noEff :: Exp r () But I don't find it so elegant... I suppose you have to encode the semantic in the Bind of the Monad instance: > data Exp :: Eff -> * -> * where > ... > Bind1 :: Exp NoEffect a -> (a -> Exp r b) -> Exp r b > Bind2 :: Exp Effect a -> (a -> Exp r b) -> Exp Effect b > instance Monad (Exp r) where > return = Const > (a :: Exp NoEffect a) >>= f = a `Bind1` f > (a :: Exp Effect a) >>= f = a `Bind2` f But this doesn't work: Couldn't match type `r' with 'NoEffect `r' is a rigid type variable Thanks a lot for the help :) all this thread helped me a lot!! Corentin On Thu, Jan 30, 2014 at 8:53 PM, Corentin Dupont wrote: > > > 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 lindsey at composition.al Sun Feb 2 19:55:17 2014 From: lindsey at composition.al (Lindsey Kuper) Date: Sun, 2 Feb 2014 14:55:17 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont wrote: > you should be able to run an effectless monad in an effectful one. > How to encode this semantic? In LVish we just have a `liftQD` operation that will let you lift a deterministic computation to a quasi-deterministic one (recall that deterministic computations can perform fewer effects): liftQD :: Par Det s a -> Par QuasiDet s a So, analogously, you could have a `liftEff` and then write `liftEff noEff`. This is also a little bit ugly, but you may find you don't have to do it very often (we rarely use `liftQD`). Lindsey From cobbe at ccs.neu.edu Sun Feb 2 21:32:19 2014 From: cobbe at ccs.neu.edu (Richard Cobbe) Date: Sun, 2 Feb 2014 16:32:19 -0500 Subject: [Haskell-cafe] problem with happy and type identity Message-ID: <20140202213219.GA238@ridcully.local> I'm working on a small project that involves an Alex scanner and a Happy parser, and I'm getting an error from the type-checker that I do not understand. Can anyone help shed some light on what's going on? I'm running Haskell Platform 2013.2.0.0, on MacOS 10.8.5 with XCode 4.6.3. I've reduced the problem to a very small example, which I've attached as a tar file. It's a cabal package, and it contains a library with some test cases. If I run "cabal configure && cabal build" then the library builds with no problems whatsoever. But if I run cabal clean && cabal configure --enable-tests && cabal build then I get the following error message: RunTests.hs:16:27: Couldn't match expected type `sample-0.4:Ast.Entry' with actual type `Entry' In the return type of a call of `Entry' In the second argument of `(~?=)', namely `Entry "mumble"' In the expression: parse "entry" ~?= Entry "mumble" And this doesn't make any sense to me, because the two types are supposed to be the same. If I take Happy and Alex out of the picture by replacing the Parser module with a hand-written parser, the error goes away. This is hardly feasible in the actual project, of course :-) so I'm hoping someone can shed some light on what I'm doing wrong here. Thanks! Richard (I apologize for the attachment, by the way, but since filesystem layout is potentially important here, and since it's only slightly larger than 1K, I figured it was the best way. If there's a better way to do this in the future (which doesn't assume I can throw it on the web somewhere), then I'd love to hear about it.) -------------- next part -------------- A non-text attachment was scrubbed... Name: sample.tgz Type: application/x-tar-gz Size: 1106 bytes Desc: not available URL: From blancomau at gmail.com Sun Feb 2 23:55:35 2014 From: blancomau at gmail.com (Mauro Blanco) Date: Sun, 2 Feb 2014 21:55:35 -0200 Subject: [Haskell-cafe] ANNOUNCE: fpnla - A library for NLA operations Message-ID: Hi. Today we are releasing fpnla , which defines a framework for linear algebra operations of BLAS and LAPACK. As its main features it allows: - Definition of multiple representations of vectors and matrices. - Arbitrary combination of strategies and structure representations. - Type-safe manipulation of context information associated to each strategy. - Definition of specialized strategies for a given representation. And also fpnla-examples , which contains many example implementations of the operations defined in fpnla using various data structures and algorithms. Regards. -- Mauro Blanco -------------- next part -------------- An HTML attachment was scrubbed... URL: From fumiexcel at gmail.com Mon Feb 3 00:59:28 2014 From: fumiexcel at gmail.com (Fumiaki Kinoshita) Date: Sun, 2 Feb 2014 16:59:28 -0800 (PST) Subject: [Haskell-cafe] What game libraries should I use? In-Reply-To: <52EB94CA.9060604@plaimi.net> References: <52EB94CA.9060604@plaimi.net> Message-ID: My free-game package has Gloss-like but far more generalized APIs[0]. When you define some series of instructions to draw something, you can move then, turn them, or compose them without touching the insides! [0] http://hackage.haskell.org/package/free-game-1.0.1/docs/FreeGame.html#t:Picture2D 2014?1?31???? 21?19?22? UTC+9 Alexander Berntsen: > > -----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 > alex... 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----- > _______________________________________________ > 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 michael at snoyman.com Mon Feb 3 08:57:28 2014 From: michael at snoyman.com (Michael Snoyman) Date: Mon, 3 Feb 2014 10:57:28 +0200 Subject: [Haskell-cafe] A new yaml module Message-ID: The yaml package[1] currently provides two modules. Text.Libyaml is a lower level, streaming API which is essentially a raw exposure of the underlying libyaml C library. Data.Yaml uses the aeson Value data type and ToJSON/FromJSON type classes for higher level serialization. For many cases, this approach works well, though there are problems: * There are problems with roundtripping, since YAML allows for ambiguity about the data type of values[2]. For example, in the yaml snippet `foo: 1234`, is 1234 intended to be numeric or a string? Either is valid. * YAML is intended to be human-readable output. But Data.Yaml provides no control over the encoded representation, e.g. should we use single or double quotes for a string (or no quotes at all), or the order of values in a mapping[3]. For other examples, just look at the issue tracker for yaml[4]. I don't want to drop the current aeson-based functionality, since I think it's still valid and useful in many cases. But I do think it's worthwhile to add in an alternative API which handles YAML-specific constructs better. My idea is: * Create a new Data.Yaml.Aeson module, and have it mirror Data.Yaml. * Deprecate Data.Yaml. * Create a new Data.Yaml.? module to contain this YAML-specific API. I'm asking for feedback on that last point. I have some basic ideas on what such an API would look like, but given that there are many people using YAML in ways different than how I'm using it, I don't think an API designed entirely by me will suit all use cases. I've opened up a new issue[5] to track this work. If you're interested in participating in this design, please contact me. I'm happy to have the discussion on this mailing list, but if (as I suspect) there are just a handful of people who are interested in pushing this forward, it likely makes sense to take the discussion offlist. Michael [1] http://hackage.haskell.org/package/yaml [2] https://github.com/snoyberg/yaml/issues/22 [3] https://github.com/snoyberg/yaml/issues/37 [4] https://github.com/snoyberg/yaml/issues [5] https://github.com/snoyberg/yaml/issues/38 -------------- next part -------------- An HTML attachment was scrubbed... URL: From hans at hanshoglund.se Mon Feb 3 09:13:03 2014 From: hans at hanshoglund.se (=?iso-8859-1?Q?Hans_H=F6glund?=) Date: Mon, 3 Feb 2014 10:13:03 +0100 Subject: [Haskell-cafe] Dispatch a type-function on the existence (or not) of instances? In-Reply-To: <67C7D749-C92D-405F-8A0F-A701AF600EB5@cis.upenn.edu> References: <31962063-6BA2-4C33-89C3-0641D1082FE4@hanshoglund.se> <67C7D749-C92D-405F-8A0F-A701AF600EB5@cis.upenn.edu> Message-ID: <8B95BF87-5F9C-4B47-AFF1-880EEA80FB58@hanshoglund.se> This makes sense, thank you for clearing it up. My problem arises from the following situation, where I want to overload t depending whether a getter is available or not. class HasTGetter a class HasTSetter a t :: HasTSetter a -> Setter a T t :: (HasTGetter a, HasTSetter a) -> Lens a T I could probably resolve the ambiguity by using a separate type function. instance HasTSetter Foo type instance LensType Foo T = Setter Foo T instance HasTGetter Bar instance HasTSetter Bar type instance LensType Bar T = Lens Bar T t :: (HasGetter a, HasSetter a) -> LensType a T Regards, Hans On 1 feb 2014, at 19:21, Richard Eisenberg wrote: > I am sure that "2) The possibility of "converting" a constraint into a type-level bool." is *not* possible. And, it really shouldn't be possible. > > The problem has to do with modules. Suppose we have: > >> module A where >> data Foo >> type Magic -- invented syntax: >> | Show Foo = Int >> | otherwise = Bool > >> module B where >> import A >> instance Show Foo >> bar :: Magic >> bar = 3 > >> module C where >> import A >> quux :: Magic -- no (Show Foo) here! >> quux = False > >> module D where >> import B >> import C >> hasSameType :: a -> a -> () >> hasSameType _ _ = () >> unit :: () >> unit = hasSameType bar quux > > Does that last line of D type-check? `bar` and `quux` are both declared to have the same type. But, of course, they don't have the same type! Yuck. Thus, `Magic` cannot exist. > > In my own work, I've often wanted something like Magic, but I've learned that whenever I start wanting Magic, what I really want is a very different design. > > If you really, really want Magic and just can't live without it though, you might consider using Template Haskell. TH code can query the database of available instances and branch on the existence of an instance. See `reifyInstances`. TH can't cause the problem I described above, because the equivalent using TH would give `bar` and `quux` different types at compile time, because the TH code is fully evaluated, unlike something like `Magic` which might not be. > > I hope this helps! > Richard > > On Jan 31, 2014, at 12:56 PM, Hans H?glund wrote: > >> 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 >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > From rob at mars.org Mon Feb 3 10:50:39 2014 From: rob at mars.org (Rob Leslie) Date: Mon, 3 Feb 2014 02:50:39 -0800 Subject: [Haskell-cafe] STM and unsafePerformIO/bracket Message-ID: I?ve run into a difficulty I?d appreciate some advice to solve. I am trying to make a call to C (through the FFI) within an STM transaction to compute what is effectively a pure result. By itself this doesn?t seem to be a problem, except that the C function depends on some global state in a way that compromises thread safety, and so I would like to serialize the process of setting up that state and calling the FFI. I have tried wrapping my call up with: > unsafePerformIO $ bracket (takeMVar lock) (putMVar lock) $ \_ -> do > setupFFIGlobalState > callFFI This seems to work as intended, with one significant exception. If the surrounding STM transaction is aborted (i.e. because of a TVar conflict detected by another thread) while inside the bracket, then apparently the second argument to ?bracket? may never be evaluated, leaving my ?lock? mutex forever empty, and eventually causing deadlock. Here is a working example of the problem: http://lpaste.net/99399 When I run that, I get: taking lock... lock acquired taking lock... stm-test: thread blocked indefinitely in an MVar operation Is this expected behavior? I realize performing any IO within an STM transaction is inherently unsafe, but I am a little surprised that ?bracket? fails here. Is there a better way to do what I?m trying to accomplish? How can I provide a pure interface to my foreign function that will work within an STM transaction? Thanks, -- Rob Leslie rob at mars.org From johnw at fpcomplete.com Mon Feb 3 11:17:04 2014 From: johnw at fpcomplete.com (John Wiegley) Date: Mon, 03 Feb 2014 05:17:04 -0600 Subject: [Haskell-cafe] STM and unsafePerformIO/bracket In-Reply-To: (Rob Leslie's message of "Mon, 3 Feb 2014 02:50:39 -0800") References: Message-ID: >>>>> Rob Leslie writes: > Is this expected behavior? I realize performing any IO within an STM > transaction is inherently unsafe, but I am a little surprised that ?bracket? > fails here. > > Is there a better way to do what I?m trying to accomplish? How can I provide > a pure interface to my foreign function that will work within an STM > transaction? If your foreign function "depends on some global state in a way that compromises thread safety", I would hestitate to simply tell the FFI that it is pure. Instead, you can break up your STM transaction into two pieces: A first part that sets up the transaction and sets a guard variable so other transactions cannot proceed until the second part is completed, then perform the FFI call, then the second part of the transaction. For example: atomically $ do m <- readTVar mutex check (not m) writeTVar m True ... do whatever STM setup work is needed here ... ffiCall atomically $ do ... do whatever STM cleanup work is needed here ... writeTVar m False This way your ffiCall is conceptually within a larger transactional block. John From corentin.dupont at gmail.com Mon Feb 3 11:44:04 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 3 Feb 2014 12:44:04 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: I saw that to write liftQD you decontruct (unwrap) the type and reconstruct it. I don't know if I can do that for my Exp (which is a full DSL)... Anyway, there should be a way to encode the Effect/NoEffect semantic at type level... Using Oleg's parametrized monad idea ( http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), I tried: > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances #-} > module DSLEffects where > import Prelude hiding (return, (>>), (>>=)) > import Control.Monad.Parameterized This data type will be promoted to kind level (thanks to DataKinds): > data Eff = Effect | NoEffect This class allows to specify the semantic on Effects (Effect + NoEffect = Effect): > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r > instance Effects Effect n Effect > instance Effects NoEffect n n This is the DSL: > data Exp :: Eff -> * -> * where > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect > Const :: a -> Exp r a > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b --Bind comes with a semantic on effects > Fmap :: (a -> b) -> Exp m a -> Exp m b > instance Functor (Exp r) where > fmap = Fmap > instance Return (Exp r) where > returnM = Const > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where > (>>=) = Bind > noEff :: Exp NoEffect () > noEff = returnM () > hasEffect :: Exp Effect () > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) This is working more or less, however I am obliged to put the type signature on the returnM (last line): why? Furthermore, I cannot write directly: > hasEffect :: Exp Effect () > hasEffect = ReadAccount Do you have a better idea? On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper wrote: > On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont > wrote: > > you should be able to run an effectless monad in an effectful one. > > How to encode this semantic? > > In LVish we just have a `liftQD` operation that will let you lift a > deterministic computation to a quasi-deterministic one (recall that > deterministic computations can perform fewer effects): > > liftQD :: Par Det s a -> Par QuasiDet s a > > So, analogously, you could have a `liftEff` and then write `liftEff > noEff`. This is also a little bit ugly, but you may find you don't > have to do it very often (we rarely use `liftQD`). > > Lindsey > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fryguybob at gmail.com Mon Feb 3 14:59:58 2014 From: fryguybob at gmail.com (Ryan Yates) Date: Mon, 3 Feb 2014 09:59:58 -0500 Subject: [Haskell-cafe] STM and unsafePerformIO/bracket In-Reply-To: References: Message-ID: John's approach is the right one, but note that the "STM setup work" will be visible to other transactions. Any work done there must be considered consistent as it will be committed. For instance if we have the following: atomically $ do m <- readTVar mutex check (not m) writeTVar m True writeTVar a True ffiCall atomically $ do writeTVar b True writeTVar m False If it should be the case that `a` is true only if `b` is true then we could run into problems with some other transaction that is not concerned with the `ffiCall` but is concerned about `a` and `b`. Another approach that might be viable is to just fix your foreign call's interface by putting a lock in the foreign code. If it really is a pure call, then there is no danger of deadlocking there. This will then be as safe as any foreign call inside STM. There are dangers here of course. One particular danger is if your call takes multiple arguments that need to be consistent, you can see inconsistency inside a failed transaction before the runtime system has determined that it is a failed transaction. For instance: atomically $ do x <- readTVar a y <- readTVar b return $ unsafePerformIO $ ffiCall x y Say `x` is an array and `y` is an index into that array. Even if your transactions keep these consistent, you could send inconsistent data to the foreign call. You can fix this by checking (at the value level) the integrity of the data or changing the granularity of the data and putting values `x` and `y` into the same `TVar`. Beyond this problem I don't know what other issues foreign calls inside STM face, but I would love to hear what others know. Ryan On Mon, Feb 3, 2014 at 6:17 AM, John Wiegley wrote: > >>>>> Rob Leslie writes: > > > Is this expected behavior? I realize performing any IO within an STM > > transaction is inherently unsafe, but I am a little surprised that > 'bracket' > > fails here. > > > > Is there a better way to do what I'm trying to accomplish? How can I > provide > > a pure interface to my foreign function that will work within an STM > > transaction? > > If your foreign function "depends on some global state in a way that > compromises thread safety", I would hestitate to simply tell the FFI that > it > is pure. > > Instead, you can break up your STM transaction into two pieces: A first > part > that sets up the transaction and sets a guard variable so other > transactions > cannot proceed until the second part is completed, then perform the FFI > call, > then the second part of the transaction. For example: > > atomically $ do > m <- readTVar mutex > check (not m) > writeTVar m True > ... do whatever STM setup work is needed here ... > ffiCall > atomically $ do > ... do whatever STM cleanup work is needed here ... > writeTVar m False > > This way your ffiCall is conceptually within a larger transactional block. > > John > _______________________________________________ > 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 Mon Feb 3 15:15:56 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 3 Feb 2014 10:15:56 -0500 Subject: [Haskell-cafe] STM and unsafePerformIO/bracket In-Reply-To: References: Message-ID: On Mon, Feb 3, 2014 at 5:50 AM, Rob Leslie wrote: > I?ve run into a difficulty I?d appreciate some advice to solve. > > I am trying to make a call to C (through the FFI) within an STM > transaction to compute what is effectively a pure result. By itself this > doesn?t seem to be a problem, except that the C function depends on some > global state in a way that compromises thread safety, and so I would like > to This does not sound particularly pure to me, from a Haskell standpoint. > unsafePerformIO $ bracket (takeMVar lock) (putMVar lock) $ \_ -> do > And this looks to me like completely undefined behavior. I suspect bracket *can't* work in unsafePerformIO. -- 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 Feb 3 15:23:56 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 3 Feb 2014 10:23:56 -0500 Subject: [Haskell-cafe] A new yaml module In-Reply-To: References: Message-ID: On Mon, Feb 3, 2014 at 3:57 AM, Michael Snoyman wrote: > * There are problems with roundtripping, since YAML allows for ambiguity > about the data type of values[2]. For example, in the yaml snippet `foo: > 1234`, is 1234 intended to be numeric or a string? Either is valid. > YAML is a pretty accurate representation of Perl values, so this is inevitable. I'm left wondering if YAML is even appropriate for 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 mail at joachim-breitner.de Mon Feb 3 15:40:06 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Mon, 03 Feb 2014 15:40:06 +0000 Subject: [Haskell-cafe] A new yaml module In-Reply-To: References: Message-ID: <1391442006.3196.15.camel@kirk> Hi, Am Montag, den 03.02.2014, 10:23 -0500 schrieb Brandon Allbery: > On Mon, Feb 3, 2014 at 3:57 AM, Michael Snoyman > wrote: > * There are problems with roundtripping, since YAML allows for > ambiguity about the data type of values[2]. For example, in > the yaml snippet `foo: 1234`, is 1234 intended to be numeric > or a string? Either is valid. > > > > YAML is a pretty accurate representation of Perl values, so this is > inevitable. I'm left wondering if YAML is even appropriate for > Haskell.... I?m left wondering if ?is ... even appropriate for Haskell? is even appropriate. If the task to be solved is ?Generate data in this particular format?, and picking the format is not part of the task, then we still want the language of our choice to be appropriate, don?t we? YAML may be an inappropriate choice of serialisation format if we are free to chose and there is only Haskell code involved. 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 vogt.adam at gmail.com Mon Feb 3 17:47:53 2014 From: vogt.adam at gmail.com (adam vogt) Date: Mon, 3 Feb 2014 12:47:53 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hi Corentin, Oleg's January 31 message has: `ReadAccount :: Exp r Int'. If you use that version you can define that last `hasEffect :: Exp Effect ()'. Then bind can just be: Bind :: Exp m a -> (a -> Exp m b) -> Exp m b And the `m' from a non-effectful thing (ReadAccount) will be set to Effect when you bind it with an effectful computation. You can still have operations that take arguments like `Exp NoEffect a', which will give you a type error when you pass in a an argument tagged with Effect. Adam On Mon, Feb 3, 2014 at 6:44 AM, Corentin Dupont wrote: > I saw that to write liftQD you decontruct (unwrap) the type and > reconstruct it. > I don't know if I can do that for my Exp (which is a full DSL)... > > Anyway, there should be a way to encode the Effect/NoEffect semantic at > type level... > Using Oleg's parametrized monad idea ( > http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), > I tried: > > > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs > > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, > UndecidableInstances #-} > > > module DSLEffects where > > import Prelude hiding (return, (>>), (>>=)) > > import Control.Monad.Parameterized > > This data type will be promoted to kind level (thanks to DataKinds): > > > > data Eff = Effect | NoEffect > > This class allows to specify the semantic on Effects (Effect + NoEffect = > Effect): > > > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r > > instance Effects Effect n Effect > > instance Effects NoEffect n n > > This is the DSL: > > > data Exp :: Eff -> * -> * where > > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect > > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect > > Const :: a -> Exp r a > > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b > --Bind comes with a semantic on effects > > Fmap :: (a -> b) -> Exp m a -> Exp m b > > > instance Functor (Exp r) where > > fmap = Fmap > > > instance Return (Exp r) where > > returnM = Const > > > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where > > (>>=) = Bind > > > noEff :: Exp NoEffect () > > noEff = returnM () > > > hasEffect :: Exp Effect () > > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) > > This is working more or less, however I am obliged to put the type > signature on the returnM (last line): why? > Furthermore, I cannot write directly: > > > hasEffect :: Exp Effect () > > hasEffect = ReadAccount > > > Do you have a better idea? > > > > On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper wrote: > >> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont >> wrote: >> > you should be able to run an effectless monad in an effectful one. >> > How to encode this semantic? >> >> In LVish we just have a `liftQD` operation that will let you lift a >> deterministic computation to a quasi-deterministic one (recall that >> deterministic computations can perform fewer effects): >> >> liftQD :: Par Det s a -> Par QuasiDet s a >> >> So, analogously, you could have a `liftEff` and then write `liftEff >> noEff`. This is also a little bit ugly, but you may find you don't >> have to do it very often (we rarely use `liftQD`). >> >> Lindsey >> > > > _______________________________________________ > 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 Feb 3 18:08:25 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 3 Feb 2014 19:08:25 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hi Adam, yes, on second thought, that's really the simpler. I was just disappointed that the type signature of "ReadAccount", an operation with no effect, would not be "Exp NoEffect ()". :) On Mon, Feb 3, 2014 at 6:47 PM, adam vogt wrote: > Hi Corentin, > > Oleg's January 31 message has: `ReadAccount :: Exp r Int'. If you use > that version you can define that last `hasEffect :: Exp Effect ()'. Then > bind can just be: > > Bind :: Exp m a -> (a -> Exp m b) -> Exp m b > > And the `m' from a non-effectful thing (ReadAccount) will be set to Effect > when you bind it with an effectful computation. You can still have > operations that take arguments like `Exp NoEffect a', which will give you a > type error when you pass in a an argument tagged with Effect. > > Adam > > > On Mon, Feb 3, 2014 at 6:44 AM, Corentin Dupont > wrote: > >> I saw that to write liftQD you decontruct (unwrap) the type and >> reconstruct it. >> I don't know if I can do that for my Exp (which is a full DSL)... >> >> Anyway, there should be a way to encode the Effect/NoEffect semantic at >> type level... >> Using Oleg's parametrized monad idea ( >> http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), >> I tried: >> >> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs >> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, >> UndecidableInstances #-} >> >> > module DSLEffects where >> > import Prelude hiding (return, (>>), (>>=)) >> > import Control.Monad.Parameterized >> >> This data type will be promoted to kind level (thanks to DataKinds): >> >> >> > data Eff = Effect | NoEffect >> >> This class allows to specify the semantic on Effects (Effect + NoEffect = >> Effect): >> >> > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r >> > instance Effects Effect n Effect >> > instance Effects NoEffect n n >> >> This is the DSL: >> >> > data Exp :: Eff -> * -> * where >> > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect >> > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect >> > Const :: a -> Exp r a >> > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b >> --Bind comes with a semantic on effects >> > Fmap :: (a -> b) -> Exp m a -> Exp m b >> >> > instance Functor (Exp r) where >> > fmap = Fmap >> >> > instance Return (Exp r) where >> > returnM = Const >> >> > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where >> > (>>=) = Bind >> >> > noEff :: Exp NoEffect () >> > noEff = returnM () >> >> > hasEffect :: Exp Effect () >> > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) >> >> This is working more or less, however I am obliged to put the type >> signature on the returnM (last line): why? >> Furthermore, I cannot write directly: >> >> > hasEffect :: Exp Effect () >> > hasEffect = ReadAccount >> >> >> Do you have a better idea? >> >> >> >> On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper wrote: >> >>> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont >>> wrote: >>> > you should be able to run an effectless monad in an effectful one. >>> > How to encode this semantic? >>> >>> In LVish we just have a `liftQD` operation that will let you lift a >>> deterministic computation to a quasi-deterministic one (recall that >>> deterministic computations can perform fewer effects): >>> >>> liftQD :: Par Det s a -> Par QuasiDet s a >>> >>> So, analogously, you could have a `liftEff` and then write `liftEff >>> noEff`. This is also a little bit ugly, but you may find you don't >>> have to do it very often (we rarely use `liftQD`). >>> >>> Lindsey >>> >> >> >> _______________________________________________ >> 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 chrisyco+haskell-cafe at gmail.com Mon Feb 3 20:07:07 2014 From: chrisyco+haskell-cafe at gmail.com (Chris Wong) Date: Tue, 4 Feb 2014 09:07:07 +1300 Subject: [Haskell-cafe] A new yaml module In-Reply-To: <1391442006.3196.15.camel@kirk> References: <1391442006.3196.15.camel@kirk> Message-ID: On Tue, Feb 4, 2014 at 4:40 AM, Joachim Breitner wrote: > Hi, > > Am Montag, den 03.02.2014, 10:23 -0500 schrieb Brandon Allbery: >> On Mon, Feb 3, 2014 at 3:57 AM, Michael Snoyman >> wrote: >> * There are problems with roundtripping, since YAML allows for >> ambiguity about the data type of values[2]. For example, in >> the yaml snippet `foo: 1234`, is 1234 intended to be numeric >> or a string? Either is valid. >> >> >> >> YAML is a pretty accurate representation of Perl values, so this is >> inevitable. I'm left wondering if YAML is even appropriate for >> Haskell.... > > I?m left wondering if ?is ... even appropriate for Haskell? is even > appropriate. If the task to be solved is ?Generate data in this > particular format?, and picking the format is not part of the task, then > we still want the language of our choice to be appropriate, don?t we? > > YAML may be an inappropriate choice of serialisation format if we are > free to chose and there is only Haskell code involved. AFAIK, Yesod uses YAML mainly for configuration files. For that use case, I've found configurator[1] much easier to use. [1] http://hackage.haskell.org/package/configurator > 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 > -- Chris Wong, fixpoint conjurer e: lambda.fairy at gmail.com w: http://lfairy.github.io From petr.mvd at gmail.com Mon Feb 3 20:21:49 2014 From: petr.mvd at gmail.com (=?ISO-8859-1?Q?Petr_Pudl=E1k?=) Date: Mon, 3 Feb 2014 21:21:49 +0100 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: Since nobody replied so far, I'm also forwarding to cafe. Petr ---------- Forwarded message ---------- From: Petr Pudl?k Date: 2014-01-29 Subject: incorrect MonadPlus law "v >> mzero = mzero"? To: "libraries at haskell.org" Hi, this law apparently fails for a MonadPlus instance that has more than one possible failure value. Consider: runIdentity . runErrorT $ ((ErrorT . Identity $ Left "failure") >> mzero :: ErrorT String Identity ()) evaluates to `Left "failure"`, which isn't equal to ErrorT's mzero `Left ""`. This isn't just the case of ErrorT, it fails for any MonadPlus with multiple failure values. For example lift (tell "foo") >> mzero :: MaybeT (Writer String) () is again distinct from mzero. Actually, no monad transformer with a MonadPlus instance can satisfy the law, because the first part in front of `>> mzero` can introduce side effects in the underlying monad. I'm not sure what should be the proper solution. Perhaps to change the laws to: return x >> mzero = mzero (v >> mzero) >>= f = (v >> mzero)` That is, if an expression ends with `mzero`, it behaves like `mzero`. Petr -------------- next part -------------- An HTML attachment was scrubbed... URL: From Charles at CharlesWeitzer.com Mon Feb 3 21:19:12 2014 From: Charles at CharlesWeitzer.com (Charles Weitzer) Date: Mon, 3 Feb 2014 13:19:12 -0800 Subject: [Haskell-cafe] CTO Opportunity Message-ID: <006901cf2125$96181160$c2483420$@CharlesWeitzer.com> My name is Charles Weitzer. I do recruiting for major quantitative hedge funds worldwide. I have a client, a startup quantitative hedge fund located in Northern California, that would like to hire a Chief Technology Officer as soon as possible. Their job description can be found below. * Chief Technology Officer Fast-growing science and technology driven company seeks a Chief Technology Officer. We apply statistical machine learning to develop automated trading systems. We are a growing group of exceptional software and infrastructure professionals and seek an experienced candidate to lead and grow the team. The CTO will manage the implementation of our next generation infrastructure, including production trading systems, software infrastructure for our research department, and our compute and storage hardware systems. The CTO will work directly with the Head of Research and the CEO to set the technical direction of the company. A strong candidate will be well-versed in state-of-the-art technology (particularly distributed systems and cluster computing), and will have a track record of building and leading elite technical teams and successfully delivering complex projects (especially in a startup environment). A background in finance is not required. We are a science-driven systematic trading firm, built on the principle that statistical machine learning provides the best solutions to the scientific problems we must solve. Our CEO is a CS PhD and founded a successful Internet startup, and our Head of Research/Chief Investment Officer is a Berkeley statistics professor; both have a background in finance. Our trading is entirely automated and based on cutting-edge machine learning techniques. We have a collegial, academic working environment, rely on open source software, and have built our own software stack. We have a track record of strong performance and have been raising money and growing fast. Willingness to take initiative, and a gritty determination to productize, are essential. Benefits and compensation are highly competitive. I look forward to speaking with you and anyone you might highly recommend about this opportunity. Thank you, Charles Weitzer CEO/Senior Recruiter Charles Weitzer and Associates, Inc. Global Financial Recruiting Services Charles at CharlesWeitzer.com Voice: USA (510) 558-9182 From danburton.email at gmail.com Mon Feb 3 22:51:04 2014 From: danburton.email at gmail.com (Dan Burton) Date: Mon, 3 Feb 2014 14:51:04 -0800 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: Indeed this issue is not limited merely to multiple failure values. >>> runMaybeT $ lift (putStrLn "effect") >> mzero effect >>> runMaybeT mzero So you're right. This law is being violated -- Dan Burton On Mon, Feb 3, 2014 at 12:21 PM, Petr Pudl?k wrote: > Since nobody replied so far, I'm also forwarding to cafe. > Petr > > > ---------- Forwarded message ---------- > From: Petr Pudl?k > Date: 2014-01-29 > Subject: incorrect MonadPlus law "v >> mzero = mzero"? > To: "libraries at haskell.org" > > > Hi, > > this law apparently fails for a MonadPlus instance that has more than one > possible failure value. Consider: > > runIdentity . runErrorT $ > ((ErrorT . Identity $ Left "failure") >> mzero :: ErrorT String > Identity ()) > > evaluates to `Left "failure"`, which isn't equal to ErrorT's mzero `Left > ""`. > > This isn't just the case of ErrorT, it fails for any MonadPlus with > multiple failure values. For example > > lift (tell "foo") >> mzero :: MaybeT (Writer String) () > > is again distinct from mzero. > > Actually, no monad transformer with a MonadPlus instance can satisfy the > law, because the first part in front of `>> mzero` can introduce side > effects in the underlying monad. > > I'm not sure what should be the proper solution. Perhaps to change the > laws to: > > return x >> mzero = mzero > (v >> mzero) >>= f = (v >> mzero)` > > That is, if an expression ends with `mzero`, it behaves like `mzero`. > > Petr > > > _______________________________________________ > 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 Mon Feb 3 23:00:36 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 3 Feb 2014 18:00:36 -0500 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: On Mon, Feb 3, 2014 at 5:51 PM, Dan Burton wrote: > Indeed this issue is not limited merely to multiple failure values. > > >>> runMaybeT $ lift (putStrLn "effect") >> mzero > effect > >>> runMaybeT mzero > > So you're right. This law is being violated > I thought it was fairly well known that IO violates one of the monad laws, in a way that would lead to this? -- 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 danburton.email at gmail.com Mon Feb 3 23:04:06 2014 From: danburton.email at gmail.com (Dan Burton) Date: Mon, 3 Feb 2014 15:04:06 -0800 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: > > I'm not sure what should be the proper solution. Perhaps to change the > laws to: > return x >> mzero = mzero > (v >> mzero) >>= f = (v >> mzero)` > That is, if an expression ends with `mzero`, it behaves like `mzero`. These laws are redundant with existing laws. The first: return x >> z = z Is true forall x and z, and can be proven by just the monad laws. The second: (v >> mzero) >>= f = (v >> mzero) Can be proven by the associativity of monadic operations: (v >> mzero) >>= f = v >> (mzero >>= f) And the other MonadPlus law already states that (mzero >>= f) = mzero. So I don't think any new laws are needed. I just think the (v >> mzero = mzero) law should be removed, or else a *lot* of instances of MonadPlus need to come with a disclaimer that they are not law-abiding. -- Dan Burton -------------- next part -------------- An HTML attachment was scrubbed... URL: From jwlato at gmail.com Mon Feb 3 23:10:47 2014 From: jwlato at gmail.com (John Lato) Date: Mon, 3 Feb 2014 15:10:47 -0800 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: On Mon, Feb 3, 2014 at 3:00 PM, Brandon Allbery wrote: > On Mon, Feb 3, 2014 at 5:51 PM, Dan Burton wrote: > >> Indeed this issue is not limited merely to multiple failure values. >> >> >>> runMaybeT $ lift (putStrLn "effect") >> mzero >> effect >> >>> runMaybeT mzero >> >> So you're right. This law is being violated >> > > I thought it was fairly well known that IO violates one of the monad laws, > in a way that would lead to this? > The choice of IO for the underlying monad is irrelevant. The issue is that a later mzero in the transformer cannot undo an earlier action in a lower monad. For example: >>> Prelude Control.Monad.Maybe Control.Monad.State> runStateT (runMaybeT $ (lift $ put "bar") >> mzero) "foo" (Nothing,"bar") >>> Prelude Control.Monad.Maybe Control.Monad.State> runStateT (runMaybeT mzero) "foo" (Nothing,"foo") -------------- next part -------------- An HTML attachment was scrubbed... URL: From danburton.email at gmail.com Mon Feb 3 23:21:41 2014 From: danburton.email at gmail.com (Dan Burton) Date: Mon, 3 Feb 2014 15:21:41 -0800 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: > > The issue is that a later mzero in the transformer cannot undo an earlier > action in a lower monad. Precisely. Another example, for fun: >>> print (runMaybeT $ lift [1,2,3] >> mzero :: [Maybe Int]) [Nothing, Nothing, Nothing] >>> print (runMaybeT mzero :: [Maybe Int]) [Nothing] Actually, I'd say the problem *isn't *that a transformer "cannot undo earlier action in a lower monad." I'd just say that most transformers *happen to be implemented *in this "forgetful" manner. It's conceivable that we could implement some of them differently, in a way that would obey the MonadPlus laws. Whether or not obedience to this particular law is worthwhile... well, that's debatable. -- Dan Burton -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.mvd at gmail.com Tue Feb 4 08:21:25 2014 From: petr.mvd at gmail.com (=?ISO-8859-1?Q?Petr_Pudl=E1k?=) Date: Tue, 4 Feb 2014 09:21:25 +0100 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: My intention wasn't to add these laws, but to replace the existing MonadPlus ones. (Adding new laws wouldn't help with the original ones being invalid.) But you're right, the laws I proposed follow from Monad laws and from mzero >>= f = mzero This single law is enough to ensure that any chain of operations containing `mzero` "ends" at this point. So the best solution seems to just remove the problematic v >> mzero = mzero 2014-02-04 Dan Burton : > I'm not sure what should be the proper solution. Perhaps to change the >> laws to: >> return x >> mzero = mzero >> (v >> mzero) >>= f = (v >> mzero)` >> That is, if an expression ends with `mzero`, it behaves like `mzero`. > > > These laws are redundant with existing laws. The first: > > return x >> z = z > > Is true forall x and z, and can be proven by just the monad laws. The > second: > > (v >> mzero) >>= f = (v >> mzero) > > Can be proven by the associativity of monadic operations: > > (v >> mzero) >>= f = v >> (mzero >>= f) > > And the other MonadPlus law already states that (mzero >>= f) = mzero. So > I don't think any new laws are needed. I just think the (v >> mzero = > mzero) law should be removed, or else a *lot* of instances of MonadPlus > need to come with a disclaimer that they are not law-abiding. > > -- Dan Burton > -------------- next part -------------- An HTML attachment was scrubbed... URL: From petr.mvd at gmail.com Tue Feb 4 08:32:19 2014 From: petr.mvd at gmail.com (=?ISO-8859-1?Q?Petr_Pudl=E1k?=) Date: Tue, 4 Feb 2014 09:32:19 +0100 Subject: [Haskell-cafe] Fwd: incorrect MonadPlus law "v >> mzero = mzero"? In-Reply-To: References: Message-ID: I would argue that a monad transformer "cannot undo earlier action in a lower monad." For example, in the case of MaybeT: In order to determine of an action succeeded or failed, it needs to evaluate in the underlying monad. But what if the underlying monad doesn't provide any means to restore its state to some previous point? So I believe having 'v >> mzero = mzero' for a transformer with MonadPlus would be only possible if the underlying monad provided some kind of check-pointing. 2014-02-04 Dan Burton : > The issue is that a later mzero in the transformer cannot undo an earlier >> action in a lower monad. > > > Precisely. Another example, for fun: > > >>> print (runMaybeT $ lift [1,2,3] >> mzero :: [Maybe Int]) > [Nothing, Nothing, Nothing] > > >>> print (runMaybeT mzero :: [Maybe Int]) > [Nothing] > > Actually, I'd say the problem *isn't *that a transformer "cannot undo > earlier action in a lower monad." I'd just say that most transformers *happen > to be implemented *in this "forgetful" manner. It's conceivable that we > could implement some of them differently, in a way that would obey the > MonadPlus laws. Whether or not obedience to this particular law is > worthwhile... well, that's debatable. > > -- Dan Burton > > _______________________________________________ > 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 jan.stolarek at p.lodz.pl Tue Feb 4 12:21:10 2014 From: jan.stolarek at p.lodz.pl (Jan Stolarek) Date: Tue, 4 Feb 2014 13:21:10 +0100 Subject: [Haskell-cafe] [ANNOUNCE] tasty-hunit-adapter and tasty-program Message-ID: <201402041321.10691.jan.stolarek@p.lodz.pl> Dear Haskellers, I recently released two small packages that extend functionality of Roman Cheplyaka's tasty testing framework: 1. tasty-hunit-adapter allows to import existing HUnit tests into tasty. Hackage: http://hackage.haskell.org/package/tasty-hunit-adapter GitHub: https://github.com/jstolarek/tasty-hunit-adapter 2. tasty-program allows to run external program and test whether it terminates successfully. Hackage: http://hackage.haskell.org/package/tasty-program GitHub: https://github.com/jstolarek/tasty-program These packages are inspired by similar packages for test-framework. tasty-program has very basic functionality at the moment, most notably it completely ignores stdout and stderr of a program. If you want this functionality please say so here: https://github.com/jstolarek/tasty-program/issues/1 Jan Stolarek From haskell-cafe at maartenfaddegon.nl Tue Feb 4 12:53:55 2014 From: haskell-cafe at maartenfaddegon.nl (Maarten Faddegon) Date: Tue, 04 Feb 2014 12:53:55 +0000 Subject: [Haskell-cafe] Mixing own and derived instances with Generic Deriving Mechanism In-Reply-To: References: <52ECE461.8080303@maartenfaddegon.nl> Message-ID: <52F0E2E3.2050905@maartenfaddegon.nl> Thanks! I rewrote my example from gshow into gshowPrec and now it works as expected :) Would it be correct to say that the 'from'-function does a shallow convert of my value into the type representation (up to the constant representations), and from there we either use an ad-hoc instance of gshowPrec, or we do another shallow convert one layer deeper via the default gShowPrec? Cheers, Maarten On 02/02/14 16:02, Jos? Pedro Magalh?es wrote: > Hi Maarten, > > The problem here is that your instance of GShow MyFancyType defines > gshow, but the > function that is defined generically is actually gshowsPrec, with the > others being given > defaults. For this to work as you'd expect it to, you have to define > gshowsPrec in the > instance GShow MyFancyType. This is a bit unfortunate, but because > gshowsPrec has > a generic default, it cannot have the usual default (like showsPrec does). > > > Cheers, > Pedro > > > > On Sat, Feb 1, 2014 at 12:11 PM, Maarten Faddegon > > wrote: > > Dear Pedro, Cafe, > > Thanks again for helping me out last December. I have been > playing a bit more with deriving show and now ran into an > interesting problem mixing my own instances with derived > instances. Hope you can enlighten me there! > > > {-# LANGUAGE DeriveGeneric #-} > > module Test where > > import GHC.Generics > > import Generics.Deriving.Show > > The Generic Deriving Mechanism adds the keyword 'default' to > class definitions. With this keyword we can define a > type-generic definition of that method when not given. For > example, if we define our own MyData type, we can derive the > GShow methods: > > > data MyData = MyData MyFancyType deriving Generic > > instance GShow MyData > > We can also still give our own definition, for example if we want > values of the MyFancyType to always be shown as the same string: > > > data MyFancyType = MyFancy1 | MyFancy2 deriving Generic > > instance GShow MyFancyType where > > gshow _ = "Fancy!" > > There is something strange here though: when we use gshow > directly on a MyFancyType value our own instance definition is > used, evaluating as expected to "Fancy!". > > > ex1 = gshow MyFancy1 > > But as soon as we are inside a derived method, we will continue > using derived instances even though we defined our own. The > example below evaluates to "MyData MyFancy1", rather than "MyData > Fancy!": > > > ex2 = gshow (MyData MyFancy1) > > The default methods of GShow are defined in terms of methods from > GShow' which operate on the type-representation. From this > representation I do not see a way to recover the information > that a type has a GShow instance. Am I correct (I hope not :) or > is there a way out? > > Cheers, > > Maarten Faddegon > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From benjamin.foppa at gmail.com Tue Feb 4 13:55:47 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Tue, 4 Feb 2014 08:55:47 -0500 Subject: [Haskell-cafe] fromString and toString Message-ID: I know we have class IsString a where fromString :: String -> a But do we have an inverse generic function toString defined anywhere? IsString implies that the type `a` is a subset of String; if all we have is fromString, then IsString defines *supersets* of String. To me, the most logical thing would be that IsString defines bijections to String (i.e. things that are subsets *and* supersets). The reason this came up is that I'm getting pretty sick of type-juggling different string types from different libraries (String, Text, various ByteStrings), especially since I have to tweak all the functions I use if a type changes; discovering fromString was fantastic, but without toString, I can't define something like reString :: (IsString a, IsString b) => a -> b which is great to have if your putStrLn only accepts one kind of string, and you have several distinct ones floating around. Thanks, Ben -------------- next part -------------- An HTML attachment was scrubbed... URL: From dima at dzhus.org Tue Feb 4 14:03:39 2014 From: dima at dzhus.org (Dmitry Dzhus) Date: Tue, 04 Feb 2014 18:03:39 +0400 Subject: [Haskell-cafe] fromString and toString In-Reply-To: References: Message-ID: <62511391522619@web23h.yandex.ru> 04.02.2014, 17:55, "Ben Foppa" : > I know we have > > class IsString a where > > ??? fromString :: String -> a > > But do we have an inverse generic function toString defined anywhere? IsString implies that the type `a` is a subset of String; if all we have is fromString, then IsString defines supersets of String. To me, the most logical thing would be that IsString defines bijections to String (i.e. things that are subsets and supersets). There's more than one way to interpret a ByteString as a String/Text and vice versa. If reString exists, what would you expect it to do when called with a ~ ByteString and b ~ Text? From bertram.felgenhauer at googlemail.com Tue Feb 4 14:06:11 2014 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Tue, 4 Feb 2014 15:06:11 +0100 Subject: [Haskell-cafe] STM and unsafePerformIO/bracket In-Reply-To: References: Message-ID: <20140204140611.GA3202@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Rob Leslie wrote: > I?ve run into a difficulty I?d appreciate some advice to solve. [unsafePerformIO and bracket, within an STM transaction] There's a long-standing bug report for this issue, https://ghc.haskell.org/trac/ghc/ticket/2401 So the current situation is that bracket within unsafePerformIO (and unsafeIOToSTM) and STM transactions don't mix. I'm a bit surprised that this doesn't bite more people. Cheers, Bertram From marco-oweber at gmx.de Tue Feb 4 14:11:10 2014 From: marco-oweber at gmx.de (Marc Weber) Date: Tue, 04 Feb 2014 15:11:10 +0100 Subject: [Haskell-cafe] Big Data & Haskell Message-ID: <1391522838-sup-5331@nixos> Is Haskell ready? Are there library which can - distribute data on multiple machines (similar to cassandra) - implement multi index things, such as having fields - name (eg of stores) - geo location (x/y) keys so that you can find items nearby a location fast - additional data to be searched as needed Maybe have server which gets "code" sent by a master to be compiled defining the data to host or such? I know that this could be done - just wondering whether it has been done already. Marc Weber From waldmann at imn.htwk-leipzig.de Tue Feb 4 14:13:13 2014 From: waldmann at imn.htwk-leipzig.de (Johannes Waldmann) Date: Tue, 4 Feb 2014 14:13:13 +0000 (UTC) Subject: [Haskell-cafe] fromString and toString References: Message-ID: Ben Foppa gmail.com> writes: > But do we have an inverse generic function toString defined anywhere? well, we have: class Show a where show :: a -> String > likereString :: (IsString a, IsString b) => a -> b well you probably don't want to actually convert from a to String (= List of Char) then from there to b, so it would need to be accompanied by some RULES (for specific instances of a, b) for efficiency. This still does not answer the concern whether it is (semantically) wise to have String as the "base" concept here. - J.W. From vlatko.basic at gmail.com Tue Feb 4 14:38:15 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Tue, 04 Feb 2014 15:38:15 +0100 Subject: [Haskell-cafe] Big Data & Haskell In-Reply-To: <1391522838-sup-5331@nixos> References: <1391522838-sup-5331@nixos> Message-ID: <52F0FB57.7000509@gmail.com> Hi Marc, Maybe you can have a look at Riak DB. It is a key/value storage written in Erlang with many features. All peers, no master/slave and replication. Haskell package is at http://hackage.haskell.org/package/riak, but haven't tried it yet. Best regards, vlatko -------- Original Message -------- Subject: [Haskell-cafe] Big Data & Haskell From: Marc Weber To: haskell-cafe Date: 04.02.2014 15:11 > Is Haskell ready? > Are there library which can > > - distribute data on multiple machines (similar to cassandra) > > - implement multi index things, such as > having fields > - name (eg of stores) > - geo location (x/y) keys so that you can find items nearby a > location fast > - additional data to be searched as needed > > Maybe have server which gets "code" sent by a master to be compiled > defining the data to host or such? > > I know that this could be done - just wondering whether it has been done > already. > > Marc Weber > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From jpmoresmau at gmail.com Tue Feb 4 16:11:04 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Tue, 4 Feb 2014 17:11:04 +0100 Subject: [Haskell-cafe] Big Data & Haskell In-Reply-To: <52F0FB57.7000509@gmail.com> References: <1391522838-sup-5331@nixos> <52F0FB57.7000509@gmail.com> Message-ID: Have you looked at Cloud Haskell ( http://www.haskell.org/haskellwiki/Cloud_Haskell)? JP On Tue, Feb 4, 2014 at 3:38 PM, Vlatko Basic wrote: > Hi Marc, > > Maybe you can have a look at Riak DB. It is a key/value storage written in > Erlang with many features. All peers, no master/slave and replication. > > Haskell package is at http://hackage.haskell.org/package/riak, but > haven't tried it yet. > > > Best regards, > > vlatko > > > -------- Original Message -------- > Subject: [Haskell-cafe] Big Data & Haskell > From: Marc Weber > To: haskell-cafe > Date: 04.02.2014 15:11 > > Is Haskell ready? >> Are there library which can >> >> - distribute data on multiple machines (similar to cassandra) >> >> - implement multi index things, such as >> having fields >> - name (eg of stores) >> - geo location (x/y) keys so that you can find items nearby a >> location fast >> - additional data to be searched as needed >> >> Maybe have server which gets "code" sent by a master to be compiled >> defining the data to host or such? >> >> I know that this could be done - just wondering whether it has been done >> already. >> >> Marc Weber >> _______________________________________________ >> 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 > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpm at cs.uu.nl Tue Feb 4 16:32:22 2014 From: jpm at cs.uu.nl (=?ISO-8859-1?Q?Jos=E9_Pedro_Magalh=E3es?=) Date: Tue, 4 Feb 2014 16:32:22 +0000 Subject: [Haskell-cafe] Mixing own and derived instances with Generic Deriving Mechanism In-Reply-To: <52F0E2E3.2050905@maartenfaddegon.nl> References: <52ECE461.8080303@maartenfaddegon.nl> <52F0E2E3.2050905@maartenfaddegon.nl> Message-ID: Hi Maarten, On Tue, Feb 4, 2014 at 12:53 PM, Maarten Faddegon < haskell-cafe at maartenfaddegon.nl> wrote: > Thanks! I rewrote my example from gshow into gshowPrec and now it works > as expected :) > > Would it be correct to say that the 'from'-function does a shallow convert > of my value into the type representation (up to the constant > representations), > This is true, yes. > and from there we either use an ad-hoc instance of gshowPrec, or we do > another shallow convert one layer deeper via the default gShowPrec? > The shallow vs. deep representation isn't really at play here. The outermost type (|MyData|) is not the same as the innermost type (|MyFancyType|). The issue is that you defined an adhoc |gshow|, but in fact the function that was being used is |gshowsPrec|, which was using the generic default. That and the fact that the generic |gshow| is defined in terms of |gshowsPrec|. Cheers, Pedro > > Cheers, > > Maarten > > > On 02/02/14 16:02, Jos? Pedro Magalh?es wrote: > > Hi Maarten, > > The problem here is that your instance of GShow MyFancyType defines > gshow, but the > function that is defined generically is actually gshowsPrec, with the > others being given > defaults. For this to work as you'd expect it to, you have to define > gshowsPrec in the > instance GShow MyFancyType. This is a bit unfortunate, but because > gshowsPrec has > a generic default, it cannot have the usual default (like showsPrec > does). > > > Cheers, > Pedro > > > > On Sat, Feb 1, 2014 at 12:11 PM, Maarten Faddegon < > haskell-cafe at maartenfaddegon.nl> wrote: > >> Dear Pedro, Cafe, >> >> Thanks again for helping me out last December. I have been >> playing a bit more with deriving show and now ran into an >> interesting problem mixing my own instances with derived >> instances. Hope you can enlighten me there! >> >> > {-# LANGUAGE DeriveGeneric #-} >> > module Test where >> > import GHC.Generics >> > import Generics.Deriving.Show >> >> The Generic Deriving Mechanism adds the keyword 'default' to >> class definitions. With this keyword we can define a >> type-generic definition of that method when not given. For >> example, if we define our own MyData type, we can derive the >> GShow methods: >> >> > data MyData = MyData MyFancyType deriving Generic >> > instance GShow MyData >> >> We can also still give our own definition, for example if we want >> values of the MyFancyType to always be shown as the same string: >> >> > data MyFancyType = MyFancy1 | MyFancy2 deriving Generic >> > instance GShow MyFancyType where >> > gshow _ = "Fancy!" >> >> There is something strange here though: when we use gshow >> directly on a MyFancyType value our own instance definition is >> used, evaluating as expected to "Fancy!". >> >> > ex1 = gshow MyFancy1 >> >> But as soon as we are inside a derived method, we will continue >> using derived instances even though we defined our own. The >> example below evaluates to "MyData MyFancy1", rather than "MyData >> Fancy!": >> >> > ex2 = gshow (MyData MyFancy1) >> >> The default methods of GShow are defined in terms of methods from >> GShow' which operate on the type-representation. From this >> representation I do not see a way to recover the information >> that a type has a GShow instance. Am I correct (I hope not :) or >> is there a way out? >> >> Cheers, >> >> Maarten Faddegon >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From k-bx at k-bx.com Tue Feb 4 20:53:03 2014 From: k-bx at k-bx.com (Konstantine Rybnikov) Date: Tue, 4 Feb 2014 21:53:03 +0100 Subject: [Haskell-cafe] hyperloglog build error Message-ID: Hi! I wanted to use hyperloglog [0] package, but got these errors: https://gist.github.com/k-bx/70654962d4d98ee52e22 I am now trying to "match by hands" why that instance doesn't exist for me, but maybe some of your could help, since I'm far away from all near-lens libraries (but I promise to learn those!). Thank you! [0]: https://github.com/ekmett/hyperloglog/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From atzeus at gmail.com Wed Feb 5 08:13:44 2014 From: atzeus at gmail.com (Atze van der Ploeg) Date: Wed, 5 Feb 2014 09:13:44 +0100 Subject: [Haskell-cafe] fromString and toString In-Reply-To: References: Message-ID: Isn't toString just show? On Feb 4, 2014 3:20 PM, "Johannes Waldmann" wrote: > Ben Foppa gmail.com> writes: > > > But do we have an inverse generic function toString defined anywhere? > > well, we have: class Show a where show :: a -> String > > > likereString :: (IsString a, IsString b) => a -> b > > well you probably don't want to actually convert from a to String > (= List of Char) then from there to b, > so it would need to be accompanied by some RULES > (for specific instances of a, b) for efficiency. > > This still does not answer the concern whether it is > (semantically) wise to have String as the "base" concept here. > > - J.W. > > > _______________________________________________ > 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 Wed Feb 5 09:35:26 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Wed, 5 Feb 2014 10:35:26 +0100 Subject: [Haskell-cafe] fromString and toString In-Reply-To: References: Message-ID: Show is usually valid Haskell (at least derived instances are), and has instances for most types. This class would only be a conversion from types that *are* strings in some sense (like Text) to String. We have a (very small) package for this called 'isstring' that we use internally. It has instances for String, Text (x2) and ByteString (x2) assuming UTF8 encoding. I'd be happy to open source it if people are interested. Regards, Erik On Wed, Feb 5, 2014 at 9:13 AM, Atze van der Ploeg wrote: > Isn't toString just show? > > On Feb 4, 2014 3:20 PM, "Johannes Waldmann" > wrote: >> >> Ben Foppa gmail.com> writes: >> >> > But do we have an inverse generic function toString defined anywhere? >> >> well, we have: class Show a where show :: a -> String >> >> > likereString :: (IsString a, IsString b) => a -> b >> >> well you probably don't want to actually convert from a to String >> (= List of Char) then from there to b, >> so it would need to be accompanied by some RULES >> (for specific instances of a, b) for efficiency. >> >> This still does not answer the concern whether it is >> (semantically) wise to have String as the "base" concept here. >> >> - J.W. >> >> >> _______________________________________________ >> 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 bjarkigeirbenediktsson at gmail.com Wed Feb 5 10:00:07 2014 From: bjarkigeirbenediktsson at gmail.com (Bjarki Geir Benediktsson) Date: Wed, 5 Feb 2014 10:00:07 +0000 Subject: [Haskell-cafe] Google Summer of Code 2014 project suggestion Message-ID: Hi I have a suggestion for a project for Google Summer of Code 2014 Currently Cabal-Install is not a fully featured package manager and can be improved considerably by adding package management features to it. Features that could be implemented include: Interaction with ghc-pkg to be able to modify (upgrade/downgrade) or remove packages Support for having multiple versions of the same package installed Automatic installation of build tools when needed (Alex, Happy) this is not an exhaustive list of what could be added to make Cabal-Install behave more like a package manager and it could be extended to interact with system package manager where available Do you agree this would be a good project for GSoC 2014 ? Do you think some important features have been overlooked ? Do you think it would be better to write a replacement for Cabal-Install from scratch rather than extending it? I would appreciate feedback. Regards Bjarki Geir Benediktsson -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Wed Feb 5 11:23:38 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 13:23:38 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions Message-ID: <20140205112338.GA5055@sniper> It is often useful to distinguish between synchronous and asynchronous exceptions. The common idiom is to run a user-supplied computation catching any synchronous exceptions but allowing asynchronous exceptions (such as user interrupt) pass through. base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that solves this problem. asynchronous-exceptions is a new package that serves two purposes: * provide compatibility with older `base` versions that lack the `SomeAsyncException` type * define convenient functions for catching only synchronous exceptions Roman -------------- 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 Wed Feb 5 11:28:01 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 13:28:01 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205112338.GA5055@sniper> References: <20140205112338.GA5055@sniper> Message-ID: <20140205112801.GA5306@sniper> The links are: http://hackage.haskell.org/package/asynchronous-exceptions https://github.com/feuerbach/asynchronous-exceptions * Roman Cheplyaka [2014-02-05 13:23:38+0200] > It is often useful to distinguish between synchronous and asynchronous > exceptions. The common idiom is to run a user-supplied computation > catching any synchronous exceptions but allowing asynchronous exceptions > (such as user interrupt) pass through. > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > solves this problem. > > asynchronous-exceptions is a new package that serves two purposes: > * provide compatibility with older `base` versions that lack the > `SomeAsyncException` type > * define convenient functions for catching only synchronous exceptions > > Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From mail at nh2.me Wed Feb 5 12:19:24 2014 From: mail at nh2.me (=?ISO-8859-1?Q?Niklas_Hamb=FCchen?=) Date: Wed, 05 Feb 2014 12:19:24 +0000 Subject: [Haskell-cafe] fromString and toString In-Reply-To: References: Message-ID: <52F22C4C.4020408@nh2.me> On 05/02/14 09:35, Erik Hesselink wrote: > Show is usually valid Haskell (at least derived instances are), and > has instances for most types. This class would only be a conversion > from types that *are* strings in some sense (like Text) to String. Totally agree. On 05/02/14 08:13, Atze van der Ploeg wrote: > Isn't toString just show? No, show is very different: show "hello" == "\"hello\"" While you would expect toString "hello" == "hello" Personally, I would always recommend this: * Make show represent the "programmer version" of your data type, e.g. close to what "deriving Show" would give you, and implement it for every data type: newtype MyString = MyS String instance Show MyString where show (MyS s) = "MyS " ++ show s * Use a different type class (e.g. a ToString) to represent the stringyness of your type: instance ToString MyString where show (MyS s) = s >From my experience, everything else makes programming really nasty, outcomes unpredictable, and debugging very hard. If you want an example, try GHC code / the GHC API, where many things unfortunately do not have a show instance. > We have a (very small) package for this called 'isstring' that we use > internally. It has instances for String, Text (x2) and ByteString (x2) > assuming UTF8 encoding. I'd be happy to open source it if people are > interested. Yes. And I think a `ToString` typeclass would be useful be in base. Also, this existed once but is now deprecate it: http://hackage.haskell.org/package/to-string-class I speculate that it got deprecated because it is not nice to maintain all the orphan instances - the class in base would fix that. From mail at eax.me Wed Feb 5 12:37:18 2014 From: mail at eax.me (Alexander Alexeev) Date: Wed, 5 Feb 2014 16:37:18 +0400 Subject: [Haskell-cafe] Is it possible to declare assignment operators in Haskell? Message-ID: <20140205163718.188430a0@portege> Hello! I'm wondering, is there any way to declare assignment operators in Haskell? For example, strict assignment operators: x .= y -- equals: let x = y `deepseq` y x := y -- equals: x <- y `deepseq` y As far as I can tell, Template Haskell is not able to do anything like this, because I can't event quote expressions like `let x = y` or `x <- y`. Is there any other way (plugin for GHC, etc)? Or maybe I'm doing something wrong and TH is quite able to handle this task? I'm pretty sure that I could use a preprocessor, but I wonted to find a better solution. -- Best regards, Alexander Alexeev http://eax.me/ From benjamin.foppa at gmail.com Wed Feb 5 12:42:25 2014 From: benjamin.foppa at gmail.com (Ben Foppa) Date: Wed, 5 Feb 2014 07:42:25 -0500 Subject: [Haskell-cafe] fromString and toString In-Reply-To: <52F22C4C.4020408@nh2.me> References: <52F22C4C.4020408@nh2.me> Message-ID: I agree that exposing the isstring package would be useful. Again, I think the name IsString for the class defining fromString is very misleading, especially if we have an isstring package defining the inverse relationship (i.e. toString). More appropriate would be StringIs, though I'm not recommending changing Data.String. -------------- next part -------------- An HTML attachment was scrubbed... URL: From atze at uu.nl Wed Feb 5 13:11:15 2014 From: atze at uu.nl (Atze Dijkstra) Date: Wed, 5 Feb 2014 14:11:15 +0100 Subject: [Haskell-cafe] ANNOUNCE: Applied Functional Programming (AFP) Summerschool 7-18 July 2014, Utrecht, Netherlands Message-ID: <5200A904-46F6-4E26-8568-71E51232FD47@uu.nl> =========== AFP Summerschool 2014 =========== Applied Functional Programming (AFP) Summerschool July 7-18, 2014 Utrecht University, Department of Information and Computing Sciences Utrecht, The Netherlands Summerschool & registration website: http://www.utrechtsummerschool.nl/courses/science/applied-functional-programming-in-haskell AFP website with edition 2013 info : http://www.cs.uu.nl/wiki/USCS contact : Uscs-afp at lists.science.uu.nl *** The 2014 edition of the Applied Functional Programming (AFP) Summerschool in Utrecht, Netherlands will be held from 7-18 July 2014. The summerschool teaches Haskell on both beginners and advanced levels via lectures and lab exercises. More info can be found via the references above, included here is an excerpt from the summerschool website: ``Typed functional programming in Haskell allows for the development of compact programs in minimal time and with maximal guarantees about robustness and correctness. The course introduces Haskell as well as its theoretical underpinnings such as typed lambda calculus, and Damas-Milner type inference. There is ample opportunity to put this all in practice during lab sessions. Typed functional programming languages allow for the development of robust, concise programs in a short amount of time. The key advantages are higher-order functions as an abstraction mechanism, and an advanced type system for safety and reusability. This course introduces Haskell, a state-of-the-art functional programming language, together with some of its theoretical background, such as typed lambda calculi, referential transparency, Damas-Milner type inference, type level programming, and functional design patterns. We will combine this with applications of functional programming, concentrating on topics such as language processing, building graphical user interfaces, networking, databases, and programming for the web. The goal of the course is not just to teach the programming language and underlying theory, but also to learn about the Haskell community and to get hands-on experience by doing lab exercises or a Haskell project of your own.'' *** regards, - Atze - Atze Dijkstra, Department of Information and Computing Sciences. /|\ Utrecht University, PO Box 80089, 3508 TB Utrecht, Netherlands. / | \ Tel.: +31-30-2534118/1454 | WWW : http://www.cs.uu.nl/~atze . /--| \ Fax : +31-30-2513971 .... | Email: atze at uu.nl ............... / |___\ From mail at joachim-breitner.de Wed Feb 5 13:47:30 2014 From: mail at joachim-breitner.de (Joachim Breitner) Date: Wed, 05 Feb 2014 13:47:30 +0000 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205112338.GA5055@sniper> References: <20140205112338.GA5055@sniper> Message-ID: <1391608050.2550.5.camel@kirk> Hi, I?m playing the ?do we really need more packages with <10 symbols? card again: Am Mittwoch, den 05.02.2014, 13:23 +0200 schrieb Roman Cheplyaka: > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > solves this problem. > > asynchronous-exceptions is a new package that serves two purposes: > * provide compatibility with older `base` versions that lack the > `SomeAsyncException` type isn?t that better done in base-compat, which provides exactly that: The scope of base-compat is to provides the same functionality as the latest version of base for a wider range of compilers. > * define convenient functions for catching only synchronous exceptions If they are convenient, maybe they should go into base? (I don?t mind such micro-packages if they are a vehicle for design space exploration and experiments, but I do think we should avoid too many packages aimed for general, stable, real-world-use if we can help it.) 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 roma at ro-che.info Wed Feb 5 14:35:04 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 16:35:04 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <1391608050.2550.5.camel@kirk> References: <20140205112338.GA5055@sniper> <1391608050.2550.5.camel@kirk> Message-ID: <20140205143504.GA7497@sniper> * Joachim Breitner [2014-02-05 13:47:30+0000] > Hi, > > I?m playing the ?do we really need more packages with <10 symbols? card > again: "We"? This is about the time I stop pretending that there are any "we" with identical interests. "We" consist of many individuals, each one with his/her own agenda. Every decision is associated with different costs and benefits for each agent. In this case, the cost for me is very low (a couple of hours or less) and the benefit is huge ? the package does exactly what I need it to do. The alternative you propose below is very costly (time spent arguing for the changes and waiting for them to be applied), and the benefit is the same at best. Of course, if you persuade me that my decision bears significant cost for others, I'll be a nice guy and cooperate (esp. if others are willing to put some effort, too, because it's them who the alternative decision will presumably benefit). But so far this cost is not obvious to me at all. Furthermore, *assuming* there is indeed cost to others, they can improve the situation directly. Indeed, I already did at least some part of the job (wrote the code that can be directly copied to the packages you mention). Why don't others do the second part of the job, that they like to say is almost trivial, and put their time and effort where their mouth is? > Am Mittwoch, den 05.02.2014, 13:23 +0200 schrieb Roman Cheplyaka: > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > > solves this problem. > > > > asynchronous-exceptions is a new package that serves two purposes: > > * provide compatibility with older `base` versions that lack the > > `SomeAsyncException` type > > isn?t that better done in base-compat, which provides exactly that: > The scope of base-compat is to provides the same functionality > as the latest version of base for a wider range of compilers. > > > * define convenient functions for catching only synchronous exceptions > > If they are convenient, maybe they should go into base? > > (I don?t mind such micro-packages if they are a vehicle for design space > exploration and experiments, but I do think we should avoid too many > packages aimed for general, stable, real-world-use if we can help it.) > > > Greetings, > Joachim -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From edskodevries at gmail.com Wed Feb 5 14:43:06 2014 From: edskodevries at gmail.com (Edsko de Vries) Date: Wed, 5 Feb 2014 14:43:06 +0000 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205112338.GA5055@sniper> References: <20140205112338.GA5055@sniper> Message-ID: Be aware that "passing through" of asynchronous exceptions is not really possible. There simply is no way to selectively catch an exception -- one must always catch and rethrow, thus turning asynchronous exceptions into synchronous exceptions. See http://www.edsko.net/2013/06/11/throwto/ for details. Edsko On Wed, Feb 5, 2014 at 11:23 AM, Roman Cheplyaka wrote: > It is often useful to distinguish between synchronous and asynchronous > exceptions. The common idiom is to run a user-supplied computation > catching any synchronous exceptions but allowing asynchronous exceptions > (such as user interrupt) pass through. > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > solves this problem. > > asynchronous-exceptions is a new package that serves two purposes: > * provide compatibility with older `base` versions that lack the > `SomeAsyncException` type > * define convenient functions for catching only synchronous exceptions > > 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 creswick at gmail.com Wed Feb 5 14:50:07 2014 From: creswick at gmail.com (Rogan Creswick) Date: Wed, 5 Feb 2014 06:50:07 -0800 Subject: [Haskell-cafe] Google Summer of Code 2014 project suggestion In-Reply-To: References: Message-ID: On Wed, Feb 5, 2014 at 2:00 AM, Bjarki Geir Benediktsson < bjarkigeirbenediktsson at gmail.com> wrote: > Hi > I have a suggestion for a project for Google Summer of Code 2014 > > > Currently Cabal-Install is not a fully featured package manager and can be > improved considerably by adding package management features to it. > > Features that could be implemented include: > Interaction with ghc-pkg to be able to modify (upgrade/downgrade) or > remove packages > This would be handy -- ghc-pkg / cabal sandbox hc-pkg help a lot here already, though, and aren't so bad to use. It would be nice, though. Support for having multiple versions of the same package installed > I think there is a good bit of on-going work to support multiple versions of one package in the same package db, and it's significantly less of an issue with sandboxes. My understanding is that this is significantly more challenging than it seems. > Automatic installation of build tools when needed (Alex, Happy) > Rather than implement tool installation directly, my preference would be to solve this first: https://github.com/haskell/cabal/issues/948 Then, once setup.hs has specific dependencies, write a simple EDSL / library that makes it trivial to conditionally install tool dependencies from within a custom build script. I think the result would be much more generally applicable, and solve a number of other issues along the way. It would also make it possible for anyone to prototype new cabal/cabal-install features without needing to distribute a new version of cabal/cabal-install. --Rogan -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Wed Feb 5 14:56:31 2014 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 5 Feb 2014 16:56:31 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205112801.GA5306@sniper> References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> Message-ID: I don't think this package works as expected. Consider the following: import Control.Concurrent import Control.Exception.Async import System.Timeout main :: IO () main = do timeout 1000000 $ do threadDelay 10000000 `catchSync` \e -> do print e threadDelay 10000000 return () The expected behavior would be that the timeout- an async exception- would kill the thread delay, the catch would ignore the async exception, and the program would exit. In reality, catchSync treats the timeout as a synchronous exception, prints it, and delays once again. Compare this to classy-prelude's catchAny, which handles the situation correctly, via the technique I described in "Catching all exceptions."[1] In this case, the issue is that the timeout exception type is not recognized as async, and a special case could be added to handle that exception type[2]. However, I think the overall approach of determining *how* an exception was thrown based on *what* was thrown is not tenable. [1] https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions [2] It's a bit difficult to do so, since IIRC the type is never exported. But a hack using the Typeable instance- while ugly- is likely possible. On Wed, Feb 5, 2014 at 1:28 PM, Roman Cheplyaka wrote: > The links are: > > http://hackage.haskell.org/package/asynchronous-exceptions > https://github.com/feuerbach/asynchronous-exceptions > > * Roman Cheplyaka [2014-02-05 13:23:38+0200] > > It is often useful to distinguish between synchronous and asynchronous > > exceptions. The common idiom is to run a user-supplied computation > > catching any synchronous exceptions but allowing asynchronous exceptions > > (such as user interrupt) pass through. > > > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > > solves this problem. > > > > asynchronous-exceptions is a new package that serves two purposes: > > * provide compatibility with older `base` versions that lack the > > `SomeAsyncException` type > > * define convenient functions for catching only synchronous exceptions > > > > 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 roma at ro-che.info Wed Feb 5 15:19:26 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 17:19:26 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> Message-ID: <20140205151926.GA9254@sniper> It works as expected. With GHC 7.8 it doesn't print the timeout exception. With earlier GHC it does (again, as expected, because the timeout exception isn't marked as asynchronous). In practice one should rarely want to use System.Timeout anyway (because of the overflow issue), and I'm going to patch one of the better timeout packages (such as unbounded-delays) to support asynchronous-exceptions. * Michael Snoyman [2014-02-05 16:56:31+0200] > I don't think this package works as expected. Consider the following: > > import Control.Concurrent > import Control.Exception.Async > import System.Timeout > > main :: IO () > main = do > timeout 1000000 $ do > threadDelay 10000000 `catchSync` \e -> do > print e > threadDelay 10000000 > return () > > The expected behavior would be that the timeout- an async exception- would > kill the thread delay, the catch would ignore the async exception, and the > program would exit. In reality, catchSync treats the timeout as a > synchronous exception, prints it, and delays once again. Compare this to > classy-prelude's catchAny, which handles the situation correctly, via the > technique I described in "Catching all exceptions."[1] > > In this case, the issue is that the timeout exception type is not > recognized as async, and a special case could be added to handle that > exception type[2]. However, I think the overall approach of determining > *how* an exception was thrown based on *what* was thrown is not tenable. > > [1] > https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions > [2] It's a bit difficult to do so, since IIRC the type is never exported. > But a hack using the Typeable instance- while ugly- is likely possible. > > > On Wed, Feb 5, 2014 at 1:28 PM, Roman Cheplyaka wrote: > > > The links are: > > > > http://hackage.haskell.org/package/asynchronous-exceptions > > https://github.com/feuerbach/asynchronous-exceptions > > > > * Roman Cheplyaka [2014-02-05 13:23:38+0200] > > > It is often useful to distinguish between synchronous and asynchronous > > > exceptions. The common idiom is to run a user-supplied computation > > > catching any synchronous exceptions but allowing asynchronous exceptions > > > (such as user interrupt) pass through. > > > > > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > > > solves this problem. > > > > > > asynchronous-exceptions is a new package that serves two purposes: > > > * provide compatibility with older `base` versions that lack the > > > `SomeAsyncException` type > > > * define convenient functions for catching only synchronous exceptions > > > > > > Roman > > > > _______________________________________________ > > 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 jmacristovao at gmail.com Wed Feb 5 15:53:34 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Wed, 5 Feb 2014 15:53:34 +0000 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205151926.GA9254@sniper> References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> Message-ID: Hi Roman, One other question: in Michael's article, he also mentions the possibility of: "Consider that, for some strange reason, we decided to asynchronously throw an IOException to a worker thread" Meaning that you can throwTo any exception asynchronouly, even if it is not a SomeAsyncException. At least from what I gathered from (GHC Head) throwTo code, this does not seem to be a restriction. Thus, your module will work for any well behaved code that does the right thing, and respects the SomeAsyncException superclass, but not for other spurious asynchronous exceptions, right? I'm just trying to frame the possible use cases of your library. Thanks Joao 2014-02-05 Roman Cheplyaka : > It works as expected. > > With GHC 7.8 it doesn't print the timeout exception. > > With earlier GHC it does (again, as expected, because the timeout > exception isn't marked as asynchronous). In practice one should rarely > want to use System.Timeout anyway (because of the overflow issue), and > I'm going to patch one of the better timeout packages (such as > unbounded-delays) to support asynchronous-exceptions. > > * Michael Snoyman [2014-02-05 16:56:31+0200] >> I don't think this package works as expected. Consider the following: >> >> import Control.Concurrent >> import Control.Exception.Async >> import System.Timeout >> >> main :: IO () >> main = do >> timeout 1000000 $ do >> threadDelay 10000000 `catchSync` \e -> do >> print e >> threadDelay 10000000 >> return () >> >> The expected behavior would be that the timeout- an async exception- would >> kill the thread delay, the catch would ignore the async exception, and the >> program would exit. In reality, catchSync treats the timeout as a >> synchronous exception, prints it, and delays once again. Compare this to >> classy-prelude's catchAny, which handles the situation correctly, via the >> technique I described in "Catching all exceptions."[1] >> >> In this case, the issue is that the timeout exception type is not >> recognized as async, and a special case could be added to handle that >> exception type[2]. However, I think the overall approach of determining >> *how* an exception was thrown based on *what* was thrown is not tenable. >> >> [1] >> https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions >> [2] It's a bit difficult to do so, since IIRC the type is never exported. >> But a hack using the Typeable instance- while ugly- is likely possible. >> >> >> On Wed, Feb 5, 2014 at 1:28 PM, Roman Cheplyaka wrote: >> >> > The links are: >> > >> > http://hackage.haskell.org/package/asynchronous-exceptions >> > https://github.com/feuerbach/asynchronous-exceptions >> > >> > * Roman Cheplyaka [2014-02-05 13:23:38+0200] >> > > It is often useful to distinguish between synchronous and asynchronous >> > > exceptions. The common idiom is to run a user-supplied computation >> > > catching any synchronous exceptions but allowing asynchronous exceptions >> > > (such as user interrupt) pass through. >> > > >> > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that >> > > solves this problem. >> > > >> > > asynchronous-exceptions is a new package that serves two purposes: >> > > * provide compatibility with older `base` versions that lack the >> > > `SomeAsyncException` type >> > > * define convenient functions for catching only synchronous exceptions >> > > >> > > 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 > From michael at snoyman.com Wed Feb 5 15:55:10 2014 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 5 Feb 2014 17:55:10 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205151926.GA9254@sniper> References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> Message-ID: So you're saying that it's expected behavior for the shim library you're providing to have drastically different behavior between different versions of GHC? I don't think that's a good idea at all. In any event, this approach is still predicated on the idea that you can identify an asynchronous event from its type. There are multiple problems with this: * As demonstrated with my previous example, not all asynchronous exceptions identify themselves as such. * There is no requirement that only asynchronous-type exceptions be thrown asynchronously. throwTo works with any instance of Exception. * If an asynchronous-type exception is caught and then rethrown as a synchronous exception, the type-based approach will still treat it as asynchronous, though it should be recognized as synchronous at that point. To demonstrate that last point, consider the example code below, which uses your asynchronous type machinery and the async package. The usage of `trySync` in `main` *should* catch that exception, since it is no longer asynchronous, but a type-only approach cannot handle that situation. ClassyPrelude's tryAny, on the other hand, gives the correct output. {-# LANGUAGE DeriveDataTypeable #-} import Control.Exception.Async import Control.Concurrent.Async import Control.Concurrent import Control.Exception import Data.Unique import Data.Typeable data Timeout = Timeout deriving (Typeable, Eq) instance Show Timeout where show _ = "Async Timeout" instance Exception Timeout where fromException = asyncExceptionFromException toException = asyncExceptionToException asyncTimeout n f = do pid <- myThreadId killer <- forkIO $ do threadDelay n throwTo pid Timeout res <- f killThread pid return res main :: IO () main = do res <- trySync f print res f :: IO String f = do x <- async $ asyncTimeout 1000000 $ do threadDelay 2000000 return "Finished" wait x On Wed, Feb 5, 2014 at 5:19 PM, Roman Cheplyaka wrote: > It works as expected. > > With GHC 7.8 it doesn't print the timeout exception. > > With earlier GHC it does (again, as expected, because the timeout > exception isn't marked as asynchronous). In practice one should rarely > want to use System.Timeout anyway (because of the overflow issue), and > I'm going to patch one of the better timeout packages (such as > unbounded-delays) to support asynchronous-exceptions. > > * Michael Snoyman [2014-02-05 16:56:31+0200] > > I don't think this package works as expected. Consider the following: > > > > import Control.Concurrent > > import Control.Exception.Async > > import System.Timeout > > > > main :: IO () > > main = do > > timeout 1000000 $ do > > threadDelay 10000000 `catchSync` \e -> do > > print e > > threadDelay 10000000 > > return () > > > > The expected behavior would be that the timeout- an async exception- > would > > kill the thread delay, the catch would ignore the async exception, and > the > > program would exit. In reality, catchSync treats the timeout as a > > synchronous exception, prints it, and delays once again. Compare this to > > classy-prelude's catchAny, which handles the situation correctly, via the > > technique I described in "Catching all exceptions."[1] > > > > In this case, the issue is that the timeout exception type is not > > recognized as async, and a special case could be added to handle that > > exception type[2]. However, I think the overall approach of determining > > *how* an exception was thrown based on *what* was thrown is not tenable. > > > > [1] > > > https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions > > [2] It's a bit difficult to do so, since IIRC the type is never exported. > > But a hack using the Typeable instance- while ugly- is likely possible. > > > > > > On Wed, Feb 5, 2014 at 1:28 PM, Roman Cheplyaka > wrote: > > > > > The links are: > > > > > > http://hackage.haskell.org/package/asynchronous-exceptions > > > https://github.com/feuerbach/asynchronous-exceptions > > > > > > * Roman Cheplyaka [2014-02-05 13:23:38+0200] > > > > It is often useful to distinguish between synchronous and > asynchronous > > > > exceptions. The common idiom is to run a user-supplied computation > > > > catching any synchronous exceptions but allowing asynchronous > exceptions > > > > (such as user interrupt) pass through. > > > > > > > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type > that > > > > solves this problem. > > > > > > > > asynchronous-exceptions is a new package that serves two purposes: > > > > * provide compatibility with older `base` versions that lack the > > > > `SomeAsyncException` type > > > > * define convenient functions for catching only synchronous > exceptions > > > > > > > > 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 roma at ro-che.info Wed Feb 5 16:09:19 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 18:09:19 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> Message-ID: <20140205160919.GA10049@sniper> Hi Jo?o, * Jo?o Crist?v?o [2014-02-05 15:53:34+0000] > Hi Roman, > > One other question: in Michael's article, he also mentions the possibility of: > "Consider that, for some strange reason, we decided to asynchronously > throw an IOException to a worker thread" > > Meaning that you can throwTo any exception asynchronouly, even if it > is not a SomeAsyncException. At least from what I gathered from (GHC > Head) throwTo code, this does not seem to be a restriction. > > Thus, your module will work for any well behaved code that does the > right thing, and respects the SomeAsyncException superclass, but not > for other spurious asynchronous exceptions, right? Precisely. > I'm just trying to frame the possible use cases of your library. > Thanks > Joao > > 2014-02-05 Roman Cheplyaka : > > It works as expected. > > > > With GHC 7.8 it doesn't print the timeout exception. > > > > With earlier GHC it does (again, as expected, because the timeout > > exception isn't marked as asynchronous). In practice one should rarely > > want to use System.Timeout anyway (because of the overflow issue), and > > I'm going to patch one of the better timeout packages (such as > > unbounded-delays) to support asynchronous-exceptions. > > > > * Michael Snoyman [2014-02-05 16:56:31+0200] > >> I don't think this package works as expected. Consider the following: > >> > >> import Control.Concurrent > >> import Control.Exception.Async > >> import System.Timeout > >> > >> main :: IO () > >> main = do > >> timeout 1000000 $ do > >> threadDelay 10000000 `catchSync` \e -> do > >> print e > >> threadDelay 10000000 > >> return () > >> > >> The expected behavior would be that the timeout- an async exception- would > >> kill the thread delay, the catch would ignore the async exception, and the > >> program would exit. In reality, catchSync treats the timeout as a > >> synchronous exception, prints it, and delays once again. Compare this to > >> classy-prelude's catchAny, which handles the situation correctly, via the > >> technique I described in "Catching all exceptions."[1] > >> > >> In this case, the issue is that the timeout exception type is not > >> recognized as async, and a special case could be added to handle that > >> exception type[2]. However, I think the overall approach of determining > >> *how* an exception was thrown based on *what* was thrown is not tenable. > >> > >> [1] > >> https://www.fpcomplete.com/user/snoyberg/general-haskell/exceptions/catching-all-exceptions > >> [2] It's a bit difficult to do so, since IIRC the type is never exported. > >> But a hack using the Typeable instance- while ugly- is likely possible. > >> > >> > >> On Wed, Feb 5, 2014 at 1:28 PM, Roman Cheplyaka wrote: > >> > >> > The links are: > >> > > >> > http://hackage.haskell.org/package/asynchronous-exceptions > >> > https://github.com/feuerbach/asynchronous-exceptions > >> > > >> > * Roman Cheplyaka [2014-02-05 13:23:38+0200] > >> > > It is often useful to distinguish between synchronous and asynchronous > >> > > exceptions. The common idiom is to run a user-supplied computation > >> > > catching any synchronous exceptions but allowing asynchronous exceptions > >> > > (such as user interrupt) pass through. > >> > > > >> > > base 4.7 (shipped with GHC 7.8) will have SomeAsyncException type that > >> > > solves this problem. > >> > > > >> > > asynchronous-exceptions is a new package that serves two purposes: > >> > > * provide compatibility with older `base` versions that lack the > >> > > `SomeAsyncException` type > >> > > * define convenient functions for catching only synchronous exceptions > >> > > > >> > > 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: 819 bytes Desc: Digital signature URL: From roma at ro-che.info Wed Feb 5 16:28:49 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 18:28:49 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> Message-ID: <20140205162849.GC10049@sniper> * Michael Snoyman [2014-02-05 17:55:10+0200] > * If an asynchronous-type exception is caught and then rethrown as a > synchronous exception, the type-based approach will still treat it as > asynchronous, though it should be recognized as synchronous at that point. I say it shouldn't. I usually don't care by what means an exception was thrown. I care that exceptions that are meant to be thrown asynchronously (that is: they do not originate from the currently executing code in the current thread, but are some indication of an outside event) are not treated the same as exceptions that arise from the code in the current thread. Example: {-# LANGUAGE ScopedTypeVariables #-} import System.Timeout import Control.Concurrent import Control.Exception import Control.Exception.Async main = do timeout (10^5) $ (threadDelay (10^6) `catch` (\(_ :: IOException) -> print 1)) `catchSync` (\_ -> print 2) I don't expect any of the exception handlers here to fire because threadDelay doesn't throw any exceptions. This is my intention. The fact that, as Edsko points out, exception are re-thrown synchronously, is a subtle technicality and I don't want to care about it. Remember that threadDelay (10^6) `catch` (\(_ :: IOException) -> print 1) sits somewhere deep inside a user-supplied action. Thus, the semantics of my clear-intentioned code timeout (10^5) $ userAction `catchSync` (\_ -> print 2) in the approach you advocate would depend on whether, somewhere deep inside a library used by the user action, any exceptions are caught. This is not compositional nor useful. 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 Wed Feb 5 16:48:22 2014 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 5 Feb 2014 18:48:22 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205162849.GC10049@sniper> References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> Message-ID: On Wed, Feb 5, 2014 at 6:28 PM, Roman Cheplyaka wrote: > * Michael Snoyman [2014-02-05 17:55:10+0200] > > * If an asynchronous-type exception is caught and then rethrown as a > > synchronous exception, the type-based approach will still treat it as > > asynchronous, though it should be recognized as synchronous at that > point. > > I say it shouldn't. I usually don't care by what means an exception was > thrown. I care that exceptions that are meant to be thrown > asynchronously (that is: they do not originate from the currently > executing code in the current thread, but are some indication of an > outside event) are not treated the same as exceptions that arise from > the code in the current thread. > > Example: > > {-# LANGUAGE ScopedTypeVariables #-} > import System.Timeout > import Control.Concurrent > import Control.Exception > import Control.Exception.Async > > main = do > timeout (10^5) $ > (threadDelay (10^6) `catch` (\(_ :: IOException) -> print 1)) > `catchSync` (\_ -> print 2) > > I don't expect any of the exception handlers here to fire because > threadDelay doesn't throw any exceptions. This is my intention. The fact > And just to point out yet again: the second exception handler *does* fire in GHC 7.6 and earlier. > that, as Edsko points out, exception are re-thrown synchronously, is a > subtle technicality and I don't want to care about it. Remember that > > threadDelay (10^6) `catch` (\(_ :: IOException) -> print 1) > > sits somewhere deep inside a user-supplied action. Thus, the semantics > of my clear-intentioned code > > timeout (10^5) $ userAction `catchSync` (\_ -> print 2) > > in the approach you advocate would depend on whether, somewhere deep > inside a library used by the user action, any exceptions are caught. > This is not compositional nor useful. > > Roman > I can't think of any situation in which the semantics you're implying make sense. To me, catching synchronous exception is a simple concept: if an exception is generated internally to `userAction`, then it's a synchronous exception. If it was terminated by something external, then it's asynchronous. I'm not sure what you're getting at about my approach requiring knowledge of what's going on deep inside a library. The real question which is not explained in your package is what use case you're actually trying to address. Here's a prime example I've run into: you're writing a web application which uses a third-party library. If that library throws an exception of any type, you want to catch the exception and display an appropriate error message (or perhaps return some data from another source). However, we still want the web application to respect timeout messages from the server to avoid slowloris attacks. The handler code would look like: myHandler = do eres <- tryAnyDeep someLibraryFunction case eres of Left e -> tellUser "I'm sorry, there was an issue making the query" Right x -> displayData x The goal is that, under no circumstances, should someLibraryFunction be able to case the exception to escape tryAnyDeep. This includes rethrowing some async exception that it received from, e.g., a timeout. This would not be honored by trySync. Michael -------------- next part -------------- An HTML attachment was scrubbed... URL: From ollie at ocharles.org.uk Wed Feb 5 17:26:38 2014 From: ollie at ocharles.org.uk (Oliver Charles) Date: Wed, 05 Feb 2014 17:26:38 +0000 Subject: [Haskell-cafe] Announcing Haskell bindings to libsystemd-journal Message-ID: <87iost1ne9.fsf@nixos.i-did-not-set--mail-host-address--so-tickle-me> Hi all, Just a brief announcement - I've just released Haskell bindings to libsystemd-journal, the systemd library for writing directly to the journal. I've tried to be moderately type safe without giving up flexibility or ease of use. The documentation is at: http://hackage.haskell.org/package/libsystemd-journal-1.0.0/docs/Systemd-Journal.html Note that some of the hyperlinks on this page don't work, and I can't be bothered fighting with Hackage to make them work. Sorry! If you need that, just install the library and you can read documentation locally. To install this library, you'll need libsystemd-journal (which you probably have if you're reading this) and then you can just run: cabal install libsystemd-journal Happy logging! - ocharles From david.sorokin at gmail.com Wed Feb 5 17:44:54 2014 From: david.sorokin at gmail.com (David Sorokin) Date: Wed, 5 Feb 2014 21:44:54 +0400 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> Message-ID: Hi! Please let me add two cents to your discussion. Just for your information. There is a working approach, when the exceptions can be indeed successfully caught within the asynchronous computation. Moreover, there is also the working try-finally block, which is more difficult to implement. This is the async workflow in F# and their Async type is actually a monad. Only they use the continuations, namely three continuations: (1) the main branch; (2) the branch for catching exceptions; (3) the branch for immediate canceling the computation. They have no special ?asynchronous? exceptions that would differ from synchronous ones. By the way, I have implemented a similar approach in my library aivika available on hackage (module Simulation.Aivika.Internal.Cont). I can catch the IO exceptions as well as I can process so called the finally blocks, and my own tests show that it works in Haskell. Thanks, David From hesselink at gmail.com Wed Feb 5 19:34:40 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Wed, 5 Feb 2014 20:34:40 +0100 Subject: [Haskell-cafe] problem with happy and type identity In-Reply-To: <20140202213219.GA238@ridcully.local> References: <20140202213219.GA238@ridcully.local> Message-ID: To be able to share code between your library and your tests, you should either * Have a separate directory for the library sources and the test sources. For example, put Ast.hs and Parser.y in 'src' and put 'Hs-source-dirs: src' in the library section. Put RunTests.hs in 'tests', and put 'Hs-source-dirs: tests' in the test-suite section. This is the preferred way. * Alternatively, don't specify 'sample' as a build-depends in the test-suite. Note that this will mean that Ast and Parser will get compiled twice. Right now, cabal somehow mixes types from the files compiled as part of the test suite with types imported from the library. Regards, Erik On Sun, Feb 2, 2014 at 10:32 PM, Richard Cobbe wrote: > I'm working on a small project that involves an Alex scanner and a Happy > parser, and I'm getting an error from the type-checker that I do not > understand. Can anyone help shed some light on what's going on? > > I'm running Haskell Platform 2013.2.0.0, on MacOS 10.8.5 with XCode 4.6.3. > > I've reduced the problem to a very small example, which I've attached as a > tar file. It's a cabal package, and it contains a library with some test > cases. > > If I run "cabal configure && cabal build" then the library builds with no > problems whatsoever. > > But if I run > > cabal clean && cabal configure --enable-tests && cabal build > > then I get the following error message: > > RunTests.hs:16:27: > Couldn't match expected type `sample-0.4:Ast.Entry' > with actual type `Entry' > In the return type of a call of `Entry' > In the second argument of `(~?=)', namely `Entry "mumble"' > In the expression: parse "entry" ~?= Entry "mumble" > > And this doesn't make any sense to me, because the two types are supposed > to be the same. > > If I take Happy and Alex out of the picture by replacing the Parser module > with a hand-written parser, the error goes away. This is hardly feasible > in the actual project, of course :-) so I'm hoping someone can shed some > light on what I'm doing wrong here. > > Thanks! > > Richard > > (I apologize for the attachment, by the way, but since filesystem layout is > potentially important here, and since it's only slightly larger than 1K, I > figured it was the best way. If there's a better way to do this in the > future (which doesn't assume I can throw it on the web somewhere), then I'd > love to hear about it.) > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From roma at ro-che.info Wed Feb 5 21:23:08 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 5 Feb 2014 23:23:08 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> Message-ID: <20140205212308.GA12415@sniper> Ok, this clears things up. I misinterpreted your approach thinking that you're also solving the problem of distinguishing async vs sync exceptions, only based on how they were thrown instead of their type. I now see that it isn't the case ? you're catching *all* exceptions. (And run the timeout handler in a different thread.) So no wonder that asynchronous-exceptions (whose description says that it lets differentiate between sync and async exceptions, in a certain sense) doesn't help you ? you simply don't want any exceptions at all. My use case is simpler ? I write testing libraries. If a test throws an exception, we have to decide whether we want to report it as a test's failure or it's a bigger problem and we want to wrap up. I don't think there's a universally right way to make this decision. It depends on what exceptions exist and what threads they can be thrown to. E.g. if there existed something like UserInterrupt but which could be thrown to any active thread, not only the main thread, then the approach "run in a separate thread and log any exceptions from that thread" simply wouldn't work. For tasty, based on the async exceptions I'm aware of, I think your approach is overall better. It's almost as simple, doesn't require patching 3rd-party timeout libraries, and catches StackOverflow (which is desirable). So I'll switch to it instead. For smallcheck, the overhead of forkIO might be significant, because it has to be performed for every single property check, and those can be numerous and very quick. I put together a simple benchmark (http://lpaste.net/99532 if anyone is interested) which shows that overhead can be noticable (16% for async vs 4% for simple catch) but tolerable, and it will be even less for more realistic properties. So I'll probably use the async approach there, too, although I may reconsider that in the future if I ever get to optimizing smallcheck and squeezing out those percents. As for the package itself, let's see if others will find any good use cases for it. I'll update the docs with some conclusions from this thread. And thanks for your input. Roman * Michael Snoyman [2014-02-05 18:48:22+0200] > I can't think of any situation in which the semantics you're implying make > sense. To me, catching synchronous exception is a simple concept: if an > exception is generated internally to `userAction`, then it's a synchronous > exception. If it was terminated by something external, then it's > asynchronous. I'm not sure what you're getting at about my approach > requiring knowledge of what's going on deep inside a library. > > The real question which is not explained in your package is what use case > you're actually trying to address. Here's a prime example I've run into: > you're writing a web application which uses a third-party library. If that > library throws an exception of any type, you want to catch the exception > and display an appropriate error message (or perhaps return some data from > another source). However, we still want the web application to respect > timeout messages from the server to avoid slowloris attacks. The handler > code would look like: > > myHandler = do > eres <- tryAnyDeep someLibraryFunction > case eres of > Left e -> tellUser "I'm sorry, there was an issue making the query" > Right x -> displayData x > > The goal is that, under no circumstances, should someLibraryFunction be > able to case the exception to escape tryAnyDeep. This includes rethrowing > some async exception that it received from, e.g., a timeout. This would not > be honored by trySync. > > Michael -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From headprogrammingczar at gmail.com Wed Feb 5 21:52:31 2014 From: headprogrammingczar at gmail.com (Joe Quinn) Date: Wed, 05 Feb 2014 16:52:31 -0500 Subject: [Haskell-cafe] Is it possible to declare assignment operators in Haskell? In-Reply-To: <20140205163718.188430a0@portege> References: <20140205163718.188430a0@portege> Message-ID: <52F2B29F.7070107@gmail.com> On 2/5/2014 7:37 AM, Alexander Alexeev wrote: > Hello! > > I'm wondering, is there any way to declare assignment operators > in Haskell? For example, strict assignment operators: > > x .= y -- equals: let x = y `deepseq` y > x := y -- equals: x <- y `deepseq` y > > As far as I can tell, Template Haskell is not able to do anything like > this, because I can't event quote expressions like `let x = y` or `x <- > y`. Is there any other way (plugin for GHC, etc)? Or maybe I'm doing > something wrong and TH is quite able to handle this task? > > I'm pretty sure that I could use a preprocessor, but I wonted to find > a better solution. > There are things that "act like assignment", but quite differently than what you are after, which looks like a macro of some sort. For instance, one of the OpenGL packages defines (:=) = writeIORef, to be used like spoofel depth stencil = do stencilVals <- map (> 0.35) <$> readIORef depth stencil := stencilVals What is the type of (.=) and (:=) that you desire? What is the larger problem you are trying to solve? From vogt.adam at gmail.com Wed Feb 5 22:01:30 2014 From: vogt.adam at gmail.com (adam vogt) Date: Wed, 5 Feb 2014 17:01:30 -0500 Subject: [Haskell-cafe] Is it possible to declare assignment operators in Haskell? In-Reply-To: <20140205163718.188430a0@portege> References: <20140205163718.188430a0@portege> Message-ID: Hi Alexander, You could quote the whole do-block: > $(strictify [| do y .= x; ... |]) And then strictify :: ExpQ -> ExpQ manipulates the AST a bit: x .= y does parse as an expression, so you can change a NoBindS containing that .= function into a BindS or LetS. Unfortunately the quotes built into TH complain about undefined variables, so you'll probably have to use a quasiquote instead (haskell-src-meta can help here). Also, you may want to desugar to "let !x = y `deepseq` y", or involve (return $!) since "let x = y `deepseq` y where y = undefined :: Int" only crashes when you seq the x. Adam On Wed, Feb 5, 2014 at 7:37 AM, Alexander Alexeev wrote: > Hello! > > I'm wondering, is there any way to declare assignment operators > in Haskell? For example, strict assignment operators: > > x .= y -- equals: let x = y `deepseq` y > x := y -- equals: x <- y `deepseq` y > > As far as I can tell, Template Haskell is not able to do anything like > this, because I can't event quote expressions like `let x = y` or `x <- > y`. Is there any other way (plugin for GHC, etc)? Or maybe I'm doing > something wrong and TH is quite able to handle this task? > > I'm pretty sure that I could use a preprocessor, but I wonted to find > a better solution. > > -- > 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 jmacristovao at gmail.com Wed Feb 5 22:13:19 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Wed, 5 Feb 2014 22:13:19 +0000 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205212308.GA12415@sniper> References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> Message-ID: Roman, By mere chance today I was, about the same time you published your library, working on the suggestion made by Michael in the end of his original blog post: splitting the async exceptions part from classy-prelude (he is ok with this). https://github.com/jcristovao/async-exception I was not yet sure about the namespace, I had opted for: Control.Concurrent.Async.Exception But yours makes more sense, Control.Async.Exception I agree that the two solutions address different problems, and as you say, for controlled situations where performance is critical yours indeed adds less overhead. But for more general solutions, Michael's solution - split from Classy prelude, seems to be the way to go, and thus my 'split' makes sense if you don't need the remaining classy prelude. As such, I was considering the namespace: Control.Async.Exception.All To differentiate from yours, signaling that it handles _all_ exceptions. What do you think? Anyhow, I also think Joachim suggestion (of at least implementing the new exception classes in base-compat) makes sense, so I volunteer to add to the work I already done here: https://github.com/sol/base-compat/pull/2 (If the patch gets accepted, of course). Cheers, Jo?o 2014-02-05 Roman Cheplyaka : > Ok, this clears things up. I misinterpreted your approach thinking that > you're also solving the problem of distinguishing async vs sync > exceptions, only based on how they were thrown instead of their type. > > I now see that it isn't the case -- you're catching *all* exceptions. > (And run the timeout handler in a different thread.) > > So no wonder that asynchronous-exceptions (whose description says that > it lets differentiate between sync and async exceptions, in a certain > sense) doesn't help you -- you simply don't want any exceptions at all. > > My use case is simpler -- I write testing libraries. If a test throws an > exception, we have to decide whether we want to report it as a test's > failure or it's a bigger problem and we want to wrap up. > > I don't think there's a universally right way to make this decision. It > depends on what exceptions exist and what threads they can be thrown to. > E.g. if there existed something like UserInterrupt but which could be > thrown to any active thread, not only the main thread, then the approach > "run in a separate thread and log any exceptions from that thread" > simply wouldn't work. > > For tasty, based on the async exceptions I'm aware of, I think your > approach is overall better. It's almost as simple, doesn't require > patching 3rd-party timeout libraries, and catches StackOverflow (which > is desirable). So I'll switch to it instead. > > For smallcheck, the overhead of forkIO might be significant, because it > has to be performed for every single property check, and those can be > numerous and very quick. I put together a simple benchmark > (http://lpaste.net/99532 if anyone is interested) which shows that > overhead can be noticable (16% for async vs 4% for simple catch) but > tolerable, and it will be even less for more realistic properties. > So I'll probably use the async approach there, too, although I may > reconsider that in the future if I ever get to optimizing smallcheck and > squeezing out those percents. > > As for the package itself, let's see if others will find any good use > cases for it. I'll update the docs with some conclusions from this > thread. > > And thanks for your input. > > Roman > > * Michael Snoyman [2014-02-05 18:48:22+0200] >> I can't think of any situation in which the semantics you're implying make >> sense. To me, catching synchronous exception is a simple concept: if an >> exception is generated internally to `userAction`, then it's a synchronous >> exception. If it was terminated by something external, then it's >> asynchronous. I'm not sure what you're getting at about my approach >> requiring knowledge of what's going on deep inside a library. >> >> The real question which is not explained in your package is what use case >> you're actually trying to address. Here's a prime example I've run into: >> you're writing a web application which uses a third-party library. If that >> library throws an exception of any type, you want to catch the exception >> and display an appropriate error message (or perhaps return some data from >> another source). However, we still want the web application to respect >> timeout messages from the server to avoid slowloris attacks. The handler >> code would look like: >> >> myHandler = do >> eres <- tryAnyDeep someLibraryFunction >> case eres of >> Left e -> tellUser "I'm sorry, there was an issue making the query" >> Right x -> displayData x >> >> The goal is that, under no circumstances, should someLibraryFunction be >> able to case the exception to escape tryAnyDeep. This includes rethrowing >> some async exception that it received from, e.g., a timeout. This would not >> be honored by trySync. >> >> Michael > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From roma at ro-che.info Wed Feb 5 22:33:53 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 6 Feb 2014 00:33:53 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> Message-ID: <20140205223353.GA17748@sniper> Well, since you happened to ask me (although I am as good a bikeshedder as the next person), I think that you don't need to mention Async anywhere in the module name, since the module doesn't make any attempt to differentiate between sync and async exceptions. And the fact that the module uses the 'async' library is just an implementation detail. I'd go with something like Control.Exception.CatchAny. Roman * Jo?o Crist?v?o [2014-02-05 22:13:19+0000] > Roman, > > By mere chance today I was, about the same time you published your > library, working on the suggestion made by Michael in the end of his > original blog post: splitting the async exceptions part from > classy-prelude (he is ok with this). > > https://github.com/jcristovao/async-exception > > I was not yet sure about the namespace, I had opted for: > Control.Concurrent.Async.Exception > > But yours makes more sense, > Control.Async.Exception > > I agree that the two solutions address different problems, and as you > say, for controlled situations where performance is critical yours > indeed adds less overhead. But for more general solutions, Michael's > solution - split from Classy prelude, seems to be the way to go, and > thus my 'split' makes sense if you don't need the remaining classy > prelude. > > As such, I was considering the namespace: > Control.Async.Exception.All > > To differentiate from yours, signaling that it handles _all_ exceptions. > What do you think? > > Anyhow, I also think Joachim suggestion (of at least implementing the > new exception classes in base-compat) makes sense, so I volunteer to > add to the work I already done here: > https://github.com/sol/base-compat/pull/2 > > (If the patch gets accepted, of course). > > Cheers, > Jo?o > > 2014-02-05 Roman Cheplyaka : > > Ok, this clears things up. I misinterpreted your approach thinking that > > you're also solving the problem of distinguishing async vs sync > > exceptions, only based on how they were thrown instead of their type. > > > > I now see that it isn't the case -- you're catching *all* exceptions. > > (And run the timeout handler in a different thread.) > > > > So no wonder that asynchronous-exceptions (whose description says that > > it lets differentiate between sync and async exceptions, in a certain > > sense) doesn't help you -- you simply don't want any exceptions at all. > > > > My use case is simpler -- I write testing libraries. If a test throws an > > exception, we have to decide whether we want to report it as a test's > > failure or it's a bigger problem and we want to wrap up. > > > > I don't think there's a universally right way to make this decision. It > > depends on what exceptions exist and what threads they can be thrown to. > > E.g. if there existed something like UserInterrupt but which could be > > thrown to any active thread, not only the main thread, then the approach > > "run in a separate thread and log any exceptions from that thread" > > simply wouldn't work. > > > > For tasty, based on the async exceptions I'm aware of, I think your > > approach is overall better. It's almost as simple, doesn't require > > patching 3rd-party timeout libraries, and catches StackOverflow (which > > is desirable). So I'll switch to it instead. > > > > For smallcheck, the overhead of forkIO might be significant, because it > > has to be performed for every single property check, and those can be > > numerous and very quick. I put together a simple benchmark > > (http://lpaste.net/99532 if anyone is interested) which shows that > > overhead can be noticable (16% for async vs 4% for simple catch) but > > tolerable, and it will be even less for more realistic properties. > > So I'll probably use the async approach there, too, although I may > > reconsider that in the future if I ever get to optimizing smallcheck and > > squeezing out those percents. > > > > As for the package itself, let's see if others will find any good use > > cases for it. I'll update the docs with some conclusions from this > > thread. > > > > And thanks for your input. > > > > Roman > > > > * Michael Snoyman [2014-02-05 18:48:22+0200] > >> I can't think of any situation in which the semantics you're implying make > >> sense. To me, catching synchronous exception is a simple concept: if an > >> exception is generated internally to `userAction`, then it's a synchronous > >> exception. If it was terminated by something external, then it's > >> asynchronous. I'm not sure what you're getting at about my approach > >> requiring knowledge of what's going on deep inside a library. > >> > >> The real question which is not explained in your package is what use case > >> you're actually trying to address. Here's a prime example I've run into: > >> you're writing a web application which uses a third-party library. If that > >> library throws an exception of any type, you want to catch the exception > >> and display an appropriate error message (or perhaps return some data from > >> another source). However, we still want the web application to respect > >> timeout messages from the server to avoid slowloris attacks. The handler > >> code would look like: > >> > >> myHandler = do > >> eres <- tryAnyDeep someLibraryFunction > >> case eres of > >> Left e -> tellUser "I'm sorry, there was an issue making the query" > >> Right x -> displayData x > >> > >> The goal is that, under no circumstances, should someLibraryFunction be > >> able to case the exception to escape tryAnyDeep. This includes rethrowing > >> some async exception that it received from, e.g., a timeout. This would not > >> be honored by trySync. > >> > >> Michael > > > > _______________________________________________ > > 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 jmacristovao at gmail.com Thu Feb 6 00:16:06 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Thu, 6 Feb 2014 00:16:06 +0000 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140205223353.GA17748@sniper> References: <20140205112338.GA5055@sniper> <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> <20140205223353.GA17748@sniper> Message-ID: Hi again, > since the module doesn't make any attempt to differentiate between sync and async exceptions. Well... If I am understanding this correctly, and I might not be: Michael code efectively distinguishes exceptions thrown asynchronously with throwTo from synchronous exceptions generated inside the catchAny. Since the code run by catchAny is run in a separate 'anonymous' thread created by withAsync, there's no way you can throw it an asynchronous exception (ThreadKilled) with throwTo - you don't know its thread id. Any code using throwTo will just know the calling thread, and thus you've got a way to distinguish between received asynchronous exceptions (the timeout example) and synchronous exceptions generated inside the function your passing to catchAny. Thus, in one hand I do not think "CatchAny" makes justice to the fact that async exceptions received by the thread using catchAny are _not_ caught by catchAny. In the other hand, I was just thinking: what if the computation runing in catchAny in the anonymous thread generates a Ctrl-C, if, for example, it interacts with stdin. However, Control.Exception states that: "UserInterrupt: This exception is raised by default in the __main__ thread of the program when the user requests to terminate the program via the usual mechanism(s) (e.g. Control-C in the console). " (emphasis mine) Thus, the problem does not pose it self. The remaining two asynchronous exceptions (StackOverflow and HeapOverflow) are again a result of the inner function execution, and could, from a certain point of view, be considered synchronous. So, for all intents and purposes, this catchAny and such _do_ allow to distinguish between asynchronous exceptions (sent with throwTo) or synchronous exceptions (generated as a result of the execution of the computation passed to catchAny). Asynchronous exceptions do not occur inside the CatchAny associated computation, except perhaps the ThreadKilled signal forward by its calling thread/parent thread when it self is killed - an in that particular case, it doesn't really matter. That asynchronous exception would be caught by catchAny, but the result returned by the exception handler would not be used - the calling thread is also dying. Am I getting this right? Jo?o 2014-02-05 Roman Cheplyaka : > Well, since you happened to ask me (although I am as good a bikeshedder > as the next person), I think that you don't need to mention Async > anywhere in the module name, since the module doesn't make any attempt > to differentiate between sync and async exceptions. > > And the fact that the module uses the 'async' library is just an > implementation detail. > > I'd go with something like Control.Exception.CatchAny. > > Roman > > * Jo?o Crist?v?o [2014-02-05 22:13:19+0000] >> Roman, >> >> By mere chance today I was, about the same time you published your >> library, working on the suggestion made by Michael in the end of his >> original blog post: splitting the async exceptions part from >> classy-prelude (he is ok with this). >> >> https://github.com/jcristovao/async-exception >> >> I was not yet sure about the namespace, I had opted for: >> Control.Concurrent.Async.Exception >> >> But yours makes more sense, >> Control.Async.Exception >> >> I agree that the two solutions address different problems, and as you >> say, for controlled situations where performance is critical yours >> indeed adds less overhead. But for more general solutions, Michael's >> solution - split from Classy prelude, seems to be the way to go, and >> thus my 'split' makes sense if you don't need the remaining classy >> prelude. >> >> As such, I was considering the namespace: >> Control.Async.Exception.All >> >> To differentiate from yours, signaling that it handles _all_ exceptions. >> What do you think? >> >> Anyhow, I also think Joachim suggestion (of at least implementing the >> new exception classes in base-compat) makes sense, so I volunteer to >> add to the work I already done here: >> https://github.com/sol/base-compat/pull/2 >> >> (If the patch gets accepted, of course). >> >> Cheers, >> Jo?o >> >> 2014-02-05 Roman Cheplyaka : >> > Ok, this clears things up. I misinterpreted your approach thinking that >> > you're also solving the problem of distinguishing async vs sync >> > exceptions, only based on how they were thrown instead of their type. >> > >> > I now see that it isn't the case -- you're catching *all* exceptions. >> > (And run the timeout handler in a different thread.) >> > >> > So no wonder that asynchronous-exceptions (whose description says that >> > it lets differentiate between sync and async exceptions, in a certain >> > sense) doesn't help you -- you simply don't want any exceptions at all. >> > >> > My use case is simpler -- I write testing libraries. If a test throws an >> > exception, we have to decide whether we want to report it as a test's >> > failure or it's a bigger problem and we want to wrap up. >> > >> > I don't think there's a universally right way to make this decision. It >> > depends on what exceptions exist and what threads they can be thrown to. >> > E.g. if there existed something like UserInterrupt but which could be >> > thrown to any active thread, not only the main thread, then the approach >> > "run in a separate thread and log any exceptions from that thread" >> > simply wouldn't work. >> > >> > For tasty, based on the async exceptions I'm aware of, I think your >> > approach is overall better. It's almost as simple, doesn't require >> > patching 3rd-party timeout libraries, and catches StackOverflow (which >> > is desirable). So I'll switch to it instead. >> > >> > For smallcheck, the overhead of forkIO might be significant, because it >> > has to be performed for every single property check, and those can be >> > numerous and very quick. I put together a simple benchmark >> > (http://lpaste.net/99532 if anyone is interested) which shows that >> > overhead can be noticable (16% for async vs 4% for simple catch) but >> > tolerable, and it will be even less for more realistic properties. >> > So I'll probably use the async approach there, too, although I may >> > reconsider that in the future if I ever get to optimizing smallcheck and >> > squeezing out those percents. >> > >> > As for the package itself, let's see if others will find any good use >> > cases for it. I'll update the docs with some conclusions from this >> > thread. >> > >> > And thanks for your input. >> > >> > Roman >> > >> > * Michael Snoyman [2014-02-05 18:48:22+0200] >> >> I can't think of any situation in which the semantics you're implying make >> >> sense. To me, catching synchronous exception is a simple concept: if an >> >> exception is generated internally to `userAction`, then it's a synchronous >> >> exception. If it was terminated by something external, then it's >> >> asynchronous. I'm not sure what you're getting at about my approach >> >> requiring knowledge of what's going on deep inside a library. >> >> >> >> The real question which is not explained in your package is what use case >> >> you're actually trying to address. Here's a prime example I've run into: >> >> you're writing a web application which uses a third-party library. If that >> >> library throws an exception of any type, you want to catch the exception >> >> and display an appropriate error message (or perhaps return some data from >> >> another source). However, we still want the web application to respect >> >> timeout messages from the server to avoid slowloris attacks. The handler >> >> code would look like: >> >> >> >> myHandler = do >> >> eres <- tryAnyDeep someLibraryFunction >> >> case eres of >> >> Left e -> tellUser "I'm sorry, there was an issue making the query" >> >> Right x -> displayData x >> >> >> >> The goal is that, under no circumstances, should someLibraryFunction be >> >> able to case the exception to escape tryAnyDeep. This includes rethrowing >> >> some async exception that it received from, e.g., a timeout. This would not >> >> be honored by trySync. >> >> >> >> Michael >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > From roma at ro-che.info Thu Feb 6 06:17:07 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 6 Feb 2014 08:17:07 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> <20140205223353.GA17748@sniper> Message-ID: <20140206061707.GA19197@sniper> > Am I getting this right? Not quite. The enclosed computation may get asynchronous exceptions whatever definition of 'asynchronous' you use ? the exact one (by throw method) or the approximate one (by type). Just a couple of examples: * The thread may catch an async exception from the RTS (such as BlockedIndefinitelyOnMVar or StackOverflow) * The thread may spawn other threads, passing its pid to them, and one of its children may eventually kill it So I'd say this method allows to catch any exceptions "related" to the computation, synchronous or asynchronous. It is this "relatedness" that is enforced by running it in a separate thread. Roman * Jo?o Crist?v?o [2014-02-06 00:16:06+0000] > Hi again, > > > since the module doesn't make any attempt to differentiate between sync and async exceptions. > > Well... If I am understanding this correctly, and I might not be: > Michael code efectively distinguishes exceptions thrown asynchronously > with throwTo from synchronous exceptions generated inside the > catchAny. Since the code run by catchAny is run in a separate > 'anonymous' thread created by withAsync, there's no way you can throw > it an asynchronous exception (ThreadKilled) with throwTo - you don't > know its thread id. > > Any code using throwTo will just know the calling thread, and thus > you've got a way to distinguish between received asynchronous > exceptions (the timeout example) and synchronous exceptions generated > inside the function your passing to catchAny. > > Thus, in one hand I do not think "CatchAny" makes justice to the fact > that async exceptions received by the thread using catchAny are _not_ > caught by catchAny. > > In the other hand, I was just thinking: what if the computation runing > in catchAny in the anonymous thread generates a Ctrl-C, if, for > example, it interacts with stdin. > However, Control.Exception states that: > "UserInterrupt: This exception is raised by default in the __main__ > thread of the program when the user requests to terminate the program > via the usual mechanism(s) (e.g. Control-C in the console). " > (emphasis mine) > > Thus, the problem does not pose it self. The remaining two > asynchronous exceptions (StackOverflow and HeapOverflow) are again a > result of the inner function execution, and could, from a certain > point of view, be considered synchronous. > > So, for all intents and purposes, this catchAny and such _do_ allow to > distinguish between asynchronous exceptions (sent with throwTo) or > synchronous exceptions (generated as a result of the execution of the > computation passed to catchAny). Asynchronous exceptions do not occur > inside the CatchAny associated computation, except perhaps the > ThreadKilled signal forward by its calling thread/parent thread when > it self is killed - an in that particular case, it doesn't really > matter. That asynchronous exception would be caught by catchAny, but > the result returned by the exception handler would not be used - the > calling thread is also dying. > > Am I getting this right? > Jo?o > > 2014-02-05 Roman Cheplyaka : > > Well, since you happened to ask me (although I am as good a bikeshedder > > as the next person), I think that you don't need to mention Async > > anywhere in the module name, since the module doesn't make any attempt > > to differentiate between sync and async exceptions. > > > > And the fact that the module uses the 'async' library is just an > > implementation detail. > > > > I'd go with something like Control.Exception.CatchAny. > > > > Roman > > > > * Jo?o Crist?v?o [2014-02-05 22:13:19+0000] > >> Roman, > >> > >> By mere chance today I was, about the same time you published your > >> library, working on the suggestion made by Michael in the end of his > >> original blog post: splitting the async exceptions part from > >> classy-prelude (he is ok with this). > >> > >> https://github.com/jcristovao/async-exception > >> > >> I was not yet sure about the namespace, I had opted for: > >> Control.Concurrent.Async.Exception > >> > >> But yours makes more sense, > >> Control.Async.Exception > >> > >> I agree that the two solutions address different problems, and as you > >> say, for controlled situations where performance is critical yours > >> indeed adds less overhead. But for more general solutions, Michael's > >> solution - split from Classy prelude, seems to be the way to go, and > >> thus my 'split' makes sense if you don't need the remaining classy > >> prelude. > >> > >> As such, I was considering the namespace: > >> Control.Async.Exception.All > >> > >> To differentiate from yours, signaling that it handles _all_ exceptions. > >> What do you think? > >> > >> Anyhow, I also think Joachim suggestion (of at least implementing the > >> new exception classes in base-compat) makes sense, so I volunteer to > >> add to the work I already done here: > >> https://github.com/sol/base-compat/pull/2 > >> > >> (If the patch gets accepted, of course). > >> > >> Cheers, > >> Jo?o > >> > >> 2014-02-05 Roman Cheplyaka : > >> > Ok, this clears things up. I misinterpreted your approach thinking that > >> > you're also solving the problem of distinguishing async vs sync > >> > exceptions, only based on how they were thrown instead of their type. > >> > > >> > I now see that it isn't the case -- you're catching *all* exceptions. > >> > (And run the timeout handler in a different thread.) > >> > > >> > So no wonder that asynchronous-exceptions (whose description says that > >> > it lets differentiate between sync and async exceptions, in a certain > >> > sense) doesn't help you -- you simply don't want any exceptions at all. > >> > > >> > My use case is simpler -- I write testing libraries. If a test throws an > >> > exception, we have to decide whether we want to report it as a test's > >> > failure or it's a bigger problem and we want to wrap up. > >> > > >> > I don't think there's a universally right way to make this decision. It > >> > depends on what exceptions exist and what threads they can be thrown to. > >> > E.g. if there existed something like UserInterrupt but which could be > >> > thrown to any active thread, not only the main thread, then the approach > >> > "run in a separate thread and log any exceptions from that thread" > >> > simply wouldn't work. > >> > > >> > For tasty, based on the async exceptions I'm aware of, I think your > >> > approach is overall better. It's almost as simple, doesn't require > >> > patching 3rd-party timeout libraries, and catches StackOverflow (which > >> > is desirable). So I'll switch to it instead. > >> > > >> > For smallcheck, the overhead of forkIO might be significant, because it > >> > has to be performed for every single property check, and those can be > >> > numerous and very quick. I put together a simple benchmark > >> > (http://lpaste.net/99532 if anyone is interested) which shows that > >> > overhead can be noticable (16% for async vs 4% for simple catch) but > >> > tolerable, and it will be even less for more realistic properties. > >> > So I'll probably use the async approach there, too, although I may > >> > reconsider that in the future if I ever get to optimizing smallcheck and > >> > squeezing out those percents. > >> > > >> > As for the package itself, let's see if others will find any good use > >> > cases for it. I'll update the docs with some conclusions from this > >> > thread. > >> > > >> > And thanks for your input. > >> > > >> > Roman > >> > > >> > * Michael Snoyman [2014-02-05 18:48:22+0200] > >> >> I can't think of any situation in which the semantics you're implying make > >> >> sense. To me, catching synchronous exception is a simple concept: if an > >> >> exception is generated internally to `userAction`, then it's a synchronous > >> >> exception. If it was terminated by something external, then it's > >> >> asynchronous. I'm not sure what you're getting at about my approach > >> >> requiring knowledge of what's going on deep inside a library. > >> >> > >> >> The real question which is not explained in your package is what use case > >> >> you're actually trying to address. Here's a prime example I've run into: > >> >> you're writing a web application which uses a third-party library. If that > >> >> library throws an exception of any type, you want to catch the exception > >> >> and display an appropriate error message (or perhaps return some data from > >> >> another source). However, we still want the web application to respect > >> >> timeout messages from the server to avoid slowloris attacks. The handler > >> >> code would look like: > >> >> > >> >> myHandler = do > >> >> eres <- tryAnyDeep someLibraryFunction > >> >> case eres of > >> >> Left e -> tellUser "I'm sorry, there was an issue making the query" > >> >> Right x -> displayData x > >> >> > >> >> The goal is that, under no circumstances, should someLibraryFunction be > >> >> able to case the exception to escape tryAnyDeep. This includes rethrowing > >> >> some async exception that it received from, e.g., a timeout. This would not > >> >> be honored by trySync. > >> >> > >> >> Michael > >> > > >> > _______________________________________________ > >> > 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 genial at alva.ro Thu Feb 6 07:59:50 2014 From: genial at alva.ro (Alvaro J. Genial) Date: Thu, 6 Feb 2014 02:59:50 -0500 Subject: [Haskell-cafe] Thr Neat templating system Message-ID: Howdy, I wrote a template system that I've used in a few personal projects and I thought it might be worth it to clean the core of it up a bit and show it to the world. I named it `neat`, for no other reason than I found it so; you can find the sources, an explanation of how it works and basic instructions on how to try it and experiment with it here: https://github.com/ajg/neat >From the synopsis: "Neat is a slightly unusual templating tool that does not interpret templates at runtime; rather, it compiles templates statically from the source (input) language into the target (output) language. In that sense neat can be thought of as a very flexible preprocessor masquerading as something fancier. Of course, the result can then be embedded or compiled directly in order to accept arbitrary data at runtime and transform it as desired, dynamically." I haven't released it as a proper package because I don't know whether it'll be useful; for now it's just a pet project; it is MIT-licensed. I'd like to get your ideas, suggestions, criticism, and other feedback. Thank you, Alvaro http://alva.ro -------------- next part -------------- An HTML attachment was scrubbed... URL: From genial at alva.ro Thu Feb 6 08:25:06 2014 From: genial at alva.ro (Alvaro J. Genial) Date: Thu, 6 Feb 2014 03:25:06 -0500 Subject: [Haskell-cafe] Thr Neat templating system In-Reply-To: References: Message-ID: That should have been *The--no affiliation to The Hollywood Reporter was intended. :) Alvaro Alvaro http://alva.ro On Thu, Feb 6, 2014 at 2:59 AM, Alvaro J. Genial wrote: > Howdy, > > I wrote a template system that I've used in a few personal projects and I > thought it might be worth it to clean the core of it up a bit and show it > to the world. I named it `neat`, for no other reason than I found it so; > you can find the sources, an explanation of how it works and basic > instructions on how to try it and experiment with it here: > > https://github.com/ajg/neat > > From the synopsis: > > "Neat is a slightly unusual templating tool that does not interpret > templates at runtime; rather, it compiles templates statically from the > source (input) language into the target (output) language. In that sense > neat can be thought of as a very flexible preprocessor masquerading as > something fancier. Of course, the result can then be embedded or compiled > directly in order to accept arbitrary data at runtime and transform it as > desired, dynamically." > > I haven't released it as a proper package because I don't know whether > it'll be useful; for now it's just a pet project; it is MIT-licensed. I'd > like to get your ideas, suggestions, criticism, and other feedback. > > Thank you, > > Alvaro > http://alva.ro > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Thu Feb 6 09:07:37 2014 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 6 Feb 2014 11:07:37 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: <20140206061707.GA19197@sniper> References: <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> <20140205223353.GA17748@sniper> <20140206061707.GA19197@sniper> Message-ID: On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka wrote: > > Am I getting this right? > > Not quite. > > The enclosed computation may get asynchronous exceptions whatever > definition of 'asynchronous' you use -- the exact one (by throw method) > or the approximate one (by type). > > Just a couple of examples: > > * The thread may catch an async exception from the RTS (such as > BlockedIndefinitelyOnMVar or StackOverflow) > * The thread may spawn other threads, passing its pid to them, and one > of its children may eventually kill it > > So I'd say this method allows to catch any exceptions "related" to > the computation, synchronous or asynchronous. It is this "relatedness" > that is enforced by running it in a separate thread. > > Roman > > I definitely think this is important to get our terminology right. A lot of the scariness of async exceptions likely spawns from the fact that we use the same term to refer to a number of very different cases. Let me give a crack at breaking down exceptions: * An exception with a synchronous type (e.g., IOException) thrown via throwIO. This is the most synchronous of synchronous exceptions. * An exception with an asynchronous type (e.g., UserInterrupt) thrown via throwIO. There's legitimate room for debate as to what we should call this. For my purposes, I'd want to call it a synchronous exception. * An exception with a synchronous type thrown via throwTo. Similar to previous bullet, but I'd consider this asynchronous. * An exception with an asynchronous type thrown via throwTo. This is solidly an asynchronous exception. Then we have some more interesting questions: * What *is* an asynchronous type? By including BlockedIndefinitelyOnMVar, it seems like you're defining it to include any exception generated by the RTS. However, I'd consider it a synchronous exception: it is generated in direct consequence of performing an IO action. It just happens to be generated by the RTS instead of via some library talking to the filesystem. * What happens if an async exception is caught and then rethrown? Has it transformed itself into a synchronous exception? That's a tricky question, and likely depends on the exact manner in which is was caught. * What happens if a function utilizes some form of asynchronous exception mechanism to affect its behavior? The prime example of this is `timeout`, or better, the `asyncTimeout` function I displayed above. Internally to that function, I think that's an async exception. However, for a *caller* of that function, the behavior is actually synchronous: there was no notification from the outside world changing the behavior of this function, it simply has the possibility to terminate by throwing a Timeout, the same way a function may terminate by throwing an IOException. That last bullet is crucial to the question of whether classy-prelude's and Jo?o's catching functions are asynchronous or not. But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do. Michael -------------- next part -------------- An HTML attachment was scrubbed... URL: From genial at alva.ro Thu Feb 6 09:14:21 2014 From: genial at alva.ro (Alvaro J. Genial) Date: Thu, 6 Feb 2014 04:14:21 -0500 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: References: <52E8BF6C.7050908@informatik.uni-kiel.de> Message-ID: Hey Jo?o, On Wed, Jan 29, 2014 at 5:13 AM, Jo?o Crist?v?o wrote: > > This leads to: > > zero (Product 1) = True. > > Is this what you wanted? > Indeed, it seems not. I'll have to think about this further. Thank you, Alvaro http://alva.ro -------------- next part -------------- An HTML attachment was scrubbed... URL: From genial at alva.ro Thu Feb 6 09:17:14 2014 From: genial at alva.ro (Alvaro J. Genial) Date: Thu, 6 Feb 2014 04:17:14 -0500 Subject: [Haskell-cafe] Generalized null / zero In-Reply-To: <52ED2A0F.9030305@acanac.net> References: <52ED2A0F.9030305@acanac.net> Message-ID: On Sat, Feb 1, 2014 at 12:08 PM, Mario Bla?evi? wrote: > On 01/28/14 21:25, Alvaro J. Genial wrote: > >> 1. Is there a more general version of `null`? (e.g. for a Monad, Functor, >> Applicative, Traversable or the like.) >> > > There is the MonoidNull class from my monoid-subclasses library. It comes > with plenty of standard instances. > This is very nice as it seems to mesh with my current thinking; I may end up using it in Neat [1] shortly. Thank you, Alvaro http://alva.ro [1] https://github.com/ajg/neat -------------- next part -------------- An HTML attachment was scrubbed... URL: From cobbe at ccs.neu.edu Thu Feb 6 11:46:45 2014 From: cobbe at ccs.neu.edu (Richard Cobbe) Date: Thu, 6 Feb 2014 06:46:45 -0500 Subject: [Haskell-cafe] problem with happy and type identity In-Reply-To: References: <20140202213219.GA238@ridcully.local> Message-ID: <20140206114645.GA238@ridcully.home> On Wed, Feb 05, 2014 at 08:34:40PM +0100, Erik Hesselink wrote: > To be able to share code between your library and your tests, you should either > > * Have a separate directory for the library sources and the test > sources. For example, put Ast.hs and Parser.y in 'src' and put > 'Hs-source-dirs: src' in the library section. Put RunTests.hs in > 'tests', and put 'Hs-source-dirs: tests' in the test-suite section. > This is the preferred way. > * Alternatively, don't specify 'sample' as a build-depends in the > test-suite. Note that this will mean that Ast and Parser will get > compiled twice. > > Right now, cabal somehow mixes types from the files compiled as part > of the test suite with types imported from the library. I see -- thanks! I'll give that a shot as soon as I get a chance. Richard From P.Achten at cs.ru.nl Thu Feb 6 13:33:12 2014 From: P.Achten at cs.ru.nl (Peter Achten) Date: Thu, 06 Feb 2014 14:33:12 +0100 Subject: [Haskell-cafe] 2nd Call for Papers - TFPIE 2014 Message-ID: <52F38F18.7090305@cs.ru.nl> All, Please find below the call for papers for the 3rd International Workshop on Trends In Functional Programming in Education, TFPIE 2014. Apologies in advance for multiple copies you may receive. Best regards, James Caldwell Call for Papers ___________________________________________________________________________________ *3rd International Workshop on Trends in Functional Programming in Education (TFPIE 2014)* May 25, 2014 Utrecht University Soesterberg, The Netherlands (http://www.cs.uwyo.edu/~jlc/tfpie14/ ) The 3rd International Workshop on Trends in Functional Programming in Education, TFPIE 2014, will be co-located with the Symposium on Trends in Functional Programming (TFP 2014) at Soesterberg, at the "Kontakt der Kontinenten" hotel in the Netherlands on Sunday, May 25th. TFP will follow from May 26-28. The goal of TFPIE is to gather researchers, teachers and professionals that use, or are interested in the use of, functional programming in education. TFPIE aims to be a venue where novel ideas, classroom-tested ideas and work-in-progress on the use of functional programming in education are discussed. The one-day workshop will foster a spirit of open discussion by having a review process for publication after the workshop. The program chair of TFPIE 2014 will screen submissions to ensure that all presentations are within scope and are of interest to participants. Potential presenters are invited to submit an extended abstract (4-6 pages) or a draft paper (up to 16 pages) in EPTCS style. The authors of accepted presentations will have their preprints and their slides made available on the workshop's website/wiki. Visitors to the TFPIE 2014 website/wiki will be able to add comments. This includes presenters who may respond to comments and questions as well as provide pointers to improvements and follow-up work. After the workshop, presenters will be invited to submit (a revised version of) their article for review. The PC will select the best articles for publication in the journalElectronic Proceedings in Theoretical Computer Science (EPTCS) . Articles not selected for presentation and extended abstracts will not be formally reviewed by the PC. TFPIE workshops have previously been held in St Andrews, Scotland (2012) and in Provo Utah, USA (2013). *Program Committee* James Caldwell, (Program Chair) University of Wyoming Peter Achten, Radboud University, Nijmgen Edwin Brady, University of St Andrews, St Andrews Jurriaan Hage, Universiteit Utrecht Philip Holzenspies, University of Twente Daniel R. Licata, Wesleyan University Marco T Morazan, Seton Hall University Christian Skalka, University of Vermont David Van Horn, Northeastern University *Submission Guidelines* There will be two types of presentations at TFPIE 2014. Regular papers and "best lecture" presentations. The best lecture talks are intended to allow for presentations or short lectures of purely pedagogical material. Papers and abstracts can be submitted via easychair at the following link: https://www.easychair.org/conferences/?conf=tfpie2014 *Papers* TFPIE 2014 welcomes submissions describing techniques used in the classroom, tools used in and/or developed for the classroom and any creative use of functional programming (FP) to aid education in or outside Computer Science. Topics of interest include, but are not limited to: * FP and beginning CS students * FP and Computational Thinking * FP and Artificial Intelligence * FP in Robotics * FP and Music * Advanced FP for undergraduates * FP in graduate education * Engaging students in research using FP * FP in Programming Languages * FP in the high school curriculum * FP as a stepping stone to other CS topics * FP and Philosophy * * *Best Lectures* In addition to papers, this year we are requesting "best lecture" presentations. What's your best lecture topic in an FP related course? Do you have a fun way to present FP concepts to novices or perhaps an especially interesting presentation of a difficult topic? In either case, please consider sharing it. Best lecture topics will be selected for presentation based on a short abstract describing the lecture and its interest to TFPIE attendees. *Important Dates* * 1 February 2014: TFPIE submissions open on easychair. * 7 April 2014: TFP and TFPIE registration opens * 21 April 2014: Submission deadline for draft TFPIE papers and abstracts * 27 April 2014: Notification of acceptance for presentation * 25 May 2014: Presentations in Soesterberg, Netherlands * 29 June 2014: Full papers for EPTCS proceedings due. * 16 August 2014: Notification of acceptance for proceedings * 8 September 2014: Camera ready copy due for EPTCS Submission of an abstract implies no obligation to submit a full paper; abstracts with no corresponding full versions by the full paper deadline will be considered as withdrawn. At least one author from each accepted presentation must attend the workshop. -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Thu Feb 6 12:35:02 2014 From: michael at snoyman.com (Michael Snoyman) Date: Thu, 6 Feb 2014 14:35:02 +0200 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> <20140205223353.GA17748@sniper> <20140206061707.GA19197@sniper> Message-ID: I like the idea of renaming the module to reflect this concept (I'm fine with either Inner or Enclosed), but leaving the function names themselves as-is. On Thu, Feb 6, 2014 at 2:12 PM, Jo?o Crist?v?o wrote: > Thanks Roman and Michael for the latest clarifications: > > I had indeed forgot the case where a thread runned in catchAny spawn > child threads that kill their parent. > > > But given how overloaded the term is, I'd be in favor of coming up with > a new term to represent what these catch functions are intended to do. > > The word currently in my head is 'inner', although Roman's suggestion > of 'enclosed' looks fine too. Internal is also correct, but as it is > regularly used to denote a package internal functions, it may lead to > confusion. > > What these functions (classy prelude/my library spin-off) do is run a > computation, isolating it from the calling thread (through async) and > catching all inner exceptions (of either synchronous or asynchronous > type, raised by either throwIO or throwTo instructions _present > somewhere inside that computation_, or by the RTS but once again > affecting only that computation, not the calling one. > > The calling one is thus 'free' to receive asynchronous exceptions in > the meantime (the execution of the inner computation). > > Thus, I propose either: > > Control.Exception.Inner / Control.Exception.Enclosed > > And/or, possibly also rename the functions to something like: > > catchAnyInner / catchAnyEnclosed > > Although I do not like this last option so much, the function name > gets too long, but that's a personal preference. > > > What do you think? > Jo?o > > 2014-02-06 Michael Snoyman : > > > > > > > > On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka > wrote: > >> > >> > Am I getting this right? > >> > >> Not quite. > >> > >> The enclosed computation may get asynchronous exceptions whatever > >> definition of 'asynchronous' you use -- the exact one (by throw method) > >> or the approximate one (by type). > >> > >> Just a couple of examples: > >> > >> * The thread may catch an async exception from the RTS (such as > >> BlockedIndefinitelyOnMVar or StackOverflow) > >> * The thread may spawn other threads, passing its pid to them, and one > >> of its children may eventually kill it > >> > >> So I'd say this method allows to catch any exceptions "related" to > >> the computation, synchronous or asynchronous. It is this "relatedness" > >> that is enforced by running it in a separate thread. > >> > >> Roman > >> > > > > I definitely think this is important to get our terminology right. A lot > of > > the scariness of async exceptions likely spawns from the fact that we use > > the same term to refer to a number of very different cases. Let me give a > > crack at breaking down exceptions: > > > > * An exception with a synchronous type (e.g., IOException) thrown via > > throwIO. This is the most synchronous of synchronous exceptions. > > * An exception with an asynchronous type (e.g., UserInterrupt) thrown via > > throwIO. There's legitimate room for debate as to what we should call > this. > > For my purposes, I'd want to call it a synchronous exception. > > * An exception with a synchronous type thrown via throwTo. Similar to > > previous bullet, but I'd consider this asynchronous. > > * An exception with an asynchronous type thrown via throwTo. This is > solidly > > an asynchronous exception. > > > > Then we have some more interesting questions: > > > > * What *is* an asynchronous type? By including > BlockedIndefinitelyOnMVar, it > > seems like you're defining it to include any exception generated by the > RTS. > > However, I'd consider it a synchronous exception: it is generated in > direct > > consequence of performing an IO action. It just happens to be generated > by > > the RTS instead of via some library talking to the filesystem. > > * What happens if an async exception is caught and then rethrown? Has it > > transformed itself into a synchronous exception? That's a tricky > question, > > and likely depends on the exact manner in which is was caught. > > * What happens if a function utilizes some form of asynchronous exception > > mechanism to affect its behavior? The prime example of this is > `timeout`, or > > better, the `asyncTimeout` function I displayed above. Internally to that > > function, I think that's an async exception. However, for a *caller* of > that > > function, the behavior is actually synchronous: there was no notification > > from the outside world changing the behavior of this function, it simply > has > > the possibility to terminate by throwing a Timeout, the same way a > function > > may terminate by throwing an IOException. > > > > That last bullet is crucial to the question of whether classy-prelude's > and > > Jo?o's catching functions are asynchronous or not. But given how > overloaded > > the term is, I'd be in favor of coming up with a new term to represent > what > > these catch functions are intended to do. > > > > Michael > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmacristovao at gmail.com Thu Feb 6 12:12:29 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Thu, 6 Feb 2014 12:12:29 +0000 Subject: [Haskell-cafe] ANN: asynchronous-exceptions In-Reply-To: References: <20140205112801.GA5306@sniper> <20140205151926.GA9254@sniper> <20140205162849.GC10049@sniper> <20140205212308.GA12415@sniper> <20140205223353.GA17748@sniper> <20140206061707.GA19197@sniper> Message-ID: Thanks Roman and Michael for the latest clarifications: I had indeed forgot the case where a thread runned in catchAny spawn child threads that kill their parent. > But given how overloaded the term is, I'd be in favor of coming up with a new term to represent what these catch functions are intended to do. The word currently in my head is 'inner', although Roman's suggestion of 'enclosed' looks fine too. Internal is also correct, but as it is regularly used to denote a package internal functions, it may lead to confusion. What these functions (classy prelude/my library spin-off) do is run a computation, isolating it from the calling thread (through async) and catching all inner exceptions (of either synchronous or asynchronous type, raised by either throwIO or throwTo instructions _present somewhere inside that computation_, or by the RTS but once again affecting only that computation, not the calling one. The calling one is thus 'free' to receive asynchronous exceptions in the meantime (the execution of the inner computation). Thus, I propose either: Control.Exception.Inner / Control.Exception.Enclosed And/or, possibly also rename the functions to something like: catchAnyInner / catchAnyEnclosed Although I do not like this last option so much, the function name gets too long, but that's a personal preference. What do you think? Jo?o 2014-02-06 Michael Snoyman : > > > > On Thu, Feb 6, 2014 at 8:17 AM, Roman Cheplyaka wrote: >> >> > Am I getting this right? >> >> Not quite. >> >> The enclosed computation may get asynchronous exceptions whatever >> definition of 'asynchronous' you use -- the exact one (by throw method) >> or the approximate one (by type). >> >> Just a couple of examples: >> >> * The thread may catch an async exception from the RTS (such as >> BlockedIndefinitelyOnMVar or StackOverflow) >> * The thread may spawn other threads, passing its pid to them, and one >> of its children may eventually kill it >> >> So I'd say this method allows to catch any exceptions "related" to >> the computation, synchronous or asynchronous. It is this "relatedness" >> that is enforced by running it in a separate thread. >> >> Roman >> > > I definitely think this is important to get our terminology right. A lot of > the scariness of async exceptions likely spawns from the fact that we use > the same term to refer to a number of very different cases. Let me give a > crack at breaking down exceptions: > > * An exception with a synchronous type (e.g., IOException) thrown via > throwIO. This is the most synchronous of synchronous exceptions. > * An exception with an asynchronous type (e.g., UserInterrupt) thrown via > throwIO. There's legitimate room for debate as to what we should call this. > For my purposes, I'd want to call it a synchronous exception. > * An exception with a synchronous type thrown via throwTo. Similar to > previous bullet, but I'd consider this asynchronous. > * An exception with an asynchronous type thrown via throwTo. This is solidly > an asynchronous exception. > > Then we have some more interesting questions: > > * What *is* an asynchronous type? By including BlockedIndefinitelyOnMVar, it > seems like you're defining it to include any exception generated by the RTS. > However, I'd consider it a synchronous exception: it is generated in direct > consequence of performing an IO action. It just happens to be generated by > the RTS instead of via some library talking to the filesystem. > * What happens if an async exception is caught and then rethrown? Has it > transformed itself into a synchronous exception? That's a tricky question, > and likely depends on the exact manner in which is was caught. > * What happens if a function utilizes some form of asynchronous exception > mechanism to affect its behavior? The prime example of this is `timeout`, or > better, the `asyncTimeout` function I displayed above. Internally to that > function, I think that's an async exception. However, for a *caller* of that > function, the behavior is actually synchronous: there was no notification > from the outside world changing the behavior of this function, it simply has > the possibility to terminate by throwing a Timeout, the same way a function > may terminate by throwing an IOException. > > That last bullet is crucial to the question of whether classy-prelude's and > Jo?o's catching functions are asynchronous or not. But given how overloaded > the term is, I'd be in favor of coming up with a new term to represent what > these catch functions are intended to do. > > Michael From corentin.dupont at gmail.com Thu Feb 6 14:50:06 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 6 Feb 2014 15:50:06 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hi guys, I'm still exploring some design space for DSLs, following our interesting discussion. I'm trying to write the evaluator for the DSL (see below). For the general case, the evaluator looks like: eval :: Nomex r a -> State Game a This eval function takes an expression (called Nomex), that can possibly have effects. It returns a state monad, to allow you to modify the game state. But for effectless instructions, it would be better to run the evaluator in the reader monad: evalNoEffect :: Nomex NoEffect a -> Reader Game a So you can have additional guaranties that evaluating your expression will not have effects. I tried (see below), but it doesn't work for the moment: > {-# LANGUAGE GADTs #-} > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, UndecidableInstances #-} > module DSLEffects where > import Control.Monad.Error > import Control.Monad.State > import Control.Monad.Reader > import Data.Typeable This is the DSL: > data Effects = Effect | NoEffect > data Nomex :: Effects -> * -> * where > ReadAccount :: Nomex r Int --ReadAccount has no effect: it can be run in whatever monad > WriteAccount :: Int -> Nomex Effect () --WriteAccount has effect > SetVictory :: Nomex NoEffect Bool -> Nomex Effect () --SetVictory don't accept effectful computations > Bind :: Nomex m a -> (a -> Nomex m b) -> Nomex m b > Return :: a -> Nomex r a --wrapping a constant has no effect > instance Monad (Nomex a) where > return = Return > (>>=) = Bind > noEff :: Nomex NoEffect () > noEff = return () > hasEffect :: Nomex Effect () > hasEffect = do > a <- ReadAccount > WriteAccount a > data Game = Game { victory :: Nomex NoEffect Bool, > account :: Int} > eval :: Nomex r a -> State Game a > eval a at ReadAccount = liftEval $ evalNoEffect a > eval (WriteAccount a) = modify (\g -> g{account = a}) > eval (SetVictory v) = modify (\g -> g{victory = v}) > eval a@(Return _) = liftEval $ evalNoEffect a > eval (Bind exp f) = eval exp >>= eval . f > evalNoEffect :: Nomex NoEffect a -> Reader Game a > evalNoEffect ReadAccount = asks account > evalNoEffect (Return a) = return a > evalNoEffect (Bind exp f) = evalNoEffect exp >>= evalNoEffect . f > liftEval :: Reader Game a -> State Game a > liftEval r = get >>= return . runReader r This is not compiling: exceptEffect.lhs:60:15: Couldn't match type 'NoEffect with 'Effect Inaccessible code in a pattern with constructor WriteAccount :: Int -> Nomex 'Effect (), in an equation for `evalEffect' In the pattern: WriteAccount a In an equation for `evalEffect': evalEffect (WriteAccount a) = modify (\ g -> g {account = a}) It seems that the type of effectless computations (NoEffect) leaks in the type of effectful ones (due to the pattern matching)... Thanks, Corentin On Mon, Feb 3, 2014 at 12:44 PM, Corentin Dupont wrote: > I saw that to write liftQD you decontruct (unwrap) the type and > reconstruct it. > I don't know if I can do that for my Exp (which is a full DSL)... > > Anyway, there should be a way to encode the Effect/NoEffect semantic at > type level... > Using Oleg's parametrized monad idea ( > http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), > I tried: > > > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs > > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, > UndecidableInstances #-} > > > module DSLEffects where > > import Prelude hiding (return, (>>), (>>=)) > > import Control.Monad.Parameterized > > This data type will be promoted to kind level (thanks to DataKinds): > > > > data Eff = Effect | NoEffect > > This class allows to specify the semantic on Effects (Effect + NoEffect = > Effect): > > > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r > > instance Effects Effect n Effect > > instance Effects NoEffect n n > > This is the DSL: > > > data Exp :: Eff -> * -> * where > > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect > > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect > > Const :: a -> Exp r a > > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b > --Bind comes with a semantic on effects > > Fmap :: (a -> b) -> Exp m a -> Exp m b > > > instance Functor (Exp r) where > > fmap = Fmap > > > instance Return (Exp r) where > > returnM = Const > > > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where > > (>>=) = Bind > > > noEff :: Exp NoEffect () > > noEff = returnM () > > > hasEffect :: Exp Effect () > > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) > > This is working more or less, however I am obliged to put the type > signature on the returnM (last line): why? > Furthermore, I cannot write directly: > > > hasEffect :: Exp Effect () > > hasEffect = ReadAccount > > > Do you have a better idea? > > > > On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper wrote: > >> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont >> wrote: >> > you should be able to run an effectless monad in an effectful one. >> > How to encode this semantic? >> >> In LVish we just have a `liftQD` operation that will let you lift a >> deterministic computation to a quasi-deterministic one (recall that >> deterministic computations can perform fewer effects): >> >> liftQD :: Par Det s a -> Par QuasiDet s a >> >> So, analogously, you could have a `liftEff` and then write `liftEff >> noEff`. This is also a little bit ugly, but you may find you don't >> have to do it very often (we rarely use `liftQD`). >> >> Lindsey >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Thu Feb 6 17:47:31 2014 From: vogt.adam at gmail.com (adam vogt) Date: Thu, 6 Feb 2014 12:47:31 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hi Corentin, You need change Effect to NoEffect to reuse the evalNoEffect: > eval ReadAccount = liftEval $ evalNoEffect ReadAccount > eval (Return a) = liftEval $ evalNoEffect (Return a) Or use a function like `unsafeCoerce :: Nomex Effect a -> Nomex NoEffect a`. If you rename the types that tag effects to something that describes exactly what the tags actually represent, maybe the above definition will be more satisfying: > data Effects > = HasBeenCombinedWithSomethingThatHasEffectsButICan'tBeSureItActuallyHasEffectsAllByItself > | DefinitelyHasNoEffects Regards, Adam On Thu, Feb 6, 2014 at 9:50 AM, Corentin Dupont wrote: > Hi guys, > I'm still exploring some design space for DSLs, following our interesting > discussion. > > I'm trying to write the evaluator for the DSL (see below). > For the general case, the evaluator looks like: > > eval :: Nomex r a -> State Game a > > This eval function takes an expression (called Nomex), that can possibly > have effects. > It returns a state monad, to allow you to modify the game state. > > But for effectless instructions, it would be better to run the evaluator > in the reader monad: > > evalNoEffect :: Nomex NoEffect a -> Reader Game a > > So you can have additional guaranties that evaluating your expression will > not have effects. > I tried (see below), but it doesn't work for the moment: > > > > {-# LANGUAGE GADTs #-} > > > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, > > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, > UndecidableInstances #-} > > > module DSLEffects where > > > import Control.Monad.Error > > import Control.Monad.State > > import Control.Monad.Reader > > import Data.Typeable > > This is the DSL: > > > data Effects = Effect | NoEffect > > > data Nomex :: Effects -> * -> * where > > ReadAccount :: Nomex r Int --ReadAccount has no > effect: it can be run in whatever monad > > WriteAccount :: Int -> Nomex Effect () --WriteAccount has effect > > SetVictory :: Nomex NoEffect Bool -> Nomex Effect () --SetVictory > don't accept effectful computations > > Bind :: Nomex m a -> (a -> Nomex m b) -> Nomex m b > > Return :: a -> Nomex r a --wrapping a constant has no effect > > > instance Monad (Nomex a) where > > return = Return > > (>>=) = Bind > > > > noEff :: Nomex NoEffect () > > noEff = return () > > > hasEffect :: Nomex Effect () > > hasEffect = do > > a <- ReadAccount > > WriteAccount a > > > data Game = Game { victory :: Nomex NoEffect Bool, > > account :: Int} > > > > eval :: Nomex r a -> State Game a > > eval a at ReadAccount = liftEval $ evalNoEffect a > > eval (WriteAccount a) = modify (\g -> g{account = a}) > > > eval (SetVictory v) = modify (\g -> g{victory = v}) > > eval a@(Return _) = liftEval $ evalNoEffect a > > eval (Bind exp f) = eval exp >>= eval . f > > > evalNoEffect :: Nomex NoEffect a -> Reader Game a > > evalNoEffect ReadAccount = asks account > > evalNoEffect (Return a) = return a > > evalNoEffect (Bind exp f) = evalNoEffect exp >>= evalNoEffect . f > > > liftEval :: Reader Game a -> State Game a > > liftEval r = get >>= return . runReader r > > > This is not compiling: > > exceptEffect.lhs:60:15: > Couldn't match type 'NoEffect with 'Effect > Inaccessible code in > a pattern with constructor > WriteAccount :: Int -> Nomex 'Effect (), > in an equation for `evalEffect' > In the pattern: WriteAccount a > In an equation for `evalEffect': > evalEffect (WriteAccount a) = modify (\ g -> g {account = a}) > > It seems that the type of effectless computations (NoEffect) leaks in the > type of effectful ones (due to the pattern matching)... > > Thanks, > Corentin > > > > On Mon, Feb 3, 2014 at 12:44 PM, Corentin Dupont < > corentin.dupont at gmail.com> wrote: > >> I saw that to write liftQD you decontruct (unwrap) the type and >> reconstruct it. >> I don't know if I can do that for my Exp (which is a full DSL)... >> >> Anyway, there should be a way to encode the Effect/NoEffect semantic at >> type level... >> Using Oleg's parametrized monad idea ( >> http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), >> I tried: >> >> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs >> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, >> UndecidableInstances #-} >> >> > module DSLEffects where >> > import Prelude hiding (return, (>>), (>>=)) >> > import Control.Monad.Parameterized >> >> This data type will be promoted to kind level (thanks to DataKinds): >> >> >> > data Eff = Effect | NoEffect >> >> This class allows to specify the semantic on Effects (Effect + NoEffect = >> Effect): >> >> > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r >> > instance Effects Effect n Effect >> > instance Effects NoEffect n n >> >> This is the DSL: >> >> > data Exp :: Eff -> * -> * where >> > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect >> > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect >> > Const :: a -> Exp r a >> > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b >> --Bind comes with a semantic on effects >> > Fmap :: (a -> b) -> Exp m a -> Exp m b >> >> > instance Functor (Exp r) where >> > fmap = Fmap >> >> > instance Return (Exp r) where >> > returnM = Const >> >> > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where >> > (>>=) = Bind >> >> > noEff :: Exp NoEffect () >> > noEff = returnM () >> >> > hasEffect :: Exp Effect () >> > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) >> >> This is working more or less, however I am obliged to put the type >> signature on the returnM (last line): why? >> Furthermore, I cannot write directly: >> >> > hasEffect :: Exp Effect () >> > hasEffect = ReadAccount >> >> >> Do you have a better idea? >> >> >> >> On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper wrote: >> >>> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont >>> wrote: >>> > you should be able to run an effectless monad in an effectful one. >>> > How to encode this semantic? >>> >>> In LVish we just have a `liftQD` operation that will let you lift a >>> deterministic computation to a quasi-deterministic one (recall that >>> deterministic computations can perform fewer effects): >>> >>> liftQD :: Par Det s a -> Par QuasiDet s a >>> >>> So, analogously, you could have a `liftEff` and then write `liftEff >>> noEff`. This is also a little bit ugly, but you may find you don't >>> have to do it very often (we rarely use `liftQD`). >>> >>> Lindsey >>> >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jake.mcarthur at gmail.com Thu Feb 6 20:35:27 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Thu, 6 Feb 2014 15:35:27 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: I still think GADTs are a bit too much for this problem. Just using type classes provides all the safety you need and even avoids the need for that liftEval function. {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} module DSLEffects where import Control.Monad.State import Control.Monad.Reader class Monad m => Nomex m where readAccount :: m Int class Nomex m => NomexEffect m where writeAccount :: Int -> m () setVictory :: (forall m. Nomex m => m Bool) -> m () data Game = Game { victory :: (forall m. Nomex m => m Bool) , account :: Int } newtype Eval a = Eval { eval :: State Game a } deriving Monad instance Nomex Eval where readAccount = Eval $ gets account instance NomexEffect Eval where writeAccount n = Eval . modify $ \game -> game { account = n } setVictory v = Eval . modify $ \game -> game { victory = v } newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } deriving Monad instance Nomex EvalNoEffect where readAccount = EvalNoEffect $ asks account noEff :: Nomex m => m () noEff = return () hasEff :: NomexEffect m => m () hasEff = readAccount >>= writeAccount On Thu, Feb 6, 2014 at 12:47 PM, adam vogt wrote: > Hi Corentin, > > You need change Effect to NoEffect to reuse the evalNoEffect: > > > eval ReadAccount = liftEval $ evalNoEffect ReadAccount > > eval (Return a) = liftEval $ evalNoEffect (Return a) > > Or use a function like `unsafeCoerce :: Nomex Effect a -> Nomex NoEffect > a`. > > If you rename the types that tag effects to something that describes > exactly what the tags actually represent, maybe the above definition will > be more satisfying: > > > data Effects > > = > HasBeenCombinedWithSomethingThatHasEffectsButICan'tBeSureItActuallyHasEffectsAllByItself > > | DefinitelyHasNoEffects > > > Regards, > Adam > > > On Thu, Feb 6, 2014 at 9:50 AM, Corentin Dupont > wrote: > >> Hi guys, >> I'm still exploring some design space for DSLs, following our interesting >> discussion. >> >> I'm trying to write the evaluator for the DSL (see below). >> For the general case, the evaluator looks like: >> >> eval :: Nomex r a -> State Game a >> >> This eval function takes an expression (called Nomex), that can possibly >> have effects. >> It returns a state monad, to allow you to modify the game state. >> >> But for effectless instructions, it would be better to run the evaluator >> in the reader monad: >> >> evalNoEffect :: Nomex NoEffect a -> Reader Game a >> >> So you can have additional guaranties that evaluating your expression >> will not have effects. >> I tried (see below), but it doesn't work for the moment: >> >> >> > {-# LANGUAGE GADTs #-} >> >> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, >> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, >> UndecidableInstances #-} >> >> > module DSLEffects where >> >> > import Control.Monad.Error >> > import Control.Monad.State >> > import Control.Monad.Reader >> > import Data.Typeable >> >> This is the DSL: >> >> > data Effects = Effect | NoEffect >> >> > data Nomex :: Effects -> * -> * where >> > ReadAccount :: Nomex r Int --ReadAccount has no >> effect: it can be run in whatever monad >> > WriteAccount :: Int -> Nomex Effect () --WriteAccount has effect >> > SetVictory :: Nomex NoEffect Bool -> Nomex Effect () --SetVictory >> don't accept effectful computations >> > Bind :: Nomex m a -> (a -> Nomex m b) -> Nomex m b >> > Return :: a -> Nomex r a --wrapping a constant has no effect >> >> > instance Monad (Nomex a) where >> > return = Return >> > (>>=) = Bind >> >> >> > noEff :: Nomex NoEffect () >> > noEff = return () >> >> > hasEffect :: Nomex Effect () >> > hasEffect = do >> > a <- ReadAccount >> > WriteAccount a >> >> > data Game = Game { victory :: Nomex NoEffect Bool, >> > account :: Int} >> >> >> > eval :: Nomex r a -> State Game a >> > eval a at ReadAccount = liftEval $ evalNoEffect a >> > eval (WriteAccount a) = modify (\g -> g{account = a}) >> >> > eval (SetVictory v) = modify (\g -> g{victory = v}) >> > eval a@(Return _) = liftEval $ evalNoEffect a >> > eval (Bind exp f) = eval exp >>= eval . f >> >> > evalNoEffect :: Nomex NoEffect a -> Reader Game a >> > evalNoEffect ReadAccount = asks account >> > evalNoEffect (Return a) = return a >> > evalNoEffect (Bind exp f) = evalNoEffect exp >>= evalNoEffect . f >> >> > liftEval :: Reader Game a -> State Game a >> > liftEval r = get >>= return . runReader r >> >> >> This is not compiling: >> >> exceptEffect.lhs:60:15: >> Couldn't match type 'NoEffect with 'Effect >> Inaccessible code in >> a pattern with constructor >> WriteAccount :: Int -> Nomex 'Effect (), >> in an equation for `evalEffect' >> In the pattern: WriteAccount a >> In an equation for `evalEffect': >> evalEffect (WriteAccount a) = modify (\ g -> g {account = a}) >> >> It seems that the type of effectless computations (NoEffect) leaks in the >> type of effectful ones (due to the pattern matching)... >> >> Thanks, >> Corentin >> >> >> >> On Mon, Feb 3, 2014 at 12:44 PM, Corentin Dupont < >> corentin.dupont at gmail.com> wrote: >> >>> I saw that to write liftQD you decontruct (unwrap) the type and >>> reconstruct it. >>> I don't know if I can do that for my Exp (which is a full DSL)... >>> >>> Anyway, there should be a way to encode the Effect/NoEffect semantic at >>> type level... >>> Using Oleg's parametrized monad idea ( >>> http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), >>> I tried: >>> >>> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs >>> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, >>> UndecidableInstances #-} >>> >>> > module DSLEffects where >>> > import Prelude hiding (return, (>>), (>>=)) >>> > import Control.Monad.Parameterized >>> >>> This data type will be promoted to kind level (thanks to DataKinds): >>> >>> >>> > data Eff = Effect | NoEffect >>> >>> This class allows to specify the semantic on Effects (Effect + NoEffect >>> = Effect): >>> >>> > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r >>> > instance Effects Effect n Effect >>> > instance Effects NoEffect n n >>> >>> This is the DSL: >>> >>> > data Exp :: Eff -> * -> * where >>> > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect >>> > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect >>> > Const :: a -> Exp r a >>> > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r >>> b --Bind comes with a semantic on effects >>> > Fmap :: (a -> b) -> Exp m a -> Exp m b >>> >>> > instance Functor (Exp r) where >>> > fmap = Fmap >>> >>> > instance Return (Exp r) where >>> > returnM = Const >>> >>> > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where >>> > (>>=) = Bind >>> >>> > noEff :: Exp NoEffect () >>> > noEff = returnM () >>> >>> > hasEffect :: Exp Effect () >>> > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) >>> >>> This is working more or less, however I am obliged to put the type >>> signature on the returnM (last line): why? >>> Furthermore, I cannot write directly: >>> >>> > hasEffect :: Exp Effect () >>> > hasEffect = ReadAccount >>> >>> >>> Do you have a better idea? >>> >>> >>> >>> On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper wrote: >>> >>>> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont >>>> wrote: >>>> > you should be able to run an effectless monad in an effectful one. >>>> > How to encode this semantic? >>>> >>>> In LVish we just have a `liftQD` operation that will let you lift a >>>> deterministic computation to a quasi-deterministic one (recall that >>>> deterministic computations can perform fewer effects): >>>> >>>> liftQD :: Par Det s a -> Par QuasiDet s a >>>> >>>> So, analogously, you could have a `liftEff` and then write `liftEff >>>> noEff`. This is also a little bit ugly, but you may find you don't >>>> have to do it very often (we rarely use `liftQD`). >>>> >>>> Lindsey >>>> >>> >>> >> > > _______________________________________________ > 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 tikhon at jelv.is Fri Feb 7 02:53:00 2014 From: tikhon at jelv.is (Tikhon Jelvis) Date: Thu, 6 Feb 2014 18:53:00 -0800 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: For what it's worth, OCaml's Core library does this with _exn, so they would call a partial last "last_exn". I would actually prefer an abbreviation of some sort (like exn) as long as it's a consistent convention. Using a full word like "exception" or "partial" adds to much noise in my opinion, especially if the base name (like "last") is shorter than the suffix! Also, I think a suffix would be better than a prefix, if only to group things conveniently when sorted alphabetically. On Thu, Jan 30, 2014 at 9:36 AM, Atze van der Ploeg wrote: > 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 >> >> > _______________________________________________ > 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 michael at snoyman.com Fri Feb 7 02:59:36 2014 From: michael at snoyman.com (Michael Snoyman) Date: Fri, 7 Feb 2014 04:59:36 +0200 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: Thanks for the input. We ended up going with an `Ex` suffix, e.g. headEx, lastEx. On Fri, Feb 7, 2014 at 4:53 AM, Tikhon Jelvis wrote: > For what it's worth, OCaml's Core library does this with _exn, so they > would call a partial last "last_exn". I would actually prefer an > abbreviation of some sort (like exn) as long as it's a consistent > convention. Using a full word like "exception" or "partial" adds to much > noise in my opinion, especially if the base name (like "last") is shorter > than the suffix! > > Also, I think a suffix would be better than a prefix, if only to group > things conveniently when sorted alphabetically. > > > On Thu, Jan 30, 2014 at 9:36 AM, Atze van der Ploeg wrote: > >> 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 >>> >>> >> _______________________________________________ >> 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 zefciu at gmail.com Fri Feb 7 08:08:20 2014 From: zefciu at gmail.com (=?UTF-8?B?U3p5bW9uIFB5xbxhbHNraQ==?=) Date: Fri, 07 Feb 2014 09:08:20 +0100 Subject: [Haskell-cafe] Filing bugs for haskell packages Message-ID: <52F49474.8080102@gmail.com> Hello! I am new to haskell and I found a bug in package http://hackage.haskell.org/package/regex-compat-0.92/docs/Text-Regex.html On the hackage page it says that the maintainer e-mail of this package is: libraries at haskell.org. So i sent a bug report there, but bounced back to me because of quota. So apparently nobody reads these e-mails. How can I file a bug report for this package? I don't feel good enough in haskell to try and fix it myself. Greetings Szymon Py?alski From chrisyco+haskell-cafe at gmail.com Fri Feb 7 08:14:31 2014 From: chrisyco+haskell-cafe at gmail.com (Chris Wong) Date: Fri, 7 Feb 2014 21:14:31 +1300 Subject: [Haskell-cafe] Filing bugs for haskell packages In-Reply-To: <52F49474.8080102@gmail.com> References: <52F49474.8080102@gmail.com> Message-ID: Hi Szymon, I can't answer your question directly, but if you want a less buggy regex library regex-tdfa[1] is a fine choice. [1] http://hackage.haskell.org/package/regex-tdfa On Fri, Feb 7, 2014 at 9:08 PM, Szymon Py?alski wrote: > Hello! > > I am new to haskell and I found a bug in package > http://hackage.haskell.org/package/regex-compat-0.92/docs/Text-Regex.html > > On the hackage page it says that the maintainer e-mail of this package is: > libraries at haskell.org. So i sent a bug report there, but bounced back to me > because of quota. So apparently nobody reads these e-mails. > > How can I file a bug report for this package? I don't feel good enough in > haskell to try and fix it myself. > > Greetings > Szymon Py?alski > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Chris Wong, fixpoint conjurer e: lambda.fairy at gmail.com w: http://lfairy.github.io From mle+hs at mega-nerd.com Fri Feb 7 08:18:31 2014 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Fri, 7 Feb 2014 19:18:31 +1100 Subject: [Haskell-cafe] Filing bugs for haskell packages In-Reply-To: <52F49474.8080102@gmail.com> References: <52F49474.8080102@gmail.com> Message-ID: <20140207191831.07e23f621fb61dc7eba149b9@mega-nerd.com> Szymon Py?alski wrote: > I am new to haskell and I found a bug in package > http://hackage.haskell.org/package/regex-compat-0.92/docs/Text-Regex.html > > On the hackage page it says that the maintainer e-mail of this package > is: libraries at haskell.org. So i sent a bug report there, but bounced > back to me because of quota. Thats likely to be a transitory issue. > So apparently nobody reads these e-mails. They very definitely do. libraries at haskell.org is as mailing list which has dozens of subscribers and usually sees a couple of emails a day. > How can I file a bug report for this package? Wait a day or so and try sending to the libraries list again. Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From roma at ro-che.info Fri Feb 7 08:20:13 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Fri, 7 Feb 2014 10:20:13 +0200 Subject: [Haskell-cafe] Filing bugs for haskell packages In-Reply-To: <52F49474.8080102@gmail.com> References: <52F49474.8080102@gmail.com> Message-ID: <20140207082013.GA7240@sniper> Hi Szymon, * Szymon Py?alski [2014-02-07 09:08:20+0100] > I am new to haskell and I found a bug in package http://hackage.haskell.org/package/regex-compat-0.92/docs/Text-Regex.html > > On the hackage page it says that the maintainer e-mail of this > package is: libraries at haskell.org. Where does it say that? The page http://hackage.haskell.org/package/regex-compat lists TextRegexLazy at ... as the maintainer's email. > So i sent a bug report there, but bounced back to me because of quota. > So apparently nobody reads these e-mails. libraries at haskell.org is a public Haskell mailing list. If you want to send emails there, you have to subscribe first. http://www.haskell.org/mailman/listinfo/libraries > How can I file a bug report for this package? I don't feel good > enough in haskell to try and fix it myself. IIUC, regex-compat is a compatibility layer on top of regex-posix. Is there any reason you're not using regex-posix directly? (Of course, I cannot tell whether the bug you've hit is in regex-posix or is introduced by regex-compat.) Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From mle+hs at mega-nerd.com Fri Feb 7 08:22:58 2014 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Fri, 7 Feb 2014 19:22:58 +1100 Subject: [Haskell-cafe] Filing bugs for haskell packages In-Reply-To: <20140207191831.07e23f621fb61dc7eba149b9@mega-nerd.com> References: <52F49474.8080102@gmail.com> <20140207191831.07e23f621fb61dc7eba149b9@mega-nerd.com> Message-ID: <20140207192258.703c1b6c86dd75a3ef0891f0@mega-nerd.com> Erik de Castro Lopo wrote: > > On the hackage page it says that the maintainer e-mail of this package > > is: libraries at haskell.org. So i sent a bug report there, but bounced > > back to me because of quota. > > Thats likely to be a transitory issue. Actually no, you probably got a message like: > You are not allowed to post to this mailing list, and your message has > been automatically rejected. If you think that your messages are > being rejected in error, contact the mailing list owner at > libraries-owner at haskell.org. because the list only accepts emails from people who are subscribed to the list. YOu can subscribe here: http://www.haskell.org/mailman/listinfo/libraries Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From chriswarbo at googlemail.com Fri Feb 7 14:27:07 2014 From: chriswarbo at googlemail.com (Chris Warburton) Date: Fri, 07 Feb 2014 14:27:07 +0000 Subject: [Haskell-cafe] Lazy Lambda Calculus implementation Message-ID: <86d2izroas.fsf@gmail.com> Hello all, I've written the following implementation of Lambda Calculus, which will evaluate its Terms non-strictly. I've verified this since the Y combinator works without diverging: data Term a = Const a | Var Nat | Lam (Term a) | Term a :@ Term a data Val a = C a | F (Partial (Val a) -> Partial (Val a)) type Env a = [Partial (Val a)] eval' :: Term a -> Env a -> Partial (Val a) eval' (Const c) env = Now (C c) eval' (Var n) env = let Just x = lookUp env n in x eval' (Lam f) env = Now (F (\a -> eval' f (a:env))) eval' (f :@ x) env = do F f' <- eval' f env Later (f' (eval' x env)) eval t = eval' [] t Nat, Partial, lookUp, etc. have pretty obvious implementations. My question is, will this behave lazily? In other words will the contents of the 'env' lists be shared between the different contexts, such that forcing an element the be evaluated twice will only perform the evaluation once? Note that the first "do" line is the only place where evaluation is forced. If anyone could point out an 'obvious' reason why it will or will not be shared, or approaches I can take to check or infer this myself (eg. a Term which would show wildly different RAM usage in each case), I'd be very interested to know. I'd also be interested if someone spots a bug ;) For those who are curious, the code is living at https://gitorious.org/lazy-lambda-calculus and I've written a blog post detailing the iteration's I've been through at http://chriswarbo.net/index.php?page=news&type=view&id=admin-s-blog%2Flazy-lambda-calculus Cheers, Chris From agocorona at gmail.com Fri Feb 7 14:51:38 2014 From: agocorona at gmail.com (Alberto G. Corona ) Date: Fri, 7 Feb 2014 15:51:38 +0100 Subject: [Haskell-cafe] STM and unsafePerformIO/bracket In-Reply-To: <20140204140611.GA3202@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> References: <20140204140611.GA3202@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Message-ID: I use this trick, that unlike the previous workarounds permits concurrency and does handle the IO computation in a civilized way, that is, it permits brackets and so on: notReallySafeButNotAsUnsafeAsUnsafeIOToSTM= safeIOToSTM safeIOToSTM ? IO a ? STM a safeIOToSTM req= unsafeIOToSTM $ do tv ? newEmptyMVar forkIO $ (req ? putMVar tv . Right) `Control.Exception.catch` (?(e ? SomeException) ? putMVar tv $ Left e ) r ? takeMVar tv case r of Right x ? return x Left e ? throw e Here the IO computation is run in another thread. Even If the STM transaction is aborted, the IO computation finalizes. If the STM transaction is retried, the IO computation is re-executed, so it is up to you to take this into account depending on what you intend to do. If the IO computation throws an exception the STM transaction throws it. As far as I remember, this trick was used in a package time ago to do solve the problem. 2014-02-04 Bertram Felgenhauer : > Rob Leslie wrote: > > I?ve run into a difficulty I?d appreciate some advice to solve. > [unsafePerformIO and bracket, within an STM transaction] > > There's a long-standing bug report for this issue, > > https://ghc.haskell.org/trac/ghc/ticket/2401 > > So the current situation is that bracket within unsafePerformIO > (and unsafeIOToSTM) and STM transactions don't mix. I'm a bit > surprised that this doesn't bite more people. > > Cheers, > > Bertram > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Alberto. -------------- next part -------------- An HTML attachment was scrubbed... URL: From hanooter at gmail.com Fri Feb 7 18:07:43 2014 From: hanooter at gmail.com (Kyle Hanson) Date: Fri, 7 Feb 2014 10:07:43 -0800 Subject: [Haskell-cafe] ANN: Wheb -- A WAI framework Message-ID: Hello all, I was rather frustrated with the use of Template Haskell as the main entry point for the big framework projects (Yesod, Snap, etc.) While these frameworks offer template-free options, they seem like second class citizens. So I started work on Wheb with the goal that out of the box I could start a project quickly, without Template Haskell and without the dreaded long list of Language Pragma's at the top. I was inspired by the simplicity of the Scotty project which showed how easy a Haskell server could be to write. I have included a couple of plugin examples for handling Auth and Sessions. Wheb is database and template agnostic, but I plan to write some plugins soon to make it easier to use the major libraries with Wheb. I just started work on it last weekend but wanted to share my progress. Take a look if it interests you! http://hackage.haskell.org/package/Wheb-0.0.1.1 https://github.com/hansonkd/Wheb-Framework Thanks, Kyle Hanson -------------- next part -------------- An HTML attachment was scrubbed... URL: From ltclifton at gmail.com Sat Feb 8 01:13:07 2014 From: ltclifton at gmail.com (Luke Clifton) Date: Sat, 8 Feb 2014 09:13:07 +0800 Subject: [Haskell-cafe] ANN: Wheb -- A WAI framework In-Reply-To: References: Message-ID: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> > I was rather frustrated with the use of Template Haskell as the main entry point for the big framework projects (Yesod, Snap, etc.) Perhaps slightly off topic, but can someone outline why Template Haskell has so much negativity? I've used Yesod a bit, and from my limited experience, the TH does a good job at removing a lot of boilerplate code, while still keeping things readable and type safe. The main negatives I see are somewhat complicated error messages if you make a mistake, but the issue is usually pretty easy to spot because the TH is pretty simple. Is portability an issue? How do the other Haskell compilers go with it? Not to detract from your work, I think it's great to have options! I'm just curious. From cdsmith at gmail.com Sat Feb 8 02:03:33 2014 From: cdsmith at gmail.com (Chris Smith) Date: Fri, 7 Feb 2014 18:03:33 -0800 Subject: [Haskell-cafe] ANN: Wheb -- A WAI framework In-Reply-To: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> References: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> Message-ID: The main disadvantage of TH for me is that it's not amenable to static analysis or reasoning. Because the meaning of a TH splice is in no way related to its type, it both breaks tools, and breaks my patterns of understanding how things work by navigating the consistent generated documentation on Hackage. There are also portability concerns. Not with non-GHC compilers (no one uses anything but GHC), but with cross-compiling and such, including projects like GHCJS (last time I checked anyway). On Feb 7, 2014 5:14 PM, "Luke Clifton" wrote: > > > I was rather frustrated with the use of Template Haskell as the main > entry point for the big framework projects (Yesod, Snap, etc.) > > Perhaps slightly off topic, but can someone outline why Template Haskell > has so much negativity? > > I've used Yesod a bit, and from my limited experience, the TH does a good > job at removing a lot of boilerplate code, while still keeping things > readable and type safe. > > The main negatives I see are somewhat complicated error messages if you > make a mistake, but the issue is usually pretty easy to spot because the TH > is pretty simple. > > Is portability an issue? How do the other Haskell compilers go with it? > > Not to detract from your work, I think it's great to have options! I'm > just curious. > _______________________________________________ > 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 hanooter at gmail.com Sat Feb 8 03:43:45 2014 From: hanooter at gmail.com (Kyle Hanson) Date: Fri, 7 Feb 2014 19:43:45 -0800 Subject: [Haskell-cafe] ANN: Wheb -- A WAI framework In-Reply-To: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> References: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> Message-ID: Hi Luke! I can tell you why I didn't want to include TH. You are correct that TH does have many benefits and does indeed make a lot of things easier in Haskell. However, easier does not always mean more understandable. Haskell has a pretty steep learning curve. Just learning the core Haskell98 is pretty difficult to grasp for a beginner. Adding TH haskell on top of that is bad news. There is an inherit disconnect between a template haskell function and the code it generates, because you can't see it. Type signatures in Haskell provide much more than hints to the compiler about types, they are also a good source of documentation. That is why I hate TH functions. Take for example Yesod's mkYesod type signature: *mkYesod :: String -> [Resource String] -> Q [Dec]* That doesn't give me any information about what to expect as a result. About the only way to know how to use this function is to find examples of it or start digging into the code. It would probably help some if it were standard practice for package maintainers to put the expected type-signatures along with the TH functions. Another problem that I see is that TH is not that discoverable. I would wager that most Haskell users know how to use Template Haskell functions but not how to implement them. TH is a sort of black box if you are beginner where you can't look at the source code for a TH function because once you look under the hood, it a bunch of VarTs, ConsTs, Decs. -- Kyle Hanson On Fri, Feb 7, 2014 at 5:13 PM, Luke Clifton wrote: > > > I was rather frustrated with the use of Template Haskell as the main > entry point for the big framework projects (Yesod, Snap, etc.) > > Perhaps slightly off topic, but can someone outline why Template Haskell > has so much negativity? > > I've used Yesod a bit, and from my limited experience, the TH does a good > job at removing a lot of boilerplate code, while still keeping things > readable and type safe. > > The main negatives I see are somewhat complicated error messages if you > make a mistake, but the issue is usually pretty easy to spot because the TH > is pretty simple. > > Is portability an issue? How do the other Haskell compilers go with it? > > Not to detract from your work, I think it's great to have options! I'm > just curious. -------------- next part -------------- An HTML attachment was scrubbed... URL: From miguelimo38 at yandex.ru Sat Feb 8 09:19:42 2014 From: miguelimo38 at yandex.ru (MigMit) Date: Sat, 8 Feb 2014 13:19:42 +0400 Subject: [Haskell-cafe] ANN: Wheb -- A WAI framework In-Reply-To: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> References: <51A799E2-2E31-4859-8F5F-F243D61FFEC8@gmail.com> Message-ID: Haskell is itself quite good at removing boilerplate code. In fact, we Haskellers sometimes take pride in writing clean and boilerplate-free code. Forcing us to use metaprogramming undermines our pride. That's why Template Haskell is much more disliked than other forms of metaprogramming ? CPP, C++ templates, Lisp macros, Tcl, Forth, etc. It essentially boils down to this: Template Haskell is hated because Haskell itself is so damn good. Of course, if you have a shitty language to start with, then metaprogramming can only be seen as great help. Personally, I'm opposed to any form of metaprogramming. I prefer simplicity (says the guy who once asked SPJ if we're going to have polymorphic kinds), so I like having abstractions that semantically lie in the problem domain. Metaprogramming constructs, by definition, have their semantics defined in terms of the code they generate. I don't want to think about code. Ideally, I'd prefer not to see any code, but that's not on the plate right now. That's why I don't like metaprogramming, except for C++ templates, they have some sort of beautiful ugliness. On 08 Feb 2014, at 05:13, Luke Clifton wrote: > >> I was rather frustrated with the use of Template Haskell as the main entry point for the big framework projects (Yesod, Snap, etc.) > > Perhaps slightly off topic, but can someone outline why Template Haskell has so much negativity? > > I've used Yesod a bit, and from my limited experience, the TH does a good job at removing a lot of boilerplate code, while still keeping things readable and type safe. > > The main negatives I see are somewhat complicated error messages if you make a mistake, but the issue is usually pretty easy to spot because the TH is pretty simple. > > Is portability an issue? How do the other Haskell compilers go with it? > > Not to detract from your work, I think it's great to have options! I'm just curious. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From miguelimo38 at yandex.ru Sat Feb 8 09:23:56 2014 From: miguelimo38 at yandex.ru (MigMit) Date: Sat, 8 Feb 2014 13:23:56 +0400 Subject: [Haskell-cafe] ANN: Wheb -- A WAI framework In-Reply-To: References: Message-ID: Kyle, have you tried Happstack? It doesn't need Template Haskell, or a long list of pragmas, and it doesn't care what template or database engine you use. It's main disadvantage is that it's not WAI, which seems to be ideologically superior; I've heard (or imagined) that there were some plans to make it WAI. On 07 Feb 2014, at 22:07, Kyle Hanson wrote: > Hello all, > > I was rather frustrated with the use of Template Haskell as the main entry point for the big framework projects (Yesod, Snap, etc.) While these frameworks offer template-free options, they seem like second class citizens. So I started work on Wheb with the goal that out of the box I could start a project quickly, without Template Haskell and without the dreaded long list of Language Pragma's at the top. I was inspired by the simplicity of the Scotty project which showed how easy a Haskell server could be to write. > > I have included a couple of plugin examples for handling Auth and Sessions. Wheb is database and template agnostic, but I plan to write some plugins soon to make it easier to use the major libraries with Wheb. > > I just started work on it last weekend but wanted to share my progress. Take a look if it interests you! > > http://hackage.haskell.org/package/Wheb-0.0.1.1 > > https://github.com/hansonkd/Wheb-Framework > > Thanks, > Kyle Hanson > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From roma at ro-che.info Sat Feb 8 17:12:47 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Sat, 8 Feb 2014 19:12:47 +0200 Subject: [Haskell-cafe] An arrow transformer Message-ID: <20140208171247.GA783@sniper> I wrote (and found useful) the following arrow transformer: data Partial ar a b = Partial (ErrorArrow () ar a b) | Total (ar a b) toPartial :: ArrowChoice ar => Partial ar a b -> ErrorArrow () ar a b toPartial (Partial f) = f toPartial (Total sf) = liftError sf instance ArrowChoice ar => Category (Partial ar) where id = Total id Total f . Total g = Total $ f . g f . g = Partial $ toPartial f . toPartial g instance ArrowChoice ar => Arrow (Partial ar) where arr = Total . arr first (Total f) = Total $ first f first (Partial f) = Partial $ first f It allows to work with partial functions/arrows and at the same time tracks which of them are actually total. I wonder if it is already defined somewhere or is perhaps an instance of a more general construction. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From omari at smileystation.com Sat Feb 8 20:06:18 2014 From: omari at smileystation.com (Omari Norman) Date: Sat, 8 Feb 2014 15:06:18 -0500 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic Message-ID: Announcing deka, a library for decimal arithmetic. Why decimal arithmetic is important is discussed at length at http://speleotrove.com/decimal/ but for a short explanation, go into ghci and type: print $ 0.1 + 0.1 + 0.1 This is 0.3, right? But on my machine I get 0.3 plus a small fraction, which is simply not acceptable for applications where it is essential to get exact results, such as financial applications. deka is a binding to the decNumber C library, a thoroughly tested and fast implementation of decimal arithmetic. deka is fully tested and I encourage you to run the tests using the usual "cabal test" method. deka is available at http://hackage.haskell.org/package/deka and is on Github at https://github.com/massysett/deka Because deka is a binding to the decNumber C library, first you will need to install decNumber. An easy to install version with the GNU autotools is at: https://github.com/massysett/decnumber/releases decNumber's website is at http://speleotrove.com/decimal/decnumber.html A literate Haskell file illustrating the use of deka is available at https://github.com/massysett/deka/blob/master/lib/Data/Deka/Docs/Examples.lhs -------------- next part -------------- An HTML attachment was scrubbed... URL: From nicolas at incubaid.com Sat Feb 8 20:39:40 2014 From: nicolas at incubaid.com (Nicolas Trangez) Date: Sat, 08 Feb 2014 21:39:40 +0100 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic In-Reply-To: References: Message-ID: <1391891980.30777.1.camel@chi.nicolast.be> Note there's some existing support for this in `base`: On Sat, 2014-02-08 at 15:06 -0500, Omari Norman wrote: > but for a short explanation, go into ghci and type: > > print $ 0.1 + 0.1 + 0.1 ? print $ (0.1 + 0.1 + 0.1 :: Double) 0.30000000000000004 ? :m + Data.Fixed ? print $ (0.1 :: Fixed E1) + (0.1 :: Fixed E1) + (0.1 :: Fixed E1) 0.3 Nicolas From omari at smileystation.com Sat Feb 8 20:46:49 2014 From: omari at smileystation.com (Omari Norman) Date: Sat, 8 Feb 2014 15:46:49 -0500 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic In-Reply-To: <1391891980.30777.1.camel@chi.nicolast.be> References: <1391891980.30777.1.camel@chi.nicolast.be> Message-ID: On Sat, Feb 8, 2014 at 3:39 PM, Nicolas Trangez wrote: > Note there's some existing support for this in `base`: > > On Sat, 2014-02-08 at 15:06 -0500, Omari Norman wrote: > > but for a short explanation, go into ghci and type: > > > > print $ 0.1 + 0.1 + 0.1 > > ? print $ (0.1 + 0.1 + 0.1 :: Double) > 0.30000000000000004 > > ? :m + Data.Fixed > Key word there is "Fixed"; deka supports floating point with up to 34 digits of precision but, yes, Data.Fixed does solve some of this problem. -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Sat Feb 8 21:12:11 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Sat, 8 Feb 2014 23:12:11 +0200 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic In-Reply-To: References: <1391891980.30777.1.camel@chi.nicolast.be> Message-ID: <20140208211211.GA24002@sniper> * Omari Norman [2014-02-08 15:46:49-0500] > On Sat, Feb 8, 2014 at 3:39 PM, Nicolas Trangez wrote: > > > Note there's some existing support for this in `base`: > > > > On Sat, 2014-02-08 at 15:06 -0500, Omari Norman wrote: > > > but for a short explanation, go into ghci and type: > > > > > > print $ 0.1 + 0.1 + 0.1 > > > > ? print $ (0.1 + 0.1 + 0.1 :: Double) > > 0.30000000000000004 > > > > ? :m + Data.Fixed > > > > Key word there is "Fixed"; deka supports floating point with up to 34 > digits of precision but So it is fixed, too? I'm not sure "Fixed" qualifies as a key word, then :) Note that Data.Fixed doesn't put any restrictions on the (fixed) precision. You could easily define E34. So yeah, a comparison with Data.Fixed would be nice to see. Is deka faster? By how much? Does it support any additional operations? Which ones? Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From omari at smileystation.com Sat Feb 8 21:45:02 2014 From: omari at smileystation.com (Omari Norman) Date: Sat, 8 Feb 2014 16:45:02 -0500 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic In-Reply-To: <20140208211211.GA24002@sniper> References: <1391891980.30777.1.camel@chi.nicolast.be> <20140208211211.GA24002@sniper> Message-ID: On Sat, Feb 8, 2014 at 4:12 PM, Roman Cheplyaka wrote: > So it is fixed, too? I'm not sure "Fixed" qualifies as a key word, then :) > > Note that Data.Fixed doesn't put any restrictions on the (fixed) > precision. You could easily define E34. > No, it is not fixed. >>> digits . unDeka . fromJust . strToDeka $ "3.00" 3 >>> digits . unDeka . fromJust . strToDeka $ "3.0000" 5 The precision is determined at runtime. In contrast, with Data.Fixed, the programmer sets the precision at compile time. There is no difference between >>> 3 :: Fixed E6 and >>> 3.00 :: Fixed E6 These issues are discussed at http://speleotrove.com/decimal/decifaq1.html#tzeros but if your reaction is "so what, it's just some extra zeroes and at compile time I can just use E34", then by all means, keep using Fixed :) Also, note that you get 34 significant digits, but that doesn't mean the exponent is limited to 34. >>> let x = fromJust . strToDeka $ "3E-200" >>> let y = fromJust . strToDeka $ "4E-200" >>> x + y Deka {unDeka = 7E-200} ...which you could do in Fixed, true. If you defined E200 first. But, oops, now I need E250... Really this is a binding to decNumber, which implements the General Decimal Arithmetic Specification, so see if decNumber and that specification scratch an itch. If they don't, use Fixed, or Decimal (also on Hackage) or something else... -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Sat Feb 8 22:00:56 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 9 Feb 2014 00:00:56 +0200 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic In-Reply-To: References: <1391891980.30777.1.camel@chi.nicolast.be> <20140208211211.GA24002@sniper> Message-ID: <20140208220056.GA25797@sniper> * Omari Norman [2014-02-08 16:45:02-0500] > Also, note that you get 34 significant digits, but that doesn't mean the > exponent is limited to 34. > > >>> let x = fromJust . strToDeka $ "3E-200" > >>> let y = fromJust . strToDeka $ "4E-200" > >>> x + y > Deka {unDeka = 7E-200} > > ...which you could do in Fixed, true. If you defined E200 first. But, > oops, now I need E250... I see now. So this is a decimal floating-point numbers library, which also attempts to track the precision of numbers. Does this sound right? Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From omari at smileystation.com Sat Feb 8 23:25:37 2014 From: omari at smileystation.com (Omari Norman) Date: Sat, 8 Feb 2014 18:25:37 -0500 Subject: [Haskell-cafe] [ANN] deka - decimal arithmetic In-Reply-To: <20140208220056.GA25797@sniper> References: <1391891980.30777.1.camel@chi.nicolast.be> <20140208211211.GA24002@sniper> <20140208220056.GA25797@sniper> Message-ID: On Sat, Feb 8, 2014 at 5:00 PM, Roman Cheplyaka wrote: > * Omari Norman [2014-02-08 16:45:02-0500] > > Also, note that you get 34 significant digits, but that doesn't mean the > > exponent is limited to 34. > > > > >>> let x = fromJust . strToDeka $ "3E-200" > > >>> let y = fromJust . strToDeka $ "4E-200" > > >>> x + y > > Deka {unDeka = 7E-200} > > > > ...which you could do in Fixed, true. If you defined E200 first. But, > > oops, now I need E250... > > I see now. So this is a decimal floating-point numbers library, which > also attempts to track the precision of numbers. Does this sound right? That's roughly right, yes. I would say"attempts" is too soft a word. decNumber and, therefore, deka, tracks every significant digit and at least maintains that significance. If it trashes significant digits without notifying you, it's a bug; please report it. The differences between Data.Fixed and this library are so huge (Fixed manipulates Integers alone; decNumber stores numbers as binary-coded decimal coefficients and integer exponents) that I didn't even think to compare them, and I won't be the one to draw performance comparisons between the two because deka is for situations where solutions like Fixed are simply wrong. Fixed does me no good, no matter how fast it is, so there's no reason for me to know how it performs. -------------- next part -------------- An HTML attachment was scrubbed... URL: From aslatter at gmail.com Sun Feb 9 03:04:58 2014 From: aslatter at gmail.com (Antoine Latter) Date: Sat, 8 Feb 2014 21:04:58 -0600 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: What does "Ex" mean? On Thu, Feb 6, 2014 at 8:59 PM, Michael Snoyman wrote: > Thanks for the input. We ended up going with an `Ex` suffix, e.g. headEx, > lastEx. > > > On Fri, Feb 7, 2014 at 4:53 AM, Tikhon Jelvis wrote: > >> For what it's worth, OCaml's Core library does this with _exn, so they >> would call a partial last "last_exn". I would actually prefer an >> abbreviation of some sort (like exn) as long as it's a consistent >> convention. Using a full word like "exception" or "partial" adds to much >> noise in my opinion, especially if the base name (like "last") is shorter >> than the suffix! >> >> Also, I think a suffix would be better than a prefix, if only to group >> things conveniently when sorted alphabetically. >> >> >> On Thu, Jan 30, 2014 at 9:36 AM, Atze van der Ploeg wrote: >> >>> 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 >>>> >>>> >>> _______________________________________________ >>> 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.pennebaker at gmail.com Sun Feb 9 04:01:55 2014 From: andrew.pennebaker at gmail.com (Andrew Pennebaker) Date: Sat, 8 Feb 2014 23:01:55 -0500 Subject: [Haskell-cafe] Puppet module for installing cabal packages? Message-ID: I'm using Vagrant and Puppet to automate setting up development, testing, and production environments. For now, I'm executing shell commands to install my favorite Cabal packages (`cabal update`, `cabal install `), but I'd prefer to use something a bit more high level. Would anyone be interested in creating a Puppet module for Cabal? This could encourage more use of awesome packages like Darcs and ShellCheck by non-Haskellers. -- Cheers, Andrew Pennebaker www.yellosoft.us -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Sun Feb 9 05:25:40 2014 From: michael at snoyman.com (Michael Snoyman) Date: Sun, 9 Feb 2014 07:25:40 +0200 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: It means "throws an *ex*ception." On Sun, Feb 9, 2014 at 5:04 AM, Antoine Latter wrote: > What does "Ex" mean? > > > On Thu, Feb 6, 2014 at 8:59 PM, Michael Snoyman wrote: > >> Thanks for the input. We ended up going with an `Ex` suffix, e.g. headEx, >> lastEx. >> >> >> On Fri, Feb 7, 2014 at 4:53 AM, Tikhon Jelvis wrote: >> >>> For what it's worth, OCaml's Core library does this with _exn, so they >>> would call a partial last "last_exn". I would actually prefer an >>> abbreviation of some sort (like exn) as long as it's a consistent >>> convention. Using a full word like "exception" or "partial" adds to much >>> noise in my opinion, especially if the base name (like "last") is shorter >>> than the suffix! >>> >>> Also, I think a suffix would be better than a prefix, if only to group >>> things conveniently when sorted alphabetically. >>> >>> >>> On Thu, Jan 30, 2014 at 9:36 AM, Atze van der Ploeg wrote: >>> >>>> 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 >>>>> >>>>> >>>> _______________________________________________ >>>> 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 Sun Feb 9 05:54:03 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 9 Feb 2014 00:54:03 -0500 Subject: [Haskell-cafe] Puppet module for installing cabal packages? In-Reply-To: References: Message-ID: andrew, have at it! (if its a need you care about, whack at it and if you get stuck ask for help!) if you get stuck / hit any issues, shoot an email at cabal-devel at haskell.org or ask for help #hackage on IRC On Sat, Feb 8, 2014 at 11:01 PM, Andrew Pennebaker < andrew.pennebaker at gmail.com> wrote: > I'm using Vagrant and Puppet to > automate setting up development, testing, and production environments. For > now, I'm executing shell commands to install my favorite Cabal packages > (`cabal update`, `cabal install `), but I'd prefer to use > something a bit more high level. > > Would anyone be interested in creating a Puppet module for Cabal? This > could encourage more use of awesome packages like Darcs and ShellCheck by > non-Haskellers. > > -- > Cheers, > > Andrew Pennebaker > www.yellosoft.us > > _______________________________________________ > 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 slyich at gmail.com Sun Feb 9 07:00:21 2014 From: slyich at gmail.com (Sergei Trofimovich) Date: Sun, 9 Feb 2014 10:00:21 +0300 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140130163055.GA19868@sniper> References: <20140130163055.GA19868@sniper> Message-ID: <20140209100021.45f49428@sf> On Thu, 30 Jan 2014 18:30:55 +0200 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 Driven here by http://ro-che.info//articles/2014-02-08-my-haskell-will.html Now as regex-tdfa-1.2.0 is on hackage. What status of your regex-tdfa-rc? May I bug you with performance problems compared to regex-dfa? -- Sergei -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From roma at ro-che.info Sun Feb 9 07:32:45 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 9 Feb 2014 09:32:45 +0200 Subject: [Haskell-cafe] Unmaintained packages and hackage upload rights In-Reply-To: <20140209100021.45f49428@sf> References: <20140130163055.GA19868@sniper> <20140209100021.45f49428@sf> Message-ID: <20140209073245.GA29009@sniper> * Sergei Trofimovich [2014-02-09 10:00:21+0300] > Now as regex-tdfa-1.2.0 is on hackage. > > What status of your regex-tdfa-rc? Thanks for the reminder. I just marked it as deprecated in favor of regex-tdfa. > May I bug you with performance problems compared to regex-dfa? No, I don't know much about how it works. My sole reason for forking was to keep it buildable. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From difrumin at gmail.com Sun Feb 9 11:14:17 2014 From: difrumin at gmail.com (Daniil Frumin) Date: Sun, 9 Feb 2014 15:14:17 +0400 Subject: [Haskell-cafe] Package for regular expressions Message-ID: Hi, everyone! Due to the recent discussions discussions about regex- packages on libraries@ and cafe, as well as due to the unicode bug in darcs that Erik Kow and I have stumbled upon I wanted to ask the Haskell community the following: What is up with the regular expression packages? Which one is the go-to package? There are really a bunch of them around (regex-compat, regex-tdfa, regex-posicx, regex-compat-tdfa,, ..) and it's not obvious at all what is the difference between them and which one should I use. Any advice or comments are appreciated. Sincerely yours, -- Daniil Frumin From magnus at therning.org Sun Feb 9 12:28:23 2014 From: magnus at therning.org (Magnus Therning) Date: Sun, 9 Feb 2014 13:28:23 +0100 Subject: [Haskell-cafe] Installing Ghc 7.8 - ghc-split missing Message-ID: <20140209122823.GA30840@tatooine.lan> I've put together an experimental package of Ghc 7.8 for ArchLinux. It's pulling the sources from git (the branch ghc-7.8 from git.haskell.org) and it basically performs the following steps to build and install: ./sync-all -r git://git.haskell.org get -b ghc-7.8 ./boot ./configure --prefix=/usr make -j 5 make DESTDIR= install The build and install completes successfully, and some trivial tests work (compiling hello-world, playing a bit with ghci, that sort of thing). However, compiling mtl fails, with this message: Configuring mtl-2.1.2... Building mtl-2.1.2... Preprocessing library mtl-2.1.2... [ 1 of 21] Compiling Control.Monad.Writer.Class ( Control/Monad/Writer/Class.hs, dist/build/Control/Monad/Writer/Class.o ) ghc: could not execute: /usr/lib/ghc-7.8.0.20140204/ghc-split And indeed, ghc-split is not installed using `make install`. Is this a known bug? /M -- Magnus Therning OpenPGP: 0xAB4DFBA4 email: magnus at therning.org jabber: magnus at therning.org twitter: magthe http://therning.org/magnus I invented the term Object-Oriented, and I can tell you I did not have C++ in mind. -- Alan Kay -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 198 bytes Desc: not available URL: From simon at banquise.net Sun Feb 9 13:38:32 2014 From: simon at banquise.net (Simon Marechal) Date: Sun, 09 Feb 2014 14:38:32 +0100 Subject: [Haskell-cafe] Package for regular expressions In-Reply-To: References: Message-ID: <52F784D8.6060109@banquise.net> On 02/09/2014 12:14 PM, Daniil Frumin wrote: > What is up with the regular expression packages? Which one is the go-to package? > There are really a bunch of them around (regex-compat, regex-tdfa, > regex-posicx, regex-compat-tdfa,, ..) and it's not obvious at all what > is the difference between them and which one should I use. This might be outdated, but provides a good comparison : http://www.haskell.org/haskellwiki/Regular_expressions I went fairly quickly to regex-pcre-builtin, as it's actually Perl compatible, which I believe is the most common regex dialect in use. It is also straightforward to use. From omari at smileystation.com Sun Feb 9 15:15:07 2014 From: omari at smileystation.com (Omari Norman) Date: Sun, 9 Feb 2014 10:15:07 -0500 Subject: [Haskell-cafe] Package for regular expressions In-Reply-To: References: Message-ID: On Sun, Feb 9, 2014 at 6:14 AM, Daniil Frumin wrote: > > What is up with the regular expression packages? Which one is the go-to package? > There are really a bunch of them around (regex-compat, regex-tdfa, > regex-posicx, regex-compat-tdfa,, ..) and it's not obvious at all what > is the difference between them and which one should I use. The great bulk of those packages accompany regex-base. They provide "backends" which you then use through the pcre-base interface. pcre-base has a heavily overloaded interface. It's novel, but I think understanding what it is really doing is not at all straightforward. This is exemplified by the chapter about regular expressions in Real World Haskell, which dismisses explaining what one of the functions does with "As a result, the type signature of the (=~) operator is difficult to understand, so we will not explain it here." http://book.realworldhaskell.org/read/efficient-file-processing-regular-expressions-and-file-name-matching.html For something easier to understand, I recommend pcre-light. Its types are straightforward. From berdario at gmail.com Sun Feb 9 16:12:53 2014 From: berdario at gmail.com (Dario Bertini) Date: Sun, 9 Feb 2014 17:12:53 +0100 Subject: [Haskell-cafe] Package for regular expressions In-Reply-To: References: Message-ID: I kinda like regex-applicative https://github.com/feuerbach/regex-applicative -- xmpp: berdario at gmail.com bitmessage: BM-2cTYXfGiSTsnx3righ6aHcJSWe4MV17jDP gpg fingerprint: 3F8D53518012716C4EEF7DF67B498306B3BF75A0 (used just for signing commits) From aslatter at gmail.com Sun Feb 9 16:41:25 2014 From: aslatter at gmail.com (Antoine Latter) Date: Sun, 9 Feb 2014 10:41:25 -0600 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: Not that it matters, but I think I prefer the "Unsafe" suffix. I'm not calling this version of "head" because I *want* an exception - I'm calling it because I want "Unsafe" (non-typechecked) behavior - I'm asserting that I've already validated some preconditions that aren't reflected in the type. But on the other hand I've always found functions like "fromMaybe" easier to work with than functions like "fromJust". Enough bikeshedding! If it works in your packages that's fine, and these are the sort of functions I have no complaints about reimplementing on my own. On Sat, Feb 8, 2014 at 11:25 PM, Michael Snoyman wrote: > It means "throws an *ex*ception." > > > On Sun, Feb 9, 2014 at 5:04 AM, Antoine Latter wrote: > >> What does "Ex" mean? >> >> >> On Thu, Feb 6, 2014 at 8:59 PM, Michael Snoyman wrote: >> >>> Thanks for the input. We ended up going with an `Ex` suffix, e.g. >>> headEx, lastEx. >>> >>> >>> On Fri, Feb 7, 2014 at 4:53 AM, Tikhon Jelvis wrote: >>> >>>> For what it's worth, OCaml's Core library does this with _exn, so they >>>> would call a partial last "last_exn". I would actually prefer an >>>> abbreviation of some sort (like exn) as long as it's a consistent >>>> convention. Using a full word like "exception" or "partial" adds to much >>>> noise in my opinion, especially if the base name (like "last") is shorter >>>> than the suffix! >>>> >>>> Also, I think a suffix would be better than a prefix, if only to group >>>> things conveniently when sorted alphabetically. >>>> >>>> >>>> On Thu, Jan 30, 2014 at 9:36 AM, Atze van der Ploeg wrote: >>>> >>>>> 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 >>>>>> >>>>>> >>>>> _______________________________________________ >>>>> 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 roma at ro-che.info Sun Feb 9 16:44:56 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Sun, 9 Feb 2014 18:44:56 +0200 Subject: [Haskell-cafe] Package for regular expressions In-Reply-To: References: Message-ID: <20140209164456.GA4815@sniper> * Dario Bertini [2014-02-09 17:12:53+0100] > I kinda like regex-applicative > > https://github.com/feuerbach/regex-applicative It is rather slow compared to ordinary regex packages. (Although it is more powerful, as it allows real parsing.) Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From m at j4.pe Sun Feb 9 17:46:43 2014 From: m at j4.pe (m at j4.pe) Date: Sun, 09 Feb 2014 18:46:43 +0100 Subject: [Haskell-cafe] haskell-search.org | research tools for Haskell Message-ID: <87mwi0b2m4.fsf@x220.j4.pe> Hello, I would like to introduce http://haskell-search.org/. The idea is to index the most common Haskell sites to facilitate research on Haskell. It is a version for testing. If you like it, I can leave it running. Regards From fuuzetsu at fuuzetsu.co.uk Sun Feb 9 18:15:03 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sun, 09 Feb 2014 18:15:03 +0000 Subject: [Haskell-cafe] haskell-search.org | research tools for Haskell In-Reply-To: <87mwi0b2m4.fsf@x220.j4.pe> References: <87mwi0b2m4.fsf@x220.j4.pe> Message-ID: <52F7C5A7.7050903@fuuzetsu.co.uk> On 09/02/14 17:46, m at j4.pe wrote: > > Hello, > > I would like to introduce http://haskell-search.org/. The idea is to > index the most common Haskell sites to facilitate research on > Haskell. It is a version for testing. If you like it, I can leave it > running. > > Regards > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Hi, I have found a 2 bugs and 2 annoyances in the first 20 seconds. First bug: 1. Go to the main page 2. Type something in the search, such as ?functor? and wait for the suggestion list to appear. 3. Press return We now get results but the suggestion list stays open, resulting in the results being obscured. Second bug: The ?Previous? button is always clickable even if we're on the first page. First annoyance: It's all a single page! The browser ?back? buttons &c do not work! Please stop this if at all possible, it makes browsing close to impossible. It's the same thing with the ?Next? and ?Previous? buttons. Same for results with 0 pages. Second annoyance: We're not told which page we're on at all. Let me know if you prefer these as bugs on GitHub instead. Other than those problems, I think this might turn out to be useful although it definitely needs some usability polish. PS: It'd be much cooler if the code running the site was in Haskell! -- Mateusz K. From m at j4.pe Sun Feb 9 18:27:04 2014 From: m at j4.pe (m at j4.pe) Date: Sun, 09 Feb 2014 19:27:04 +0100 Subject: [Haskell-cafe] haskell-search.org | research tools for Haskell In-Reply-To: <52F7C5A7.7050903@fuuzetsu.co.uk> References: <87mwi0b2m4.fsf@x220.j4.pe> <52F7C5A7.7050903@fuuzetsu.co.uk> Message-ID: <871tzcywef.fsf@x220.j4.pe> You can add the bugs on github this will push me to solve it. At the moment this is a POC. The principle is very simple. HTML / JS to call a REST webservice (i use www.open-search-server.com). I can write the front with Yesod or Snap but rewrite the search engine in haskell is just impossible for me. Before I want to see if it useful or not. regards fuuzetsu at fuuzetsu.co.uk writes: > On 09/02/14 17:46, m at j4.pe wrote: >> >> Hello, >> >> I would like to introduce http://haskell-search.org/. The idea is to >> index the most common Haskell sites to facilitate research on >> Haskell. It is a version for testing. If you like it, I can leave it >> running. >> >> Regards _______________________________________________ Haskell-Cafe >> mailing list Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > Hi, > > I have found a 2 bugs and 2 annoyances in the first 20 seconds. First > bug: > > 1. Go to the main page 2. Type something in the search, such as > ?functor? and wait for the suggestion list to appear. 3. Press return > > We now get results but the suggestion list stays open, resulting in > the results being obscured. > > Second bug: The ?Previous? button is always clickable even if we're on > the first page. > > First annoyance: It's all a single page! The browser ?back? buttons &c > do not work! Please stop this if at all possible, it makes browsing > close to impossible. It's the same thing with the ?Next? and > ?Previous? buttons. Same for results with 0 pages. > > Second annoyance: We're not told which page we're on at all. > > Let me know if you prefer these as bugs on GitHub instead. > > Other than those problems, I think this might turn out to be useful > although it definitely needs some usability polish. > > PS: It'd be much cooler if the code running the site was in Haskell! From tyler.huffman at tylerh.org Mon Feb 10 02:50:55 2014 From: tyler.huffman at tylerh.org (Tyler Huffman) Date: Sun, 9 Feb 2014 19:50:55 -0700 Subject: [Haskell-cafe] Master's Thesis: Open areas of research in Haskell Message-ID: Hello all! Beginning in September, I'll begin my Master's program in Computer Science, and I'm completely set on doing my thesis in some form of functional programming and/or Haskell. I've seen the Internship opportunities and areas of research for GHC (https://ghc.haskell.org/trac/ghc/wiki/Internships) but they all seem to apply to Ph.D candidates. That said, are there open areas of research that I could look into, or more resources in Haskell that would be useful for a two-year program's research? I'm hoping to have a set thesis by the time I begin my Master's program, which is why I'm giving myself six months in advance. Any help would be highly appreciated! Regards -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Mon Feb 10 05:38:17 2014 From: michael at snoyman.com (Michael Snoyman) Date: Mon, 10 Feb 2014 07:38:17 +0200 Subject: [Haskell-cafe] Naming scheme for partial functions In-Reply-To: References: Message-ID: I don't want to drag out bikeshedding either. But I *do* want to point out that mono-traversable also includes a function unsafeHead, separate from headEx. While headEx guarantees that it will throw an exception in the case of an empty Foldable, unsafeHead may crash your program. This is the same kind of distinction as vector and bytestring make between head and unsafeHead. On Sun, Feb 9, 2014 at 6:41 PM, Antoine Latter wrote: > Not that it matters, but I think I prefer the "Unsafe" suffix. I'm not > calling this version of "head" because I *want* an exception - I'm calling > it because I want "Unsafe" (non-typechecked) behavior - I'm asserting that > I've already validated some preconditions that aren't reflected in the type. > > But on the other hand I've always found functions like "fromMaybe" easier > to work with than functions like "fromJust". > > Enough bikeshedding! If it works in your packages that's fine, and these > are the sort of functions I have no complaints about reimplementing on my > own. > > > On Sat, Feb 8, 2014 at 11:25 PM, Michael Snoyman wrote: > >> It means "throws an *ex*ception." >> >> >> On Sun, Feb 9, 2014 at 5:04 AM, Antoine Latter wrote: >> >>> What does "Ex" mean? >>> >>> >>> On Thu, Feb 6, 2014 at 8:59 PM, Michael Snoyman wrote: >>> >>>> Thanks for the input. We ended up going with an `Ex` suffix, e.g. >>>> headEx, lastEx. >>>> >>>> >>>> On Fri, Feb 7, 2014 at 4:53 AM, Tikhon Jelvis wrote: >>>> >>>>> For what it's worth, OCaml's Core library does this with _exn, so they >>>>> would call a partial last "last_exn". I would actually prefer an >>>>> abbreviation of some sort (like exn) as long as it's a consistent >>>>> convention. Using a full word like "exception" or "partial" adds to much >>>>> noise in my opinion, especially if the base name (like "last") is shorter >>>>> than the suffix! >>>>> >>>>> Also, I think a suffix would be better than a prefix, if only to group >>>>> things conveniently when sorted alphabetically. >>>>> >>>>> >>>>> On Thu, Jan 30, 2014 at 9:36 AM, Atze van der Ploeg wrote: >>>>> >>>>>> 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 >>>>>>> >>>>>>> >>>>>> _______________________________________________ >>>>>> 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 ky3 at atamo.com Mon Feb 10 06:32:26 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 10 Feb 2014 13:32:26 +0700 Subject: [Haskell-cafe] Master's Thesis: Open areas of research in Haskell In-Reply-To: References: Message-ID: On Mon, Feb 10, 2014 at 9:50 AM, Tyler Huffman wrote: > I've seen the Internship opportunities and areas of research for GHC ( > https://ghc.haskell.org/trac/ghc/wiki/Internships) but they all seem to > apply to Ph.D candidates. > I wouldn't worry about these restrictions, they aren't set in stone. It's better to look at the slate of people (and what they've done, not their paper qualifications) who have actually gotten in previously to get a sense of the benchmark. If you've hacked GHC in interesting ways before applying, you'll definitely turn heads. > That said, are there open areas of research that I could look into > Skim the titles of previous years ICFP and Haskell Symposium proceedings. Read the abstracts. Look at the references. Does anything strike the eye? -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From dominique.devriese at cs.kuleuven.be Mon Feb 10 07:46:58 2014 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Mon, 10 Feb 2014 08:46:58 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Fully agree with Jake. Corentin's effect system is rather simple so that indexed monads are overkill here and Jake's solution is simpler. I just want to point out that the key component of Jake's proposed solution is not really type classes, but rather an (underappreciated) pattern that I call /effect polymorphism/: monadic computations that are polymorphic over the monad in which they produce effects: > noEff :: Nomex m => m () > noEff = return () > > hasEff :: NomexEffect m => m () > hasEff = readAccount >>= writeAccount I would say that type classes are not the key here, since you could use the same pattern, but replace type classes with dictionaries and get the same benefits, although with a bit more administration to be done by the user. Such computations have many useful properties, thanks to the parametricity of the polymorphic quantification. This has been well explained by Voigtlaender: http://wwwtcs.inf.tu-dresden.de/~voigt/icfp09.pdf. Effect polymorphism has also been used by Oliveira, Schrijvers and Cook in a model of (among other features) aspect composition: http://users.ugent.be/~tschrijv/Research/papers/jfp_mri.pdf. Note by the way that Jake's proposal is still compatible with the previously suggested solutions based on indexed monads, since you can write: instance Nomex (Exp r) where readAccount = ReadAccount instance NomexEffect (Exp Effect) where ... Regards, Dominique 2014-02-06 21:35 GMT+01:00 Jake McArthur : > I still think GADTs are a bit too much for this problem. Just using type > classes provides all the safety you need and even avoids the need for that > liftEval function. > > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > module DSLEffects where > > import Control.Monad.State > import Control.Monad.Reader > > class Monad m => Nomex m where > readAccount :: m Int > > class Nomex m => NomexEffect m where > writeAccount :: Int -> m () > setVictory :: (forall m. Nomex m => m Bool) -> m () > > data Game = Game { victory :: (forall m. Nomex m => m Bool) > , account :: Int > } > > newtype Eval a = Eval { eval :: State Game a } > deriving Monad > > instance Nomex Eval where > readAccount = Eval $ gets account > > instance NomexEffect Eval where > writeAccount n = Eval . modify $ \game -> game { account = n } > setVictory v = Eval . modify $ \game -> game { victory = v } > > newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } > deriving Monad > > instance Nomex EvalNoEffect where > readAccount = EvalNoEffect $ asks account > > > > > On Thu, Feb 6, 2014 at 12:47 PM, adam vogt wrote: >> >> Hi Corentin, >> >> You need change Effect to NoEffect to reuse the evalNoEffect: >> >> > eval ReadAccount = liftEval $ evalNoEffect ReadAccount >> > eval (Return a) = liftEval $ evalNoEffect (Return a) >> >> Or use a function like `unsafeCoerce :: Nomex Effect a -> Nomex NoEffect >> a`. >> >> If you rename the types that tag effects to something that describes >> exactly what the tags actually represent, maybe the above definition will be >> more satisfying: >> >> > data Effects >> > = >> > HasBeenCombinedWithSomethingThatHasEffectsButICan'tBeSureItActuallyHasEffectsAllByItself >> > | DefinitelyHasNoEffects >> >> >> Regards, >> Adam >> >> >> On Thu, Feb 6, 2014 at 9:50 AM, Corentin Dupont >> wrote: >>> >>> Hi guys, >>> I'm still exploring some design space for DSLs, following our interesting >>> discussion. >>> >>> I'm trying to write the evaluator for the DSL (see below). >>> For the general case, the evaluator looks like: >>> >>> eval :: Nomex r a -> State Game a >>> >>> This eval function takes an expression (called Nomex), that can possibly >>> have effects. >>> It returns a state monad, to allow you to modify the game state. >>> >>> But for effectless instructions, it would be better to run the evaluator >>> in the reader monad: >>> >>> evalNoEffect :: Nomex NoEffect a -> Reader Game a >>> >>> So you can have additional guaranties that evaluating your expression >>> will not have effects. >>> I tried (see below), but it doesn't work for the moment: >>> >>> >>> > {-# LANGUAGE GADTs #-} >>> >>> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, >>> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, >>> > UndecidableInstances #-} >>> >>> > module DSLEffects where >>> >>> > import Control.Monad.Error >>> > import Control.Monad.State >>> > import Control.Monad.Reader >>> > import Data.Typeable >>> >>> This is the DSL: >>> >>> > data Effects = Effect | NoEffect >>> >>> > data Nomex :: Effects -> * -> * where >>> > ReadAccount :: Nomex r Int --ReadAccount has no >>> > effect: it can be run in whatever monad >>> > WriteAccount :: Int -> Nomex Effect () --WriteAccount has effect >>> > SetVictory :: Nomex NoEffect Bool -> Nomex Effect () --SetVictory >>> > don't accept effectful computations >>> > Bind :: Nomex m a -> (a -> Nomex m b) -> Nomex m b >>> > Return :: a -> Nomex r a --wrapping a constant has no effect >>> >>> > instance Monad (Nomex a) where >>> > return = Return >>> > (>>=) = Bind >>> >>> >>> > noEff :: Nomex NoEffect () >>> > noEff = return () >>> >>> > hasEffect :: Nomex Effect () >>> > hasEffect = do >>> > a <- ReadAccount >>> > WriteAccount a >>> >>> > data Game = Game { victory :: Nomex NoEffect Bool, >>> > account :: Int} >>> >>> >>> > eval :: Nomex r a -> State Game a >>> > eval a at ReadAccount = liftEval $ evalNoEffect a >>> > eval (WriteAccount a) = modify (\g -> g{account = a}) >>> >>> > eval (SetVictory v) = modify (\g -> g{victory = v}) >>> > eval a@(Return _) = liftEval $ evalNoEffect a >>> > eval (Bind exp f) = eval exp >>= eval . f >>> >>> > evalNoEffect :: Nomex NoEffect a -> Reader Game a >>> > evalNoEffect ReadAccount = asks account >>> > evalNoEffect (Return a) = return a >>> > evalNoEffect (Bind exp f) = evalNoEffect exp >>= evalNoEffect . f >>> >>> > liftEval :: Reader Game a -> State Game a >>> > liftEval r = get >>= return . runReader r >>> >>> >>> This is not compiling: >>> >>> exceptEffect.lhs:60:15: >>> Couldn't match type 'NoEffect with 'Effect >>> Inaccessible code in >>> a pattern with constructor >>> WriteAccount :: Int -> Nomex 'Effect (), >>> in an equation for `evalEffect' >>> In the pattern: WriteAccount a >>> In an equation for `evalEffect': >>> evalEffect (WriteAccount a) = modify (\ g -> g {account = a}) >>> >>> It seems that the type of effectless computations (NoEffect) leaks in the >>> type of effectful ones (due to the pattern matching)... >>> >>> Thanks, >>> Corentin >>> >>> >>> >>> On Mon, Feb 3, 2014 at 12:44 PM, Corentin Dupont >>> wrote: >>>> >>>> I saw that to write liftQD you decontruct (unwrap) the type and >>>> reconstruct it. >>>> I don't know if I can do that for my Exp (which is a full DSL)... >>>> >>>> Anyway, there should be a way to encode the Effect/NoEffect semantic at >>>> type level... >>>> Using Oleg's parametrized monad idea >>>> (http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html), >>>> I tried: >>>> >>>> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs >>>> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, >>>> > UndecidableInstances #-} >>>> >>>> > module DSLEffects where >>>> > import Prelude hiding (return, (>>), (>>=)) >>>> > import Control.Monad.Parameterized >>>> >>>> This data type will be promoted to kind level (thanks to DataKinds): >>>> >>>> >>>> > data Eff = Effect | NoEffect >>>> >>>> This class allows to specify the semantic on Effects (Effect + NoEffect >>>> = Effect): >>>> >>>> > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r >>>> > instance Effects Effect n Effect >>>> > instance Effects NoEffect n n >>>> >>>> This is the DSL: >>>> >>>> > data Exp :: Eff -> * -> * where >>>> > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect >>>> > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect >>>> > Const :: a -> Exp r a >>>> > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r >>>> > b --Bind comes with a semantic on effects >>>> > Fmap :: (a -> b) -> Exp m a -> Exp m b >>>> >>>> > instance Functor (Exp r) where >>>> > fmap = Fmap >>>> >>>> > instance Return (Exp r) where >>>> > returnM = Const >>>> >>>> > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where >>>> > (>>=) = Bind >>>> >>>> > noEff :: Exp NoEffect () >>>> > noEff = returnM () >>>> >>>> > hasEffect :: Exp Effect () >>>> > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) >>>> >>>> This is working more or less, however I am obliged to put the type >>>> signature on the returnM (last line): why? >>>> Furthermore, I cannot write directly: >>>> >>>> > hasEffect :: Exp Effect () >>>> > hasEffect = ReadAccount >>>> >>>> >>>> Do you have a better idea? >>>> >>>> >>>> >>>> On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper >>>> wrote: >>>>> >>>>> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont >>>>> wrote: >>>>> > you should be able to run an effectless monad in an effectful one. >>>>> > How to encode this semantic? >>>>> >>>>> In LVish we just have a `liftQD` operation that will let you lift a >>>>> deterministic computation to a quasi-deterministic one (recall that >>>>> deterministic computations can perform fewer effects): >>>>> >>>>> liftQD :: Par Det s a -> Par QuasiDet s a >>>>> >>>>> So, analogously, you could have a `liftEff` and then write `liftEff >>>>> noEff`. This is also a little bit ugly, but you may find you don't >>>>> have to do it very often (we rarely use `liftQD`). >>>>> >>>>> Lindsey >>>> >>>> >>> >> >> >> _______________________________________________ >> 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 corentin.dupont at gmail.com Mon Feb 10 09:48:02 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 10 Feb 2014 10:48:02 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: That is really interesting. In fact, I didn't have the time to experiment with it, but I definitely want to (have to find some spare time!). I must say I am less used to type classes. At first, my concern with the technique was that two things that belong together, "ReadAccount" and "WriteAccount", are separated. I was also confused that the evaluator is wrapped in a newtype, and that it is an instance of Nomex. Beside, I suppose it is possible to factorize EvalNoEffect with Eval? Maybe using liftEval anyway... On Mon, Feb 10, 2014 at 8:46 AM, Dominique Devriese < dominique.devriese at cs.kuleuven.be> wrote: > Fully agree with Jake. Corentin's effect system is rather simple so that > indexed monads are overkill here and Jake's solution is simpler. > > I just want to point out that the key component of Jake's proposed > solution is not > really type classes, but rather an (underappreciated) pattern that I > call /effect polymorphism/: monadic computations that are polymorphic > over the monad in which they produce effects: > > > noEff :: Nomex m => m () > > noEff = return () > > > > hasEff :: NomexEffect m => m () > > hasEff = readAccount >>= writeAccount > > I would say that type classes are not the key here, since you could > use the same pattern, but replace type classes with dictionaries and > get the same benefits, although with a bit more administration to be > done by the user. > > Such computations have many useful properties, thanks to the > parametricity of the polymorphic quantification. This has been well > explained by Voigtlaender: > http://wwwtcs.inf.tu-dresden.de/~voigt/icfp09.pdf. Effect > polymorphism has also been used by Oliveira, Schrijvers and Cook in a > model of (among other features) aspect composition: > http://users.ugent.be/~tschrijv/Research/papers/jfp_mri.pdf. > > Note by the way that Jake's proposal is still compatible with the > previously suggested solutions based on indexed monads, since you can > write: > > instance Nomex (Exp r) where > readAccount = ReadAccount > > instance NomexEffect (Exp Effect) where > ... > > Regards, > Dominique > > 2014-02-06 21:35 GMT+01:00 Jake McArthur : > > I still think GADTs are a bit too much for this problem. Just using type > > classes provides all the safety you need and even avoids the need for > that > > liftEval function. > > > > {-# LANGUAGE RankNTypes #-} > > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > > module DSLEffects where > > > > import Control.Monad.State > > import Control.Monad.Reader > > > > class Monad m => Nomex m where > > readAccount :: m Int > > > > class Nomex m => NomexEffect m where > > writeAccount :: Int -> m () > > setVictory :: (forall m. Nomex m => m Bool) -> m () > > > > data Game = Game { victory :: (forall m. Nomex m => m Bool) > > , account :: Int > > } > > > > newtype Eval a = Eval { eval :: State Game a } > > deriving Monad > > > > instance Nomex Eval where > > readAccount = Eval $ gets account > > > > instance NomexEffect Eval where > > writeAccount n = Eval . modify $ \game -> game { account = n } > > setVictory v = Eval . modify $ \game -> game { victory = v } > > > > newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } > > deriving Monad > > > > instance Nomex EvalNoEffect where > > readAccount = EvalNoEffect $ asks account > > > > > > > > > > On Thu, Feb 6, 2014 at 12:47 PM, adam vogt wrote: > >> > >> Hi Corentin, > >> > >> You need change Effect to NoEffect to reuse the evalNoEffect: > >> > >> > eval ReadAccount = liftEval $ evalNoEffect ReadAccount > >> > eval (Return a) = liftEval $ evalNoEffect (Return a) > >> > >> Or use a function like `unsafeCoerce :: Nomex Effect a -> Nomex NoEffect > >> a`. > >> > >> If you rename the types that tag effects to something that describes > >> exactly what the tags actually represent, maybe the above definition > will be > >> more satisfying: > >> > >> > data Effects > >> > = > >> > > HasBeenCombinedWithSomethingThatHasEffectsButICan'tBeSureItActuallyHasEffectsAllByItself > >> > | DefinitelyHasNoEffects > >> > >> > >> Regards, > >> Adam > >> > >> > >> On Thu, Feb 6, 2014 at 9:50 AM, Corentin Dupont > >> wrote: > >>> > >>> Hi guys, > >>> I'm still exploring some design space for DSLs, following our > interesting > >>> discussion. > >>> > >>> I'm trying to write the evaluator for the DSL (see below). > >>> For the general case, the evaluator looks like: > >>> > >>> eval :: Nomex r a -> State Game a > >>> > >>> This eval function takes an expression (called Nomex), that can > possibly > >>> have effects. > >>> It returns a state monad, to allow you to modify the game state. > >>> > >>> But for effectless instructions, it would be better to run the > evaluator > >>> in the reader monad: > >>> > >>> evalNoEffect :: Nomex NoEffect a -> Reader Game a > >>> > >>> So you can have additional guaranties that evaluating your expression > >>> will not have effects. > >>> I tried (see below), but it doesn't work for the moment: > >>> > >>> > >>> > {-# LANGUAGE GADTs #-} > >>> > >>> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, > >>> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, > >>> > UndecidableInstances #-} > >>> > >>> > module DSLEffects where > >>> > >>> > import Control.Monad.Error > >>> > import Control.Monad.State > >>> > import Control.Monad.Reader > >>> > import Data.Typeable > >>> > >>> This is the DSL: > >>> > >>> > data Effects = Effect | NoEffect > >>> > >>> > data Nomex :: Effects -> * -> * where > >>> > ReadAccount :: Nomex r Int --ReadAccount has no > >>> > effect: it can be run in whatever monad > >>> > WriteAccount :: Int -> Nomex Effect () --WriteAccount has effect > >>> > SetVictory :: Nomex NoEffect Bool -> Nomex Effect () --SetVictory > >>> > don't accept effectful computations > >>> > Bind :: Nomex m a -> (a -> Nomex m b) -> Nomex m b > >>> > Return :: a -> Nomex r a --wrapping a constant has no effect > >>> > >>> > instance Monad (Nomex a) where > >>> > return = Return > >>> > (>>=) = Bind > >>> > >>> > >>> > noEff :: Nomex NoEffect () > >>> > noEff = return () > >>> > >>> > hasEffect :: Nomex Effect () > >>> > hasEffect = do > >>> > a <- ReadAccount > >>> > WriteAccount a > >>> > >>> > data Game = Game { victory :: Nomex NoEffect Bool, > >>> > account :: Int} > >>> > >>> > >>> > eval :: Nomex r a -> State Game a > >>> > eval a at ReadAccount = liftEval $ evalNoEffect a > >>> > eval (WriteAccount a) = modify (\g -> g{account = a}) > >>> > >>> > eval (SetVictory v) = modify (\g -> g{victory = v}) > >>> > eval a@(Return _) = liftEval $ evalNoEffect a > >>> > eval (Bind exp f) = eval exp >>= eval . f > >>> > >>> > evalNoEffect :: Nomex NoEffect a -> Reader Game a > >>> > evalNoEffect ReadAccount = asks account > >>> > evalNoEffect (Return a) = return a > >>> > evalNoEffect (Bind exp f) = evalNoEffect exp >>= evalNoEffect . f > >>> > >>> > liftEval :: Reader Game a -> State Game a > >>> > liftEval r = get >>= return . runReader r > >>> > >>> > >>> This is not compiling: > >>> > >>> exceptEffect.lhs:60:15: > >>> Couldn't match type 'NoEffect with 'Effect > >>> Inaccessible code in > >>> a pattern with constructor > >>> WriteAccount :: Int -> Nomex 'Effect (), > >>> in an equation for `evalEffect' > >>> In the pattern: WriteAccount a > >>> In an equation for `evalEffect': > >>> evalEffect (WriteAccount a) = modify (\ g -> g {account = a}) > >>> > >>> It seems that the type of effectless computations (NoEffect) leaks in > the > >>> type of effectful ones (due to the pattern matching)... > >>> > >>> Thanks, > >>> Corentin > >>> > >>> > >>> > >>> On Mon, Feb 3, 2014 at 12:44 PM, Corentin Dupont > >>> wrote: > >>>> > >>>> I saw that to write liftQD you decontruct (unwrap) the type and > >>>> reconstruct it. > >>>> I don't know if I can do that for my Exp (which is a full DSL)... > >>>> > >>>> Anyway, there should be a way to encode the Effect/NoEffect semantic > at > >>>> type level... > >>>> Using Oleg's parametrized monad idea > >>>> ( > http://hackage.haskell.org/package/monad-param-0.0.2/docs/Control-Monad-Parameterized.html > ), > >>>> I tried: > >>>> > >>>> > {-# LANGUAGE KindSignatures, DataKinds, ScopedTypeVariables, GADTs > >>>> > MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, > >>>> > UndecidableInstances #-} > >>>> > >>>> > module DSLEffects where > >>>> > import Prelude hiding (return, (>>), (>>=)) > >>>> > import Control.Monad.Parameterized > >>>> > >>>> This data type will be promoted to kind level (thanks to DataKinds): > >>>> > >>>> > >>>> > data Eff = Effect | NoEffect > >>>> > >>>> This class allows to specify the semantic on Effects (Effect + > NoEffect > >>>> = Effect): > >>>> > >>>> > class Effects (m :: Eff) (n::Eff) (r::Eff) | m n -> r > >>>> > instance Effects Effect n Effect > >>>> > instance Effects NoEffect n n > >>>> > >>>> This is the DSL: > >>>> > >>>> > data Exp :: Eff -> * -> * where > >>>> > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect > >>>> > WriteAccount :: Int -> Exp Effect () --WriteAccount has effect > >>>> > Const :: a -> Exp r a > >>>> > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp > r > >>>> > b --Bind comes with a semantic on effects > >>>> > Fmap :: (a -> b) -> Exp m a -> Exp m b > >>>> > >>>> > instance Functor (Exp r) where > >>>> > fmap = Fmap > >>>> > >>>> > instance Return (Exp r) where > >>>> > returnM = Const > >>>> > >>>> > instance (Effects m n r) => Bind (Exp m) (Exp n) (Exp r) where > >>>> > (>>=) = Bind > >>>> > >>>> > noEff :: Exp NoEffect () > >>>> > noEff = returnM () > >>>> > >>>> > hasEffect :: Exp Effect () > >>>> > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) > >>>> > >>>> This is working more or less, however I am obliged to put the type > >>>> signature on the returnM (last line): why? > >>>> Furthermore, I cannot write directly: > >>>> > >>>> > hasEffect :: Exp Effect () > >>>> > hasEffect = ReadAccount > >>>> > >>>> > >>>> Do you have a better idea? > >>>> > >>>> > >>>> > >>>> On Sun, Feb 2, 2014 at 8:55 PM, Lindsey Kuper > > >>>> wrote: > >>>>> > >>>>> On Sun, Feb 2, 2014 at 2:42 PM, Corentin Dupont > >>>>> wrote: > >>>>> > you should be able to run an effectless monad in an effectful one. > >>>>> > How to encode this semantic? > >>>>> > >>>>> In LVish we just have a `liftQD` operation that will let you lift a > >>>>> deterministic computation to a quasi-deterministic one (recall that > >>>>> deterministic computations can perform fewer effects): > >>>>> > >>>>> liftQD :: Par Det s a -> Par QuasiDet s a > >>>>> > >>>>> So, analogously, you could have a `liftEff` and then write `liftEff > >>>>> noEff`. This is also a little bit ugly, but you may find you don't > >>>>> have to do it very often (we rarely use `liftQD`). > >>>>> > >>>>> Lindsey > >>>> > >>>> > >>> > >> > >> > >> _______________________________________________ > >> 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 dominique.devriese at cs.kuleuven.be Mon Feb 10 10:33:27 2014 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Mon, 10 Feb 2014 11:33:27 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Corentin, 2014-02-10 10:48 GMT+01:00 Corentin Dupont : > That is really interesting. In fact, I didn't have the time to experiment > with it, but I definitely want to (have to find some spare time!). > I must say I am less used to type classes. > At first, my concern with the technique was that two things that belong > together, "ReadAccount" and "WriteAccount", are separated. Yes, this separation of ReadAccount and WriteAccount into Nomex vs NomexEffect is how the two parts (read-only vs read-write) of the DSL are distinguished in this approach.. > I was also confused that the evaluator is wrapped in a newtype, and that it > is an instance of Nomex. That is non-essential. You can also use instance Nomex (State Game) where but it's just cleaner with a newtype... > Beside, I suppose it is possible to factorize EvalNoEffect with Eval? Maybe > using liftEval anyway... If I understand correctly, you're asking about how to remove the duplication between EvalNoEffect and Eval? This is a very good question. My answer is basically that Haskell is missing some type-class-related features to allow for the perfect solution, specifically a form of local instances. The long story is that instead of the above instances of Nomex and NomexEffect for Eval and EvalNoEffect separately, we would like to be able to write the following instances: instance MonadReader Game m => Nomex m where readAccount = asks account instance (MonadReader Game m, MonadState Game m) => NomexEffect m where writeAccount n = modify $ \game -> game { account = n } setVictory v = modify $ \game -> game { victory = v } and then we can declare newtype Eval a = Eval { eval :: State Game a } deriving (Monad, MonadState Game, MonadReader Game) newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } deriving (Monad, MonadReader Game) and reuse the single implementation of Nomex for both Eval and EvalNoEffect. However, there are various problems with this solution: * the instances are not permitted without UndecidableInstances (which I recommend against), * the derivation of MonadReader from State won't work because MonadReader is not treated as a superclass of MonadState in Haskell, despite the fact that functionality-wise it is. What is needed to solve these problems is a feature that is in my opinion strongly missing in Haskell: a form of local instances. This means that we would be able to explicitly specify what implementation of a certain type class should be used to satisfy a certain type class constraint, e.g. sort :: Ord a => [a] -> [a] sortBy :: forall a. (a -> a -> Bool) -> [a] -> [a] sortBy f = let instance ordDict :: Ord.Dict a ordDict = constructOrdDict f in sort :: Ord a => [a] -> [a] Local instances were already considered by Wadler when he proposed type classes, but they are problematic to combine with type inference. However, it seems likely that this is not an issue if we require sufficiently informative type annotations. For the problem above, this would allow to construct, use and lift (together with newtype coercions) a MonadReader dictionary for the State monad without necessarily having it derived automatically if this is not desired. Also, this would allow to write the undecidable instances as normal functions that need to be explicitly invoked instead of inferred by type inference, avoiding the UndecidableInstances problem. Regards Dominique From andres at well-typed.com Mon Feb 10 10:47:07 2014 From: andres at well-typed.com (=?ISO-8859-1?Q?Andres_L=F6h?=) Date: Mon, 10 Feb 2014 11:47:07 +0100 Subject: [Haskell-cafe] Haskell meeting in Regensburg, 2014-02-11, 20:00 Message-ID: Hi. Tomorrow, there will be another Haskell meeting in Regensburg, Germany: Tuesday, 11 February 2014 20:00 Binary Kitchen, Walderdorffstr. 13b, 93053 Regensburg There'll be no official talk or presentation, but the theme of the session is going to be "Performance". If you have Haskell sample code that runs slower than expected, feel free to bring it along. The plan is to discuss a number of small demo problems and consider best practices for improving performance of Haskell programs. Everyone who's interested in Haskell is welcome. No actual knowledge of Haskell is expected or required. We'll speak German and/or English, depending on who's going to be there. If you'd like to get updates about future Regensburg Haskell meetings or vote on when we meet next, please join our mailing list at http://lists.binary-kitchen.de/listinfo/haskell If you have any questions and for some reason don't want to join the mailing list, you can also email me :) Cheers, Andres -- Andres L?h, Haskell Consultant Well-Typed LLP, http://www.well-typed.com From allbery.b at gmail.com Mon Feb 10 15:03:43 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 10 Feb 2014 10:03:43 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: On Mon, Feb 10, 2014 at 5:33 AM, Dominique Devriese < dominique.devriese at cs.kuleuven.be> wrote: > Local instances were already considered by Wadler when he proposed > type classes, but they are problematic to combine with type inference > Local instances have a bigger problem: you can use them to trivially violate invariants. Consider a local replacement for Ord on a Data.Map. They're not going to happen. -- 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 dominique.devriese at cs.kuleuven.be Mon Feb 10 15:55:52 2014 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Mon, 10 Feb 2014 16:55:52 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hm. Interesting point, I guess this is the same problem as the whole orphan instances debate... I didn't think of the connection to that problem. Still, I'm convinced there are situations where local instances are *exactly* what we need, so there must be some way to avoid this problem... Regards, Dominique 2014-02-10 16:03 GMT+01:00 Brandon Allbery : > On Mon, Feb 10, 2014 at 5:33 AM, Dominique Devriese > wrote: >> >> Local instances were already considered by Wadler when he proposed >> type classes, but they are problematic to combine with type inference > > > Local instances have a bigger problem: you can use them to trivially violate > invariants. Consider a local replacement for Ord on a Data.Map. They're not > going to happen. > > -- > brandon s allbery kf8nh sine nomine associates > allbery.b at gmail.com ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net From daniel.trstenjak at gmail.com Mon Feb 10 16:10:01 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 10 Feb 2014 17:10:01 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: Message-ID: <20140210161001.GA11167@machine> Hi Dominique, On Mon, Feb 10, 2014 at 04:55:52PM +0100, Dominique Devriese wrote: > Hm. Interesting point, I guess this is the same problem as the whole > orphan instances debate... I didn't think of the connection to that > problem. Still, I'm convinced there are situations where local > instances are *exactly* what we need, so there must be some way to > avoid this problem... If a type class has a clear semantical meaning, what should then be the point of having multiple instances for the same data type? A clear semantical meaning contradicts multiple instances, they would only make reasoning about your code harder. The few use cases where it might be nice to be able to define a new instance aren't IMHO worth the drawbacks. You would just open Haskell for Ruby like monkey patching. Greetings, Daniel From dominique.devriese at cs.kuleuven.be Mon Feb 10 16:26:37 2014 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Mon, 10 Feb 2014 17:26:37 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: <20140210161001.GA11167@machine> References: <20140210161001.GA11167@machine> Message-ID: Hi Daniel, 2014-02-10 17:10 GMT+01:00 Daniel Trstenjak : > On Mon, Feb 10, 2014 at 04:55:52PM +0100, Dominique Devriese wrote: >> Hm. Interesting point, I guess this is the same problem as the whole >> orphan instances debate... I didn't think of the connection to that >> problem. Still, I'm convinced there are situations where local >> instances are *exactly* what we need, so there must be some way to >> avoid this problem... > > If a type class has a clear semantical meaning, what should then > be the point of having multiple instances for the same data type? > > A clear semantical meaning contradicts multiple instances, they would > only make reasoning about your code harder. I disagree. Just think about the Ord type class. A decidable order relation for a type is definitely something I would consider a clear semantical meaning, but different sensible instances can be defined for many types... The same thing goes for Eq or Monoid or MonadState or... Regards, Dominique From allbery.b at gmail.com Mon Feb 10 17:16:12 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 10 Feb 2014 12:16:12 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140210161001.GA11167@machine> Message-ID: On Mon, Feb 10, 2014 at 11:26 AM, Dominique Devriese < dominique.devriese at cs.kuleuven.be> wrote: > I disagree. Just think about the Ord type class. A decidable order > relation for a type is definitely something I would consider a clear > semantical meaning, but different sensible instances can be defined > for many types... The same thing goes for Eq or Monoid or MonadState > or... > Sure... but now you have to make sure everything agrees about it. The way you do this in Haskell is to give your custom instance a distinct type to go with it. (Now go look at the Sum and Product monoids). -- 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 roma at ro-che.info Mon Feb 10 17:22:20 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 10 Feb 2014 19:22:20 +0200 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: <20140210161001.GA11167@machine> References: <20140210161001.GA11167@machine> Message-ID: <20140210172220.GA10487@sniper> * Daniel Trstenjak [2014-02-10 17:10:01+0100] > > Hi Dominique, > > On Mon, Feb 10, 2014 at 04:55:52PM +0100, Dominique Devriese wrote: > > Hm. Interesting point, I guess this is the same problem as the whole > > orphan instances debate... I didn't think of the connection to that > > problem. Still, I'm convinced there are situations where local > > instances are *exactly* what we need, so there must be some way to > > avoid this problem... > > If a type class has a clear semantical meaning, what should then > be the point of having multiple instances for the same data type? > > A clear semantical meaning contradicts multiple instances, they would > only make reasoning about your code harder. > > The few use cases where it might be nice to be able to define a new > instance aren't IMHO worth the drawbacks. > > You would just open Haskell for Ruby like monkey patching. How about a compromise. We already have a way to introduce fresh type names: using existential types. They look like good candidates for local instances (by definition, they can't have global instances, because the names themselves are necessarily local). Of course, you can define an instance only once, as for usual types. This would cover the case when "dynamic" instances are needed without compromising soundness. Example: data IsoInt = forall a . IsoInt (Int -> a) (a -> Int) foo modulus = case IsoInt id id of IsoInt (fromInt :: Int -> a) toInt -> let eqMod x1 x2 = (toInt x1 - toInt x2) `mod` modulus == 0 -- note: a is rigid here instance Eq a where (==) = eqMod in ... Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From christopher.howard at frigidcode.com Mon Feb 10 17:33:22 2014 From: christopher.howard at frigidcode.com (Christopher Howard) Date: Mon, 10 Feb 2014 08:33:22 -0900 Subject: [Haskell-cafe] Lisp Style Restarts in Haskell Message-ID: <52F90D62.20308@frigidcode.com> Hi. I was curious if Haskell has something like "restarts" in Common Lisp. My search engines didn't give relevant results for "Haskell restarts". However, there were several results for "Haskell coroutines" and, from what I can gather, restarts and coroutines are a similar or related subject. -- http://www.lugod.org/presentations/pgp/why.html -------------- next part -------------- A non-text attachment was scrubbed... Name: 0x25C6C407.asc Type: application/pgp-keys Size: 1748 bytes Desc: not available URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 551 bytes Desc: OpenPGP digital signature URL: From davidleothomas at gmail.com Mon Feb 10 17:38:47 2014 From: davidleothomas at gmail.com (David Thomas) Date: Mon, 10 Feb 2014 09:38:47 -0800 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140210161001.GA11167@machine> Message-ID: I think what we're running into is a slight mismatch between a natural understanding of types-as-sets and types-as-ADTs. In the former sense - particularly about things we're used to thinking of as sets (say, Integer) - we want to be able to say "this is still integers, we just want to couple them with this operation and get a monoid here, and that operation and get a different monoid over there, but the objects are all still integers". Viewed as ADTs, it's more intuitive to say "there is some data here behind this interface, and the combination yields a single type", and that's what we're doing with typeclasses in Haskell. I don't *think* there is actually a need to express the former more directly, and I'm not convinced there's a way to do it that's actually cleaner, but I think that's the origin of the impulse (and I don't think the impulse itself is "wrong" - you just need to remember the translation). On Mon, Feb 10, 2014 at 9:16 AM, Brandon Allbery wrote: > On Mon, Feb 10, 2014 at 11:26 AM, Dominique Devriese < > dominique.devriese at cs.kuleuven.be> wrote: > >> I disagree. Just think about the Ord type class. A decidable order >> relation for a type is definitely something I would consider a clear >> semantical meaning, but different sensible instances can be defined >> for many types... The same thing goes for Eq or Monoid or MonadState >> or... >> > > Sure... but now you have to make sure everything agrees about it. The way > you do this in Haskell is to give your custom instance a distinct type to > go with it. (Now go look at the Sum and Product monoids). > > > -- > 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 dominique.devriese at cs.kuleuven.be Mon Feb 10 19:07:37 2014 From: dominique.devriese at cs.kuleuven.be (Dominique Devriese) Date: Mon, 10 Feb 2014 20:07:37 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: <20140210172220.GA10487@sniper> References: <20140210161001.GA11167@machine> <20140210172220.GA10487@sniper> Message-ID: Roman, 2014-02-10 18:22 GMT+01:00 Roman Cheplyaka : > * Daniel Trstenjak [2014-02-10 17:10:01+0100] >> On Mon, Feb 10, 2014 at 04:55:52PM +0100, Dominique Devriese wrote: >> > Hm. Interesting point, I guess this is the same problem as the whole >> > orphan instances debate... I didn't think of the connection to that >> > problem. Still, I'm convinced there are situations where local >> > instances are *exactly* what we need, so there must be some way to >> > avoid this problem... >> >> If a type class has a clear semantical meaning, what should then >> be the point of having multiple instances for the same data type? >> >> A clear semantical meaning contradicts multiple instances, they would >> only make reasoning about your code harder. >> >> The few use cases where it might be nice to be able to define a new >> instance aren't IMHO worth the drawbacks. >> >> You would just open Haskell for Ruby like monkey patching. > > How about a compromise. We already have a way to introduce fresh type > names: using existential types. They look like good candidates for local > instances (by definition, they can't have global instances, because the > names themselves are necessarily local). Of course, you can define an > instance only once, as for usual types. > > This would cover the case when "dynamic" instances are needed without > compromising soundness. Example: > > data IsoInt = forall a . IsoInt (Int -> a) (a -> Int) > > foo modulus = > case IsoInt id id of > IsoInt (fromInt :: Int -> a) toInt -> > let > eqMod x1 x2 = (toInt x1 - toInt x2) `mod` modulus == 0 > > -- note: a is rigid here > instance Eq a where > (==) = eqMod > in ... Just a note that your proposal seems very related to what Kiselyov and Shan propose in their paper on "Implicit Configurations" (http://dl.acm.org/citation.cfm?id=1017481). Anyway, I still think that there are cases where I want to say that I want to use "real" local instances. Another interesting example by the way is instancing MonadState for IO. Consider how every IORef a can be used to build a MonadState a instance for IO: data MonadStateD a m = MonadStateD { putM :: a -> m (), getM :: m a } ioRefStateD :: IORef a -> MonadStateD a IO ioRefStateD ref = MonadStateD (writeIORef ref) (readIORef ref) I have the feeling that Brandon's argument (that multiple instances cannot be permitted because, for example, Data.Map should only be used with a single Ord instance) in some way comes down to solving a lack for an ML-like module system by imposing an otherwise artificial restriction on type classes: to enforce that a type class instance is unique within a module parameterised by it, we simply require that the instance be globally unique... That being said, Brendan is clearly right that we can't just drop a guarantee that is widely relied upon. Regards, Dominique From miguelimo38 at yandex.ru Mon Feb 10 19:31:08 2014 From: miguelimo38 at yandex.ru (MigMit) Date: Mon, 10 Feb 2014 23:31:08 +0400 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: On 10 Feb 2014, at 19:03, Brandon Allbery wrote: > On Mon, Feb 10, 2014 at 5:33 AM, Dominique Devriese wrote: > Local instances were already considered by Wadler when he proposed > type classes, but they are problematic to combine with type inference > > Local instances have a bigger problem: you can use them to trivially violate invariants. Consider a local replacement for Ord on a Data.Map. They're not going to happen. You can easily achieve the same thing with orphan instances, and they only result in a compiler warning. From daniel.trstenjak at gmail.com Mon Feb 10 19:47:33 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 10 Feb 2014 20:47:33 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140210161001.GA11167@machine> Message-ID: <014D6EBE-14E6-48F0-B0D1-6571A926CFF6@gmail.com> Am 10.02.2014 um 17:26 schrieb Dominique Devriese : > I disagree. Just think about the Ord type class. A decidable order > relation for a type is definitely something I would consider a clear > semantical meaning ... Why shouldn't be the kind of ordering part of the semantical meaning of Ord? Otherwise what could you then say about the result of the 'sort' function? sort :: Ord a => [a] -> [a] My gut feeling is, that if the effective range of the active instance is too narrow, then it's not very useful, but if you widen it, then you're getting all of the possible drawbacks. Greetings, Daniel From tyler.huffman at tylerh.org Tue Feb 11 03:16:47 2014 From: tyler.huffman at tylerh.org (Tyler Huffman) Date: Mon, 10 Feb 2014 20:16:47 -0700 Subject: [Haskell-cafe] Master's Thesis: Open areas of research in Haskell In-Reply-To: References: Message-ID: Perfect! Thank you very much for the pointers! Regards On Sun, Feb 9, 2014 at 11:32 PM, Kim-Ee Yeoh wrote: > > On Mon, Feb 10, 2014 at 9:50 AM, Tyler Huffman wrote: > >> I've seen the Internship opportunities and areas of research for GHC ( >> https://ghc.haskell.org/trac/ghc/wiki/Internships) but they all seem to >> apply to Ph.D candidates. >> > > I wouldn't worry about these restrictions, they aren't set in stone. It's > better to look at the slate of people (and what they've done, not their > paper qualifications) who have actually gotten in previously to get a sense > of the benchmark. > > If you've hacked GHC in interesting ways before applying, you'll > definitely turn heads. > > >> That said, are there open areas of research that I could look into >> > > Skim the titles of previous years ICFP and Haskell Symposium proceedings. > Read the abstracts. Look at the references. Does anything strike the eye? > > -- Kim-Ee > -- Tyler Huffman Computer Science/Software Engineer tyler.huffman at tylerh.org (406) 480-6148 -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmitdase at gmail.com Tue Feb 11 05:15:43 2014 From: jmitdase at gmail.com (Joey) Date: Mon, 10 Feb 2014 23:15:43 -0600 Subject: [Haskell-cafe] How Plugins works with a Cabal sandbox Message-ID: <52F9B1FF.9070901@gmail.com> I was wondering, could somebody talk me through how the Plugins package works with a Cabal sandbox, or Cabal in general? Basically, I'm writing a program where I want to dynamically load and run user-supplied code. There are two cabal DBs in question: the sandbox which I'm using to build my program, and my "global" sandbox located in /home/user/.cabal. Which database, if either, does a program I load with System.Plugins.Load.load have access to via "import" statements? How can I avoid double-loading of packages? In particular, I'm currently getting this error when I try to load my code. Any thoughts? GHCi runtime linker: fatal error: I found a duplicate definition for symbol transformerszm0zi3zi0zi0_ControlziMonadziTransziError_mapErrorT1_closure whilst processing object file /home/joey/.cabal/lib/transformers-0.3.0.0/ghc-7.6.3/HStransformers-0.3.0.0.o This could be caused by: * Loading two different object files which export the same symbol * Specifying the same object file twice on the GHCi command line * An incorrect `package.conf' entry, causing some object to be loaded twice. GHCi cannot safely continue in this situation. Exiting now. Sorry. -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Tue Feb 11 10:02:42 2014 From: michael at snoyman.com (Michael Snoyman) Date: Tue, 11 Feb 2014 12:02:42 +0200 Subject: [Haskell-cafe] A new yaml module In-Reply-To: References: Message-ID: I've made an initial stab at this new API. It lives in two modules: Data.Yaml.Builder, and Data.Yaml.Parser. Both of these modules are highly inspired by the aeson equivalents, but they allow for more control of serialization, and proper handling of ambiguous values like 12345, which can now be parsed as either an Int or a Text. In order to make it easier to experiment with this API, I've included these two modules in the most recent version of the yaml package on Hackage[1]. Note that: * The API isn't fully fleshed out. In particular, many ToYaml and FromYaml instances need to be written. * The API is subject to change over the next few iterations, so please don't start depending on it yet. Discussion on this API has been taking place on the issue tracker[2]. You can see some simple example usages of the API at [3][4]. [1] http://hackage.haskell.org/package/yaml-0.8.7 [2] https://github.com/snoyberg/yaml/issues/38 [3] https://github.com/snoyberg/yaml/blob/master/builder-test.hs [4] https://github.com/snoyberg/yaml/blob/master/parser-test.hs On Mon, Feb 3, 2014 at 10:57 AM, Michael Snoyman wrote: > The yaml package[1] currently provides two modules. Text.Libyaml is a > lower level, streaming API which is essentially a raw exposure of the > underlying libyaml C library. Data.Yaml uses the aeson Value data type and > ToJSON/FromJSON type classes for higher level serialization. For many > cases, this approach works well, though there are problems: > > * There are problems with roundtripping, since YAML allows for ambiguity > about the data type of values[2]. For example, in the yaml snippet `foo: > 1234`, is 1234 intended to be numeric or a string? Either is valid. > * YAML is intended to be human-readable output. But Data.Yaml provides no > control over the encoded representation, e.g. should we use single or > double quotes for a string (or no quotes at all), or the order of values in > a mapping[3]. > > For other examples, just look at the issue tracker for yaml[4]. > > I don't want to drop the current aeson-based functionality, since I think > it's still valid and useful in many cases. But I do think it's worthwhile > to add in an alternative API which handles YAML-specific constructs better. > My idea is: > > * Create a new Data.Yaml.Aeson module, and have it mirror Data.Yaml. > * Deprecate Data.Yaml. > * Create a new Data.Yaml.? module to contain this YAML-specific API. > > I'm asking for feedback on that last point. I have some basic ideas on > what such an API would look like, but given that there are many people > using YAML in ways different than how I'm using it, I don't think an API > designed entirely by me will suit all use cases. > > I've opened up a new issue[5] to track this work. If you're interested in > participating in this design, please contact me. I'm happy to have the > discussion on this mailing list, but if (as I suspect) there are just a > handful of people who are interested in pushing this forward, it likely > makes sense to take the discussion offlist. > > Michael > > [1] http://hackage.haskell.org/package/yaml > [2] https://github.com/snoyberg/yaml/issues/22 > [3] https://github.com/snoyberg/yaml/issues/37 > [4] https://github.com/snoyberg/yaml/issues > [5] https://github.com/snoyberg/yaml/issues/38 > -------------- next part -------------- An HTML attachment was scrubbed... URL: From horstmey at Mathematik.Uni-Marburg.de Tue Feb 11 16:00:12 2014 From: horstmey at Mathematik.Uni-Marburg.de (Thomas Horstmeyer) Date: Tue, 11 Feb 2014 17:00:12 +0100 Subject: [Haskell-cafe] Lazy Lambda Calculus implementation In-Reply-To: <86d2izroas.fsf@gmail.com> References: <86d2izroas.fsf@gmail.com> Message-ID: <52FA490C.8070902@informatik.uni-marburg.de> Hello Chris, it looks to me like it should be shared. One approach to test this is "println-debugging". The Module Debug.Trace has functions to let you write to stdout as side-effect, outside the IO monad. import Debug.Trace(trace) eval' (Lam f) env = Now (F (\a -> eval' f (trace "evaluating element" a:env))) With this, you would get the output "evaluating element" whenever an entry in the list env is evaluated. HTH Thomas Am 07.02.2014 15:27, schrieb Chris Warburton: > Hello all, I've written the following implementation of Lambda Calculus, > which will evaluate its Terms non-strictly. I've verified this since the > Y combinator works without diverging: > > data Term a = Const a > | Var Nat > | Lam (Term a) > | Term a :@ Term a > > data Val a = C a > | F (Partial (Val a) -> Partial (Val a)) > > type Env a = [Partial (Val a)] > > eval' :: Term a -> Env a -> Partial (Val a) > eval' (Const c) env = Now (C c) > eval' (Var n) env = let Just x = lookUp env n in x > eval' (Lam f) env = Now (F (\a -> eval' f (a:env))) > eval' (f :@ x) env = do F f' <- eval' f env > Later (f' (eval' x env)) > > eval t = eval' [] t > > Nat, Partial, lookUp, etc. have pretty obvious implementations. > > My question is, will this behave lazily? In other words will the > contents of the 'env' lists be shared between the different contexts, > such that forcing an element the be evaluated twice will only perform > the evaluation once? Note that the first "do" line is the only place > where evaluation is forced. > > If anyone could point out an 'obvious' reason why it will or will not be > shared, or approaches I can take to check or infer this myself (eg. a > Term which would show wildly different RAM usage in each case), I'd be > very interested to know. I'd also be interested if someone spots a bug ;) > > For those who are curious, the code is living at > https://gitorious.org/lazy-lambda-calculus and I've written a blog post > detailing the iteration's I've been through at > http://chriswarbo.net/index.php?page=news&type=view&id=admin-s-blog%2Flazy-lambda-calculus > > Cheers, > Chris > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From flickyfrans at gmail.com Tue Feb 11 21:46:47 2014 From: flickyfrans at gmail.com (flicky frans) Date: Wed, 12 Feb 2014 00:46:47 +0300 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. Message-ID: Hello. I am currently writing lists with lazy semantics in the pure lambda-calculus with call-by-value reduction strategy. Here is an example: http://pastebin.com/SvQ5hCSD Here is a simple interpetator: http://pastebin.com/mejCWqpu Am I reinventing the wheel? Are there some sources, from where i can learn more about lazy evaluation in the strict languages? From kyle.marek.spartz at gmail.com Tue Feb 11 21:54:34 2014 From: kyle.marek.spartz at gmail.com (Kyle Marek-Spartz) Date: Tue, 11 Feb 2014 15:54:34 -0600 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: References: Message-ID: SICP comes to mind:?http://mitpress.mit.edu/sicp/full-text/sicp/book/node70.html -- Kyle Marek-Spartz On February 11, 2014 at 3:47:09 PM, flicky frans (flickyfrans at gmail.com) wrote: > > Hello. I am currently writing lists with lazy semantics in the > pure > lambda-calculus with call-by-value reduction strategy. > Here is an example: http://pastebin.com/SvQ5hCSD > Here is a simple interpetator: http://pastebin.com/mejCWqpu > Am I reinventing the wheel? Are there some sources, from where > i can > learn more about lazy evaluation in the strict languages? > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From flickyfrans at gmail.com Tue Feb 11 22:42:02 2014 From: flickyfrans at gmail.com (flicky frans) Date: Wed, 12 Feb 2014 01:42:02 +0300 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: References: Message-ID: >interpetator Sorry, interpreter. Thanks, Kyle Marek-Spartz. I've read SICP a few years ago, but completely forgot about this chapter. That's what I wrote modulo CPS, but CPS is a significant part. 2014-02-12 0:54 GMT+03:00, Kyle Marek-Spartz : > SICP comes to > mind:?http://mitpress.mit.edu/sicp/full-text/sicp/book/node70.html > > -- > Kyle Marek-Spartz > > On February 11, 2014 at 3:47:09 PM, flicky frans (flickyfrans at gmail.com) > wrote: >> >> Hello. I am currently writing lists with lazy semantics in the >> pure >> lambda-calculus with call-by-value reduction strategy. >> Here is an example: http://pastebin.com/SvQ5hCSD >> Here is a simple interpetator: http://pastebin.com/mejCWqpu >> Am I reinventing the wheel? Are there some sources, from where >> i can >> learn more about lazy evaluation in the strict languages? >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > From roma at ro-che.info Tue Feb 11 22:52:07 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 12 Feb 2014 00:52:07 +0200 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: References: Message-ID: <20140211225207.GA3885@sniper> Except Scheme is not pure ? they use set! to achieve memoisation. I don't think the OP bothers with memoisation in his/her encoding, though. Roman * Kyle Marek-Spartz [2014-02-11 15:54:34-0600] > SICP comes to mind:?http://mitpress.mit.edu/sicp/full-text/sicp/book/node70.html > > -- > Kyle Marek-Spartz > > On February 11, 2014 at 3:47:09 PM, flicky frans (flickyfrans at gmail.com) wrote: > > > > Hello. I am currently writing lists with lazy semantics in the > > pure > > lambda-calculus with call-by-value reduction strategy. > > Here is an example: http://pastebin.com/SvQ5hCSD > > Here is a simple interpetator: http://pastebin.com/mejCWqpu > > Am I reinventing the wheel? Are there some sources, from where > > i can > > learn more about lazy evaluation in the strict languages? > > _______________________________________________ > > 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: 819 bytes Desc: Digital signature URL: From roma at ro-che.info Tue Feb 11 23:31:05 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Wed, 12 Feb 2014 01:31:05 +0200 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: References: Message-ID: <20140211233105.GA4451@sniper> Do you know about the Church encoding? I don't quite understand your encoding. Consider your cons function: cons = \x xs f z. f (\_. x) (\f' _. xs f' z); 1. Why do you pass (\_. x) instead of x to f? This looks like an attempt to delay evaluation of x, but by the time cons is applied, x must have been evaluated already due to CBV. 2. Why do you ask for a new f' but ignore the new z' (as compared to f and z)? Also, your interpreter doesn't seem to finish in a reasonable time on your own input. Roman * flicky frans [2014-02-12 00:46:47+0300] > Hello. I am currently writing lists with lazy semantics in the pure > lambda-calculus with call-by-value reduction strategy. > Here is an example: http://pastebin.com/SvQ5hCSD > Here is a simple interpetator: http://pastebin.com/mejCWqpu > Am I reinventing the wheel? Are there some sources, from where i can > learn more about lazy evaluation in the strict languages? > _______________________________________________ > 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 flickyfrans at gmail.com Wed Feb 12 00:02:55 2014 From: flickyfrans at gmail.com (flicky frans) Date: Wed, 12 Feb 2014 03:02:55 +0300 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: <20140211233105.GA4451@sniper> References: <20140211233105.GA4451@sniper> Message-ID: >Do you know about the Church encoding? Yes. >1. Why do you pass (\_. x) instead of x to f? This looks like an attempt >to delay evaluation of x, but by the time cons is applied, x must >have been evaluated already due to CBV. It's for constructing lists from the evaluated values. For lazy purposes there is consC. 2. Why do you ask for a new f' but ignore the new z' (as compared to f >and z)? It's for the tail function, which is problematic in the standard Church encoding. Here it is O(1). While folding, actual f passes over the whole list. >Also, your interpreter doesn't seem to finish in a reasonable time on your own input. It's very simple and unoptimized. And there is much arithmetic in the code. It finishes, but if you don't want to wait, you can try "sum (take (s (s z)) (cycle (take (s (s z)) (filter (leq (s z)) nats))))". 2014-02-12 2:31 GMT+03:00, Roman Cheplyaka : > Do you know about the Church encoding? > > I don't quite understand your encoding. Consider your cons function: > > cons = \x xs f z. f (\_. x) (\f' _. xs f' z); > > 1. Why do you pass (\_. x) instead of x to f? This looks like an attempt > to delay evaluation of x, but by the time cons is applied, x must > have been evaluated already due to CBV. > > 2. Why do you ask for a new f' but ignore the new z' (as compared to f > and z)? > > Also, your interpreter doesn't seem to finish in a reasonable time on > your own input. > > Roman > > * flicky frans [2014-02-12 00:46:47+0300] >> Hello. I am currently writing lists with lazy semantics in the pure >> lambda-calculus with call-by-value reduction strategy. >> Here is an example: http://pastebin.com/SvQ5hCSD >> Here is a simple interpetator: http://pastebin.com/mejCWqpu >> Am I reinventing the wheel? Are there some sources, from where i can >> learn more about lazy evaluation in the strict languages? >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > From kmill31415 at gmail.com Wed Feb 12 03:24:40 2014 From: kmill31415 at gmail.com (Kyle Miller) Date: Tue, 11 Feb 2014 22:24:40 -0500 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: <20140211225207.GA3885@sniper> References: <20140211225207.GA3885@sniper> Message-ID: Please correct me if I'm wrong, but isn't Haskell secretly doing a set! when parts of an ADT are evaluated to memoize them? In the vein of lazy lists, taking the tail of a list in Haskell would be one such example. I noticed this secret set! when I was learning about its garbage collector: I was surprised at first that objects in older generations could ever have pointers to objects in newer generations! Kyle On Tue, Feb 11, 2014 at 5:52 PM, Roman Cheplyaka wrote: > Except Scheme is not pure -- they use set! to achieve memoisation. > > I don't think the OP bothers with memoisation in his/her encoding, > though. > > Roman > > * Kyle Marek-Spartz [2014-02-11 > 15:54:34-0600] > > SICP comes to mind: > http://mitpress.mit.edu/sicp/full-text/sicp/book/node70.html > > > > -- > > Kyle Marek-Spartz > > > > On February 11, 2014 at 3:47:09 PM, flicky frans (flickyfrans at gmail.com) > wrote: > > > > > > Hello. I am currently writing lists with lazy semantics in the > > > pure > > > lambda-calculus with call-by-value reduction strategy. > > > Here is an example: http://pastebin.com/SvQ5hCSD > > > Here is a simple interpetator: http://pastebin.com/mejCWqpu > > > Am I reinventing the wheel? Are there some sources, from where > > > i can > > > learn more about lazy evaluation in the strict languages? > > > _______________________________________________ > > > 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 danny.gratzer at gmail.com Wed Feb 12 03:45:19 2014 From: danny.gratzer at gmail.com (Danny Gratzer) Date: Tue, 11 Feb 2014 21:45:19 -0600 Subject: [Haskell-cafe] Lazy lists with with call-by-value reduction strategy. In-Reply-To: References: <20140211225207.GA3885@sniper> Message-ID: Yes. Edward Yang has a wonderful series on how Haskell's (GHC's) runtime works under the hood http://blog.ezyang.com/2011/04/the-haskell-heap/. Cheers, Danny Gratzer On Tue, Feb 11, 2014 at 9:24 PM, Kyle Miller wrote: > Please correct me if I'm wrong, but isn't Haskell secretly doing a set! > when parts of an ADT are evaluated to memoize them? In the vein of lazy > lists, taking the tail of a list in Haskell would be one such example. > > I noticed this secret set! when I was learning about its garbage > collector: I was surprised at first that objects in older generations could > ever have pointers to objects in newer generations! > > Kyle > > > On Tue, Feb 11, 2014 at 5:52 PM, Roman Cheplyaka wrote: > >> Except Scheme is not pure ? they use set! to achieve memoisation. >> >> I don't think the OP bothers with memoisation in his/her encoding, >> though. >> >> Roman >> >> * Kyle Marek-Spartz [2014-02-11 >> 15:54:34-0600] >> > SICP comes to mind: >> http://mitpress.mit.edu/sicp/full-text/sicp/book/node70.html >> > >> > -- >> > Kyle Marek-Spartz >> > >> > On February 11, 2014 at 3:47:09 PM, flicky frans (flickyfrans at gmail.com) >> wrote: >> > > >> > > Hello. I am currently writing lists with lazy semantics in the >> > > pure >> > > lambda-calculus with call-by-value reduction strategy. >> > > Here is an example: http://pastebin.com/SvQ5hCSD >> > > Here is a simple interpetator: http://pastebin.com/mejCWqpu >> > > Am I reinventing the wheel? Are there some sources, from where >> > > i can >> > > learn more about lazy evaluation in the strict languages? >> > > _______________________________________________ >> > > 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 >> >> > > _______________________________________________ > 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 jonathangfischoff at gmail.com Wed Feb 12 04:51:38 2014 From: jonathangfischoff at gmail.com (Jonathan Fischoff) Date: Tue, 11 Feb 2014 20:51:38 -0800 Subject: [Haskell-cafe] ANN: generic-maybe-0.3.0.2 Message-ID: generic-maybe utilizes GHC.Generics to generalize the functions of Data.Maybe to arbitrary sum types with two constructors, with one "empty." Here is a quick example: ?> :set -XDeriveGeneric ?> import GHC.Generics ?> data Result a = Success a | Fail deriving (Show, Generic) ?> fromMaybe 'a' Fail 'a' ?> fromMaybe 'a' $ Success 'b' 'b' Additionally, it lets you convert between two representations: ?> convert (Just 'a') :: Result Char Success 'a' Documentation on Hackage: http://hackage.haskell.org/package/generic-maybe-0.3.0.2/docs/Data-Generics-Maybe.html -Jonathan Fischoff -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Wed Feb 12 16:44:17 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Wed, 12 Feb 2014 17:44:17 +0100 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hi guys, so I tried to implement fully the proposition (see below). It works well. However I find it a bit redundant. Can we reduce the repetitions? Perhaps I didn't understand how to write the evaluation... {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} module Main where import Control.Monad.State import Control.Monad.Reader class Monad m => Nomex m where readAccount :: m Int class Nomex m => NomexEffect m where writeAccount :: Int -> m () setVictory :: (forall n. Nomex n => n Bool) -> m () data Exp a where ReadAccount :: Exp Int WriteAccount :: Int -> Exp () SetVictory :: (forall m. Nomex m => m Bool) -> Exp () Bind :: Exp a -> (a -> Exp b) -> Exp b Return :: a -> Exp a instance Monad Exp where return = Return (>>=) = Bind instance Nomex Exp where readAccount = ReadAccount instance NomexEffect Exp where writeAccount = WriteAccount setVictory = SetVictory data Game = Game { victory :: (forall m. Nomex m => m Bool) , account :: Int } instance Nomex (State Game) where readAccount = gets account instance NomexEffect (State Game) where writeAccount n = modify $ \game -> game { account = n } setVictory v = modify $ \game -> game { victory = v } instance Nomex (Reader Game) where readAccount = asks account evaluate :: Exp a -> State Game a evaluate (WriteAccount i) = writeAccount i evaluate ReadAccount = readAccount evaluate (SetVictory v) = setVictory v evaluate (Return a) = return a evaluate (Bind a f) = (evaluate a) >>= evaluate . f evalNoEff :: Exp a -> Reader Game a evalNoEff ReadAccount = readAccount evalNoEff (Return a) = return a evalNoEff (Bind a f) = (evalNoEff a) >>= evalNoEff . f isVictory :: Game -> Bool isVictory g = runReader (evalNoEff (victory g)) g incrAccount :: NomexEffect m => m () incrAccount = readAccount >>= writeAccount . (+101) winOnBigMoney :: NomexEffect m => m () winOnBigMoney = setVictory $ do i <- readAccount --writeAccount 100 return (i > 100) play = do winOnBigMoney incrAccount initGame = Game (return False) 0 main = do let g = execState (evaluate jeu) initGame putStrLn $ show $ isVictory g On Mon, Feb 10, 2014 at 11:33 AM, Dominique Devriese < dominique.devriese at cs.kuleuven.be> wrote: > Corentin, > > 2014-02-10 10:48 GMT+01:00 Corentin Dupont : > > That is really interesting. In fact, I didn't have the time to experiment > > with it, but I definitely want to (have to find some spare time!). > > I must say I am less used to type classes. > > At first, my concern with the technique was that two things that belong > > together, "ReadAccount" and "WriteAccount", are separated. > > Yes, this separation of ReadAccount and WriteAccount into Nomex vs > NomexEffect is how the two parts (read-only vs read-write) of the DSL > are distinguished in this approach.. > > > I was also confused that the evaluator is wrapped in a newtype, and that > it > > is an instance of Nomex. > > That is non-essential. You can also use > > instance Nomex (State Game) where > > but it's just cleaner with a newtype... > > > Beside, I suppose it is possible to factorize EvalNoEffect with Eval? > Maybe > > using liftEval anyway... > > If I understand correctly, you're asking about how to remove the > duplication between EvalNoEffect and Eval? > > This is a very good question. My answer is basically that Haskell is > missing some type-class-related features to allow for the perfect > solution, specifically a form of local instances. > > The long story is that instead of the above instances of Nomex and > NomexEffect for Eval and EvalNoEffect separately, we would like to be > able to write the following instances: > > instance MonadReader Game m => Nomex m where > readAccount = asks account > > instance (MonadReader Game m, MonadState Game m) => NomexEffect m where > writeAccount n = modify $ \game -> game { account = n } > setVictory v = modify $ \game -> game { victory = v } > > and then we can declare > newtype Eval a = Eval { eval :: State Game a } > deriving (Monad, MonadState Game, MonadReader Game) > > newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } > deriving (Monad, MonadReader Game) > > and reuse the single implementation of Nomex for both Eval and > EvalNoEffect. However, there are various problems with this solution: > > * the instances are not permitted without UndecidableInstances (which > I recommend against), > * the derivation of MonadReader from State won't work because > MonadReader is not treated as a superclass of MonadState in Haskell, > despite the fact that functionality-wise it is. > > What is needed to solve these problems is a feature that is in my > opinion strongly missing in Haskell: a form of local instances. This > means that we would be able to explicitly specify what implementation > of a certain type class should be used to satisfy a certain type class > constraint, e.g. > > sort :: Ord a => [a] -> [a] > sortBy :: forall a. (a -> a -> Bool) -> [a] -> [a] > sortBy f = let instance ordDict :: Ord.Dict a > ordDict = constructOrdDict f > in sort :: Ord a => [a] -> [a] > > Local instances were already considered by Wadler when he proposed > type classes, but they are problematic to combine with type inference. > However, it seems likely that this is not an issue if we require > sufficiently informative type annotations. > > For the problem above, this would allow to construct, use and lift > (together with newtype coercions) a MonadReader dictionary for the > State monad without necessarily having it derived automatically if > this is not desired. Also, this would allow to write the undecidable > instances as normal functions that need to be explicitly invoked > instead of inferred by type inference, avoiding the > UndecidableInstances problem. > > Regards > Dominique > -------------- next part -------------- An HTML attachment was scrubbed... URL: From erik.dominikus71 at gmail.com Wed Feb 12 18:16:39 2014 From: erik.dominikus71 at gmail.com (Erik Dominikus) Date: Thu, 13 Feb 2014 01:16:39 +0700 Subject: [Haskell-cafe] Lisp Style Restarts in Haskell In-Reply-To: <52F90D62.20308@frigidcode.com> References: <52F90D62.20308@frigidcode.com> Message-ID: How about the Control.Retry module in the 'retry' package? http://hackage.haskell.org/package/retry On Feb 11, 2014 12:51 AM, "Christopher Howard" < christopher.howard at frigidcode.com> wrote: > Hi. I was curious if Haskell has something like "restarts" in Common > Lisp. My search engines didn't give relevant results for "Haskell > restarts". However, there were several results for "Haskell coroutines" > and, from what I can gather, restarts and coroutines are a similar or > related subject. > > -- > http://www.lugod.org/presentations/pgp/why.html > > > _______________________________________________ > 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 chrisyco+haskell-cafe at gmail.com Wed Feb 12 21:08:30 2014 From: chrisyco+haskell-cafe at gmail.com (Chris Wong) Date: Thu, 13 Feb 2014 10:08:30 +1300 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: Hi Corentin, If I read this correctly, once we have the type class representation, we no longer need the GADT. Try removing Exp, evaluate, and evalNoEff, and just use the procedures directly. On Thu, Feb 13, 2014 at 5:44 AM, Corentin Dupont wrote: > > Hi guys, > so I tried to implement fully the proposition (see below). > It works well. However I find it a bit redundant. Can we reduce the > repetitions? > Perhaps I didn't understand how to write the evaluation... > > > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > {-# LANGUAGE GADTs #-} > {-# LANGUAGE TypeSynonymInstances #-} > {-# LANGUAGE FlexibleInstances #-} > module Main where > > import Control.Monad.State > import Control.Monad.Reader > > class Monad m => Nomex m where > readAccount :: m Int > > class Nomex m => NomexEffect m where > writeAccount :: Int -> m () > setVictory :: (forall n. Nomex n => n Bool) -> m () > > data Exp a where > ReadAccount :: Exp Int > WriteAccount :: Int -> Exp () > SetVictory :: (forall m. Nomex m => m Bool) -> Exp () > Bind :: Exp a -> (a -> Exp b) -> Exp b > Return :: a -> Exp a > > instance Monad Exp where > return = Return > (>>=) = Bind > > instance Nomex Exp where > readAccount = ReadAccount > > instance NomexEffect Exp where > writeAccount = WriteAccount > setVictory = SetVictory > > data Game = Game { victory :: (forall m. Nomex m => m Bool) > , account :: Int > } > > instance Nomex (State Game) where > readAccount = gets account > > instance NomexEffect (State Game) where > writeAccount n = modify $ \game -> game { account = n } > setVictory v = modify $ \game -> game { victory = v } > > instance Nomex (Reader Game) where > readAccount = asks account > > evaluate :: Exp a -> State Game a > evaluate (WriteAccount i) = writeAccount i > evaluate ReadAccount = readAccount > evaluate (SetVictory v) = setVictory v > evaluate (Return a) = return a > evaluate (Bind a f) = (evaluate a) >>= evaluate . f > > evalNoEff :: Exp a -> Reader Game a > evalNoEff ReadAccount = readAccount > evalNoEff (Return a) = return a > evalNoEff (Bind a f) = (evalNoEff a) >>= evalNoEff . f > > isVictory :: Game -> Bool > isVictory g = runReader (evalNoEff (victory g)) g > > incrAccount :: NomexEffect m => m () > incrAccount = readAccount >>= writeAccount . (+101) > > winOnBigMoney :: NomexEffect m => m () > winOnBigMoney = setVictory $ do > i <- readAccount > --writeAccount 100 > return (i > 100) > > play = do > winOnBigMoney > incrAccount > > initGame = Game (return False) 0 > > main = do > let g = execState (evaluate jeu) initGame > putStrLn $ show $ isVictory g > > > > On Mon, Feb 10, 2014 at 11:33 AM, Dominique Devriese > wrote: >> >> Corentin, >> >> 2014-02-10 10:48 GMT+01:00 Corentin Dupont : >> > That is really interesting. In fact, I didn't have the time to >> > experiment >> > with it, but I definitely want to (have to find some spare time!). >> > I must say I am less used to type classes. >> > At first, my concern with the technique was that two things that belong >> > together, "ReadAccount" and "WriteAccount", are separated. >> >> Yes, this separation of ReadAccount and WriteAccount into Nomex vs >> NomexEffect is how the two parts (read-only vs read-write) of the DSL >> are distinguished in this approach.. >> >> > I was also confused that the evaluator is wrapped in a newtype, and that >> > it >> > is an instance of Nomex. >> >> That is non-essential. You can also use >> >> instance Nomex (State Game) where >> >> but it's just cleaner with a newtype... >> >> > Beside, I suppose it is possible to factorize EvalNoEffect with Eval? >> > Maybe >> > using liftEval anyway... >> >> If I understand correctly, you're asking about how to remove the >> duplication between EvalNoEffect and Eval? >> >> This is a very good question. My answer is basically that Haskell is >> missing some type-class-related features to allow for the perfect >> solution, specifically a form of local instances. >> >> The long story is that instead of the above instances of Nomex and >> NomexEffect for Eval and EvalNoEffect separately, we would like to be >> able to write the following instances: >> >> instance MonadReader Game m => Nomex m where >> readAccount = asks account >> >> instance (MonadReader Game m, MonadState Game m) => NomexEffect m where >> writeAccount n = modify $ \game -> game { account = n } >> setVictory v = modify $ \game -> game { victory = v } >> >> and then we can declare >> newtype Eval a = Eval { eval :: State Game a } >> deriving (Monad, MonadState Game, MonadReader Game) >> >> newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } >> deriving (Monad, MonadReader Game) >> >> and reuse the single implementation of Nomex for both Eval and >> EvalNoEffect. However, there are various problems with this solution: >> >> * the instances are not permitted without UndecidableInstances (which >> I recommend against), >> * the derivation of MonadReader from State won't work because >> MonadReader is not treated as a superclass of MonadState in Haskell, >> despite the fact that functionality-wise it is. >> >> What is needed to solve these problems is a feature that is in my >> opinion strongly missing in Haskell: a form of local instances. This >> means that we would be able to explicitly specify what implementation >> of a certain type class should be used to satisfy a certain type class >> constraint, e.g. >> >> sort :: Ord a => [a] -> [a] >> sortBy :: forall a. (a -> a -> Bool) -> [a] -> [a] >> sortBy f = let instance ordDict :: Ord.Dict a >> ordDict = constructOrdDict f >> in sort :: Ord a => [a] -> [a] >> >> Local instances were already considered by Wadler when he proposed >> type classes, but they are problematic to combine with type inference. >> However, it seems likely that this is not an issue if we require >> sufficiently informative type annotations. >> >> For the problem above, this would allow to construct, use and lift >> (together with newtype coercions) a MonadReader dictionary for the >> State monad without necessarily having it derived automatically if >> this is not desired. Also, this would allow to write the undecidable >> instances as normal functions that need to be explicitly invoked >> instead of inferred by type inference, avoiding the >> UndecidableInstances problem. >> >> Regards >> Dominique > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Chris Wong, fixpoint conjurer e: lambda.fairy at gmail.com w: http://lfairy.github.io From hjgtuyl at chello.nl Wed Feb 12 22:17:07 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Wed, 12 Feb 2014 23:17:07 +0100 Subject: [Haskell-cafe] Lisp Style Restarts in Haskell In-Reply-To: References: <52F90D62.20308@frigidcode.com> Message-ID: Or Control.Exception in the base package? On Wed, 12 Feb 2014 19:16:39 +0100, Erik Dominikus wrote: > How about the Control.Retry module in the 'retry' package? > > http://hackage.haskell.org/package/retry > On Feb 11, 2014 12:51 AM, "Christopher Howard" < > christopher.howard at frigidcode.com> wrote: > >> Hi. I was curious if Haskell has something like "restarts" in Common >> Lisp. My search engines didn't give relevant results for "Haskell >> restarts". However, there were several results for "Haskell coroutines" >> and, from what I can gather, restarts and coroutines are a similar or >> related subject. >> Regards, Henk-Jan van Tuyl -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From ky3 at atamo.com Wed Feb 12 22:58:29 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Thu, 13 Feb 2014 05:58:29 +0700 Subject: [Haskell-cafe] Lisp Style Restarts in Haskell In-Reply-To: <52F90D62.20308@frigidcode.com> References: <52F90D62.20308@frigidcode.com> Message-ID: On Tue, Feb 11, 2014 at 12:33 AM, Christopher Howard < christopher.howard at frigidcode.com> wrote: > I was curious if Haskell has something like "restarts" in Common > Lisp. My search engines didn't give relevant results for "Haskell > restarts". > Searching "lisp style restarts" brings up this Haskell-relevant link: http://lambda-the-ultimate.org/node/1544 -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From jake.mcarthur at gmail.com Wed Feb 12 23:44:46 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Wed, 12 Feb 2014 18:44:46 -0500 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: References: <20140129033404.76144.qmail@www1.g3.pair.com> Message-ID: As Chris says, you no longer need the GADT at all. {-# LANGUAGE RankNTypes #-} {-# LANGUAGE FlexibleInstances #-} import Control.Monad.Identity import Control.Monad.State import Control.Monad.Reader class Monad m => Nomex m where readAccount :: m Int class Nomex m => NomexEffect m where writeAccount :: Int -> m () setVictory :: (forall n. Nomex n => n Bool) -> m () data Game = Game { victory :: (forall m. Nomex m => m Bool) , account :: Int } instance Nomex (State Game) where readAccount = gets account instance NomexEffect (State Game) where writeAccount n = modify $ \game -> game { account = n } setVictory v = modify $ \game -> game { victory = v } instance Nomex (Reader Game) where readAccount = asks account isVictory :: Game -> Bool isVictory = join (runReader . victory) incrAccount :: NomexEffect m => m () incrAccount = readAccount >>= writeAccount . (+101) winOnBigMoney :: NomexEffect m => m () winOnBigMoney = setVictory $ do i <- readAccount --writeAccount 100 return (i > 100) play :: StateT Game Identity () play = do winOnBigMoney incrAccount initGame :: Game initGame = Game (return False) 0 main :: IO () main = do let g = execState play initGame putStrLn $ show $ isVictory g On Wed, Feb 12, 2014 at 11:44 AM, Corentin Dupont wrote: > > Hi guys, > so I tried to implement fully the proposition (see below). > It works well. However I find it a bit redundant. Can we reduce the > repetitions? > Perhaps I didn't understand how to write the evaluation... > > > {-# LANGUAGE RankNTypes #-} > {-# LANGUAGE GeneralizedNewtypeDeriving #-} > {-# LANGUAGE GADTs #-} > {-# LANGUAGE TypeSynonymInstances #-} > {-# LANGUAGE FlexibleInstances #-} > module Main where > > > import Control.Monad.State > import Control.Monad.Reader > > class Monad m => Nomex m where > readAccount :: m Int > > class Nomex m => NomexEffect m where > writeAccount :: Int -> m () > setVictory :: (forall n. Nomex n => n Bool) -> m () > > > data Exp a where > ReadAccount :: Exp Int > WriteAccount :: Int -> Exp () > SetVictory :: (forall m. Nomex m => m Bool) -> Exp () > Bind :: Exp a -> (a -> Exp b) -> Exp b > > Return :: a -> Exp a > > instance Monad Exp where > > return = Return > (>>=) = Bind > > instance Nomex Exp where > readAccount = ReadAccount > > instance NomexEffect Exp where > writeAccount = WriteAccount > setVictory = SetVictory > > > data Game = Game { victory :: (forall m. Nomex m => m Bool) > , account :: Int > } > > instance Nomex (State Game) where > readAccount = gets account > > instance NomexEffect (State Game) where > > writeAccount n = modify $ \game -> game { account = n } > setVictory v = modify $ \game -> game { victory = v } > > instance Nomex (Reader Game) where > readAccount = asks account > > evaluate :: Exp a -> State Game a > evaluate (WriteAccount i) = writeAccount i > evaluate ReadAccount = readAccount > evaluate (SetVictory v) = setVictory v > evaluate (Return a) = return a > evaluate (Bind a f) = (evaluate a) >>= evaluate . f > > evalNoEff :: Exp a -> Reader Game a > evalNoEff ReadAccount = readAccount > evalNoEff (Return a) = return a > evalNoEff (Bind a f) = (evalNoEff a) >>= evalNoEff . f > > isVictory :: Game -> Bool > isVictory g = runReader (evalNoEff (victory g)) g > > incrAccount :: NomexEffect m => m () > incrAccount = readAccount >>= writeAccount . (+101) > > winOnBigMoney :: NomexEffect m => m () > winOnBigMoney = setVictory $ do > i <- readAccount > --writeAccount 100 > return (i > 100) > > play = do > winOnBigMoney > incrAccount > > initGame = Game (return False) 0 > > main = do > let g = execState (evaluate jeu) initGame > putStrLn $ show $ isVictory g > > > > On Mon, Feb 10, 2014 at 11:33 AM, Dominique Devriese < > dominique.devriese at cs.kuleuven.be> wrote: > >> Corentin, >> >> 2014-02-10 10:48 GMT+01:00 Corentin Dupont : >> > That is really interesting. In fact, I didn't have the time to >> experiment >> > with it, but I definitely want to (have to find some spare time!). >> > I must say I am less used to type classes. >> > At first, my concern with the technique was that two things that belong >> > together, "ReadAccount" and "WriteAccount", are separated. >> >> Yes, this separation of ReadAccount and WriteAccount into Nomex vs >> NomexEffect is how the two parts (read-only vs read-write) of the DSL >> are distinguished in this approach.. >> >> > I was also confused that the evaluator is wrapped in a newtype, and >> that it >> > is an instance of Nomex. >> >> That is non-essential. You can also use >> >> instance Nomex (State Game) where >> >> but it's just cleaner with a newtype... >> >> > Beside, I suppose it is possible to factorize EvalNoEffect with Eval? >> Maybe >> > using liftEval anyway... >> >> If I understand correctly, you're asking about how to remove the >> duplication between EvalNoEffect and Eval? >> >> This is a very good question. My answer is basically that Haskell is >> missing some type-class-related features to allow for the perfect >> solution, specifically a form of local instances. >> >> The long story is that instead of the above instances of Nomex and >> NomexEffect for Eval and EvalNoEffect separately, we would like to be >> able to write the following instances: >> >> instance MonadReader Game m => Nomex m where >> readAccount = asks account >> >> instance (MonadReader Game m, MonadState Game m) => NomexEffect m where >> writeAccount n = modify $ \game -> game { account = n } >> setVictory v = modify $ \game -> game { victory = v } >> >> and then we can declare >> newtype Eval a = Eval { eval :: State Game a } >> deriving (Monad, MonadState Game, MonadReader Game) >> >> newtype EvalNoEffect a = EvalNoEffect { evalNoEffect :: Reader Game a } >> deriving (Monad, MonadReader Game) >> >> and reuse the single implementation of Nomex for both Eval and >> EvalNoEffect. However, there are various problems with this solution: >> >> * the instances are not permitted without UndecidableInstances (which >> I recommend against), >> * the derivation of MonadReader from State won't work because >> MonadReader is not treated as a superclass of MonadState in Haskell, >> despite the fact that functionality-wise it is. >> >> What is needed to solve these problems is a feature that is in my >> opinion strongly missing in Haskell: a form of local instances. This >> means that we would be able to explicitly specify what implementation >> of a certain type class should be used to satisfy a certain type class >> constraint, e.g. >> >> sort :: Ord a => [a] -> [a] >> sortBy :: forall a. (a -> a -> Bool) -> [a] -> [a] >> sortBy f = let instance ordDict :: Ord.Dict a >> ordDict = constructOrdDict f >> in sort :: Ord a => [a] -> [a] >> >> Local instances were already considered by Wadler when he proposed >> type classes, but they are problematic to combine with type inference. >> However, it seems likely that this is not an issue if we require >> sufficiently informative type annotations. >> >> For the problem above, this would allow to construct, use and lift >> (together with newtype coercions) a MonadReader dictionary for the >> State monad without necessarily having it derived automatically if >> this is not desired. Also, this would allow to write the undecidable >> instances as normal functions that need to be explicitly invoked >> instead of inferred by type inference, avoiding the >> UndecidableInstances problem. >> >> Regards >> Dominique >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From oleg at okmij.org Thu Feb 13 07:28:25 2014 From: oleg at okmij.org (oleg at okmij.org) Date: 13 Feb 2014 07:28:25 -0000 Subject: [Haskell-cafe] manage effects in a DSL In-Reply-To: Message-ID: <20140213072825.96930.qmail@www1.g3.pair.com> Sorry for the very late and probably no longer relevant reply. > Building up on the exemple below, I have a problem with mixing > effectful/effectless computations. For example, this would not compile: > > > noEff :: Exp NoEffect () > > noEff = return () > > > hasEffect :: Exp Effect () > > hasEffect = do > > noEff <--- won't compile > > return () > > But it should: you should be able to run an effectless monad in an > effectful one. How to encode this semantic? This is a very, very common problem. We have an expression e of type T1, and we want to use it in the context that requires the type T2 (e.g., we want to pass 'e' to a function whose argument type is T2). We feel that we ought to be able to do that. One example is the one you cited: a computation that performs no effect can be regarded as a computation that _may_ perform an effect, and so we should be able to use a non-effectful expression in an effectful context. Another example is numerics: natural numbers are subset of rationals; so it should be morally OK to use a natural number where a rational is required. There are two ways of solving this problem. One is polymorphism, another is subtyping. In the first approach, we define noEff above with the polymorphic type: > noEff :: forall r. Exp r () > noEff = return () This says that noEff can be used either in NoEffect or Effect contexts. Polymorphic terms can be regarded as `macros', at least conceptually, -- sort of as an abbreviation for the family of definitions noEff_1 :: Exp NoEffect () noEff_1 = return () noEff_2 :: Exp Effect () noEff_2 = return () When you use noEff in the program, the compiler chooses either noEff_1 or noEff_2 depending on the type required by the context. (GHC actually does that in some circumstances). Subtyping means defining a (partial) order among types T2 >= T1 and adding a subsumption rule to the type system e :: T1 T2 >= T1 ----------------- e :: T2 That is, if e has type T1 and T2 is at least as great, e can be given the type T2. Such a rule is very common in various object systems. Since we can't add new rules into the Haskell type system, we have to use a work-around, the explicit coercion. We introduce a function coerce :: T1 -> T2 (often an identity), which is a proof that it is really OK to use (e::T1) at the type T2. We have to explicitly write this coercion function: > hasEffect :: Exp Effect () > hasEffect = do > coerceEff noEff > return () We are all familiar with this approach, explicitly writing 'return 1' to, say, return an integer result from a monadic function. Here, return is the explicit coercion, from 1::Int (the pure expression) to m Int (the potentially effectful expression). Other familiar example is newtype: newtype Speed = Speed{unSpeed :: Float} Then expressions (Speed 1.0) or (unSpeed x) / 10.0 etc. are all examples of explicit coercions (which are operationally identity). [Here were do want the coercions to be explicit, at least the Float->Speed coercion. The other could be implicit.] Haskell uses this approach for numeric literals. When we want to use an integer 1 where a rational number is required, we have to write fromInteger 1. Here fromInteger being the explicit coercion. Only we don't have to write 'fromInteger' because GHC inserts it implicitly. The latter example makes too points: explicit coercions are cumbersome to write and we'd rather had them out of sight. The second point is that the coercion is not a single function, but an overloaded function (e.g., return fromInteger). The coercions return and fromInteger are also not operationally identity, which actually do something at run-time. Let's go back to our example and change it to be more interesting, splitting Effect into Read and Write effects, with the order NoEffect < ReadEff < WriteEff. To witness the order, we define class Coerce t1 t2 where coerce :: Exp t1 a -> Exp t2 a instance Coerce NoEffect ReadEff where ... instance Coerce NoEffect WriteEff where ... instance Coerce ReadEffect WriteEff where ... so that we can define > noEff :: Exp NoEffect () > noEff = return () and write (coerce noEff) if we want to use noEff in effectful situations. We observe that if we make Coerce reflexive, that is, add instance Coerce NoEffect NoEffect where coerce = id ... then we can write (coerce noEff) all the time. And if we do that, why not to fuse coerce into the definition of noEff: > noEff :: Coerce Noeff r => Exp r () > noEff = coerce (return ()) We come the full circle to polymorphism -- although generally bounded polymorphism. (In noEff example above we can drop the Coerce constraint since Noeff can be coerced to any other effect. Not so for ReadEffect). > > data Exp :: Eff -> * -> * where > > ReadAccount :: Exp NoEffect Int --ReadAccount has no effect > > Bind :: Effects m n r => Exp m a -> (a -> Exp n b) -> Exp r b > > ... > > hasEffect :: Exp Effect () > > hasEffect = ReadAccount >> (returnM () :: Exp Effect ()) > This is working more or less, however I am obliged to put the type > signature on the returnM (last line): why? This is the infamous read-show problem. See for example http://book.realworldhaskell.org/read/using-typeclasses.html#typeclasses.wellknown.read > eval :: Nomex r a -> State Game a > eval a at ReadAccount = liftEval $ evalNoEffect a > eval (WriteAccount a) = modify (\g -> g{account = a}) > eval (SetVictory v) = modify (\g -> g{victory = v}) > eval a@(Return _) = liftEval $ evalNoEffect a > eval (Bind exp f) = eval exp >>= eval . f This is a common pitfall. We should write > eval :: Nomex r a -> State Game a > eval ReadAccount = liftEval $ evalNoEffect ReadAccount > eval (Return x) = liftEval $ evalNoEffect (Return x) > ... It seems like a boilerplate: why do we have to write the same 'ReadAccount' on the left hand side and on the right-hand side (ditto for Return x). Can't we just share, like in the original code? The answer is no: The ReadAccount on the left hand side of the eval equation is different from ReadAccount on the right-hand side. They are spelled the same, but their types differ. On the left-hand-side, ReadAccount :: Nomex Effect (), but on the right-hand side, ReadAccount :: Nomex Effect (). This is a frequent problem with constants like [] which may have more than one type. From drowland at lincoln.ac.uk Thu Feb 13 08:29:31 2014 From: drowland at lincoln.ac.uk (Duncan Rowland) Date: Thu, 13 Feb 2014 08:29:31 +0000 Subject: [Haskell-cafe] ghci in gallery Message-ID: Dear All, new to haskell, so this might be obvious, but... I'm setting up a gallery installation (OSX) that exposes a command line haskell to the visitors. The process is run with user 'nobody', so hopefully that will be a bit safer, i.e. cat visitor_commands_pipe | sudo -u nobody ghci -XOverloadedStrings But how question are: 1) what sort of damage could a malicious user do to my system by entering commands into the pipe? 2) what should I do to protect my system? I can filter the user commands as I like, but I do not want to run 'in a webpage'. Thanks in advance, -Duncan. From haskell at ibotty.net Thu Feb 13 09:01:32 2014 From: haskell at ibotty.net (Tobias Florek) Date: Thu, 13 Feb 2014 10:01:32 +0100 Subject: [Haskell-cafe] ghci in gallery In-Reply-To: References: Message-ID: <52FC89EC.2020008@ibotty.net> hi, > The process is run with user 'nobody', so hopefully that will be a > bit safer, i.e. a bit, yes. apart from breaking out of the account (and becoming root) via os vulnerabilities the user can send any network traffic they like, which might or might not be ok. also there might be any number of important processes running for user nobody. you better use a dedicated user for running ghci. that might also allow you to sandbox the account easier (firewall and dac's/mac's, etc. i don't know what's available on mac os x). you might also like to look into SafeHaskell to restrict what users can do. good luck, tobias florek From haskell at ibotty.net Thu Feb 13 09:01:41 2014 From: haskell at ibotty.net (Tobias Florek) Date: Thu, 13 Feb 2014 10:01:41 +0100 Subject: [Haskell-cafe] ghci in gallery In-Reply-To: References: Message-ID: <52FC89F5.6060306@ibotty.net> hi, > The process is run with user 'nobody', so hopefully that will be a > bit safer, i.e. a bit, yes. apart from breaking out of the account (and becoming root) via os vulnerabilities the user can send any network traffic they like, which might or might not be ok. also there might be any number of important processes running for user nobody. you better use a dedicated user for running ghci. that might also allow you to sandbox the account easier (firewall and dac's/mac's, etc. i don't know what's available on mac os x). you might also like to look into SafeHaskell to restrict what users can do. good luck, tobias florek From mlen at mlen.pl Thu Feb 13 09:51:32 2014 From: mlen at mlen.pl (Mateusz Lenik) Date: Thu, 13 Feb 2014 10:51:32 +0100 Subject: [Haskell-cafe] ghci in gallery In-Reply-To: References: Message-ID: <20140213095132.GA19735@polaris.local> Hi Duncan, I'd highly recommend using something like mueval: http://hackage.haskell.org/package/mueval In the setup you suggested malicious user can: 1) execute other processes (to create a remote shell using nc, or to try to exploit suid binaries), 2) do any network IO (to send spam for example), 3) read files readable to all users (kind of obvious, but /etc/passwd can be read by anyone on the system -- attackers can learn who uses the system, what services are running), 4) it allows access to loopback interface which it makes it very hard to firewall it properly. And this is only the stuff that came up to my mind in 5 minutes. Basically this setup is like giving anyone access to shell. Cheers, Mateusz On Thu, Feb 13, 2014 at 08:29:31AM +0000, Duncan Rowland wrote: > Dear All, > > new to haskell, so this might be obvious, but... > > I'm setting up a gallery installation (OSX) that exposes a command > line haskell to the visitors. > The process is run with user 'nobody', so hopefully that will be a > bit safer, i.e. > > cat visitor_commands_pipe | sudo -u nobody ghci -XOverloadedStrings > > But how question are: > 1) what sort of damage could a malicious user do to my system by > entering commands into the pipe? > 2) what should I do to protect my system? I can filter the user > commands as I like, but I do not want to run 'in a webpage'. > > Thanks in advance, > -Duncan. > _______________________________________________ > 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: not available Type: application/pgp-signature Size: 833 bytes Desc: not available URL: From chriswarbo at googlemail.com Thu Feb 13 09:58:38 2014 From: chriswarbo at googlemail.com (Chris Warburton) Date: Thu, 13 Feb 2014 09:58:38 +0000 Subject: [Haskell-cafe] ghci in gallery In-Reply-To: (Duncan Rowland's message of "Thu, 13 Feb 2014 08:29:31 +0000") References: Message-ID: <86iosjs59t.fsf@gmail.com> Duncan Rowland writes: > 2) what should I do to protect my system? I can filter the user > commands as I like, but I do not want to run 'in a webpage'. You might want to read http://www.haskell.org/haskellwiki/Safely_running_untrusted_Haskell_code which explains the security measures taken by "lambdabot" (an IRC bot which executes any Haskell code it's sent) Cheers, Chris From mbrock at goula.sh Thu Feb 13 11:10:28 2014 From: mbrock at goula.sh (Mikael Brockman) Date: Thu, 13 Feb 2014 12:10:28 +0100 Subject: [Haskell-cafe] Lisp Style Restarts in Haskell References: <52F90D62.20308@frigidcode.com> Message-ID: "Henk-Jan van Tuyl" writes: > Or Control.Exception in the base package? With Lisp-style restarts, exceptions (Common Lisp calls them "conditions") don't necessarily "unwind the stack." Instead, they provide a set of alternatives for how to proceed. Calls to the throwing function can be wrapped in a handler that chooses, say, whether to skip or abort. To take a Haskell example, Data.Text.Encoding has an API for doing Unicode decoding with "controllable error handling." It's pretty simple, and not very flexible. > type OnDecodeError = String -> Maybe Word8 -> Maybe Char > > decodeUtf8With :: OnDecodeError -> ByteString -> Text Considering some different possibilities for this API... Something like this (a kind of defunctionalized version) might be more familiar to a CL programmer: > data DecodeCondition = InvalidWord Word8 | UnexpectedEOF > data DecodeRestart = Ignore | UseChar Char > > decodeUtf8With :: (DecodeCondition -> DecodeRestart) > -> ByteString -> Text We can use ImplicitParams to approximate the dynamic scope behavior, and LambdaCase to write what CL calls the "restart-case": > decodeUtf8 :: (?restart :: DecodeCondition -> DecodeRestart) > -> ByteString -> Text Usage: > myDecode s = > let ?restart = \case InvalidWord _ -> UseChar '*' > UnexpectedEOF -> Ignore > in decodeUtf8 s * * * One of the cool things about CL's condition system that this implementation doesn't capture is the way the runtime environment can provide interactive prompts for restarting uncaught conditions. An example session: > CL-USER 6 > (restartable-gethash 'mango *fruits-and-vegetables*) > > Error: RESTARTABLE-GETHASH error getting MANGO [...] > 1 (continue) Return not having found the value. > 2 Try getting the key from the hash again. > 3 Use a new key. > 4 Use a new hash. > 5 (abort) Return to level 0. > 6 Return to top loop level 0. > > Type :b for backtrace, :c