From icfp.publicity at googlemail.com Fri Jul 1 02:11:16 2016 From: icfp.publicity at googlemail.com (Lindsey Kuper) Date: Thu, 30 Jun 2016 19:11:16 -0700 Subject: [Haskell-cafe] Deadline extended: Commercial Users of Functional Programming Call For Tutorials Message-ID: The 2016 Commercial Users of Functional Programming (CUFP) call for tutorials have passed the initial deadlines, but we have more seat for tutors. CUFP tutorial is a good opportunity if you have some idea you want to spread to the real world, say, your favorite programming language (Clojure, Erlang, F#, F*, Haskell, ML, OCaml, Scala, Scheme...), concepts (e.g. Lens, Liquid-Haskell, Proof Assistance, ...), applications (Web, high-performance computing, finance...,) tools and techniques (QuickCheck, Elm, ...), or theories. If you are interested, we kindly invite you to submit a proposal for the Call For Tutorials from here: http://cufp.org/2016/call-for-tutorials.html , before July 3rd. If you have any questions, please do not hesitate to contact us: Roman Gonzalez: roman at unbounce.com Takayuki Muranushi: muranushi at gmail.com best regards, Takayuki From icfp.publicity at googlemail.com Fri Jul 1 02:20:11 2016 From: icfp.publicity at googlemail.com (Lindsey Kuper) Date: Thu, 30 Jun 2016 19:20:11 -0700 Subject: [Haskell-cafe] ICFP 2016 Student Research Competition: Call for Submissions Message-ID: ====================================================================== CALL FOR SUBMISSIONS SRC at ICFP 2016 Nara, Japan 18-24 September 2016 http://conf.researchr.org/info/icfp-2016/student-research-competition Co-located with the International Conference on Functional Programming (ICFP 2016) ====================================================================== Student Research Competition ---------------------------- This year ICFP will host a Student Research Competition where undergraduate and postgraduate students can present posters. The SRC at ICFP 2016 consists of three rounds: * Extended abstract round. All students are encouraged to submit an extended abstract of up to 800 words outlining their research. * Poster session. Based on the abstracts, a panel of judges will select the most promising entrants to participate in the poster session which will take place at ICFP. Students who make it to this round will be eligible for some travel support to attend the conference. In the poster session, students will have the opportunity to present their work to the judges, who will select three finalists in each category (graduate/undergraduate) to advance to the next round. * ICFP presentation. The last round will consist of an oral presentation at ICFP to compete for the final award. Prizes ------ * The top three graduate and the top three undergraduate winners will receive prizes of $500, $300, and $200, respectively. * All six winners will receive award medals and a two-year complimentary ACM student membership, including a subscription to ACM's Digital Library. * The names of the winners will be posted on the ACM SRC web site. * The first-place winners will be invited to participate in the ACM SRC Grand Finals, an on-line round of competition among the winners of conference-hosted SRCs. * Grand Finalists and their advisors will be invited to the Annual ACM Awards Banquet for an all-expenses-paid trip, where they will be recognized for their accomplishments along with other prestigious ACM award winners, including the winner of the Turing Award (also known as the Nobel Prize of Computing). * The top three graduate Grand Finalists will receive an additional $500, $300, and $200. Likewise, the top three undergraduate Grand Finalists will receive an additional $500, $300, and $200. All six Grand Finalists will receive Grand Finalist certificates. * The ACM, Microsoft Research, and our industrial partners provide financial support for students attending the SRC. You can find more information about this on the ACM website. Eligibility ----------- The SRC is open to both undergraduate (not in a PhD programme) and graduate students (in a PhD programme). Upon submission, entrants must be enrolled as a student at their universities, and are ACM student members. Furthermore, there are some constraints on what kind of work may be submitted. Previously published work: Submissions should consist of original work (not yet accepted for publication). If the work is a continuation of previously published work, the submission should focus on the contribution over what has already been published. We encourage students to see this as an opportunity to get early feedback and exposure for the work they plan to submit to the next ICFP or POPL. Collaborative work: Students are encouraged to submit work they have been conducting in collaboration with others, including advisors, internship mentors, or other students. However, submissions are individual, so they must focus on the contributions of the student. Submission Details ------------------ Each submission should include the student author's name, institutional affiliation, e-mail address, and postal address; research advisor's name; ACM student member number; category (undergraduate or graduate); research title; and an extended abstract addressing the following: * Problem and Motivation: Clearly state the problem being addressed and explain the reasons for seeking a solution to this problem. * Background and Related Work: Describe the specialized (but pertinent) background necessary to appreciate the work. Include references to the literature where appropriate, and briefly explain where your work departs from that done by others. * Approach and Uniqueness: Describe your approach in attacking the problem and clearly state how your approach is novel. * Results and Contributions: Clearly show how the results of your work contribute to computer science and explain the significance of those results. The abstract must describe the student's individual research and must be authored solely by the student. If the work is collaborative with others and/or part of a larger group project, the abstract should make clear what the student's role was and should focus on that portion of the work. The extended abstract must not exceed 800 words and must not be longer than 2 pages. The reference list does not count towards these limits. To submit an abstract, please register through the submission page and follow the instructions. Abstracts submitted after the deadline may be considered at the committee's discretion, but only after decisions have been made on all abstracts submitted before the deadline. If you have any problems, don't hesitate to contact the competition chair. Please submit your abstract at the EasyChair submission page: https://easychair.org/conferences/?conf=icfp2016src Important Dates --------------- * Deadline for submission: 3 August * Notification of acceptance: 10 August Selection Committee ------------------- To include: Chair: David Van Horn, University of Maryland Ronald Garcia, University of British Columbia Ilya Sergey, University College London From vogt.adam at gmail.com Fri Jul 1 13:18:16 2016 From: vogt.adam at gmail.com (adam vogt) Date: Fri, 1 Jul 2016 09:18:16 -0400 Subject: [Haskell-cafe] Type-class predicates head-normal forms In-Reply-To: References: Message-ID: Hi Sheng, Maybe MPTCs can be explained as syntax sugar for extensions that might be (more easily) specified. http://lpaste.net/168659 has one version using type equality (GADTs here), and another that depends on user discipline. I think both translations need FlexibleInstances/FlexibleContexts. Regards, Adam On Wed, Jun 22, 2016 at 1:31 AM, sheng chen wrote: > Hello, > > I got a question about what the form of types in Haskell are allowed. > Specifically, what are the requirements of the context of a type? The paper > > Typing Haskell in Haskell > > required the type to be in the form P => t, where P to be in head-normal > form or in other words shouldn't be something like Num Bool. > > Now what about multi-parameter classes? The paper > > Type classes: an exploration of the design space > > listed several potential choices but didn't say exactly what. > > The Haskell 2010 report covered single-parameter type classes only. > > Given the following definition. > > class Collects ce e | ce -> e where > empty :: ce > insert :: e -> ce -> ce > > insert2 c = insert True (insert False c) > > The function insert2 has the following type > > insert2 :: Collects ce Bool => ce -> ce > > This shows that the definition of head-normal forms for multi-parameter > class differs from that for single-parameter classes. Is there any definite > specification about the context of Haskell types? > > Thank you, > Sheng > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From wangbj at gmail.com Fri Jul 1 17:28:43 2016 From: wangbj at gmail.com (Baojun Wang) Date: Fri, 01 Jul 2016 17:28:43 +0000 Subject: [Haskell-cafe] type level Min function for GHC.TypeLits? Message-ID: Hi Cafe, I'm trying to do some basic type level tricks, I wonder whether it is possible to get ``vZipWith`` in below code snippet working: {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -fplugin GHC.TypeLits.Normalise #-} import GHC.TypeLits import Data.Proxy data Vect :: (Nat -> * -> *) where VNil :: Vect 0 a VCons :: a -> Vect n a -> Vect (1+n) a deriving instance (Show a) => Show (Vect n a) vlength :: forall n a . KnownNat n => Vect n a -> Integer vlength _ = natVal (Proxy :: Proxy n) vconcat :: Vect n a -> Vect m a -> Vect (n+m) a -- Need type checker plugin vconcat VNil ys = ys vconcat xs VNil = xs vconcat (VCons x xs) ys = VCons x (vconcat xs ys) type family Min3 (t :: Bool) (m :: Nat) (n :: Nat) :: Nat type instance Min3 'True m n = m type instance Min3 'False m n = n type Min m n = Min3 (m <=? n) m n vZipWith :: (a -> b -> c) -> Vect m a -> Vect n b -> Vect (Min m n) c vZipWith f VNil _ = VNil vZipWith f _ VNil = VNil vZipWith f (VCons x xs) (VCons y ys) = f x y `VCons` vZipWith f xs ys As I got errors: /home/wangbj/downloads/stack/vect/src/Vect.hs:51:21: Could not deduce (Min3 (m <=? 0) m 0 ~ 0) from the context (n ~ 0) bound by a pattern with constructor VNil :: forall a. Vect 0 a, in an equation for ‘vZipWith’ at /home/wangbj/downloads/stack/vect/src/Vect.hs:51:14-17 Expected type: Vect (Min m n) c Actual type: Vect 0 c Relevant bindings include vZipWith :: (a -> b -> c) -> Vect m a -> Vect n b -> Vect (Min m n) c (bound at /home/wangbj/downloads/stack/vect/src/Vect.hs:50:1) In the expression: VNil In an equation for ‘vZipWith’: vZipWith f _ VNil = VNil /home/wangbj/downloads/stack/vect/src/Vect.hs:52:40: Could not deduce (Min3 (m <=? n) m n ~ (1 + Min3 (n1 <=? n2) n1 n2)) from the context (m ~ (1 + n1)) bound by a pattern with constructor VCons :: forall a (n :: Nat). a -> Vect n a -> Vect (1 + n) a, in an equation for ‘vZipWith’ at /home/wangbj/downloads/stack/vect/src/Vect.hs:52:13-22 or from (n ~ (1 + n2)) bound by a pattern with constructor VCons :: forall a (n :: Nat). a -> Vect n a -> Vect (1 + n) a, in an equation for ‘vZipWith’ at /home/wangbj/downloads/stack/vect/src/Vect.hs:52:26-35 Expected type: Vect (Min m n) c Actual type: Vect (1 + Min n1 n2) c Relevant bindings include ys :: Vect n2 b (bound at /home/wangbj/downloads/stack/vect/src/Vect.hs:52:34) xs :: Vect n1 a (bound at /home/wangbj/downloads/stack/vect/src/Vect.hs:52:21) vZipWith :: (a -> b -> c) -> Vect m a -> Vect n b -> Vect (Min m n) c (bound at /home/wangbj/downloads/stack/vect/src/Vect.hs:50:1) In the expression: f x y `VCons` vZipWith f xs ys In an equation for ‘vZipWith’: vZipWith f (VCons x xs) (VCons y ys) = f x y `VCons` vZipWith f xs ys Failed, modules loaded: none. Also I tried https://github.com/yav/type-nat-solver but got error like: *** Exception: user error (Unexpected result from the SMT solver: Expected: success Result: (error "line 57 column 16: unknown constant tn_0" ) Which I have no idea what it really means. Is there any way to get ``vZipWith`` working without too much hassle? Thanks baojun -------------- next part -------------- An HTML attachment was scrubbed... URL: From madjestic13 at gmail.com Fri Jul 1 22:11:02 2016 From: madjestic13 at gmail.com (Vlad Lopatin) Date: Sat, 2 Jul 2016 00:11:02 +0200 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 154, Issue 27 In-Reply-To: References: Message-ID: Re: up-to-date glfw examples (briand at aracnet.com) Hey, Brian Here's a bare-bones example of modern OpenGL(4.5) (VBO's, vertex/fragment shaders), using GLFW-b to handle windows/input and Yampa for animation. Shader-loading is handled by Sven Panne's code: https://github.com/madjestic/Haskell-OpenGL-Tutorial/tree/master/Mandelbrot-FRP Cheers, Vlad -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Sat Jul 2 03:34:41 2016 From: will.yager at gmail.com (William Yager) Date: Fri, 1 Jul 2016 20:34:41 -0700 Subject: [Haskell-cafe] How to make Repa do stencils unboxed? Message-ID: Hello all, TL;DR: Repa appears to be calculating my stencil operation using boxed arithmetic, which is very slow. How do I make it do unboxed arithmetic? I am currently working on a project where I need to simulate a 2D environment that exhibits wave behavior. I'm accomplishing this by directly discretizing the wave equation and turning it into a cellular automaton. The math here is relatively simple. Let's specify the example to the physical system of a rubber sheet, which exhibits wave behavior. To simulate a rubber sheet, you divide it up into grids. Then, you keep track of the velocity and height of each grid. At each iteration of the simulation, you update the velocity of each grid based on the force exerted upon it by its neighboring grids. This is simply a linear multiple of the distance between the grid and its neighbors (i.e. how stretched the sheet is). For example, if cell x is at height X, and its neighbors a,b,c,d are at height A,B,C,D, the tension on X is, for some constant L, T = L*((A-X)+(B-X)+...) = L*(A+B+C+D-4X). You can calculate this efficiently via a matrix convolution, in particular by a convolution with the matrix [[ 0 1 0 1 -4 1 0 1 0 ]] You can be more physically accurate by including the diagonals (weighted down a bit). A popular stencil for such purposes is [[ 1 2 1 2 -12 2 1 2 1 ]] Technically the off-diagonal elements should be something like sqrt(2), but this is sufficient for most purposes. After calculating the tension matrix, you divide it by the mass of each grid. This is the acceleration on each grid. Multiply it by the length of your time step, and you get the change in velocity of each grid. Add this to the velocity matrix. Then, multiply the velocity matrix by the time step, and that's the change in height. Add this to the height matrix. Boom, you've simulated a single time step of a rubber sheet. Keep doing this over and over to get the time-evolution of the rubber sheet. My code to do this is as follows: https://gist.github.com/wyager/8c468c9d18ad62aff8bc9738aa947ea4 The imports are messy; sorry about that. You'll notice I'm using the Dimensional library, which provides statically typed physical dimensions over any numeric value using a newtype wrapper with typelits. Hopefully this isn't slowing things down somehow. According to profiling via "ghc -Odph -rtsopts -threaded -fno-liberate-case -funfolding-use-threshold1000 -funfolding-keeness-factor1000 -optlo-O3 -fforce-recomp -prof -fprof-auto -fexternal-interpreter RepaSim.hs" (whew), fully 80% of time and 84% of allocation comes from the stencil operation. The simulation starts with a rubber sheet with a smooth bump in the middle, simulates 100ms of time steps, saves a .png file of the sheet, and then repeats n times (n is typed in via standard input). How can I make Repa do this stencil unboxed, and are there other things I should be doing to get better performance? Thanks, Will -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Sat Jul 2 04:49:55 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sat, 02 Jul 2016 00:49:55 -0400 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity Message-ID: <1467429537-sup-6217@sabre> In 2010, in the thread "Asynchronous exception wormholes kill modularity" [1], Bas van Dijk observed that 'unblock :: IO a -> IO a' broke modularity, as the sequence of calls 'block . block . unblock $ io' would result in 'io' being run with asynchronous exceptions unblocked, despite the outer 'block' "expecting" that asynchronous exceptions cannot be thrown. I would like to make two claims: 1. The new mask/restore interface is insufficient to "solve" this modularity problem, as *interruptible* operations can still be used to catch asynchronous exceptions. 2. Thus, we should provide an unblock combinator which can be used to catch asynchronous exceptions from a 'mask' (though not an 'uninterruptibleMask')--though it is doubtful if anyone should ever use 'mask' in the first place. Claim 1: Here is some code which reimplements 'unblock': import Control.Exception import Control.Concurrent import Control.Concurrent.MVar unblock :: IO a -> IO a unblock io = do m <- newEmptyMVar _ <- forkIO (io >>= putMVar m) takeMVar m The main idea is that 'takeMVar' is an interruptible operation: when it blocks, the thread can now receive asynchronous exceptions. In general, a thread can unmask exceptions by blocking. Here is a simple test-case: main = do let x = 10000000 -- Just do a bit of work tid <- myThreadId forkIO $ (threadDelay 10000 >> killThread tid) r <- mask $ \restore -> do -- restore $ do -- unblock $ do -- do something non-blocking evaluate (f x []) -- If the exception is delivered in a timely manner, -- shouldn't get here. print r f 0 r = r f n r = f (n-1) (n:r) With both restore and unblock commented, the ThreadKilled exception is delayed; uncommenting either restore or unblock causes the exception to be delivered. This admonition does not apply to uninterruptibleMask, for which there are no interruptible exceptions. Claim 2: Thus, I come to the conclusion that we were wrong to remove 'unblock', and that it is no worse than the ability for interruptible actions to catch asynchronous exceptions. You could very well argue that interruptible actions are a design flaw. Then you should use 'uninterruptibleMask' instead, which effectively removes the concept of interruptibility--and is thus modular. Indeed, Eyal Lotem proposed [2] that 'bracket' should instead use 'uninterruptibleMask', for precisely the reason that it is too easy to reenable asynchronous exceptions in 'mask'. But assuming that interruptible masks are a good idea (Simon Marlow has defended them as "a way avoid reasoning about asynchronous exceptions except at specific points, i.e., where you might block"), there should be an 'unblock' for this type of mask. It should be said that the absence of 'unblock' for 'uninterruptibleMask' only implies that a passed in IO action (e.g., the cleanup action in bracket) does not have access to the exceptions thrown to the current thread; it doesn't actually guarantee uninterruptibility, since the passed in IO action could always raise a normal exception. Haskell's type system is not up to the task of enforcing such invariants. Cheers, Edward [1] https://mail.haskell.org/pipermail/libraries/2010-March/013310.html https://mail.haskell.org/pipermail/libraries/2010-April/013420.html [2] https://mail.haskell.org/pipermail/libraries/2014-September/023675.html P.S. You were CC'ed to this mail because you participated in the original "Asynchronous exception wormholes kill modularity" discussion. P.P.S. I have some speculations about using uninterruptibleMask more frequently: it seems to me that there ought to be a variant of uninterruptibleMask that immediately raises an exception if the "uninterruptible" action blocks. This would probably of great assistance of noticing and eliminating blocking in uninterruptible code. From marlowsd at gmail.com Sat Jul 2 09:58:14 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Sat, 2 Jul 2016 10:58:14 +0100 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity In-Reply-To: <1467429537-sup-6217@sabre> References: <1467429537-sup-6217@sabre> Message-ID: Hi Edward, On 2 July 2016 at 05:49, Edward Z. Yang wrote: > In 2010, in the thread "Asynchronous exception wormholes kill modularity" > [1], > Bas van Dijk observed that 'unblock :: IO a -> IO a' broke modularity, > as the sequence of calls 'block . block . unblock $ io' would result in > 'io' being run with asynchronous exceptions unblocked, despite the outer > 'block' "expecting" that asynchronous exceptions cannot be thrown. > > I would like to make two claims: > > 1. The new mask/restore interface is insufficient to "solve" > this modularity problem, as *interruptible* operations can > still be used to catch asynchronous exceptions. > > 2. Thus, we should provide an unblock combinator which > can be used to catch asynchronous exceptions from a 'mask' > (though not an 'uninterruptibleMask')--though it is > doubtful if anyone should ever use 'mask' in the first > place. > > Claim 1: Here is some code which reimplements 'unblock': > > import Control.Exception > import Control.Concurrent > import Control.Concurrent.MVar > > unblock :: IO a -> IO a > unblock io = do > m <- newEmptyMVar > _ <- forkIO (io >>= putMVar m) > takeMVar m > > This isn't really an implementation of unblock, because it doesn't enable fully-asynchronous exceptions inside io. If a stack overflow occurs, it won't be thrown, for example. Also, io will not be interrupted by an asynchronous exception thrown to the current thread. We already have a way to allow asynchronous exceptions to be thrown within a mask, it's called allowInterrupt: http://hackage.haskell.org/package/base-4.9.0.0/docs/Control-Exception.html#v:allowInterrupt I don't buy the claim that this breaks "modularity". The way to think about mask is that it disables fully-asynchronous exceptions, only allowing them to be thrown at certain well-defined points. This makes them tractable, it means you can write code without worrying that an async exception will pop up at any point. Inside a mask, the only way to get back to the state of fully asynchronous exceptions is to use the unblock action that mask gives you (provided you weren't already inside a mask). > The main idea is that 'takeMVar' is an interruptible operation: > when it blocks, the thread can now receive asynchronous exceptions. > In general, a thread can unmask exceptions by blocking. Here > is a simple test-case: > > main = do > let x = 10000000 -- Just do a bit of work > tid <- myThreadId > forkIO $ (threadDelay 10000 >> killThread tid) > r <- mask $ \restore -> do > -- restore $ do > -- unblock $ do > -- do something non-blocking > evaluate (f x []) > -- If the exception is delivered in a timely manner, > -- shouldn't get here. > print r > > f 0 r = r > f n r = f (n-1) (n:r) > > With both restore and unblock commented, the ThreadKilled > exception is delayed; uncommenting either restore or unblock > causes the exception to be delivered. > > This admonition does not apply to uninterruptibleMask, for > which there are no interruptible exceptions. > > Claim 2: Thus, I come to the conclusion that we were wrong > to remove 'unblock', and that it is no worse than the > ability for interruptible actions to catch asynchronous > exceptions. > > I don't think your argument undermines mask. > You could very well argue that interruptible actions are a design flaw. > I disagree - it's impossible to define withMVar without interruptible mask. > Then you should use 'uninterruptibleMask' instead, which effectively > removes the concept of interruptibility--and is thus modular. Indeed, > Eyal Lotem proposed [2] that 'bracket' should instead use > 'uninterruptibleMask', for precisely the reason that it is too easy to > reenable asynchronous exceptions in 'mask'. The problem he was talking about was to do with the interruptibility of the cleanup action in bracket, not the acquire, which really needs interruptible mask. The interruptibility of the cleanup is a complex issue with arguments on both sides. Michael Snoyman recently brought it up again in the context of his safe-exceptions library. We might yet change that - perhaps at the very least we should implement a catchUninterruptible# that behaves like catch# but applies uninterruptibleMask to the handler, and appropriate user-level wrappers. > But assuming that > interruptible masks are a good idea (Simon Marlow has defended them > as "a way avoid reasoning about asynchronous exceptions except > at specific points, i.e., where you might block"), there should > be an 'unblock' for this type of mask. > > It should be said that the absence of 'unblock' for > 'uninterruptibleMask' only implies that a passed in IO action (e.g., the > cleanup action in bracket) does not have access to the exceptions thrown > to the current thread; it doesn't actually guarantee uninterruptibility, > since the passed in IO action could always raise a normal exception. > Haskell's type system is not up to the task of enforcing such > invariants. > > Cheers, > Edward > > [1] > https://mail.haskell.org/pipermail/libraries/2010-March/013310.html > https://mail.haskell.org/pipermail/libraries/2010-April/013420.html > > [2] > https://mail.haskell.org/pipermail/libraries/2014-September/0 > > Cheers, > Simon > > 23675.html > > > P.S. You were CC'ed to this mail because you participated in the original > "Asynchronous exception wormholes kill modularity" discussion. > > P.P.S. I have some speculations about using uninterruptibleMask more > frequently: it seems to me that there ought to be a variant of > uninterruptibleMask that immediately raises an exception if > the "uninterruptible" action blocks. This would probably of > great assistance of noticing and eliminating blocking in > uninterruptible code. > Now that's an interesting idea! Cheers, Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From benl at ouroborus.net Sat Jul 2 10:46:02 2016 From: benl at ouroborus.net (Ben Lippmeier) Date: Sat, 2 Jul 2016 20:46:02 +1000 Subject: [Haskell-cafe] How to make Repa do stencils unboxed? In-Reply-To: References: Message-ID: <56C26914-C0B8-420B-8574-3A51DB2F247F@ouroborus.net> > On 2 Jul 2016, at 1:34 PM, William Yager wrote: > > My code to do this is as follows: > > https://gist.github.com/wyager/8c468c9d18ad62aff8bc9738aa947ea4 > 1) Put INLINE pragmas on all the leaf functions, especially ‘kernel’. If the compiler does not inline these functions they won’t fuse. This is a key problem with the Repa approach to fusion. 2) The ‘dimensional’ packages wraps a data type around all those values. I’m not convinced the simplifier will be able to undo the wrapping / unwrapping. You’ll need to inspect the core code to check. Ben. -------------- next part -------------- An HTML attachment was scrubbed... URL: From shumovichy at gmail.com Sat Jul 2 13:06:59 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Sat, 02 Jul 2016 16:06:59 +0300 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity In-Reply-To: <1467429537-sup-6217@sabre> References: <1467429537-sup-6217@sabre> Message-ID: <1467464819.2456.4.camel@gmail.com> On Sat, 2016-07-02 at 00:49 -0400, Edward Z. Yang wrote: > > P.P.S. I have some speculations about using uninterruptibleMask more > frequently: it seems to me that there ought to be a variant of > uninterruptibleMask that immediately raises an exception if > the "uninterruptible" action blocks.  This would probably of > great assistance of noticing and eliminating blocking in > uninterruptible code. Could you please elaborate where it is useful. Any particular example? I'm interested because few years ago I proposed similar function, but in a bit different context. I needed it to make interruptible cleanup actions safe to use. Thanks, Yuras. From ezyang at mit.edu Sat Jul 2 16:25:07 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sat, 02 Jul 2016 12:25:07 -0400 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity In-Reply-To: References: <1467429537-sup-6217@sabre> Message-ID: <1467469617-sup-4243@sabre> Excerpts from Simon Marlow's message of 2016-07-02 05:58:14 -0400: > > Claim 1: Here is some code which reimplements 'unblock': > > > > import Control.Exception > > import Control.Concurrent > > import Control.Concurrent.MVar > > > > unblock :: IO a -> IO a > > unblock io = do > > m <- newEmptyMVar > > _ <- forkIO (io >>= putMVar m) > > takeMVar m > > > > > This isn't really an implementation of unblock, because it doesn't enable > fully-asynchronous exceptions inside io. If a stack overflow occurs, it > won't be thrown, for example. Also, io will not be interrupted by an > asynchronous exception thrown to the current thread. Oh, that's true. I suppose you could work around this by passing on an asynchronous exception to a child thread that is unmasked using forkIOWithUnmask, although maybe you would consider that cheating? > We already have a way to allow asynchronous exceptions to be thrown within > a mask, it's called allowInterrupt: > http://hackage.haskell.org/package/base-4.9.0.0/docs/Control-Exception.html#v:allowInterrupt Well, it's different, right? allowInterrupt allows asynchronous exceptions to be thrown at a specific point of execution; unblock allows asynchronous exceptions to be thrown at any point while the inner IO action is executing. I don't see why you would allow the former without the latter. > I don't buy the claim that this breaks "modularity". The way to think > about mask is that it disables fully-asynchronous exceptions, only allowing > them to be thrown at certain well-defined points. This makes them > tractable, it means you can write code without worrying that an async > exception will pop up at any point. Inside a mask, the only way to get > back to the state of fully asynchronous exceptions is to use the unblock > action that mask gives you (provided you weren't already inside a mask). I suppose what I don't understand, then, is that if interruptible points are modular, I don't see why unblock isn't modular either; it's just a more convenient way of inserting allowInterrupt between every indivisible IO operation in user code. > > You could very well argue that interruptible actions are a design flaw. > > > > I disagree - it's impossible to define withMVar without interruptible mask. What about this version of withMVar using uninterruptible? (Assume no other producers.) withMVarUninterruptible :: MVar a -> (a -> IO b) -> IO b withMVarUninterruptible m io = uninterruptibleMask $ \restore -> do a <- restore (takeMVar m) b <- restore (io a) `onException` putMVar m a putMVar m a return b I don't think it is quite right, as there is race between when takeMVar unblocks, and when the uninterruptible mask is restored. But perhaps the primary utility of interruptible masks is to let you eliminate this race. > > Then you should use 'uninterruptibleMask' instead, which effectively > > removes the concept of interruptibility--and is thus modular. Indeed, > > Eyal Lotem proposed [2] that 'bracket' should instead use > > 'uninterruptibleMask', for precisely the reason that it is too easy to > > reenable asynchronous exceptions in 'mask'. > > > The problem he was talking about was to do with the interruptibility of the > cleanup action in bracket, not the acquire, which really needs > interruptible mask. The interruptibility of the cleanup is a complex issue > with arguments on both sides. Michael Snoyman recently brought it up again > in the context of his safe-exceptions library. We might yet change that - > perhaps at the very least we should implement a catchUninterruptible# that > behaves like catch# but applies uninterruptibleMask to the handler, and > appropriate user-level wrappers. Yes, it is complex, and I won't claim to know the right answer here. > > But assuming that > > interruptible masks are a good idea (Simon Marlow has defended them > > as "a way avoid reasoning about asynchronous exceptions except > > at specific points, i.e., where you might block"), there should > > be an 'unblock' for this type of mask. > > > > It should be said that the absence of 'unblock' for > > 'uninterruptibleMask' only implies that a passed in IO action (e.g., the > > cleanup action in bracket) does not have access to the exceptions thrown > > to the current thread; it doesn't actually guarantee uninterruptibility, > > since the passed in IO action could always raise a normal exception. > > Haskell's type system is not up to the task of enforcing such > > invariants. > > > > Cheers, > > Edward > > > > [1] > > https://mail.haskell.org/pipermail/libraries/2010-March/013310.html > > https://mail.haskell.org/pipermail/libraries/2010-April/013420.html > > > > [2] > > https://mail.haskell.org/pipermail/libraries/2014-September/0 > > > > Cheers, > > Simon > > > > 23675.html > > > > > > P.S. You were CC'ed to this mail because you participated in the original > > "Asynchronous exception wormholes kill modularity" discussion. > > > > P.P.S. I have some speculations about using uninterruptibleMask more > > frequently: it seems to me that there ought to be a variant of > > uninterruptibleMask that immediately raises an exception if > > the "uninterruptible" action blocks. This would probably of > > great assistance of noticing and eliminating blocking in > > uninterruptible code. > > > > Now that's an interesting idea! It is too bad that it is far too difficult to let Haskell-land iterate and try these things out: need RTS cooperation. Edward From ezyang at mit.edu Sat Jul 2 16:29:30 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Sat, 02 Jul 2016 12:29:30 -0400 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity In-Reply-To: <1467464819.2456.4.camel@gmail.com> References: <1467429537-sup-6217@sabre> <1467464819.2456.4.camel@gmail.com> Message-ID: <1467476738-sup-805@sabre> Excerpts from Yuras Shumovich's message of 2016-07-02 09:06:59 -0400: > On Sat, 2016-07-02 at 00:49 -0400, Edward Z. Yang wrote: > > > > P.P.S. I have some speculations about using uninterruptibleMask more > > frequently: it seems to me that there ought to be a variant of > > uninterruptibleMask that immediately raises an exception if > > the "uninterruptible" action blocks.  This would probably of > > great assistance of noticing and eliminating blocking in > > uninterruptible code. > > > Could you please elaborate where it is useful. Any particular example? You would use it in any situation you use an uninterruptibleMask. The point is that uninterruptible code is not supposed to take too long (the program is unresponsive in the meantime), so it's fairly bad news if inside uninterruptible code you block. The block = exception variant would help you find out when this occurred. Arguably, it would be more Haskelly if there was a static type discipline for distinguishing blocking and non-blocking IO operations. But some operations are only known to be (non-)blocking at runtime, e.g., takeMVar/putMVar, so a dynamic discipline is necessary. > I'm interested because few years ago I proposed similar function, but > in a bit different context. I needed it to make interruptible cleanup > actions safe to use. Could you elaborate more / post a link? Cheers, Edward From shumovichy at gmail.com Sat Jul 2 18:39:44 2016 From: shumovichy at gmail.com (Yuras Shumovich) Date: Sat, 02 Jul 2016 21:39:44 +0300 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity In-Reply-To: <1467476738-sup-805@sabre> References: <1467429537-sup-6217@sabre> <1467464819.2456.4.camel@gmail.com> <1467476738-sup-805@sabre> Message-ID: <1467484784.2456.22.camel@gmail.com> On Sat, 2016-07-02 at 12:29 -0400, Edward Z. Yang wrote: > Excerpts from Yuras Shumovich's message of 2016-07-02 09:06:59 -0400: > > On Sat, 2016-07-02 at 00:49 -0400, Edward Z. Yang wrote: > > > > > > P.P.S. I have some speculations about using uninterruptibleMask > > > more > > > frequently: it seems to me that there ought to be a variant of > > > uninterruptibleMask that immediately raises an exception if > > > the "uninterruptible" action blocks.  This would probably of > > > great assistance of noticing and eliminating blocking in > > > uninterruptible code. > > > > > > Could you please elaborate where it is useful. Any particular > > example? > > You would use it in any situation you use an uninterruptibleMask. > The point is that uninterruptible code is not supposed to take > too long (the program is unresponsive in the meantime), so it's > fairly bad news if inside uninterruptible code you block.  The > block = exception variant would help you find out when this occurred. Hmm, ununterruptibleMask is used when the code can block, but you don't want it to throw (async) exception. waitQSem is an example: https://hackage.haskell.org/package/base-4.9.0.0/docs/src/Control.Concurrent.QSem.html#waitQSem Basically, there are cases where code can block, yet you don't want it to be interrupted. Why to you need uninterruptibleMask when the code can't block anyway? It is a no-op in that case. > > Arguably, it would be more Haskelly if there was a static type > discipline for distinguishing blocking and non-blocking IO > operations. > But some operations are only known to be (non-)blocking at runtime, > e.g., takeMVar/putMVar, so a dynamic discipline is necessary. That is correct. In theory it would be useful to encode on type level whether IO operations can block, or can be iterrupted by async exception, or can fail with sync exception. Unfortunately it depends on runtime, so in practice it is less useful. > > > I'm interested because few years ago I proposed similar function, > > but > > in a bit different context. I needed it to make interruptible > > cleanup > > actions safe to use. > > Could you elaborate more / post a link? Sorry, I thought I added the link. I'm talking about this: http://blog.haskell-exists.com/yuras/posts/handling-async-exceptions-in-haskell-pushing-bracket-to-the-limits.html#example-6-pushing-to-the-limits The idea is to disable external async exceptions, but interrupt any interruptable operation on the way. The article describes the reason I need it. Thanks, Yuras. From erantapaa at gmail.com Sat Jul 2 21:33:09 2016 From: erantapaa at gmail.com (Erik Rantapaa) Date: Sat, 2 Jul 2016 14:33:09 -0700 (PDT) Subject: [Haskell-cafe] haskell-browser-mods - v0.1 Message-ID: <57bb2b11-dfbf-4eef-aa0b-7cb9a009d26f@googlegroups.com> Hi everyone, I've created a browser extension to aid in navigating around Haskell-related websites. The extension adds information to visited pages, create links to other relevent pages and adds keyboard shortcuts and conveniences. The sites the extension knows about include: - haskellnews.org - hdiff.luite.com - hackage.haskell.org - packdeps.haskellers.com - hayoo.fh-wedel.de The extension is currently available for Safari and Chrome. For more information and downloads visit: https://github.com/erantapaa/haskell-browser-mods Feedback, suggestions, bug reports and PRs are very welcome. Erik -------------- next part -------------- An HTML attachment was scrubbed... URL: From briand at aracnet.com Sat Jul 2 21:50:40 2016 From: briand at aracnet.com (briand at aracnet.com) Date: Sat, 2 Jul 2016 14:50:40 -0700 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 154, Issue 27 In-Reply-To: References: Message-ID: <20160702145040.32583ea9@basalt.deldotd.com> On Sat, 2 Jul 2016 00:11:02 +0200 Vlad Lopatin wrote: > Re: up-to-date glfw examples (briand at aracnet.com) > > Hey, Brian > > Here's a bare-bones example of modern OpenGL(4.5) (VBO's, vertex/fragment > shaders), using GLFW-b to handle windows/input and Yampa for animation. > Shader-loading is handled by Sven Panne's code: > https://github.com/madjestic/Haskell-OpenGL-Tutorial/tree/master/Mandelbrot-FRP > > Yes i did find those examples in my searching. Very helpful. Thank you, Brian From will.yager at gmail.com Sat Jul 2 22:46:58 2016 From: will.yager at gmail.com (William Yager) Date: Sat, 2 Jul 2016 15:46:58 -0700 Subject: [Haskell-cafe] How to make Repa do stencils unboxed? In-Reply-To: <56C26914-C0B8-420B-8574-3A51DB2F247F@ouroborus.net> References: <56C26914-C0B8-420B-8574-3A51DB2F247F@ouroborus.net> Message-ID: OK, some interesting things: 1. INLINE pragmas seem to have no substantial effect. 2. Regrettably, using Dimensional does seem to have some negative effect on performance. It's about 1.5x slower with Dimensional. The fragility of our currently used fusion techniques renders empty the promise of "overhead-free" newtype abstractions. 3. I got a *huge* performance boost by calculating `outputs` through `runIdentity` rather than treating it as an IO action. Several times faster. This makes sense, but I'm surprised the results are so drastic. At this point, `mapStencil2 On Sat, Jul 2, 2016 at 3:46 AM, Ben Lippmeier wrote: > > On 2 Jul 2016, at 1:34 PM, William Yager wrote: > > My code to do this is as follows: > > https://gist.github.com/wyager/8c468c9d18ad62aff8bc9738aa947ea4 > > > 1) Put INLINE pragmas on all the leaf functions, especially ‘kernel’. If > the compiler does not inline these functions they won’t fuse. This is a key > problem with the Repa approach to fusion. > > 2) The ‘dimensional’ packages wraps a data type around all those values. > I’m not convinced the simplifier will be able to undo the wrapping / > unwrapping. You’ll need to inspect the core code to check. > > Ben. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Sat Jul 2 22:50:50 2016 From: will.yager at gmail.com (William Yager) Date: Sat, 2 Jul 2016 15:50:50 -0700 Subject: [Haskell-cafe] How to make Repa do stencils unboxed? In-Reply-To: References: <56C26914-C0B8-420B-8574-3A51DB2F247F@ouroborus.net> Message-ID: Oops, sent prematurely. `mapStencil2` seems to be allocating one extra machine word per stencil computation. So not entirely unboxed, but much better. Latest code is at https://gist.github.com/wyager/1c5879660a61c5cd6afaceb3e928d889 Can anyone explain to me how the Identity monad manages to guarantee the sequencing/non-nesting requirements of computeP? As far as I can tell, it should be reduced to plain old function application, which is the same as nesting computeP, which is what we were trying to prevent. In other words, what effect does the Identity monad have over not having a monad at all? Its bind definition has no sequencing effects or anything, so I can't imagine that it actually accomplishes anything. Cheers, Will On Sat, Jul 2, 2016 at 3:46 PM, William Yager wrote: > OK, some interesting things: > > 1. INLINE pragmas seem to have no substantial effect. > > 2. Regrettably, using Dimensional does seem to have some negative effect > on performance. It's about 1.5x slower with Dimensional. The fragility of > our currently used fusion techniques renders empty the promise of > "overhead-free" newtype abstractions. > > 3. I got a *huge* performance boost by calculating `outputs` through > `runIdentity` rather than treating it as an IO action. Several times > faster. This makes sense, but I'm surprised the results are so drastic. > > At this point, `mapStencil2 > > On Sat, Jul 2, 2016 at 3:46 AM, Ben Lippmeier wrote: > >> >> On 2 Jul 2016, at 1:34 PM, William Yager wrote: >> >> My code to do this is as follows: >> >> https://gist.github.com/wyager/8c468c9d18ad62aff8bc9738aa947ea4 >> >> >> 1) Put INLINE pragmas on all the leaf functions, especially ‘kernel’. If >> the compiler does not inline these functions they won’t fuse. This is a key >> problem with the Repa approach to fusion. >> >> 2) The ‘dimensional’ packages wraps a data type around all those values. >> I’m not convinced the simplifier will be able to undo the wrapping / >> unwrapping. You’ll need to inspect the core code to check. >> >> Ben. >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at schmong.org Mon Jul 4 02:03:48 2016 From: michael at schmong.org (Michael Litchard) Date: Sun, 3 Jul 2016 19:03:48 -0700 Subject: [Haskell-cafe] Octree and Bounding Boxes Message-ID: I've forked the octree library and added some bounding box functionality. The problem is, it turns out kd-trees are better for my use case. I'd rather not junk the code, but I can't see a use case for the octree library as it stands. Below is the link to the branch where the code is, is there a use case for point octrees needing bounding boxes? https://github.com/mlitchard/octree/tree/test-reorg/Data/Octree/BoundingBox -------------- next part -------------- An HTML attachment was scrubbed... URL: From benl at ouroborus.net Mon Jul 4 04:37:33 2016 From: benl at ouroborus.net (Ben Lippmeier) Date: Mon, 4 Jul 2016 14:37:33 +1000 Subject: [Haskell-cafe] How to make Repa do stencils unboxed? In-Reply-To: References: <56C26914-C0B8-420B-8574-3A51DB2F247F@ouroborus.net> Message-ID: <751AAC7E-8DA0-4055-A2E8-0B73BF4D82FF@ouroborus.net> > On 3 Jul 2016, at 8:46 AM, William Yager wrote: > 2. Regrettably, using Dimensional does seem to have some negative effect on performance. It's about 1.5x slower with Dimensional. The fragility of our currently used fusion techniques renders empty the promise of "overhead-free" newtype abstractions. Yes, this is a massive problem with the Repa approach to array fusion. The compilation method (and resulting runtime performance) depends on the GHC simplifier acting in a certain way — yet there is no specification of exactly what the simplifier should do, and no easy way to check that it did what was expected other than eyeballing the intermediate code. We really need a different approach to program optimisation, such as a working supercompiler, instead of just “a lot of bullets in the gun” that might hit the target or not. The latter is fine for general purpose code optimisation but not “compile by transformation” where we really depend on the transformations doing what they’re supposed to. The use of syntactic witnesses of type equality in the core language doesn’t help either, as they tend do get in the way of other program transformations. I think the way the Repa API is *set up* is fine, but expecting a general purpose compiler to always successfully fuse such code is too optimistic. We had the same sort of problems in DPH. Live and learn. > 3. I got a *huge* performance boost by calculating `outputs` through `runIdentity` rather than treating it as an IO action. Several times faster. This makes sense, but I'm surprised the results are so drastic. If a source level change causes some syntactic wibble in the intermediate code that helps fusion, then the result will be drastic. > Can anyone explain to me how the Identity monad manages to guarantee the sequencing/non-nesting requirements of computeP? It doesn’t. I wrapped computeP in a identity monad to discourage people from trying to perform a computeP in the worker function of another parallel operator (like map). > As far as I can tell, it should be reduced to plain old function application, which is the same as nesting computeP, which is what we were trying to prevent. Yes. Doing this would create a nested parallel computation, which Repa does not support (as you mentioned). If you were to use ‘runIdentity' to discharge the identity constructor, then create a nested parallel computation anyway, then you’d get a runtime warning on the console. > In other words, what effect does the Identity monad have over not having a monad at all? Its bind definition has no sequencing effects or anything, so I can't imagine that it actually accomplishes anything. Its purpose is psychological. It forces the user to question what is really going on. Ben. From marlowsd at gmail.com Mon Jul 4 08:17:29 2016 From: marlowsd at gmail.com (Simon Marlow) Date: Mon, 4 Jul 2016 09:17:29 +0100 Subject: [Haskell-cafe] Interruptible exception wormholes kill modularity In-Reply-To: <1467469617-sup-4243@sabre> References: <1467429537-sup-6217@sabre> <1467469617-sup-4243@sabre> Message-ID: On 2 July 2016 at 17:25, Edward Z. Yang wrote: > Excerpts from Simon Marlow's message of 2016-07-02 05:58:14 -0400: > > > Claim 1: Here is some code which reimplements 'unblock': > > > > > > import Control.Exception > > > import Control.Concurrent > > > import Control.Concurrent.MVar > > > > > > unblock :: IO a -> IO a > > > unblock io = do > > > m <- newEmptyMVar > > > _ <- forkIO (io >>= putMVar m) > > > takeMVar m > > > > > > > > This isn't really an implementation of unblock, because it doesn't enable > > fully-asynchronous exceptions inside io. If a stack overflow occurs, it > > won't be thrown, for example. Also, io will not be interrupted by an > > asynchronous exception thrown to the current thread. > > Oh, that's true. I suppose you could work around this by passing > on an asynchronous exception to a child thread that is unmasked > using forkIOWithUnmask, although maybe you would consider that > cheating? > Yes, you can use forkIOWithUnmask as a way to break out of mask. Perhaps for that reason it should have "unsafe" in the name, but I think it's hard to use it by accident. I actually do agree with you that the "modularity" provided by mask isn't really useful. But my reasoning is a bit different. The caller of mask is saying "I want asynchronous exceptions to only occur at known places.". Those known places are interruptible operations, and library code (because we can't know whether library code performs an interruptible operation or not). From the point of view of the caller of mask, they cannot tell the difference between library code that invokes an interruptible operation, and library code that calls "unblock". So it would be perfectly fine to provide an "unblock" that re-enables fully asynchronous exceptions. (indeed I think this was kind of what I had in mind with the original block/unblock, but I didn't articulate the argument clearly enough when everyone was asking for "mask") However, things are a bit different with uninterruptibleMask. Here the caller is saying "I don't expect to see *any* asynchronous exceptions, either in my code or from library code". So clearly an unblock cannot undo an uninterruptibleMask. Having said all this, I don't think the current API is necessarily bad, it just provides more guarantees than we really need, and perhaps it's a bit less efficient than it could be, due to the need to pass the IO action to mask. But we would still need to do this for uninterruptibleMask, and having the API of uninterruptibleMask be the same as mask is good. > We already have a way to allow asynchronous exceptions to be thrown within > > a mask, it's called allowInterrupt: > > > http://hackage.haskell.org/package/base-4.9.0.0/docs/Control-Exception.html#v:allowInterrupt > > Well, it's different, right? allowInterrupt allows asynchronous > exceptions to > be thrown at a specific point of execution; unblock allows asynchronous > exceptions to be thrown at any point while the inner IO action is > executing. I don't see why you would allow the former without the > latter. > Ok, so the point I was trying to make was that the idea of blocking to allow asynchronous exceptions to be thrown inside a mask is fully sanctioned, and we made an API for it. But you're quite right that it's not exactly the same as unblock. > > > You could very well argue that interruptible actions are a design flaw. > > > > > > > I disagree - it's impossible to define withMVar without interruptible > mask. > > What about this version of withMVar using uninterruptible? (Assume > no other producers.) > > withMVarUninterruptible :: MVar a -> (a -> IO b) -> IO b > withMVarUninterruptible m io = > uninterruptibleMask $ \restore -> do > a <- restore (takeMVar m) > b <- restore (io a) `onException` putMVar m a > putMVar m a > return b > > I don't think it is quite right, as there is race between when > takeMVar unblocks, and when the uninterruptible mask is restored. > But perhaps the primary utility of interruptible masks is to > let you eliminate this race. > Exactly! This race condition is the reason for interruptible operations. [snip] > > Edward > Cheers Simon -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Mon Jul 4 20:43:43 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 4 Jul 2016 22:43:43 +0200 Subject: [Haskell-cafe] Intanciate data type Message-ID: Hi all, I have a data type looking like this: data Foo e a where Foo :: e → Foo e a I would like to instantiate it to make it equivalent to: data Bar a where A :: String → Bar Int B :: Maybe a → Bar a How can I do that? With a functional dependency? I probably need to change the definition of Foo. -------------- next part -------------- An HTML attachment was scrubbed... URL: From gautier.difolco at gmail.com Mon Jul 4 21:31:08 2016 From: gautier.difolco at gmail.com (Gautier DI FOLCO) Date: Mon, 4 Jul 2016 23:31:08 +0200 Subject: [Haskell-cafe] Intanciate data type In-Reply-To: References: Message-ID: Hello, I would say that type families should do the joke: {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE GADTs #-} type family Prod a where Prod String = Int Prod (Maybe a) = a data Foo e a where Foo :: e -> Foo (Prod e) a Regards. 2016-07-04 22:43 GMT+02:00 Corentin Dupont : > Hi all, > I have a data type looking like this: > > data Foo e a > where > > Foo :: e → Foo e a > > I would like to instantiate it to make it equivalent to: > > data Bar a > where > > A :: String → Bar Int > B :: Maybe a → Bar a > > How can I do that? With a functional dependency? > I probably need to change the definition of Foo. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From trebla at vex.net Tue Jul 5 01:39:14 2016 From: trebla at vex.net (Albert Y. C. Lai) Date: Mon, 4 Jul 2016 21:39:14 -0400 Subject: [Haskell-cafe] Packaging a library with a separate shared object In-Reply-To: <20160630160305.6e61c847@khumba.net> References: <20160630160305.6e61c847@khumba.net> Message-ID: <577B0FC2.2020703@vex.net> On 2016-06-30 07:03 PM, Bryan Gardiner wrote: > I'm working on packaging Qtah (my Qt bindings) for upload to Hackage. > This is somewhat complicated, as I have some C++ glue code that I > build into a shared library that the Haskell library needs. > > Currently, my build hooks are as follows, in: > https://gitlab.com/khumba/qtah/blob/packaging/qtah/Setup.hs > > - postConf: Generate Haskell code in src/ and C++ code in cpp/. > > - preBuild: Add cpp/ to HookedBuildInfo.extraLibDirs because the build > phase needs this needs this. > > - buildHook: Run make to build the C++ code into libqtah.so before > the Haskell code builds. > > - copyHook and instHook: Copy libqtah.so into InstallDirs.libdir > (~/.cabal/lib/.../qtah-*/). > > This installs successfully, but ultimately doesn't work because the > Haskell libHSqtah*.so that gets built can't find libqtah.so. The > installation directory ~/cabal/lib/.../qtah-*/ isn't on > libHSqtah*.so's RUNPATH (which makes sense, it's not known at link > time). I don't know how to write custom Setup.hs, so I don't know how to do the following, but the theory is: When creating libHSqtah*.so, the linker needs to be told: -Wl,-rpath,xxx Replace xxx by InstallDirs.libdir. This is how to set RUNPATH (or is it RPATH?). From bog at khumba.net Tue Jul 5 06:01:12 2016 From: bog at khumba.net (Bryan Gardiner) Date: Mon, 4 Jul 2016 23:01:12 -0700 Subject: [Haskell-cafe] Packaging a library with a separate shared object In-Reply-To: <577B0FC2.2020703@vex.net> References: <20160630160305.6e61c847@khumba.net> <577B0FC2.2020703@vex.net> Message-ID: <20160704230112.1b9acc26@khumba.net> On Mon, 4 Jul 2016 21:39:14 -0400 "Albert Y. C. Lai" wrote: > On 2016-06-30 07:03 PM, Bryan Gardiner wrote: > > I'm working on packaging Qtah (my Qt bindings) for upload to Hackage. > > This is somewhat complicated, as I have some C++ glue code that I > > build into a shared library that the Haskell library needs. > > > > Currently, my build hooks are as follows, in: > > https://gitlab.com/khumba/qtah/blob/packaging/qtah/Setup.hs > > > > - postConf: Generate Haskell code in src/ and C++ code in cpp/. > > > > - preBuild: Add cpp/ to HookedBuildInfo.extraLibDirs because the build > > phase needs this needs this. > > > > - buildHook: Run make to build the C++ code into libqtah.so before > > the Haskell code builds. > > > > - copyHook and instHook: Copy libqtah.so into InstallDirs.libdir > > (~/.cabal/lib/.../qtah-*/). > > > > This installs successfully, but ultimately doesn't work because the > > Haskell libHSqtah*.so that gets built can't find libqtah.so. The > > installation directory ~/cabal/lib/.../qtah-*/ isn't on > > libHSqtah*.so's RUNPATH (which makes sense, it's not known at link > > time). > > I don't know how to write custom Setup.hs, so I don't know how to do the > following, but the theory is: > > When creating libHSqtah*.so, the linker needs to be told: > -Wl,-rpath,xxx > Replace xxx by InstallDirs.libdir. This is how to set RUNPATH (or is it > RPATH?). And since installing happens after building, this will in fact require two packages. Okay, thanks Albert. (RUNPATH appears to be the new and preferred way since it doesn't shadow LD_LIBRARY_PATH, and "-Wl,-rpath=xxx,--enable-new-dtags" looks like the magic string...) I went ahead and did the split, and things are working with some small catches: executables must be linked dynamically because the necessary RUNPATH isn't set on a statically-linked executable, and I can't seem to inject the libdir into "cabal test" via HookedBuildInfo the same way I can with "cabal build". But overall it works! Thanks, Bryan -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 801 bytes Desc: OpenPGP digital signature URL: From publicityifl at gmail.com Tue Jul 5 10:17:09 2016 From: publicityifl at gmail.com (publicityifl at gmail.com) Date: Tue, 05 Jul 2016 10:17:09 +0000 Subject: [Haskell-cafe] 2nd CfP: IFL 2016 (28th Symposium on Implementation and Application of Functional Languages) Message-ID: <001a114223986fef940536e0c1de@google.com> Hello, Please, find below the second call for papers for IFL 2016. Please forward these to anyone you think may be interested. Apologies for any duplicates you may receive. best regards, Jurriaan Hage Publicity Chair of IFL --- IFL 2016 - 2nd Call for papers 28th SYMPOSIUM ON IMPLEMENTATION AND APPLICATION OF FUNCTIONAL LANGUAGES - IFL 2016 KU Leuven, Belgium In cooperation with ACM SIGPLAN August 31 - September 2, 2016 https://dtai.cs.kuleuven.be/events/ifl2016/ Scope The goal of the IFL symposia is to bring together researchers actively engaged in the implementation and application of functional and function-based programming languages. IFL 2016 will be a venue for researchers to present and discuss new ideas and concepts, work in progress, and publication-ripe results related to the implementation and application of functional languages and function-based programming. Peer-review Following the IFL tradition, IFL 2016 will use a post-symposium review process to produce the formal proceedings. All participants of IFL 2016 are invited to submit either a draft paper or an extended abstract describing work to be presented at the symposium. At no time may work submitted to IFL be simultaneously submitted to other venues; submissions must adhere to ACM SIGPLAN's republication policy: http://www.sigplan.org/Resources/Policies/Republication The submissions will be screened by the program committee chair to make sure they are within the scope of IFL, and will appear in the draft proceedings distributed at the symposium. Submissions appearing in the draft proceedings are not peer-reviewed publications. Hence, publications that appear only in the draft proceedings are not subject to the ACM SIGPLAN republication policy. After the symposium, authors will be given the opportunity to incorporate the feedback from discussions at the symposium and will be invited to submit a revised full article for the formal review process. From the revised submissions, the program committee will select papers for the formal proceedings considering their correctness, novelty, originality, relevance, significance, and clarity. The formal proceedings will appear in the International Conference Proceedings Series of the ACM Digital Library. Important dates August 1: Submission deadline draft papers August 3: Notification of acceptance for presentation August 5: Early registration deadline August 12: Late registration deadline August 22: Submission deadline for pre-symposium proceedings August 31 - September 2: IFL Symposium December 1: Submission deadline for post-symposium proceedings January 31, 2017: Notification of acceptance for post-symposium proceedings March 15, 2017: Camera-ready version for post-symposium proceedings Submission details Prospective authors are encouraged to submit papers or extended abstracts to be published in the draft proceedings and to present them at the symposium. All contributions must be written in English. Papers must use the new ACM two columns conference format, which can be found at: http://www.acm.org/publications/proceedings-template For the pre-symposium proceedings we adopt a 'weak' page limit of 12 pages. For the post-symposium proceedings the page limit of 12 pages is firm. Authors submit through EasyChair: https://easychair.org/conferences/?conf=ifl2016 Topics IFL welcomes submissions describing practical and theoretical work as well as submissions describing applications and tools in the context of functional programming. If you are not sure whether your work is appropriate for IFL 2016, please contact the PC chair at tom.schrijvers at cs.kuleuven.be. Topics of interest include, but are not limited to: - language concepts - type systems, type checking, type inferencing - compilation techniques - staged compilation - run-time function specialization - run-time code generation - partial evaluation - (abstract) interpretation - metaprogramming - generic programming - automatic program generation - array processing - concurrent/parallel programming - concurrent/parallel program execution - embedded systems - web applications - (embedded) domain specific languages - security - novel memory management techniques - run-time profiling performance measurements - debugging and tracing - virtual/abstract machine architectures - validation, verification of functional programs - tools and programming techniques - (industrial) applications Peter Landin Prize The Peter Landin Prize is awarded to the best paper presented at the symposium every year. The honored article is selected by the program committee based on the submissions received for the formal review process. The prize carries a cash award equivalent to 150 Euros. Programme committee Chair: Tom Schrijvers, KU Leuven, Belgium - Sandrine Blazy, University of Rennes 1, France - Laura Castro, University of A Coruña, Spain - Jacques, Garrigue, Nagoya University, Japan - Clemens Grelck, University of Amsterdam, The Netherlands - Zoltan Horvath, Eotvos Lorand University, Hungary - Jan Martin Jansen, Netherlands Defence Academy, The Netherlands - Mauro Jaskelioff, CIFASIS/Universidad Nacional de Rosario, Argentina - Patricia Johann, Appalachian State University, USA - Wolfram Kahl, McMaster University, Canada - Pieter Koopman, Radboud University Nijmegen, The Netherlands - Shin-Cheng Mu, Academia Sinica, Taiwan - Henrik Nilsson, University of Nottingham, UK - Nikolaos Papaspyrou, National Technical University of Athens, Greece - Atze van der Ploeg, Chalmers University of Technology, Sweden - Matija Pretnar, University of Ljubljana, Slovenia - Tillmann Rendel, University of Tübingen, Germany - Christophe Scholliers, Universiteit Gent, Belgium - Sven-Bodo Scholz, Heriot-Watt University, UK - Melinda Toth, Eotvos Lorand University, Hungary - Meng Wang, University of Kent, UK - Jeremy Yallop, University of Cambridge, UK Venue The 28th IFL will be held in association with the Faculty of Computer Science, KU Leuven, Belgium. Leuven is centrally located in Belgium and can be easily reached from Brussels Airport by train (~15 minutes). The venue in the Arenberg Castle park can be reached by foot, bus or taxi from the city center. See the website for more information on the venue. -------------- next part -------------- An HTML attachment was scrubbed... URL: From breitner at kit.edu Tue Jul 5 17:39:41 2016 From: breitner at kit.edu (Joachim Breitner) Date: Tue, 05 Jul 2016 19:39:41 +0200 Subject: [Haskell-cafe] Haskell in Leipzig 2016: Another Call for Papers (deadline extended) Message-ID: <1467740381.13592.10.camel@kit.edu>                              Haskell in Leipzig                             September 14-15, 2016                             HTKW Leipzig, Germany                          http://hal2016.haskell.org/ We have received good and interesting proposals, but our schedule still has room for more. So whether you wanted to submit, but just did not make the first deadline, or whether you only now decide to come to Leipzig, this is your chance: Please submit your short abstract until Friday, July 15th. Do you need ideas? Here some possible directions:  * Very fancy type tricks using all  of GHC’s extensions.  * Very fancy type tricks using none of GHC’s extensions.  * Getting Haskell to run really really fast.  * Using Haskell to make real money, in real life.  * Showing how this one odd Haskell library make doing something    appear rally simple.  * Stuff that is really horrible with Haskell (and how to do it better)  * What is cool in other functional programming language right now. We are particularly interested in good tutorials. These could range from impressing beginners with what you can do with Haskell to teaching new tricks to the experts. So if you think you have something useful to teach, please submit a proposal. Please share this CfP with whoever might be interested. == About HaL == The workshop series “Haskell in Leipzig”, now in its 11th year, brings together Haskell developers, Haskell researchers, Haskell enthusiasts and Haskell beginners to listen to talks, take part in tutorials, and join in interesting conversations. Everything related to Haskell is on topic, whether it is about current research, practical applications, interesting ideas off the beaten track, education, or art, and topics may extend to functional programming in general and its connections to other programming paradigms as well. This year, HaL is colocated with two related conferences,  * the Workshop on Functional and (Constraint) Logic Programming (WFLP) and  * the Workshop on (Constraint) Logic Programming (WLP), to form the Leipzig Week of Declarative Programming (L-DEC):     http://nfa.imn.htwk-leipzig.de/LDEC2016/ In order to accommodate and welcome a more international audience, this year’s HaL will be held in English. == Invited Speaker == Unsure about whether HaL is interesting to you? No need to worry:                             Alejandro Russo (from Chalmers) is our keynote speaker and will talk about his work on information-flow control (i.e. SecLib, LIO, MAC, HLIO) – a great topic that is of interest to researchers, practitioners and beginners alike.  == Submissions == Contributions can take the form of  * talks (about 30 minutes),  * tutorials (about 90 minutes),  * demonstrations, artistic performances, or other extraordinary     things. Please submit an abstract that describes the content and form of your presentation, the intended audience, and required previous knowledge. We recommend a length of 2 pages, so that the PC and the audience get a good idea of your submission, but this is not a hard requirement. You can submit your abstract, as an PDF document, at    https://easychair.org/conferences/?conf=hal2016 until Friday, July 15, 2016. You will be notified by July 30, 2016. == Program committee ==  * Andreas Abel, Chalmers and Gothenburg University, Sweden  * Heinrich Apfelmus, Leipzig, Germany  * Joachim Breitner, Karlsruhe Institute of Technology, Germany (Chair)  * Matthias Fischmann, Zerobuzz, Germany  * Petra Hofstedt, BTU Cottbus-Senftenberg, Germany  * Wolfgang Jeltsch, Institute of Cybernetics at Tallinn University of     Technology, Estonia  * Andres Löh, Well-Typed LLP, Germany  * Alejandro Serrano Mena, Universiteit Utrecht, Netherlands  * Neil Mitchell, Standard Chartered Bank, UK  * Katie Ots, Facebook, UK  * Peter Stadler, University of Leipzig, Germany  * Henning Thielemann, Freelancer, Germany  * Niki Vazou, University of California, San Diego, USA If you have any questions, please do not hesitate to contact Joachim Breitner . -- Dr. rer. nat. Joachim Breitner Wissenschaftlicher Mitarbeiter http://pp.ipd.kit.edu/~breitner -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: This is a digitally signed message part URL: From gurudev.devanla at gmail.com Wed Jul 6 01:26:50 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Tue, 5 Jul 2016 18:26:50 -0700 Subject: [Haskell-cafe] Haskell Data Structure design Message-ID: Hello All, I am just getting myself to code in Haskell and would like to design advice. Below, I have a made up example: data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, students: Map StudentId Student} data Student = Student {name::String, feesOwed::Float} data StudentId = Integer get_fees_owed classroom student_id = extra_fees + feesOwed $ (students classroom) M.! studentid Here the `get_fees_owed` needs information from the container 'classroom'. Here is my question/problem: I believe I should model most of my code as expressions, rather than storing pre-computed values such as `fees_owed`. But, defining expressions involve passing the container objects all over. For example, deep down in a function that deals with just one `student`, I might need the fees owed information. Without, having a reference to the container, I cannot call get_fees_owed. Also, I think it hinders composing of functions that just deal with one student at a time, but end up with some dependency on the container. I have several questions related to this design hurdle, but I will start with the one above. Thanks! Guru -------------- next part -------------- An HTML attachment was scrubbed... URL: From michaelburge at pobox.com Wed Jul 6 02:18:28 2016 From: michaelburge at pobox.com (Michael Burge) Date: Tue, 5 Jul 2016 19:18:28 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: When I have functions that are pure but depend on some common state(say in a config file, or retrieved from a database at startup), I like to use implicit parameters to hide it. You can use a type alias to avoid it cluttering up most signatures. Below, a value of type 'Environmental Float' means 'A float value, dependent on some fixed environment containing all students and the single unique classroom'. If you have a deep chain of 'Environmental a' values, the implicit parameter will be automatically propagated to the deepest parts of the expression. You could also use a Reader monad, but they seem to require more invasive syntactic changes: They are better if you later expect to need other monads like IO, but if you're just doing calculations they're overkill. You could also define a type alias 'Environmental a = Environment -> a', but then if you have multiple such states they don't compose well(they require you to apply the implicit state in the correct order, and it can be a little awkward to propagate the parameter). Here's how I would start to structure your example in a larger project: {-# LANGUAGE ImplicitParams,RankNTypes #-} import qualified Data.IntMap as M newtype RowId a = RowId Int data Classroom = Classroom { classroom_id :: RowId Classroom, classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } data Student = Student { student_id :: RowId Student, student_name::String, student_feesOwed::Float} data Environment = Environment { environment_classroom :: Classroom, environment_students :: M.IntMap Student } type Environmental a = (?e :: Environment) => a classroom :: (?e :: Environment) => Classroom classroom = environment_classroom ?e students :: (?e :: Environment) => M.IntMap Student students = environment_students ?e student_totalFeesOwed :: RowId Student -> Environmental Float student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom + (student_feesOwed $ students M.! studentId) main = do let student = Student (RowId 1) "Bob" 250.00 let ?e = Environment { environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ], environment_students = M.fromList [ (1, student) ] } putStrLn $ show $ student_totalFeesOwed $ RowId 1 On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla wrote: > Hello All, > > I am just getting myself to code in Haskell and would like to design > advice. Below, I have a made up example: > > > > > data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, > students: Map StudentId Student} > data Student = Student {name::String, feesOwed::Float} > data StudentId = > Integer > > > > get_fees_owed classroom student_id = extra_fees + feesOwed $ (students > classroom) M.! studentid > > > > Here the `get_fees_owed` needs information from the container > 'classroom'. > > Here is my question/problem: > > > I believe I should model most of my code as expressions, rather than > storing pre-computed values such as `fees_owed`. But, > defining expressions involve passing the container objects all over. For > example, deep down in a function that deals with just > one `student`, I might need the fees owed information. Without, having a > reference to the container, I cannot call get_fees_owed. > > Also, I think it hinders composing of functions that just deal with one > student at a time, but end up with some dependency on > the container. > > I have several questions related to this design hurdle, but I will start > with the one above. > > Thanks! > Guru > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Wed Jul 6 04:44:21 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Tue, 5 Jul 2016 21:44:21 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: Hi Michael, That is excellent. I read about Implicit parameters after reading your post. I like this approach better than Reader monad for my current use case. I wanted to stay away from Reader Monad given that this is my first experimental project and dealing with Reader Monads into levels of nested function calls involved lot more head-ache for me. That said, I plan to try this approach and also see how I can enable this set up in my HUnit tests as well. One other question, I have regarding this design is as follows: Say, during the progress of the computation, the `student_feesOwed` changes, and therefore we have a new instance of classroom with new instance of student in it (with the updated feesOwed). I am guessing, this would mean, wrapping up this new instance into the environment from there on and calling the subsequent functions. Is that assumption, right. Nevertheless, I will play with approach tomorrow and report back! Thanks Guru On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge wrote: > When I have functions that are pure but depend on some common state(say in > a config file, or retrieved from a database at startup), I like to use > implicit parameters to hide it. You can use a type alias to avoid it > cluttering up most signatures. Below, a value of type 'Environmental Float' > means 'A float value, dependent on some fixed environment containing all > students and the single unique classroom'. If you have a deep chain of > 'Environmental a' values, the implicit parameter will be automatically > propagated to the deepest parts of the expression. > > You could also use a Reader monad, but they seem to require more invasive > syntactic changes: They are better if you later expect to need other monads > like IO, but if you're just doing calculations they're overkill. You could > also define a type alias 'Environmental a = Environment -> a', but then if > you have multiple such states they don't compose well(they require you to > apply the implicit state in the correct order, and it can be a little > awkward to propagate the parameter). > > Here's how I would start to structure your example in a larger project: > > {-# LANGUAGE ImplicitParams,RankNTypes #-} > > import qualified Data.IntMap as M > > newtype RowId a = RowId Int > > data Classroom = Classroom { classroom_id :: RowId Classroom, > classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } > data Student = Student { student_id :: RowId Student, > student_name::String, student_feesOwed::Float} > > data Environment = Environment { > environment_classroom :: Classroom, > environment_students :: M.IntMap Student > } > > type Environmental a = (?e :: Environment) => a > > classroom :: (?e :: Environment) => Classroom > classroom = environment_classroom ?e > > students :: (?e :: Environment) => M.IntMap Student > students = environment_students ?e > > student_totalFeesOwed :: RowId Student -> Environmental Float > student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom + > (student_feesOwed $ students M.! studentId) > > main = do > let student = Student (RowId 1) "Bob" 250.00 > let ?e = Environment { > environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ], > environment_students = M.fromList [ (1, student) ] > } > putStrLn $ show $ student_totalFeesOwed $ RowId 1 > > > On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla > wrote: > >> Hello All, >> >> I am just getting myself to code in Haskell and would like to design >> advice. Below, I have a made up example: >> >> >> >> >> data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, >> students: Map StudentId Student} >> data Student = Student {name::String, feesOwed::Float} >> data StudentId = >> Integer >> >> >> >> get_fees_owed classroom student_id = extra_fees + feesOwed $ (students >> classroom) M.! studentid >> >> >> >> Here the `get_fees_owed` needs information from the container >> 'classroom'. >> >> Here is my question/problem: >> >> >> I believe I should model most of my code as expressions, rather than >> storing pre-computed values such as `fees_owed`. But, >> defining expressions involve passing the container objects all over. For >> example, deep down in a function that deals with just >> one `student`, I might need the fees owed information. Without, having a >> reference to the container, I cannot call get_fees_owed. >> >> Also, I think it hinders composing of functions that just deal with one >> student at a time, but end up with some dependency on >> the container. >> >> I have several questions related to this design hurdle, but I will start >> with the one above. >> >> Thanks! >> Guru >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michaelburge at pobox.com Wed Jul 6 05:30:38 2016 From: michaelburge at pobox.com (Michael Burge) Date: Tue, 5 Jul 2016 22:30:38 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: The implicit parameter approach is best if the environment never changes, or at least doesn't change during the computation You can rebind the variable in the middle of a computation, but it's not a good road to go down. The easiest way to simulate a changing environment is to use the State monad. There are other techniques: lenses, nested patterns, rebinding an implicit parameter, ST monad, generating a list of changes and applying the changes to the original state, etc. But - despite having to change your syntax somewhat - I think you'll find it easiest to use a state monad to manage this. Here's a somewhat verbose example of using State to track updates. You can make it less verbose, but I chose to keep it simple. In this example, it updates student_feesOwed as part of registering for a class. So we no longer need to calculate anything: It just grabs the value off of the Student. import Control.Applicative import Control.Monad.Trans.State.Strict import Data.Monoid import qualified Data.IntMap as M newtype RowId a = RowId Int deriving (Eq) data Classroom = Classroom { classroom_id :: RowId Classroom, classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } data Student = Student { student_id :: RowId Student, student_name::String, student_feesOwed::Float} data Environment = Environment { environment_classroom :: Maybe Classroom, environment_students :: M.IntMap Student } student_totalFeesOwed :: RowId Student -> State Environment Float student_totalFeesOwed (RowId studentId) = do (Environment mClassroom students) <- get case mClassroom of Nothing -> return 0.0 Just classroom -> do let fees = student_feesOwed $ students M.! studentId return fees student_addFee :: RowId Student -> Float -> State Environment () student_addFee studentId fee = do modify $ \e -> e { environment_students = M.map (addFee studentId fee) $ environment_students e } where addFee studentId fee student = if studentId == student_id student then student { student_feesOwed = student_feesOwed student + fee } else student environment_addStudent :: Student -> State Environment () environment_addStudent student = do let (RowId key) = student_id student value = student modify $ \e -> e { environment_students = M.insert key value (environment_students e) } classroom_addStudent :: Classroom -> RowId Student -> State Environment () classroom_addStudent classroom studentId = do modify $ \e -> e { environment_classroom = addStudent studentId <$> environment_classroom e } where addStudent :: RowId Student -> Classroom -> Classroom addStudent studentId classroom = classroom { classroom_students = studentId : (classroom_students classroom) } student_registerClass :: RowId Student -> Classroom -> State Environment () student_registerClass studentId classroom = do student_addFee studentId (classroom_extraFees classroom) modify $ \e -> e { environment_classroom = Just classroom } classroom_addStudent classroom studentId main = do let studentId = RowId 1 student = Student studentId "Bob" 250.00 classroom = Classroom (RowId 1) 500.00 [] initialEnvironment = Environment Nothing mempty let totalFeesOwed = flip evalState initialEnvironment $ do environment_addStudent student student_registerClass studentId classroom totalFeesOwed <- student_totalFeesOwed studentId return totalFeesOwed putStrLn $ show totalFeesOwed On Tue, Jul 5, 2016 at 9:44 PM, Guru Devanla wrote: > Hi Michael, > > That is excellent. I read about Implicit parameters after reading your > post. I like this approach better than Reader monad for my current use > case. I wanted to stay away from Reader Monad given that this is my first > experimental project and dealing with Reader Monads into levels of nested > function calls involved lot more head-ache for me. > > That said, I plan to try this approach and also see how I can enable this > set up in my HUnit tests as well. > > One other question, I have regarding this design is as follows: Say, > during the progress of the computation, the `student_feesOwed` changes, and > therefore we have a new instance of classroom with new instance of student > in it (with the updated feesOwed). I am guessing, this would mean, wrapping > up this new instance into the environment from there on and calling the > subsequent functions. Is that assumption, right. Nevertheless, I will play > with approach tomorrow and report back! > > Thanks > Guru > > > > > > > > > > > > On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge > wrote: > >> When I have functions that are pure but depend on some common state(say >> in a config file, or retrieved from a database at startup), I like to use >> implicit parameters to hide it. You can use a type alias to avoid it >> cluttering up most signatures. Below, a value of type 'Environmental Float' >> means 'A float value, dependent on some fixed environment containing all >> students and the single unique classroom'. If you have a deep chain of >> 'Environmental a' values, the implicit parameter will be automatically >> propagated to the deepest parts of the expression. >> >> You could also use a Reader monad, but they seem to require more invasive >> syntactic changes: They are better if you later expect to need other monads >> like IO, but if you're just doing calculations they're overkill. You could >> also define a type alias 'Environmental a = Environment -> a', but then if >> you have multiple such states they don't compose well(they require you to >> apply the implicit state in the correct order, and it can be a little >> awkward to propagate the parameter). >> >> Here's how I would start to structure your example in a larger project: >> >> {-# LANGUAGE ImplicitParams,RankNTypes #-} >> >> import qualified Data.IntMap as M >> >> newtype RowId a = RowId Int >> >> data Classroom = Classroom { classroom_id :: RowId Classroom, >> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } >> data Student = Student { student_id :: RowId Student, >> student_name::String, student_feesOwed::Float} >> >> data Environment = Environment { >> environment_classroom :: Classroom, >> environment_students :: M.IntMap Student >> } >> >> type Environmental a = (?e :: Environment) => a >> >> classroom :: (?e :: Environment) => Classroom >> classroom = environment_classroom ?e >> >> students :: (?e :: Environment) => M.IntMap Student >> students = environment_students ?e >> >> student_totalFeesOwed :: RowId Student -> Environmental Float >> student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom + >> (student_feesOwed $ students M.! studentId) >> >> main = do >> let student = Student (RowId 1) "Bob" 250.00 >> let ?e = Environment { >> environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ], >> environment_students = M.fromList [ (1, student) ] >> } >> putStrLn $ show $ student_totalFeesOwed $ RowId 1 >> >> >> On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla >> wrote: >> >>> Hello All, >>> >>> I am just getting myself to code in Haskell and would like to design >>> advice. Below, I have a made up example: >>> >>> >>> >>> >>> data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, >>> students: Map StudentId Student} >>> data Student = Student {name::String, feesOwed::Float} >>> data StudentId = >>> Integer >>> >>> >>> >>> get_fees_owed classroom student_id = extra_fees + feesOwed $ (students >>> classroom) M.! studentid >>> >>> >>> >>> Here the `get_fees_owed` needs information from the container >>> 'classroom'. >>> >>> Here is my question/problem: >>> >>> >>> I believe I should model most of my code as expressions, rather than >>> storing pre-computed values such as `fees_owed`. But, >>> defining expressions involve passing the container objects all over. For >>> example, deep down in a function that deals with just >>> one `student`, I might need the fees owed information. Without, having a >>> reference to the container, I cannot call get_fees_owed. >>> >>> Also, I think it hinders composing of functions that just deal with one >>> student at a time, but end up with some dependency on >>> the container. >>> >>> I have several questions related to this design hurdle, but I will start >>> with the one above. >>> >>> Thanks! >>> Guru >>> >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >>> >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anton.kholomiov at gmail.com Wed Jul 6 10:22:00 2016 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Wed, 6 Jul 2016 14:22:00 +0400 Subject: [Haskell-cafe] [ANN] processing-for-haskell. New graphics and animation package Message-ID: I'd like to announce a graphics libary processing-for-haskell (available on Hackage). It tries to implement Processing language with Haskell. Processing is an imperative DSL for graphics and animation. It's very easy and fun to use. Intended to be used by non-programmers it has very small but powerful core of functions. It's a shallow EDSL. The Processing is implemented with OpenGL and GLUT. That gives us an opportunity to use all Haskell IO-functions inside the animation loop. Enjoy! github: https://github.com/anton-k/processing-for-haskell hackage: http://hackage.haskell.org/package/processing-for-haskell -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Thu Jul 7 03:39:02 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Wed, 6 Jul 2016 20:39:02 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: The State monad makes a lot of sense for this. I was initially hesitant to go down this path *fearing* monads. But, today I was able to change most of my code to work with the same pattern you provided. Also, my initial impression on State monads was that, it was not a good idea to carry a *big blob* of State around. That impression comes from the thought process influenced by imperative programming. After coding up this, it is a lot clear that State monad declares operations and it is not the `state` itself that is carried around. I am elated! Thank you for the help. I may have more questions as I progress down this path. Thanks Guru On Tue, Jul 5, 2016 at 10:30 PM, Michael Burge wrote: > The implicit parameter approach is best if the environment never changes, > or at least doesn't change during the computation You can rebind the > variable in the middle of a computation, but it's not a good road to go > down. > > The easiest way to simulate a changing environment is to use the State > monad. There are other techniques: lenses, nested patterns, rebinding an > implicit parameter, ST monad, generating a list of changes and applying the > changes to the original state, etc. But - despite having to change your > syntax somewhat - I think you'll find it easiest to use a state monad to > manage this. > > Here's a somewhat verbose example of using State to track updates. You can > make it less verbose, but I chose to keep it simple. In this example, it > updates student_feesOwed as part of registering for a class. So we no > longer need to calculate anything: It just grabs the value off of the > Student. > > import Control.Applicative > import Control.Monad.Trans.State.Strict > import Data.Monoid > > import qualified Data.IntMap as M > > newtype RowId a = RowId Int deriving (Eq) > > data Classroom = Classroom { classroom_id :: RowId Classroom, > classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } > data Student = Student { student_id :: RowId Student, > student_name::String, student_feesOwed::Float} > > data Environment = Environment { > environment_classroom :: Maybe Classroom, > environment_students :: M.IntMap Student > } > > student_totalFeesOwed :: RowId Student -> State Environment Float > student_totalFeesOwed (RowId studentId) = do > (Environment mClassroom students) <- get > case mClassroom of > Nothing -> return 0.0 > Just classroom -> do > let fees = student_feesOwed $ students M.! studentId > return fees > > student_addFee :: RowId Student -> Float -> State Environment () > student_addFee studentId fee = do > modify $ \e -> e { environment_students = M.map (addFee studentId fee) $ > environment_students e } > where > addFee studentId fee student = > if studentId == student_id student > then student { student_feesOwed = student_feesOwed student + fee } > else student > > environment_addStudent :: Student -> State Environment () > environment_addStudent student = do > let (RowId key) = student_id student > value = student > modify $ \e -> e { environment_students = M.insert key value > (environment_students e) } > > classroom_addStudent :: Classroom -> RowId Student -> State Environment () > classroom_addStudent classroom studentId = do > modify $ \e -> e { environment_classroom = addStudent studentId <$> > environment_classroom e } > where > addStudent :: RowId Student -> Classroom -> Classroom > addStudent studentId classroom = classroom { classroom_students = > studentId : (classroom_students classroom) } > > student_registerClass :: RowId Student -> Classroom -> State Environment () > student_registerClass studentId classroom = do > student_addFee studentId (classroom_extraFees classroom) > modify $ \e -> e { environment_classroom = Just classroom } > classroom_addStudent classroom studentId > > main = do > let studentId = RowId 1 > student = Student studentId "Bob" 250.00 > classroom = Classroom (RowId 1) 500.00 [] > initialEnvironment = Environment Nothing mempty > let totalFeesOwed = flip evalState initialEnvironment $ do > environment_addStudent student > student_registerClass studentId classroom > totalFeesOwed <- student_totalFeesOwed studentId > return totalFeesOwed > putStrLn $ show totalFeesOwed > > > On Tue, Jul 5, 2016 at 9:44 PM, Guru Devanla > wrote: > >> Hi Michael, >> >> That is excellent. I read about Implicit parameters after reading your >> post. I like this approach better than Reader monad for my current use >> case. I wanted to stay away from Reader Monad given that this is my first >> experimental project and dealing with Reader Monads into levels of nested >> function calls involved lot more head-ache for me. >> >> That said, I plan to try this approach and also see how I can enable this >> set up in my HUnit tests as well. >> >> One other question, I have regarding this design is as follows: Say, >> during the progress of the computation, the `student_feesOwed` changes, and >> therefore we have a new instance of classroom with new instance of student >> in it (with the updated feesOwed). I am guessing, this would mean, wrapping >> up this new instance into the environment from there on and calling the >> subsequent functions. Is that assumption, right. Nevertheless, I will play >> with approach tomorrow and report back! >> >> Thanks >> Guru >> >> >> >> >> >> >> >> >> >> >> >> On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge >> wrote: >> >>> When I have functions that are pure but depend on some common state(say >>> in a config file, or retrieved from a database at startup), I like to use >>> implicit parameters to hide it. You can use a type alias to avoid it >>> cluttering up most signatures. Below, a value of type 'Environmental Float' >>> means 'A float value, dependent on some fixed environment containing all >>> students and the single unique classroom'. If you have a deep chain of >>> 'Environmental a' values, the implicit parameter will be automatically >>> propagated to the deepest parts of the expression. >>> >>> You could also use a Reader monad, but they seem to require more >>> invasive syntactic changes: They are better if you later expect to need >>> other monads like IO, but if you're just doing calculations they're >>> overkill. You could also define a type alias 'Environmental a = Environment >>> -> a', but then if you have multiple such states they don't compose >>> well(they require you to apply the implicit state in the correct order, and >>> it can be a little awkward to propagate the parameter). >>> >>> Here's how I would start to structure your example in a larger project: >>> >>> {-# LANGUAGE ImplicitParams,RankNTypes #-} >>> >>> import qualified Data.IntMap as M >>> >>> newtype RowId a = RowId Int >>> >>> data Classroom = Classroom { classroom_id :: RowId Classroom, >>> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } >>> data Student = Student { student_id :: RowId Student, >>> student_name::String, student_feesOwed::Float} >>> >>> data Environment = Environment { >>> environment_classroom :: Classroom, >>> environment_students :: M.IntMap Student >>> } >>> >>> type Environmental a = (?e :: Environment) => a >>> >>> classroom :: (?e :: Environment) => Classroom >>> classroom = environment_classroom ?e >>> >>> students :: (?e :: Environment) => M.IntMap Student >>> students = environment_students ?e >>> >>> student_totalFeesOwed :: RowId Student -> Environmental Float >>> student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom >>> + (student_feesOwed $ students M.! studentId) >>> >>> main = do >>> let student = Student (RowId 1) "Bob" 250.00 >>> let ?e = Environment { >>> environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ], >>> environment_students = M.fromList [ (1, student) ] >>> } >>> putStrLn $ show $ student_totalFeesOwed $ RowId 1 >>> >>> >>> On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla >>> wrote: >>> >>>> Hello All, >>>> >>>> I am just getting myself to code in Haskell and would like to design >>>> advice. Below, I have a made up example: >>>> >>>> >>>> >>>> >>>> data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, >>>> students: Map StudentId Student} >>>> data Student = Student {name::String, feesOwed::Float} >>>> data StudentId = >>>> Integer >>>> >>>> >>>> >>>> get_fees_owed classroom student_id = extra_fees + feesOwed $ (students >>>> classroom) M.! studentid >>>> >>>> >>>> >>>> Here the `get_fees_owed` needs information from the container >>>> 'classroom'. >>>> >>>> Here is my question/problem: >>>> >>>> >>>> I believe I should model most of my code as expressions, rather than >>>> storing pre-computed values such as `fees_owed`. But, >>>> defining expressions involve passing the container objects all over. >>>> For example, deep down in a function that deals with just >>>> one `student`, I might need the fees owed information. Without, having >>>> a reference to the container, I cannot call get_fees_owed. >>>> >>>> Also, I think it hinders composing of functions that just deal with one >>>> student at a time, but end up with some dependency on >>>> the container. >>>> >>>> I have several questions related to this design hurdle, but I will >>>> start with the one above. >>>> >>>> Thanks! >>>> Guru >>>> >>>> >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>>> >>> >>> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ruben.astud at gmail.com Thu Jul 7 03:53:40 2016 From: ruben.astud at gmail.com (Ruben Astudillo) Date: Wed, 6 Jul 2016 23:53:40 -0400 Subject: [Haskell-cafe] Resumable applicative parsing from tail end? In-Reply-To: <5767C8AC.4070106@web.de> References: <5767C8AC.4070106@web.de> Message-ID: On 20/06/16 06:42, martin wrote: > as the simulation progresses, I collect "primary" log entries, each one associated with a timestamp. These entries carry > the information I am interested in (and not so much the final state). Currently I am using a simple list to collect log > entries. Since (:) is so much easier than (++) I prepend new entries to the head of the list. So my log runs backwards > in time with the oldest entries at the tail end. > > Because the log-entries are typically too fine-grained to be useful, I want to aggregate several of them into a single > log entry in a secondary log. I want to do this "as I go" and discard primary log entries which are already aggregated. > Thus I can keep the primary log reasonably small. > > I thought that aggregation is just a special case of parsing. And indeed, I could write an applicative parser > > PrimaryLog -> (PrimaryLog, SecondaryLog) > > which does the trick, except I had to reverse the ordering of the primary log. This is because the parser/aggregator > must parse from past to future, because there may be new log entries coming up in the future. I need to be able to > resume parsing where I left off whenever new primary log entries are entered, becuase I may then have just enough > unconsumed primary log entries to create another secondary entry. You are dealing with the classic "streaming problem" when you keep a growing "Log" that you can't reduce until the end of the process; instead of it being returned incrementally as when you `map a list`. Luckily this problem has two standards solution namely pipes/conduit. They let you recover the streaming behaviour you want and will make your parsing go left-to-right. -- -- Ruben Astudillo From anton.kholomiov at gmail.com Fri Jul 8 08:06:07 2016 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Fri, 8 Jul 2016 12:06:07 +0400 Subject: [Haskell-cafe] Strange error with cabal install on windows: Message-ID: I've got an error that I don't know how to fix with cabal install. Has anyone experienced such a thing? It installs fine on ubuntu but fails to install on windows 7. It's my own package called `sharc-timbre`: ~~~ Building sharc-timbre-0.1... Preprocessing library sharc-timbre-0.1... C:\Program Files\Haskell Platform\8.0.1\bin\ghc.exe: createProcess: does not exist (No such file or directory) cabal: Leaving directory 'C:\Users\антон\AppData\Local\Temp\cabal-tmp-4484\sharc-timbre-0.1' ~~~ Thanks, Anton -------------- next part -------------- An HTML attachment was scrubbed... URL: From graninas at gmail.com Fri Jul 8 12:21:59 2016 From: graninas at gmail.com (Alexander Granin) Date: Fri, 8 Jul 2016 18:21:59 +0600 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 155, Issue 8 In-Reply-To: References: Message-ID: Hi Anton! My first thought is to blame Russian letters and/or spaces. Try to move your programs and libraries to plain English path. No guarantees it would help, though. Best, Alexander 2016-07-08 18:00 GMT+06:00 : > Send Haskell-Cafe mailing list submissions to > haskell-cafe at haskell.org > > To subscribe or unsubscribe via the World Wide Web, visit > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > or, via email, send a message with subject or body 'help' to > haskell-cafe-request at haskell.org > > You can reach the person managing the list at > haskell-cafe-owner at haskell.org > > When replying, please edit your Subject line so it is more specific > than "Re: Contents of Haskell-Cafe digest..." > > > Today's Topics: > > 1. Strange error with cabal install on windows: (Anton Kholomiov) > > > ---------------------------------------------------------------------- > > Message: 1 > Date: Fri, 8 Jul 2016 12:06:07 +0400 > From: Anton Kholomiov > To: Haskell Cafe > Subject: [Haskell-cafe] Strange error with cabal install on windows: > Message-ID: > < > CADDxdqOVLzBe+KYiPKieZzjfeZJEkqAHsr1jcdM4pcvfiJ8Qzg at mail.gmail.com> > Content-Type: text/plain; charset="utf-8" > > I've got an error that I don't know how to fix with cabal install. > Has anyone experienced such a thing? It installs fine on ubuntu but > fails to install on windows 7. It's my own package called `sharc-timbre`: > > ~~~ > Building sharc-timbre-0.1... > Preprocessing library sharc-timbre-0.1... > C:\Program Files\Haskell Platform\8.0.1\bin\ghc.exe: createProcess: does > not > exist (No such file or directory) > cabal: Leaving directory > 'C:\Users\антон\AppData\Local\Temp\cabal-tmp-4484\sharc-timbre-0.1' > ~~~ > > Thanks, > Anton > -------------- next part -------------- > An HTML attachment was scrubbed... > URL: < > http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160708/a7f52664/attachment-0001.html > > > > ------------------------------ > > Subject: Digest Footer > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > ------------------------------ > > End of Haskell-Cafe Digest, Vol 155, Issue 8 > ******************************************** > -- С уважением, Александр -------------- next part -------------- An HTML attachment was scrubbed... URL: From brucker at spamfence.net Fri Jul 8 12:26:35 2016 From: brucker at spamfence.net (Achim D. Brucker) Date: Fri, 8 Jul 2016 14:26:35 +0200 Subject: [Haskell-cafe] 3rd Call for Papers: OCL and Textual Modeling Tools and Textual Model Transformations (OCL 2016) - Less Than 10 Days Left To Submit Your Paper! Message-ID: <20160708122635.GA23405@fujikawa.home.brucker.ch> (Apologies for duplicates) Less than 10 days until the deadline! CALL FOR PAPERS 16th International Workshop on OCL and Textual Modeling Co-located with ACM/IEEE 19th International Conference on Model Driven Engineering Languages and Systems (MODELS 2016) October 2, 2016, Saint-Malo, France http://oclworkshop.github.io Modeling started out with UML and its precursors as a graphical notation. Such visual representations enable direct intuitive capturing of reality, but some of their features are difficult to formalize and lack the level of precision required to create complete and unambiguous specifications. Limitations of the graphical notations encouraged the development of text-based modeling languages that either integrate with or replace graphical notations for modeling. Typical examples of such languages are OCL, textual MOF, Epsilon, and Alloy. Textual modeling languages have their roots in formal language paradigms like logic, programming and databases. The goal of this workshop is to create a forum where researchers and practitioners interested in building models using OCL or other kinds of textual languages can directly interact, report advances, share results, identify tools for language development, and discuss appropriate standards. In particular, the workshop will encourage discussions for achieving synergy from different modeling language concepts and modeling language use. The close interaction will enable researchers and practitioners to identify common interests and options for potential cooperation. Topics of interest include (but are not limited to) =================================================== - Mappings between textual modeling languages and other languages or formalisms - Algorithms, evaluation strategies and optimizations in the context of textual modeling languages for -- validation, verification, and testing, -- model transformation and code generation, -- meta-modeling and DSLs, and -- query and constraint specifications - Alternative graphical/textual notations for textual modeling languages - Evolution, transformation and simplification of textual modeling expressions - Libraries, templates and patterns for textual modeling languages - Tools that support textual modeling languages (e.g., verification of OCL formulae, runtime monitoring of invariants) - Complexity results for textual modeling languages - Quality models and benchmarks for comparing and evaluating textual modeling tools and algorithms - Successful applications of textual modeling languages - Case studies on industrial applications of textual modeling languages - Experience reports -- usage of textual modeling languages and tools in complex domains, -- usability of textual modeling languages and tools for end-users - Empirical studies about the benefits and drawbacks of textual modeling languages - Innovative textual modeling tools - Comparison, evaluation and integration of modeling languages - Correlation between modeling languages and modeling tasks This year, we particularly encourage submissions describing tools that support - in a very broad sense - textual modeling languages (if you have implemented OCL.js to run OCL in a web browser, this is the right workshop to present your work) as well as textual model transformations. Venue ===== The workshop will be organized as a part of MODELS 2016 Conference in Saint-Malo, France. It continues the series of OCL workshops held at UML/MODELS conferences: York (2000), Toronto (2001), San Francisco (2003), Lisbon (2004), Montego Bay (2005), Genova (2006), Nashville (2007), Toulouse (2008), Denver (2009), Oslo (2010), Zurich (2011, at the TOOLs conference), 2012 in Innsbruck, 2013 in Miami, 2014 in Valencia, Spain, and 2015 in Ottawa, Canada. Similar to its predecessors, the workshop addresses both people from academia and industry. The aim is to provide a forum for addressing integration of OCL and other textual modeling languages, as well as tools for textual modeling, and for disseminating good practice and discussing the new requirements for textual modeling. Workshop Format =============== The workshop will include short (about 15 min) presentations, parallel sessions of working groups, and sum-up discussions. Submissions =========== Two types of papers will be considered: * short contributions (between 6 and 8 pages) describing new ideas, innovative tools or position papers. * full papers (between 12 and 16 pages) in LNCS format. Submissions should be uploaded to EasyChair (https://easychair.org/conferences/?conf=ocl16). The program committee will review the submissions (minimum 2 reviews per paper, usually 3 reviews) and select papers according to their relevance and interest for discussions that will take place at the workshop. Accepted papers will be published online in a post-conference edition of CEUR (http://www.ceur-ws.org). Important Dates =============== Submission of papers: July 17, 2016 Notification: August 14, 2016 Workshop date: October 2, 2016 Organizers ========== Achim D. Brucker, The University of Sheffield, UK Jordi Cabot, ICREA - Open University of Catalonia, Spain Adolfo Sánchez-Barbudo Herrera, University of York, UK Programme Committee (TBC) ========================= Thomas Baar, University of Applied Sciences Berlin, Germany Mira Balaban, Ben-Gurion University of the Negev, Israel Tricia Balfe, Nomos Software, Ireland Domenico Bianculli, University of Luxembourg Dan Chiorean, Babes-Bolyai University, Romania Robert Clariso, Universitat Oberta de Catalunya, Spain Tony Clark, Middlesex University, UK Manuel Clavel, IMDEA Software Institute, Spain Birgit Demuth, Technische Universitat Dresden, Germany Marina Egea, Indra Sistemas S.A., Spain Geri Georg, Colorado State University, USA Martin Gogolla, University of Bremen, Germany Shahar Maoz, Tel Aviv University, Israel Istvan Rath, Budapest University of Technology and Economics, Hungary Bernhard Rumpe, RWTH Aachen, Germany Massimo Tisi, Mines de Nantes, France Frederic Tuong, Univ. Paris-Sud - IRT SystemX - LRI, France Edward Willink, Willink Transformations Ltd., UK Burkhart Wolff, Univ. Paris-Sud - LRI, France Steffen Zschaler, King's College, UK -- Dr. Achim D. Brucker | Software Assurance & Security | University of Sheffield https://www.brucker.uk/ | https://logicalhacking.com/blog From brucker at spamfence.net Fri Jul 8 13:04:18 2016 From: brucker at spamfence.net (Achim D. Brucker) Date: Fri, 8 Jul 2016 15:04:18 +0200 Subject: [Haskell-cafe] Chair in Information/Computer Security (Sheffield, UK) Message-ID: <20160708130418.GA28776@fujikawa.home.brucker.ch> (Apologies for duplicates) Dear all, The Computer Science Department of The University Of Sheffield has an open position for a Chair in Computer and Information Security. The new chair will lead a new research group in the Department of Computer Science and establish an agenda for security and privacy research across the wider university. Applications are welcome in all areas of computer and/or information security, including * Human factors and secure systems * Security aspects of distributed and autonomous systems Internet of things, cloud computing * Applications of secure systems Manufacturing, health, transport, robotics * Security analysis Intrusion monitoring, threat detection, links with machine learning and language processing * Secure software engineering (Both empirical and theoretical approaches) * Applied cryptography Applications in IT systems, homomorphic encryption For more information about the position and the Department, please visit http://www.sheffield.ac.uk/dcs/research/groups/security/index Or apply directly at https://goo.gl/FSfk5P, application deadline is 27th July, 2016. Best, Achim -- Dr. Achim D. Brucker | Software Assurance & Security | University of Sheffield https://www.brucker.uk/ | https://logicalhacking.com/blog From hon.lianhung at gmail.com Fri Jul 8 13:35:53 2016 From: hon.lianhung at gmail.com (Lian Hung Hon) Date: Fri, 8 Jul 2016 21:35:53 +0800 Subject: [Haskell-cafe] Natural keys in Haskell data structures Message-ID: Dear cafe, What is the idiomatic way to "split" records into their natural keys and content in a data structure? For example, given a user: data User = { username :: ByteString, hash :: ByteString, address :: Text, ... } Using map, a first choice would be Map ByteString User, but this leads to duplication of the username. And it is possible to make mistakes, such as insert "John" (User "Jane" ... What does cafe think? Is there any pattern for this? This is probably just a small nit in the overall architecture, but I'm curious to know the clean way to do it. Regards, Hon -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Fri Jul 8 13:40:46 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Fri, 08 Jul 2016 09:40:46 -0400 Subject: [Haskell-cafe] Natural keys in Haskell data structures In-Reply-To: References: Message-ID: <1467985014-sup-4912@sabre> Hello Lian, I recently wrote a module for just this purpose. Here is the approach that I (and Edward Kmett) like to take: 1. Create a type class with an associated type representing elements whic have keys: {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} class Ord (Key a) => HasKey a where type Key a :: * getKey :: a -> Key a 2. Write new data structures which utilize this type-class. import qualified Data.Map as OldMap data Map a = OldMap.Map (Key a) a insert :: HasKey a => a -> Map a -> Map a These structures are responsible for maintaining the key-value invariants (which can be tricky at times; be careful!) There are other approaches too; for example you can use a multiparameter type class with a functional dependency. "HasKey k a | a -> k" Unfortunately I am not aware of any standardized naming scheme for HasKey/getKey. Edward Excerpts from Lian Hung Hon's message of 2016-07-08 09:35:53 -0400: > Dear cafe, > > What is the idiomatic way to "split" records into their natural keys and > content in a data structure? For example, given a user: > > data User = { username :: ByteString, hash :: ByteString, address :: Text, > ... } > > Using map, a first choice would be Map ByteString User, but this leads to > duplication of the username. And it is possible to make mistakes, such as > > insert "John" (User "Jane" ... > > What does cafe think? Is there any pattern for this? This is probably just > a small nit in the overall architecture, but I'm curious to know the clean > way to do it. > > > Regards, > Hon From anton.kholomiov at gmail.com Fri Jul 8 17:22:22 2016 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Fri, 8 Jul 2016 20:22:22 +0300 Subject: [Haskell-cafe] Haskell-Cafe Digest, Vol 155, Issue 8 In-Reply-To: References: Message-ID: The length of command in windows terminal is limited. Pavel Troev provided the clues, he discovered that the length of the build command is too long. I've got too many modules in my package. I guess that I need to group some submodules to single modules to make it work on windows. 2016-07-08 15:21 GMT+03:00 Alexander Granin : > Hi Anton! > > My first thought is to blame Russian letters and/or spaces. Try to move > your programs and libraries to plain English path. No guarantees it would > help, though. > > Best, > Alexander > > > 2016-07-08 18:00 GMT+06:00 : > >> Send Haskell-Cafe mailing list submissions to >> haskell-cafe at haskell.org >> >> To subscribe or unsubscribe via the World Wide Web, visit >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> or, via email, send a message with subject or body 'help' to >> haskell-cafe-request at haskell.org >> >> You can reach the person managing the list at >> haskell-cafe-owner at haskell.org >> >> When replying, please edit your Subject line so it is more specific >> than "Re: Contents of Haskell-Cafe digest..." >> >> >> Today's Topics: >> >> 1. Strange error with cabal install on windows: (Anton Kholomiov) >> >> >> ---------------------------------------------------------------------- >> >> Message: 1 >> Date: Fri, 8 Jul 2016 12:06:07 +0400 >> From: Anton Kholomiov >> To: Haskell Cafe >> Subject: [Haskell-cafe] Strange error with cabal install on windows: >> Message-ID: >> < >> CADDxdqOVLzBe+KYiPKieZzjfeZJEkqAHsr1jcdM4pcvfiJ8Qzg at mail.gmail.com> >> Content-Type: text/plain; charset="utf-8" >> >> I've got an error that I don't know how to fix with cabal install. >> Has anyone experienced such a thing? It installs fine on ubuntu but >> fails to install on windows 7. It's my own package called `sharc-timbre`: >> >> ~~~ >> Building sharc-timbre-0.1... >> Preprocessing library sharc-timbre-0.1... >> C:\Program Files\Haskell Platform\8.0.1\bin\ghc.exe: createProcess: does >> not >> exist (No such file or directory) >> cabal: Leaving directory >> 'C:\Users\антон\AppData\Local\Temp\cabal-tmp-4484\sharc-timbre-0.1' >> ~~~ >> >> Thanks, >> Anton >> -------------- next part -------------- >> An HTML attachment was scrubbed... >> URL: < >> http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160708/a7f52664/attachment-0001.html >> > >> >> ------------------------------ >> >> Subject: Digest Footer >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> >> >> ------------------------------ >> >> End of Haskell-Cafe Digest, Vol 155, Issue 8 >> ******************************************** >> > > > > -- > С уважением, > Александр > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anton.kholomiov at gmail.com Fri Jul 8 17:27:51 2016 From: anton.kholomiov at gmail.com (Anton Kholomiov) Date: Fri, 8 Jul 2016 20:27:51 +0300 Subject: [Haskell-cafe] Strange error with cabal install on windows: In-Reply-To: References: Message-ID: For those who wants to help. Pavel discovered the cause of the problem for me. I've got too many modules in my package and it causes the error. The length of the command line strings is limited for windows so if you have too many modules the final build command can not list them all. I need to regroup my modules I guess.. It's solved! 8 июля 2016 г., 20:24 пользователь Anton Kholomiov < anton.kholomiov at gmail.com> написал: > Ноо тогда он их не включит в пакет. Не сгенерит объектные файлы для этих > модулей. Я думаю, что мне надо перегруппировать модули. Чтобы их стало > поменьше. Но не слишком сильно, чтобы ghc смог скомпилировать файлы. Если > файл слишком большой он будет крайне долго компилировать. > > 8 июля 2016 г., 13:07 пользователь Pavel Troev > написал: > > ну да.. у меня давно зуб на виндовую консоль по поводу utf-8 >> >> похоже надо подправить .cabal файл - >> убрать все модули из секции Library / Other-Modules: >> >> >> >> C:\sap\sharc_timbre\sharc-timbre-0.1>cabal install >> Warning: The package list for 'hackage.haskell.org' is 81.2 days old. >> Run 'cabal update' to get the latest list of available packages. >> Resolving dependencies... >> Configuring sharc-timbre-0.1... >> Building sharc-timbre-0.1... >> Preprocessing library sharc-timbre-0.1... >> In-place registering sharc-timbre-0.1... >> Creating package registration file: >> C:\Users\root\AppData\Local\Temp\pkgConf-sharc-timbre-048275436.1 >> Installing library in >> >> C:\Users\root\AppData\Roaming\cabal\x86_64-windows-ghc-7.10.3\sharc-timbre-0.1-Ig1DfnlqQG6G3PN7S26idD >> Registering sharc-timbre-0.1... >> Installed sharc-timbre-0.1 >> >> >> [image: Встроенное изображение 1] >> >> >> 8 июля 2016 г., 12:02 пользователь Anton Kholomiov < >> anton.kholomiov at gmail.com> написал: >> >> Похоже слишком много модулей, я этот пакет кодогенерил из БД, стоит >>> пересмотреть структуру пакета, >>> спасибо, теперь я знаю причину.. я что-то слышал о том, что в windows >>> есть лимит на длину строк в командной строке, и мой пакет упёрся в это >>> ограничение >>> >>> 8 июля 2016 г., 12:51 пользователь Pavel Troev >>> написал: >>> >>>> cabal get sharc-timbre >>>> cabal cd sharc-timbre-0.1 >>>> cabal configure >>>> cabal build -v >>>> видим строку ghc --make .... >>>> удаляем где-то половину нот до "Sharc.Instruments.ViolinMuted.Note15" >>>> начал компилировать, похоже дело именно в длине команды >>>> [ 618 of 1379] Compiling Sharc.Instruments.Cell >>>> arc\Instruments\CelloPizzicato\Note25.o ) >>>> [ 619 of 1379] Compiling Sharc.Instruments.Cell >>>> arc\Instruments\CelloPizzicato\Note26.o ) >>>> ... >>>> >>>> >>>> 8 июля 2016 г., 11:40 пользователь Anton Kholomiov < >>>> anton.kholomiov at gmail.com> написал: >>>> >>>>> я пока ещё не изучал вопрос, но вроде работает и там очень много >>>>> обновлений, но судя по тому что они писали в HCAR могут быть сюрпризы, они >>>>> планируют следующие релизы посвятить стабилизации ghc. >>>>> >>>>> >>>>> 2016-07-08 12:27 GMT+04:00 Pavel Troev : >>>>> >>>>>> а стоит на ghc 8 переходить? >>>>>> >>>>>> 2016-07-08 11:24 GMT+03:00 Anton Kholomiov >>>>> >: >>>>>> >>>>>>> Спасибо, то есть это от версии может зависеть.. >>>>>>> >>>>>>> У меня ghc-8.0.1. со стэком у меня не сложилось под виндой, но это >>>>>>> совсем другая история... >>>>>>> >>>>>>> 2016-07-08 12:19 GMT+04:00 Pavel Troev : >>>>>>> >>>>>>>> было похожее - пакет не собирался на win ghc 7.10.2 и спокойно >>>>>>>> собрался на 7.10.3, >>>>>>>> если используете stack, то можно просто поменять lts на 7.10.3 >>>>>>>> >>>>>>>> 2016-07-08 11:06 GMT+03:00 Anton Kholomiov < >>>>>>>> anton.kholomiov at gmail.com>: >>>>>>>> >>>>>>>>> I've got an error that I don't know how to fix with cabal install. >>>>>>>>> Has anyone experienced such a thing? It installs fine on ubuntu but >>>>>>>>> fails to install on windows 7. It's my own package called >>>>>>>>> `sharc-timbre`: >>>>>>>>> >>>>>>>>> ~~~ >>>>>>>>> Building sharc-timbre-0.1... >>>>>>>>> Preprocessing library sharc-timbre-0.1... >>>>>>>>> C:\Program Files\Haskell Platform\8.0.1\bin\ghc.exe: >>>>>>>>> createProcess: does not >>>>>>>>> exist (No such file or directory) >>>>>>>>> cabal: Leaving directory >>>>>>>>> 'C:\Users\антон\AppData\Local\Temp\cabal-tmp-4484\sharc-timbre-0.1' >>>>>>>>> ~~~ >>>>>>>>> >>>>>>>>> Thanks, >>>>>>>>> Anton >>>>>>>>> >>>>>>>>> _______________________________________________ >>>>>>>>> Haskell-Cafe mailing list >>>>>>>>> To (un)subscribe, modify options or view archives go to: >>>>>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>>>>>>> Only members subscribed via the mailman list are allowed to post. >>>>>>>>> >>>>>>>> >>>>>>>> >>>>>>>> >>>>>>>> -- >>>>>>>> С уважением, >>>>>>>> >>>>>>>> Павел Троев >>>>>>>> Консультант БерингПойнт >>>>>>>> Проект SOL, Газпром-нефть >>>>>>>> Моб. тел: +7 916 441 48 61 >>>>>>>> pavel.troev at gmail.com | troev.pd at gazprom-neft.ru >>>>>>>> >>>>>>>> >>>>>>>> >>>>>>> >>>>>> >>>>>> >>>>>> -- >>>>>> С уважением, >>>>>> >>>>>> Павел Троев >>>>>> Консультант БерингПойнт >>>>>> Проект SOL, Газпром-нефть >>>>>> Моб. тел: +7 916 441 48 61 >>>>>> pavel.troev at gmail.com | troev.pd at gazprom-neft.ru >>>>>> >>>>>> >>>>>> >>>>> >>>> >>>> >>>> -- >>>> С уважением, >>>> >>>> Павел Троев >>>> Консультант БерингПойнт >>>> Проект SOL, Газпром-нефть >>>> Моб. тел: +7 916 441 48 61 >>>> pavel.troev at gmail.com | troev.pd at gazprom-neft.ru >>>> >>>> >>>> >>> >> >> >> -- >> С уважением, >> >> Павел Троев >> Консультант БерингПойнт >> Проект SOL, Газпром-нефть >> Моб. тел: +7 916 441 48 61 >> pavel.troev at gmail.com | troev.pd at gazprom-neft.ru >> >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: image.png Type: image/png Size: 60919 bytes Desc: not available URL: From vogt.adam at gmail.com Fri Jul 8 23:11:45 2016 From: vogt.adam at gmail.com (adam vogt) Date: Fri, 8 Jul 2016 19:11:45 -0400 Subject: [Haskell-cafe] Natural keys in Haskell data structures In-Reply-To: <1467985014-sup-4912@sabre> References: <1467985014-sup-4912@sabre> Message-ID: Hi, I think what Edward describes can be achieved by taking a multi index set library, and using only one index. I searched Hackage and found many unmaintained options: deprecated: tables, HiggsSet data-store -- needs dependency version bumps at least These are probably usable options: ixset, ixset-typed, data-map-multikey Based on my search, it seems to me that there are very few maintained libraries between Data.Map and packages like persistent and groundhog. Those two libraries provide convenient access to sql databases, which is probably unnecessarily complex for the original problem. Regards, Adam On Fri, Jul 8, 2016 at 9:40 AM, Edward Z. Yang wrote: > Hello Lian, > > I recently wrote a module for just this purpose. Here is the approach > that I (and Edward Kmett) like to take: > > 1. Create a type class with an associated type representing elements > whic have keys: > > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE UndecidableInstances #-} > class Ord (Key a) => HasKey a where > type Key a :: * > getKey :: a -> Key a > > 2. Write new data structures which utilize this type-class. > > import qualified Data.Map as OldMap > data Map a = OldMap.Map (Key a) a > insert :: HasKey a => a -> Map a -> Map a > > These structures are responsible for maintaining the key-value > invariants (which can be tricky at times; be careful!) > > There are other approaches too; for example you can use a multiparameter > type class with a functional dependency. "HasKey k a | a -> k" > > Unfortunately I am not aware of any standardized naming scheme > for HasKey/getKey. > > Edward > > Excerpts from Lian Hung Hon's message of 2016-07-08 09:35:53 -0400: > > Dear cafe, > > > > What is the idiomatic way to "split" records into their natural keys and > > content in a data structure? For example, given a user: > > > > data User = { username :: ByteString, hash :: ByteString, address :: > Text, > > ... } > > > > Using map, a first choice would be Map ByteString User, but this leads to > > duplication of the username. And it is possible to make mistakes, such as > > > > insert "John" (User "Jane" ... > > > > What does cafe think? Is there any pattern for this? This is probably > just > > a small nit in the overall architecture, but I'm curious to know the > clean > > way to do it. > > > > > > Regards, > > Hon > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From vogt.adam at gmail.com Fri Jul 8 23:57:02 2016 From: vogt.adam at gmail.com (adam vogt) Date: Fri, 8 Jul 2016 19:57:02 -0400 Subject: [Haskell-cafe] Intanciate data type In-Reply-To: References: Message-ID: I'll add that Gautier's Prod has an inverse. When it's included, ghc can infer the types of x in these expressions: \x -> (Foo x :: Foo Int a) \x -> (Foo x :: Foo String a) as String and Maybe String respectively. Prod was unchanged, but the rest becomes: type family ProdInv a where ProdInv Int = String ProdInv a = Maybe a data Foo e a where Foo :: e ~ ProdInv (Prod e) => e -> Foo (Prod e) a I also thought about using a data family instead of a pair of type families. But then you still have two constructors. `class ProdFD e pe | e -> pe, pe -> e` can't work: 1. FDs don't provide coercions like TFs 2. the two ProdFD instances are rejected -- they overlap/violate FDs On Mon, Jul 4, 2016 at 5:31 PM, Gautier DI FOLCO wrote: > Hello, > > I would say that type families should do the joke: > > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE GADTs #-} > type family Prod a where > Prod String = Int > Prod (Maybe a) = a > > data Foo e a > where > > Foo :: e -> Foo (Prod e) a > > Regards. > > 2016-07-04 22:43 GMT+02:00 Corentin Dupont : > >> Hi all, >> I have a data type looking like this: >> >> data Foo e a >> where >> >> Foo :: e → Foo e a >> >> I would like to instantiate it to make it equivalent to: >> >> data Bar a >> where >> >> A :: String → Bar Int >> B :: Maybe a → Bar a >> >> How can I do that? With a functional dependency? >> I probably need to change the definition of Foo. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Sat Jul 9 01:57:26 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Fri, 8 Jul 2016 18:57:26 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: Hi Michael, I have been taking this approach of State Monads and I have hit upon 3 common patterns that I think may not be the idiomatic way of dealing with state. I would like to continue with the example we have to explain those scenarios. Any input on this would be great.. 1. I see that almost in every function I deal with state, I have e <- get , expression in the begining. I always ending up having to use the state to query for different values. I guess this is OK. 2. In deeply nested function, where I pass state, I also end up calling evalState a couple of times to get to some values. Is that common. Here is one example, from our toy problem. first_student_owes_more :: RowId Student -> RowId Student -> State Environment Bool first_student_owes_more student_1 student_2 = do e <- get let fees_owed_by_student_1 = evalState (student_totalFeesOwed student_1) $ e let fees_owed_by_student_2 = evalState (student_totalFeesOwed student_2) $ e return $ fees_owed_by_student_1 > fees_owed_by_student_2 You see, I have to evalState twice to get to what I want. Is that a common way to use the State. 3. I also end up performing evalState while mapping over a list of values. Say, I wanted to loop around a list of students to perform the function in (2), then invariable for each iteration of Map, I am calling evalState once. This gets hairy, if the value in my State is a Data.Map structure. Am I using the State Monad in a round about way? Thanks Guru On Wed, Jul 6, 2016 at 8:39 PM, Guru Devanla wrote: > The State monad makes a lot of sense for this. I was initially hesitant to > go down this path *fearing* monads. But, today I was able to change most of > my code to work with the same pattern you provided. Also, my initial > impression on State monads was that, it was not a good idea to carry a *big > blob* of State around. That impression comes from the thought process > influenced by imperative programming. After coding up this, it is a lot > clear that State monad declares operations and it is not the `state` itself > that is carried around. I am elated! > > Thank you for the help. I may have more questions as I progress down this > path. > > Thanks > Guru > > > On Tue, Jul 5, 2016 at 10:30 PM, Michael Burge > wrote: > >> The implicit parameter approach is best if the environment never changes, >> or at least doesn't change during the computation You can rebind the >> variable in the middle of a computation, but it's not a good road to go >> down. >> >> The easiest way to simulate a changing environment is to use the State >> monad. There are other techniques: lenses, nested patterns, rebinding an >> implicit parameter, ST monad, generating a list of changes and applying the >> changes to the original state, etc. But - despite having to change your >> syntax somewhat - I think you'll find it easiest to use a state monad to >> manage this. >> >> Here's a somewhat verbose example of using State to track updates. You >> can make it less verbose, but I chose to keep it simple. In this example, >> it updates student_feesOwed as part of registering for a class. So we no >> longer need to calculate anything: It just grabs the value off of the >> Student. >> >> import Control.Applicative >> import Control.Monad.Trans.State.Strict >> import Data.Monoid >> >> import qualified Data.IntMap as M >> >> newtype RowId a = RowId Int deriving (Eq) >> >> data Classroom = Classroom { classroom_id :: RowId Classroom, >> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } >> data Student = Student { student_id :: RowId Student, >> student_name::String, student_feesOwed::Float} >> >> data Environment = Environment { >> environment_classroom :: Maybe Classroom, >> environment_students :: M.IntMap Student >> } >> >> student_totalFeesOwed :: RowId Student -> State Environment Float >> student_totalFeesOwed (RowId studentId) = do >> (Environment mClassroom students) <- get >> case mClassroom of >> Nothing -> return 0.0 >> Just classroom -> do >> let fees = student_feesOwed $ students M.! studentId >> return fees >> >> student_addFee :: RowId Student -> Float -> State Environment () >> student_addFee studentId fee = do >> modify $ \e -> e { environment_students = M.map (addFee studentId fee) >> $ environment_students e } >> where >> addFee studentId fee student = >> if studentId == student_id student >> then student { student_feesOwed = student_feesOwed student + fee } >> else student >> >> environment_addStudent :: Student -> State Environment () >> environment_addStudent student = do >> let (RowId key) = student_id student >> value = student >> modify $ \e -> e { environment_students = M.insert key value >> (environment_students e) } >> >> classroom_addStudent :: Classroom -> RowId Student -> State Environment () >> classroom_addStudent classroom studentId = do >> modify $ \e -> e { environment_classroom = addStudent studentId <$> >> environment_classroom e } >> where >> addStudent :: RowId Student -> Classroom -> Classroom >> addStudent studentId classroom = classroom { classroom_students = >> studentId : (classroom_students classroom) } >> >> student_registerClass :: RowId Student -> Classroom -> State Environment >> () >> student_registerClass studentId classroom = do >> student_addFee studentId (classroom_extraFees classroom) >> modify $ \e -> e { environment_classroom = Just classroom } >> classroom_addStudent classroom studentId >> >> main = do >> let studentId = RowId 1 >> student = Student studentId "Bob" 250.00 >> classroom = Classroom (RowId 1) 500.00 [] >> initialEnvironment = Environment Nothing mempty >> let totalFeesOwed = flip evalState initialEnvironment $ do >> environment_addStudent student >> student_registerClass studentId classroom >> totalFeesOwed <- student_totalFeesOwed studentId >> return totalFeesOwed >> putStrLn $ show totalFeesOwed >> >> >> On Tue, Jul 5, 2016 at 9:44 PM, Guru Devanla >> wrote: >> >>> Hi Michael, >>> >>> That is excellent. I read about Implicit parameters after reading your >>> post. I like this approach better than Reader monad for my current use >>> case. I wanted to stay away from Reader Monad given that this is my first >>> experimental project and dealing with Reader Monads into levels of nested >>> function calls involved lot more head-ache for me. >>> >>> That said, I plan to try this approach and also see how I can enable >>> this set up in my HUnit tests as well. >>> >>> One other question, I have regarding this design is as follows: Say, >>> during the progress of the computation, the `student_feesOwed` changes, and >>> therefore we have a new instance of classroom with new instance of student >>> in it (with the updated feesOwed). I am guessing, this would mean, wrapping >>> up this new instance into the environment from there on and calling the >>> subsequent functions. Is that assumption, right. Nevertheless, I will play >>> with approach tomorrow and report back! >>> >>> Thanks >>> Guru >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> >>> On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge >>> wrote: >>> >>>> When I have functions that are pure but depend on some common state(say >>>> in a config file, or retrieved from a database at startup), I like to use >>>> implicit parameters to hide it. You can use a type alias to avoid it >>>> cluttering up most signatures. Below, a value of type 'Environmental Float' >>>> means 'A float value, dependent on some fixed environment containing all >>>> students and the single unique classroom'. If you have a deep chain of >>>> 'Environmental a' values, the implicit parameter will be automatically >>>> propagated to the deepest parts of the expression. >>>> >>>> You could also use a Reader monad, but they seem to require more >>>> invasive syntactic changes: They are better if you later expect to need >>>> other monads like IO, but if you're just doing calculations they're >>>> overkill. You could also define a type alias 'Environmental a = Environment >>>> -> a', but then if you have multiple such states they don't compose >>>> well(they require you to apply the implicit state in the correct order, and >>>> it can be a little awkward to propagate the parameter). >>>> >>>> Here's how I would start to structure your example in a larger project: >>>> >>>> {-# LANGUAGE ImplicitParams,RankNTypes #-} >>>> >>>> import qualified Data.IntMap as M >>>> >>>> newtype RowId a = RowId Int >>>> >>>> data Classroom = Classroom { classroom_id :: RowId Classroom, >>>> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } >>>> data Student = Student { student_id :: RowId Student, >>>> student_name::String, student_feesOwed::Float} >>>> >>>> data Environment = Environment { >>>> environment_classroom :: Classroom, >>>> environment_students :: M.IntMap Student >>>> } >>>> >>>> type Environmental a = (?e :: Environment) => a >>>> >>>> classroom :: (?e :: Environment) => Classroom >>>> classroom = environment_classroom ?e >>>> >>>> students :: (?e :: Environment) => M.IntMap Student >>>> students = environment_students ?e >>>> >>>> student_totalFeesOwed :: RowId Student -> Environmental Float >>>> student_totalFeesOwed (RowId studentId) = classroom_extraFees classroom >>>> + (student_feesOwed $ students M.! studentId) >>>> >>>> main = do >>>> let student = Student (RowId 1) "Bob" 250.00 >>>> let ?e = Environment { >>>> environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ], >>>> environment_students = M.fromList [ (1, student) ] >>>> } >>>> putStrLn $ show $ student_totalFeesOwed $ RowId 1 >>>> >>>> >>>> On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla >>> > wrote: >>>> >>>>> Hello All, >>>>> >>>>> I am just getting myself to code in Haskell and would like to design >>>>> advice. Below, I have a made up example: >>>>> >>>>> >>>>> >>>>> >>>>> data ClassRoom = ClassRoom { classRoomNo:: Integer, extra_fees::Float, >>>>> students: Map StudentId Student} >>>>> data Student = Student {name::String, feesOwed::Float} >>>>> data StudentId = >>>>> Integer >>>>> >>>>> >>>>> >>>>> get_fees_owed classroom student_id = extra_fees + feesOwed $ (students >>>>> classroom) M.! studentid >>>>> >>>>> >>>>> >>>>> Here the `get_fees_owed` needs information from the container >>>>> 'classroom'. >>>>> >>>>> Here is my question/problem: >>>>> >>>>> >>>>> I believe I should model most of my code as expressions, rather than >>>>> storing pre-computed values such as `fees_owed`. But, >>>>> defining expressions involve passing the container objects all over. >>>>> For example, deep down in a function that deals with just >>>>> one `student`, I might need the fees owed information. Without, having >>>>> a reference to the container, I cannot call get_fees_owed. >>>>> >>>>> Also, I think it hinders composing of functions that just deal with >>>>> one student at a time, but end up with some dependency on >>>>> the container. >>>>> >>>>> I have several questions related to this design hurdle, but I will >>>>> start with the one above. >>>>> >>>>> Thanks! >>>>> Guru >>>>> >>>>> >>>>> >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> To (un)subscribe, modify options or view archives go to: >>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>>> Only members subscribed via the mailman list are allowed to post. >>>>> >>>> >>>> >>> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Sat Jul 9 02:07:56 2016 From: will.yager at gmail.com (William Yager) Date: Fri, 8 Jul 2016 22:07:56 -0400 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: For #1, look into using the Lens library's support for the State monad. You can often avoid doing a get, and instead write things like `fees += 5`, which will add 5 to the field in the state called "fees". For #2, you should just be able to do fees_1 <- student_totalFeesOwed student_1 fees_2 <- student_totalFeesOwed student_2 unless `student_totalFeesOwed` changes the state and you want to prevent it from doing so. For #3, you should be able to use e.g. mapM. It sounds like you are using the State monad in a somewhat roundabout way. The whole point is that you don't have to get the state and pass it into evalState; this happens automatically as part of the State Monad's (>>=) operator. Will On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla wrote: > Hi Michael, > > I have been taking this approach of State Monads and I have hit upon 3 > common patterns that I think may not be the idiomatic way of dealing with > state. I would like to continue with the example we have to explain those > scenarios. Any input on this would be great.. > > 1. I see that almost in every function I deal with state, I have e <- get > , expression in the begining. I always ending up having to use the state to > query for different values. I guess this is OK. > > 2. In deeply nested function, where I pass state, I also end up calling > evalState a couple of times to get to some values. Is that common. Here is > one example, from our toy problem. > > first_student_owes_more :: RowId Student -> RowId Student -> State > Environment Bool > first_student_owes_more student_1 student_2 = do > e <- get > let fees_owed_by_student_1 = evalState (student_totalFeesOwed student_1) > $ e > let fees_owed_by_student_2 = evalState (student_totalFeesOwed student_2) > $ e > return $ fees_owed_by_student_1 > fees_owed_by_student_2 > > You see, I have to evalState twice to get to what I want. Is that a common > way to use the State. > > 3. I also end up performing evalState while mapping over a list of > values. Say, I wanted to loop around a list of students to perform the > function in (2), then invariable for each iteration of Map, I am calling > evalState once. > > This gets hairy, if the value in my State is a Data.Map structure. > > Am I using the State Monad in a round about way? > > Thanks > Guru > > > > > > > > On Wed, Jul 6, 2016 at 8:39 PM, Guru Devanla > wrote: > >> The State monad makes a lot of sense for this. I was initially hesitant >> to go down this path *fearing* monads. But, today I was able to change most >> of my code to work with the same pattern you provided. Also, my initial >> impression on State monads was that, it was not a good idea to carry a *big >> blob* of State around. That impression comes from the thought process >> influenced by imperative programming. After coding up this, it is a lot >> clear that State monad declares operations and it is not the `state` itself >> that is carried around. I am elated! >> >> Thank you for the help. I may have more questions as I progress down this >> path. >> >> Thanks >> Guru >> >> >> On Tue, Jul 5, 2016 at 10:30 PM, Michael Burge >> wrote: >> >>> The implicit parameter approach is best if the environment never >>> changes, or at least doesn't change during the computation You can rebind >>> the variable in the middle of a computation, but it's not a good road to go >>> down. >>> >>> The easiest way to simulate a changing environment is to use the State >>> monad. There are other techniques: lenses, nested patterns, rebinding an >>> implicit parameter, ST monad, generating a list of changes and applying the >>> changes to the original state, etc. But - despite having to change your >>> syntax somewhat - I think you'll find it easiest to use a state monad to >>> manage this. >>> >>> Here's a somewhat verbose example of using State to track updates. You >>> can make it less verbose, but I chose to keep it simple. In this example, >>> it updates student_feesOwed as part of registering for a class. So we no >>> longer need to calculate anything: It just grabs the value off of the >>> Student. >>> >>> import Control.Applicative >>> import Control.Monad.Trans.State.Strict >>> import Data.Monoid >>> >>> import qualified Data.IntMap as M >>> >>> newtype RowId a = RowId Int deriving (Eq) >>> >>> data Classroom = Classroom { classroom_id :: RowId Classroom, >>> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } >>> data Student = Student { student_id :: RowId Student, >>> student_name::String, student_feesOwed::Float} >>> >>> data Environment = Environment { >>> environment_classroom :: Maybe Classroom, >>> environment_students :: M.IntMap Student >>> } >>> >>> student_totalFeesOwed :: RowId Student -> State Environment Float >>> student_totalFeesOwed (RowId studentId) = do >>> (Environment mClassroom students) <- get >>> case mClassroom of >>> Nothing -> return 0.0 >>> Just classroom -> do >>> let fees = student_feesOwed $ students M.! studentId >>> return fees >>> >>> student_addFee :: RowId Student -> Float -> State Environment () >>> student_addFee studentId fee = do >>> modify $ \e -> e { environment_students = M.map (addFee studentId fee) >>> $ environment_students e } >>> where >>> addFee studentId fee student = >>> if studentId == student_id student >>> then student { student_feesOwed = student_feesOwed student + fee } >>> else student >>> >>> environment_addStudent :: Student -> State Environment () >>> environment_addStudent student = do >>> let (RowId key) = student_id student >>> value = student >>> modify $ \e -> e { environment_students = M.insert key value >>> (environment_students e) } >>> >>> classroom_addStudent :: Classroom -> RowId Student -> State Environment >>> () >>> classroom_addStudent classroom studentId = do >>> modify $ \e -> e { environment_classroom = addStudent studentId <$> >>> environment_classroom e } >>> where >>> addStudent :: RowId Student -> Classroom -> Classroom >>> addStudent studentId classroom = classroom { classroom_students = >>> studentId : (classroom_students classroom) } >>> >>> student_registerClass :: RowId Student -> Classroom -> State Environment >>> () >>> student_registerClass studentId classroom = do >>> student_addFee studentId (classroom_extraFees classroom) >>> modify $ \e -> e { environment_classroom = Just classroom } >>> classroom_addStudent classroom studentId >>> >>> main = do >>> let studentId = RowId 1 >>> student = Student studentId "Bob" 250.00 >>> classroom = Classroom (RowId 1) 500.00 [] >>> initialEnvironment = Environment Nothing mempty >>> let totalFeesOwed = flip evalState initialEnvironment $ do >>> environment_addStudent student >>> student_registerClass studentId classroom >>> totalFeesOwed <- student_totalFeesOwed studentId >>> return totalFeesOwed >>> putStrLn $ show totalFeesOwed >>> >>> >>> On Tue, Jul 5, 2016 at 9:44 PM, Guru Devanla >>> wrote: >>> >>>> Hi Michael, >>>> >>>> That is excellent. I read about Implicit parameters after reading your >>>> post. I like this approach better than Reader monad for my current use >>>> case. I wanted to stay away from Reader Monad given that this is my first >>>> experimental project and dealing with Reader Monads into levels of nested >>>> function calls involved lot more head-ache for me. >>>> >>>> That said, I plan to try this approach and also see how I can enable >>>> this set up in my HUnit tests as well. >>>> >>>> One other question, I have regarding this design is as follows: Say, >>>> during the progress of the computation, the `student_feesOwed` changes, and >>>> therefore we have a new instance of classroom with new instance of student >>>> in it (with the updated feesOwed). I am guessing, this would mean, wrapping >>>> up this new instance into the environment from there on and calling the >>>> subsequent functions. Is that assumption, right. Nevertheless, I will play >>>> with approach tomorrow and report back! >>>> >>>> Thanks >>>> Guru >>>> >>>> >>>> >>>> >>>> >>>> >>>> >>>> >>>> >>>> >>>> >>>> On Tue, Jul 5, 2016 at 7:18 PM, Michael Burge >>>> wrote: >>>> >>>>> When I have functions that are pure but depend on some common >>>>> state(say in a config file, or retrieved from a database at startup), I >>>>> like to use implicit parameters to hide it. You can use a type alias to >>>>> avoid it cluttering up most signatures. Below, a value of type >>>>> 'Environmental Float' means 'A float value, dependent on some fixed >>>>> environment containing all students and the single unique classroom'. If >>>>> you have a deep chain of 'Environmental a' values, the implicit parameter >>>>> will be automatically propagated to the deepest parts of the expression. >>>>> >>>>> You could also use a Reader monad, but they seem to require more >>>>> invasive syntactic changes: They are better if you later expect to need >>>>> other monads like IO, but if you're just doing calculations they're >>>>> overkill. You could also define a type alias 'Environmental a = Environment >>>>> -> a', but then if you have multiple such states they don't compose >>>>> well(they require you to apply the implicit state in the correct order, and >>>>> it can be a little awkward to propagate the parameter). >>>>> >>>>> Here's how I would start to structure your example in a larger project: >>>>> >>>>> {-# LANGUAGE ImplicitParams,RankNTypes #-} >>>>> >>>>> import qualified Data.IntMap as M >>>>> >>>>> newtype RowId a = RowId Int >>>>> >>>>> data Classroom = Classroom { classroom_id :: RowId Classroom, >>>>> classroom_extraFees :: Float, classroom_students :: [ RowId Student ] } >>>>> data Student = Student { student_id :: RowId Student, >>>>> student_name::String, student_feesOwed::Float} >>>>> >>>>> data Environment = Environment { >>>>> environment_classroom :: Classroom, >>>>> environment_students :: M.IntMap Student >>>>> } >>>>> >>>>> type Environmental a = (?e :: Environment) => a >>>>> >>>>> classroom :: (?e :: Environment) => Classroom >>>>> classroom = environment_classroom ?e >>>>> >>>>> students :: (?e :: Environment) => M.IntMap Student >>>>> students = environment_students ?e >>>>> >>>>> student_totalFeesOwed :: RowId Student -> Environmental Float >>>>> student_totalFeesOwed (RowId studentId) = classroom_extraFees >>>>> classroom + (student_feesOwed $ students M.! studentId) >>>>> >>>>> main = do >>>>> let student = Student (RowId 1) "Bob" 250.00 >>>>> let ?e = Environment { >>>>> environment_classroom = Classroom (RowId 1) 500.00 [ RowId 1 ], >>>>> environment_students = M.fromList [ (1, student) ] >>>>> } >>>>> putStrLn $ show $ student_totalFeesOwed $ RowId 1 >>>>> >>>>> >>>>> On Tue, Jul 5, 2016 at 6:26 PM, Guru Devanla < >>>>> gurudev.devanla at gmail.com> wrote: >>>>> >>>>>> Hello All, >>>>>> >>>>>> I am just getting myself to code in Haskell and would like to design >>>>>> advice. Below, I have a made up example: >>>>>> >>>>>> >>>>>> >>>>>> >>>>>> data ClassRoom = ClassRoom { classRoomNo:: Integer, >>>>>> extra_fees::Float, students: Map StudentId Student} >>>>>> data Student = Student {name::String, feesOwed::Float} >>>>>> data StudentId = >>>>>> Integer >>>>>> >>>>>> >>>>>> >>>>>> get_fees_owed classroom student_id = extra_fees + feesOwed $ >>>>>> (students classroom) M.! studentid >>>>>> >>>>>> >>>>>> >>>>>> Here the `get_fees_owed` needs information from the container >>>>>> 'classroom'. >>>>>> >>>>>> Here is my question/problem: >>>>>> >>>>>> >>>>>> I believe I should model most of my code as expressions, rather than >>>>>> storing pre-computed values such as `fees_owed`. But, >>>>>> defining expressions involve passing the container objects all over. >>>>>> For example, deep down in a function that deals with just >>>>>> one `student`, I might need the fees owed information. Without, >>>>>> having a reference to the container, I cannot call get_fees_owed. >>>>>> >>>>>> Also, I think it hinders composing of functions that just deal with >>>>>> one student at a time, but end up with some dependency on >>>>>> the container. >>>>>> >>>>>> I have several questions related to this design hurdle, but I will >>>>>> start with the one above. >>>>>> >>>>>> Thanks! >>>>>> Guru >>>>>> >>>>>> >>>>>> >>>>>> _______________________________________________ >>>>>> Haskell-Cafe mailing list >>>>>> To (un)subscribe, modify options or view archives go to: >>>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>>>> Only members subscribed via the mailman list are allowed to post. >>>>>> >>>>> >>>>> >>>> >>> >> > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From amindfv at gmail.com Sat Jul 9 02:55:17 2016 From: amindfv at gmail.com (amindfv at gmail.com) Date: Fri, 8 Jul 2016 22:55:17 -0400 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: Message-ID: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> >> On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla wrote: >> 1. I see that almost in every function I deal with state, I have e <- get , expression in the begining. I always ending up having to use the state to query for different values. I guess this is OK. > El 8 jul 2016, a las 22:07, William Yager escribió: > > For #1, look into using the Lens library's support for the State monad. You can often avoid doing a get, and instead write things like `fees += 5`, which will add 5 to the field in the state called "fees". > Lens is a pretty heavy extra thing for a beginner to have to learn -- you'll do fine with the 'modify' function: modify :: (s -> s) -> State s () So instead of writing: do s <- get put (s + 5) You say: modify (+5) Tom -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Sat Jul 9 04:56:37 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Fri, 8 Jul 2016 21:56:37 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> References: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> Message-ID: William/Tom, (1) Yes, looking into lens and re-factoring my current experimental project in lens will be my next iteration. For now, I plan not to spend time on it. (2) Agreed. Not sure how I missed that. (3) I see how foldM works now. I missed the point that foldM not only is a `map` but also does a `sequence` after that. I got stuck earlier, thinking I will end up with a list of state monads. The sequence steps executes this monadic action. But, how can I do a foldM in a state monad. Say, I need to map over a list of students and add up all their fees, can I get away not `evalState` inside the foldM step function? Thanks. this is very exciting as I keep simplifying my code! Guru On Fri, Jul 8, 2016 at 7:55 PM, wrote: > > On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla > wrote: > > > 1. I see that almost in every function I deal with state, I have e <- get >> , expression in the begining. I always ending up having to use the state to >> query for different values. I guess this is OK. >> > > El 8 jul 2016, a las 22:07, William Yager escribió: > > For #1, look into using the Lens library's support for the State monad. > You can often avoid doing a get, and instead write things like `fees += 5`, > which will add 5 to the field in the state called "fees". > > > Lens is a pretty heavy extra thing for a beginner to have to learn -- > you'll do fine with the 'modify' function: > > modify :: (s -> s) -> State s () > > So instead of writing: > > do > s <- get > put (s + 5) > > You say: > > modify (+5) > > > Tom > -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Sat Jul 9 16:15:56 2016 From: will.yager at gmail.com (Will Yager) Date: Sat, 9 Jul 2016 12:15:56 -0400 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> Message-ID: I did the same thing when I was learning to generalize my understanding of monads! Very common mistake. I'm not sure I understand your question about #3. Can you give an example using evalState? We'll tell you if you can do it without evalState. I suspect you want something like "mapM_ addStudentFee students" Will > On Jul 9, 2016, at 00:56, Guru Devanla wrote: > > William/Tom, > > (1) Yes, looking into lens and re-factoring my current experimental project in lens will be my next iteration. For now, I plan not to spend time on it. > > (2) Agreed. Not sure how I missed that. > > (3) I see how foldM works now. I missed the point that foldM not only is a `map` but also does a `sequence` after that. I got stuck earlier, thinking I will end up with a list of state monads. The sequence steps executes this monadic action. > > But, how can I do a foldM in a state monad. Say, I need to map over a list of students and add up all their fees, can I get away not `evalState` inside the foldM step function? > > Thanks. this is very exciting as I keep simplifying my code! > > Guru > > > > >> On Fri, Jul 8, 2016 at 7:55 PM, wrote: >> >>> On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla wrote: >> >> >>>> 1. I see that almost in every function I deal with state, I have e <- get , expression in the begining. I always ending up having to use the state to query for different values. I guess this is OK. >> >> >> El 8 jul 2016, a las 22:07, William Yager escribió: >> >>> For #1, look into using the Lens library's support for the State monad. You can often avoid doing a get, and instead write things like `fees += 5`, which will add 5 to the field in the state called "fees". >> >> Lens is a pretty heavy extra thing for a beginner to have to learn -- you'll do fine with the 'modify' function: >> >> modify :: (s -> s) -> State s () >> >> So instead of writing: >> >> do >> s <- get >> put (s + 5) >> >> You say: >> >> modify (+5) >> >> >> Tom > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Sat Jul 9 17:10:26 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Sat, 9 Jul 2016 10:10:26 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> Message-ID: Say, in the above example, I want to add up values returned by `student_totalFeesOwed` by using foldM operation. Is it possible? For example, here is an expression I have L.foldr (\a b-> (evalState (student_totalFeesOwed a) $ env) + b) 0 [(RowId 1), (RowId 2)] On Sat, Jul 9, 2016 at 9:15 AM, Will Yager wrote: > I did the same thing when I was learning to generalize my understanding of > monads! Very common mistake. > > I'm not sure I understand your question about #3. Can you give an example > using evalState? We'll tell you if you can do it without evalState. > > I suspect you want something like > > "mapM_ addStudentFee students" > > Will > > On Jul 9, 2016, at 00:56, Guru Devanla wrote: > > William/Tom, > > (1) Yes, looking into lens and re-factoring my current experimental > project in lens will be my next iteration. For now, I plan not to spend > time on it. > > (2) Agreed. Not sure how I missed that. > > (3) I see how foldM works now. I missed the point that foldM not only is > a `map` but also does a `sequence` after that. I got stuck earlier, > thinking I will end up with a list of state monads. The sequence steps > executes this monadic action. > > But, how can I do a foldM in a state monad. Say, I need to map over a list > of students and add up all their fees, can I get away not `evalState` > inside the foldM step function? > > Thanks. this is very exciting as I keep simplifying my code! > > Guru > > > > > On Fri, Jul 8, 2016 at 7:55 PM, wrote: > >> >> On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla >> wrote: >> >> >> 1. I see that almost in every function I deal with state, I have e <- >>> get , expression in the begining. I always ending up having to use the >>> state to query for different values. I guess this is OK. >>> >> >> El 8 jul 2016, a las 22:07, William Yager >> escribió: >> >> For #1, look into using the Lens library's support for the State monad. >> You can often avoid doing a get, and instead write things like `fees += 5`, >> which will add 5 to the field in the state called "fees". >> >> >> Lens is a pretty heavy extra thing for a beginner to have to learn -- >> you'll do fine with the 'modify' function: >> >> modify :: (s -> s) -> State s () >> >> So instead of writing: >> >> do >> s <- get >> put (s + 5) >> >> You say: >> >> modify (+5) >> >> >> Tom >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Sat Jul 9 18:25:52 2016 From: will.yager at gmail.com (Will Yager) Date: Sat, 9 Jul 2016 14:25:52 -0400 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> Message-ID: <5BF79662-52DA-4A1F-999F-40D620D4EC35@gmail.com> fees <- mapM totalFeesOwed students let total = sum fees You can use a fold instead of sum if you want. Will > On Jul 9, 2016, at 13:10, Guru Devanla wrote: > > Say, in the above example, I want to add up values returned by `student_totalFeesOwed` by using foldM operation. Is it possible? > > For example, here is an expression I have > > L.foldr (\a b-> (evalState (student_totalFeesOwed a) $ env) + b) 0 [(RowId 1), (RowId 2)] > >> On Sat, Jul 9, 2016 at 9:15 AM, Will Yager wrote: >> I did the same thing when I was learning to generalize my understanding of monads! Very common mistake. >> >> I'm not sure I understand your question about #3. Can you give an example using evalState? We'll tell you if you can do it without evalState. >> >> I suspect you want something like >> >> "mapM_ addStudentFee students" >> >> Will >> >>> On Jul 9, 2016, at 00:56, Guru Devanla wrote: >>> >>> William/Tom, >>> >>> (1) Yes, looking into lens and re-factoring my current experimental project in lens will be my next iteration. For now, I plan not to spend time on it. >>> >>> (2) Agreed. Not sure how I missed that. >>> >>> (3) I see how foldM works now. I missed the point that foldM not only is a `map` but also does a `sequence` after that. I got stuck earlier, thinking I will end up with a list of state monads. The sequence steps executes this monadic action. >>> >>> But, how can I do a foldM in a state monad. Say, I need to map over a list of students and add up all their fees, can I get away not `evalState` inside the foldM step function? >>> >>> Thanks. this is very exciting as I keep simplifying my code! >>> >>> Guru >>> >>> >>> >>> >>>> On Fri, Jul 8, 2016 at 7:55 PM, wrote: >>>> >>>>> On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla wrote: >>>> >>>> >>>>>> 1. I see that almost in every function I deal with state, I have e <- get , expression in the begining. I always ending up having to use the state to query for different values. I guess this is OK. >>>> >>>> >>>> El 8 jul 2016, a las 22:07, William Yager escribió: >>>> >>>>> For #1, look into using the Lens library's support for the State monad. You can often avoid doing a get, and instead write things like `fees += 5`, which will add 5 to the field in the state called "fees". >>>> >>>> Lens is a pretty heavy extra thing for a beginner to have to learn -- you'll do fine with the 'modify' function: >>>> >>>> modify :: (s -> s) -> State s () >>>> >>>> So instead of writing: >>>> >>>> do >>>> s <- get >>>> put (s + 5) >>>> >>>> You say: >>>> >>>> modify (+5) >>>> >>>> >>>> Tom > -------------- next part -------------- An HTML attachment was scrubbed... URL: From conal at conal.net Sat Jul 9 18:59:11 2016 From: conal at conal.net (Conal Elliott) Date: Sat, 9 Jul 2016 11:59:11 -0700 Subject: [Haskell-cafe] Commutative monads vs Applicative functors In-Reply-To: <49a77b7a0805140959v39462883g5950e652f65b5494@mail.gmail.com> References: <62728db30805131806q232cc251g24bf64acadd033af@mail.gmail.com> <49a77b7a0805140959v39462883g5950e652f65b5494@mail.gmail.com> Message-ID: Eight years later, I stumbled across this thread. Here's a cute way to express commutativity of an applicative functor: > forall f. flip (liftA2 f) == liftA2 (flip f) Cuter yet, > flip . liftA2 == liftA2 . flip -- Conal On Wed, May 14, 2008 at 9:59 AM, David Menendez wrote: > On Tue, May 13, 2008 at 9:06 PM, Ronald Guida wrote: > > I have a few questions about commutative monads and applicative functors. > > > > >From what I have read about applicative functors, they are weaker than > > monads because with a monad, I can use the results of a computation to > > select between alternative future computations and their side effects, > > whereas with an applicative functor, I can only select between the > > results of computations, while the structure of those computations and > > their side effects are fixed in advance. > > > > But then there are commutative monads. I'm not exactly sure what a > > commutative monad is, but my understanding is that in a commutative > > monad the order of side effects does not matter. > > > > This leads me to wonder, are commutative monads still stronger than > > applicative functors, or are they equivalent? > > > > And by the way, what exactly is a commutative monad? > > A monad is commutative if the expression "a >>= \x -> b >>= \y -> f x > y" is equivalent to "b >>= \y -> a >>= \x -> f x y". The identity, > state reader, and maybe monads are commutative, for example. > > To put it another way, a monad is commutative if > > liftM2 f a b = liftM2 (flip f) b a > > Since liftA2 generalizes liftM2, we can also say that an applicative > functor is commutative if > > liftA2 f a b = liftA2 (flip f) b a > > Or, put another way, if > > a <*> b = flip ($) <$> b <*> a > > If w is a commutative monoid (that is, if mappend w1 w2 == mappend w2 > w1), then Const w is a commutative applicative functor. > > To summarize: some applicative functors are commutative, some > applicative functors are monads, and the ones that are both are > commutative monads. > > -- > Dave Menendez > > _______________________________________________ > 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 will.yager at gmail.com Sat Jul 9 20:21:21 2016 From: will.yager at gmail.com (Will Yager) Date: Sat, 9 Jul 2016 16:21:21 -0400 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> <5BF79662-52DA-4A1F-999F-40D620D4EC35@gmail.com> Message-ID: I believe you could use foldM (\sum student -> (sum +) <$> totalFeesOwed student) 0 students Will > On Jul 9, 2016, at 15:09, Guru Devanla wrote: > > OK. Thank you. That is what I ended up doing after I understood how mapM worked. But, since I was going through 2 steps, I was wondering if using foldM directly was possible in this case. > > >> On Sat, Jul 9, 2016 at 11:25 AM, Will Yager wrote: >> fees <- mapM totalFeesOwed students >> let total = sum fees >> >> You can use a fold instead of sum if you want. >> >> Will >> >>> On Jul 9, 2016, at 13:10, Guru Devanla wrote: >>> >>> Say, in the above example, I want to add up values returned by `student_totalFeesOwed` by using foldM operation. Is it possible? >>> >>> For example, here is an expression I have >>> >>> L.foldr (\a b-> (evalState (student_totalFeesOwed a) $ env) + b) 0 [(RowId 1), (RowId 2)] >>> >>>> On Sat, Jul 9, 2016 at 9:15 AM, Will Yager wrote: >>>> I did the same thing when I was learning to generalize my understanding of monads! Very common mistake. >>>> >>>> I'm not sure I understand your question about #3. Can you give an example using evalState? We'll tell you if you can do it without evalState. >>>> >>>> I suspect you want something like >>>> >>>> "mapM_ addStudentFee students" >>>> >>>> Will >>>> >>>>> On Jul 9, 2016, at 00:56, Guru Devanla wrote: >>>>> >>>>> William/Tom, >>>>> >>>>> (1) Yes, looking into lens and re-factoring my current experimental project in lens will be my next iteration. For now, I plan not to spend time on it. >>>>> >>>>> (2) Agreed. Not sure how I missed that. >>>>> >>>>> (3) I see how foldM works now. I missed the point that foldM not only is a `map` but also does a `sequence` after that. I got stuck earlier, thinking I will end up with a list of state monads. The sequence steps executes this monadic action. >>>>> >>>>> But, how can I do a foldM in a state monad. Say, I need to map over a list of students and add up all their fees, can I get away not `evalState` inside the foldM step function? >>>>> >>>>> Thanks. this is very exciting as I keep simplifying my code! >>>>> >>>>> Guru >>>>> >>>>> >>>>> >>>>> >>>>>> On Fri, Jul 8, 2016 at 7:55 PM, wrote: >>>>>> >>>>>>> On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla wrote: >>>>>> >>>>>> >>>>>>>> 1. I see that almost in every function I deal with state, I have e <- get , expression in the begining. I always ending up having to use the state to query for different values. I guess this is OK. >>>>>> >>>>>> >>>>>> El 8 jul 2016, a las 22:07, William Yager escribió: >>>>>> >>>>>>> For #1, look into using the Lens library's support for the State monad. You can often avoid doing a get, and instead write things like `fees += 5`, which will add 5 to the field in the state called "fees". >>>>>> >>>>>> Lens is a pretty heavy extra thing for a beginner to have to learn -- you'll do fine with the 'modify' function: >>>>>> >>>>>> modify :: (s -> s) -> State s () >>>>>> >>>>>> So instead of writing: >>>>>> >>>>>> do >>>>>> s <- get >>>>>> put (s + 5) >>>>>> >>>>>> You say: >>>>>> >>>>>> modify (+5) >>>>>> >>>>>> >>>>>> Tom > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gurudev.devanla at gmail.com Sun Jul 10 01:35:08 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Sat, 9 Jul 2016 18:35:08 -0700 Subject: [Haskell-cafe] Haskell Data Structure design In-Reply-To: References: <6274D305-0797-4CF8-BC82-C8F40B317815@gmail.com> <5BF79662-52DA-4A1F-999F-40D620D4EC35@gmail.com> Message-ID: That is a nice trick! Thanks On Jul 9, 2016 1:22 PM, "Will Yager" wrote: > I believe you could use > > foldM (\sum student -> (sum +) <$> totalFeesOwed student) 0 students > > Will > > On Jul 9, 2016, at 15:09, Guru Devanla wrote: > > OK. Thank you. That is what I ended up doing after I understood how mapM > worked. But, since I was going through 2 steps, I was wondering if using > foldM directly was possible in this case. > > > On Sat, Jul 9, 2016 at 11:25 AM, Will Yager wrote: > >> fees <- mapM totalFeesOwed students >> let total = sum fees >> >> You can use a fold instead of sum if you want. >> >> Will >> >> On Jul 9, 2016, at 13:10, Guru Devanla wrote: >> >> Say, in the above example, I want to add up values returned by >> `student_totalFeesOwed` by using foldM operation. Is it possible? >> >> For example, here is an expression I have >> >> L.foldr (\a b-> (evalState (student_totalFeesOwed a) $ env) + b) 0 >> [(RowId 1), (RowId 2)] >> >> On Sat, Jul 9, 2016 at 9:15 AM, Will Yager wrote: >> >>> I did the same thing when I was learning to generalize my understanding >>> of monads! Very common mistake. >>> >>> I'm not sure I understand your question about #3. Can you give an >>> example using evalState? We'll tell you if you can do it without evalState. >>> >>> I suspect you want something like >>> >>> "mapM_ addStudentFee students" >>> >>> Will >>> >>> On Jul 9, 2016, at 00:56, Guru Devanla >>> wrote: >>> >>> William/Tom, >>> >>> (1) Yes, looking into lens and re-factoring my current experimental >>> project in lens will be my next iteration. For now, I plan not to spend >>> time on it. >>> >>> (2) Agreed. Not sure how I missed that. >>> >>> (3) I see how foldM works now. I missed the point that foldM not only >>> is a `map` but also does a `sequence` after that. I got stuck earlier, >>> thinking I will end up with a list of state monads. The sequence steps >>> executes this monadic action. >>> >>> But, how can I do a foldM in a state monad. Say, I need to map over a >>> list of students and add up all their fees, can I get away not `evalState` >>> inside the foldM step function? >>> >>> Thanks. this is very exciting as I keep simplifying my code! >>> >>> Guru >>> >>> >>> >>> >>> On Fri, Jul 8, 2016 at 7:55 PM, wrote: >>> >>>> >>>> On Fri, Jul 8, 2016 at 9:57 PM, Guru Devanla >>> > wrote: >>>> >>>> >>>> 1. I see that almost in every function I deal with state, I have e <- >>>>> get , expression in the begining. I always ending up having to use the >>>>> state to query for different values. I guess this is OK. >>>>> >>>> >>>> El 8 jul 2016, a las 22:07, William Yager >>>> escribió: >>>> >>>> For #1, look into using the Lens library's support for the State monad. >>>> You can often avoid doing a get, and instead write things like `fees += 5`, >>>> which will add 5 to the field in the state called "fees". >>>> >>>> >>>> Lens is a pretty heavy extra thing for a beginner to have to learn -- >>>> you'll do fine with the 'modify' function: >>>> >>>> modify :: (s -> s) -> State s () >>>> >>>> So instead of writing: >>>> >>>> do >>>> s <- get >>>> put (s + 5) >>>> >>>> You say: >>>> >>>> modify (+5) >>>> >>>> >>>> Tom >>>> >>> >>> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hon.lianhung at gmail.com Sun Jul 10 04:27:21 2016 From: hon.lianhung at gmail.com (Lian Hung Hon) Date: Sun, 10 Jul 2016 12:27:21 +0800 Subject: [Haskell-cafe] Natural keys in Haskell data structures In-Reply-To: References: <1467985014-sup-4912@sabre> Message-ID: Dear Edward, Adam, Thanks for the advice, will give them a shot :) Regards, Hon On 9 July 2016 at 07:11, adam vogt wrote: > Hi, > > I think what Edward describes can be achieved by taking a multi index set > library, and using only one index. I searched Hackage and found many > unmaintained options: > > deprecated: tables, HiggsSet > > data-store -- needs dependency version bumps at least > > These are probably usable options: > > ixset, ixset-typed, data-map-multikey > > Based on my search, it seems to me that there are very few maintained > libraries between Data.Map and packages like persistent and groundhog. > Those two libraries provide convenient access to sql databases, which is > probably unnecessarily complex for the original problem. > > Regards, > Adam > > > On Fri, Jul 8, 2016 at 9:40 AM, Edward Z. Yang wrote: > >> Hello Lian, >> >> I recently wrote a module for just this purpose. Here is the approach >> that I (and Edward Kmett) like to take: >> >> 1. Create a type class with an associated type representing elements >> whic have keys: >> >> {-# LANGUAGE TypeFamilies #-} >> {-# LANGUAGE UndecidableInstances #-} >> class Ord (Key a) => HasKey a where >> type Key a :: * >> getKey :: a -> Key a >> >> 2. Write new data structures which utilize this type-class. >> >> import qualified Data.Map as OldMap >> data Map a = OldMap.Map (Key a) a >> insert :: HasKey a => a -> Map a -> Map a >> >> These structures are responsible for maintaining the key-value >> invariants (which can be tricky at times; be careful!) >> >> There are other approaches too; for example you can use a multiparameter >> type class with a functional dependency. "HasKey k a | a -> k" >> >> Unfortunately I am not aware of any standardized naming scheme >> for HasKey/getKey. >> >> Edward >> >> Excerpts from Lian Hung Hon's message of 2016-07-08 09:35:53 -0400: >> > Dear cafe, >> > >> > What is the idiomatic way to "split" records into their natural keys and >> > content in a data structure? For example, given a user: >> > >> > data User = { username :: ByteString, hash :: ByteString, address :: >> Text, >> > ... } >> > >> > Using map, a first choice would be Map ByteString User, but this leads >> to >> > duplication of the username. And it is possible to make mistakes, such >> as >> > >> > insert "John" (User "Jane" ... >> > >> > What does cafe think? Is there any pattern for this? This is probably >> just >> > a small nit in the overall architecture, but I'm curious to know the >> clean >> > way to do it. >> > >> > >> > Regards, >> > Hon >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From martin.drautzburg at web.de Sun Jul 10 09:55:31 2016 From: martin.drautzburg at web.de (martin) Date: Sun, 10 Jul 2016 11:55:31 +0200 Subject: [Haskell-cafe] What's wrong in my Data.Generic.Zipper code? Message-ID: <57821B93.30606@web.de> Hello all, I do not understand why this simple piece of code returns Nothing instead of [1,2,3]. Can anybody help? {-# LANGUAGE BangPatterns,NoMonomorphismRestriction, DeriveDataTypeable #-} import Data.Typeable import Data.Data import Data.Generics.Zipper ex_list1 :: [Int] ex_list1 = [1,2,3] t1 = toZipper ex_list1 -- *Main> getHole t1 -- Nothing From martijn at oblomov.com Sun Jul 10 13:17:13 2016 From: martijn at oblomov.com (Martijn Schrage) Date: Sun, 10 Jul 2016 06:17:13 -0700 Subject: [Haskell-cafe] What's wrong in my Data.Generic.Zipper code? In-Reply-To: <57821B93.30606@web.de> References: <57821B93.30606@web.de> Message-ID: Hi Martin, Ghci defaults the type of 'getHole t1' to 'Maybe ()'. You can see this happening if you enable warnings in ghci with ':set -Wall'. Providing the correct type signature gives you the answer you're expecting: *Main> getHole t1 :: Maybe [Int] Just [1,2,3] Cheers, Martijn On 10 juli 2016 at 11:55:48, martin (martin.drautzburg at web.de) wrote: Hello all, I do not understand why this simple piece of code returns Nothing instead of [1,2,3]. Can anybody help? {-# LANGUAGE BangPatterns,NoMonomorphismRestriction, DeriveDataTypeable #-} import Data.Typeable import Data.Data import Data.Generics.Zipper ex_list1 :: [Int] ex_list1 = [1,2,3] t1 = toZipper ex_list1 -- *Main> getHole t1 -- Nothing _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ozgurakgun at gmail.com Sun Jul 10 14:39:26 2016 From: ozgurakgun at gmail.com (=?UTF-8?B?w5Z6Z8O8ciBBa2fDvG4=?=) Date: Sun, 10 Jul 2016 15:39:26 +0100 Subject: [Haskell-cafe] Strange error with cabal install on windows: In-Reply-To: References: Message-ID: 2016-07-08 20:27 GMT+03:00 Anton Kholomiov : > For those who wants to help. Pavel discovered the cause of the problem for > me. I've got too many modules in my package and it causes the error. The > length of the command line strings is limited for windows so if you have > too many modules the final build command can not list them all. I need to > regroup my modules I guess.. > Just out of curiosity, how many modules are too many for Windows? -- Özgür Akgün -------------- next part -------------- An HTML attachment was scrubbed... URL: From steve at fenestra.com Sun Jul 10 15:20:01 2016 From: steve at fenestra.com (Steve Schafer) Date: Sun, 10 Jul 2016 10:20:01 -0500 Subject: [Haskell-cafe] Strange error with cabal install on windows: In-Reply-To: References: Message-ID: On Sun, 10 Jul 2016 15:39:26 +0100, you wrote: >Just out of curiosity, how many modules are too many for Windows? It depends on the version of Windows you're running. Pre-XP, the command line is limited to 2047 characters. Post-XP, the limit is 8191 characters. There are also limits with regard to the nesting of directories. Although the Unicode versions of the Windows APi functions support paths up to 32,767 characters long, many of the command line processor functions give up after about 260 characters. -Steve Schafer -- This message has been scanned for viruses and dangerous content by MailScanner, and is believed to be clean. From ch.howard at zoho.com Sun Jul 10 15:41:31 2016 From: ch.howard at zoho.com (Christopher Howard) Date: Sun, 10 Jul 2016 07:41:31 -0800 Subject: [Haskell-cafe] Memory Management and Lists Message-ID: <57826CAB.50302@zoho.com> Hi, short version of the question: when elements are 'drop'ped from a list, when is the memory for those elements released? And is there some way to control that? Longer version: I have this situation where I've got a State monad carrying a Data.Matrix, and I... 1) generate in infinite list of monadic operations with (repeat mf) where mf is a monadic function. 2) 'sequence' (from Control.Monad) to get a monad containing the infinite list of all states (i.e., a list of Matrices). 3) evalState(T) to extract the list 4) extract the nth state with (head (drop (n-1))) I like this approach. However, there seems to be a memory management issue: a Matrix itself should only be, I'm guessing, somewhere around 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. Maybe I'm generating list elements (Matrices) a lot faster than memory management is releasing them...? -- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu). From michael at schmong.org Sun Jul 10 16:22:10 2016 From: michael at schmong.org (Michael Litchard) Date: Sun, 10 Jul 2016 09:22:10 -0700 Subject: [Haskell-cafe] Links on https://hackage.haskell.org/package/Cabal-1.24.0.0/docs/Language-Haskell-Extension.html are broken. How can I help? Message-ID: Links to documentation are broken. I would be happy to fix. But how? https://hackage.haskell.org/package/Cabal-1.24.0.0/docs/Language-Haskell-Extension.html -------------- next part -------------- An HTML attachment was scrubbed... URL: From fa-ml at ariis.it Sun Jul 10 16:28:02 2016 From: fa-ml at ariis.it (Francesco Ariis) Date: Sun, 10 Jul 2016 18:28:02 +0200 Subject: [Haskell-cafe] Links on https://hackage.haskell.org/package/Cabal-1.24.0.0/docs/Language-Haskell-Extension.html are broken. How can I help? In-Reply-To: References: Message-ID: <20160710162802.GA5271@casa.casa> On Sun, Jul 10, 2016 at 09:22:10AM -0700, Michael Litchard wrote: > Links to documentation are broken. I would be happy to fix. But how? > > https://hackage.haskell.org/package/Cabal-1.24.0.0/docs/Language-Haskell-Extension.html Nice find. I would say a patch in cabal-devel at haskell.org or (if you have a github account), directly a pull request here [1]. [1] https://github.com/haskell/cabal/ From will.yager at gmail.com Sun Jul 10 17:26:03 2016 From: will.yager at gmail.com (Will Yager) Date: Sun, 10 Jul 2016 13:26:03 -0400 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <57826CAB.50302@zoho.com> References: <57826CAB.50302@zoho.com> Message-ID: I'm not an expert here, but the GC should not allow that to happen if you were truly no longer using the elements. Most likely you have a dangling reference to the list head or something. Please post your code. Will > On Jul 10, 2016, at 11:41, Christopher Howard wrote: > > Hi, short version of the question: when elements are 'drop'ped from a > list, when is the memory for those elements released? And is there some > way to control that? > > Longer version: I have this situation where I've got a State monad > carrying a Data.Matrix, and I... > > 1) generate in infinite list of monadic operations with (repeat mf) > where mf is a monadic function. > 2) 'sequence' (from Control.Monad) to get a monad containing the > infinite list of all states (i.e., a list of Matrices). > 3) evalState(T) to extract the list > 4) extract the nth state with (head (drop (n-1))) > > I like this approach. However, there seems to be a memory management > issue: a Matrix itself should only be, I'm guessing, somewhere around > 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. > Maybe I'm generating list elements (Matrices) a lot faster than memory > management is releasing them...? > > -- > http://qlfiles.net > To protect my privacy, please use PGP encryption. It's free and easy > to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From martin.drautzburg at web.de Sun Jul 10 18:03:48 2016 From: martin.drautzburg at web.de (martin) Date: Sun, 10 Jul 2016 20:03:48 +0200 Subject: [Haskell-cafe] What's wrong in my Data.Generic.Zipper code? In-Reply-To: References: <57821B93.30606@web.de> Message-ID: <57828E04.4020407@web.de> Am 07/10/2016 um 03:17 PM schrieb Martijn Schrage: > Hi Martin, > > Ghci defaults the type of 'getHole t1' to 'Maybe ()'. You can see this happening if you enable warnings in ghci with > ':set -Wall'. Providing the correct type signature gives you the answer you're expecting: > > *Main> getHole t1 :: Maybe [Int] > Just [1,2,3] I understand, thanks. I tried a generic Zipper with a pair and noticed that going down gives me the second component. This does make some sense, but I am still having trouble to anticipate what up, down, left and right do when the the datatype is more complicated and not a tree. E.g. this one gives me trouble: import qualified Data.Sequence as S data Items lbl = Items (S.Seq (lbl, Items lbl)) deriving (Eq, Show, Typeable, Data) Is there an easy way to understinfing those moves? From aeyakovenko at gmail.com Sun Jul 10 18:23:11 2016 From: aeyakovenko at gmail.com (Anatoly Yakovenko) Date: Sun, 10 Jul 2016 18:23:11 +0000 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> Message-ID: Haskell is lazy evaluated. So data isn't "dropped" until all the thunks that use it are evaluated. Play around with foldl and foldl'. The strict evaluation of the accumulator in foldl' prevents a large thunk from forming and eating up all the memory On Sun, Jul 10, 2016 at 10:26 AM Will Yager wrote: > I'm not an expert here, but the GC should not allow that to happen if you > were truly no longer using the elements. Most likely you have a dangling > reference to the list head or something. Please post your code. > > Will > > > On Jul 10, 2016, at 11:41, Christopher Howard > wrote: > > > > Hi, short version of the question: when elements are 'drop'ped from a > > list, when is the memory for those elements released? And is there some > > way to control that? > > > > Longer version: I have this situation where I've got a State monad > > carrying a Data.Matrix, and I... > > > > 1) generate in infinite list of monadic operations with (repeat mf) > > where mf is a monadic function. > > 2) 'sequence' (from Control.Monad) to get a monad containing the > > infinite list of all states (i.e., a list of Matrices). > > 3) evalState(T) to extract the list > > 4) extract the nth state with (head (drop (n-1))) > > > > I like this approach. However, there seems to be a memory management > > issue: a Matrix itself should only be, I'm guessing, somewhere around > > 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. > > Maybe I'm generating list elements (Matrices) a lot faster than memory > > management is releasing them...? > > > > -- > > http://qlfiles.net > > To protect my privacy, please use PGP encryption. It's free and easy > > to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Jul 10 18:30:04 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 10 Jul 2016 19:30:04 +0100 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <57826CAB.50302@zoho.com> References: <57826CAB.50302@zoho.com> Message-ID: <20160710183004.GF3616@weber> On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: > issue: a Matrix itself should only be, I'm guessing, somewhere around > 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. > Maybe I'm generating list elements (Matrices) a lot faster than memory > management is releasing them...? You have almost certainly got a space leak. Can you post your code? From kc1956 at gmail.com Sun Jul 10 18:44:46 2016 From: kc1956 at gmail.com (KC) Date: Sun, 10 Jul 2016 11:44:46 -0700 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell Message-ID: Is the #functional programming paradigm antithetical to efficient strings? #Haskell -- -- Sent from an expensive device which will be obsolete in a few months! :D Casey -------------- next part -------------- An HTML attachment was scrubbed... URL: From miguelimo38 at yandex.ru Sun Jul 10 18:56:18 2016 From: miguelimo38 at yandex.ru (MigMit) Date: Sun, 10 Jul 2016 20:56:18 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: No it's #not. > On 10 Jul 2016, at 20:44, KC wrote: > > Is the #functional programming paradigm antithetical to efficient strings? #Haskell > > -- > -- > > Sent from an expensive device which will be obsolete in a few months! :D > > Casey > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From petr.mvd at gmail.com Sun Jul 10 20:27:40 2016 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Sun, 10 Jul 2016 20:27:40 +0000 Subject: [Haskell-cafe] Practical use of Stream's monad instance? Message-ID: Hi, we've been debating the usefulness of Monad instances for Stream [2] or homogeneous tuples (fixed-length vectors). The Applicative implementation for them is simply zipping, very useful indeed. The "join" of their Monad instances takes the diagonal of a 2-dimensional plane (finite for tuples, infinite for Stream). (See also [1].) The question is, are such monad instances used in the wild? Are they actually useful or interesting for anything? [1] https://mail.haskell.org/pipermail/haskell-cafe/2009-April/thread.html#59079 [2] https://hackage.haskell.org/package/Stream-0.4.7.2/docs/Data-Stream.html Thanks Petr -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Sun Jul 10 20:57:23 2016 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Sun, 10 Jul 2016 22:57:23 +0200 (CEST) Subject: [Haskell-cafe] Commutative monads vs Applicative functors Message-ID: Anders Kock has a nice paper on commutative monads [1]. He relates commutativity to the Fubini theorem, because that is what commutativity is for the monad of meaures: You can change the order in integration by parts. He works in a symmetric monoidal closed category, so Hask works, too. It is the sort of category theory paper where you can go along the paper and implement most of it in Haskell. In particular, he mentions that MonadPlus has an alternative set of laws: A monad m is a MonadPlus when there are isomorphisms iso0 :: () -> m Void iso2 :: (m a,m b) -> m (Either a b) Indeed, let mzero = liftM absurd (iso0 ()) mplus x y = liftM codiagonal (iso2 (x,y)) where codiagonal (Left x) = x codiagonal (Right y) = y Conversely, let iso0 () = mzero iso2 (x,y) = (liftM Left x) `mplus` (liftM Right y) Then Kock shows that the MonadPlus operations are automatically Eilenberg-Moore algebra homomorphisms, which is the abstract way of saying that addition distributes over multiplication. On a related note, I wonder whether the following is true: Let m be a monad and let r be an object which is an m-algebra. Think of m as the free semigroup monad. Now consider the continuation monad type T x = (x -> r) -> r Observe that (x -> r) inherits the m-algebra structure of r. Let T' x be the subset of maps in T x which are m-linear. Is T' a monad, too? Can this me made concrete in a Haskell function? Regards, Olaf [1] @article{kock12, author="Kock, Anders", title="Commutative monads as a theory of distributions", journal="Theory and Applications of Categories", volume=26, number=4, pages="97-131", year=2012, url="http://www.tac.mta.ca/tac/volumes/26/4/26-04.pdf" } From monnier at iro.umontreal.ca Sun Jul 10 21:20:13 2016 From: monnier at iro.umontreal.ca (Stefan Monnier) Date: Sun, 10 Jul 2016 17:20:13 -0400 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell References: Message-ID: > Is the #functional programming paradigm antithetical to efficient strings? Why would it be? Most string operations in non-low-level languages are naturally functional (e.g. my local Emacs build makes strings immutable and 99% of Elisp packages don't even notice the difference). Stefan From martijn at oblomov.com Sun Jul 10 21:37:38 2016 From: martijn at oblomov.com (Martijn Schrage) Date: Sun, 10 Jul 2016 17:37:38 -0400 Subject: [Haskell-cafe] What's wrong in my Data.Generic.Zipper code? In-Reply-To: <57828E04.4020407@web.de> References: <57821B93.30606@web.de> <57828E04.4020407@web.de> Message-ID: On 10 juli 2016 at 20:03:57, martin (martin.drautzburg at web.de) wrote: Am 07/10/2016 um 03:17 PM schrieb Martijn Schrage: > Hi Martin, > > Ghci defaults the type of 'getHole t1' to 'Maybe ()'. You can see this happening if you enable warnings in ghci with > ':set -Wall'. Providing the correct type signature gives you the answer you're expecting: > > *Main> getHole t1 :: Maybe [Int] > Just [1,2,3] I understand, thanks. I tried a generic Zipper with a pair and noticed that going down gives me the second component. This does make some sense, but I am still having trouble to anticipate what up, down, left and right do when the the datatype is more complicated and not a tree. E.g. this one gives me trouble: import qualified Data.Sequence as S To understand the navigation, just draw your values as trees, with the constructor on one level and the children below. For example, a list [1,2] becomes: (:) / \ 1 (:) / \ 2 [] And a tuple (1,2) becomes: (,) / \ 1 2 Also note that down not only moves a level downward, but also to the rightmost child (down' moves to the leftmost child instead). I'm not sure how useful it is to use a zipper on a Seq (which, as you can see in the source, is still just a tree, like all data types,) as the implementation uses a balanced FingerTree which is kept abstract. But as it turns out, the Seq Data instance follows the right-associative view pattern, so if you wish you could navigate similar to lists (down for the tail, and down' or down followed by left for the head). Cheers, Martijn data Items lbl = Items (S.Seq (lbl, Items lbl)) deriving (Eq, Show, Typeable, Data) Is there an easy way to understinfing those moves? -------------- next part -------------- An HTML attachment was scrubbed... URL: From cma at bitemyapp.com Sun Jul 10 22:56:33 2016 From: cma at bitemyapp.com (Christopher Allen) Date: Sun, 10 Jul 2016 17:56:33 -0500 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: Even if it was, you could use a mutable container of runes if there was something that didn't really gel with the algorithm you wanted. IME, the slicing based API of ByteString and Vector has been great when I've needed efficient string code. http://hackage.haskell.org/package/bytestring-trie is a great library if you're doing stuff like dictionaries of strings. There's not really any limitations in Haskell as to what you can do, it just doesn't let you lie about what it is you're up to. On Sun, Jul 10, 2016 at 1:44 PM, KC wrote: > Is the #functional programming paradigm antithetical to efficient strings? > #Haskell > > -- > -- > > Sent from an expensive device which will be obsolete in a few months! :D > > Casey > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Chris Allen Currently working on http://haskellbook.com From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Jul 10 22:58:33 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 10 Jul 2016 23:58:33 +0100 Subject: [Haskell-cafe] Practical use of Stream's monad instance? In-Reply-To: References: Message-ID: <20160710225833.GC8616@weber> On Sun, Jul 10, 2016 at 08:27:40PM +0000, Petr Pudlák wrote: > we've been debating the usefulness of Monad instances for Stream [2] or > homogeneous tuples (fixed-length vectors). The Applicative implementation > for them is simply zipping, very useful indeed. The "join" of their Monad > instances takes the diagonal of a 2-dimensional plane (finite for tuples, > infinite for Stream). (See also [1].) > > The question is, are such monad instances used in the wild? Are they > actually useful or interesting for anything? They are all equivalent to `Reader a`, for some choice of `a`. From ok at cs.otago.ac.nz Mon Jul 11 02:06:32 2016 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Mon, 11 Jul 2016 14:06:32 +1200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: <7eaad85c-a2ad-5650-2f80-aef930d801c7@cs.otago.ac.nz> On 11/07/16 6:44 AM, KC wrote: > > Is the #functional programming paradigm antithetical to efficient > strings? #Haskell > What on earth does "efficient strings" mean? To the extent that I can extract any meaning from that, the answer is "no, obviously not". The functional programming paradigm includes languages like ML, which has always had packed-array-of-byte strings and corresponding contiguous-slice-of-shared-packed-array-of-byte substrings, and languages where the default implementation is a singly-linked list with one cell per code. What is "efficient" is a matter of what you are *doing* with the strings. An important consideration these days is that the old idea of a mutable array with one element per character (which was never the only way to implement strings) is a very poor fit for Unicode. From bog at khumba.net Mon Jul 11 02:55:57 2016 From: bog at khumba.net (Bryan Gardiner) Date: Sun, 10 Jul 2016 19:55:57 -0700 Subject: [Haskell-cafe] ANN: qtah-0.1.0 Message-ID: <20160710195557.32ee566f@khumba.net> Hello all, I'm happy to announce the first Hackage-ready release of Qtah, Qt bindings for Haskell. I announced Qtah earlier this year, but a lot of work was needed to get it to the point where you can just "cabal install" it. That work has now been done, so I invite you to install qtah-qt5 or qtah-examples[1] (currently just the Qt notepad example), and check out: http://khumba.net/projects/qtah https://gitlab.com/khumba/qtah As a small demonstration, I have a good portion of Goatee ported (board rendering clearly missing): http://khumba.net/tmp/20160710-goatee-qt.png However, there is still lots of the Qt API left to cover. Thanks to ezyang for help working with some Cabal internals. Cheers, Bryan [1] cabal install --enable-executable-dynamic qtah-examples -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 801 bytes Desc: OpenPGP digital signature URL: From kwangyul.seo at gmail.com Mon Jul 11 03:35:14 2016 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Mon, 11 Jul 2016 12:35:14 +0900 Subject: [Haskell-cafe] ANN: enchant-0.1.0.0 Message-ID: Hello, I'm happy to announce the first release of enchant, binding for the Enchant library. https://hackage.haskell.org/package/enchant-0.1.0.0 https://github.com/kseo/enchant What is Enchant? (from http://www.abisource.com/projects/enchant/) On the surface, Enchant appears to be a generic spell checking library. You > can request dictionaries from it, ask if a word is correctly spelled, get > corrections for a misspelled word, etc... > > Beneath the surface, Enchant is a whole lot more - and less - than that. > You'll see that Enchant isn't really a spell checking library at all. > > "What's that?" you ask. Well, Enchant doesn't try to do any of the work > itself. It's lazy, and requires backends to do most of its dirty work. > Looking closer, you'll see the Enchant is more-or-less a fancy wrapper > around the dlopen() system call. Enchant steps in to provide uniformity and > conformity on top of these libraries, and implement certain features that > may be lacking in any individual provider library. Everything should "just > work" for any and every definition of "just working." Thanks, Kwang Yul Seo -------------- next part -------------- An HTML attachment was scrubbed... URL: From magicloud.magiclouds at gmail.com Mon Jul 11 07:49:20 2016 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Mon, 11 Jul 2016 07:49:20 +0000 Subject: [Haskell-cafe] Cannot install any packages after upgrading to GHC 8.0.1 Message-ID: Hi, I update my GHC to 8.0.1 and failed to install any packages since then. If I use cabal, I got 'installed package info from too old version of Cabal (key field does not match id field)' for every package. If I use Setup.hs, I got 'Configuring Cabal-1.24.0.0... Setup.hs: ghc-pkg dump failed'. What should I do? Googling did not get me an answer. -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Mon Jul 11 08:48:26 2016 From: michael at snoyman.com (Michael Snoyman) Date: Mon, 11 Jul 2016 11:48:26 +0300 Subject: [Haskell-cafe] Cannot install any packages after upgrading to GHC 8.0.1 In-Reply-To: References: Message-ID: I'd guess that you've got an older version of cabal-install on your system that doesn't support GHC 8. You can test that with `cabal --version` and see if it's 1.24 or later. My recommendation would be to try out Stack. There are new easier installation instructions at https://haskell-lang.org/get-started, and recent Stackage Nightly snapshots are all using GHC 8.0.1. On Mon, Jul 11, 2016 at 10:49 AM, Magicloud Magiclouds < magicloud.magiclouds at gmail.com> wrote: > Hi, > I update my GHC to 8.0.1 and failed to install any packages since then. > If I use cabal, I got 'installed package info from too old version of > Cabal (key field does not match id field)' for every package. > If I use Setup.hs, I got 'Configuring Cabal-1.24.0.0... > Setup.hs: ghc-pkg dump failed'. > What should I do? Googling did not get me an answer. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dsf at seereason.com Mon Jul 11 12:54:48 2016 From: dsf at seereason.com (David Fox) Date: Mon, 11 Jul 2016 05:54:48 -0700 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On Sun, Jul 10, 2016 at 11:44 AM, KC wrote: > Is the #functional programming paradigm antithetical to efficient strings? > #Haskell > ​I can certainly see how it might seem so. Our main string representation​ uses about 10 times more memory than seems necessary, and is relatively fast, though probably not compared to C. Recently I spent some time looking into how to reduce this memory overhead, and I modified the pretty library (https://github.com/ddssff/pretty/tree/textdetails) so it could use any type that was an instance of ListLike and StringLike ( https://github.com/JohnLato/listlike). Then I tried the UnitLargeDoc test with several different data types. This just concatenates a list of ten million "Hello" strings. Using String this happens in about 5 seconds. Using strict or lazy Text it immediately blew the stack. When I increased the stack size to over 1GB it took minutes to complete. When I used the Data.Text.Lazy.Builder type instead it took about 30 seconds to complete. Results with utf8 encoded ByteStrings were siimilar. When I mentioned some of this, I was told "different data structures for different purposes", which sort of makes sense, but honestly if Haskell is a language where you have to sit down and choose a representation every time you want to build some text, I get a bit discouraged. So is functional programming antithetical to efficient strings? In theory maybe not, but I would love to see some hard evidence. -------------- next part -------------- An HTML attachment was scrubbed... URL: From i.caught.air at gmail.com Mon Jul 11 13:33:16 2016 From: i.caught.air at gmail.com (Alex Belanger) Date: Mon, 11 Jul 2016 09:33:16 -0400 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: That's not just about Haskell, it's C.S. in general. You're always going to make space and time tradeoffs. Funny how the same constraints appear in physics; I wonder if it is trying to tell us something... - nitrix On Jul 11, 2016 8:54 AM, "David Fox" wrote: On Sun, Jul 10, 2016 at 11:44 AM, KC wrote: > Is the #functional programming paradigm antithetical to efficient strings? > #Haskell > ​I can certainly see how it might seem so. Our main string representation​ uses about 10 times more memory than seems necessary, and is relatively fast, though probably not compared to C. Recently I spent some time looking into how to reduce this memory overhead, and I modified the pretty library (https://github.com/ddssff/pretty/tree/textdetails) so it could use any type that was an instance of ListLike and StringLike ( https://github.com/JohnLato/listlike). Then I tried the UnitLargeDoc test with several different data types. This just concatenates a list of ten million "Hello" strings. Using String this happens in about 5 seconds. Using strict or lazy Text it immediately blew the stack. When I increased the stack size to over 1GB it took minutes to complete. When I used the Data.Text.Lazy.Builder type instead it took about 30 seconds to complete. Results with utf8 encoded ByteStrings were siimilar. When I mentioned some of this, I was told "different data structures for different purposes", which sort of makes sense, but honestly if Haskell is a language where you have to sit down and choose a representation every time you want to build some text, I get a bit discouraged. So is functional programming antithetical to efficient strings? In theory maybe not, but I would love to see some hard evidence. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From stephen.tetley at gmail.com Mon Jul 11 14:28:01 2016 From: stephen.tetley at gmail.com (Stephen Tetley) Date: Mon, 11 Jul 2016 15:28:01 +0100 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On 11 July 2016 at 13:54, David Fox wrote: > > When I mentioned some of this, I was told "different data structures for > different purposes", which sort of makes sense, but honestly if Haskell is a > language where you have to sit down and choose a representation every time > you want to build some text, I get a bit discouraged. Don't C# and Java have StringBuilder classes (different to their regular String types) for this as well? Maybe imperative OO is also antithetical to efficient strings... From gershomb at gmail.com Mon Jul 11 14:55:34 2016 From: gershomb at gmail.com (Gershom B) Date: Mon, 11 Jul 2016 10:55:34 -0400 Subject: [Haskell-cafe] Cannot install any packages after upgrading to GHC 8.0.1 In-Reply-To: References: Message-ID: On July 11, 2016 at 3:49:46 AM, Magicloud Magiclouds (magicloud.magiclouds at gmail.com) wrote: > Hi, > I update my GHC to 8.0.1 and failed to install any packages since then. > If I use cabal, I got 'installed package info from too old version of Cabal > (key field does not match id field)' for every package. > If I use Setup.hs, I got 'Configuring Cabal-1.24.0.0... > Setup.hs: ghc-pkg dump failed'. > What should I do? Googling did not get me an answer. The former error can occur if your cabal binary is too old. You can download a newer cabal binary from: https://www.haskell.org/cabal/download.html If the latter error persists, then perhaps your ghc-pkg was not updated along with your ghc? —gershom From ch.howard at zoho.com Mon Jul 11 15:01:24 2016 From: ch.howard at zoho.com (Christopher Howard) Date: Mon, 11 Jul 2016 07:01:24 -0800 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <20160710183004.GF3616@weber> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> Message-ID: <5783B4C4.70902@zoho.com> -- I'm a bit embarrassed of this code because I haven't yet optimized -- the 'stamp' algorithm for reduced number of matrix operations. But -- even in this state I should think the memory requirements shouldn't -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, -- etc. are being preserved in memory unnecessarily. -- Monad Stack type StateReader s c a = StateT s (Reader c) a evalStateReader m s c = (runReader (evalStateT m s)) c -- Helper function type Point = (Float, Float) type Metric = Point -> Point -> Float euclidean :: Metric euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) -- monadic function. haven't had chance yet to optimize algorithm to -- reduce number of matrix operations stamp = do radius <- ask (oMatrix, walk) <- get (wX, wY) <- (return . head) walk let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) (\(x, y) -> let (x', y') = (fromIntegral x, fromIntegral y) in if euclidean (x', y') (wX, wY) > radius then getElem x y oMatrix else getElem x y oMatrix + 1) in put (nMatrix, tail walk) >> get -- sequences and gathers results as list stampingStates initMx radius walk = map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius -- Some quick experimentation code. h is the list h = stampingStates initMx radius walk' where initMx = zero 250 250 radius = 40 walk' = walk 40 (125, 125) (mkStdGen 31415) -- get 2001st Matrix and convert to Gloss Picture, employing -- some color interpretation code intensityG = let mx = head (drop 2000 h) in toImage mx (lightnessInt 272 (minMax mx)) On 07/10/2016 10:30 AM, Tom Ellis wrote: > On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: >> issue: a Matrix itself should only be, I'm guessing, somewhere around >> 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. >> Maybe I'm generating list elements (Matrices) a lot faster than memory >> management is releasing them...? > > You have almost certainly got a space leak. Can you post your code? > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu). From ezyang at mit.edu Mon Jul 11 15:11:34 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Mon, 11 Jul 2016 11:11:34 -0400 Subject: [Haskell-cafe] Cannot install any packages after upgrading to GHC 8.0.1 In-Reply-To: References: Message-ID: <1468249841-sup-771@sabre> Yes, you need to upgrade your cabal-install. If you still have an old version of GHC around, you can upgrade using: cabal update cabal install -w /path/to/old/ghc cabal-install Edward Excerpts from Magicloud Magiclouds's message of 2016-07-11 03:49:20 -0400: > Hi, > I update my GHC to 8.0.1 and failed to install any packages since then. > If I use cabal, I got 'installed package info from too old version of Cabal > (key field does not match id field)' for every package. > If I use Setup.hs, I got 'Configuring Cabal-1.24.0.0... > Setup.hs: ghc-pkg dump failed'. > What should I do? Googling did not get me an answer. From dsf at seereason.com Mon Jul 11 15:33:57 2016 From: dsf at seereason.com (David Fox) Date: Mon, 11 Jul 2016 08:33:57 -0700 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On Mon, Jul 11, 2016 at 7:28 AM, Stephen Tetley wrote: > On 11 July 2016 at 13:54, David Fox wrote: > > > > > When I mentioned some of this, I was told "different data structures for > > different purposes", which sort of makes sense, but honestly if Haskell > is a > > language where you have to sit down and choose a representation every > time > > you want to build some text, I get a bit discouraged. > > Don't C# and Java have StringBuilder classes (different to their > regular String types) for this as well? > > Maybe imperative OO is also antithetical to efficient strings... > ​Probably.​ -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Mon Jul 11 17:35:32 2016 From: spam at scientician.net (Bardur Arantsson) Date: Mon, 11 Jul 2016 19:35:32 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On 07/11/2016 04:28 PM, Stephen Tetley wrote: > On 11 July 2016 at 13:54, David Fox wrote: > >> >> When I mentioned some of this, I was told "different data structures for >> different purposes", which sort of makes sense, but honestly if Haskell is a >> language where you have to sit down and choose a representation every time >> you want to build some text, I get a bit discouraged. > > Don't C# and Java have StringBuilder classes (different to their > regular String types) for this as well? Yes, they do. If you just naively do String s = ""; for (int i = 0; i < 1000000; i++) { s = s + "hello"; } in Java you'll also get terrible performance (O(n^2)) as opposed to the equivalent code using StringBuilder which would be O(n). This does not change if you use e.g. Text/ByteString/Vector in Haskell. In Haskell, I could certainly imagine List[Char] being more performant than copying huge chunks of memory over and over... even though List traversal *is* generally slow. (Of course the actual performance depends on lots and lots of specifics.) > > Maybe imperative OO is also antithetical to efficient strings... Bad algorithms and data structures are antithetical to efficient strings :). Regards, From david.feuer at gmail.com Mon Jul 11 19:56:23 2016 From: david.feuer at gmail.com (David Feuer) Date: Mon, 11 Jul 2016 15:56:23 -0400 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <5783B4C4.70902@zoho.com> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> Message-ID: Please repost your code, giving a type signature for each top-level binding. Without them, the code is very difficult to follow. I also strongly recommend using a newtype for your custom monad. Something like this: {-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, StandaloneDeriving, ... #-} newtype StateReader s c a = SR {runSR :: StateT s (Reader c) a} deriving (Functor, Applicative, Monad) deriving instance MonadReader c (StateReader s c) deriving instance MonadState s (StateReader s c) On Jul 11, 2016 11:07 AM, "Christopher Howard" wrote: > -- I'm a bit embarrassed of this code because I haven't yet optimized > -- the 'stamp' algorithm for reduced number of matrix operations. But > -- even in this state I should think the memory requirements shouldn't > -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, > -- etc. are being preserved in memory unnecessarily. > > -- Monad Stack > > type StateReader s c a = StateT s (Reader c) a > > evalStateReader m s c = (runReader (evalStateT m s)) c > > -- Helper function > > type Point = (Float, Float) > type Metric = Point -> Point -> Float > > euclidean :: Metric > euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) > > -- monadic function. haven't had chance yet to optimize algorithm to > -- reduce number of matrix operations > > stamp = do radius <- ask > (oMatrix, walk) <- get > (wX, wY) <- (return . head) walk > let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) > (\(x, y) -> let (x', y') = (fromIntegral x, fromIntegral > y) > in if euclidean (x', y') (wX, wY) > radius > then getElem x y oMatrix > else getElem x y oMatrix + 1) > in put (nMatrix, tail walk) >> get > > > > -- sequences and gathers results as list > > stampingStates initMx radius walk = > map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius > > > -- Some quick experimentation code. h is the list > > h = stampingStates initMx radius walk' > where initMx = zero 250 250 > radius = 40 > walk' = walk 40 (125, 125) (mkStdGen 31415) > > -- get 2001st Matrix and convert to Gloss Picture, employing > -- some color interpretation code > > intensityG = let mx = head (drop 2000 h) > in toImage mx (lightnessInt 272 (minMax mx)) > > > On 07/10/2016 10:30 AM, Tom Ellis wrote: > > On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: > >> issue: a Matrix itself should only be, I'm guessing, somewhere around > >> 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. > >> Maybe I'm generating list elements (Matrices) a lot faster than memory > >> management is releasing them...? > > > > You have almost certainly got a space leak. Can you post your code? > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > -- > http://qlfiles.net > To protect my privacy, please use PGP encryption. It's free and easy > to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Mon Jul 11 20:07:06 2016 From: david.feuer at gmail.com (David Feuer) Date: Mon, 11 Jul 2016 16:07:06 -0400 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: Edward Kmett did some work with things he called "ropes" https://hackage.haskell.org/package/rope that can be efficient for some byte string manipulations. There may be other good choices. On Jul 11, 2016 1:42 PM, "Bardur Arantsson" wrote: > On 07/11/2016 04:28 PM, Stephen Tetley wrote: > > On 11 July 2016 at 13:54, David Fox wrote: > > > >> > >> When I mentioned some of this, I was told "different data structures for > >> different purposes", which sort of makes sense, but honestly if Haskell > is a > >> language where you have to sit down and choose a representation every > time > >> you want to build some text, I get a bit discouraged. > > > > Don't C# and Java have StringBuilder classes (different to their > > regular String types) for this as well? > > Yes, they do. > > If you just naively do > > String s = ""; > for (int i = 0; i < 1000000; i++) { > s = s + "hello"; > } > > in Java you'll also get terrible performance (O(n^2)) as opposed to the > equivalent code using StringBuilder which would be O(n). This does not > change if you use e.g. Text/ByteString/Vector in Haskell. > > In Haskell, I could certainly imagine List[Char] being more performant > than copying huge chunks of memory over and over... even though List > traversal *is* generally slow. > > (Of course the actual performance depends on lots and lots of specifics.) > > > > > Maybe imperative OO is also antithetical to efficient strings... > > Bad algorithms and data structures are antithetical to efficient strings > :). > > Regards, > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From olf at aatal-apotheke.de Mon Jul 11 20:10:43 2016 From: olf at aatal-apotheke.de (Olaf Klinke) Date: Mon, 11 Jul 2016 22:10:43 +0200 (CEST) Subject: [Haskell-cafe] Practical use of Stream's monad instance? Message-ID: As someone else on this list whose name I don't recall put it, there is no choice on whether to make Stream a monad or not. It simply _is_ a monad. Anyone with some CS education hearing 'diagonal of inifinite list of infinite lists' should immediately think of Georg Cantor. import Data.Stream import Data.Ratio type Real = Stream Rational -- approximate a real number by an ascending stream -- of lower bounds. supremum :: Stream Real -> Real supremum = join -- If a stream of reals is index-wise ascending, -- the monad instance for Stream computes its supremum. -- Use this e.g. to compute any mathematical quantity -- defined as a supremum. -- Olaf From spam at scientician.net Mon Jul 11 21:08:59 2016 From: spam at scientician.net (Bardur Arantsson) Date: Mon, 11 Jul 2016 23:08:59 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On 07/11/2016 10:07 PM, David Feuer wrote: > Edward Kmett did some work with things he called "ropes" > https://hackage..haskell.org/package/rope > that can be efficient for > some byte string manipulations. There may be other good choices. > Yup, sometimes you want ropes (e.g. editors may benefit), other times you want VLists, etc. etc. From spam at scientician.net Mon Jul 11 21:09:34 2016 From: spam at scientician.net (Bardur Arantsson) Date: Mon, 11 Jul 2016 23:09:34 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On 07/11/2016 02:54 PM, David Fox wrote: > On Sun, Jul 10, 2016 at 11:44 AM, KC > wrote: > > Is the #functional programming paradigm antithetical to efficient > strings? #Haskell > > ​I can certainly see how it might seem so. Our main string > representation​ uses about 10 times more memory than seems necessary, > and is relatively fast, though probably not compared to C. Recently I > spent some time looking into how to reduce this memory overhead, and I > modified the pretty library > (https://github.com/ddssff/pretty/tree/textdetails) so it could use any > type that was an instance of ListLike and StringLike > (https://github.com/JohnLato/listlike > ). Then I tried the UnitLargeDoc > test with several different data types. This just concatenates a list > of ten million "Hello" strings. Using String this happens in about 5 > seconds. Using strict or lazy Text it immediately blew the stack. When > I increased the stack size to over 1GB it took minutes to complete. > When I used the Data.Text.Lazy.Builder type instead it took about 30 > seconds to complete. Results with utf8 encoded ByteStrings were siimilar. > Did you try similar code on Java/C# (or whatever)? From jake.waksbaum at gmail.com Mon Jul 11 22:08:03 2016 From: jake.waksbaum at gmail.com (Jake) Date: Mon, 11 Jul 2016 22:08:03 +0000 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> Message-ID: Just out of curiosity, what is the advantage to using a newtype in this case when you will not be writing your own instances of typeclasses? On Mon, Jul 11, 2016, 15:56 David Feuer wrote: > Please repost your code, giving a type signature for each top-level > binding. Without them, the code is very difficult to follow. I also > strongly recommend using a newtype for your custom monad. Something like > this: > > {-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, > StandaloneDeriving, ... #-} > > newtype StateReader s c a = SR {runSR :: StateT s (Reader c) a} deriving > (Functor, Applicative, Monad) > > deriving instance MonadReader c (StateReader s c) > deriving instance MonadState s (StateReader s c) > On Jul 11, 2016 11:07 AM, "Christopher Howard" wrote: > >> -- I'm a bit embarrassed of this code because I haven't yet optimized >> -- the 'stamp' algorithm for reduced number of matrix operations. But >> -- even in this state I should think the memory requirements shouldn't >> -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, >> -- etc. are being preserved in memory unnecessarily. >> >> -- Monad Stack >> >> type StateReader s c a = StateT s (Reader c) a >> >> evalStateReader m s c = (runReader (evalStateT m s)) c >> >> -- Helper function >> >> type Point = (Float, Float) >> type Metric = Point -> Point -> Float >> >> euclidean :: Metric >> euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) >> >> -- monadic function. haven't had chance yet to optimize algorithm to >> -- reduce number of matrix operations >> >> stamp = do radius <- ask >> (oMatrix, walk) <- get >> (wX, wY) <- (return . head) walk >> let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) >> (\(x, y) -> let (x', y') = (fromIntegral x, fromIntegral >> y) >> in if euclidean (x', y') (wX, wY) > radius >> then getElem x y oMatrix >> else getElem x y oMatrix + 1) >> in put (nMatrix, tail walk) >> get >> >> >> >> -- sequences and gathers results as list >> >> stampingStates initMx radius walk = >> map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) >> radius >> >> >> -- Some quick experimentation code. h is the list >> >> h = stampingStates initMx radius walk' >> where initMx = zero 250 250 >> radius = 40 >> walk' = walk 40 (125, 125) (mkStdGen 31415) >> >> -- get 2001st Matrix and convert to Gloss Picture, employing >> -- some color interpretation code >> >> intensityG = let mx = head (drop 2000 h) >> in toImage mx (lightnessInt 272 (minMax mx)) >> >> >> On 07/10/2016 10:30 AM, Tom Ellis wrote: >> > On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: >> >> issue: a Matrix itself should only be, I'm guessing, somewhere around >> >> 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. >> >> Maybe I'm generating list elements (Matrices) a lot faster than memory >> >> management is releasing them...? >> > >> > You have almost certainly got a space leak. Can you post your code? >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > To (un)subscribe, modify options or view archives go to: >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > Only members subscribed via the mailman list are allowed to post. >> > >> >> -- >> http://qlfiles.net >> To protect my privacy, please use PGP encryption. It's free and easy >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From dsf at seereason.com Mon Jul 11 22:22:41 2016 From: dsf at seereason.com (David Fox) Date: Mon, 11 Jul 2016 15:22:41 -0700 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On Mon, Jul 11, 2016 at 2:09 PM, Bardur Arantsson wrote: > On 07/11/2016 02:54 PM, David Fox wrote: > > On Sun, Jul 10, 2016 at 11:44 AM, KC > > wrote: > > > > Is the #functional programming paradigm antithetical to efficient > > strings? #Haskell > > > > ​I can certainly see how it might seem so. Our main string > > representation​ uses about 10 times more memory than seems necessary, > > and is relatively fast, though probably not compared to C. Recently I > > spent some time looking into how to reduce this memory overhead, and I > > modified the pretty library > > (https://github.com/ddssff/pretty/tree/textdetails) so it could use any > > type that was an instance of ListLike and StringLike > > (https://github.com/JohnLato/listlike > > ). Then I tried the UnitLargeDoc > > test with several different data types. This just concatenates a list > > of ten million "Hello" strings. Using String this happens in about 5 > > seconds. Using strict or lazy Text it immediately blew the stack. When > > I increased the stack size to over 1GB it took minutes to complete. > > When I used the Data.Text.Lazy.Builder type instead it took about 30 > > seconds to complete. Results with utf8 encoded ByteStrings were > siimilar. > > > > Did you try similar code on Java/C# (or whatever)? ​I did not.​ -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Mon Jul 11 22:33:41 2016 From: spam at scientician.net (Bardur Arantsson) Date: Tue, 12 Jul 2016 00:33:41 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: On 07/12/2016 12:22 AM, David Fox wrote: > > > On Mon, Jul 11, 2016 at 2:09 PM, Bardur Arantsson > wrote: > > On 07/11/2016 02:54 PM, David Fox wrote: > > On Sun, Jul 10, 2016 at 11:44 AM, KC > > >> wrote: > > > > Is the #functional programming paradigm antithetical to efficient > > strings? #Haskell > > > > ​I can certainly see how it might seem so. Our main string > > representation​ uses about 10 times more memory than seems necessary, > > and is relatively fast, though probably not compared to C. Recently I > > spent some time looking into how to reduce this memory overhead, and I > > modified the pretty library > > (https://github.com/ddssff/pretty/tree/textdetails) so it could use any > > type that was an instance of ListLike and StringLike > > (https://github.com/JohnLato/listlike > > ). Then I tried the > UnitLargeDoc > > test with several different data types. This just concatenates a list > > of ten million "Hello" strings. Using String this happens in about 5 > > seconds. Using strict or lazy Text it immediately blew the stack.. When > > I increased the stack size to over 1GB it took minutes to complete. > > When I used the Data.Text.Lazy.Builder type instead it took about 30 > > seconds to complete. Results with utf8 encoded ByteStrings were siimilar. > > > > Did you try similar code on Java/C# (or whatever)? > > > ​I did not.​ > Do try it -- it's an educational experience! (Even in C++, Rust or whatever takes your fancy.) (... and at this point I'm left wondering whether KC is just trolling.) From david.feuer at gmail.com Tue Jul 12 00:09:30 2016 From: david.feuer at gmail.com (David Feuer) Date: Mon, 11 Jul 2016 20:09:30 -0400 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> Message-ID: The advantage of using a newtype is that it hides the structure from the outside. Users of StateReader don't need to know that it's made of StateT and Reader. If something else gets tossed onto the transformer stack, existing users of StateReader won't need to change. On Jul 11, 2016 6:08 PM, "Jake" wrote: > Just out of curiosity, what is the advantage to using a newtype in this > case when you will not be writing your own instances of typeclasses? > > On Mon, Jul 11, 2016, 15:56 David Feuer wrote: > >> Please repost your code, giving a type signature for each top-level >> binding. Without them, the code is very difficult to follow. I also >> strongly recommend using a newtype for your custom monad. Something like >> this: >> >> {-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, >> StandaloneDeriving, ... #-} >> >> newtype StateReader s c a = SR {runSR :: StateT s (Reader c) a} deriving >> (Functor, Applicative, Monad) >> >> deriving instance MonadReader c (StateReader s c) >> deriving instance MonadState s (StateReader s c) >> On Jul 11, 2016 11:07 AM, "Christopher Howard" >> wrote: >> >>> -- I'm a bit embarrassed of this code because I haven't yet optimized >>> -- the 'stamp' algorithm for reduced number of matrix operations. But >>> -- even in this state I should think the memory requirements shouldn't >>> -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, >>> -- etc. are being preserved in memory unnecessarily. >>> >>> -- Monad Stack >>> >>> type StateReader s c a = StateT s (Reader c) a >>> >>> evalStateReader m s c = (runReader (evalStateT m s)) c >>> >>> -- Helper function >>> >>> type Point = (Float, Float) >>> type Metric = Point -> Point -> Float >>> >>> euclidean :: Metric >>> euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) >>> >>> -- monadic function. haven't had chance yet to optimize algorithm to >>> -- reduce number of matrix operations >>> >>> stamp = do radius <- ask >>> (oMatrix, walk) <- get >>> (wX, wY) <- (return . head) walk >>> let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) >>> (\(x, y) -> let (x', y') = (fromIntegral x, >>> fromIntegral y) >>> in if euclidean (x', y') (wX, wY) > radius >>> then getElem x y oMatrix >>> else getElem x y oMatrix + 1) >>> in put (nMatrix, tail walk) >> get >>> >>> >>> >>> -- sequences and gathers results as list >>> >>> stampingStates initMx radius walk = >>> map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) >>> radius >>> >>> >>> -- Some quick experimentation code. h is the list >>> >>> h = stampingStates initMx radius walk' >>> where initMx = zero 250 250 >>> radius = 40 >>> walk' = walk 40 (125, 125) (mkStdGen 31415) >>> >>> -- get 2001st Matrix and convert to Gloss Picture, employing >>> -- some color interpretation code >>> >>> intensityG = let mx = head (drop 2000 h) >>> in toImage mx (lightnessInt 272 (minMax mx)) >>> >>> >>> On 07/10/2016 10:30 AM, Tom Ellis wrote: >>> > On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: >>> >> issue: a Matrix itself should only be, I'm guessing, somewhere around >>> >> 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. >>> >> Maybe I'm generating list elements (Matrices) a lot faster than memory >>> >> management is releasing them...? >>> > >>> > You have almost certainly got a space leak. Can you post your code? >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > To (un)subscribe, modify options or view archives go to: >>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > Only members subscribed via the mailman list are allowed to post. >>> > >>> >>> -- >>> http://qlfiles.net >>> To protect my privacy, please use PGP encryption. It's free and easy >>> to use! My public key ID is 0x340EA95A (pgp.mit.edu). >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ch.howard at zoho.com Tue Jul 12 00:12:22 2016 From: ch.howard at zoho.com (Christopher Howard) Date: Mon, 11 Jul 2016 16:12:22 -0800 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> Message-ID: <578435E6.4060308@zoho.com> On 07/11/2016 11:56 AM, David Feuer wrote: > Please repost your code, giving a type signature for each top-level > binding. Without them, the code is very difficult to follow. I also > strongly recommend using a newtype for your custom monad. Something like > this: > > {-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, > StandaloneDeriving, ... #-} > > newtype StateReader s c a = SR {runSR :: StateT s (Reader c) a} deriving > (Functor, Applicative, Monad) > > deriving instance MonadReader c (StateReader s c) > deriving instance MonadState s (StateReader s c) > > On Jul 11, 2016 11:07 AM, "Christopher Howard" > wrote: > > -- I'm a bit embarrassed of this code because I haven't yet optimized > -- the 'stamp' algorithm for reduced number of matrix operations. But > -- even in this state I should think the memory requirements shouldn't > -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, > -- etc. are being preserved in memory unnecessarily. > > -- Monad Stack > > type StateReader s c a = StateT s (Reader c) a > > evalStateReader m s c = (runReader (evalStateT m s)) c > > -- Helper function > > type Point = (Float, Float) > type Metric = Point -> Point -> Float > > euclidean :: Metric > euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) > stamp :: StateReader (Matrix Float, [Point]) Float (Matrix Float, [Point]) > -- monadic function. haven't had chance yet to optimize algorithm to > -- reduce number of matrix operations > > stamp = do radius <- ask > (oMatrix, walk) <- get > (wX, wY) <- (return . head) walk > let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) > (\(x, y) -> let (x', y') = (fromIntegral x, > fromIntegral y) > in if euclidean (x', y') (wX, wY) > radius > then getElem x y oMatrix > else getElem x y oMatrix + 1) > in put (nMatrix, tail walk) >> get > > > > -- sequences and gathers results as list > stampingStates :: Matrix Float -> Float -> [Point] -> [Matrix Float] > stampingStates initMx radius walk = > map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) > radius > > > -- Some quick experimentation code. h is the list > h :: [Matrix Float] intensityG :: Picture displayIntensityG :: IO () > h = stampingStates initMx radius walk' > where initMx = zero 250 250 > radius = 40 > walk' = walk 40 (125, 125) (mkStdGen 31415) > > -- get 2001st Matrix and convert to Gloss Picture, employing > -- some color interpretation code > > intensityG = let mx = head (drop 2000 h) > in toImage mx (lightnessInt 272 (minMax mx)) > > -- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu). From magicloud.magiclouds at gmail.com Tue Jul 12 01:54:49 2016 From: magicloud.magiclouds at gmail.com (Magicloud Magiclouds) Date: Tue, 12 Jul 2016 01:54:49 +0000 Subject: [Haskell-cafe] Cannot install any packages after upgrading to GHC 8.0.1 In-Reply-To: References: Message-ID: Thank you all. Did not know I should update cabal as well. 'ghc-pkg dump' error was just because I forgot to initialize database. Magicloud Magiclouds 于2016年7月11日周一 下午3:49写道: > Hi, > I update my GHC to 8.0.1 and failed to install any packages since then. > If I use cabal, I got 'installed package info from too old version of > Cabal (key field does not match id field)' for every package. > If I use Setup.hs, I got 'Configuring Cabal-1.24.0.0... > Setup.hs: ghc-pkg dump failed'. > What should I do? Googling did not get me an answer. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Tue Jul 12 02:24:51 2016 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Tue, 12 Jul 2016 14:24:51 +1200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: Please do NOT confuse "the functional programming paradigm" with Haskell. "The imperative programming paradigm" is not identical to C, is it? The following measurements were made on a 3.2 GHz core i5 Mac running OSX 10.11 with clang (Apple LLVM version 7.3.0). Making an array with 10,000,000 pointers to "Hello world" in optimised C took 32 milliseconds and concatenating them to make a new 110,000,000 character string took 134 milliseconds. Using the built-in 'string' type in C++, no array, just hr += hw, took 260 milliseconds optimised, 460 milliseconds unoptimised. The maximum String size in SML/NJ is 2^24 characters, which is unfortunately too small for this problem. Taking 1,000,000 strings and concatenating them took 61.4 milliseconds, so presumably if String.maxSize were large enough the ML version would take 614 milliseconds. Making a list of "Hello world" 10,000,000 times and then concatenating that list to produce a single String took 0.87 seconds (start program to end program) in Haskell. Having made an array of 10,000,000 'Hello world' strings, concatenating the strings into a single String (a *mutable* packed array of character codes) took 0.50 seconds in Smalltalk (an object-oriented programming language). Concatenating the ten million strings in Java 1.8 using a StringBuilder took 0.84 seconds, very close to the Haskell time. Concatenating 10,000,000 copies of 'Hello world' in Python3 (using StringIO) took 1.312 seconds. Frankly, the Haskell time just doesn't stand out here. In a real program, I'd be trying to avoid string concatenation in *any* language. By the way, one toy microbenchmark by itself tells us NOTHING worth knowing about string efficiency, because there are many many other things we want to do to strings. A colleague of mine who uses C++ for text-heavy applications wouldn't be caught dead using C++ strings. I note that Clean, which in many ways resembles Haskell, has always had packed byte strings. Then of course there are languages like OCaml and F#, where F# uses the same string processing as C#, so F# strings should have the *same* efficiency (whatever that means) as C#. From will.yager at gmail.com Tue Jul 12 03:36:50 2016 From: will.yager at gmail.com (William Yager) Date: Mon, 11 Jul 2016 23:36:50 -0400 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: You picked the single slowest way to do it. Please see https://gist.github.com/wyager/df063ad4edd9a9c8b0ab762c91a79894 All times are on my Intel Atom Macbook. Compiled with -O3, no other options. Using Lazy Bytestrings (either through the Builder interface or plain old concatenation) is about 7-7.5 times faster than string concatenation so on your computer it should take about 0.12 seconds. In other words, faster than C. This is my usual experience with lazy bytestrings; due to their optimization for cache size, they are extremely fast with almost no effort. They often out-perform "fast" array operations in C due to fusion and cache coherency. I will note that if you want to do exactly what C does (often with only slightly different assembly output), you can often achieve this with unboxed vectors (mutable or immutable, depending on your application). --Will On Mon, Jul 11, 2016 at 10:24 PM, Richard A. O'Keefe wrote: > > > Making a list of "Hello world" 10,000,000 times and then > concatenating that list to produce a single String took > 0.87 seconds (start program to end program) in Haskell. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From aeyakovenko at gmail.com Tue Jul 12 05:19:58 2016 From: aeyakovenko at gmail.com (Anatoly Yakovenko) Date: Tue, 12 Jul 2016 05:19:58 +0000 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <578435E6.4060308@zoho.com> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <578435E6.4060308@zoho.com> Message-ID: have you tried adding some strict evaluation to your algorithm? The easy spot to do that when using the state monad is in the state variable. On Mon, Jul 11, 2016 at 5:12 PM Christopher Howard wrote: > > > > On 07/11/2016 11:56 AM, David Feuer wrote: > > Please repost your code, giving a type signature for each top-level > > binding. Without them, the code is very difficult to follow. I also > > strongly recommend using a newtype for your custom monad. Something like > > this: > > > > {-# LANGUAGE GeneralizedNewtypeDeriving, MultiParamTypeClasses, > > StandaloneDeriving, ... #-} > > > > newtype StateReader s c a = SR {runSR :: StateT s (Reader c) a} deriving > > (Functor, Applicative, Monad) > > > > deriving instance MonadReader c (StateReader s c) > > deriving instance MonadState s (StateReader s c) > > > > On Jul 11, 2016 11:07 AM, "Christopher Howard" > > wrote: > > > > -- I'm a bit embarrassed of this code because I haven't yet optimized > > -- the 'stamp' algorithm for reduced number of matrix operations. But > > -- even in this state I should think the memory requirements > shouldn't > > -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, > n-2, > > -- etc. are being preserved in memory unnecessarily. > > > > -- Monad Stack > > > > type StateReader s c a = StateT s (Reader c) a > > > > evalStateReader m s c = (runReader (evalStateT m s)) c > > > > -- Helper function > > > > type Point = (Float, Float) > > type Metric = Point -> Point -> Float > > > > euclidean :: Metric > > euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) > > > > stamp :: StateReader (Matrix Float, [Point]) > Float (Matrix Float, [Point]) > > > > -- monadic function. haven't had chance yet to optimize algorithm to > > -- reduce number of matrix operations > > > > stamp = do radius <- ask > > (oMatrix, walk) <- get > > (wX, wY) <- (return . head) walk > > let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) > > (\(x, y) -> let (x', y') = (fromIntegral x, > > fromIntegral y) > > in if euclidean (x', y') (wX, wY) > > radius > > then getElem x y oMatrix > > else getElem x y oMatrix + 1) > > in put (nMatrix, tail walk) >> get > > > > > > > > -- sequences and gathers results as list > > > > > stampingStates > :: Matrix Float -> Float -> [Point] -> [Matrix Float] > > > > stampingStates initMx radius walk = > > map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) > > radius > > > > > > -- Some quick experimentation code. h is the list > > > > h :: [Matrix Float] > > intensityG :: Picture > > displayIntensityG :: IO () > > > h = stampingStates initMx radius walk' > > where initMx = zero 250 250 > > radius = 40 > > walk' = walk 40 (125, 125) (mkStdGen 31415) > > > > -- get 2001st Matrix and convert to Gloss Picture, employing > > -- some color interpretation code > > > > intensityG = let mx = head (drop 2000 h) > > in toImage mx (lightnessInt 272 (minMax mx)) > > > > > > -- > http://qlfiles.net > To protect my privacy, please use PGP encryption. It's free and easy > to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ruben.astud at gmail.com Tue Jul 12 10:35:14 2016 From: ruben.astud at gmail.com (Ruben Astudillo) Date: Tue, 12 Jul 2016 06:35:14 -0400 Subject: [Haskell-cafe] network package and SIGVTALRM Message-ID: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> Hi all I am doing a DCC subsystem on a irc client. After all the handshakes are done I just connect to the server and start `recv`. The code I use for this is: getPackets :: MVar Int -> FilePath -- ^ Name media -> Int -- ^ File size -> AddrInfo -> ExceptT DCCError IO () getPackets mvar name totalSize addr = do receivedSize <- lift $ bracket acquire release receive let delta = (totalSize - receivedSize) if delta > 0 then throwE (NotFullRecv delta) else return () where bufferSize = 16384 acquire :: IO (IO.Handle,Socket) acquire = (,) <$> (IO.openFile name IO.WriteMode) <*> newSocket addr release :: (IO.Handle,Socket) -> IO () release (hdl, sock) = IO.hClose hdl >> close sock receive :: (IO.Handle,Socket) -> IO Int receive (hdl, sock) = flip execStateT 0 . fix $ \loop -> do mediaData <- lift (B.recv sock bufferSize) unless (B.null mediaData) $ do S.modify' (+ (B.length mediaData)) currentSize <- S.get lift $ B.hPut hdl mediaData >> B.send sock (int2BS currentSize) >> swapMVar mvar currentSize loop Part of the protocol is that on each `recv` I send the current received size on network byte order. Hence the B.send line on receive I use this function: -- | given a number forms a bytestring with each digit on a separated -- Word8 in network byte-order int2BS :: Int -> B.ByteString int2BS i | w <- (fromIntegral i :: Word32) = B.pack [ (fromIntegral (shiftR w 24) :: Word8) , (fromIntegral (shiftR w 16) :: Word8) , (fromIntegral (shiftR w 8) :: Word8) , (fromIntegral w :: Word8)] Everything works correctly until around 1/2 of a test transfer (ie in a file of 340M it gets 170). That first half is gotten in the right order (I tested with a video and it was playable until the middle). On tinier files the bug doesn't happen, the file is received completly. I did a little bit of `strace` and `tcpdump` and I got this -- strace -e trace=network -p $client (..) 30439 recvfrom(13, "\312\255\201\337\376\355\253\r\177\276\204X]8\6\221\301#\361<>\273+\355\5\343B \333\366\351W"..., 16384, 0, NULL, NULL) = 1380 30439 sendto(13, "\n\273\31l", 4, 0, NULL, 0) = 4 30439 recvfrom(13, 0x20023f010, 16384, 0, NULL, NULL) = -1 EAGAIN (Resource temporarily unavailable) 30439 recvfrom(13, "\222llq_H\23\17\275\f}\367\"P4\23\207\312$w\371J\354aW2\243R\32\v\n\251"..., 16384, 0, NULL, NULL) = 1380 30439 sendto(13, "\n\273\36\320", 4, 0, NULL, 0) = -1 EAGAIN (Resource temporarily unavailable) 30438 --- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER, si_timerid=0, si_overrun=0, si_value={int=0, ptr=0}} --- 30438 --- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER, si_timerid=0, si_overrun=0, si_value={int=0, ptr=0}} --- (..) -- tcpdump 05:20:22.788273 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack 48004680, win 489, options [nop,nop,TS val 627805332 ecr 675358947,nop,nop,sack 1 {48006060:48066780}], length 0 05:20:22.975627 IP 198.255.92.74.36103 > tapioca.36346: Flags [.], seq 48004680:48006060, ack 82629, win 0, options [nop,nop,TS val 675359033 ecr 627805248], length 1380 05:20:23.014991 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack 48066780, win 4, options [nop,nop,TS val 627805559 ecr 675359033], length 0 05:20:23.768012 IP 198.255.92.74.36103 > tapioca.36346: Flags [P.], seq 48066780:48067292, ack 82629, win 0, options [nop,nop,TS val 675359232 ecr 627805559], length 512 05:20:23.768143 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack 48067292, win 0, options [nop,nop,TS val 627806312 ecr 675359232], length 0 05:20:24.523397 IP 198.255.92.74.36103 > tapioca.36346: Flags [.], ack 82629, win 0, options [nop,nop,TS val 675359421 ecr 627806312], length 0 What bothers me is that SIGVTALRM on the strace output. I am not the greatest unix hacker but that signal is related to settimer and I haven't explicitly set that up. So I am scratching me head a little. Maybe somebody has experienced something related with the network package? Do you notice something on the logs? thanks in advance. -- -- Ruben Astudillo From petr.mvd at gmail.com Tue Jul 12 11:10:52 2016 From: petr.mvd at gmail.com (=?UTF-8?B?UGV0ciBQdWRsw6Fr?=) Date: Tue, 12 Jul 2016 11:10:52 +0000 Subject: [Haskell-cafe] Practical use of Stream's monad instance? In-Reply-To: References: Message-ID: Indeed, the question is not wherever it's a monad or not, just to what extent is the monad useful. Dne po 11. 7. 2016 22:08 uživatel Olaf Klinke napsal: > As someone else on this list whose name I don't recall put it, there is no > choice on whether to make Stream a monad or not. It simply _is_ a monad. > Anyone with some CS education hearing 'diagonal of inifinite list of > infinite lists' should immediately think of Georg Cantor. > > import Data.Stream > import Data.Ratio > > type Real = Stream Rational > -- approximate a real number by an ascending stream > -- of lower bounds. > > supremum :: Stream Real -> Real > supremum = join > -- If a stream of reals is index-wise ascending, > -- the monad instance for Stream computes its supremum. > -- Use this e.g. to compute any mathematical quantity > -- defined as a supremum. > > -- Olaf > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kwangyul.seo at gmail.com Tue Jul 12 12:23:42 2016 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Tue, 12 Jul 2016 21:23:42 +0900 Subject: [Haskell-cafe] ANN: tagsoup-megaparsec-0.1.0.0 Message-ID: Hello all, I'm pleased to announce the first release of tagsoup-megaparsec, a Tag token parser library. This library helps you build a megaparsec parser using TagSoup's Tags as tokens. https://hackage.haskell.org/package/tagsoup-megaparsec https://github.com/kseo/tagsoup-megaparsec Regards, Kwang Yul Seo -------------- next part -------------- An HTML attachment was scrubbed... URL: From blaze at ruddy.ru Tue Jul 12 15:40:33 2016 From: blaze at ruddy.ru (Andrey Sverdlichenko) Date: Tue, 12 Jul 2016 15:40:33 +0000 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> Message-ID: Hi Ruben, This signal is used internally by Haskell IO manager, nothing is wrong with it. What I see in the dump is that 198.255.92.74 is announcing window of size 0 from the beginning and tapioca ends up sending 0 window too. Are you sure they both reading what other one sends to them? Given that your code only fails on large files, I guess sender never reads this 4-byte status messages receiver sends to it, and processes deadlock after socket buffer is filled up. As a side node, consider using putWord32be from binary or cereal packages instead of serializing data yourself. On Tue, 12 Jul 2016 at 03:35, Ruben Astudillo wrote: > Hi all > > I am doing a DCC subsystem on a irc client. After all the handshakes are > done I just connect to the server and start `recv`. The code I use for > this is: > > getPackets :: MVar Int > -> FilePath -- ^ Name media > -> Int -- ^ File size > -> AddrInfo -> ExceptT DCCError IO () > getPackets mvar name totalSize addr = > do receivedSize <- lift $ bracket acquire release receive > let delta = (totalSize - receivedSize) > if delta > 0 then throwE (NotFullRecv delta) else return () > where > bufferSize = 16384 > > acquire :: IO (IO.Handle,Socket) > acquire = (,) <$> (IO.openFile name IO.WriteMode) > <*> newSocket addr > > release :: (IO.Handle,Socket) -> IO () > release (hdl, sock) = IO.hClose hdl >> close sock > > receive :: (IO.Handle,Socket) -> IO Int > receive (hdl, sock) = > flip execStateT 0 . fix $ \loop -> do > mediaData <- lift (B.recv sock bufferSize) > unless (B.null mediaData) $ do > S.modify' (+ (B.length mediaData)) > currentSize <- S.get > lift $ B.hPut hdl mediaData > >> B.send sock (int2BS currentSize) > >> swapMVar mvar currentSize > loop > > Part of the protocol is that on each `recv` I send the current received > size on network byte order. Hence the B.send line on receive I use this > function: > > -- | given a number forms a bytestring with each digit on a separated > -- Word8 in network byte-order > int2BS :: Int -> B.ByteString > int2BS i | w <- (fromIntegral i :: Word32) = > B.pack [ (fromIntegral (shiftR w 24) :: Word8) > , (fromIntegral (shiftR w 16) :: Word8) > , (fromIntegral (shiftR w 8) :: Word8) > , (fromIntegral w :: Word8)] > > Everything works correctly until around 1/2 of a test transfer (ie in a > file of 340M it gets 170). That first half is gotten in the right order > (I tested with a video and it was playable until the middle). On tinier > files the bug doesn't happen, the file is received completly. I did a > little bit of `strace` and `tcpdump` and I got this > > -- strace -e trace=network -p $client > (..) > 30439 recvfrom(13, > > "\312\255\201\337\376\355\253\r\177\276\204X]8\6\221\301#\361<>\273+\355\5\343B > \333\366\351W"..., 16384, 0, NULL, NULL) = 1380 > 30439 sendto(13, "\n\273\31l", 4, 0, NULL, 0) = 4 > 30439 recvfrom(13, 0x20023f010, 16384, 0, NULL, NULL) = -1 EAGAIN > (Resource temporarily unavailable) > 30439 recvfrom(13, > > "\222llq_H\23\17\275\f}\367\"P4\23\207\312$w\371J\354aW2\243R\32\v\n\251"..., > 16384, 0, NULL, NULL) = 1380 > 30439 sendto(13, "\n\273\36\320", 4, 0, NULL, 0) = -1 EAGAIN (Resource > temporarily unavailable) > 30438 --- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER, > si_timerid=0, si_overrun=0, si_value={int=0, ptr=0}} --- > 30438 --- SIGVTALRM {si_signo=SIGVTALRM, si_code=SI_TIMER, > si_timerid=0, si_overrun=0, si_value={int=0, ptr=0}} --- > (..) > > -- tcpdump > 05:20:22.788273 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack > 48004680, win 489, options [nop,nop,TS val 627805332 ecr > 675358947,nop,nop,sack 1 {48006060:48066780}], length 0 > 05:20:22.975627 IP 198.255.92.74.36103 > tapioca.36346: Flags [.], seq > 48004680:48006060, ack 82629, win 0, options [nop,nop,TS val 675359033 ecr > 627805248], length 1380 > 05:20:23.014991 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack > 48066780, win 4, options [nop,nop,TS val 627805559 ecr 675359033], length 0 > 05:20:23.768012 IP 198.255.92.74.36103 > tapioca.36346: Flags [P.], > seq 48066780:48067292, ack 82629, win 0, options [nop,nop,TS val 675359232 > ecr 627805559], length 512 > 05:20:23.768143 IP tapioca.36346 > 198.255.92.74.36103: Flags [.], ack > 48067292, win 0, options [nop,nop,TS val 627806312 ecr 675359232], length 0 > 05:20:24.523397 IP 198.255.92.74.36103 > tapioca.36346: Flags [.], ack > 82629, win 0, options [nop,nop,TS val 675359421 ecr 627806312], length 0 > > What bothers me is that SIGVTALRM on the strace output. I am not the > greatest unix hacker but that signal is related to settimer and I haven't > explicitly set that up. So I am scratching me head a little. Maybe > somebody has experienced something related with the network package? Do > you notice something on the logs? thanks in advance. > > -- > -- Ruben Astudillo > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Tue Jul 12 18:40:58 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Tue, 12 Jul 2016 19:40:58 +0100 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <5783B4C4.70902@zoho.com> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> Message-ID: <20160712184058.GH11559@weber> I can't run this code because it's missing several things, including the definition of Matrix and walk, and imports. Certainly you are building up a large chain of thunks repeatedly applying the calculation for nMatrix, but how to solve it I cannot say without more information. On Mon, Jul 11, 2016 at 07:01:24AM -0800, Christopher Howard wrote: > -- I'm a bit embarrassed of this code because I haven't yet optimized > -- the 'stamp' algorithm for reduced number of matrix operations. But > -- even in this state I should think the memory requirements shouldn't > -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, > -- etc. are being preserved in memory unnecessarily. > > -- Monad Stack > > type StateReader s c a = StateT s (Reader c) a > > evalStateReader m s c = (runReader (evalStateT m s)) c > > -- Helper function > > type Point = (Float, Float) > type Metric = Point -> Point -> Float > > euclidean :: Metric > euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) > > -- monadic function. haven't had chance yet to optimize algorithm to > -- reduce number of matrix operations > > stamp = do radius <- ask > (oMatrix, walk) <- get > (wX, wY) <- (return . head) walk > let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) > (\(x, y) -> let (x', y') = (fromIntegral x, fromIntegral y) > in if euclidean (x', y') (wX, wY) > radius > then getElem x y oMatrix > else getElem x y oMatrix + 1) > in put (nMatrix, tail walk) >> get > > > > -- sequences and gathers results as list > > stampingStates initMx radius walk = > map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius > > > -- Some quick experimentation code. h is the list > > h = stampingStates initMx radius walk' > where initMx = zero 250 250 > radius = 40 > walk' = walk 40 (125, 125) (mkStdGen 31415) > > -- get 2001st Matrix and convert to Gloss Picture, employing > -- some color interpretation code > > intensityG = let mx = head (drop 2000 h) > in toImage mx (lightnessInt 272 (minMax mx)) > > > On 07/10/2016 10:30 AM, Tom Ellis wrote: > > On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: > >> issue: a Matrix itself should only be, I'm guessing, somewhere around > >> 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. > >> Maybe I'm generating list elements (Matrices) a lot faster than memory > >> management is releasing them...? > > > > You have almost certainly got a space leak. Can you post your code? From joehillen at gmail.com Tue Jul 12 23:56:15 2016 From: joehillen at gmail.com (Joe Hillenbrand) Date: Tue, 12 Jul 2016 16:56:15 -0700 Subject: [Haskell-cafe] ANN: tagsoup-megaparsec-0.1.0.0 In-Reply-To: References: Message-ID: Please add a tutorial. On Tue, Jul 12, 2016 at 5:23 AM, KwangYul Seo wrote: > Hello all, > > I'm pleased to announce the first release of tagsoup-megaparsec, a Tag token > parser library. This library helps you build a megaparsec parser using > TagSoup's Tags as tokens. > > https://hackage.haskell.org/package/tagsoup-megaparsec > > https://github.com/kseo/tagsoup-megaparsec > > Regards, > Kwang Yul Seo > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From ok at cs.otago.ac.nz Wed Jul 13 02:30:30 2016 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Wed, 13 Jul 2016 14:30:30 +1200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: <9bc3ec9e-3a00-3c22-0171-be45e478b113@cs.otago.ac.nz> On 12/07/16 3:36 PM, William Yager wrote: > You picked the single slowest way to do it. No, the way I did it was linear time, making it NOT the slowest way to do it. The point I was making is that the simplest not-totally-stupid way to do it in Haskell isn't actually all that bad compared with other languages. From ch.howard at zoho.com Wed Jul 13 02:39:53 2016 From: ch.howard at zoho.com (Christopher Howard) Date: Tue, 12 Jul 2016 18:39:53 -0800 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <20160712184058.GH11559@weber> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> Message-ID: <5785A9F9.2060006@zoho.com> I guess I was hesitating on posting the entire program source code in an cafe email. I suppose I could send you a tarball, if you really wanted it... Matrix is from Data.Matrix . It is hard to understand how thunks alone would explain it... there would be at most 2000 thunks, right? Unless... Could there be a thunk for every single call to getElem? That would be a lot of thunks! Somebody suggested adding some strictness here... could you elaborate on that? I tried inserting seq, but I didn't really understand how I was supposed to use it... On 07/12/2016 10:40 AM, Tom Ellis wrote: > I can't run this code because it's missing several things, including the > definition of Matrix and walk, and imports. > > Certainly you are building up a large chain of thunks repeatedly applying > the calculation for nMatrix, but how to solve it I cannot say without more > information. > > On Mon, Jul 11, 2016 at 07:01:24AM -0800, Christopher Howard wrote: >> -- I'm a bit embarrassed of this code because I haven't yet optimized >> -- the 'stamp' algorithm for reduced number of matrix operations. But >> -- even in this state I should think the memory requirements shouldn't >> -- exceed 1MB while generating the nth Matrix, unless Matrix n-1, n-2, >> -- etc. are being preserved in memory unnecessarily. >> >> -- Monad Stack >> >> type StateReader s c a = StateT s (Reader c) a >> >> evalStateReader m s c = (runReader (evalStateT m s)) c >> >> -- Helper function >> >> type Point = (Float, Float) >> type Metric = Point -> Point -> Float >> >> euclidean :: Metric >> euclidean (x1, y1) (x2, y2) = sqrt ((x2 - x1)**2 + (y2 - y1)**2) >> >> -- monadic function. haven't had chance yet to optimize algorithm to >> -- reduce number of matrix operations >> >> stamp = do radius <- ask >> (oMatrix, walk) <- get >> (wX, wY) <- (return . head) walk >> let nMatrix = matrix (nrows oMatrix) (ncols oMatrix) >> (\(x, y) -> let (x', y') = (fromIntegral x, fromIntegral y) >> in if euclidean (x', y') (wX, wY) > radius >> then getElem x y oMatrix >> else getElem x y oMatrix + 1) >> in put (nMatrix, tail walk) >> get >> >> >> >> -- sequences and gathers results as list >> >> stampingStates initMx radius walk = >> map fst $ evalStateReader (sequence (repeat stamp)) (initMx, walk) radius >> >> >> -- Some quick experimentation code. h is the list >> >> h = stampingStates initMx radius walk' >> where initMx = zero 250 250 >> radius = 40 >> walk' = walk 40 (125, 125) (mkStdGen 31415) >> >> -- get 2001st Matrix and convert to Gloss Picture, employing >> -- some color interpretation code >> >> intensityG = let mx = head (drop 2000 h) >> in toImage mx (lightnessInt 272 (minMax mx)) >> >> >> On 07/10/2016 10:30 AM, Tom Ellis wrote: >>> On Sun, Jul 10, 2016 at 07:41:31AM -0800, Christopher Howard wrote: >>>> issue: a Matrix itself should only be, I'm guessing, somewhere around >>>> 100KB. But instead I'm maxing out the 3GB of RAM on my old T60 laptop. >>>> Maybe I'm generating list elements (Matrices) a lot faster than memory >>>> management is releasing them...? >>> >>> You have almost certainly got a space leak. Can you post your code? > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu). From ch.howard at zoho.com Wed Jul 13 03:28:05 2016 From: ch.howard at zoho.com (Christopher Howard) Date: Tue, 12 Jul 2016 19:28:05 -0800 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <5785A9F9.2060006@zoho.com> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> Message-ID: <5785B545.5000206@zoho.com> After pondering this problem some more, I found a solution to the problem was to introduce strictness, not deep down in the StateReader monad, but rather at the top level, i.e., forcing evaluation of each Matrix as soon as it is pulled of the list of Matrices. I found I could do this simply by summing all the elements in each matrix and printing the sum to std out. With this approach, i successfully run the full program and never even saw my memory performance graph move up. I suppose there might be a way to do the same thing more efficiently with seq...? On 07/12/2016 06:39 PM, Christopher Howard wrote: > I guess I was hesitating on posting the entire program source code in an > cafe email. I suppose I could send you a tarball, if you really wanted it... > > Matrix is from Data.Matrix > . > > It is hard to understand how thunks alone would explain it... there > would be at most 2000 thunks, right? Unless... Could there be a thunk > for every single call to getElem? That would be a lot of thunks! > > Somebody suggested adding some strictness here... could you elaborate on > that? I tried inserting seq, but I didn't really understand how I was > supposed to use it... > -- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu). From will.yager at gmail.com Wed Jul 13 03:56:23 2016 From: will.yager at gmail.com (William Yager) Date: Tue, 12 Jul 2016 23:56:23 -0400 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <5785B545.5000206@zoho.com> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> Message-ID: You probably want Control.DeepSeq. No extraneous work doing addition that way either. Will On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard wrote: > After pondering this problem some more, I found a solution to the > problem was to introduce strictness, not deep down in the StateReader > monad, but rather at the top level, i.e., forcing evaluation of each > Matrix as soon as it is pulled of the list of Matrices. I found I could > do this simply by summing all the elements in each matrix and printing > the sum to std out. With this approach, i successfully run the full > program and never even saw my memory performance graph move up. > > I suppose there might be a way to do the same thing more efficiently > with seq...? > > On 07/12/2016 06:39 PM, Christopher Howard wrote: > > I guess I was hesitating on posting the entire program source code in an > > cafe email. I suppose I could send you a tarball, if you really wanted > it... > > > > Matrix is from Data.Matrix > > >. > > > > It is hard to understand how thunks alone would explain it... there > > would be at most 2000 thunks, right? Unless... Could there be a thunk > > for every single call to getElem? That would be a lot of thunks! > > > > Somebody suggested adding some strictness here... could you elaborate on > > that? I tried inserting seq, but I didn't really understand how I was > > supposed to use it... > > > > -- > http://qlfiles.net > To protect my privacy, please use PGP encryption. It's free and easy > to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From erantapaa at gmail.com Wed Jul 13 05:36:12 2016 From: erantapaa at gmail.com (Erik Rantapaa) Date: Tue, 12 Jul 2016 22:36:12 -0700 (PDT) Subject: [Haskell-cafe] ANN: tagsoup-megaparsec-0.1.0.0 In-Reply-To: References: Message-ID: <1141844c-2303-45c5-93e0-76bfd4598fe3@googlegroups.com> On Tuesday, July 12, 2016 at 6:56:25 PM UTC-5, Joe Hillenbrand wrote: > > Please add a tutorial. FWIW, there is a simple example in the test directory: https://github.com/kseo/tagsoup-megaparsec/blob/master/test/Spec.hs -------------- next part -------------- An HTML attachment was scrubbed... URL: From ruben.astud at gmail.com Wed Jul 13 10:14:32 2016 From: ruben.astud at gmail.com (Ruben Astudillo) Date: Wed, 13 Jul 2016 06:14:32 -0400 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> Message-ID: <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> On 12/07/16 11:40, Andrey Sverdlichenko wrote: > they both reading what other one sends to them? Given that your code only > fails on large files, I guess sender never reads this 4-byte status > messages receiver sends to it, and processes deadlock after socket buffer > is filled up. Right on the nail. I played a bit with tcpdump/wireshark to see I was just sending 0 length ACKs and multiple 4 byte messages joined on a single packet. Seems TCP buffers tiny packets using a strategy called Nagle's algorithm and thus joined all my packets on a bufferzone until a threeshold. Then it sent them all at once, making the other end crazy. Adding on a function that set-ups the socket this line newSocket :: AddrInfo -> IO Socket newSocket addr = do sock <- socket AF_INET Stream defaultProtocol setSocketOption sock NoDelay 1 -- this was added connect sock (addrAddress addr) return sock makes the downloads go until the end. :-) > As a side node, consider using putWord32be from binary or cereal packages > instead of serializing data yourself. Note taken. I just don't want to impose on a new dependency on my first patch. I did copy/pasted putWord32be (at least on style) for my int2BS function though. Thanks a lot! -- Ruben Astudillo From kwangyul.seo at gmail.com Wed Jul 13 11:26:00 2016 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Wed, 13 Jul 2016 20:26:00 +0900 Subject: [Haskell-cafe] ANN: tagsoup-megaparsec-0.1.0.0 In-Reply-To: References: Message-ID: Thanks for the feedback! I added a usage section to the readme. The example will help you understand how to use tagsoup-megaparsec. https://github.com/kseo/tagsoup-megaparsec/blob/master/README.md There is also a simple example in the test directory as Erik Rantapaa mentioned: https://github.com/kseo/tagsoup-megaparsec/blob/master/test/Spec.hs Regards, Kwang Yul Seo On Wed, Jul 13, 2016 at 8:56 AM, Joe Hillenbrand wrote: > Please add a tutorial. > > On Tue, Jul 12, 2016 at 5:23 AM, KwangYul Seo > wrote: > > Hello all, > > > > I'm pleased to announce the first release of tagsoup-megaparsec, a Tag > token > > parser library. This library helps you build a megaparsec parser using > > TagSoup's Tags as tokens. > > > > https://hackage.haskell.org/package/tagsoup-megaparsec > > > > https://github.com/kseo/tagsoup-megaparsec > > > > Regards, > > Kwang Yul Seo > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From branimir.maksimovic at gmail.com Wed Jul 13 11:41:09 2016 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Wed, 13 Jul 2016 13:41:09 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: Message-ID: <7172e6b3-1318-828f-a7f7-a58a6e8e435d@gmail.com> rust (no need for array but anyway) [bmaxa at manjaro rust]$ time ./append 10000000 took 0.064016791 110000000 took 0.13466229 real 0m0.204s user 0m0.167s sys 0m0.033s haskell (your fastest version) [bmaxa at manjaro rust]$ time ./concat "Done" real 0m0.224s user 0m0.220s sys 0m0.000s c++ (no array) [bmaxa at manjaro rust]$ time ./a.out real 0m0.115s user 0m0.100s sys 0m0.013s rust: use std::time::*; fn main() { let mut arr=Vec::new(); arr.reserve(10_000_000); let start = Instant::now(); for _ in 0 .. 10_000_000 { arr.push("hello world"); } let end = start.elapsed(); let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as u64) as f64/1000000000.; println!("{} took {}",arr.len(),diff); let mut str = String::new(); str.reserve(110_000_000); let start = Instant::now(); for i in arr { str .push_str(i); } let end = start.elapsed(); let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as u64) as f64/1000000000.; println!("{} took {}",str.len(),diff); } c++: #include #include int main() { std::string tmp; tmp.reserve(110000000); for (int i=0;i<10000000;i++) { tmp += "hello world"; } } Model name: Intel(R) Core(TM) i3-5005U CPU @ 2.00GHz On 07/12/2016 05:36 AM, William Yager wrote: > You picked the single slowest way to do it. Please see > https://gist.github.com/wyager/df063ad4edd9a9c8b0ab762c91a79894 > > All times are on my Intel Atom Macbook. Compiled with -O3, no other > options. > > Using Lazy Bytestrings (either through the Builder interface or plain > old concatenation) is about 7-7.5 times faster than string > concatenation so on your computer it should take about 0.12 seconds. > In other words, faster than C. > > This is my usual experience with lazy bytestrings; due to their > optimization for cache size, they are extremely fast with almost no > effort. They often out-perform "fast" array operations in C due to > fusion and cache coherency. > > I will note that if you want to do exactly what C does (often with > only slightly different assembly output), you can often achieve this > with unboxed vectors (mutable or immutable, depending on your > application). > > --Will > > On Mon, Jul 11, 2016 at 10:24 PM, Richard A. O'Keefe > > wrote: > > > Making a list of "Hello world" 10,000,000 times and then > concatenating that list to produce a single String took > 0.87 seconds (start program to end program) in Haskell. > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mitchellwrosen at gmail.com Wed Jul 13 13:57:50 2016 From: mitchellwrosen at gmail.com (Mitchell Rosen) Date: Wed, 13 Jul 2016 06:57:50 -0700 (PDT) Subject: [Haskell-cafe] Can't log into to GHC trac Message-ID: <4f55e77d-5dab-4f79-b08d-1125d547ff56@googlegroups.com> Hi, embarrassingly I've forgotten my password (and username) to the GHC trac, and there's no automatic way to reset any of it: - When I try to register an account it says my email address is already in use - To reset my password I need to give both my username and password, but I don't know my username Who can I contact to help resolve the issue? -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Wed Jul 13 18:00:12 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Wed, 13 Jul 2016 19:00:12 +0100 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <5785B545.5000206@zoho.com> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> Message-ID: <20160713180012.GC16574@weber> On Tue, Jul 12, 2016 at 07:28:05PM -0800, Christopher Howard wrote: > After pondering this problem some more, I found a solution to the > problem was to introduce strictness, not deep down in the StateReader > monad, but rather at the top level, i.e., forcing evaluation of each > Matrix as soon as it is pulled of the list of Matrices. I found I could > do this simply by summing all the elements in each matrix and printing > the sum to std out. With this approach, i successfully run the full > program and never even saw my memory performance graph move up. > > I suppose there might be a way to do the same thing more efficiently > with seq...? Undoubtedly, but it's customary when asking for help to produce a complete minimal example that reproduces the problem. I can't help if I can't run your code! From blaze at ruddy.ru Wed Jul 13 18:10:00 2016 From: blaze at ruddy.ru (Andrey Sverdlichenko) Date: Wed, 13 Jul 2016 18:10:00 +0000 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> Message-ID: On Wed, Jul 13, 2016 at 3:14 AM Ruben Astudillo wrote: > > Right on the nail. I played a bit with tcpdump/wireshark to see I was > just sending 0 length ACKs and multiple 4 byte messages joined on a > single packet. Seems TCP buffers tiny packets using a strategy called > Nagle's algorithm and thus joined all my packets on a bufferzone until a > threeshold. Then it sent them all at once, making the other end crazy. > This looks a bit scary. It should not matter if replies are merged or not. By any chance, don't your code use recv with some large max buffer size, but expect to get only 4 bytes because this is how much receiver sends each time? If so, change it to read 4 bytes only, and handle the case when less than 4 bytes are out. TCP do not preserve message boundaries and you can expect reads to return data in arbitrary sized chunks. Regards, Andrey -------------- next part -------------- An HTML attachment was scrubbed... URL: From wangbj at gmail.com Wed Jul 13 18:42:54 2016 From: wangbj at gmail.com (Baojun Wang) Date: Wed, 13 Jul 2016 18:42:54 +0000 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> Message-ID: Suppose TCP_NODELAY sock opt can prevent Nagle join small packets? On Wed, Jul 13, 2016 at 11:10 AM Andrey Sverdlichenko wrote: > On Wed, Jul 13, 2016 at 3:14 AM Ruben Astudillo > wrote: > >> >> Right on the nail. I played a bit with tcpdump/wireshark to see I was >> just sending 0 length ACKs and multiple 4 byte messages joined on a >> single packet. Seems TCP buffers tiny packets using a strategy called >> Nagle's algorithm and thus joined all my packets on a bufferzone until a >> threeshold. Then it sent them all at once, making the other end crazy. >> > > This looks a bit scary. It should not matter if replies are merged or not. > By any chance, don't your code use recv with some large max buffer size, > but expect to get only 4 bytes because this is how much receiver sends each > time? If so, change it to read 4 bytes only, and handle the case when less > than 4 bytes are out. TCP do not preserve message boundaries and you can > expect reads to return data in arbitrary sized chunks. > > Regards, > Andrey > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From blaze at ruddy.ru Wed Jul 13 18:54:23 2016 From: blaze at ruddy.ru (Andrey Sverdlichenko) Date: Wed, 13 Jul 2016 18:54:23 +0000 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> Message-ID: If you are lucky. They still may be merged by sender if retransmission occurs, or on receiving side, if receiver waits too long before reads, and this is up to OS scheduler to control. NDELAY option is used to improve interactive latency, it will not make TCP obey message boundaries. On Wed, Jul 13, 2016 at 11:43 AM Baojun Wang wrote: > Suppose TCP_NODELAY sock opt can prevent Nagle join small packets? > > On Wed, Jul 13, 2016 at 11:10 AM Andrey Sverdlichenko > wrote: > >> On Wed, Jul 13, 2016 at 3:14 AM Ruben Astudillo >> wrote: >> >>> >>> Right on the nail. I played a bit with tcpdump/wireshark to see I was >>> just sending 0 length ACKs and multiple 4 byte messages joined on a >>> single packet. Seems TCP buffers tiny packets using a strategy called >>> Nagle's algorithm and thus joined all my packets on a bufferzone until a >>> threeshold. Then it sent them all at once, making the other end crazy. >>> >> >> This looks a bit scary. It should not matter if replies are merged or not. >> By any chance, don't your code use recv with some large max buffer size, >> but expect to get only 4 bytes because this is how much receiver sends each >> time? If so, change it to read 4 bytes only, and handle the case when less >> than 4 bytes are out. TCP do not preserve message boundaries and you can >> expect reads to return data in arbitrary sized chunks. >> >> Regards, >> Andrey >> > _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Wed Jul 13 19:32:18 2016 From: david.feuer at gmail.com (David Feuer) Date: Wed, 13 Jul 2016 15:32:18 -0400 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> Message-ID: You have to be careful with deepseq. Using it in the wrong place can lead to very bad performance. It's a big hammer. Its blow can sometimes be softened using the NF type from the nf package, but it's really not the right thing most of the time. On Tue, Jul 12, 2016 at 11:56 PM, William Yager wrote: > You probably want Control.DeepSeq. No extraneous work doing addition that > way either. > > Will > > On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard > wrote: >> >> After pondering this problem some more, I found a solution to the >> problem was to introduce strictness, not deep down in the StateReader >> monad, but rather at the top level, i.e., forcing evaluation of each >> Matrix as soon as it is pulled of the list of Matrices. I found I could >> do this simply by summing all the elements in each matrix and printing >> the sum to std out. With this approach, i successfully run the full >> program and never even saw my memory performance graph move up. >> >> I suppose there might be a way to do the same thing more efficiently >> with seq...? >> >> On 07/12/2016 06:39 PM, Christopher Howard wrote: >> > I guess I was hesitating on posting the entire program source code in an >> > cafe email. I suppose I could send you a tarball, if you really wanted >> > it... >> > >> > Matrix is from Data.Matrix >> > >> > . >> > >> > It is hard to understand how thunks alone would explain it... there >> > would be at most 2000 thunks, right? Unless... Could there be a thunk >> > for every single call to getElem? That would be a lot of thunks! >> > >> > Somebody suggested adding some strictness here... could you elaborate on >> > that? I tried inserting seq, but I didn't really understand how I was >> > supposed to use it... >> > >> >> -- >> http://qlfiles.net >> To protect my privacy, please use PGP encryption. It's free and easy >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From mitchellwrosen at gmail.com Wed Jul 13 20:54:11 2016 From: mitchellwrosen at gmail.com (Mitchell Rosen) Date: Wed, 13 Jul 2016 13:54:11 -0700 (PDT) Subject: [Haskell-cafe] Use GHC API in standalone executable? Message-ID: Hi, I'd like to compile an executable that internally uses the GHC API, but otherwise does not require users to have GHC installed on their machine. Is this possible? As far as I can tell, lots of functions in the GHC API read package databases per $GHC_PACKAGE_PATH and things of that nature. Thanks, Mitchell -------------- next part -------------- An HTML attachment was scrubbed... URL: From kwangyul.seo at gmail.com Thu Jul 14 00:40:13 2016 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Thu, 14 Jul 2016 09:40:13 +0900 Subject: [Haskell-cafe] How to support multiple string types in Haskell? Message-ID: Hi all, There are multiple string types in Haskell – String, lazy/strict ByteString, lazy/strict Text to name a few. So to make a string handling function maximally reusable, it needs to support multiple string types. One approach used by TagSoup library is to make a type class StringLike which represents the polymorphic string type and uses it where a String type is normally needed. For example, parseTags :: StringLike str => str -> [Tag str] Here parseTags takes a StringLike type instead of a fixed string type. Users of TagSoup can pick any of String, lazy/strict ByteString, lazy/strict Text because they are all instances of StringLike type class. It seems StringLike type class is quite generic but it is used only in the TagSoup package. This makes me wonder what is the idiomatic way to support multiple string types in Haskell. What other approaches do we have? Thanks, Kwang Yul Seo -------------- next part -------------- An HTML attachment was scrubbed... URL: From ezyang at mit.edu Thu Jul 14 01:00:03 2016 From: ezyang at mit.edu (Edward Z. Yang) Date: Wed, 13 Jul 2016 18:00:03 -0700 Subject: [Haskell-cafe] How to support multiple string types in Haskell? In-Reply-To: References: Message-ID: <1468457891-sup-4775@sabre> Hello KwangYul, Supporting this sort of parametricity is one of the goals of the Backpack project. You can see some code that demonstrates how this might be done: https://github.com/yihuang/tagstream-conduit/pull/18 Maybe you'll get to use this feature in GHC 8.2! A big problem with StringLike type classes is that you must pre-commit to the set of operations which are supported before hand. For strings, there are many, many such operations, and it is difficult to agree a priori what these operations should be. Edward Excerpts from KwangYul Seo's message of 2016-07-13 17:40:13 -0700: > Hi all, > > There are multiple string types in Haskell – String, lazy/strict > ByteString, lazy/strict Text to name a few. So to make a string handling > function maximally reusable, it needs to support multiple string types. > > One approach used by TagSoup library is to make a type class StringLike > which represents the polymorphic string type and uses it where a String > type is normally needed. For example, > > parseTags :: StringLike str => str -> [Tag str] > > Here parseTags takes a StringLike type instead of a fixed string type. > Users of TagSoup can pick any of String, lazy/strict ByteString, > lazy/strict Text because they are all instances of StringLike type class. > > It seems StringLike type class is quite generic but it is used only in the > TagSoup package. This makes me wonder what is the idiomatic way to support > multiple string types in Haskell. What other approaches do we have? > > Thanks, > Kwang Yul Seo From heraldhoi at gmail.com Thu Jul 14 04:42:09 2016 From: heraldhoi at gmail.com (Geraldus) Date: Thu, 14 Jul 2016 04:42:09 +0000 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: <7172e6b3-1318-828f-a7f7-a58a6e8e435d@gmail.com> References: <7172e6b3-1318-828f-a7f7-a58a6e8e435d@gmail.com> Message-ID: Your rust version pushes only 10'000'000 strings from arr into str, doesn't it? ср, 13 июл. 2016 г. в 16:41, Branimir Maksimovic < branimir.maksimovic at gmail.com>: > rust (no need for array but anyway) > > [bmaxa at manjaro rust]$ time ./append > 10000000 took 0.064016791 > 110000000 took 0.13466229 > > real 0m0.204s > user 0m0.167s > sys 0m0.033s > > haskell (your fastest version) > > [bmaxa at manjaro rust]$ time ./concat > "Done" > > real 0m0.224s > user 0m0.220s > sys 0m0.000s > > c++ (no array) > > [bmaxa at manjaro rust]$ time ./a.out > > real 0m0.115s > user 0m0.100s > sys 0m0.013s > > rust: > > use std::time::*; > > fn main() { > let mut arr=Vec::new(); > arr.reserve(10_000_000); > let start = Instant::now(); > for _ in 0 .. 10_000_000 { > arr.push("hello world"); > } > let end = start.elapsed(); > let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as u64) as > f64/1000000000.; > println!("{} took {}",arr.len(),diff); > let mut str = String::new(); > str.reserve(110_000_000); > let start = Instant::now(); > for i in arr { > str .push_str(i); > } > let end = start.elapsed(); > let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as u64) as > f64/1000000000.; > println!("{} took {}",str.len(),diff); > } > > c++: > > #include > #include > > > int main() { > std::string tmp; > tmp.reserve(110000000); > for (int i=0;i<10000000;i++) { > tmp += "hello world"; > } > } > > Model name: Intel(R) Core(TM) i3-5005U CPU @ 2.00GHz > > On 07/12/2016 05:36 AM, William Yager wrote: > > You picked the single slowest way to do it. Please see > https://gist.github.com/wyager/df063ad4edd9a9c8b0ab762c91a79894 > > All times are on my Intel Atom Macbook. Compiled with -O3, no other > options. > > Using Lazy Bytestrings (either through the Builder interface or plain old > concatenation) is about 7-7.5 times faster than string concatenation so on > your computer it should take about 0.12 seconds. In other words, faster > than C. > > This is my usual experience with lazy bytestrings; due to their > optimization for cache size, they are extremely fast with almost no effort. > They often out-perform "fast" array operations in C due to fusion and cache > coherency. > > I will note that if you want to do exactly what C does (often with only > slightly different assembly output), you can often achieve this with > unboxed vectors (mutable or immutable, depending on your application). > > --Will > > On Mon, Jul 11, 2016 at 10:24 PM, Richard A. O'Keefe > wrote: >> >> >> Making a list of "Hello world" 10,000,000 times and then >> concatenating that list to produce a single String took >> 0.87 seconds (start program to end program) in Haskell. >> > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to:http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From branimir.maksimovic at gmail.com Thu Jul 14 04:56:08 2016 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Thu, 14 Jul 2016 06:56:08 +0200 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: References: <7172e6b3-1318-828f-a7f7-a58a6e8e435d@gmail.com> Message-ID: <5bd853cb-4d7c-a9b9-59a8-99c6aecb20d0@gmail.com> Isn't that how suppose to be? 10000000 "hello worlds" ? On 07/14/2016 06:42 AM, Geraldus wrote: > Your rust version pushes only 10'000'000 strings from arr into str, > doesn't it? > > ср, 13 июл. 2016 г. в 16:41, Branimir Maksimovic > >: > > rust (no need for array but anyway) > > [bmaxa at manjaro rust]$ time ./append > 10000000 took 0.064016791 > 110000000 took 0.13466229 > > real 0m0.204s > user 0m0.167s > sys 0m0.033s > > haskell (your fastest version) > > [bmaxa at manjaro rust]$ time ./concat > "Done" > > real 0m0.224s > user 0m0.220s > sys 0m0.000s > > c++ (no array) > > [bmaxa at manjaro rust]$ time ./a.out > > real 0m0.115s > user 0m0.100s > sys 0m0.013s > > rust: > > use std::time::*; > > fn main() { > let mut arr=Vec::new(); > arr.reserve(10_000_000); > let start = Instant::now(); > for _ in 0 .. 10_000_000 { > arr.push("hello world"); > } > let end = start.elapsed(); > let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as > u64) as f64/1000000000.; > println!("{} took {}",arr.len(),diff); > let mut str = String::new(); > str.reserve(110_000_000); > let start = Instant::now(); > for i in arr { > str .push_str(i); > } > let end = start.elapsed(); > let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as > u64) as f64/1000000000.; > println!("{} took {}",str.len(),diff); > } > > c++: > > #include > #include > > > int main() { > std::string tmp; > tmp.reserve(110000000); > for (int i=0;i<10000000;i++) { > tmp += "hello world"; > } > } > > Model name: Intel(R) Core(TM) i3-5005U CPU @ 2.00GHz > > > On 07/12/2016 05:36 AM, William Yager wrote: >> You picked the single slowest way to do it. Please see >> https://gist.github.com/wyager/df063ad4edd9a9c8b0ab762c91a79894 >> >> All times are on my Intel Atom Macbook. Compiled with -O3, no >> other options. >> >> Using Lazy Bytestrings (either through the Builder interface or >> plain old concatenation) is about 7-7.5 times faster than string >> concatenation so on your computer it should take about 0.12 >> seconds. In other words, faster than C. >> >> This is my usual experience with lazy bytestrings; due to their >> optimization for cache size, they are extremely fast with almost >> no effort. They often out-perform "fast" array operations in C >> due to fusion and cache coherency. >> >> I will note that if you want to do exactly what C does (often >> with only slightly different assembly output), you can often >> achieve this with unboxed vectors (mutable or immutable, >> depending on your application). >> >> --Will >> >> On Mon, Jul 11, 2016 at 10:24 PM, Richard A. O'Keefe >> > wrote: >> >> >> Making a list of "Hello world" 10,000,000 times and then >> concatenating that list to produce a single String took >> 0.87 seconds (start program to end program) in Haskell. >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From heraldhoi at gmail.com Thu Jul 14 05:10:57 2016 From: heraldhoi at gmail.com (Geraldus) Date: Thu, 14 Jul 2016 05:10:57 +0000 Subject: [Haskell-cafe] Is the #functional programming paradigm antithetical to efficient strings? #Haskell In-Reply-To: <5bd853cb-4d7c-a9b9-59a8-99c6aecb20d0@gmail.com> References: <7172e6b3-1318-828f-a7f7-a58a6e8e435d@gmail.com> <5bd853cb-4d7c-a9b9-59a8-99c6aecb20d0@gmail.com> Message-ID: Oh, sorry, yes it. чт, 14 июл. 2016 г. в 9:56, Branimir Maksimovic < branimir.maksimovic at gmail.com>: > Isn't that how suppose to be? 10000000 "hello worlds" ? > > On 07/14/2016 06:42 AM, Geraldus wrote: > > Your rust version pushes only 10'000'000 strings from arr into str, > doesn't it? > > ср, 13 июл. 2016 г. в 16:41, Branimir Maksimovic < > branimir.maksimovic at gmail.com>: > >> rust (no need for array but anyway) >> >> [bmaxa at manjaro rust]$ time ./append >> 10000000 took 0.064016791 >> 110000000 took 0.13466229 >> >> real 0m0.204s >> user 0m0.167s >> sys 0m0.033s >> >> haskell (your fastest version) >> >> [bmaxa at manjaro rust]$ time ./concat >> "Done" >> >> real 0m0.224s >> user 0m0.220s >> sys 0m0.000s >> >> c++ (no array) >> >> [bmaxa at manjaro rust]$ time ./a.out >> >> real 0m0.115s >> user 0m0.100s >> sys 0m0.013s >> >> rust: >> >> use std::time::*; >> >> fn main() { >> let mut arr=Vec::new(); >> arr.reserve(10_000_000); >> let start = Instant::now(); >> for _ in 0 .. 10_000_000 { >> arr.push("hello world"); >> } >> let end = start.elapsed(); >> let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as u64) as >> f64/1000000000.; >> println!("{} took {}",arr.len(),diff); >> let mut str = String::new(); >> str.reserve(110_000_000); >> let start = Instant::now(); >> for i in arr { >> str .push_str(i); >> } >> let end = start.elapsed(); >> let diff = (end.as_secs()*1000000000 + end.subsec_nanos() as u64) as >> f64/1000000000.; >> println!("{} took {}",str.len(),diff); >> } >> >> c++: >> >> #include >> #include >> >> >> int main() { >> std::string tmp; >> tmp.reserve(110000000); >> for (int i=0;i<10000000;i++) { >> tmp += "hello world"; >> } >> } >> >> Model name: Intel(R) Core(TM) i3-5005U CPU @ 2.00GHz >> >> On 07/12/2016 05:36 AM, William Yager wrote: >> >> You picked the single slowest way to do it. Please see >> https://gist.github.com/wyager/df063ad4edd9a9c8b0ab762c91a79894 >> >> All times are on my Intel Atom Macbook. Compiled with -O3, no other >> options. >> >> Using Lazy Bytestrings (either through the Builder interface or plain old >> concatenation) is about 7-7.5 times faster than string concatenation so on >> your computer it should take about 0.12 seconds. In other words, faster >> than C. >> >> This is my usual experience with lazy bytestrings; due to their >> optimization for cache size, they are extremely fast with almost no effort. >> They often out-perform "fast" array operations in C due to fusion and cache >> coherency. >> >> I will note that if you want to do exactly what C does (often with only >> slightly different assembly output), you can often achieve this with >> unboxed vectors (mutable or immutable, depending on your application). >> >> --Will >> >> On Mon, Jul 11, 2016 at 10:24 PM, Richard A. O'Keefe >> wrote: >>> >>> >>> Making a list of "Hello world" 10,000,000 times and then >>> concatenating that list to produce a single String took >>> 0.87 seconds (start program to end program) in Haskell. >>> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to:http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ch.howard at zoho.com Thu Jul 14 06:07:32 2016 From: ch.howard at zoho.com (Christopher Howard) Date: Wed, 13 Jul 2016 22:07:32 -0800 Subject: [Haskell-cafe] efficient operations on immutable structures Message-ID: <57872C24.3000204@zoho.com> Hi again all. From some online research, I understand that operations on complex immutable structures (for example, a "setter" function a -> (Int, Int) -> Matrix -> Matrix which alters one element in the Matrix) is not necessarily inefficient in Haskell, because the (compiler? runtime?) has some means of sharing unchanged values between the input and output structure. What I am not clear on, however, is how this works, and how you ensure that this happens. Could someone perhaps elaborate, or point me to a really good read on the subject? -- http://qlfiles.net To protect my privacy, please use PGP encryption. It's free and easy to use! My public key ID is 0x340EA95A (pgp.mit.edu). From spam at scientician.net Thu Jul 14 06:27:35 2016 From: spam at scientician.net (Bardur Arantsson) Date: Thu, 14 Jul 2016 08:27:35 +0200 Subject: [Haskell-cafe] efficient operations on immutable structures In-Reply-To: <57872C24.3000204@zoho.com> References: <57872C24.3000204@zoho.com> Message-ID: On 07/14/2016 08:07 AM, Christopher Howard wrote: > Hi again all. From some online research, I understand that operations on > complex immutable structures (for example, a "setter" function a -> > (Int, Int) -> Matrix -> Matrix which alters one element in the Matrix) > is not necessarily inefficient in Haskell, because the (compiler? > runtime?) has some means of sharing unchanged values between the input > and output structure. What I am not clear on, however, is how this > works, and how you ensure that this happens. Could someone perhaps > elaborate, or point me to a really good read on the subject? > https://en.wikipedia.org/wiki/Persistent_data_structure See in particular the section "Trees". (It basically works the same for records; just imagine that a record is a 2-level tree, where each field/label in the record is an edge from the "field label" to the "field value". Multiple levels of records work essentially work the same as multi-level trees do.) From tdammers at gmail.com Thu Jul 14 07:24:29 2016 From: tdammers at gmail.com (Tobias Dammers) Date: Thu, 14 Jul 2016 09:24:29 +0200 Subject: [Haskell-cafe] How to support multiple string types in Haskell? In-Reply-To: <1468457891-sup-4775@sabre> References: <1468457891-sup-4775@sabre> Message-ID: In my experience, it is usually a more pragmatic solution to pick the string type that is most suitable for the library's purposes, and leave conversions to the consumer. In practice, the choice is typically between strict and lazy Text only: bytestrings do not represent strings but byte arrays, so they are not suitable for textual data; and String has atrocious performance, unless the use case is just linear character-wise traversal (and even then, lazy Texts are probably still a better choice). I would only choose String if my library were closely related to another library that has already picked String, and converting to and from Text would introduce a lot of overhead. The downside of making your API polymorphic is that you will often find yourself having to type-annotate to disambiguate (foo . (bar :: Int -> Text) $ n), or introduce type-binding dummy functions (foo . asText . bar $ n). Another downside is that there is no canonical "StringLike" typeclass, so you either have to write your own, or pick one as a dependency. That said, there are a few libraries out there that aim to make the Haskell string situation less painful, including my own string-convert. They all differ in a few details, it mostly comes down to preference. On Jul 14, 2016 3:00 AM, "Edward Z. Yang" wrote: > Hello KwangYul, > > Supporting this sort of parametricity is one of the goals of the > Backpack project. You can see some code that demonstrates > how this might be done: > https://github.com/yihuang/tagstream-conduit/pull/18 > Maybe you'll get to use this feature in GHC 8.2! > > A big problem with StringLike type classes is that you must > pre-commit to the set of operations which are supported before > hand. For strings, there are many, many such operations, and it is > difficult to agree a priori what these operations should be. > > Edward > > Excerpts from KwangYul Seo's message of 2016-07-13 17:40:13 -0700: > > Hi all, > > > > There are multiple string types in Haskell – String, lazy/strict > > ByteString, lazy/strict Text to name a few. So to make a string handling > > function maximally reusable, it needs to support multiple string types. > > > > One approach used by TagSoup library is to make a type class StringLike > > which represents the polymorphic string type and uses it where a String > > type is normally needed. For example, > > > > parseTags :: StringLike str => str -> [Tag str] > > > > Here parseTags takes a StringLike type instead of a fixed string type. > > Users of TagSoup can pick any of String, lazy/strict ByteString, > > lazy/strict Text because they are all instances of StringLike type class. > > > > It seems StringLike type class is quite generic but it is used only in > the > > TagSoup package. This makes me wonder what is the idiomatic way to > support > > multiple string types in Haskell. What other approaches do we have? > > > > Thanks, > > Kwang Yul Seo > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tdammers at gmail.com Thu Jul 14 07:29:42 2016 From: tdammers at gmail.com (Tobias Dammers) Date: Thu, 14 Jul 2016 09:29:42 +0200 Subject: [Haskell-cafe] efficient operations on immutable structures In-Reply-To: References: <57872C24.3000204@zoho.com> Message-ID: Another trick is lazy evaluation. Rather than building the actual data structure fully, Haskell creates a thunk, that is, it keeps a reference to a recipe that, when evaluated, will produce the desired value. And it does this recursively. So when you say let foo = Foo bar baz, neither bar nor baz are necessarily evaluated at all, you just get a recipe for a Foo based on two other recipes for its fields. Creating another Foo based on this one, but with one field swapped out for a different value, merely created a new recipe, and evaluating the new data structure will not descend into the field values that are no longer used in the recipe. This stuff takes a while to settle in, but it's actually quite neat. On Jul 14, 2016 8:27 AM, "Bardur Arantsson" wrote: > On 07/14/2016 08:07 AM, Christopher Howard wrote: > > Hi again all. From some online research, I understand that operations on > > complex immutable structures (for example, a "setter" function a -> > > (Int, Int) -> Matrix -> Matrix which alters one element in the Matrix) > > is not necessarily inefficient in Haskell, because the (compiler? > > runtime?) has some means of sharing unchanged values between the input > > and output structure. What I am not clear on, however, is how this > > works, and how you ensure that this happens. Could someone perhaps > > elaborate, or point me to a really good read on the subject? > > > > https://en.wikipedia.org/wiki/Persistent_data_structure > > See in particular the section "Trees". (It basically works the same for > records; just imagine that a record is a 2-level tree, where each > field/label in the record is an edge from the "field label" to the > "field value". Multiple levels of records work essentially work the same > as multi-level trees do.) > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From palotai.robin at gmail.com Thu Jul 14 07:45:33 2016 From: palotai.robin at gmail.com (Robin Palotai) Date: Thu, 14 Jul 2016 07:45:33 +0000 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> Message-ID: For deepseq also see the"Once trick". I'm surprised it's not quoted more often. In fact our would make sense to mention it in the deepseq docs. On Wed, Jul 13, 2016, 21:32 David Feuer wrote: > You have to be careful with deepseq. Using it in the wrong place can > lead to very bad performance. It's a big hammer. Its blow can > sometimes be softened using the NF type from the nf package, but it's > really not the right thing most of the time. > > On Tue, Jul 12, 2016 at 11:56 PM, William Yager > wrote: > > You probably want Control.DeepSeq. No extraneous work doing addition that > > way either. > > > > Will > > > > On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard > > > wrote: > >> > >> After pondering this problem some more, I found a solution to the > >> problem was to introduce strictness, not deep down in the StateReader > >> monad, but rather at the top level, i.e., forcing evaluation of each > >> Matrix as soon as it is pulled of the list of Matrices. I found I could > >> do this simply by summing all the elements in each matrix and printing > >> the sum to std out. With this approach, i successfully run the full > >> program and never even saw my memory performance graph move up. > >> > >> I suppose there might be a way to do the same thing more efficiently > >> with seq...? > >> > >> On 07/12/2016 06:39 PM, Christopher Howard wrote: > >> > I guess I was hesitating on posting the entire program source code in > an > >> > cafe email. I suppose I could send you a tarball, if you really wanted > >> > it... > >> > > >> > Matrix is from Data.Matrix > >> > > >> > < > http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>. > >> > > >> > It is hard to understand how thunks alone would explain it... there > >> > would be at most 2000 thunks, right? Unless... Could there be a thunk > >> > for every single call to getElem? That would be a lot of thunks! > >> > > >> > Somebody suggested adding some strictness here... could you elaborate > on > >> > that? I tried inserting seq, but I didn't really understand how I was > >> > supposed to use it... > >> > > >> > >> -- > >> http://qlfiles.net > >> To protect my privacy, please use PGP encryption. It's free and easy > >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> To (un)subscribe, modify options or view archives go to: > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >> Only members subscribed via the mailman list are allowed to post. > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Thu Jul 14 07:56:32 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 14 Jul 2016 08:56:32 +0100 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> Message-ID: <20160714075632.GE16574@weber> Yes, this is a very neat trick and very effective. (I couldn't acutally find it on Hoogle. Does anyone have a link?) On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote: > For deepseq also see the"Once trick". I'm surprised it's not quoted more > often. In fact our would make sense to mention it in the deepseq docs. > > On Wed, Jul 13, 2016, 21:32 David Feuer wrote: > > > You have to be careful with deepseq. Using it in the wrong place can > > lead to very bad performance. It's a big hammer. Its blow can > > sometimes be softened using the NF type from the nf package, but it's > > really not the right thing most of the time. > > > > On Tue, Jul 12, 2016 at 11:56 PM, William Yager > > wrote: > > > You probably want Control.DeepSeq. No extraneous work doing addition that > > > way either. > > > > > > Will > > > > > > On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard > > > > > wrote: > > >> > > >> After pondering this problem some more, I found a solution to the > > >> problem was to introduce strictness, not deep down in the StateReader > > >> monad, but rather at the top level, i.e., forcing evaluation of each > > >> Matrix as soon as it is pulled of the list of Matrices. I found I could > > >> do this simply by summing all the elements in each matrix and printing > > >> the sum to std out. With this approach, i successfully run the full > > >> program and never even saw my memory performance graph move up. > > >> > > >> I suppose there might be a way to do the same thing more efficiently > > >> with seq...? > > >> > > >> On 07/12/2016 06:39 PM, Christopher Howard wrote: > > >> > I guess I was hesitating on posting the entire program source code in > > an > > >> > cafe email. I suppose I could send you a tarball, if you really wanted > > >> > it... > > >> > > > >> > Matrix is from Data.Matrix > > >> > > > >> > < > > http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>. > > >> > > > >> > It is hard to understand how thunks alone would explain it... there > > >> > would be at most 2000 thunks, right? Unless... Could there be a thunk > > >> > for every single call to getElem? That would be a lot of thunks! > > >> > > > >> > Somebody suggested adding some strictness here... could you elaborate > > on > > >> > that? I tried inserting seq, but I didn't really understand how I was > > >> > supposed to use it... > > >> > > > >> > > >> -- > > >> http://qlfiles.net > > >> To protect my privacy, please use PGP encryption. It's free and easy > > >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > >> > > >> _______________________________________________ > > >> Haskell-Cafe mailing list > > >> To (un)subscribe, modify options or view archives go to: > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >> Only members subscribed via the mailman list are allowed to post. > > > > > > > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. From mattjbray at gmail.com Thu Jul 14 08:32:25 2016 From: mattjbray at gmail.com (Matthew Bray) Date: Thu, 14 Jul 2016 08:32:25 +0000 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: <20160714075632.GE16574@weber> References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> <20160714075632.GE16574@weber> Message-ID: https://www.schoolofhaskell.com/user/edwardk/snippets/once Cool trick :) On Thu, 14 Jul 2016 at 08:56 Tom Ellis < tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote: > Yes, this is a very neat trick and very effective. (I couldn't acutally > find it on Hoogle. Does anyone have a link?) > > On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote: > > For deepseq also see the"Once trick". I'm surprised it's not quoted more > > often. In fact our would make sense to mention it in the deepseq docs. > > > > On Wed, Jul 13, 2016, 21:32 David Feuer wrote: > > > > > You have to be careful with deepseq. Using it in the wrong place can > > > lead to very bad performance. It's a big hammer. Its blow can > > > sometimes be softened using the NF type from the nf package, but it's > > > really not the right thing most of the time. > > > > > > On Tue, Jul 12, 2016 at 11:56 PM, William Yager > > > wrote: > > > > You probably want Control.DeepSeq. No extraneous work doing addition > that > > > > way either. > > > > > > > > Will > > > > > > > > On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard < > ch.howard at zoho.com > > > > > > > > wrote: > > > >> > > > >> After pondering this problem some more, I found a solution to the > > > >> problem was to introduce strictness, not deep down in the > StateReader > > > >> monad, but rather at the top level, i.e., forcing evaluation of each > > > >> Matrix as soon as it is pulled of the list of Matrices. I found I > could > > > >> do this simply by summing all the elements in each matrix and > printing > > > >> the sum to std out. With this approach, i successfully run the full > > > >> program and never even saw my memory performance graph move up. > > > >> > > > >> I suppose there might be a way to do the same thing more efficiently > > > >> with seq...? > > > >> > > > >> On 07/12/2016 06:39 PM, Christopher Howard wrote: > > > >> > I guess I was hesitating on posting the entire program source > code in > > > an > > > >> > cafe email. I suppose I could send you a tarball, if you really > wanted > > > >> > it... > > > >> > > > > >> > Matrix is from Data.Matrix > > > >> > > > > >> > < > > > > http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>. > > > >> > > > > >> > It is hard to understand how thunks alone would explain it... > there > > > >> > would be at most 2000 thunks, right? Unless... Could there be a > thunk > > > >> > for every single call to getElem? That would be a lot of thunks! > > > >> > > > > >> > Somebody suggested adding some strictness here... could you > elaborate > > > on > > > >> > that? I tried inserting seq, but I didn't really understand how I > was > > > >> > supposed to use it... > > > >> > > > > >> > > > >> -- > > > >> http://qlfiles.net > > > >> To protect my privacy, please use PGP encryption. It's free and easy > > > >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). > > > >> > > > >> _______________________________________________ > > > >> Haskell-Cafe mailing list > > > >> To (un)subscribe, modify options or view archives go to: > > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > >> Only members subscribed via the mailman list are allowed to post. > > > > > > > > > > > > > > > > _______________________________________________ > > > > Haskell-Cafe mailing list > > > > To (un)subscribe, modify options or view archives go to: > > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > Only members subscribed via the mailman list are allowed to post. > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ruben.astud at gmail.com Thu Jul 14 09:48:18 2016 From: ruben.astud at gmail.com (Ruben Astudillo) Date: Thu, 14 Jul 2016 05:48:18 -0400 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> Message-ID: <1e66ce8c-b2bc-206e-0302-353e821d953e@gmail.com> On 13/07/16 14:54, Andrey Sverdlichenko wrote: > If you are lucky. They still may be merged by sender if retransmission > occurs, or on receiving side, if receiver waits too long before reads, and > this is up to OS scheduler to control. > NDELAY option is used to improve interactive latency, it will not make TCP > obey message boundaries. You're right. But understanding a little better the problem maybe will clarify why NODELAY is a valid option. DCC is in parts a redundant protocol. When you connect, the senders gives you the file you want but for coherency reasons every once in a while you have to reply the current transfered size through the same socket. This was a mean of preserving consistency that is redundant by the same mechanisms implemented on TCP. From the page[1] I am using to implement ``client A sends blocks of data (usually 1-2 KB) and at every block awaits confirmation from the client B, that when receiving a block should reply 4 bytes containing an positive number specifying the total size of the file received up to that moment. The transmission closes when the last acknowledge is received by client A. The acknowledges were meant to include some sort of coherency check in the transmission, but in fact no client can recover from an acknowledge error/desync, all of them just close the connection declaring the transfer as failed (the situation is even worse in fact, often acknowledge errors aren't even detected!). Since the packet-acknowledge round trip eats a lot of time, many clients included the send-ahead feature; the client A does not wait for the acknowledge of the first packet before sending the second one.'' The last part explains why my download still succeded until half the size of the file. But no sending any reply (because the message is too little to send) is a failure of interactivity on the protocol, not of message boundaries (which specify that the reply is 4 byte in length). [1]: http://www.kvirc.net/doc/doc_dcc_connection.html -- -- Ruben Astudillo From dct25-561bs at mythic-beasts.com Thu Jul 14 12:55:37 2016 From: dct25-561bs at mythic-beasts.com (David Turner) Date: Thu, 14 Jul 2016 13:55:37 +0100 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: <1e66ce8c-b2bc-206e-0302-353e821d953e@gmail.com> References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> <1e66ce8c-b2bc-206e-0302-353e821d953e@gmail.com> Message-ID: Hi Ruben, I think you're falling into a common trap re. TCP. On a lightly-loaded network, if you send a block of data on one host it typically arrives at the other end of the connection as one thing. In other words, calls to send() and recv() are one-to-one. In that situation adding NODELAY will (seem to) solve problems like the ones that you were seeing. However, it will all fall to pieces when you're running under load or there's congestion or some other kind of problem, as it's perfectly legitimate for packets to be combined and/or fragmented which breaks this one-to-one relationship on which the correctness of your program rests. You _must_ treat data received over TCP as a continuous stream of bytes and not a sequence of discrete packets, and do things such as accounting for the case where your 4-byte length indicator is split across two packets so does not all arrive at once. If you don't, it will bite you at the very worst time, and will do so nondeterministically. This kind of thing is very hard to reproduce in a test environment. There is nothing special about the DCC protocol that makes it immune from this effect. Best wishes, David On 14 July 2016 at 10:48, Ruben Astudillo wrote: > On 13/07/16 14:54, Andrey Sverdlichenko wrote: > >> If you are lucky. They still may be merged by sender if retransmission >> occurs, or on receiving side, if receiver waits too long before reads, and >> this is up to OS scheduler to control. >> NDELAY option is used to improve interactive latency, it will not make TCP >> obey message boundaries. >> > > You're right. But understanding a little better the problem maybe will > clarify why NODELAY is a valid option. DCC is in parts a redundant > protocol. When you connect, the senders gives you the file you want but > for coherency reasons every once in a while you have to reply the current > transfered size through the same socket. This was a mean of preserving > consistency that is redundant by the same mechanisms implemented on TCP. > From the page[1] I am using to implement > > ``client A sends blocks of data (usually 1-2 KB) and at every block > awaits > confirmation from the client B, that when receiving a block should reply > 4 bytes containing an positive number specifying the total size of the > file received up to that moment. > > The transmission closes when the last acknowledge is received by client > A. > > The acknowledges were meant to include some sort of coherency check in > the transmission, but in fact no client can recover from an acknowledge > error/desync, all of them just close the connection declaring the > transfer as failed (the situation is even worse in fact, often > acknowledge errors aren't even detected!). > > Since the packet-acknowledge round trip eats a lot of time, many clients > included the send-ahead feature; the client A does not wait for the > acknowledge of the first packet before sending the second one.'' > > The last part explains why my download still succeded until half the size > of the file. But no sending any reply (because the message is too little > to send) is a failure of interactivity on the protocol, not of message > boundaries (which specify that the reply is 4 byte in length). > > [1]: http://www.kvirc.net/doc/doc_dcc_connection.html > -- > -- Ruben Astudillo > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hon.lianhung at gmail.com Thu Jul 14 15:43:40 2016 From: hon.lianhung at gmail.com (Lian Hung Hon) Date: Thu, 14 Jul 2016 23:43:40 +0800 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> <20160714075632.GE16574@weber> Message-ID: I faced the same problem in an RWS monad, where adding a print to the evalRWS resolves the space leak. Obviously, it's not very elegant to clutter the output. I tried the unsafeInterleaveIO (works sometimes), seq/deepseq (works on Windows but not on Linux??), strictness annotations (didn't seem to help at all?), but finally settled on using pipes/conduit. It's remarkable how a streaming library is more practical than the language's core feature - laziness. On 14 July 2016 at 16:32, Matthew Bray wrote: > https://www.schoolofhaskell.com/user/edwardk/snippets/once > > Cool trick :) > > On Thu, 14 Jul 2016 at 08:56 Tom Ellis < > tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote: > >> Yes, this is a very neat trick and very effective. (I couldn't acutally >> find it on Hoogle. Does anyone have a link?) >> >> On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote: >> > For deepseq also see the"Once trick". I'm surprised it's not quoted more >> > often. In fact our would make sense to mention it in the deepseq docs. >> > >> > On Wed, Jul 13, 2016, 21:32 David Feuer wrote: >> > >> > > You have to be careful with deepseq. Using it in the wrong place can >> > > lead to very bad performance. It's a big hammer. Its blow can >> > > sometimes be softened using the NF type from the nf package, but it's >> > > really not the right thing most of the time. >> > > >> > > On Tue, Jul 12, 2016 at 11:56 PM, William Yager > > >> > > wrote: >> > > > You probably want Control.DeepSeq. No extraneous work doing >> addition that >> > > > way either. >> > > > >> > > > Will >> > > > >> > > > On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard < >> ch.howard at zoho.com >> > > > >> > > > wrote: >> > > >> >> > > >> After pondering this problem some more, I found a solution to the >> > > >> problem was to introduce strictness, not deep down in the >> StateReader >> > > >> monad, but rather at the top level, i.e., forcing evaluation of >> each >> > > >> Matrix as soon as it is pulled of the list of Matrices. I found I >> could >> > > >> do this simply by summing all the elements in each matrix and >> printing >> > > >> the sum to std out. With this approach, i successfully run the full >> > > >> program and never even saw my memory performance graph move up. >> > > >> >> > > >> I suppose there might be a way to do the same thing more >> efficiently >> > > >> with seq...? >> > > >> >> > > >> On 07/12/2016 06:39 PM, Christopher Howard wrote: >> > > >> > I guess I was hesitating on posting the entire program source >> code in >> > > an >> > > >> > cafe email. I suppose I could send you a tarball, if you really >> wanted >> > > >> > it... >> > > >> > >> > > >> > Matrix is from Data.Matrix >> > > >> > >> > > >> > < >> > > >> http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>. >> > > >> > >> > > >> > It is hard to understand how thunks alone would explain it... >> there >> > > >> > would be at most 2000 thunks, right? Unless... Could there be a >> thunk >> > > >> > for every single call to getElem? That would be a lot of thunks! >> > > >> > >> > > >> > Somebody suggested adding some strictness here... could you >> elaborate >> > > on >> > > >> > that? I tried inserting seq, but I didn't really understand how >> I was >> > > >> > supposed to use it... >> > > >> > >> > > >> >> > > >> -- >> > > >> http://qlfiles.net >> > > >> To protect my privacy, please use PGP encryption. It's free and >> easy >> > > >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). >> > > >> >> > > >> _______________________________________________ >> > > >> Haskell-Cafe mailing list >> > > >> To (un)subscribe, modify options or view archives go to: >> > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > >> Only members subscribed via the mailman list are allowed to post. >> > > > >> > > > >> > > > >> > > > _______________________________________________ >> > > > Haskell-Cafe mailing list >> > > > To (un)subscribe, modify options or view archives go to: >> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > > Only members subscribed via the mailman list are allowed to post. >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > To (un)subscribe, modify options or view archives go to: >> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > Only members subscribed via the mailman list are allowed to post. >> >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > To (un)subscribe, modify options or view archives go to: >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From will.yager at gmail.com Thu Jul 14 17:50:18 2016 From: will.yager at gmail.com (Will Yager) Date: Thu, 14 Jul 2016 13:50:18 -0400 Subject: [Haskell-cafe] Memory Management and Lists In-Reply-To: References: <57826CAB.50302@zoho.com> <20160710183004.GF3616@weber> <5783B4C4.70902@zoho.com> <20160712184058.GH11559@weber> <5785A9F9.2060006@zoho.com> <5785B545.5000206@zoho.com> <20160714075632.GE16574@weber> Message-ID: <9E7E734C-4FAA-43B3-9CC2-89A573E1CEFF@gmail.com> See http://comments.gmane.org/gmane.comp.lang.haskell.libraries/18980 The W part of RWS is bad for performance. Best approach is to implement R, W, and S using a strict StateT. Will > On Jul 14, 2016, at 11:43, Lian Hung Hon wrote: > > I faced the same problem in an RWS monad, where adding a print to the evalRWS resolves the space leak. Obviously, it's not very elegant to clutter the output. I tried the unsafeInterleaveIO (works sometimes), seq/deepseq (works on Windows but not on Linux??), strictness annotations (didn't seem to help at all?), but finally settled on using pipes/conduit. It's remarkable how a streaming library is more practical than the language's core feature - laziness. > >> On 14 July 2016 at 16:32, Matthew Bray wrote: >> https://www.schoolofhaskell.com/user/edwardk/snippets/once >> >> Cool trick :) >> >>> On Thu, 14 Jul 2016 at 08:56 Tom Ellis wrote: >>> Yes, this is a very neat trick and very effective. (I couldn't acutally >>> find it on Hoogle. Does anyone have a link?) >>> >>> On Thu, Jul 14, 2016 at 07:45:33AM +0000, Robin Palotai wrote: >>> > For deepseq also see the"Once trick". I'm surprised it's not quoted more >>> > often. In fact our would make sense to mention it in the deepseq docs. >>> > >>> > On Wed, Jul 13, 2016, 21:32 David Feuer wrote: >>> > >>> > > You have to be careful with deepseq. Using it in the wrong place can >>> > > lead to very bad performance. It's a big hammer. Its blow can >>> > > sometimes be softened using the NF type from the nf package, but it's >>> > > really not the right thing most of the time. >>> > > >>> > > On Tue, Jul 12, 2016 at 11:56 PM, William Yager >>> > > wrote: >>> > > > You probably want Control.DeepSeq. No extraneous work doing addition that >>> > > > way either. >>> > > > >>> > > > Will >>> > > > >>> > > > On Tue, Jul 12, 2016 at 11:28 PM, Christopher Howard >> > > > >>> > > > wrote: >>> > > >> >>> > > >> After pondering this problem some more, I found a solution to the >>> > > >> problem was to introduce strictness, not deep down in the StateReader >>> > > >> monad, but rather at the top level, i.e., forcing evaluation of each >>> > > >> Matrix as soon as it is pulled of the list of Matrices. I found I could >>> > > >> do this simply by summing all the elements in each matrix and printing >>> > > >> the sum to std out. With this approach, i successfully run the full >>> > > >> program and never even saw my memory performance graph move up. >>> > > >> >>> > > >> I suppose there might be a way to do the same thing more efficiently >>> > > >> with seq...? >>> > > >> >>> > > >> On 07/12/2016 06:39 PM, Christopher Howard wrote: >>> > > >> > I guess I was hesitating on posting the entire program source code in >>> > > an >>> > > >> > cafe email. I suppose I could send you a tarball, if you really wanted >>> > > >> > it... >>> > > >> > >>> > > >> > Matrix is from Data.Matrix >>> > > >> > >>> > > >> > < >>> > > http://hackage.haskell.org/package/matrix-0.3.5.0/docs/Data-Matrix.html>. >>> > > >> > >>> > > >> > It is hard to understand how thunks alone would explain it... there >>> > > >> > would be at most 2000 thunks, right? Unless... Could there be a thunk >>> > > >> > for every single call to getElem? That would be a lot of thunks! >>> > > >> > >>> > > >> > Somebody suggested adding some strictness here... could you elaborate >>> > > on >>> > > >> > that? I tried inserting seq, but I didn't really understand how I was >>> > > >> > supposed to use it... >>> > > >> > >>> > > >> >>> > > >> -- >>> > > >> http://qlfiles.net >>> > > >> To protect my privacy, please use PGP encryption. It's free and easy >>> > > >> to use! My public key ID is 0x340EA95A (pgp.mit.edu). >>> > > >> >>> > > >> _______________________________________________ >>> > > >> Haskell-Cafe mailing list >>> > > >> To (un)subscribe, modify options or view archives go to: >>> > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > > >> Only members subscribed via the mailman list are allowed to post. >>> > > > >>> > > > >>> > > > >>> > > > _______________________________________________ >>> > > > Haskell-Cafe mailing list >>> > > > To (un)subscribe, modify options or view archives go to: >>> > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > > > Only members subscribed via the mailman list are allowed to post. >>> > > _______________________________________________ >>> > > Haskell-Cafe mailing list >>> > > To (un)subscribe, modify options or view archives go to: >>> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > > Only members subscribed via the mailman list are allowed to post. >>> >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > To (un)subscribe, modify options or view archives go to: >>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > Only members subscribed via the mailman list are allowed to post. >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From mblazevic at stilo.com Thu Jul 14 18:13:53 2016 From: mblazevic at stilo.com (Mario Blazevic) Date: Thu, 14 Jul 2016 14:13:53 -0400 Subject: [Haskell-cafe] How to support multiple string types in Haskell? In-Reply-To: References: Message-ID: On Wed, Jul 13, 2016 at 8:40 PM, KwangYul Seo wrote: > Hi all, > > There are multiple string types in Haskell – String, lazy/strict > ByteString, lazy/strict Text to name a few. So to make a string handling > function maximally reusable, it needs to support multiple string types. > > ... > It seems StringLike type class is quite generic but it is used only in the > TagSoup package. This makes me wonder what is the idiomatic way to support > multiple string types in Haskell. What other approaches do we have? > StringLike is only one of the packages supplying the class or classes to support all the usual string types. There is also ListLike and (my own) monoid-subclasses. You can visit http://packdeps.haskellers.com/reverse to see all their reverse dependencies and see how they're used. -------------- next part -------------- An HTML attachment was scrubbed... URL: From blaze at ruddy.ru Thu Jul 14 19:34:18 2016 From: blaze at ruddy.ru (Andrey Sverdlichenko) Date: Thu, 14 Jul 2016 19:34:18 +0000 Subject: [Haskell-cafe] network package and SIGVTALRM In-Reply-To: <1e66ce8c-b2bc-206e-0302-353e821d953e@gmail.com> References: <4585475b-d3db-7b8e-5168-1506c9094ac7@gmail.com> <39622401-b8b9-894a-d604-4702e1b94e23@gmail.com> <1e66ce8c-b2bc-206e-0302-353e821d953e@gmail.com> Message-ID: > > The last part explains why my download still succeded until half the size > of the file. But no sending any reply (because the message is too little > to send) is a failure of interactivity on the protocol, not of message > boundaries (which specify that the reply is 4 byte in length). > TCP with Nagle algorithm enabled will not hold data infinitely. In fact, it only waits for a few tenths of a second, hoping there would be more data to send. If not, whatever it has is sent away. What your dumps show is a window announcement of size 0, which means there was a lot of data successfully received by TCP stack, but never read from socket, and this happens in both directions. You may want to check why you processes stop issuing read/recv calls. -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Thu Jul 14 22:19:23 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Fri, 15 Jul 2016 00:19:23 +0200 Subject: [Haskell-cafe] another instance of MonadError Message-ID: Hello, IO is an instance of MonadError IOException... However I also need to make it an instance of MonadError String... Is it possible? I'm trying to instanciate this class: class (Typeable n, Monad n, Applicative n, MonadError String n) => EvMgt n where ... instance EvMgt IO where... Any idea? -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Thu Jul 14 22:24:12 2016 From: david.feuer at gmail.com (David Feuer) Date: Thu, 14 Jul 2016 18:24:12 -0400 Subject: [Haskell-cafe] another instance of MonadError In-Reply-To: References: Message-ID: You can't do that; sorry. You can always turn a string into an IOException if you like. Or you could write a wrapper around IO. But MonadError has a functional dependency, so you can only have one error type per monad. On Jul 14, 2016 6:19 PM, "Corentin Dupont" wrote: Hello, IO is an instance of MonadError IOException... However I also need to make it an instance of MonadError String... Is it possible? I'm trying to instanciate this class: class (Typeable n, Monad n, Applicative n, MonadError String n) => EvMgt n where ... instance EvMgt IO where... Any idea? _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From rustompmody at gmail.com Sat Jul 16 03:22:21 2016 From: rustompmody at gmail.com (Rustom Mody) Date: Sat, 16 Jul 2016 08:52:21 +0530 Subject: [Haskell-cafe] Passing a cabal flag to stack Message-ID: I’ve been trying to compile hoodle following the instructions in the readme: https://github.com/wavewave/hoodle Went further than year or two earlier when attempt got mired in cabal-hell This time stack build went through (after a couple of deb packages needing installation) Now I get this error on trying to run GTK+ 2.x symbols detected. Using GTK+ 2.x and GTK+ 3 in the same process is not supported Asking on the hoodle mailing list I was told that one has to build poppler with option -fgtk3 Where/How to give that? Looking at https://github.com/commercialhaskell/stack/issues/191 I tried the following: 1. Delete every file/directory under .stack-work that has the word poppler 2. stack build poppler --flag gtk:gtk3 3. stack build Seems to have built Ok I get the same warning that stack seems to be generally giving — dozens of them — viz ============ No packages found in snapshot which provide a "gtk2hsC2hs" executable, which is a build-tool dependency of "glib" Missing build-tools may be caused by dependencies of the build-tool being overridden by extra-deps. This should be fixed soon - see this issue https://github.com/commercialhaskell/stack/issues/595 ============= But thereafter stack exec hoodle results in the same error. So whats the official way of putting the -fgtk3 flag into stack? Any other suggestions? stack first tried from deb; then redone from stack website $ ghc --version The Glorious Glasgow Haskell Compilation System, version 7.10.3 ubuntu 16.4 (if that matters) Thanks -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Sat Jul 16 04:18:07 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Sat, 16 Jul 2016 06:18:07 +0200 Subject: [Haskell-cafe] Passing a cabal flag to stack In-Reply-To: References: Message-ID: Hi! > So whats the official way of putting the -fgtk3 flag into stack? To pass that flag to poppler, the syntax is --flag poppler:gtk3 > 1. Delete every file/directory under .stack-work that has the word poppler That shouldn't be necessary. > 2. stack build poppler --flag gtk:gtk3 > 3. stack build It's best to be consistent about flag settings. It might be easiest to put them in your stack.yaml: http://docs.haskellstack.org/en/stable/yaml_configuration/#flags Hope that helps! Simon From rustompmody at gmail.com Sat Jul 16 04:32:19 2016 From: rustompmody at gmail.com (Rustom Mody) Date: Sat, 16 Jul 2016 10:02:19 +0530 Subject: [Haskell-cafe] Passing a cabal flag to stack In-Reply-To: References: Message-ID: On Sat, Jul 16, 2016 at 9:48 AM, Simon Jakobi wrote: > Hi! > > > So whats the official way of putting the -fgtk3 flag into stack? > > To pass that flag to poppler, the syntax is > > --flag poppler:gtk3 > When I try stack build --flag poppler:gtk3 I get ================= -- Failure when adding dependencies: hoodle-core: needed (>=0.15.0 && <0.16), couldn't resolve its dependencies needed for package hoodle-0.4.999 -- Failure when adding dependencies: hoodle-publish: needed (>=0.2), couldn't resolve its dependencies hoodle-render: needed (>=0.5.0 && <0.6), couldn't resolve its dependencies poppler: needed (>=0.12.2.2), couldn't resolve its dependencies needed for package hoodle-core-0.15.999 -- Failure when adding dependencies: hoodle-render: needed (>=0.5.0), couldn't resolve its dependencies needed for package hoodle-publish-0.2.0 -- Failure when adding dependencies: poppler: needed (>=0.12.2.2), couldn't resolve its dependencies needed for package hoodle-render-0.5.999 -- Failure when adding dependencies: gtk3: needed (>=0.13 && <0.14), 0.14.2 found (latest applicable is 0.13.9) needed for package poppler-0.13.1 with flags: gtk3: True ============= Happens whether I try more focussed: $ stack build poppler --flag poppler:gtk3 get ============= While constructing the BuildPlan the following exceptions were encountered: -- Failure when adding dependencies: gtk3: needed (>=0.13 && <0.14), 0.14.2 found (latest applicable is 0.13.9) needed for package poppler-0.13.1 with flags: gtk3: True ================ [In cut pasting Ive elided oodles of stuff like: No packages found in snapshot which provide a "gtk2hsC2hs" executable, which is a build-tool dependency of "glib" Missing build-tools may be caused by dependencies of the build-tool being overridden by extra-deps. This should be fixed soon - see this issue https://github.com/commercialhaskell/stack/issues/595 ] > > > 1. Delete every file/directory under .stack-work that has the word > poppler > > That shouldn't be necessary. > > > 2. stack build poppler --flag gtk:gtk3 > > 3. stack build > > It's best to be consistent about flag settings. It might be easiest to > put them in your stack.yaml: > http://docs.haskellstack.org/en/stable/yaml_configuration/#flags > > This is the stack.yaml (without comments) ======================= # This file was automatically generated by stack init # For more information, see: http://docs.haskellstack.org/en/stable/yaml_configuration/ # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) resolver: lts-5.8 # Local packages, usually specified by relative directory name packages: - coroutine-object/ - hoodle/ - hoodle-builder/ - hoodle-core/ - hoodle-daemon/ - hoodle-extra/ - hoodle-manage/ - hoodle-parser/ - hoodle-publish/ - hoodle-render/ - hoodle-types/ - xournal-parser/ - xournal-types/ # Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3) extra-deps: - TypeCompose-0.9.11 - aeson-0.11.1.1 - attoparsec-conduit-1.1.0 - gtk-0.13.9 - handa-gdata-0.7.0.3 - persistent-sqlite-2.2.1 - poppler-0.13.1 - svgcairo-0.13.0.4 - text-1.2.2.0 - transformers-free-1.0.1 - zlib-conduit-1.1.0 # Override default flag values for local packages and extra-deps flags: {} # Extra package databases containing global packages extra-package-dbs: [] ======================== What do you recommend to try to change? -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Sat Jul 16 04:44:17 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Sat, 16 Jul 2016 06:44:17 +0200 Subject: [Haskell-cafe] Passing a cabal flag to stack In-Reply-To: References: Message-ID: > What do you recommend to try to change? Put that flag setting into your stack.yaml, delete the extra-deps except poppler and run stack solver. I hope that works… From rustompmody at gmail.com Sat Jul 16 12:34:58 2016 From: rustompmody at gmail.com (Rustom Mody) Date: Sat, 16 Jul 2016 18:04:58 +0530 Subject: [Haskell-cafe] Passing a cabal flag to stack In-Reply-To: References: Message-ID: Ran -- thanks Simon! I’ll put a short rundown as best as I can in a bit! [Quite a blackart if you ask me] On Sat, Jul 16, 2016 at 10:14 AM, Simon Jakobi wrote: > > What do you recommend to try to change? > > Put that flag setting into your stack.yaml, delete the extra-deps > except poppler and run stack solver. I hope that works… > -- http://www.the-magus.in http://blog.languager.org -------------- next part -------------- An HTML attachment was scrubbed... URL: From simon.jakobi at googlemail.com Sat Jul 16 12:43:47 2016 From: simon.jakobi at googlemail.com (Simon Jakobi) Date: Sat, 16 Jul 2016 14:43:47 +0200 Subject: [Haskell-cafe] Passing a cabal flag to stack In-Reply-To: References: Message-ID: > Ran -- thanks Simon! Glad it worked! > I’ll put a short rundown as best as I can in a bit! Looking forward to it! > [Quite a blackart if you ask me] …says "the magus"! ;) From brucker at spamfence.net Sun Jul 17 09:13:01 2016 From: brucker at spamfence.net (Achim D. Brucker) Date: Sun, 17 Jul 2016 10:13:01 +0100 Subject: [Haskell-cafe] OCL 2016: ** Deadline Extension ** Submit Your Paper Until July 24, 2016 Message-ID: <20160717091301.GA23345@fujikawa.home.brucker.ch> (Apologies for duplicates) If you are working on the foundations, methods, or tools for OCL or textual modelling, you should now finalise your submission for the OCL workshop! *** The submission deadline has been extended to July 24th, 2016! *** CALL FOR PAPERS 16th International Workshop on OCL and Textual Modeling Co-located with ACM/IEEE 19th International Conference on Model Driven Engineering Languages and Systems (MODELS 2016) October 2, 2016, Saint-Malo, France http://oclworkshop.github.io Modeling started out with UML and its precursors as a graphical notation. Such visual representations enable direct intuitive capturing of reality, but some of their features are difficult to formalize and lack the level of precision required to create complete and unambiguous specifications. Limitations of the graphical notations encouraged the development of text-based modeling languages that either integrate with or replace graphical notations for modeling. Typical examples of such languages are OCL, textual MOF, Epsilon, and Alloy. Textual modeling languages have their roots in formal language paradigms like logic, programming and databases. The goal of this workshop is to create a forum where researchers and practitioners interested in building models using OCL or other kinds of textual languages can directly interact, report advances, share results, identify tools for language development, and discuss appropriate standards. In particular, the workshop will encourage discussions for achieving synergy from different modeling language concepts and modeling language use. The close interaction will enable researchers and practitioners to identify common interests and options for potential cooperation. Topics of interest include (but are not limited to) =================================================== - Mappings between textual modeling languages and other languages or formalisms - Algorithms, evaluation strategies and optimizations in the context of textual modeling languages for -- validation, verification, and testing, -- model transformation and code generation, -- meta-modeling and DSLs, and -- query and constraint specifications - Alternative graphical/textual notations for textual modeling languages - Evolution, transformation and simplification of textual modeling expressions - Libraries, templates and patterns for textual modeling languages - Tools that support textual modeling languages (e.g., verification of OCL formulae, runtime monitoring of invariants) - Complexity results for textual modeling languages - Quality models and benchmarks for comparing and evaluating textual modeling tools and algorithms - Successful applications of textual modeling languages - Case studies on industrial applications of textual modeling languages - Experience reports -- usage of textual modeling languages and tools in complex domains, -- usability of textual modeling languages and tools for end-users - Empirical studies about the benefits and drawbacks of textual modeling languages - Innovative textual modeling tools - Comparison, evaluation and integration of modeling languages - Correlation between modeling languages and modeling tasks This year, we particularly encourage submissions describing tools that support - in a very broad sense - textual modeling languages (if you have implemented OCL.js to run OCL in a web browser, this is the right workshop to present your work) as well as textual model transformations. Venue ===== The workshop will be organized as a part of MODELS 2016 Conference in Saint-Malo, France. It continues the series of OCL workshops held at UML/MODELS conferences: York (2000), Toronto (2001), San Francisco (2003), Lisbon (2004), Montego Bay (2005), Genova (2006), Nashville (2007), Toulouse (2008), Denver (2009), Oslo (2010), Zurich (2011, at the TOOLs conference), 2012 in Innsbruck, 2013 in Miami, 2014 in Valencia, Spain, and 2015 in Ottawa, Canada. Similar to its predecessors, the workshop addresses both people from academia and industry. The aim is to provide a forum for addressing integration of OCL and other textual modeling languages, as well as tools for textual modeling, and for disseminating good practice and discussing the new requirements for textual modeling. Workshop Format =============== The workshop will include short (about 15 min) presentations, parallel sessions of working groups, and sum-up discussions. Submissions =========== Two types of papers will be considered: * short contributions (between 6 and 8 pages) describing new ideas, innovative tools or position papers. * full papers (between 12 and 16 pages) in LNCS format. Submissions should be uploaded to EasyChair (https://easychair.org/conferences/?conf=ocl16). The program committee will review the submissions (minimum 2 reviews per paper, usually 3 reviews) and select papers according to their relevance and interest for discussions that will take place at the workshop. Accepted papers will be published online in a post-conference edition of CEUR (http://www.ceur-ws.org). Important Dates =============== Submission of papers: July 24, 2016 Notification: August 14, 2016 Workshop date: October 2, 2016 Organizers ========== Achim D. Brucker, The University of Sheffield, UK Jordi Cabot, ICREA - Open University of Catalonia, Spain Adolfo Sánchez-Barbudo Herrera, University of York, UK Programme Committee (TBC) ========================= Thomas Baar, University of Applied Sciences Berlin, Germany Mira Balaban, Ben-Gurion University of the Negev, Israel Tricia Balfe, Nomos Software, Ireland Domenico Bianculli, University of Luxembourg Dan Chiorean, Babes-Bolyai University, Romania Robert Clariso, Universitat Oberta de Catalunya, Spain Tony Clark, Middlesex University, UK Manuel Clavel, IMDEA Software Institute, Spain Birgit Demuth, Technische Universitat Dresden, Germany Marina Egea, Indra Sistemas S.A., Spain Geri Georg, Colorado State University, USA Martin Gogolla, University of Bremen, Germany Shahar Maoz, Tel Aviv University, Israel Istvan Rath, Budapest University of Technology and Economics, Hungary Bernhard Rumpe, RWTH Aachen, Germany Massimo Tisi, Mines de Nantes, France Frederic Tuong, Univ. Paris-Sud - IRT SystemX - LRI, France Edward Willink, Willink Transformations Ltd., UK Burkhart Wolff, Univ. Paris-Sud - LRI, France Steffen Zschaler, King's College, UK -- Dr. Achim D. Brucker | Software Assurance & Security | University of Sheffield https://www.brucker.uk/ | https://logicalhacking.com/blog From olivier.duhart at gmail.com Sun Jul 17 16:50:27 2016 From: olivier.duhart at gmail.com (Olivier Duhart) Date: Sun, 17 Jul 2016 09:50:27 -0700 (PDT) Subject: [Haskell-cafe] parsec get line number of lexems Message-ID: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> hello, I am experimenting with parsec. I am building a very simple language. I have a (almost) wholy funcrionning language : syntactic check, AST building and byte code génération. Now i want to improve error checking (type checking more precisely). this should be done on the AST basis. but in the ast i lose the line number information for precise error message. so my question is : is ther a way to get the line numbers at parsers level ? i would then store it in the ast for semantic check purpose thanks for your answers Olivier From fa-ml at ariis.it Sun Jul 17 17:04:26 2016 From: fa-ml at ariis.it (Francesco Ariis) Date: Sun, 17 Jul 2016 19:04:26 +0200 Subject: [Haskell-cafe] parsec get line number of lexems In-Reply-To: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> References: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> Message-ID: <20160717170426.GA15057@casa.casa> On Sun, Jul 17, 2016 at 09:50:27AM -0700, Olivier Duhart wrote: > is ther a way to get the line numbers at parsers level? Hi Olivier, maybe you are looking for http://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec.html#v:getPosition (which is very simple and used mainly for error reporting) or you could just keep track of `currLine` into a State of your choice (the 's' in ParsecT s ...). Does that help? -F From corentin.dupont at gmail.com Mon Jul 18 13:01:55 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 18 Jul 2016 15:01:55 +0200 Subject: [Haskell-cafe] another instance of MonadError In-Reply-To: References: Message-ID: I could also do my own MonadError class also, no? However this doesn't work: {-# LANGUAGE ConstraintKinds #-} type EvError a = MonadError String a class (Typeable n, Monad n, Applicative n, EvError n) => EvMgt n where ... instance EvMgt IO where... How can I create a new class "EvError" that inherits all the functions of "MonadError String"? On Fri, Jul 15, 2016 at 12:24 AM, David Feuer wrote: > You can't do that; sorry. You can always turn a string into an IOException > if you like. Or you could write a wrapper around IO. But MonadError has a > functional dependency, so you can only have one error type per monad. > > On Jul 14, 2016 6:19 PM, "Corentin Dupont" > wrote: > > Hello, > IO is an instance of MonadError IOException... > However I also need to make it an instance of MonadError String... > Is it possible? > I'm trying to instanciate this class: > > class (Typeable n, Monad n, Applicative n, MonadError String n) => EvMgt n > where ... > > instance EvMgt IO where... > > Any idea? > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From olivier.duhart at gmail.com Mon Jul 18 14:28:46 2016 From: olivier.duhart at gmail.com (Olivier Duhart) Date: Mon, 18 Jul 2016 07:28:46 -0700 (PDT) Subject: [Haskell-cafe] parsec get line number of lexems In-Reply-To: <20160717170426.GA15057@casa.casa> References: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> <20160717170426.GA15057@casa.casa> Message-ID: <4e20287b-f9f8-45cb-940b-31edda6679c0@googlegroups.com> thanks for your answer, exactly what I was looking for. Now I have parsers like this : ifStmt :: Parser Stmt ifStmt = do reserved "if" *pos <- getPosition* cond <- expression reserved "then" stmt1 <- statement reserved "else" stmt2 <- statement return $ If cond stmt1 stmt2 *pos* My AST is not fully "positioned" though as I don't get how to add position in expression (more precisely on operators). I am using the buildExpressionParser to build expression parsers so I have operators = [ [Prefix (reservedOp "-" >> return (Neg )) ] , [Infix (reservedOp "*" >> return (Binary Multiply)) AssocLeft, ..... And I dont known how to tell parsec to add a SourcePos to my operators. Any suggestion please ? Le dimanche 17 juillet 2016 19:09:32 UTC+2, Francesco Ariis a écrit : > > On Sun, Jul 17, 2016 at 09:50:27AM -0700, Olivier Duhart wrote: > > is ther a way to get the line numbers at parsers level? > > Hi Olivier, > maybe you are looking for > > > http://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec.html#v:getPosition > > (which is very simple and used mainly for error reporting) or you could > just keep track of `currLine` into a State of your choice (the 's' in > ParsecT s ...). > Does that help? > -F > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael.adler at tngtech.com Mon Jul 18 14:39:43 2016 From: michael.adler at tngtech.com (Michael Adler) Date: Mon, 18 Jul 2016 16:39:43 +0200 Subject: [Haskell-cafe] Announcing MuniHac 2016 Message-ID: <20160718143943.q7j4637ipp25ib6i@kratos.int.tngtech.com> Hi fellow Haskellers! Together with Alexander Lehmann from TNG Technology Consulting GmbH and Andres Löh from Well-Typed LLP, I am organizing a new Haskell Hackathon that will take place in Munich, from Friday September 2 - Sunday September 4. TNG is graciously offering to host the Hackathon at their premises. This Hackathon is in the tradition of other Haskell Hackathons such as ZuriHac, HacBerlin, UHac and others. We have capacity for 80-100 Haskellers to collaborate on any project they like. Hacking on Haskell projects will be the main focus of the event, but we will also have a couple of talks by renowned Haskellers. More details and a link to the registration platform can be found on www.munihac.de Hope to see you in Munich! Best regards, Michael -- Michael Adler TNG Technology Consulting michael.adler at tngtech.com TNG Technology Consulting GmbH, Betastr. 13a, 85774 Unterföhring Geschäftsführer: Henrik Klagges, Christoph Stock, Dr. Robert Dahlke Amtsgericht München, HRB 135082 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: not available URL: From chpatrick at gmail.com Mon Jul 18 14:50:24 2016 From: chpatrick at gmail.com (Patrick Chilton) Date: Mon, 18 Jul 2016 16:50:24 +0200 Subject: [Haskell-cafe] parsec get line number of lexems In-Reply-To: <4e20287b-f9f8-45cb-940b-31edda6679c0@googlegroups.com> References: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> <20160717170426.GA15057@casa.casa> <4e20287b-f9f8-45cb-940b-31edda6679c0@googlegroups.com> Message-ID: Assuming you have a constructor Binary Op Pos Expr Expr, you can do: Infix (Binary Multiply <$> getPosition <* reservedOp "*") AssocLeft See Control.Applicative for the operators. On Mon, Jul 18, 2016 at 4:28 PM, Olivier Duhart wrote: > thanks for your answer, exactly what I was looking for. Now I have parsers > like this : > > ifStmt :: Parser Stmt > ifStmt = > do reserved "if" > *pos <- getPosition* > cond <- expression > reserved "then" > stmt1 <- statement > reserved "else" > stmt2 <- statement > return $ If cond stmt1 stmt2 *pos* > > My AST is not fully "positioned" though as I don't get how to add position > in expression (more precisely on operators). > I am using the buildExpressionParser to build expression parsers so I have > > operators = [ [Prefix (reservedOp "-" >> return (Neg )) ] > , [Infix (reservedOp "*" >> return (Binary Multiply)) > AssocLeft, ..... > > And I dont known how to tell parsec to add a SourcePos to my operators. > > Any suggestion please ? > > > > > Le dimanche 17 juillet 2016 19:09:32 UTC+2, Francesco Ariis a écrit : >> >> On Sun, Jul 17, 2016 at 09:50:27AM -0700, Olivier Duhart wrote: >> > is ther a way to get the line numbers at parsers level? >> >> Hi Olivier, >> maybe you are looking for >> >> >> http://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec.html#v:getPosition >> >> (which is very simple and used mainly for error reporting) or you could >> just keep track of `currLine` into a State of your choice (the 's' in >> ParsecT s ...). >> Does that help? >> -F >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> >> > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From olivier.duhart at gmail.com Mon Jul 18 14:58:49 2016 From: olivier.duhart at gmail.com (Olivier Duhart) Date: Mon, 18 Jul 2016 07:58:49 -0700 (PDT) Subject: [Haskell-cafe] parsec get line number of lexems In-Reply-To: References: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> <20160717170426.GA15057@casa.casa> <4e20287b-f9f8-45cb-940b-31edda6679c0@googlegroups.com> Message-ID: thanks for your answer, looks like what I am looking for. Will try and tell Le lundi 18 juillet 2016 16:50:36 UTC+2, Patrick Chilton a écrit : > > Assuming you have a constructor Binary Op Pos Expr Expr, you can do: > > Infix (Binary Multiply <$> getPosition <* reservedOp "*") AssocLeft > > See Control.Applicative for the operators. > > On Mon, Jul 18, 2016 at 4:28 PM, Olivier Duhart > wrote: > >> thanks for your answer, exactly what I was looking for. Now I have >> parsers like this : >> >> ifStmt :: Parser Stmt >> ifStmt = >> do reserved "if" >> *pos <- getPosition* >> cond <- expression >> reserved "then" >> stmt1 <- statement >> reserved "else" >> stmt2 <- statement >> return $ If cond stmt1 stmt2 *pos* >> >> My AST is not fully "positioned" though as I don't get how to add >> position in expression (more precisely on operators). >> I am using the buildExpressionParser to build expression parsers so I have >> >> operators = [ [Prefix (reservedOp "-" >> return (Neg )) ] >> , [Infix (reservedOp "*" >> return (Binary Multiply)) >> AssocLeft, ..... >> >> And I dont known how to tell parsec to add a SourcePos to my operators. >> >> Any suggestion please ? >> >> >> >> >> Le dimanche 17 juillet 2016 19:09:32 UTC+2, Francesco Ariis a écrit : >>> >>> On Sun, Jul 17, 2016 at 09:50:27AM -0700, Olivier Duhart wrote: >>> > is ther a way to get the line numbers at parsers level? >>> >>> Hi Olivier, >>> maybe you are looking for >>> >>> >>> http://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec.html#v:getPosition >>> >>> (which is very simple and used mainly for error reporting) or you could >>> just keep track of `currLine` into a State of your choice (the 's' in >>> ParsecT s ...). >>> Does that help? >>> -F >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >>> >>> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nectarien at gmail.com Mon Jul 18 15:06:32 2016 From: nectarien at gmail.com (Peter Dedecker) Date: Mon, 18 Jul 2016 17:06:32 +0200 Subject: [Haskell-cafe] Linking to a DLL with relative path on Windows using stack build Message-ID: <5585B66A-71F9-4DA0-9A73-ECC3F631F611@gmail.com> Hello all, I am writing a Haskell program that controls a scientific instrument (a very sensitive camera). The instrument vendor makes a Windows DLL available that exposes a C interface. I have already set up the FFI bindings. I am building the application using Stack on Windows 8. But I am not sure how I can get “stack build” to find the DLL at link time. My Google searches have not cleared things up. My questions: 1. What global directory should I place the DLL in so “stack build” will pick it up? I tried placing it in C:\Windows\SysWOW64 but that doesn’t work. I realize I could add an "extra-lib-dirs” argument in the .cabal file but I would like to know what the default linker search paths are. But in fact I prefer to not install the DLL in a hardcoded, global location. Since the instrument is attached to a specific measurement computer, there is no point in having it installed on the developer PCs. I would prefer to have it all self-contained into a single project. In my C++ development I solve this by placing the DLLs (well, import libraries, really) in a project-specific “lib” directory next to the source code, and under version control. For example, in Visual Studio my linker path is simply "$(SolutionDir)\..\lib”, which works nicely. 2. But: why can’t I use a project-relative "extra-lib-dirs" argument in the .cabal file? What I would really like is to be able to say "extra-lib-dirs={$projectroot}/lib” in the cabal file. And then, after compilation, I can just copy the binary to the measurement computer (controlling the instrument), copy the DLL into the .exe folder, and have it all work. Except that it doesn’t work. A relative path in the .cabal file results in "lib is a relative path which makes no sense (as there is nothing for it to be relative to)." I don’t understand why it makes no sense in this case (where I am linking to a DLL). Seems to me like this does make sense? Any suggestions on how to go about this? I have stumbled across this: http://stackoverflow.com/questions/24444675/use-relative-paths-for-extra-lib-dirs-on-cabal but that seems awfully hackish and I haven’t been able to get it to work. With thanks Peter From david.feuer at gmail.com Mon Jul 18 19:12:53 2016 From: david.feuer at gmail.com (David Feuer) Date: Mon, 18 Jul 2016 15:12:53 -0400 Subject: [Haskell-cafe] another instance of MonadError In-Reply-To: References: Message-ID: Type synonyms change nothing. I don't think your current line of questioning is going to lead anywhere useful. Could you give some more context for your original question? If you tell us what you're ultimately trying to accomplish, someone might be able to find a way to do it. On Mon, Jul 18, 2016 at 9:01 AM, Corentin Dupont wrote: > > I could also do my own MonadError class also, no? > However this doesn't work: > > > {-# LANGUAGE ConstraintKinds #-} > > type EvError a = MonadError String a > > class (Typeable n, Monad n, Applicative n, EvError n) => EvMgt n where ... > > instance EvMgt IO where... > > > How can I create a new class "EvError" that inherits all the functions of > "MonadError String"? > > > On Fri, Jul 15, 2016 at 12:24 AM, David Feuer wrote: >> >> You can't do that; sorry. You can always turn a string into an IOException >> if you like. Or you could write a wrapper around IO. But MonadError has a >> functional dependency, so you can only have one error type per monad. >> >> >> On Jul 14, 2016 6:19 PM, "Corentin Dupont" >> wrote: >> >> Hello, >> IO is an instance of MonadError IOException... >> However I also need to make it an instance of MonadError String... >> Is it possible? >> I'm trying to instanciate this class: >> >> class (Typeable n, Monad n, Applicative n, MonadError String n) => EvMgt n >> where ... >> >> instance EvMgt IO where... >> >> Any idea? >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> >> > From corentin.dupont at gmail.com Mon Jul 18 19:40:17 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Mon, 18 Jul 2016 21:40:17 +0200 Subject: [Haskell-cafe] another instance of MonadError In-Reply-To: References: Message-ID: I'm trying to define a typeclass for the management of events. I thought it would be "nice" if IO can be an instance of it. This would allow to manage my events in IO, as a good demonstration. However those events can fail, so I'd like to use MonadError! IO is an instance of MonadError IOException, but IOException is not interesting for me since the events have other kind of exceptions. So I see only two possibilities: - wrap IO in a newtype, but bye-bye nice demonstration :) - define my own error class, similar to MonadError. Thanks! On Mon, Jul 18, 2016 at 9:12 PM, David Feuer wrote: > Type synonyms change nothing. I don't think your current line of > questioning is going to lead anywhere useful. Could you give some more > context for your original question? If you tell us what you're > ultimately trying to accomplish, someone might be able to find a way > to do it. > > On Mon, Jul 18, 2016 at 9:01 AM, Corentin Dupont > wrote: > > > > I could also do my own MonadError class also, no? > > However this doesn't work: > > > > > > {-# LANGUAGE ConstraintKinds #-} > > > > type EvError a = MonadError String a > > > > class (Typeable n, Monad n, Applicative n, EvError n) => EvMgt n where > ... > > > > instance EvMgt IO where... > > > > > > How can I create a new class "EvError" that inherits all the functions of > > "MonadError String"? > > > > > > On Fri, Jul 15, 2016 at 12:24 AM, David Feuer > wrote: > >> > >> You can't do that; sorry. You can always turn a string into an > IOException > >> if you like. Or you could write a wrapper around IO. But MonadError has > a > >> functional dependency, so you can only have one error type per monad. > >> > >> > >> On Jul 14, 2016 6:19 PM, "Corentin Dupont" > >> wrote: > >> > >> Hello, > >> IO is an instance of MonadError IOException... > >> However I also need to make it an instance of MonadError String... > >> Is it possible? > >> I'm trying to instanciate this class: > >> > >> class (Typeable n, Monad n, Applicative n, MonadError String n) => > EvMgt n > >> where ... > >> > >> instance EvMgt IO where... > >> > >> Any idea? > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> To (un)subscribe, modify options or view archives go to: > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >> Only members subscribed via the mailman list are allowed to post. > >> > >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kwangyul.seo at gmail.com Tue Jul 19 04:07:54 2016 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Tue, 19 Jul 2016 13:07:54 +0900 Subject: [Haskell-cafe] ANN: blockhash-0.1.0.0 Message-ID: Hi all! I'm pleased to announce the first release of blockhash, a perceptual image hash calculation tool based on algorithm described in Block Mean Value Based Image Perceptual Hashing by Bian Yang, Fan Gu and Xiamu Niu. https://hackage.haskell.org/package/blockhash https://github.com/kseo/blockhash Program: Usage: blockhash [-q|--quick] [-b|--bits ARG] filenames blockhash Available options: -h,--help Show this help text -q,--quick Use quick hashing method -b,--bits ARG Create hash of size N^2 bits. Library: import qualified Codec.Picture as P import Data.Blockhash import qualified Data.Vector.Generic as VG import qualified Data.Vector.Unboxed as V printHash :: FilePath -> IO () printHash :: filename = do res <- P.readImage filename case res of Left err -> putStrLn ("Fail to read: " ++ filename) Right dynamicImage -> do let rgbaImage = P.convertRGBA8 dynamicImage pixels = VG.convert (P.imageData rgbaImage) image = Image { imagePixels = pixels , imageWidth = P.imageWidth rgbaImage , imageHeight = P.imageHeight rgbaImage } hash = blockhash image 16 Precise putStrLn (show hash) For further information on the blockhash algorithm, please visit the web site: http://blockhash.io/ Thanks, Kwang Yul Seo -------------- next part -------------- An HTML attachment was scrubbed... URL: From icfp.publicity at googlemail.com Tue Jul 19 05:44:14 2016 From: icfp.publicity at googlemail.com (Lindsey Kuper) Date: Mon, 18 Jul 2016 22:44:14 -0700 Subject: [Haskell-cafe] Call for Participation: ICFP 2016 Message-ID: <578dbe2e5ea64_17b03fddc1c65be060515@landin.local.mail> [ Early registration ends 17 August. ] ===================================================================== Call for Participation ICFP 2016 21st ACM SIGPLAN International Conference on Functional Programming and affiliated events September 18 - September 24, 2016 Nara, Japan http://conf.researchr.org/home/icfp-2016 ===================================================================== ICFP provides a forum for researchers and developers to hear about the latest work on the design, implementations, principles, and uses of functional programming. The conference covers the entire spectrum of work, from practice to theory, including its peripheries. A full week dedicated to functional programming: 1 conference, 1 symposium, 10 workshops, tutorials, programming contest results, student research competition, and mentoring workshop * Overview and affiliated events: http://conf.researchr.org/home/icfp-2016 * Program: http://conf.researchr.org/program/icfp-2016/program-icfp-2016 * Accepted Papers: http://conf.researchr.org/track/icfp-2016/icfp-2016-papers#event-overview * Registration is available via: https://regmaster4.com/2016conf/ICFP16/register.php Early registration is due 17 August, 2016. * Programming contest, 5-8 August, 2016: http://2016.icfpcontest.org/ * Student Research Competition (deadline: 3 August, 2016): http://conf.researchr.org/info/icfp-2016/student-research-competition * Follow @icfp_conference on twitter for the latest news: http://twitter.com/icfp_conference There are several events affiliated with ICFP: Sunday, September 18 Workshop on Higher-order Programming with Effects Workshop on Type-Driven Development Scheme and Functional Programming Workshop Programming Languages Mentoring Workshop Monday, September 19 – Wednesday, September 21 ICFP Thursday, September 22 Haskell Symposium – Day 1 ML Family Workshop Workshop on Functional High-Performance Computing Commercial Users of Functional Programming – Day 1 Friday, September 23 Haskell Symposium – Day 2 OCaml Workshop Erlang Workshop Commercial Users of Functional Programming – Day 2 Saturday, September 5 Commercial Users of Functional Programming – Day 3 Haskell Implementors Workshop Functional Art, Music, Modeling and Design Conference Organizers General Co-Chairs: Jacques Garrigue, Nagoya University Gabriele Keller, University of New South Wales Program Chair: Eijiro Sumii, Tohoku University Local Arrangements Co-Chairs: Shinya Katsumata, Kyoto University Susumu Nishimura, Kyoto University Industrial Relations Chair: Rian Trinkle, Obsidian Systems LLC Workshop Co-Chairs: Nicolas Wu, University of Bristol Andres Loeh, Well-Typed LLP Programming Contest Chair: Keisuke Nakano, The University of Electro-Communications Student Research Competition Chair: David Van Horn, University of Maryland, College Park Mentoring Workshop Co-Chairs: Amal Ahmed, Northeastern University Robby Findler, Northwestern University Atsushi Igarashi, Kyoto Universty Publicity Chair: Lindsey Kuper, Intel Labs Video Chair: Iavor Diatchki, Galois Jose Calderon, Galois Student Volunteer Co-Chairs: Yosuke Fukuda, Kyoto University Yuki Nishida, Kyoto University Gabriel Scherer, INRIA Industrial partners: Platinum partners Jane Street Capital Ahrefs Gold partners Mozilla Research Silver partners Ambiata Tsuru Capital Bronze partners Awake Networks Microsoft Research ===================================================================== From olivier.duhart at gmail.com Tue Jul 19 06:57:42 2016 From: olivier.duhart at gmail.com (Olivier Duhart) Date: Mon, 18 Jul 2016 23:57:42 -0700 (PDT) Subject: [Haskell-cafe] parsec get line number of lexems In-Reply-To: References: <2d3b1192-1e3f-4815-b923-3cc61973e3f3@googlegroups.com> <20160717170426.GA15057@casa.casa> <4e20287b-f9f8-45cb-940b-31edda6679c0@googlegroups.com> Message-ID: <6f198a90-3dcd-4f4d-8c46-d63d26690217@googlegroups.com> So I did it and it works exactly as expected. thanks again Patrick Le lundi 18 juillet 2016 16:58:49 UTC+2, Olivier Duhart a écrit : > > thanks for your answer, looks like what I am looking for. Will try and tell > > Le lundi 18 juillet 2016 16:50:36 UTC+2, Patrick Chilton a écrit : >> >> Assuming you have a constructor Binary Op Pos Expr Expr, you can do: >> >> Infix (Binary Multiply <$> getPosition <* reservedOp "*") AssocLeft >> >> See Control.Applicative for the operators. >> >> On Mon, Jul 18, 2016 at 4:28 PM, Olivier Duhart >> wrote: >> >>> thanks for your answer, exactly what I was looking for. Now I have >>> parsers like this : >>> >>> ifStmt :: Parser Stmt >>> ifStmt = >>> do reserved "if" >>> *pos <- getPosition* >>> cond <- expression >>> reserved "then" >>> stmt1 <- statement >>> reserved "else" >>> stmt2 <- statement >>> return $ If cond stmt1 stmt2 *pos* >>> >>> My AST is not fully "positioned" though as I don't get how to add >>> position in expression (more precisely on operators). >>> I am using the buildExpressionParser to build expression parsers so I >>> have >>> >>> operators = [ [Prefix (reservedOp "-" >> return (Neg )) ] >>> , [Infix (reservedOp "*" >> return (Binary Multiply)) >>> AssocLeft, ..... >>> >>> And I dont known how to tell parsec to add a SourcePos to my operators. >>> >>> Any suggestion please ? >>> >>> >>> >>> >>> Le dimanche 17 juillet 2016 19:09:32 UTC+2, Francesco Ariis a écrit : >>>> >>>> On Sun, Jul 17, 2016 at 09:50:27AM -0700, Olivier Duhart wrote: >>>> > is ther a way to get the line numbers at parsers level? >>>> >>>> Hi Olivier, >>>> maybe you are looking for >>>> >>>> >>>> http://hackage.haskell.org/package/parsec-3.1.11/docs/Text-Parsec.html#v:getPosition >>>> >>>> (which is very simple and used mainly for error reporting) or you could >>>> just keep track of `currLine` into a State of your choice (the 's' in >>>> ParsecT s ...). >>>> Does that help? >>>> -F >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> To (un)subscribe, modify options or view archives go to: >>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>>> Only members subscribed via the mailman list are allowed to post. >>>> >>>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >>> >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From apfelmus at quantentunnel.de Tue Jul 19 17:11:15 2016 From: apfelmus at quantentunnel.de (Heinrich Apfelmus) Date: Tue, 19 Jul 2016 19:11:15 +0200 Subject: [Haskell-cafe] Local Haskell talk in Leipzig, 27 July 2016 at 3:30pm in HTWK Message-ID: Dear (filter (`livesInOrCloseTo` Leipzig_Germany) haskellers), we would like to invite you to a talk by Stephen Blackheath "They why and how of Functional Reactive Programming with Java/Sodium" on Wednesday, 27 July 2016, at 15:30 Uhr in Room Gu 102, Gutenberg-Bau, HTWK Leipzig Abstract: Afterwards (~ 17:00 Uhr) there will be a get-together in the Cafe Suedbrause . Stop Listening! Johannes Waldmann and Heinrich Apfelmus From amindfv at gmail.com Wed Jul 20 00:21:12 2016 From: amindfv at gmail.com (amindfv at gmail.com) Date: Tue, 19 Jul 2016 20:21:12 -0400 Subject: [Haskell-cafe] [Haskell] Function to replace given element in list In-Reply-To: References: Message-ID: <980C12F5-7684-4639-9D2F-4EAFC5F4CC2D@gmail.com> (Moving to haskell-cafe@ -- haskell@ is only for announcements) > El 19 jul 2016, a las 19:44, David Feuer escribió: > > A zipper is a good way to separate the search from the replacement. But the problem at hand does not require such a separation! If you don't need that, a zipper seems like overkill. > > > On Jul 19, 2016 7:39 PM, "Carl Folke Henschen Edman" wrote: > On Tue, Jul 19, 2016 at 6:13 PM, David Feuer wrote: >> Using a zipper will not get you very far here. The best way would >> likely be to replace the list with a balanced search tree. > > > That depends on the pattern of access and usage. For some a zippered list will outperform a self-balancing tree and vice versa. For others a zippered tree, or something else, will beat either. But when seeing the pattern of changing a single element in the middle of a list, a zippered list is the first improved data structure that comes to mind. > > > Carl Edman > > _______________________________________________ > Haskell mailing list > Haskell at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Wed Jul 20 13:09:13 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Wed, 20 Jul 2016 14:09:13 +0100 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST Message-ID: Dear all, For several months I have had a branch of haskell-src-exts which has been updated for all the new features in GHC 8. However, I have not yet released the changes as in this version I also removed the simplified AST. To those unfamiliar, HSE provides two ASTs, one which has source locations and one which doesn't. I have removed the one which doesn't. This simplifies maintenance and I think also makes the library easier to use. I have held back releasing this version as there are some people who use the simplified AST. The changes necessary for the new version are mechanical and easy to make. For example, David Fox updated haskell-names to use my branch [1] with few problems. The question is, are there any users of the library who object to this change? Matt [1]: https://github.com/haskell-suite/haskell-names/pull/73 From conal at conal.net Wed Jul 20 13:50:43 2016 From: conal at conal.net (Conal Elliott) Date: Wed, 20 Jul 2016 06:50:43 -0700 Subject: [Haskell-cafe] Practical use of Stream's monad instance? In-Reply-To: References: Message-ID: Hi Petr. As Tom hinted, Stream is isomorphic to function-from-Nat (Peano/lazy natural numbers), being the memoized (trie) representation of such functions. The Stream Monad instance corresponds to the function-from-a Monad ("reader") instance, so all such trie Monad instances are useful wherever we want to work monadically with functions but want memoization. I like Olaf's example use as well: 'fmap not . join' constructs a stream of binary representations of numbers in [0,1] that disagrees with every element of any given enumeration of such numbers. A very terse demonstration of a profoundly important mathematical discovery. - Conal On Tue, Jul 12, 2016 at 4:10 AM, Petr Pudlák wrote: > Indeed, the question is not wherever it's a monad or not, just to what > extent is the monad useful. > > Dne po 11. 7. 2016 22:08 uživatel Olaf Klinke > napsal: > >> As someone else on this list whose name I don't recall put it, there is no >> choice on whether to make Stream a monad or not. It simply _is_ a monad. >> Anyone with some CS education hearing 'diagonal of inifinite list of >> infinite lists' should immediately think of Georg Cantor. >> >> import Data.Stream >> import Data.Ratio >> >> type Real = Stream Rational >> -- approximate a real number by an ascending stream >> -- of lower bounds. >> >> supremum :: Stream Real -> Real >> supremum = join >> -- If a stream of reals is index-wise ascending, >> -- the monad instance for Stream computes its supremum. >> -- Use this e.g. to compute any mathematical quantity >> -- defined as a supremum. >> >> -- Olaf >> > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Wed Jul 20 15:18:26 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Wed, 20 Jul 2016 17:18:26 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data Message-ID: Hi all, I'm surprised this doesn't work: data SomeData = forall e. (Typeable e, Eq e) => SomeData e (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool (===) x y = cast x == Just y test :: SomeData' -> Bool test (SomeData' e) | e === Nothing = True test _ = False It says Could not deduce (Eq a1) arising from a use of ‘===’ How can I achieve something of the same effect? Thanks Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From chpatrick at gmail.com Wed Jul 20 15:44:15 2016 From: chpatrick at gmail.com (Patrick Chilton) Date: Wed, 20 Jul 2016 17:44:15 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: It's because you're doing === Nothing and the type of the Nothing is ambiguous (Maybe a1). On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont wrote: > Hi all, > I'm surprised this doesn't work: > > data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool > (===) x y = cast x == Just y > > test :: SomeData' -> Bool > test (SomeData' e) | e === Nothing = True > test _ = False > > It says > Could not deduce (Eq a1) arising from a use of ‘===’ > > How can I achieve something of the same effect? > > Thanks > Corentin > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Wed Jul 20 16:30:39 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Wed, 20 Jul 2016 18:30:39 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: I see.... The think is, I am interested to know if "e" is "Nothing", whatever the type of Nothing is! On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton wrote: > It's because you're doing === Nothing and the type of the Nothing is > ambiguous (Maybe a1). > > On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont < > corentin.dupont at gmail.com> wrote: > >> Hi all, >> I'm surprised this doesn't work: >> >> data SomeData = forall e. (Typeable e, Eq e) => SomeData e >> >> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool >> (===) x y = cast x == Just y >> >> test :: SomeData' -> Bool >> test (SomeData' e) | e === Nothing = True >> test _ = False >> >> It says >> Could not deduce (Eq a1) arising from a use of ‘===’ >> >> How can I achieve something of the same effect? >> >> Thanks >> Corentin >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michaelburge at pobox.com Wed Jul 20 17:40:16 2016 From: michaelburge at pobox.com (Michael Burge) Date: Wed, 20 Jul 2016 10:40:16 -0700 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: I've used toConstr from Data.Data when I only care which constructor a value was constructed with. The specific type 'a' in 'Maybe a' is effectively a phantom type for the Nothing constructor, which I haven't used before. But it looks like it still works, so you could try comparing the constructors: Prelude Data.Typeable Data.Data> toConstr (Nothing :: Maybe Int) == toConstr (Nothing :: Maybe String) True Most of the time, you should be able to use a typeclass for this. On Wed, Jul 20, 2016 at 9:30 AM, Corentin Dupont wrote: > I see.... > The think is, I am interested to know if "e" is "Nothing", whatever the > type of Nothing is! > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > wrote: > >> It's because you're doing === Nothing and the type of the Nothing is >> ambiguous (Maybe a1). >> >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont < >> corentin.dupont at gmail.com> wrote: >> >>> Hi all, >>> I'm surprised this doesn't work: >>> >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e >>> >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool >>> (===) x y = cast x == Just y >>> >>> test :: SomeData' -> Bool >>> test (SomeData' e) | e === Nothing = True >>> test _ = False >>> >>> It says >>> Could not deduce (Eq a1) arising from a use of ‘===’ >>> >>> How can I achieve something of the same effect? >>> >>> Thanks >>> Corentin >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >>> >> >> > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From max at amanshauser.eu Wed Jul 20 15:52:44 2016 From: max at amanshauser.eu (Max Amanshauser) Date: Wed, 20 Jul 2016 17:52:44 +0200 Subject: [Haskell-cafe] Different behaviour with -XAllowAmbiguousTypes in 7.10.3b and 8.0.1 Message-ID: Hi, while porting a library to Haskell, which deals with persisting finite state automata to various stores, depending on the user's choice and the instances provided for types s(tate) e(vent) a(ction), I ran into different behaviour in ghc 7.10.3b and 8.0.1 related to ambiguity checks. This is a minimised and somewhat contrived example: > -- testme.hs > > {-# LANGUAGE MultiParamTypeClasses #-} > {-# LANGUAGE FlexibleInstances #-} > {-# LANGUAGE AllowAmbiguousTypes #-} > > module TestMe where > > data MyStore = MyStore > > class FSMStore st s e a where > fsmRead :: st -> String -> s > > instance (Num s) => FSMStore MyStore s e a where > fsmRead st i = 23 > > get :: (FSMStore st s e a) => st -> String -> s > get st i = fsmRead st i With GHC 8.0.1 I get: > *TestMe> :l test.hs > [1 of 1] Compiling TestMe ( test.hs, interpreted ) > > test.hs:19:12: error: > • Could not deduce (FSMStore st s e0 a0) > arising from a use of ‘fsmRead’ > from the context: FSMStore st s e a > bound by the type signature for: > get :: FSMStore st s e a => st -> String -> s > at test.hs:18:1-47 > The type variables ‘e0’, ‘a0’ are ambiguous > Relevant bindings include > st :: st (bound at test.hs:19:5) > get :: st -> String -> s (bound at test.hs:19:1) > These potential instance exist: > instance Num s => FSMStore MyStore s e a > -- Defined at test.hs:12:10 > • In the expression: fsmRead st i > In an equation for ‘get’: get st i = fsmRead st i > Failed, modules loaded: none. However, when I remove the type signature for get: > Prelude> :l test.hs > [1 of 1] Compiling TestMe ( test.hs, interpreted ) > Ok, modules loaded: TestMe. > *TestMe> :t get > get :: FSMStore st s e a => st -> String -> s > *TestMe> get MyStore "asdf" > 23 GHC inferred the exact same type I provided, but this time it compiles successfully. When going back to GHC 7.10.3b, without type signature: > GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help > :Prelude> :l test.hs > [1 of 1] Compiling TestMe ( test.hs, interpreted ) > > test.hs:19:1: > Could not deduce (FSMStore st s e0 a0) > from the context (FSMStore st s e a) > bound by the inferred type for ‘get’: > FSMStore st s e a => st -> String -> s > at test.hs:19:1-23 > The type variables ‘e0’, ‘a0’ are ambiguous > When checking that ‘get’ has the inferred type > get :: forall st s e a. FSMStore st s e a => st -> String -> s > Probable cause: the inferred type is ambiguous > Failed, modules loaded: none. So my questions are: *) What's with the different behaviour depending on whether the type sig is inferred or provided? *) Is GHC 7.10.3b or 8.0.1 closer to the correct behaviour w.r.t. -XAllowAmbiguousTypes? -- Regards, Max Amanshauser. From ivan.miljenovic at gmail.com Wed Jul 20 21:21:54 2016 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Thu, 21 Jul 2016 07:21:54 +1000 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: On 21 July 2016 at 02:30, Corentin Dupont wrote: > I see.... > The think is, I am interested to know if "e" is "Nothing", whatever the type > of Nothing is! Data.Maybe.isNothing ? > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > wrote: >> >> It's because you're doing === Nothing and the type of the Nothing is >> ambiguous (Maybe a1). >> >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont >> wrote: >>> >>> Hi all, >>> I'm surprised this doesn't work: >>> >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e >>> >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool >>> (===) x y = cast x == Just y >>> >>> test :: SomeData' -> Bool >>> test (SomeData' e) | e === Nothing = True >>> test _ = False >>> >>> It says >>> Could not deduce (Eq a1) arising from a use of ‘===’ >>> >>> How can I achieve something of the same effect? >>> >>> Thanks >>> Corentin >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From corentin.dupont at gmail.com Thu Jul 21 07:51:05 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 21 Jul 2016 09:51:05 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: Hi Ivan, I could use isNothing, but the data is forall'ed... I tried but it doesn't work: data SomeData = forall e. (Typeable e, Eq e) => SomeData e isNothing' :: SomeData -> Bool isNothing' (SomeData a) = case (cast a) of (a :: Maybe a) -> isNothing a Could not deduce (Typeable a) arising from a use of ‘cast’ On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic < ivan.miljenovic at gmail.com> wrote: > On 21 July 2016 at 02:30, Corentin Dupont > wrote: > > I see.... > > The think is, I am interested to know if "e" is "Nothing", whatever the > type > > of Nothing is! > > Data.Maybe.isNothing ? > > > > > > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > > wrote: > >> > >> It's because you're doing === Nothing and the type of the Nothing is > >> ambiguous (Maybe a1). > >> > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont > >> wrote: > >>> > >>> Hi all, > >>> I'm surprised this doesn't work: > >>> > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e > >>> > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool > >>> (===) x y = cast x == Just y > >>> > >>> test :: SomeData' -> Bool > >>> test (SomeData' e) | e === Nothing = True > >>> test _ = False > >>> > >>> It says > >>> Could not deduce (Eq a1) arising from a use of ‘===’ > >>> > >>> How can I achieve something of the same effect? > >>> > >>> Thanks > >>> Corentin > >>> > >>> _______________________________________________ > >>> Haskell-Cafe mailing list > >>> To (un)subscribe, modify options or view archives go to: > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >>> Only members subscribed via the mailman list are allowed to post. > >> > >> > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anselm.scholl at tu-harburg.de Thu Jul 21 08:23:34 2016 From: anselm.scholl at tu-harburg.de (Jonas Scholl) Date: Thu, 21 Jul 2016 10:23:34 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: If you want to use just Typeable, you can implement your own cast: Extract the TypeRep of the thing in SomeData, get the TyCon, which is the top-level constructor, i.e. Maybe without arguments, and compare it with the TyCon from Maybe. If they match, you coerce the value to Maybe () and use isNothing. While this is not completely safe, we do not evaluate the thing we just coerced to (), and thus are safe, as Maybe should have identical representation regardless of the type parameter. isNothing' :: SomeData -> Bool isNothing' (SomeData a) = tyCon == maybeTyCon && isNothing (unsafeCoerce a :: Maybe ()) where tyCon = typeRepTyCon (typeRep (mkProxy a)) maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ())) mkProxy :: a -> Proxy a mkProxy = const Proxy On 07/21/2016 09:51 AM, Corentin Dupont wrote: > Hi Ivan, > I could use isNothing, but the data is forall'ed... > I tried but it doesn't work: > > data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > isNothing' :: SomeData -> Bool > isNothing' (SomeData a) = case (cast a) of > (a :: Maybe a) -> isNothing a > > Could not deduce (Typeable a) arising from a use of ‘cast’ > > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic > > wrote: > > On 21 July 2016 at 02:30, Corentin Dupont > wrote: > > I see.... > > The think is, I am interested to know if "e" is "Nothing", whatever the type > > of Nothing is! > > Data.Maybe.isNothing ? > > > > > > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > > > > wrote: > >> > >> It's because you're doing === Nothing and the type of the Nothing is > >> ambiguous (Maybe a1). > >> > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont > >> > wrote: > >>> > >>> Hi all, > >>> I'm surprised this doesn't work: > >>> > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e > >>> > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> Bool > >>> (===) x y = cast x == Just y > >>> > >>> test :: SomeData' -> Bool > >>> test (SomeData' e) | e === Nothing = True > >>> test _ = False > >>> > >>> It says > >>> Could not deduce (Eq a1) arising from a use of ‘===’ > >>> > >>> How can I achieve something of the same effect? > >>> > >>> Thanks > >>> Corentin > >>> > >>> _______________________________________________ > >>> Haskell-Cafe mailing list > >>> To (un)subscribe, modify options or view archives go to: > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > >>> Only members subscribed via the mailman list are allowed to post. > >> > >> > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 473 bytes Desc: OpenPGP digital signature URL: From corentin.dupont at gmail.com Thu Jul 21 08:48:53 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 21 Jul 2016 10:48:53 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: That's great, exactly what I need. What do you mean by "just Typeable"? Do you have another idea in mind? On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl wrote: > If you want to use just Typeable, you can implement your own cast: > Extract the TypeRep of the thing in SomeData, get the TyCon, which is > the top-level constructor, i.e. Maybe without arguments, and compare it > with the TyCon from Maybe. If they match, you coerce the value to Maybe > () and use isNothing. While this is not completely safe, we do not > evaluate the thing we just coerced to (), and thus are safe, as Maybe > should have identical representation regardless of the type parameter. > > isNothing' :: SomeData -> Bool > isNothing' (SomeData a) = tyCon == maybeTyCon > && isNothing (unsafeCoerce a :: Maybe ()) > where > tyCon = typeRepTyCon (typeRep (mkProxy a)) > maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ())) > mkProxy :: a -> Proxy a > mkProxy = const Proxy > > > On 07/21/2016 09:51 AM, Corentin Dupont wrote: > > Hi Ivan, > > I could use isNothing, but the data is forall'ed... > > I tried but it doesn't work: > > > > data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > > > isNothing' :: SomeData -> Bool > > isNothing' (SomeData a) = case (cast a) of > > (a :: Maybe a) -> isNothing a > > > > Could not deduce (Typeable a) arising from a use of ‘cast’ > > > > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic > > > wrote: > > > > On 21 July 2016 at 02:30, Corentin Dupont > > wrote: > > > I see.... > > > The think is, I am interested to know if "e" is "Nothing", > whatever the type > > > of Nothing is! > > > > Data.Maybe.isNothing ? > > > > > > > > > > > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > > > > > > wrote: > > >> > > >> It's because you're doing === Nothing and the type of the Nothing > is > > >> ambiguous (Maybe a1). > > >> > > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont > > >> > > wrote: > > >>> > > >>> Hi all, > > >>> I'm surprised this doesn't work: > > >>> > > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > >>> > > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> > Bool > > >>> (===) x y = cast x == Just y > > >>> > > >>> test :: SomeData' -> Bool > > >>> test (SomeData' e) | e === Nothing = True > > >>> test _ = False > > >>> > > >>> It says > > >>> Could not deduce (Eq a1) arising from a use of ‘===’ > > >>> > > >>> How can I achieve something of the same effect? > > >>> > > >>> Thanks > > >>> Corentin > > >>> > > >>> _______________________________________________ > > >>> Haskell-Cafe mailing list > > >>> To (un)subscribe, modify options or view archives go to: > > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >>> Only members subscribed via the mailman list are allowed to post. > > >> > > >> > > > > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > > > > > > > -- > > Ivan Lazar Miljenovic > > Ivan.Miljenovic at gmail.com > > http://IvanMiljenovic.wordpress.com > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anselm.scholl at tu-harburg.de Thu Jul 21 09:26:46 2016 From: anselm.scholl at tu-harburg.de (Jonas Scholl) Date: Thu, 21 Jul 2016 11:26:46 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: With "just Typeable" I mean using only the Typeable class. As already mentioned by Michael, it is also possible to achieve the same effect with the Data class: data SomeData = forall e. (Data e, Eq e) => SomeData e isNothing'' :: SomeData -> Bool isNothing'' (SomeData a) = toConstr a == toConstr (Nothing :: Maybe ()) Depending on your use-case, this may be simpler and it avoids using unsafeCoerce, which may make one feel a little bit uneasy. On the other hand, it adds an additional constraint. Additionally, a programmer can write his own Data instance while Typeable instances are always generated by the compiler (in newer versions of GHC). On 07/21/2016 10:48 AM, Corentin Dupont wrote: > That's great, exactly what I need. > What do you mean by "just Typeable"? > Do you have another idea in mind? > > On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl > > wrote: > > If you want to use just Typeable, you can implement your own cast: > Extract the TypeRep of the thing in SomeData, get the TyCon, which is > the top-level constructor, i.e. Maybe without arguments, and compare it > with the TyCon from Maybe. If they match, you coerce the value to Maybe > () and use isNothing. While this is not completely safe, we do not > evaluate the thing we just coerced to (), and thus are safe, as Maybe > should have identical representation regardless of the type parameter. > > isNothing' :: SomeData -> Bool > isNothing' (SomeData a) = tyCon == maybeTyCon > && isNothing (unsafeCoerce a :: Maybe ()) > where > tyCon = typeRepTyCon (typeRep (mkProxy a)) > maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ())) > mkProxy :: a -> Proxy a > mkProxy = const Proxy > > > On 07/21/2016 09:51 AM, Corentin Dupont wrote: > > Hi Ivan, > > I could use isNothing, but the data is forall'ed... > > I tried but it doesn't work: > > > > data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > > > isNothing' :: SomeData -> Bool > > isNothing' (SomeData a) = case (cast a) of > > (a :: Maybe a) -> isNothing a > > > > Could not deduce (Typeable a) arising from a use of ‘cast’ > > > > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic > > > >> wrote: > > > > On 21 July 2016 at 02:30, Corentin Dupont > > >> wrote: > > > I see.... > > > The think is, I am interested to know if "e" is "Nothing", whatever the type > > > of Nothing is! > > > > Data.Maybe.isNothing ? > > > > > > > > > > > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > > > >> > > > wrote: > > >> > > >> It's because you're doing === Nothing and the type of the Nothing is > > >> ambiguous (Maybe a1). > > >> > > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont > > >> >> wrote: > > >>> > > >>> Hi all, > > >>> I'm surprised this doesn't work: > > >>> > > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > >>> > > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b > -> Bool > > >>> (===) x y = cast x == Just y > > >>> > > >>> test :: SomeData' -> Bool > > >>> test (SomeData' e) | e === Nothing = True > > >>> test _ = False > > >>> > > >>> It says > > >>> Could not deduce (Eq a1) arising from a use of ‘===’ > > >>> > > >>> How can I achieve something of the same effect? > > >>> > > >>> Thanks > > >>> Corentin > > >>> > > >>> _______________________________________________ > > >>> Haskell-Cafe mailing list > > >>> To (un)subscribe, modify options or view archives go to: > > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > >>> Only members subscribed via the mailman list are allowed > to post. > > >> > > >> > > > > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to > post. > > > > > > > > -- > > Ivan Lazar Miljenovic > > Ivan.Miljenovic at gmail.com > > > > http://IvanMiljenovic.wordpress.com > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > > -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 473 bytes Desc: OpenPGP digital signature URL: From chpatrick at gmail.com Thu Jul 21 09:50:33 2016 From: chpatrick at gmail.com (Patrick Chilton) Date: Thu, 21 Jul 2016 11:50:33 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: You also might want to consider whether this existential approach is correct to begin with. Could you just use a Maybe SomeData instead? Do you need the existential at all? https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/ On Thu, Jul 21, 2016 at 10:48 AM, Corentin Dupont wrote: > That's great, exactly what I need. > What do you mean by "just Typeable"? > Do you have another idea in mind? > > On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl < > anselm.scholl at tu-harburg.de> wrote: > >> If you want to use just Typeable, you can implement your own cast: >> Extract the TypeRep of the thing in SomeData, get the TyCon, which is >> the top-level constructor, i.e. Maybe without arguments, and compare it >> with the TyCon from Maybe. If they match, you coerce the value to Maybe >> () and use isNothing. While this is not completely safe, we do not >> evaluate the thing we just coerced to (), and thus are safe, as Maybe >> should have identical representation regardless of the type parameter. >> >> isNothing' :: SomeData -> Bool >> isNothing' (SomeData a) = tyCon == maybeTyCon >> && isNothing (unsafeCoerce a :: Maybe ()) >> where >> tyCon = typeRepTyCon (typeRep (mkProxy a)) >> maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ())) >> mkProxy :: a -> Proxy a >> mkProxy = const Proxy >> >> >> On 07/21/2016 09:51 AM, Corentin Dupont wrote: >> > Hi Ivan, >> > I could use isNothing, but the data is forall'ed... >> > I tried but it doesn't work: >> > >> > data SomeData = forall e. (Typeable e, Eq e) => SomeData e >> > >> > isNothing' :: SomeData -> Bool >> > isNothing' (SomeData a) = case (cast a) of >> > (a :: Maybe a) -> isNothing a >> > >> > Could not deduce (Typeable a) arising from a use of ‘cast’ >> > >> > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic >> > > wrote: >> > >> > On 21 July 2016 at 02:30, Corentin Dupont < >> corentin.dupont at gmail.com >> > > wrote: >> > > I see.... >> > > The think is, I am interested to know if "e" is "Nothing", >> whatever the type >> > > of Nothing is! >> > >> > Data.Maybe.isNothing ? >> > >> > > >> > > >> > > >> > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton >> > > >> > > wrote: >> > >> >> > >> It's because you're doing === Nothing and the type of the >> Nothing is >> > >> ambiguous (Maybe a1). >> > >> >> > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont >> > >> > >> wrote: >> > >>> >> > >>> Hi all, >> > >>> I'm surprised this doesn't work: >> > >>> >> > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e >> > >>> >> > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> >> Bool >> > >>> (===) x y = cast x == Just y >> > >>> >> > >>> test :: SomeData' -> Bool >> > >>> test (SomeData' e) | e === Nothing = True >> > >>> test _ = False >> > >>> >> > >>> It says >> > >>> Could not deduce (Eq a1) arising from a use of ‘===’ >> > >>> >> > >>> How can I achieve something of the same effect? >> > >>> >> > >>> Thanks >> > >>> Corentin >> > >>> >> > >>> _______________________________________________ >> > >>> Haskell-Cafe mailing list >> > >>> To (un)subscribe, modify options or view archives go to: >> > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > >>> Only members subscribed via the mailman list are allowed to >> post. >> > >> >> > >> >> > > >> > > >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > To (un)subscribe, modify options or view archives go to: >> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > Only members subscribed via the mailman list are allowed to post. >> > >> > >> > >> > -- >> > Ivan Lazar Miljenovic >> > Ivan.Miljenovic at gmail.com >> > http://IvanMiljenovic.wordpress.com >> > >> > >> > >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > To (un)subscribe, modify options or view archives go to: >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > Only members subscribed via the mailman list are allowed to post. >> > >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Thu Jul 21 11:26:56 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 21 Jul 2016 13:26:56 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: That's right, there are hints that my design is overly complex, I'm looking at simplifying it. On Thu, Jul 21, 2016 at 11:50 AM, Patrick Chilton wrote: > You also might want to consider whether this existential approach is > correct to begin with. Could you just use a Maybe SomeData instead? Do you > need the existential at all? > https://lukepalmer.wordpress.com/2010/01/24/haskell-antipattern-existential-typeclass/ > > On Thu, Jul 21, 2016 at 10:48 AM, Corentin Dupont < > corentin.dupont at gmail.com> wrote: > >> That's great, exactly what I need. >> What do you mean by "just Typeable"? >> Do you have another idea in mind? >> >> On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl < >> anselm.scholl at tu-harburg.de> wrote: >> >>> If you want to use just Typeable, you can implement your own cast: >>> Extract the TypeRep of the thing in SomeData, get the TyCon, which is >>> the top-level constructor, i.e. Maybe without arguments, and compare it >>> with the TyCon from Maybe. If they match, you coerce the value to Maybe >>> () and use isNothing. While this is not completely safe, we do not >>> evaluate the thing we just coerced to (), and thus are safe, as Maybe >>> should have identical representation regardless of the type parameter. >>> >>> isNothing' :: SomeData -> Bool >>> isNothing' (SomeData a) = tyCon == maybeTyCon >>> && isNothing (unsafeCoerce a :: Maybe ()) >>> where >>> tyCon = typeRepTyCon (typeRep (mkProxy a)) >>> maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe ())) >>> mkProxy :: a -> Proxy a >>> mkProxy = const Proxy >>> >>> >>> On 07/21/2016 09:51 AM, Corentin Dupont wrote: >>> > Hi Ivan, >>> > I could use isNothing, but the data is forall'ed... >>> > I tried but it doesn't work: >>> > >>> > data SomeData = forall e. (Typeable e, Eq e) => SomeData e >>> > >>> > isNothing' :: SomeData -> Bool >>> > isNothing' (SomeData a) = case (cast a) of >>> > (a :: Maybe a) -> isNothing a >>> > >>> > Could not deduce (Typeable a) arising from a use of ‘cast’ >>> > >>> > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic >>> > > wrote: >>> > >>> > On 21 July 2016 at 02:30, Corentin Dupont < >>> corentin.dupont at gmail.com >>> > > wrote: >>> > > I see.... >>> > > The think is, I am interested to know if "e" is "Nothing", >>> whatever the type >>> > > of Nothing is! >>> > >>> > Data.Maybe.isNothing ? >>> > >>> > > >>> > > >>> > > >>> > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton >>> > > >>> > > wrote: >>> > >> >>> > >> It's because you're doing === Nothing and the type of the >>> Nothing is >>> > >> ambiguous (Maybe a1). >>> > >> >>> > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont >>> > >> > >>> wrote: >>> > >>> >>> > >>> Hi all, >>> > >>> I'm surprised this doesn't work: >>> > >>> >>> > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e >>> > >>> >>> > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b -> >>> Bool >>> > >>> (===) x y = cast x == Just y >>> > >>> >>> > >>> test :: SomeData' -> Bool >>> > >>> test (SomeData' e) | e === Nothing = True >>> > >>> test _ = False >>> > >>> >>> > >>> It says >>> > >>> Could not deduce (Eq a1) arising from a use of ‘===’ >>> > >>> >>> > >>> How can I achieve something of the same effect? >>> > >>> >>> > >>> Thanks >>> > >>> Corentin >>> > >>> >>> > >>> _______________________________________________ >>> > >>> Haskell-Cafe mailing list >>> > >>> To (un)subscribe, modify options or view archives go to: >>> > >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > >>> Only members subscribed via the mailman list are allowed to >>> post. >>> > >> >>> > >> >>> > > >>> > > >>> > > _______________________________________________ >>> > > Haskell-Cafe mailing list >>> > > To (un)subscribe, modify options or view archives go to: >>> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > > Only members subscribed via the mailman list are allowed to post. >>> > >>> > >>> > >>> > -- >>> > Ivan Lazar Miljenovic >>> > Ivan.Miljenovic at gmail.com >>> > http://IvanMiljenovic.wordpress.com >>> > >>> > >>> > >>> > >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > To (un)subscribe, modify options or view archives go to: >>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> > Only members subscribed via the mailman list are allowed to post. >>> > >>> >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >>> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From corentin.dupont at gmail.com Thu Jul 21 20:27:50 2016 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Thu, 21 Jul 2016 22:27:50 +0200 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: That's great, it works, thanks. Now I am blocked on this one: data Foo a where A :: Foo a B :: Foo [a] deriving instance Typeable Foo deriving instance (Data a) => Data (Foo a) Could not deduce (a ~ [a0]) from the context (Typeable (Foo a), Data a) It would compile only if I comment the B constructor. How can I make a Data instance of Foo?? On Thu, Jul 21, 2016 at 11:26 AM, Jonas Scholl wrote: > With "just Typeable" I mean using only the Typeable class. As already > mentioned by Michael, it is also possible to achieve the same effect > with the Data class: > > data SomeData = forall e. (Data e, Eq e) => SomeData e > > isNothing'' :: SomeData -> Bool > isNothing'' (SomeData a) = toConstr a == toConstr (Nothing :: Maybe ()) > > Depending on your use-case, this may be simpler and it avoids using > unsafeCoerce, which may make one feel a little bit uneasy. On the other > hand, it adds an additional constraint. Additionally, a programmer can > write his own Data instance while Typeable instances are always > generated by the compiler (in newer versions of GHC). > > On 07/21/2016 10:48 AM, Corentin Dupont wrote: > > That's great, exactly what I need. > > What do you mean by "just Typeable"? > > Do you have another idea in mind? > > > > On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl > > > > wrote: > > > > If you want to use just Typeable, you can implement your own cast: > > Extract the TypeRep of the thing in SomeData, get the TyCon, which is > > the top-level constructor, i.e. Maybe without arguments, and compare > it > > with the TyCon from Maybe. If they match, you coerce the value to > Maybe > > () and use isNothing. While this is not completely safe, we do not > > evaluate the thing we just coerced to (), and thus are safe, as Maybe > > should have identical representation regardless of the type > parameter. > > > > isNothing' :: SomeData -> Bool > > isNothing' (SomeData a) = tyCon == maybeTyCon > > && isNothing (unsafeCoerce a :: Maybe ()) > > where > > tyCon = typeRepTyCon (typeRep (mkProxy a)) > > maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe > ())) > > mkProxy :: a -> Proxy a > > mkProxy = const Proxy > > > > > > On 07/21/2016 09:51 AM, Corentin Dupont wrote: > > > Hi Ivan, > > > I could use isNothing, but the data is forall'ed... > > > I tried but it doesn't work: > > > > > > data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > > > > > isNothing' :: SomeData -> Bool > > > isNothing' (SomeData a) = case (cast a) of > > > (a :: Maybe a) -> isNothing a > > > > > > Could not deduce (Typeable a) arising from a use of ‘cast’ > > > > > > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic > > > > > > >> wrote: > > > > > > On 21 July 2016 at 02:30, Corentin Dupont < > corentin.dupont at gmail.com > > > corentin.dupont at gmail.com>>> wrote: > > > > I see.... > > > > The think is, I am interested to know if "e" is "Nothing", > whatever the type > > > > of Nothing is! > > > > > > Data.Maybe.isNothing ? > > > > > > > > > > > > > > > > > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton > > > > > >> > > > > wrote: > > > >> > > > >> It's because you're doing === Nothing and the type of the > Nothing is > > > >> ambiguous (Maybe a1). > > > >> > > > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont > > > >> > > >> wrote: > > > >>> > > > >>> Hi all, > > > >>> I'm surprised this doesn't work: > > > >>> > > > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e > > > >>> > > > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b > > -> Bool > > > >>> (===) x y = cast x == Just y > > > >>> > > > >>> test :: SomeData' -> Bool > > > >>> test (SomeData' e) | e === Nothing = True > > > >>> test _ = False > > > >>> > > > >>> It says > > > >>> Could not deduce (Eq a1) arising from a use of ‘===’ > > > >>> > > > >>> How can I achieve something of the same effect? > > > >>> > > > >>> Thanks > > > >>> Corentin > > > >>> > > > >>> _______________________________________________ > > > >>> Haskell-Cafe mailing list > > > >>> To (un)subscribe, modify options or view archives go to: > > > >>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > >>> Only members subscribed via the mailman list are allowed > > to post. > > > >> > > > >> > > > > > > > > > > > > _______________________________________________ > > > > Haskell-Cafe mailing list > > > > To (un)subscribe, modify options or view archives go to: > > > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > > Only members subscribed via the mailman list are allowed to > > post. > > > > > > > > > > > > -- > > > Ivan Lazar Miljenovic > > > Ivan.Miljenovic at gmail.com > > >> > > > http://IvanMiljenovic.wordpress.com > > > > > > > > > > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > > > > > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. > > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.feuer at gmail.com Fri Jul 22 09:45:11 2016 From: david.feuer at gmail.com (David Feuer) Date: Fri, 22 Jul 2016 05:45:11 -0400 Subject: [Haskell-cafe] pattern match on forall'ed data In-Reply-To: References: Message-ID: I would be surprised if GHC could derive a Data instance for a GADT. Deriving generally tends to fall down for GADTs. I also suspect Data doesn't work for GADTs at all. Generic mechanisms for GADTs in Haskell seem a bit researchy still. On Jul 21, 2016 4:27 PM, "Corentin Dupont" wrote: > That's great, it works, thanks. > Now I am blocked on this one: > > data Foo a where > A :: Foo a > B :: Foo [a] > > deriving instance Typeable Foo > deriving instance (Data a) => Data (Foo a) > > Could not deduce (a ~ [a0]) > from the context (Typeable (Foo a), Data a) > > > It would compile only if I comment the B constructor. > How can I make a Data instance of Foo?? > > > On Thu, Jul 21, 2016 at 11:26 AM, Jonas Scholl < > anselm.scholl at tu-harburg.de> wrote: > >> With "just Typeable" I mean using only the Typeable class. As already >> mentioned by Michael, it is also possible to achieve the same effect >> with the Data class: >> >> data SomeData = forall e. (Data e, Eq e) => SomeData e >> >> isNothing'' :: SomeData -> Bool >> isNothing'' (SomeData a) = toConstr a == toConstr (Nothing :: Maybe ()) >> >> Depending on your use-case, this may be simpler and it avoids using >> unsafeCoerce, which may make one feel a little bit uneasy. On the other >> hand, it adds an additional constraint. Additionally, a programmer can >> write his own Data instance while Typeable instances are always >> generated by the compiler (in newer versions of GHC). >> >> On 07/21/2016 10:48 AM, Corentin Dupont wrote: >> > That's great, exactly what I need. >> > What do you mean by "just Typeable"? >> > Do you have another idea in mind? >> > >> > On Thu, Jul 21, 2016 at 10:23 AM, Jonas Scholl >> > > >> wrote: >> > >> > If you want to use just Typeable, you can implement your own cast: >> > Extract the TypeRep of the thing in SomeData, get the TyCon, which >> is >> > the top-level constructor, i.e. Maybe without arguments, and >> compare it >> > with the TyCon from Maybe. If they match, you coerce the value to >> Maybe >> > () and use isNothing. While this is not completely safe, we do not >> > evaluate the thing we just coerced to (), and thus are safe, as >> Maybe >> > should have identical representation regardless of the type >> parameter. >> > >> > isNothing' :: SomeData -> Bool >> > isNothing' (SomeData a) = tyCon == maybeTyCon >> > && isNothing (unsafeCoerce a :: Maybe ()) >> > where >> > tyCon = typeRepTyCon (typeRep (mkProxy a)) >> > maybeTyCon = typeRepTyCon $ typeRep (Proxy :: Proxy (Maybe >> ())) >> > mkProxy :: a -> Proxy a >> > mkProxy = const Proxy >> > >> > >> > On 07/21/2016 09:51 AM, Corentin Dupont wrote: >> > > Hi Ivan, >> > > I could use isNothing, but the data is forall'ed... >> > > I tried but it doesn't work: >> > > >> > > data SomeData = forall e. (Typeable e, Eq e) => SomeData e >> > > >> > > isNothing' :: SomeData -> Bool >> > > isNothing' (SomeData a) = case (cast a) of >> > > (a :: Maybe a) -> isNothing a >> > > >> > > Could not deduce (Typeable a) arising from a use of ‘cast’ >> > > >> > > On Wed, Jul 20, 2016 at 11:21 PM, Ivan Lazar Miljenovic >> > > >> > > > >> wrote: >> > > >> > > On 21 July 2016 at 02:30, Corentin Dupont < >> corentin.dupont at gmail.com >> > > > corentin.dupont at gmail.com>>> wrote: >> > > > I see.... >> > > > The think is, I am interested to know if "e" is "Nothing", >> whatever the type >> > > > of Nothing is! >> > > >> > > Data.Maybe.isNothing ? >> > > >> > > > >> > > > >> > > > >> > > > On Wed, Jul 20, 2016 at 5:44 PM, Patrick Chilton >> > > >> > >> >> > > > wrote: >> > > >> >> > > >> It's because you're doing === Nothing and the type of the >> Nothing is >> > > >> ambiguous (Maybe a1). >> > > >> >> > > >> On Wed, Jul 20, 2016 at 5:18 PM, Corentin Dupont >> > > >> > > > corentin.dupont at gmail.com >> > >> wrote: >> > > >>> >> > > >>> Hi all, >> > > >>> I'm surprised this doesn't work: >> > > >>> >> > > >>> data SomeData = forall e. (Typeable e, Eq e) => SomeData e >> > > >>> >> > > >>> (===) :: (Typeable a, Typeable b, Eq a, Eq b) => a -> b >> > -> Bool >> > > >>> (===) x y = cast x == Just y >> > > >>> >> > > >>> test :: SomeData' -> Bool >> > > >>> test (SomeData' e) | e === Nothing = True >> > > >>> test _ = False >> > > >>> >> > > >>> It says >> > > >>> Could not deduce (Eq a1) arising from a use of ‘===’ >> > > >>> >> > > >>> How can I achieve something of the same effect? >> > > >>> >> > > >>> Thanks >> > > >>> Corentin >> > > >>> >> > > >>> _______________________________________________ >> > > >>> Haskell-Cafe mailing list >> > > >>> To (un)subscribe, modify options or view archives go to: >> > > >>> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > >>> Only members subscribed via the mailman list are allowed >> > to post. >> > > >> >> > > >> >> > > > >> > > > >> > > > _______________________________________________ >> > > > Haskell-Cafe mailing list >> > > > To (un)subscribe, modify options or view archives go to: >> > > > >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > > Only members subscribed via the mailman list are allowed to >> > post. >> > > >> > > >> > > >> > > -- >> > > Ivan Lazar Miljenovic >> > > Ivan.Miljenovic at gmail.com >> > > >> >> > > http://IvanMiljenovic.wordpress.com >> > > >> > > >> > > >> > > >> > > _______________________________________________ >> > > Haskell-Cafe mailing list >> > > To (un)subscribe, modify options or view archives go to: >> > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > > Only members subscribed via the mailman list are allowed to post. >> > > >> > >> > >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > To (un)subscribe, modify options or view archives go to: >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> > Only members subscribed via the mailman list are allowed to post. >> > >> > >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Sat Jul 23 12:57:35 2016 From: adam at bergmark.nl (Adam Bergmark) Date: Sat, 23 Jul 2016 14:57:35 +0200 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: References: Message-ID: This sounds good to me, it is pretty awkward to have both representations, especially since they have diverged. It will also help the overlong compile time. One question: Will you still be able pretty print if you remove the annotations? - Adam On Wed, Jul 20, 2016 at 3:09 PM, Matthew Pickering < matthewtpickering at gmail.com> wrote: > Dear all, > > For several months I have had a branch of haskell-src-exts which has > been updated for all the new features in GHC 8. > > However, I have not yet released the changes as in this version I also > removed the simplified AST. To those unfamiliar, HSE provides two > ASTs, one which has source locations and one which doesn't. I have > removed the one which doesn't. > > This simplifies maintenance and I think also makes the library easier to > use. > > I have held back releasing this version as there are some people who > use the simplified AST. The changes necessary for the new version are > mechanical and easy to make. For example, David Fox updated > haskell-names to use my branch [1] with few problems. > > The question is, are there any users of the library who object to this > change? > > Matt > > > [1]: https://github.com/haskell-suite/haskell-names/pull/73 > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Sat Jul 23 13:10:57 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sat, 23 Jul 2016 15:10:57 +0200 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: References: Message-ID: Yes, I ported the pretty printer to work with the annotated tree but ignore the annotations. Matt On Sat, Jul 23, 2016 at 2:57 PM, Adam Bergmark wrote: > This sounds good to me, it is pretty awkward to have both representations, > especially since they have diverged. It will also help the overlong compile > time. > > One question: Will you still be able pretty print if you remove the > annotations? > > - Adam > > > On Wed, Jul 20, 2016 at 3:09 PM, Matthew Pickering > wrote: >> >> Dear all, >> >> For several months I have had a branch of haskell-src-exts which has >> been updated for all the new features in GHC 8. >> >> However, I have not yet released the changes as in this version I also >> removed the simplified AST. To those unfamiliar, HSE provides two >> ASTs, one which has source locations and one which doesn't. I have >> removed the one which doesn't. >> >> This simplifies maintenance and I think also makes the library easier to >> use. >> >> I have held back releasing this version as there are some people who >> use the simplified AST. The changes necessary for the new version are >> mechanical and easy to make. For example, David Fox updated >> haskell-names to use my branch [1] with few problems. >> >> The question is, are there any users of the library who object to this >> change? >> >> Matt >> >> >> [1]: https://github.com/haskell-suite/haskell-names/pull/73 >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > From matthewtpickering at gmail.com Sun Jul 24 10:11:14 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sun, 24 Jul 2016 12:11:14 +0200 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: References: Message-ID: I have released a new version, 1.18. https://hackage.haskell.org/package/haskell-src-exts-1.18.0 If anyone has any problems after upgrading then please send me an email or post an issue on the issue tracker. Matt On Sat, Jul 23, 2016 at 3:10 PM, Matthew Pickering wrote: > Yes, I ported the pretty printer to work with the annotated tree but > ignore the annotations. > > Matt > > On Sat, Jul 23, 2016 at 2:57 PM, Adam Bergmark wrote: >> This sounds good to me, it is pretty awkward to have both representations, >> especially since they have diverged. It will also help the overlong compile >> time. >> >> One question: Will you still be able pretty print if you remove the >> annotations? >> >> - Adam >> >> >> On Wed, Jul 20, 2016 at 3:09 PM, Matthew Pickering >> wrote: >>> >>> Dear all, >>> >>> For several months I have had a branch of haskell-src-exts which has >>> been updated for all the new features in GHC 8. >>> >>> However, I have not yet released the changes as in this version I also >>> removed the simplified AST. To those unfamiliar, HSE provides two >>> ASTs, one which has source locations and one which doesn't. I have >>> removed the one which doesn't. >>> >>> This simplifies maintenance and I think also makes the library easier to >>> use. >>> >>> I have held back releasing this version as there are some people who >>> use the simplified AST. The changes necessary for the new version are >>> mechanical and easy to make. For example, David Fox updated >>> haskell-names to use my branch [1] with few problems. >>> >>> The question is, are there any users of the library who object to this >>> change? >>> >>> Matt >>> >>> >>> [1]: https://github.com/haskell-suite/haskell-names/pull/73 >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> To (un)subscribe, modify options or view archives go to: >>> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >>> Only members subscribed via the mailman list are allowed to post. >> >> From lanablack at amok.cc Sun Jul 24 17:50:31 2016 From: lanablack at amok.cc (Lana Black) Date: Sun, 24 Jul 2016 17:50:31 +0000 Subject: [Haskell-cafe] How do I debug this RTS segfault? Message-ID: <20160724175031.GA7614@glow> Hello, I have run into this RTS bug recently. In short, when executing multiple consequtive forks, after 500-600 or so the process is terminated by SIGSEGV. I know this kind of thing is totally artificial, but still. The problem I have is that I can't get any meaningful backtrace in gdb. For example, for threaded RTS I get this (gdb) bt #0 0x0000000000560d63 in base_GHCziEventziThread_ensureIOManagerIsRunning1_info () Backtrace stopped: Cannot access memory at address 0x7fffff7fcea0 For non-threaded RTS I get this (gdb) bt #0 0x00000000007138c9 in stg_makeStablePtrzh () Backtrace stopped: Cannot access memory at address 0x7fffff7fc720 Build command: ghc --make -O2 -g -fforce-recomp fork.hs Add threaded if needed. I was able to reproduce this bug with both GHC 7.10.3 and todays HEAD with the code below. >import System.Exit (exitSuccess) >import System.Posix.Process (forkProcess) > >fork_ n | n > 0 = processPid =<< forkProcess (fork_ $! n - 1) > | otherwise = putStrLn "I'm done!" > >processPid pid | pid > 0 = exitSuccess > | pid < 0 = putStrLn "OOOPS, forkProcess failed!" > | otherwise = pure () > >main = fork_ 1000 > With best regards. From aeyakovenko at gmail.com Sun Jul 24 21:25:08 2016 From: aeyakovenko at gmail.com (Anatoly Yakovenko) Date: Sun, 24 Jul 2016 21:25:08 +0000 Subject: [Haskell-cafe] How do I debug this RTS segfault? In-Reply-To: <20160724175031.GA7614@glow> References: <20160724175031.GA7614@glow> Message-ID: It's probably out of file descriptors. It's possible that it tries to open another one during the error handling. On Sun, Jul 24, 2016 at 10:50 AM Lana Black wrote: > Hello, > > I have run into this RTS bug recently. In short, when executing multiple > consequtive forks, after 500-600 or so the process is terminated by > SIGSEGV. I know this kind of thing is totally artificial, but still. > > The problem I have is that I can't get any meaningful backtrace in gdb. > For example, for threaded RTS I get this > > (gdb) bt > #0 0x0000000000560d63 in > base_GHCziEventziThread_ensureIOManagerIsRunning1_info () > Backtrace stopped: Cannot access memory at address 0x7fffff7fcea0 > > For non-threaded RTS I get this > > (gdb) bt > #0 0x00000000007138c9 in stg_makeStablePtrzh () > Backtrace stopped: Cannot access memory at address 0x7fffff7fc720 > > Build command: ghc --make -O2 -g -fforce-recomp fork.hs > Add threaded if needed. > > I was able to reproduce this bug with both GHC 7.10.3 and todays HEAD > with the code below. > > >import System.Exit (exitSuccess) > >import System.Posix.Process (forkProcess) > > > >fork_ n | n > 0 = processPid =<< forkProcess (fork_ $! n - 1) > > | otherwise = putStrLn "I'm done!" > > > >processPid pid | pid > 0 = exitSuccess > > | pid < 0 = putStrLn "OOOPS, forkProcess failed!" > > | otherwise = pure () > > > >main = fork_ 1000 > > > > With best regards. > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From briand at aracnet.com Sun Jul 24 23:48:20 2016 From: briand at aracnet.com (briand at aracnet.com) Date: Sun, 24 Jul 2016 16:48:20 -0700 Subject: [Haskell-cafe] good choice for random number generator ? Message-ID: <20160724164820.2f66cd20@basalt.deldotd.com> There's quite a few. Many are very old. I would have like to use vector-random and got this : Data/Vector/Random/Mersenne.hs:33:18: Could not find module ‘Data.Vector.Fusion.Stream’ It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. Use -v to see a list of the files searched for. Data/Vector/Random/Mersenne.hs:35:18: Could not find module ‘Data.Vector.Fusion.Stream.Size’ It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. Use -v to see a list of the files searched for. I wouldn't be opposed to fixing it, but I'm wondering at this point there isn't a better package to use instead. I'm looking for both integer and floating point random numbers, uniform and gaussian. gsl-random looks promising as does mwc-random. any other suggestions ? Thanks, Brian From lanablack at amok.cc Mon Jul 25 00:46:54 2016 From: lanablack at amok.cc (Lana Black) Date: Mon, 25 Jul 2016 00:46:54 +0000 Subject: [Haskell-cafe] How do I debug this RTS segfault? In-Reply-To: References: <20160724175031.GA7614@glow> Message-ID: <20160725004654.GB7614@glow> On 21:25 Sun 24 Jul , Anatoly Yakovenko wrote: > It's probably out of file descriptors. It's possible that it tries to open > another one during the error handling. > On Sun, Jul 24, 2016 at 10:50 AM Lana Black wrote: > > > Hello, > > > > I have run into this RTS bug recently. In short, when executing multiple > > consequtive forks, after 500-600 or so the process is terminated by > > SIGSEGV. I know this kind of thing is totally artificial, but still. > > > > The problem I have is that I can't get any meaningful backtrace in gdb. > > For example, for threaded RTS I get this > > > > (gdb) bt > > #0 0x0000000000560d63 in > > base_GHCziEventziThread_ensureIOManagerIsRunning1_info () > > Backtrace stopped: Cannot access memory at address 0x7fffff7fcea0 > > > > For non-threaded RTS I get this > > > > (gdb) bt > > #0 0x00000000007138c9 in stg_makeStablePtrzh () > > Backtrace stopped: Cannot access memory at address 0x7fffff7fc720 > > > > Build command: ghc --make -O2 -g -fforce-recomp fork.hs > > Add threaded if needed. > > > > I was able to reproduce this bug with both GHC 7.10.3 and todays HEAD > > with the code below. > > > > >import System.Exit (exitSuccess) > > >import System.Posix.Process (forkProcess) > > > > > >fork_ n | n > 0 = processPid =<< forkProcess (fork_ $! n - 1) > > > | otherwise = putStrLn "I'm done!" > > > > > >processPid pid | pid > 0 = exitSuccess > > > | pid < 0 = putStrLn "OOOPS, forkProcess failed!" > > > | otherwise = pure () > > > > > >main = fork_ 1000 > > > > > > > With best regards. > > _______________________________________________ > > Haskell-Cafe mailing list > > To (un)subscribe, modify options or view archives go to: > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > Only members subscribed via the mailman list are allowed to post. Seems like this is not the case. I actually overlooked GHCs -debug option, with it I'm now able to get a stacktrace. Furthermore, the number of used file descriptors is well within the limit, and changing the latter with `ulimit -n` does not affect the outcome. Curiously, the stacks are rather different for threaded and non-threaded RTS. Non-threaded: (gdb) bt #0 INFO_PTR_TO_STRUCT (info=) at includes/rts/storage/ClosureMacros.h:60 #1 0x000000000070e956 in get_itbl (c=0x20006e7f8) at includes/rts/storage/ClosureMacros.h:87 #2 0x000000000070ec3c in closure_sizeW (p=0x20006e7f8) at includes/rts/storage/ClosureMacros.h:439 #3 0x000000000070ecf7 in overwritingClosure (p=0x20006e7f8) at includes/rts/storage/ClosureMacros.h:555 #4 0x0000000000725dd7 in stg_upd_frame_info () #5 0x0000000000000000 in ?? () Threaded: (gdb) bt #0 0x00007ffff6ce49ce in _IO_vfprintf_internal (s=s at entry=0x7fffff7ff430, format=format at entry=0x7ffff75c3550 "/proc/self/task/%u/comm", ap=ap at entry=0x7fffff7ff558) at vfprintf.c:1266 #1 0x00007ffff6d0954b in __IO_vsprintf (string=0x7fffff7ff630 "`\366\177\377\377\177", format=0x7ffff75c3550 "/proc/self/task/%u/comm", args=args at entry=0x7fffff7ff558) at iovsprintf.c:42 #2 0x00007ffff6cecd47 in __sprintf (s=s at entry=0x7fffff7ff630 "`\366\177\377\377\177", format=format at entry=0x7ffff75c3550 "/proc/self/task/%u/comm") at sprintf.c:32 #3 0x00007ffff75c1f2b in pthread_setname_np (th=140737317025536, name=0x78ba04 "ghc_ticker") at ../sysdeps/unix/sysv/linux/pthread_setname.c:49 #4 0x000000000072ce4e in initTicker (interval=10000000, handle_tick=0x71a23d ) at rts/posix/itimer/Pthread.c:173 #5 0x000000000071a32f in initTimer () at rts/Timer.c:111 #6 0x0000000000703c26 in forkProcess (entry=0x207) at rts/Schedule.c:2072 #7 0x0000000000405bf7 in s7dF_info () #8 0x0000000000000000 in ?? () From mle+hs at mega-nerd.com Mon Jul 25 11:19:39 2016 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Mon, 25 Jul 2016 21:19:39 +1000 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: <20160724164820.2f66cd20@basalt.deldotd.com> References: <20160724164820.2f66cd20@basalt.deldotd.com> Message-ID: <20160725211939.e8d352c1230c830208bf27a2@mega-nerd.com> briand at aracnet.com wrote: > Data/Vector/Random/Mersenne.hs:33:18: > Could not find module ‘Data.Vector.Fusion.Stream’ > It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. > Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. Have you tried adding the vector package to the build-depends to you cabal file as suggested in that error message? Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From oleg.grenrus at iki.fi Mon Jul 25 11:25:35 2016 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Mon, 25 Jul 2016 14:25:35 +0300 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: <20160724164820.2f66cd20@basalt.deldotd.com> References: <20160724164820.2f66cd20@basalt.deldotd.com> Message-ID: I added vector-random to matrix.h.h.o build queue [1]: Will check whether it have some problems, and report here & upstream Oleg - [1] http://matrix.hackage.haskell.org/package/vector-random > On 25 Jul 2016, at 02:48, wrote: > > There's quite a few. Many are very old. > > I would have like to use vector-random and got this : > > Data/Vector/Random/Mersenne.hs:33:18: > Could not find module ‘Data.Vector.Fusion.Stream’ > It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. > Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. > Use -v to see a list of the files searched for. > > Data/Vector/Random/Mersenne.hs:35:18: > Could not find module ‘Data.Vector.Fusion.Stream.Size’ > It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. > Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. > Use -v to see a list of the files searched for. > > I wouldn't be opposed to fixing it, but I'm wondering at this point there isn't a better package to use instead. > > I'm looking for both integer and floating point random numbers, uniform and gaussian. > > gsl-random looks promising as does mwc-random. > > any other suggestions ? > > Thanks, > > Brian > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From chneukirchen at gmail.com Mon Jul 25 12:22:03 2016 From: chneukirchen at gmail.com (Christian Neukirchen) Date: Mon, 25 Jul 2016 14:22:03 +0200 Subject: [Haskell-cafe] Munich Haskell Meeting, 2016-07-27 @ 19:30 Augustiner Bierhalle Message-ID: <87y44phpqs.fsf@gmail.com> Dear all, This week, our monthly Munich Haskell Meeting will take place again on Wednesday, July 27 at Augustiner Bierhalle (Neuhauser Str.) at 19h30. For details see here: http://muenchen.haskell.bayern/dates.html If you plan to join, please add yourself to this dudle so we can reserve enough seats! It is OK to add yourself to the dudle anonymously or pseudonymously. https://dudle.inf.tu-dresden.de/haskell-munich-jul-2016/ Everybody is welcome! cu, -- Christian Neukirchen http://chneukirchen.org From lonetiger at gmail.com Mon Jul 25 12:52:38 2016 From: lonetiger at gmail.com (Phyx) Date: Mon, 25 Jul 2016 12:52:38 +0000 Subject: [Haskell-cafe] linking dlls with relative paths on Windows Message-ID: Hi Peter, I forgot to respond to this, if you haven't received an answer to this yet then feel free to open a ticket on the ghc trac and I will take a look as soon as I have working Internet again. I don't know what the status is of this for now, the linked to stackoverfow article should work though. Also 7.10.3 has some issues when loading dependent dlls in the same folder as the main one being loaded when not on the search path. 8.0.1 should be fine. Kind regards, Tamar -------------- next part -------------- An HTML attachment was scrubbed... URL: From konn.jinro at gmail.com Mon Jul 25 15:24:20 2016 From: konn.jinro at gmail.com (Hiromi ISHII) Date: Tue, 26 Jul 2016 00:24:20 +0900 Subject: [Haskell-cafe] Is there any way in GHC plugin to refer exposed but defined in a hidden module? Message-ID: <6413D892-A51E-41DF-9952-CFECCCF4020A@gmail.com> Hi Cafe, I'm currently writing a simple GHC Typechecker plugin to augment typelevel naturals with a presburger arithmetic solver [^1]. I want to use type-class constraints to give premisses to the solver, for example, `Empty a` constraint means "a is false (empty type)". So I have to get TyCon information in TcPluginM monad and I wrote as follows: ```haskell do md <- lookupModule (mkModuleName "Proof.Propositional.Empty") (fsLit "equational-reasoning") classTyCon <$> (tcLookupClass =<< lookupOrig md (mkTcOcc "Empty")) ``` But this code doesn't work as expected. For example, the code ```haskell {-# LANGUAGE DataKinds, TypeOperators, GADTs, TypeFamilies, ExplicitForAll, FlexibleContexts #-} import Data.Type.Equality import GHC.TypeLits (type (+), type (<=), type (<=?)) import Proof.Propositional (Empty(..)) predSucc :: Empty (n :~: 0) => proxy n -> (n + 1 <=? n + n) :~: 'True predSucc _ = Witness ``` resulted in the following compile-time error: ``` Can't find interface-file declaration for type constructor or class equational-reasoning-0.4.0.0:Proof.Propositional.Empty Probable cause: bug in .hi-boot file, or inconsistent .hi file Use -ddump-if-trace to get an idea of which file caused the error ``` The probem is, Empty class is provided by separate existing package [^2], but is once defined in hidden module and re-exported from exposed from exposed module. If I expose the module where Empty is originally defined and change the module name passed to lookupModule appropriately, then the first code becomes working as expected. So the question: is there any way to retrieve TyCon information defined in hidden module but exported? [^1]: https://github.com/konn/ghc-typelits-presburger/ [^2]: https://github.com/konn/equational-reasoning-in-haskell -- Hiromi ISHII konn.jinro at gmail.com Doctoral program in Mathematics, University of Tsukuba -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 496 bytes Desc: Message signed with OpenPGP using GPGMail URL: From trebla at vex.net Mon Jul 25 19:13:07 2016 From: trebla at vex.net (Albert Y. C. Lai) Date: Mon, 25 Jul 2016 15:13:07 -0400 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: <20160724164820.2f66cd20@basalt.deldotd.com> References: <20160724164820.2f66cd20@basalt.deldotd.com> Message-ID: <370eb2bd-2809-1f54-a112-3b59cbaef723@vex.net> On 2016-07-24 07:48 PM, briand at aracnet.com wrote: > I'm looking for both integer and floating point random numbers, uniform and gaussian. > > gsl-random looks promising as does mwc-random. > > any other suggestions ? I like tf-random for its functional interface and splittable design. But I have only judged subjectively. And it only does uniform. From oleg.grenrus at iki.fi Mon Jul 25 19:30:24 2016 From: oleg.grenrus at iki.fi (Oleg Grenrus) Date: Mon, 25 Jul 2016 22:30:24 +0300 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: References: <20160724164820.2f66cd20@basalt.deldotd.com> Message-ID: <08F96967-6CFF-4C0D-BE70-85A176023544@iki.fi> Seems that `vector-random-0.2` is incompatible with new fusion implementation of `vector-0.11` Also due “recent” GHC being more strict about pragmas, build fails for all GHC >=7.2 Data/Vector/Random/Mersenne.hs:85:5: The INLINE pragma for default method `random' lacks an accompanying binding I edited bounds on Hackage to disallow invalid build-plans. - Oleg > On 25 Jul 2016, at 14:25, Oleg Grenrus wrote: > > I added vector-random to matrix.h.h.o build queue [1]: > > Will check whether it have some problems, and report here & upstream > > Oleg > > - [1] http://matrix.hackage.haskell.org/package/vector-random > > >> On 25 Jul 2016, at 02:48, wrote: >> >> There's quite a few. Many are very old. >> >> I would have like to use vector-random and got this : >> >> Data/Vector/Random/Mersenne.hs:33:18: >> Could not find module ‘Data.Vector.Fusion.Stream’ >> It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. >> Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. >> Use -v to see a list of the files searched for. >> >> Data/Vector/Random/Mersenne.hs:35:18: >> Could not find module ‘Data.Vector.Fusion.Stream.Size’ >> It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. >> Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. >> Use -v to see a list of the files searched for. >> >> I wouldn't be opposed to fixing it, but I'm wondering at this point there isn't a better package to use instead. >> >> I'm looking for both integer and floating point random numbers, uniform and gaussian. >> >> gsl-random looks promising as does mwc-random. >> >> any other suggestions ? >> >> Thanks, >> >> Brian >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 842 bytes Desc: Message signed with OpenPGP using GPGMail URL: From lonetiger at gmail.com Mon Jul 25 21:03:28 2016 From: lonetiger at gmail.com (Phyx) Date: Mon, 25 Jul 2016 21:03:28 +0000 Subject: [Haskell-cafe] Use GHC API in standalone executable? Message-ID: I guess this depends on what you want to do. I've seen various level of GHC API usage in standalone applications, but it just depends on how much of the compiler pipeline you want to use. Their are ways to override the paths or provide stubs for programs ghc expects to be there. I've packaged API calls into shared libraries myself before, in that case I was mostly accessing the compiler frontend. -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Jul 26 00:40:50 2016 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 25 Jul 2016 20:40:50 -0400 Subject: [Haskell-cafe] How do I debug this RTS segfault? In-Reply-To: <20160725004654.GB7614@glow> References: <20160724175031.GA7614@glow> <20160725004654.GB7614@glow> Message-ID: Fork process is very very different from forkIo and fork os. Have you tried fork bombing from shell with a similar program? I don't think your os can handle 2^1000 process ids? Right? I seem to reall process ids being 32 or 64 bit. On Sunday, July 24, 2016, Lana Black wrote: > On 21:25 Sun 24 Jul , Anatoly Yakovenko wrote: > > It's probably out of file descriptors. It's possible that it tries to > open > > another one during the error handling. > > On Sun, Jul 24, 2016 at 10:50 AM Lana Black wrote: > > > > > Hello, > > > > > > I have run into this RTS bug recently. In short, when executing > multiple > > > consequtive forks, after 500-600 or so the process is terminated by > > > SIGSEGV. I know this kind of thing is totally artificial, but still. > > > > > > The problem I have is that I can't get any meaningful backtrace in gdb. > > > For example, for threaded RTS I get this > > > > > > (gdb) bt > > > #0 0x0000000000560d63 in > > > base_GHCziEventziThread_ensureIOManagerIsRunning1_info () > > > Backtrace stopped: Cannot access memory at address 0x7fffff7fcea0 > > > > > > For non-threaded RTS I get this > > > > > > (gdb) bt > > > #0 0x00000000007138c9 in stg_makeStablePtrzh () > > > Backtrace stopped: Cannot access memory at address 0x7fffff7fc720 > > > > > > Build command: ghc --make -O2 -g -fforce-recomp fork.hs > > > Add threaded if needed. > > > > > > I was able to reproduce this bug with both GHC 7.10.3 and todays HEAD > > > with the code below. > > > > > > >import System.Exit (exitSuccess) > > > >import System.Posix.Process (forkProcess) > > > > > > > >fork_ n | n > 0 = processPid =<< forkProcess (fork_ $! n - 1) > > > > | otherwise = putStrLn "I'm done!" > > > > > > > >processPid pid | pid > 0 = exitSuccess > > > > | pid < 0 = putStrLn "OOOPS, forkProcess failed!" > > > > | otherwise = pure () > > > > > > > >main = fork_ 1000 > > > > > > > > > > With best regards. > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > To (un)subscribe, modify options or view archives go to: > > > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > Only members subscribed via the mailman list are allowed to post. > > Seems like this is not the case. I actually overlooked GHCs -debug > option, with it I'm now able to get a stacktrace. Furthermore, the > number of used file descriptors is well within the limit, and changing > the latter with `ulimit -n` does not affect the outcome. > > Curiously, the stacks are rather different for threaded and non-threaded > RTS. > > Non-threaded: > (gdb) bt > #0 INFO_PTR_TO_STRUCT (info= memory at address 0x7fffff7feff0>) at > includes/rts/storage/ClosureMacros.h:60 > #1 0x000000000070e956 in get_itbl (c=0x20006e7f8) at > includes/rts/storage/ClosureMacros.h:87 > #2 0x000000000070ec3c in closure_sizeW (p=0x20006e7f8) at > includes/rts/storage/ClosureMacros.h:439 > #3 0x000000000070ecf7 in overwritingClosure (p=0x20006e7f8) at > includes/rts/storage/ClosureMacros.h:555 > #4 0x0000000000725dd7 in stg_upd_frame_info () > #5 0x0000000000000000 in ?? () > > Threaded: > (gdb) bt > #0 0x00007ffff6ce49ce in _IO_vfprintf_internal (s=s at entry=0x7fffff7ff430, > format=format at entry=0x7ffff75c3550 "/proc/self/task/%u/comm", ap=ap at entry > =0x7fffff7ff558) > at vfprintf.c:1266 > #1 0x00007ffff6d0954b in __IO_vsprintf (string=0x7fffff7ff630 > "`\366\177\377\377\177", format=0x7ffff75c3550 "/proc/self/task/%u/comm", > args=args at entry=0x7fffff7ff558) > at iovsprintf.c:42 > #2 0x00007ffff6cecd47 in __sprintf (s=s at entry=0x7fffff7ff630 > "`\366\177\377\377\177", format=format at entry=0x7ffff75c3550 > "/proc/self/task/%u/comm") at sprintf.c:32 > #3 0x00007ffff75c1f2b in pthread_setname_np (th=140737317025536, > name=0x78ba04 "ghc_ticker") at > ../sysdeps/unix/sysv/linux/pthread_setname.c:49 > #4 0x000000000072ce4e in initTicker (interval=10000000, > handle_tick=0x71a23d ) at rts/posix/itimer/Pthread.c:173 > #5 0x000000000071a32f in initTimer () at rts/Timer.c:111 > #6 0x0000000000703c26 in forkProcess (entry=0x207) at rts/Schedule.c:2072 > #7 0x0000000000405bf7 in s7dF_info () > #8 0x0000000000000000 in ?? () > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From briand at aracnet.com Tue Jul 26 04:33:34 2016 From: briand at aracnet.com (briand at aracnet.com) Date: Mon, 25 Jul 2016 21:33:34 -0700 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: <20160725211939.e8d352c1230c830208bf27a2@mega-nerd.com> References: <20160724164820.2f66cd20@basalt.deldotd.com> <20160725211939.e8d352c1230c830208bf27a2@mega-nerd.com> Message-ID: <20160725213334.70a11771@basalt.deldotd.com> On Mon, 25 Jul 2016 21:19:39 +1000 Erik de Castro Lopo wrote: > briand at aracnet.com wrote: > > > Data/Vector/Random/Mersenne.hs:33:18: > > Could not find module ‘Data.Vector.Fusion.Stream’ > > It is a member of the hidden package ‘vector-0.10.12.3 at vecto_1COyUuV1LrA1IjYnWfJnbs’. > > Perhaps you need to add ‘vector’ to the build-depends in your .cabal file. > > Have you tried adding the vector package to the build-depends to you > cabal file as suggested in that error message? > No. it looked very old and out-of-date, so I thought i would see what other recommendations people had. Brian From briand at aracnet.com Tue Jul 26 04:35:44 2016 From: briand at aracnet.com (briand at aracnet.com) Date: Mon, 25 Jul 2016 21:35:44 -0700 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: <08F96967-6CFF-4C0D-BE70-85A176023544@iki.fi> References: <20160724164820.2f66cd20@basalt.deldotd.com> <08F96967-6CFF-4C0D-BE70-85A176023544@iki.fi> Message-ID: <20160725213544.1393f82e@basalt.deldotd.com> On Mon, 25 Jul 2016 22:30:24 +0300 Oleg Grenrus wrote: > Seems that `vector-random-0.2` is incompatible with new fusion implementation of `vector-0.11` > Also due “recent” GHC being more strict about pragmas, build fails for all GHC >=7.2 > > Data/Vector/Random/Mersenne.hs:85:5: > The INLINE pragma for default method `random' lacks an accompanying binding > > I edited bounds on Hackage to disallow invalid build-plans. > Do you think it's fixable by going through and updating pragmas and such, or does it require a more involved rewrite ? Brian From tanuki at gmail.com Tue Jul 26 04:51:57 2016 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Mon, 25 Jul 2016 21:51:57 -0700 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: <20160725213544.1393f82e@basalt.deldotd.com> References: <20160724164820.2f66cd20@basalt.deldotd.com> <08F96967-6CFF-4C0D-BE70-85A176023544@iki.fi> <20160725213544.1393f82e@basalt.deldotd.com> Message-ID: It's been well over a year since I was looking at RNGs and I'm not sure I trust my instincts from that far back, but my pick at the time was pcg-random: https://hackage.haskell.org/package/pcg-random On Jul 25, 2016 9:35 PM, wrote: > On Mon, 25 Jul 2016 22:30:24 +0300 > Oleg Grenrus wrote: > > > Seems that `vector-random-0.2` is incompatible with new fusion > implementation of `vector-0.11` > > Also due “recent” GHC being more strict about pragmas, build fails for > all GHC >=7.2 > > > > Data/Vector/Random/Mersenne.hs:85:5: > > The INLINE pragma for default method `random' lacks an accompanying > binding > > > > I edited bounds on Hackage to disallow invalid build-plans. > > > > Do you think it's fixable by going through and updating pragmas and such, > or does it require a more involved rewrite ? > > Brian > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From briand at aracnet.com Tue Jul 26 05:21:11 2016 From: briand at aracnet.com (briand at aracnet.com) Date: Mon, 25 Jul 2016 22:21:11 -0700 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: References: <20160724164820.2f66cd20@basalt.deldotd.com> <08F96967-6CFF-4C0D-BE70-85A176023544@iki.fi> <20160725213544.1393f82e@basalt.deldotd.com> Message-ID: <20160725222111.2395bd45@basalt.deldotd.com> On Mon, 25 Jul 2016 21:51:57 -0700 Theodore Lief Gannon wrote: > It's been well over a year since I was looking at RNGs and I'm not sure I > trust my instincts from that far back, but my pick at the time was > pcg-random: https://hackage.haskell.org/package/pcg-random > Thanks. I hadn't seen that one. Brian From adam at well-typed.com Tue Jul 26 08:24:38 2016 From: adam at well-typed.com (Adam Gundry) Date: Tue, 26 Jul 2016 09:24:38 +0100 Subject: [Haskell-cafe] Different behaviour with -XAllowAmbiguousTypes in 7.10.3b and 8.0.1 In-Reply-To: References: Message-ID: <9f068bee-5ef0-4f30-d39f-281d1d29d298@well-typed.com> Hi Max, I think 7.10.3 is correct to reject both programs. The `get` function with a type signature is ambiguous, even when AllowAmbiguousTypes is enabled, because there is no reason for GHC to pick `e` and `a` when instantiating the type variables in the call to `fsmRead`. In general, if a function's type can be inferred, it should be possible to give it a signature with that type. 8.0.1 apparently doesn't respect this property, which is a bug. AllowAmbiguousTypes should make it possible to write a function with the same type signature as `get`, e.g. by using TypeApplications to fix the variables: get :: forall st s e a. (FSMStore st s e a) => st -> String -> s get st i = fsmRead @st @s @e @a st i Of course, this merely defers the ambiguity to the call sites of `get`. Hope this helps, Adam On 20/07/16 16:52, Max Amanshauser wrote: > Hi, > > while porting a library to Haskell, which deals with persisting finite state automata to various stores, depending on the user's choice and the instances provided for types s(tate) e(vent) a(ction), I ran into different behaviour in ghc 7.10.3b and 8.0.1 related to ambiguity checks. This is a minimised and somewhat contrived example: > >> -- testme.hs >> >> {-# LANGUAGE MultiParamTypeClasses #-} >> {-# LANGUAGE FlexibleInstances #-} >> {-# LANGUAGE AllowAmbiguousTypes #-} >> >> module TestMe where >> >> data MyStore = MyStore >> >> class FSMStore st s e a where >> fsmRead :: st -> String -> s >> >> instance (Num s) => FSMStore MyStore s e a where >> fsmRead st i = 23 >> >> get :: (FSMStore st s e a) => st -> String -> s >> get st i = fsmRead st i > > With GHC 8.0.1 I get: > >> *TestMe> :l test.hs >> [1 of 1] Compiling TestMe ( test.hs, interpreted ) >> >> test.hs:19:12: error: >> • Could not deduce (FSMStore st s e0 a0) >> arising from a use of ‘fsmRead’ >> from the context: FSMStore st s e a >> bound by the type signature for: >> get :: FSMStore st s e a => st -> String -> s >> at test.hs:18:1-47 >> The type variables ‘e0’, ‘a0’ are ambiguous >> Relevant bindings include >> st :: st (bound at test.hs:19:5) >> get :: st -> String -> s (bound at test.hs:19:1) >> These potential instance exist: >> instance Num s => FSMStore MyStore s e a >> -- Defined at test.hs:12:10 >> • In the expression: fsmRead st i >> In an equation for ‘get’: get st i = fsmRead st i >> Failed, modules loaded: none. > > However, when I remove the type signature for get: > >> Prelude> :l test.hs >> [1 of 1] Compiling TestMe ( test.hs, interpreted ) >> Ok, modules loaded: TestMe. >> *TestMe> :t get >> get :: FSMStore st s e a => st -> String -> s >> *TestMe> get MyStore "asdf" >> 23 > > GHC inferred the exact same type I provided, but this time it compiles successfully. > > When going back to GHC 7.10.3b, without type signature: > >> GHCi, version 7.10.3: http://www.haskell.org/ghc/ :? for help >> :Prelude> :l test.hs >> [1 of 1] Compiling TestMe ( test.hs, interpreted ) >> >> test.hs:19:1: >> Could not deduce (FSMStore st s e0 a0) >> from the context (FSMStore st s e a) >> bound by the inferred type for ‘get’: >> FSMStore st s e a => st -> String -> s >> at test.hs:19:1-23 >> The type variables ‘e0’, ‘a0’ are ambiguous >> When checking that ‘get’ has the inferred type >> get :: forall st s e a. FSMStore st s e a => st -> String -> s >> Probable cause: the inferred type is ambiguous >> Failed, modules loaded: none. > > So my questions are: > *) What's with the different behaviour depending on whether the type sig is inferred or provided? > *) Is GHC 7.10.3b or 8.0.1 closer to the correct behaviour w.r.t. -XAllowAmbiguousTypes? > > -- > Regards, > Max Amanshauser. From dominic at steinitz.org Tue Jul 26 09:08:30 2016 From: dominic at steinitz.org (Dominic Steinitz) Date: Tue, 26 Jul 2016 09:08:30 +0000 (UTC) Subject: [Haskell-cafe] good choice for random number generator ? References: <20160724164820.2f66cd20@basalt.deldotd.com> Message-ID: If you want distributions in distinction to just a random number generator, I recommend random-fu. You can plug in at least MT and MWC as the random number generators and you get pdfs and cdfs as well. Let me know if you need anything adding to it. I am also keen to improve its documentation. I made a small start here: https://hackage.haskell.org/package/random-fu-0.2.7.0/docs/Data-Random- Distribution-Binomial.html but time as always is the enemy. Feel free to contribute. Dominic. From list at mroth.net Tue Jul 26 10:36:09 2016 From: list at mroth.net (Michael Roth) Date: Tue, 26 Jul 2016 12:36:09 +0200 Subject: [Haskell-cafe] Forcing the kind in data Message-ID: Hi, if I have: data Foobar a b = Foobar it has kind: * -> * -> * How can I force the kind to: (* -> *) -> * -> * ? Thank you! From ivan.miljenovic at gmail.com Tue Jul 26 10:55:44 2016 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Tue, 26 Jul 2016 20:55:44 +1000 Subject: [Haskell-cafe] Forcing the kind in data In-Reply-To: References: Message-ID: On 26 July 2016 at 20:36, Michael Roth wrote: > Hi, > > if I have: > > data Foobar a b = Foobar > > it has kind: > > * -> * -> * > > How can I force the kind to: > > (* -> *) -> * -> * {-# LANGUAGE KindSignatures #-} data Foobar (a :: * -> *) (b :: *) = Foobar -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From trupill at gmail.com Tue Jul 26 10:59:37 2016 From: trupill at gmail.com (Alejandro Serrano Mena) Date: Tue, 26 Jul 2016 12:59:37 +0200 Subject: [Haskell-cafe] Forcing the kind in data In-Reply-To: References: Message-ID: Given that neither `a` nor `b` are used in the data type, you could also make `Foobar` kind-polymorphic: {-# LANGUAGE PolyKinds #-} data Foobar a b = Foobar You can check that GHC has inferred polymorphic kinds by asking for information in a GHCi prompt: Prelude> :info Foobar data Foobar (a :: k1) (b :: k2) = Foobar 2016-07-26 12:55 GMT+02:00 Ivan Lazar Miljenovic : > On 26 July 2016 at 20:36, Michael Roth wrote: > > Hi, > > > > if I have: > > > > data Foobar a b = Foobar > > > > it has kind: > > > > * -> * -> * > > > > How can I force the kind to: > > > > (* -> *) -> * -> * > > {-# LANGUAGE KindSignatures #-} > > data Foobar (a :: * -> *) (b :: *) = Foobar > > -- > Ivan Lazar Miljenovic > Ivan.Miljenovic at gmail.com > http://IvanMiljenovic.wordpress.com > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From anatoly.zaretsky at gmail.com Tue Jul 26 13:46:15 2016 From: anatoly.zaretsky at gmail.com (Anatoly Zaretsky) Date: Tue, 26 Jul 2016 16:46:15 +0300 Subject: [Haskell-cafe] How do I debug this RTS segfault? In-Reply-To: <20160724175031.GA7614@glow> References: <20160724175031.GA7614@glow> Message-ID: Hello, On Sun, Jul 24, 2016 at 8:50 PM, Lana Black wrote: > I have run into this RTS bug recently. In short, when executing multiple > consequtive forks, after 500-600 or so the process is terminated by > SIGSEGV. I know this kind of thing is totally artificial, but still. > Here's a bug report with some analysis: https://ghc.haskell.org/trac/ghc/ticket/12436 -------------- next part -------------- An HTML attachment was scrubbed... URL: From lanablack at amok.cc Tue Jul 26 14:09:45 2016 From: lanablack at amok.cc (Lana Black) Date: Tue, 26 Jul 2016 14:09:45 +0000 Subject: [Haskell-cafe] How do I debug this RTS segfault? In-Reply-To: References: <20160724175031.GA7614@glow> Message-ID: <20160726140945.4403282.22791.4447@amok.cc> An HTML attachment was scrubbed... URL: From briand at aracnet.com Wed Jul 27 04:35:39 2016 From: briand at aracnet.com (briand at aracnet.com) Date: Tue, 26 Jul 2016 21:35:39 -0700 Subject: [Haskell-cafe] good choice for random number generator ? In-Reply-To: References: <20160724164820.2f66cd20@basalt.deldotd.com> Message-ID: <20160726213539.48052f82@basalt.deldotd.com> On Tue, 26 Jul 2016 09:08:30 +0000 (UTC) Dominic Steinitz wrote: > If you want distributions in distinction to just a random number > generator, I recommend random-fu. You can plug in at least MT and MWC > as the random number generators and you get pdfs and cdfs as well. > Let me know if you need anything adding to it. I am also keen to > improve its documentation. I made a small start here: > https://hackage.haskell.org/package/random-fu-0.2.7.0/docs/Data-Random- > Distribution-Binomial.html but time as always is the enemy. Feel free > to contribute. > I'll definitely give it a try. Thanks. Brian From capn.freako at gmail.com Wed Jul 27 14:14:44 2016 From: capn.freako at gmail.com (David Banas) Date: Wed, 27 Jul 2016 07:14:44 -0700 Subject: [Haskell-cafe] Question, re: upgrading Stack manually. Message-ID: <6596D114-A7C5-4F2B-93E3-6E74DC0E2B7E@gmail.com> Hi Stackers, Is this a show stopper, wrt/ upgrading Stack manually, via: - stack unpack stack-1.1.2 - pushed - stack setup - stack build Warning: /Users/dbanas/Documents/Projects/stack/upgrade_2016-07-27/stack-1.1.2/stack.yaml: Unrecognized field in ProjectAndConfigMonoid: nix ? Thanks, -db -------------- next part -------------- An HTML attachment was scrubbed... URL: From evan at evanrutledgeborden.dreamhosters.com Wed Jul 27 14:24:13 2016 From: evan at evanrutledgeborden.dreamhosters.com (evan@evan-borden.com) Date: Wed, 27 Jul 2016 10:24:13 -0400 Subject: [Haskell-cafe] ANN: network-2.6.3.0 Message-ID: Good day, I am pleased to announce the release of network 2.6.3.0. This release is primarily focused on stability, but includes a few new APIs. Thank you to the contributors for their continued excellence. https://hackage.haskell.org/package/network-2.6.3.0 Release Notes, Version 2.6.3.0: * New maintainers: Evan Borden (@eborden) and Kazu Yamamoto (@kazu-yamamoto). The maintainer for a long period, Johan Tibell (@tibbe) stepped down. Thank you, Johan, for your hard work for a long time. * New APIs: ntohl, htonl,hostAddressToTuple{,6} and tupleToHostAddress{,6}. [#210](https://github.com/haskell/network/pull/210) * Added a Read instance for PortNumber. [#145]( https://github.com/haskell/network/pull/145) * We only set the IPV6_V6ONLY flag to 0 for stream and datagram socket types, as opposed to all of them. This makes it possible to use ICMPv6. [#180](https://github.com/haskell/network/pull/180) [#181](https://github.com/haskell/network/pull/181) * Work around GHC bug #12020. Socket errors no longer cause segfaults or hangs on Windows. [#192](https://github.com/haskell/network/pull/192) * Various documentation improvements and the deprecated pragmas. [#186](https://github.com/haskell/network/pull/186) [#201](https://github.com/haskell/network/issues/201) [#205](https://github.com/haskell/network/pull/205) [#206](https://github.com/haskell/network/pull/206) [#211](https://github.com/haskell/network/issues/211) * Various internal improvements. [#193](https://github.com/haskell/network/pull/193) [#200](https://github.com/haskell/network/pull/200) -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Wed Jul 27 14:39:16 2016 From: michael at snoyman.com (Michael Snoyman) Date: Wed, 27 Jul 2016 17:39:16 +0300 Subject: [Haskell-cafe] Question, re: upgrading Stack manually. In-Reply-To: <6596D114-A7C5-4F2B-93E3-6E74DC0E2B7E@gmail.com> References: <6596D114-A7C5-4F2B-93E3-6E74DC0E2B7E@gmail.com> Message-ID: It shouldn't be a problem, the build should complete successfully. It's just warning you that there's a configuration value that it doesn't know how to handle, but it shouldn't prevent success. On Wed, Jul 27, 2016 at 5:14 PM, David Banas wrote: > Hi Stackers, > > Is this a show stopper, wrt/ upgrading Stack manually, via: > - stack unpack stack-1.1.2 > - pushed > - stack setup > - stack build > > Warning: > /Users/dbanas/Documents/Projects/stack/upgrade_2016-07-27/stack-1.1.2/stack.yaml: > Unrecognized field in ProjectAndConfigMonoid: nix > > ? > > Thanks, > -db > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From hi-angel at ya.ru Thu Jul 28 13:43:03 2016 From: hi-angel at ya.ru (Constantine Kharlamov) Date: Thu, 28 Jul 2016 16:43:03 +0300 Subject: [Haskell-cafe] Breaking in library, and getting stacktrace Message-ID: <147361469713383@web5j.yandex.ru> An HTML attachment was scrubbed... URL: From carlos.dagostino at gmail.com Fri Jul 29 12:33:38 2016 From: carlos.dagostino at gmail.com (Carlos D'Agostino) Date: Fri, 29 Jul 2016 14:33:38 +0200 Subject: [Haskell-cafe] Breaking in library, and getting stacktrace Message-ID: Without knowing too much about your project setup, and if I'm understanding correctly, see http://haddock.stackage.org/lts-5.1/base-4.8.2.0/Debug-Trace.html#v:traceStack Keep in mind that you have to build with the corresponding flags in order to get it working correctly. Assuming you're using stack that would be: stack build --enable-profiling --library-profiling --ghc-options="-fprof-auto-rtsopts" Though I'm not sure if that's 100% what you're looking for since it doesn't break as much as that it logs with a stack trace. Hope it helps! > ---------------------------------------------------------------------- > > Message: 1 > Date: Thu, 28 Jul 2016 16:43:03 +0300 > From: Constantine Kharlamov > To: haskell-cafe at haskell.org > Subject: [Haskell-cafe] Breaking in library, and getting stacktrace > Message-ID: <147361469713383 at web5j.yandex.ru> > Content-Type: text/plain; charset="utf-8" > > An HTML attachment was scrubbed... > URL: < > http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160728/b4652af8/attachment-0001.html > > > > ------------------------------ > > Subject: Digest Footer > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > > > ------------------------------ > > End of Haskell-Cafe Digest, Vol 155, Issue 33 > ********************************************* > -- Carlos D'Agostino. -------------- next part -------------- An HTML attachment was scrubbed... URL: From slyich at gmail.com Sat Jul 30 08:39:57 2016 From: slyich at gmail.com (Sergei Trofimovich) Date: Sat, 30 Jul 2016 09:39:57 +0100 Subject: [Haskell-cafe] ANN: network-2.6.3.0 In-Reply-To: References: Message-ID: <20160730093957.7069fa76@sf> On Wed, 27 Jul 2016 10:24:13 -0400 "evan at evan-borden.com" wrote: > Good day, > > I am pleased to announce the release of network 2.6.3.0. This release is > primarily focused > on stability, but includes a few new APIs. Thank you to the contributors > for their continued > excellence. > > https://hackage.haskell.org/package/network-2.6.3.0 Woohoo! I've updated network package from 2.6.2.1 to 2.6.3.0 and noticed a few package packages started failing tests with seemingly the same point to network changes. Release notes don't point to chages in exception delivery. Do you think the following failures are package bugs or subtle network change? >>> Failed to emerge dev-haskell/simple-sendfile-0.2.25, Log file: >>> '/tmp/portage-tmpdir/portage/dev-haskell/simple-sendfile-0.2.25/temp/build.log' >>> Failed to emerge dev-haskell/fluent-logger-0.2.3.1, Log file: >>> '/tmp/portage-tmpdir/portage/dev-haskell/fluent-logger-0.2.3.1/temp/build.log' >>> Failed to emerge dev-haskell/http-client-0.4.30, Log file: >>> '/tmp/portage-tmpdir/portage/dev-haskell/http-client-0.4.30/temp/build.log' >>> Failed to emerge dev-haskell/dbus-0.10.12, Log file: >>> '/tmp/portage-tmpdir/portage/dev-haskell/dbus-0.10.12/temp/build.log' simple-sendfile-0.2.25 Failures: test/SendfileSpec.hs:30: 1) Sendfile.sendfile sends an entire file uncaught exception: IOException of type EOF (Network.Socket.recvBuf: end of file (end of file)) fluent-logger-0.2.3.1 Network.Fluent.Logger post fluent-logger-spec: Network.Socket.recvBuf: end of file (end of file) http-client-0.4.30 spec-nonet: Network.Socket.recvBuf: end of file (end of file) connecting to missing server gives nice error message extra headers after 100 #49 dbus-0.10.12 Test suite dbus_tests: RUNNING... dbus_tests: Network.Socket.recvBuf: end of file (end of file) [ ABORT ] Transport.handle-lost-connection Test aborted due to exception: TransportError {transportErrorMessage = "Network.Socket.recvBuf: end of file (end of file)", t ransportErrorAddress = Just (Address "tcp:family=ipv4,host=localhost,port=52067")} -- Sergei From slyich at gmail.com Sat Jul 30 11:11:39 2016 From: slyich at gmail.com (Sergei Trofimovich) Date: Sat, 30 Jul 2016 12:11:39 +0100 Subject: [Haskell-cafe] ANN: network-2.6.3.0 In-Reply-To: <20160730093957.7069fa76@sf> References: <20160730093957.7069fa76@sf> Message-ID: <20160730121139.1b464b80@sf> On Sat, 30 Jul 2016 09:39:57 +0100 Sergei Trofimovich wrote: > On Wed, 27 Jul 2016 10:24:13 -0400 > "evan at evan-borden.com" wrote: > > > Good day, > > > > I am pleased to announce the release of network 2.6.3.0. This release is > > primarily focused > > on stability, but includes a few new APIs. Thank you to the contributors > > for their continued > > excellence. > > > > https://hackage.haskell.org/package/network-2.6.3.0 > > Woohoo! > > I've updated network package from 2.6.2.1 to 2.6.3.0 > and noticed a few package packages started failing tests > with seemingly the same point to network changes. > > Release notes don't point to chages in exception delivery. > > Do you think the following failures are package bugs > or subtle network change? Answering my own question. Known network-2.6.3.0 bug: https://github.com/haskell/network/issues/215 Posted minimal test to the bug. -- Sergei From gurudev.devanla at gmail.com Sat Jul 30 22:01:58 2016 From: gurudev.devanla at gmail.com (Gurudev Devanla) Date: Sat, 30 Jul 2016 15:01:58 -0700 (PDT) Subject: [Haskell-cafe] Design Question - Functions taking 'subtype' like arguments but has to be restricted to one type Message-ID: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> Hello All, I have a design question where I could use some of your thoughts and suggestions. Here is the setup. I apologize for the long email but I have resisted asking this question, since it needs a long explanation, until now. I have a set of data structures defined as follows -- An Item that can be of two types, one whose value can be changed, one whose value are frozen once created data Item = FreeToChange {freeToChangeCount:: Int} | CannotChange {frozenCount:: Int} -- The item is part of a basket data Basket = Basket { name:: String, item::Item } -- The cart can have both kind of Baskets at the start of the program, or during runtime. data Cart = List Basket You can imagine this be a shopping cart with fixed set of items. Where the count of some of the items in the basket can be changed during shopping but not the count of the items once they are tagged as frozen. Therefore, valid operation are: 1. I can create an Basket with either FreeToChange item or CannotChange item. 2. I can update the count for FreeToChange item in the Basket 3. But, once I create an instance of the Basket to contain the CannotChange item, we cannot update the count anymore or update the Basket. One approach I have taken is to throw an error if this happens by pattern matching on type. But, this is an runtime check. addToBasket :: Basket -> Basket addToBasket b = let i = item b i' = case i of FreeToChange f -> FreeToChange {freeToChangeCount = f + 1} CannotChange f -> error ("This operation is not allowed") in b {item=i'} Here are my questions: 1. Is there a way to design the above data structures in such a way I could use the type system. 2. Since, these are runtime changes, is it even a good design pattern to push this responsibility to a type system? Thanks Guru -------------- next part -------------- An HTML attachment was scrubbed... URL: From bertram.felgenhauer at googlemail.com Sat Jul 30 22:22:19 2016 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sun, 31 Jul 2016 00:22:19 +0200 Subject: [Haskell-cafe] RFC: revisiting the simplified haskell-src-exts AST Message-ID: <20160730222219.GB25770@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Dear all, the latest major release of haskell-src-exts (version 1.18) removed the annotation free variant of the Haskell AST. It occurred to me that using ghc's pattern synonyms it is possible to offer a light-weight simplified view on the annotated AST. For example, Language.Haskell.Exts.Syntax defines data Name l = Ident l String | Symbol l String and we can provide a simplified view with all annotations equal to () by doing {-# LANGUAGE PatternSynonyms #-} import qualified Language.Haskell.Exts.Syntax as H type Name = H.Name () pattern Ident a = H.Ident () a pattern Symbol a = H.Symbol () a Because the type isn't changed, no code has to be reimplemented to work with this AST. A first rough cut at an implementation can be found on github [1]. Before releasing it on hackage (which requires some more polishing) I'd appreciate feedback on the approach. Would you consider using such a package? Is there a better approach? Also any thoughts on usability (e.g., how to approach documentation) would be welcome. Cheers, Bertram [1] https://github.com/int-e/haskell-src-exts-simple P.S. This grew out of an effort to update lambdabot to HSE-1.18, which made me feel awful about all the superfluous and ugly () in the resulting code. I also have some numbers showing that the annotation-free view makes updating the code smoother: Using the annotation-free view, the update touches 75 lines: src/Lambdabot/Plugin/Haskell/Eval.hs | 18 +- src/Lambdabot/Plugin/Haskell/Pointful.hs | 201 +++++++++++++++---------------- src/Lambdabot/Plugin/Haskell/Pretty.hs | 14 +- src/Lambdabot/Plugin/Haskell/UnMtl.hs | 62 ++++----- src/Lambdabot/Plugin/Haskell/Undo.hs | 115 ++++++++--------- 5 files changed, 72 insertions(+), 75 deletions(-) Using the haskell-src-exts 1.18 AST, the update touches 208 lines: src/Lambdabot/Plugin/Haskell/Pointful.hs | 87 ++++++++++++++----------------- src/Lambdabot/Plugin/Haskell/Pretty.hs | 12 ++-- src/Lambdabot/Plugin/Haskell/UnMtl.hs | 10 +-- src/Lambdabot/Plugin/Haskell/Undo.hs | 34 ++++++------ 5 files changed, 204 insertions(+), 206 deletions(-) From tanuki at gmail.com Sun Jul 31 00:55:06 2016 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Sat, 30 Jul 2016 17:55:06 -0700 Subject: [Haskell-cafe] Design Question - Functions taking 'subtype' like arguments but has to be restricted to one type In-Reply-To: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> References: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> Message-ID: (Apologies for any duplicates... for some reason the original's reply address is haskell-cafe at googlegroups.com rather than haskell-cafe at haskell.org, and it sent a rejection notice for my reply.) If I understand your model right, the Item is just a count, and it's the Basket's 'name' field which actually says what the item is? Assuming I have that right, check this out: -- A basket is the association of an item with a count. data Basket = Basket {item :: String, count :: Int} -- Open and closed baskets are just baskets with different behavior. newtype OpenBasket = OpenBasket {getOpenBasket :: Basket} newtype ClosedBasket = ClosedBasket {getClosedBasket :: Basket} -- A cart can contain a mix of both basket types. type CartBasket = Either OpenBasket ClosedBasket data Cart = List CartBasket -- We'll want to conveniently inspect CartBaskets. getCartBasket :: CartBasket -> Basket getCartBasket = either getOpenBasket getClosedBasket -- This function accepts only OpenBaskets. No need for a runtime check. addToOpenBasket :: OpenBasket -> OpenBasket addToOpenBasket (OpenBasket b@(Basket _ i)) = OpenBasket (b {count = i+1}) -- First-class functions let you keep this safety all the way to the top... data UserControl a = UserControl {label :: String, behavior :: a -> a} -- Only allow the user to see valid behaviors! getAddToCartBasketUserControl :: CartBasket -> UserControl CartBasket getAddToCartBasketUserControl = let f = either (Left . addToOpenBasket) Right in either (const (UserControl "Add" f)) (const (UserControl "Locked" f)) On Sat, Jul 30, 2016 at 3:01 PM, Gurudev Devanla wrote: > Hello All, > > I have a design question where I could use some of your thoughts and > suggestions. Here is the setup. I apologize > for the long email but I have resisted asking this question, since it > needs a long explanation, until now. > > I have a set of data structures defined as follows > > -- An Item that can be of two types, one whose value can be changed, one > whose value are frozen once created > data Item = FreeToChange {freeToChangeCount:: Int} > | CannotChange {frozenCount:: Int} > > -- The item is part of a basket > data Basket = Basket { name:: String, item::Item } > > -- The cart can have both kind of Baskets at the start of the program, or > during runtime. > data Cart = List Basket > > You can imagine this be a shopping cart with fixed set of items. Where > the count of > some of the items in the basket can be changed during shopping but not the > count of the > items once they are tagged as frozen. > > Therefore, valid operation are: > > 1. I can create an Basket with either FreeToChange item or CannotChange > item. > 2. I can update the count for FreeToChange item in the Basket > 3. But, once I create an instance of the Basket to contain the > CannotChange item, > we cannot update the count anymore or update the Basket. > > One approach I have taken is to throw an error if this happens by pattern > matching on type. But, this is > an runtime check. > > addToBasket :: Basket -> Basket > addToBasket b = let > i = item b > i' = case i of > FreeToChange f -> FreeToChange {freeToChangeCount = f + 1} > CannotChange f -> error ("This operation is not allowed") > in > b {item=i'} > > > Here are my questions: > > 1. Is there a way to design the above data structures in such a way I > could use the type system. > 2. Since, these are runtime changes, is it even a good design pattern to > push this responsibility to a type system? > > > Thanks > Guru > > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanuki at gmail.com Sun Jul 31 01:02:05 2016 From: tanuki at gmail.com (Theodore Lief Gannon) Date: Sat, 30 Jul 2016 18:02:05 -0700 Subject: [Haskell-cafe] Design Question - Functions taking 'subtype' like arguments but has to be restricted to one type In-Reply-To: References: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> Message-ID: Ha, whoops... I duplicated an error in your original because it compiles. -- This creates a constructor named "List" which holds a single CartBasket! data Cart = List CartBasket -- You probably intended this: type Cart = [CartBasket] On Sat, Jul 30, 2016 at 5:55 PM, Theodore Lief Gannon wrote: > (Apologies for any duplicates... for some reason the original's reply > address is haskell-cafe at googlegroups.com rather than > haskell-cafe at haskell.org, and it sent a rejection notice for my reply.) > > If I understand your model right, the Item is just a count, and it's the > Basket's 'name' field which actually says what the item is? Assuming I have > that right, check this out: > > -- A basket is the association of an item with a count. > data Basket = Basket {item :: String, count :: Int} > > -- Open and closed baskets are just baskets with different behavior. > newtype OpenBasket = OpenBasket {getOpenBasket :: Basket} > newtype ClosedBasket = ClosedBasket {getClosedBasket :: Basket} > > -- A cart can contain a mix of both basket types. > type CartBasket = Either OpenBasket ClosedBasket > data Cart = List CartBasket > > -- We'll want to conveniently inspect CartBaskets. > getCartBasket :: CartBasket -> Basket > getCartBasket = either getOpenBasket getClosedBasket > > -- This function accepts only OpenBaskets. No need for a runtime check. > addToOpenBasket :: OpenBasket -> OpenBasket > addToOpenBasket (OpenBasket b@(Basket _ i)) > = OpenBasket (b {count = i+1}) > > -- First-class functions let you keep this safety all the way to the top... > data UserControl a = UserControl {label :: String, behavior :: a -> a} > > -- Only allow the user to see valid behaviors! > getAddToCartBasketUserControl :: CartBasket -> UserControl CartBasket > getAddToCartBasketUserControl = > let f = either (Left . addToOpenBasket) Right > in either (const (UserControl "Add" f)) (const (UserControl "Locked" f)) > > > On Sat, Jul 30, 2016 at 3:01 PM, Gurudev Devanla < > gurudev.devanla at gmail.com> wrote: > >> Hello All, >> >> I have a design question where I could use some of your thoughts and >> suggestions. Here is the setup. I apologize >> for the long email but I have resisted asking this question, since it >> needs a long explanation, until now. >> >> I have a set of data structures defined as follows >> >> -- An Item that can be of two types, one whose value can be changed, >> one whose value are frozen once created >> data Item = FreeToChange {freeToChangeCount:: Int} >> | CannotChange {frozenCount:: Int} >> >> -- The item is part of a basket >> data Basket = Basket { name:: String, item::Item } >> >> -- The cart can have both kind of Baskets at the start of the program, or >> during runtime. >> data Cart = List Basket >> >> You can imagine this be a shopping cart with fixed set of items. Where >> the count of >> some of the items in the basket can be changed during shopping but not >> the count of the >> items once they are tagged as frozen. >> >> Therefore, valid operation are: >> >> 1. I can create an Basket with either FreeToChange item or CannotChange >> item. >> 2. I can update the count for FreeToChange item in the Basket >> 3. But, once I create an instance of the Basket to contain the >> CannotChange item, >> we cannot update the count anymore or update the Basket. >> >> One approach I have taken is to throw an error if this happens by >> pattern matching on type. But, this is >> an runtime check. >> >> addToBasket :: Basket -> Basket >> addToBasket b = let >> i = item b >> i' = case i of >> FreeToChange f -> FreeToChange {freeToChangeCount = f + 1} >> CannotChange f -> error ("This operation is not allowed") >> in >> b {item=i'} >> >> >> Here are my questions: >> >> 1. Is there a way to design the above data structures in such a way I >> could use the type system. >> 2. Since, these are runtime changes, is it even a good design pattern to >> push this responsibility to a type system? >> >> >> Thanks >> Guru >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Sun Jul 31 11:45:23 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sun, 31 Jul 2016 12:45:23 +0100 Subject: [Haskell-cafe] RFC: revisiting the simplified haskell-src-exts AST In-Reply-To: References: <20160730222219.GB25770@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Message-ID: Hello Bertram, This is a good idea. I also considered this but to provide a proper compatibility layer it is necessary to "bundle" pattern synonyms with suitable type constructors so that when users import the type constructor then they also import the suitable pattern synonyms. This feature was only implemented in GHC 8.0. It is currently not much effort to maintain HSE to support back to at least GHC 7.4 so it didn't seem worth sacrificing this. It would be good to provide this shim in future versions of the library but at the moment the feature isn't mature enough. Message me when you release this to Hackage and I will add a link to the README. Matt On Sat, Jul 30, 2016 at 11:22 PM, Bertram Felgenhauer via Haskell-Cafe < haskell-cafe at haskell.org> wrote: > Dear all, > > the latest major release of haskell-src-exts (version 1.18) removed > the annotation free variant of the Haskell AST. It occurred to me that > using ghc's pattern synonyms it is possible to offer a light-weight > simplified view on the annotated AST. For example, > Language.Haskell.Exts.Syntax defines > > data Name l = Ident l String | Symbol l String > > and we can provide a simplified view with all annotations equal to () > by doing > > {-# LANGUAGE PatternSynonyms #-} > import qualified Language.Haskell.Exts.Syntax as H > > type Name = H.Name () > pattern Ident a = H.Ident () a > pattern Symbol a = H.Symbol () a > > Because the type isn't changed, no code has to be reimplemented to > work with this AST. > > A first rough cut at an implementation can be found on github [1]. > Before releasing it on hackage (which requires some more polishing) > I'd appreciate feedback on the approach. Would you consider using > such a package? Is there a better approach? Also any thoughts on > usability (e.g., how to approach documentation) would be welcome. > > Cheers, Bertram > > [1] https://github.com/int-e/haskell-src-exts-simple > > > P.S. This grew out of an effort to update lambdabot to HSE-1.18, > which made me feel awful about all the superfluous and ugly () in > the resulting code. I also have some numbers showing that the > annotation-free view makes updating the code smoother: > > Using the annotation-free view, the update touches 75 lines: > src/Lambdabot/Plugin/Haskell/Eval.hs | 18 +- > src/Lambdabot/Plugin/Haskell/Pointful.hs | 201 +++++++++++++++---------------- > src/Lambdabot/Plugin/Haskell/Pretty.hs | 14 +- > src/Lambdabot/Plugin/Haskell/UnMtl.hs | 62 ++++----- > src/Lambdabot/Plugin/Haskell/Undo.hs | 115 ++++++++--------- > 5 files changed, 72 insertions(+), 75 deletions(-) > > Using the haskell-src-exts 1.18 AST, the update touches 208 lines: > src/Lambdabot/Plugin/Haskell/Pointful.hs | 87 ++++++++++++++----------------- > src/Lambdabot/Plugin/Haskell/Pretty.hs | 12 ++-- > src/Lambdabot/Plugin/Haskell/UnMtl.hs | 10 +-- > src/Lambdabot/Plugin/Haskell/Undo.hs | 34 ++++++------ > 5 files changed, 204 insertions(+), 206 deletions(-) > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Jul 31 11:52:42 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 31 Jul 2016 12:52:42 +0100 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: References: Message-ID: <20160731115242.GD28014@weber> On Wed, Jul 20, 2016 at 02:09:13PM +0100, Matthew Pickering wrote: > HSE provides two ASTs, one which has source locations and one which > doesn't. I have removed the one which doesn't. I haven't been following very closely, but can I ask what the use case was for the one which did not have source locations? Is it just to avoid filling in/ignoring a dummy () parameter when constructing/destructing respectively? From adam at bergmark.nl Sun Jul 31 12:06:47 2016 From: adam at bergmark.nl (Adam Bergmark) Date: Sun, 31 Jul 2016 14:06:47 +0200 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: <20160731115242.GD28014@weber> References: <20160731115242.GD28014@weber> Message-ID: Old versions of HSE only had the un-annotated version so perhaps the annotations were added in separate types to avoid breaking changes. On Sun, Jul 31, 2016 at 1:52 PM, Tom Ellis < tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote: > On Wed, Jul 20, 2016 at 02:09:13PM +0100, Matthew Pickering wrote: > > HSE provides two ASTs, one which has source locations and one which > > doesn't. I have removed the one which doesn't. > > I haven't been following very closely, but can I ask what the use case was > for the one which did not have source locations? Is it just to avoid > filling in/ignoring a dummy () parameter when constructing/destructing > respectively? > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Sun Jul 31 12:07:46 2016 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Sun, 31 Jul 2016 13:07:46 +0100 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: <20160731115242.GD28014@weber> References: <20160731115242.GD28014@weber> Message-ID: I'm not sure. I think it was mostly a historical artifact. Originally there was only the simplified AST, at some point the AST was augmented with source locations but the simplified tree was not removed for backwards compatability. Some of the library still operated on the old simpler AST such as the pretty printer but now everything is ported over. Matt On 31 Jul 2016 12:52 p.m., "Tom Ellis" < tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk> wrote: > On Wed, Jul 20, 2016 at 02:09:13PM +0100, Matthew Pickering wrote: > > HSE provides two ASTs, one which has source locations and one which > > doesn't. I have removed the one which doesn't. > > I haven't been following very closely, but can I ask what the use case was > for the one which did not have source locations? Is it just to avoid > filling in/ignoring a dummy () parameter when constructing/destructing > respectively? > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Jul 31 12:13:14 2016 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 31 Jul 2016 13:13:14 +0100 Subject: [Haskell-cafe] RFC: New version of haskell-src-exts without simplified AST In-Reply-To: References: <20160731115242.GD28014@weber> Message-ID: <20160731121314.GE28014@weber> On Sun, Jul 31, 2016 at 01:07:46PM +0100, Matthew Pickering wrote: > I'm not sure. I think it was mostly a historical artifact. Originally there > was only the simplified AST, at some point the AST was augmented with > source locations but the simplified tree was not removed for backwards > compatability. Some of the library still operated on the old simpler AST > such as the pretty printer but now everything is ported over. Good work getting rid of the old stuff then! From gurudev.devanla at gmail.com Sun Jul 31 13:24:39 2016 From: gurudev.devanla at gmail.com (Guru Devanla) Date: Sun, 31 Jul 2016 06:24:39 -0700 Subject: [Haskell-cafe] Design Question - Functions taking 'subtype' like arguments but has to be restricted to one type In-Reply-To: References: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> Message-ID: @Theodore, thank you for the working example. You did simplify the problem statement. Actually Basket itself is a more complicated structure, with Item being one of its attributes. But, let me go along with your simplification. It seems to me that, your approach replaces placeholder "error" expression I had, with a no-op on the Right value. Of course, I could switch the right function to 'either' to do some thing more than a no-op. Is that correct? @Imants, @Matthias : I agree with your suggestions and that is where @Theodore's approach was also leading to but in a different form. Looks like unless I have 2 separate entities, one for Frozen and one for Flexible, I will have to deal with run-time behaviour. I say this, since in a more complicated scenario, I might want to map over a list of buckets,. but only be able to called updated on items in the list that are of particular type. Thanks Guru On Sat, Jul 30, 2016 at 5:55 PM, Theodore Lief Gannon wrote: > (Apologies for any duplicates... for some reason the original's reply > address is haskell-cafe at googlegroups.com rather than > haskell-cafe at haskell.org, and it sent a rejection notice for my reply.) > > If I understand your model right, the Item is just a count, and it's the > Basket's 'name' field which actually says what the item is? Assuming I have > that right, check this out: > > -- A basket is the association of an item with a count. > data Basket = Basket {item :: String, count :: Int} > > -- Open and closed baskets are just baskets with different behavior. > newtype OpenBasket = OpenBasket {getOpenBasket :: Basket} > newtype ClosedBasket = ClosedBasket {getClosedBasket :: Basket} > > -- A cart can contain a mix of both basket types. > type CartBasket = Either OpenBasket ClosedBasket > data Cart = List CartBasket > > -- We'll want to conveniently inspect CartBaskets. > getCartBasket :: CartBasket -> Basket > getCartBasket = either getOpenBasket getClosedBasket > > -- This function accepts only OpenBaskets. No need for a runtime check. > addToOpenBasket :: OpenBasket -> OpenBasket > addToOpenBasket (OpenBasket b@(Basket _ i)) > = OpenBasket (b {count = i+1}) > > -- First-class functions let you keep this safety all the way to the top... > data UserControl a = UserControl {label :: String, behavior :: a -> a} > > -- Only allow the user to see valid behaviors! > getAddToCartBasketUserControl :: CartBasket -> UserControl CartBasket > getAddToCartBasketUserControl = > let f = either (Left . addToOpenBasket) Right > in either (const (UserControl "Add" f)) (const (UserControl "Locked" f)) > > > On Sat, Jul 30, 2016 at 3:01 PM, Gurudev Devanla < > gurudev.devanla at gmail.com> wrote: > >> Hello All, >> >> I have a design question where I could use some of your thoughts and >> suggestions. Here is the setup. I apologize >> for the long email but I have resisted asking this question, since it >> needs a long explanation, until now. >> >> I have a set of data structures defined as follows >> >> -- An Item that can be of two types, one whose value can be changed, >> one whose value are frozen once created >> data Item = FreeToChange {freeToChangeCount:: Int} >> | CannotChange {frozenCount:: Int} >> >> -- The item is part of a basket >> data Basket = Basket { name:: String, item::Item } >> >> -- The cart can have both kind of Baskets at the start of the program, or >> during runtime. >> data Cart = List Basket >> >> You can imagine this be a shopping cart with fixed set of items. Where >> the count of >> some of the items in the basket can be changed during shopping but not >> the count of the >> items once they are tagged as frozen. >> >> Therefore, valid operation are: >> >> 1. I can create an Basket with either FreeToChange item or CannotChange >> item. >> 2. I can update the count for FreeToChange item in the Basket >> 3. But, once I create an instance of the Basket to contain the >> CannotChange item, >> we cannot update the count anymore or update the Basket. >> >> One approach I have taken is to throw an error if this happens by >> pattern matching on type. But, this is >> an runtime check. >> >> addToBasket :: Basket -> Basket >> addToBasket b = let >> i = item b >> i' = case i of >> FreeToChange f -> FreeToChange {freeToChangeCount = f + 1} >> CannotChange f -> error ("This operation is not allowed") >> in >> b {item=i'} >> >> >> Here are my questions: >> >> 1. Is there a way to design the above data structures in such a way I >> could use the type system. >> 2. Since, these are runtime changes, is it even a good design pattern to >> push this responsibility to a type system? >> >> >> Thanks >> Guru >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> To (un)subscribe, modify options or view archives go to: >> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe >> Only members subscribed via the mailman list are allowed to post. >> > > > _______________________________________________ > Haskell-Cafe mailing list > To (un)subscribe, modify options or view archives go to: > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe > Only members subscribed via the mailman list are allowed to post. > -------------- next part -------------- An HTML attachment was scrubbed... URL: From imantc at gmail.com Sun Jul 31 13:53:34 2016 From: imantc at gmail.com (Imants Cekusins) Date: Sun, 31 Jul 2016 15:53:34 +0200 Subject: [Haskell-cafe] Design Question - Functions taking 'subtype' like arguments but has to be restricted to one type In-Reply-To: References: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> Message-ID: Beware: if you go with Either and combine Either ops with >>=, first Left result stops evaluation and returns 1st Left result. Right results continue evaluation. If this is expected, Either fits. If more ops are expected after 'update count' no-op (if Left stands for Frozen), then Either and >>= should not be used together. Algebraic type (Flex count | Frozen count) is also suitable. Let the calling functions decide how to process Frozen values. At least they'll know the difference. -------------- next part -------------- An HTML attachment was scrubbed... URL: From bertram.felgenhauer at googlemail.com Sun Jul 31 17:40:37 2016 From: bertram.felgenhauer at googlemail.com (Bertram Felgenhauer) Date: Sun, 31 Jul 2016 19:40:37 +0200 Subject: [Haskell-cafe] ANN: haskell-src-exts-simple Message-ID: <20160731174037.GC25770@24f89f8c-e6a1-4e75-85ee-bb8a3743bb9f> Dear all, I've just released haskell-src-exts-simple 1.18.0.0 on hackage [1]. (This is the first release. The first two components of the version follow haskell-src-exts.) >From the README: This package provides a shim for haskell-src-exts, exposing the same AST but without annotations. This package is useful for synthesizing and manipulating HSE ASTs that don't carry source location information. It may also aid in porting packages from haskell-src-exts 1.17 to 1.18, but it is not a drop-in replacement for the old annotation-free AST. See [2] for details. Happy hacking, Bertram [1] https://hackage.haskell.org/package/haskell-src-exts-simple [2] https://github.com/int-e/haskell-src-exts-simple/blob/master/COMPATIBILITY.md From monkleyon at googlemail.com Sun Jul 31 18:41:53 2016 From: monkleyon at googlemail.com (MarLinn) Date: Sun, 31 Jul 2016 20:41:53 +0200 Subject: [Haskell-cafe] Design Question - Functions taking 'subtype' like arguments but has to be restricted to one type In-Reply-To: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> References: <8ed829cc-3f7b-407d-a1cb-fd66785ac60a@googlegroups.com> Message-ID: <614e9096-57a1-21da-7e75-a0ffc8d977cf@gmail.com> This sounds like a perfect opportunity to use phantom types. I'll be using it's DataKind-enhanced variant for added beauty. > -- An Item that can be of two types, one whose value can be changed, > one whose value are frozen once created > data Item = FreeToChange {freeToChangeCount:: Int} > | CannotChange {frozenCount:: Int} I assume all items are equal apart from their changeability. Not that it's necessary, but it makes the demonstration simpler. If changeable and unchangeable items have differing structure you may need additional tools like smart constructors. Accordingly, my items have the type data PlainItem = PlainItem { count :: Int } Changeability will be added on top: data Changeability = Changeable | Unchangeable data Item (c :: Changeability) = Item { plainItem :: PlainItem } Why separate /Item/ and /PlainItem/? One second, please. > -- The item is part of a basket > data Basket = Basket { name:: String, item::Item } data Basket c = Basket { name :: String, item :: Item c } -- No kind signature necessary. Thanks, solver. > Therefore, valid operation are: > > 1. I can create an Basket with either FreeToChange item or > CannotChange item. The new /Basket/ constructor can do that by default. > 2. I can update the count for FreeToChange item in the Basket changeItem :: (PlainItem -> PlainItem) -> Item 'Changeable -> Item 'Changeable changeItem f (Item i) = Item (f i) changeBasket :: (PlainItem -> PlainItem) -> Basket 'Changeable -> Basket 'Changeable changeBasket f basket at Basket{..} = basket { item = changeItem f item } And that's why /PlainItem/ was separated, so we can have a simple type signature here. You might worry that it was exposed, but it will not give anyone access to a frozen basket. And of course you are free to further restrict access to it. And as we're speaking about freezing, that's extremely simple as well. freezeItem :: Item c -> Item 'Unchangeable freezeItem (Item i) = Item i freezeBasket :: Basket c -> Basket 'Unchangeable freezeBasket basket at Basket{..} = basket { item = freezeItem item } You later mention that you might want to map updates only over some of the baskets in a cart. That's not hard either. As an example, here's a way to implement a function that updates changeable baskets while ignoring unchangeable ones: class MaybeUpdateBasket c where updateBasket :: (PlainItem -> PlainItem) -> Basket c -> Basket c instance MaybeUpdateBasket 'Changeable where updateBasket = changeBasket instance MaybeUpdateBasket 'Unchangeable where updateBasket _ = id Just /map/ it over your cart as always. If you want more complicated things (eg. you want a cart to freeze once any bucket freezes) you just have to expand the ideas here. You may need MultiParamTypeClasses and FunctionalDependencies, but the basic ideas are the same. Cheers. -------------- next part -------------- An HTML attachment was scrubbed... URL: