From schlepptop at henning-thielemann.de Sat Mar 1 06:47:42 2014 From: schlepptop at henning-thielemann.de (Henning Thielemann) Date: Sat, 01 Mar 2014 07:47:42 +0100 Subject: [Haskell-cafe] [Haskell] Can Haskell use short floats; i.e. 16 bit floats to save space? In-Reply-To: References: Message-ID: <5311828E.9080904@henning-thielemann.de> moving to Haskell-Cafe ... Am 01.03.2014 07:09, schrieb KC: > Can Haskell use short floats; i.e. 16 bit floats to save space? You could wrap an Int16 in a newtype and implement your own floating point arithmetic with some bit manipulation and make that instances of Num, Fractional or numeric-prelude or yap classes. From johan.tibell at gmail.com Sat Mar 1 07:56:59 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Sat, 1 Mar 2014 08:56:59 +0100 Subject: [Haskell-cafe] [Haskell] Can Haskell use short floats; i.e. 16 bit floats to save space? In-Reply-To: <5311828E.9080904@henning-thielemann.de> References: <5311828E.9080904@henning-thielemann.de> Message-ID: > > Am 01.03.2014 07:09, schrieb KC: > > Can Haskell use short floats; i.e. 16 bit floats to save space? >> > GHC pads all basic data types to one word in its in-memory representation, so no. It's possible that the boxed vectors in the "vector" package has a more compact representation for arrays of Floats. -- Johan -------------- next part -------------- An HTML attachment was scrubbed... URL: From kwangyul.seo at gmail.com Sat Mar 1 12:35:09 2014 From: kwangyul.seo at gmail.com (KwangYul Seo) Date: Sat, 1 Mar 2014 21:35:09 +0900 Subject: [Haskell-cafe] Type checking string literal in Haskell? Message-ID: In Java, the Checker Framework ( http://types.cs.washington.edu/checker-framework/) provides a way to type check string literals. For example, Java signatures type system differentiates strings literals in different forms: 1. Unqualified strings : "Hello, world!" -> @Unqualified String 2. Fully qualified names: "package.Outer.Inner" -> @FullyQualifiedString String 3. Binary names: "package.Outer$Inner" -> @BinaryName String 4. Field descriptors: "Lpackage/Outer$Inner;" -> @FieldDescriptor String It can do the similar checks with regular expressions or SQL statements. Is it possible to type check string literals in Haskell? I think it would be nice if we can check if a given string literal is a valid URL or an email address at compile time. Regards, Kwang Yul Seo -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell at nand.wakku.to Sat Mar 1 12:45:15 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Sat, 1 Mar 2014 13:45:15 +0100 Subject: [Haskell-cafe] Type checking string literal in Haskell? In-Reply-To: References: Message-ID: <20140301134515.GA12612@nanodesu.talocan.mine.nu> On Sat, 1 Mar 2014 21:35:09 +0900, KwangYul Seo wrote: > In Java, the Checker Framework ( > http://types.cs.washington.edu/checker-framework/) provides a way to type > check string literals. For example, Java signatures type system > differentiates strings literals in different forms: > > 1. Unqualified strings : > "Hello, world!" -> @Unqualified String > > 2. Fully qualified names: > "package.Outer.Inner" -> @FullyQualifiedString String > > 3. Binary names: > "package.Outer$Inner" -> @BinaryName String > > 4. Field descriptors: > "Lpackage/Outer$Inner;" -> @FieldDescriptor String > > It can do the similar checks with regular expressions or SQL statements. > > Is it possible to type check string literals in Haskell? I think it would > be nice if we can check if a given string literal is a valid URL or an > email address at compile time. > > Regards, > Kwang Yul Seo Non-text part: text/html > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe I think QuasiQuoters were designed for pretty much this purpose. They're basically functions from Strings to expressions (or types/declarations/patterns, depending on the context). A quasiquoter like [url|http://example.com] could parse the string passed to it ("http://example.com") at compile time and return an expression of type URL (or throw an error or something else), or maybe even some other data structure that will end up being useful. From jwlato at gmail.com Sat Mar 1 16:15:26 2014 From: jwlato at gmail.com (John Lato) Date: Sat, 1 Mar 2014 08:15:26 -0800 Subject: [Haskell-cafe] [Haskell] Can Haskell use short floats; i.e. 16 bit floats to save space? In-Reply-To: References: <5311828E.9080904@henning-thielemann.de> Message-ID: Did you mean unboxed vectors? Storable vectors will store an Int16 in 16 bits, so that's another approach. On Fri, Feb 28, 2014 at 11:56 PM, Johan Tibell wrote: > Am 01.03.2014 07:09, schrieb KC: >> >> Can Haskell use short floats; i.e. 16 bit floats to save space? >>> >> > GHC pads all basic data types to one word in its in-memory representation, > so no. It's possible that the boxed vectors in the "vector" package has a > more compact representation for arrays of Floats. > > -- Johan > > > _______________________________________________ > 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 omari at smileystation.com Sat Mar 1 17:48:08 2014 From: omari at smileystation.com (Omari Norman) Date: Sat, 1 Mar 2014 12:48:08 -0500 Subject: [Haskell-cafe] Safe Haskell design question - package trust Message-ID: Safe Haskell has three levels of safety: Safe - pure functions won't launch missiles. Well, sort of. They might launch missiles if they apply functions from other Trustworthy modules that do launch missiles, though one can use -fpackage-trust to mitigate this issue. Unsafe - pure functions might launch missiles, watch out. Trustworthy - module author raises her hand and says "My pure functions won't launch missiles, I promise." I can use the package trust feature to say "only trust a Trustworthy package if I say so." My issue is this: why is there no easy way to trust *any* package, not just packages that are Trustworthy? I should be able to say "I trust this package." It is immaterial whether the package author has raised her hand and said "my pure functions don't launch missiles" when I can examine the code for myself and determine whether the code launches missiles. Indeed, if I use package trust, I need to either examine the code or trust the author--the author's pledge isn't determinative. I see what "Trustworthy" adds when you're not using package trust, but it's just an informational flag if you are using package trust. Despite this Safe Haskell will not recognize the trustworthiness of packages that I have deliberately marked as trusted--merely because the author has not made a pledge. I ask because Safe Haskell has been around for over two years now yet the time package, which ships with GHC, has modules that are unsafe. I have examined them; they don't launch missiles. Yet the only easy way to get them working with Safe Haskell is to get the modules marked Trustworthy. I have emailed the maintainer and the libraries mailing list and so far have heard nothing. I have seen at least one package author get annoyed because people asked him to mark his modules Trustworthy, and I think he's right. He shouldn't need to say they're Trustworthy; rather, the Safe Haskell user should be able to do this himself. (True, the Safe Haskell user can do this by recompiling--come on, it shouldn't be that hard, and I don't want to recompile a package like time, that ships with GHC.) From keydana at gmx.de Sat Mar 1 18:33:47 2014 From: keydana at gmx.de (keydana at gmx.de) Date: Sat, 1 Mar 2014 19:33:47 +0100 Subject: [Haskell-cafe] parsec problem: infinite loop (possibly connected to try(lookahead ...)) but how?) Message-ID: <5F3D34CD-8371-4BCC-A601-9472E62488BB@gmx.de> Hi, I want to parse a rather unstructured log file, skipping blocks I'm not interested in but keeping others. For that purpose, I define "markers" that flag the beginning of interesting chunks. The "skip parser" reads anything until such a marker (using manyTill parseAny (try (lookAhead parseMarker)) and then the relative content parser starts by really consuming this marker string. I have a test case demonstrating this principle which works fine, but when I execute the (seemingly!) equivalent "real" code on a piece of a (seemingly!) equivalent "real log file", ghci enters an infinite loop - and I have no idea why... I'd be very grateful for any help, as I'm completely stuck here ;-) Following are: - the test input file - the piece of "real logfile" - the complete code in one piece (Main.hs), with the test case code in the bottom These are the results when I run 1) the test case: *Main> readFile "testfile.txt" >>= parseTest parseAll ["aaa\naaa\n","aaa\naaa\n","aaa\naaa\n"] 2) the main code (endless loop interrupted, with output from debug.trace): parseUntilChunkWFG: "" parseMaybeChunk: Nothing parseWFGMarker: Global Wait-For-Graph(WFG) at ddTS[0.3] : parseUntilChunkWFG: "" parseMaybeChunk: Nothing ^CparseWFGMarker: Global Wait-For-Graph(WFG) at ddTS[0.3] : parseUntilChunkWFG: "" parseMaybeChunk: Nothing Interrupted. This is the test input file, with vi newline symbols: ########################################################################## this is just some stuff$ I wanna skip$ $ this is, too$ 12[] $ $ BEGIN_MARKER$ aaa$ aaa$ $ this here again I can skip$ $ BEGIN_MARKER$ aaa$ aaa$ $ and then it goes on till the end of the file$ ########################################################################## ... and this is the real piece (part of, what is important I have 2 chunks of "interesting content"): ########################################################################## client details:$ O/S info: user: oracle, term: pts/2, ospid: 5820$ machine: node1.skyrac.com program: sqlplus at node1.skyrac.com (TNS V1-V3)$ application name: sqlplus at node1.skyrac.com (TNS V1-V3), hash value=10026263$ current SQL:$ insert into test values(2)$ DUMP LOCAL BLOCKER: initiate state dump for DEADLOCK$ possible owner[39.5827] on resource TX-00080011-00000545$ $ *** 2014-02-22 08:43:55.554$ Submitting asynchronized dump request [28]. summary=[ges process stack dump (kjdglblkrdm1)].$ Global blockers dump end:-----------------------------------$ Global Wait-For-Graph(WFG) at ddTS[0.3] :$ BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0xc0006.0x1c5(ext 0x4,0x0)[27000-0001-00000001] inst 1 $ BLOCKER 0x83b196a8 3 wq 1 cvtops x28 TX 0xc0006.0x1c5(ext 0x4,0x0)[36000-0002-00000005] inst 2 $ BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0x80011.0x545(ext 0x2,0x0)[36000-0002-00000005] inst 2 $ BLOCKER 0x83b35b10 3 wq 1 cvtops x28 TX 0x80011.0x545(ext 0x2,0x0)[27000-0001-00000001] inst 1 $ $ *** 2014-02-22 08:43:56.292$ * Cancel deadlock victim lockp 0x83437238 $ DUMP LOCAL BLOCKER: initiate state dump for DEADLOCK$ possible owner[39.5827] on resource TX-00080011-00000545$ $ *** 2014-02-22 08:43:55.554$ Submitting asynchronized dump request [28]. summary=[ges process stack dump (kjdglblkrdm1)].$ Global blockers dump end:-----------------------------------$ Global Wait-For-Graph(WFG) at ddTS[0.3] :$ BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0xc0006.0x1c5(ext 0x4,0x0)[27000-0001-00000001] inst 1$ BLOCKER 0x83b196a8 3 wq 1 cvtops x28 TX 0xc0006.0x1c5(ext 0x4,0x0)[36000-0002-00000005] inst 2$ BLOCKED 0x83437238 3 wq 2 cvtops x1 TX 0x80011.0x545(ext 0x2,0x0)[36000-0002-00000005] inst 2$ BLOCKER 0x83b35b10 3 wq 1 cvtops x28 TX 0x80011.0x545(ext 0x2,0x0)[27000-0001-00000001] inst 1$ $ *** 2014-02-22 08:43:56.292$ ########################################################################## ... and this is the code: ########################################################################## module Main ( main ) where import System.Environment import System.Directory import Text.ParserCombinators.Parsec import Debug.Trace import Numeric import Data.Maybe import Data.Char main = do --files <- getArgs currDir <- getCurrentDirectory --let filepaths = map ((currDir ++ "/") ++) ["munip1_lmd0_5702.trc", "munip2_lmd0_5966.trc"] let filepaths = map ((currDir ++ "/") ++) ["munip1_lmd0_5702.trc"] wfgs <- mapM (\p -> parseFromFile parseChunks p) filepaths print wfgs parseChunks :: Parser [Chunk] parseChunks = do chunks <- many1 parseMaybeChunk -- trace ("parseChunks: " ++ (show chunks)) return (catMaybes chunks) return (catMaybes chunks) parseMaybeChunk :: Parser (Maybe Chunk) parseMaybeChunk = do chunk <- try (parseChunkWFG >>= return . Just) <|> try (parseUntilChunkWFG >> return Nothing) <|> (parseTillEOF >> return Nothing) trace ("parseMaybeChunk: " ++ show chunk) return chunk --return chunk parseUntilChunkWFG :: Parser [Char] parseUntilChunkWFG = do skip <- manyTill parseAny (try (lookAhead parseWFGMarker) ) trace ("parseUntilChunkWFG: " ++ show skip) return skip --return skip parseAny :: Parser Char parseAny = do anyC <- oneOf (['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9'] ++ "()[]* -:.,/_?@='\n\\") --trace ("parseAny: " ++ (show anyC)) return anyC return anyC parseWFGMarker :: Parser [Char] parseWFGMarker = do marker <- string "Global Wait-For-Graph(WFG) at ddTS[0.3] :\n" trace ("parseWFGMarker: " ++ marker) return marker --return marker parseTillEOF :: Parser [Char] parseTillEOF = do anyCs <- many1 anyChar eof --trace ("parseTillEOF: " ++ anyCs) return anyCs return anyCs parseChunkWFG :: Parser Chunk parseChunkWFG = do marker <- string "Global Wait-For-Graph(WFG) at ddTS[0.3] :\n" wfg <- manyTill parseWFGEntry newline --trace ("parseChunkWFG: " ++ (show wfg)) return $ ChunkWFG wfg return $ ChunkWFG wfg parseWFGEntry :: Parser WFGEntry parseWFGEntry = do role <- try (string "BLOCKER") <|> string "BLOCKED" skipMany1 (space >> string "0x") lockaddr <- many1 hexDigit skipMany1 (space >> (many1 digit) >> space >> string "wq" >> space >> (many1 digit) >> space >> string "cvtops" >> space >> char 'x' >> (many1 digit) >> space) restype <- manyTill upper space skipMany1 (string "0x") id1 <- manyTill hexDigit (string ".0x") id2 <- manyTill hexDigit (string "(ext ") manyTill (digit <|> oneOf ")[]x,-") (string " inst ") instid <- manyTill digit (space >> newline) let wfgEntry = WFGEntry (read role :: Role) lockaddr (ResourceId id1 id2 restype) (read instid) --trace ("parseWFGEntry: " ++ show wfgEntry) return $ wfgEntry {- trace ("parseWFGEntry: " ++ role ++ " " ++ lockaddr ++ " " ++ restype ++ " " ++ id1 ++ " " ++ id2 ++ " " ++ instid) return $ wfgEntry -} return $ wfgEntry data Chunk = ChunkWFG WFG deriving (Show, Read) data ResourceId = ResourceId { id1 :: String, id2 :: String, restype :: String } deriving (Show, Read) data WFGEntry = WFGEntry { role :: Role, lockaddr :: String, resource :: ResourceId, instid :: Int } deriving (Show, Read) type WFG = [WFGEntry] data Role = BLOCKED | BLOCKER deriving (Show, Read) ------------------- testcase code --------------------------- parseAll :: Parser [String] parseAll = do chunks <- many1 parseChunk return (catMaybes chunks) parseChunk :: Parser (Maybe [Char]) parseChunk = do chunk <- try (parseContent >>= return . Just) <|> try (parseUntilMarker >> return Nothing) <|> (parseTillEOF >> return Nothing) --trace ("parseChunk: " ++ show chunk) return chunk return chunk parseUntilMarker :: Parser [Char] parseUntilMarker = do skip <- manyTill parseAny (try (lookAhead parseMarker) ) --trace ("parseUntilMarker: " ++ show skip) return skip return skip parseMarker :: Parser [Char] parseMarker = do marker <- string "BEGIN_MARKER\n" --trace ("parseWFGMarker: " ++ marker) return marker return marker parseContent :: Parser [Char] parseContent = do marker <- string "BEGIN_MARKER\n" items <- manyTill parseItem newline --trace ("parseContent: " ++ (show items)) return $ concat items return $ concat items parseItem :: Parser [Char] parseItem = string "aaa\n" ########################################################################## Many thanks in advance for any hints what might be going on :-)! Sigrid -------------- next part -------------- An HTML attachment was scrubbed... URL: From cobbe at ccs.neu.edu Sun Mar 2 00:35:09 2014 From: cobbe at ccs.neu.edu (Richard Cobbe) Date: Sat, 1 Mar 2014 19:35:09 -0500 Subject: [Haskell-cafe] questions about ghc-clang-wrapper Message-ID: <20140302003509.GC307@ridcully.home> I've just run the ghc-clang-wrapper script (from https://gist.github.com/tibbe/8448715) to try to get GHC 7.6.3 (part of Haskell Platform 2013-2.0.0) working with XCode 5.0.2 on a MacOS 10.8.5 machine. Things look good, but I have two questions: Question 1: How do I know this worked? I tested it by modifying a package that I'm writing so that it requires CPP to build correctly, and successfully built it with "cabal clean; cabal configure; cabal build". (More details available on request.) Does that mean I'm in good shape? (I'm asking because I was never entirely clear on what the incompatibility was; all I know is that it has something to do with cpp.) Question 2: Is there any harm in adding -Wno-return-type to extraClangArgs in ghc-clang-wrapper? This silences an annoying but apparently harmless warning I get from "cabal configure". Thanks, Richard From carter.schonwald at gmail.com Sun Mar 2 00:40:15 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 1 Mar 2014 19:40:15 -0500 Subject: [Haskell-cafe] questions about ghc-clang-wrapper In-Reply-To: <20140302003509.GC307@ridcully.home> References: <20140302003509.GC307@ridcully.home> Message-ID: Just use GCC and follow the alternative directions for getting ghc to point at a real GCC. They're linked to from the Mac Haskell platform page as the alternative directions. On Saturday, March 1, 2014, Richard Cobbe wrote: > I've just run the ghc-clang-wrapper script (from > https://gist.github.com/tibbe/8448715) to try to get GHC 7.6.3 (part of > Haskell Platform 2013-2.0.0) working with XCode 5.0.2 on a MacOS 10.8.5 > machine. Things look good, but I have two questions: > > Question 1: How do I know this worked? I tested it by modifying a package > that I'm writing so that it requires CPP to build correctly, and > successfully built it with "cabal clean; cabal configure; cabal build". > (More details available on request.) Does that mean I'm in good shape? > > (I'm asking because I was never entirely clear on what the incompatibility > was; all I know is that it has something to do with cpp.) > > Question 2: Is there any harm in adding -Wno-return-type to extraClangArgs > in ghc-clang-wrapper? This silences an annoying but apparently harmless > warning I get from "cabal configure". > > Thanks, > > Richard > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Mar 2 00:44:18 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sat, 1 Mar 2014 19:44:18 -0500 Subject: [Haskell-cafe] questions about ghc-clang-wrapper In-Reply-To: <20140302003509.GC307@ridcully.home> References: <20140302003509.GC307@ridcully.home> Message-ID: On Sat, Mar 1, 2014 at 7:35 PM, Richard Cobbe wrote: > Question 1: How do I know this worked? I tested it by modifying a package > that I'm writing so that it requires CPP to build correctly, and > successfully built it with "cabal clean; cabal configure; cabal build". > (More details available on request.) Does that mean I'm in good shape? > If you didn't get a compile failure after a bunch of syntax errors reported by cpp, you're good. (The problem is that clang's cpp is more pedantic about C syntax than gcc's, and doesn't appreciate being run on Haskell source. The patch adds options to disable the pedanticism.) -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Mar 2 01:35:22 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 1 Mar 2014 20:35:22 -0500 Subject: [Haskell-cafe] questions about ghc-clang-wrapper In-Reply-To: References: <20140302003509.GC307@ridcully.home> Message-ID: woops, yeah, brandon is correct. you're fine On Sat, Mar 1, 2014 at 7:44 PM, Brandon Allbery wrote: > On Sat, Mar 1, 2014 at 7:35 PM, Richard Cobbe wrote: > >> Question 1: How do I know this worked? I tested it by modifying a package >> that I'm writing so that it requires CPP to build correctly, and >> successfully built it with "cabal clean; cabal configure; cabal build". >> (More details available on request.) Does that mean I'm in good shape? >> > > If you didn't get a compile failure after a bunch of syntax errors > reported by cpp, you're good. (The problem is that clang's cpp is more > pedantic about C syntax than gcc's, and doesn't appreciate being run on > Haskell source. The patch adds options to disable the pedanticism.) > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From philip.dexter at gmail.com Sun Mar 2 04:15:14 2014 From: philip.dexter at gmail.com (Philip Dexter) Date: Sat, 1 Mar 2014 23:15:14 -0500 Subject: [Haskell-cafe] ICFP 2014 deadline discrepancy: UTC -11 /= anywhere in the world Message-ID: ICFP 2014's website [1] (and all notices) list the deadline as Saturday, 1 March 2014, 23:59 UTC-11 (anywhere in the world) Anywhere in the world time, also known as Anywhere on Earth (AoE), is UTC-12, not UTC-11. Is there anybody that can confirm that this is intentional? EasyChair does not list a deadline. -- [1] http://www.icfpconference.org/icfp2014/index.html -------------- next part -------------- An HTML attachment was scrubbed... URL: From amit at amitlevy.com Sun Mar 2 05:27:26 2014 From: amit at amitlevy.com (Amit Aryeh Levy) Date: Sat, 01 Mar 2014 21:27:26 -0800 Subject: [Haskell-cafe] ICFP 2014 deadline discrepancy: UTC -11 /= anywhere in the world In-Reply-To: References: Message-ID: <5312C13E.4040605@amitlevy.com> Any news on this by chance? I would love to have an extra hour of not sleeping! On 03/01/2014 08:15 PM, Philip Dexter wrote: > ICFP 2014's website [1] (and all notices) list the deadline as > > Saturday, 1 March 2014, 23:59 UTC-11 (anywhere in the world) > > Anywhere in the world time, also known as Anywhere on Earth (AoE), is > UTC-12, not UTC-11. > > Is there anybody that can confirm that this is intentional? EasyChair > does not list a deadline. > > > -- > > [1] http://www.icfpconference.org/icfp2014/index.html > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From philip.dexter at gmail.com Sun Mar 2 05:33:52 2014 From: philip.dexter at gmail.com (Philip Dexter) Date: Sun, 2 Mar 2014 00:33:52 -0500 Subject: [Haskell-cafe] ICFP 2014 deadline discrepancy: UTC -11 /= anywhere in the world In-Reply-To: <5312C13E.4040605@amitlevy.com> References: <5312C13E.4040605@amitlevy.com> Message-ID: On Sun, Mar 2, 2014 at 12:27 AM, Amit Aryeh Levy wrote: > Any news on this by chance? I would love to have an extra hour of not > sleeping! > > None yet, unfortunately. My advisor said he would wake up 2 hours before the deadline to make one final pass. He said this under the impression that the deadline was tonight, AoE. He'll be cranky when I call him an hour earlier! -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at snoyman.com Sun Mar 2 06:43:34 2014 From: michael at snoyman.com (Michael Snoyman) Date: Sun, 2 Mar 2014 08:43:34 +0200 Subject: [Haskell-cafe] Scaling Haskell/Yesod on OpenShift In-Reply-To: References: Message-ID: On Fri, Feb 28, 2014 at 10:22 PM, Joey Eremondi wrote: > I was wondering, does anyone have experience with using Haskell/Yesod on > the OpenShift PaaS? I've seen the Haskell and Yesod cartridges, but I'm > wondering if there's any way to get Haskell playing nice with their > load-balancing and automatic scaling capabilities? Would CloudHaskell be > useful at all in this? > > I'm reasonably experienced with Haskell but very new to Cloud computing > and Web stuff, so any advice, even if basic, is helpful. Thanks! > > I have no experience with OpenShift. But if you avoid using shared-memory operations and instead store shared data in an out-of-process database, scaling horizontally should be possible by just using the load balancer. CloudHaskell could certainly be used for some tasks, but in my experience, most web applications fall into the embarrassingly parallelizable category, where simply throwing a few more machines at the problem works. Michael -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Sun Mar 2 19:54:40 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Sun, 2 Mar 2014 21:54:40 +0200 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question Message-ID: Hi all, I'm designing a ncurses based GUI library. I'm calling smallest GUI elements "widgets". A widget can have internal state of any type. Let's call this type `s`. I want to be able to have something like this: > data Widget s = Widget > { handleKey :: Key -> s -> s > , draw :: Int -> Int -> Int -> Int -> IO () > , getFocus :: s -> s > , loseFocus :: s -> s > -- more methods may be added in the future > } I also want to be able to have container types like this: > data Container = Container [Widget s] but obviously this does not work because widgets may have different types of states. So problem I'm trying to solve here is that I should somehow abstract internal state used in a Widget but still be able to keep track of that state so that I can pass it to methods in sequential invocations of that methods. Also, once I have a container like this, updating widget states would become a problem. I'd have to somehow keep all those states like: > data Container = Container [Widget] [WidgetState] or > data Container = Container [(Widget, WidgetState)] and then manually pass state to widgets when calling methods, and update the list using return values of methods. In a sense I'm like trying to emulate something like closures with mutable closed-over data in impure languages. I think one way to have a similar effect is to use closures with closed-over IORefs. Then I could modify that state but then I'd need to have methods with types `IO ()`. I want to have more "precise" types. i.e. IO is a lot more general than what I'd like to have as my widget methods. (side effect of a widget should be limited with changes in it's internal state) Sorry for badly organized post, I'm a bit tired right now and I hope my points are clear. I'm trying to figure out Haskell way of doing something like this, without going into IO world. Ideas/suggestions would be appreciated. Thanks, --- ?mer Sinan A?acan http://osa1.net From ianwookim at gmail.com Sun Mar 2 20:41:37 2014 From: ianwookim at gmail.com (Ian-Woo Kim) Date: Sun, 2 Mar 2014 12:41:37 -0800 Subject: [Haskell-cafe] ANN: poppler-0.12.3 is released. Message-ID: Hi, Haskellers! A new version of haskell poppler library is now released. Poppler is a pdf rendering library, based on xpdf code base. It's being developed and has quite complete features. Haskell poppler library is a binding to the native poppler library. Recently, gtk2hs-0.12.5 was released and we now have support to gtk3. We also have a great advance of Cabal-1.18, but the previous version of poppler was not buildable with the new Cabal. So this version (0.12.3) of poppler is to support gtk2hs-0.12.5 and Cabal-1.18. By default, poppler is compiled against gtk version 2, but with -fgtk3 option, one can build poppler with gtk3. The new version of poppler is available on hackage. Enjoy! Ian-Woo Kim From daniel.trstenjak at gmail.com Sun Mar 2 21:38:02 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Sun, 2 Mar 2014 22:38:02 +0100 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: References: Message-ID: <20140302213802.GA17085@machine> Hi ?mer, > In a sense I'm like trying to emulate something like closures with > mutable closed-over data in impure languages. One way is to keep the specific data completely out of the Widget and use a closure to hold the data: data Widget = Widget { handleKey :: Key -> Widget , draw :: Int -> Int -> Int -> Int -> IO () , getFocus :: Widget , loseFocus :: Widget } someWidget :: SomeWidgetData -> Widget someWidget dat = Widget { handleKey = \key -> case key of 'A' -> someWidget $ dat { ... } ; ... , draw = \x y w h -> ... , getFocus = someWidget $ dat { focus = True } , loseFocus = someWidget $ dat { focus = False } } Greetings, Daniel From roma at ro-che.info Mon Mar 3 02:00:46 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 3 Mar 2014 04:00:46 +0200 Subject: [Haskell-cafe] ANN: tasty-0.8 Message-ID: <20140303020046.GA10372@sniper> I'm glad to announce the 0.8 release of tasty, a modern Haskell testing framework. http://hackage.haskell.org/package/tasty-0.8 Among the important user-visible changes are: - New running modes `--hide-successes` and `--quiet` - Short flags for some existing options (`-p` for `--pattern`, `-j` for `--num-threads`) - Timeout support - Possibility to pass options via environment variables - Fix of a resources-related bug For details, see the CHANGELOG and README: https://github.com/feuerbach/tasty/blob/master/CHANGES.md http://documentup.com/feuerbach/tasty tasty now has a mailing list[ml] and an IRC channel #tasty at FreeNode. The IRC channel is logged at ircbrowse.net[logs] (thanks to Chris Done). [ml]: https://groups.google.com/forum/#!forum/haskell-tasty [logs]: http://ircbrowse.net/tasty Read more: http://ro-che.info/articles/2014-03-03-tasty-0.8.html Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From jwlato at gmail.com Mon Mar 3 03:59:30 2014 From: jwlato at gmail.com (John Lato) Date: Sun, 2 Mar 2014 19:59:30 -0800 Subject: [Haskell-cafe] Type checking string literal in Haskell? In-Reply-To: References: Message-ID: Yes. In Haskell, types are your friends. You should define new types liberally. I think the usual approach is to create newtype wrapper: > module EmailAddr (EmailAddr, mkEmailAddr) where > > newtype EmailAddr = EmailAddr String > > mkEmailAddr :: String -> Maybe EmailAddr > mkEmailAddr str = if isEmailAddr then Just (EmailAddr str) else Nothing The only way to make an EmailAddr is via the mkEmailAddr function, which checks that the string is actually a valid address (implementation omitted). Therefore, there's a guarantee that any EmailAddr is actually a well-formed email address, and any functions that operate on an EmailAddr can rely upon this. Of course, it might be useful to create an actual algebraic type instead: > data EmailAddr = EmailAddr { address :: String, domain :: String } (and the domain could similarly be an algebraic type instead of a plain string) In general, you should be working with types that closely reflect the domain you're working in. This will make your functions more clear, and the compiler/type checker will be able to provide more help during development. John L. On Sat, Mar 1, 2014 at 4:35 AM, KwangYul Seo wrote: > In Java, the Checker Framework ( > http://types.cs.washington.edu/checker-framework/) provides a way to type > check string literals. For example, Java signatures type system > differentiates strings literals in different forms: > > 1. Unqualified strings : > "Hello, world!" -> @Unqualified String > > 2. Fully qualified names: > "package.Outer.Inner" -> @FullyQualifiedString String > > 3. Binary names: > "package.Outer$Inner" -> @BinaryName String > > 4. Field descriptors: > "Lpackage/Outer$Inner;" -> @FieldDescriptor String > > It can do the similar checks with regular expressions or SQL statements. > > Is it possible to type check string literals in Haskell? I think it would > be nice if we can check if a given string literal is a valid URL or an > email address at compile time. > > Regards, > Kwang Yul Seo > > > _______________________________________________ > 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 charles.c.strahan at gmail.com Mon Mar 3 05:41:13 2014 From: charles.c.strahan at gmail.com (Charles Strahan) Date: Mon, 3 Mar 2014 00:41:13 -0500 Subject: [Haskell-cafe] question re: FFI and ensuring unwrapped values are present on stack Message-ID: Hello all, This is probably going to be a pretty niche question, but I'm hoping someone here can lend a hand. I'm working on a binding for the YARV Ruby VM, and I'm struggling to come up a with a good interop story with respect to its GC implementation. I have two options to prevent premature GC of Ruby object pointers: 1) Guarantee that the pointers reside on the stack or in registers, 2) or copy the pointer itself to another static area of memory and register that address with the GC. So, the big question is: is there a way to make #1 a reality, while operating in the IO monad? I can picture something like the following: newtype RValue = RValue (Ptr RValue) deriving (Storable) withObject :: IO RValue -- e.g. result of some ccall, or some further transformation thereof -> (RValue -> IO a) -- the RValue is now on the stack (or in a register), available for use without worry of premature GC -> IO a -- the result of computation With Haskell being a non-strict language, I understand that there are a lot of instances where a value could end up on the heap, with a thunk being passed via stack/registers. For my needs, I'd need some way to guarantee that the RValues being passed to and from withObject are at all times kept unwrapped and off the heap, and likewise within the second argument. Given my rather limited knowledge of Haskell (I've been programming in Haskell for about a month now), I think the best I can come up with is the second option suggested above: withObject :: (Ptr RValue -> IO ()) -- e.g. void some_fun(VALUE* out) {...} -> (RValue -> IO a) -- e.g. do something with `out` derefed -> IO a withObject f g = alloca $ \ptr -> do rb_gc_register_address ptr -- prevent GC f ptr -- call wrapped native function val <- peek ptr -- deref the VALUE* res <- g val -- pass to function rb_gc_unregister_address ptr -- clean up res So, while the above would work, it's really, really ugly (IMO). That, and I'd have to wrap all the native functions so that instead of returning VALUE, they'd write to some out ptr and return void. And there's the otherwise unnecessary alloca. I hope that was clear enough - any advice would be super duper appreciated! I'm assuming that there isn't a way I can get away with using the typical monadic bind syntax while keeping the RValues off the heap; if I'm wrong, and I can skip the whole withObject/HOF approach, I'd love to know it! I'm not (yet) familiar enough with the compiler / language spec to know about such guarantees, should they exist... - Charles -------------- next part -------------- An HTML attachment was scrubbed... URL: From sean at functionaljobs.com Mon Mar 3 07:00:05 2014 From: sean at functionaljobs.com (Functional Jobs) Date: Mon, 3 Mar 2014 02:00:05 -0500 Subject: [Haskell-cafe] New Functional Programming Job Opportunities Message-ID: <53142878dd17b@functionaljobs.com> Here are some functional programming job opportunities that were posted recently: NixOS/Haskell DevOps Engineer at Zalora http://functionaljobs.com/jobs/8687-nixos-haskell-devops-engineer-at-zalora functional software developer at OpinionLab http://functionaljobs.com/jobs/8685-functional-software-developer-at-opinionlab Platform Engineer at Signal Vine LLC http://functionaljobs.com/jobs/8684-platform-engineer-at-signal-vine-llc Cheers, Sean Murphy FunctionalJobs.com From omeragacan at gmail.com Mon Mar 3 07:50:19 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 3 Mar 2014 09:50:19 +0200 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: <20140302213802.GA17085@machine> References: <20140302213802.GA17085@machine> Message-ID: Hi Daniel, This won't work. Let's say there has been two keypresses and I called handleKey two times. First time it updates the `dat` and returns it but how can I pass that updated `dat` object to the same function in second invocation? --- ?mer Sinan A?acan http://osa1.net 2014-03-02 23:38 GMT+02:00 Daniel Trstenjak : > > Hi ?mer, > >> In a sense I'm like trying to emulate something like closures with >> mutable closed-over data in impure languages. > > One way is to keep the specific data completely out of the Widget and > use a closure to hold the data: > > data Widget = Widget > { handleKey :: Key -> Widget > , draw :: Int -> Int -> Int -> Int -> IO () > , getFocus :: Widget > , loseFocus :: Widget > } > > someWidget :: SomeWidgetData -> Widget > someWidget dat = Widget > { handleKey = \key -> case key of 'A' -> someWidget $ dat { ... } ; ... > , draw = \x y w h -> ... > , getFocus = someWidget $ dat { focus = True } > , loseFocus = someWidget $ dat { focus = False } > } > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From daniel.trstenjak at gmail.com Mon Mar 3 08:06:46 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 3 Mar 2014 09:06:46 +0100 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: References: <20140302213802.GA17085@machine> Message-ID: <20140303080645.GB2069@machine> Hi ?mer, On Mon, Mar 03, 2014 at 09:50:19AM +0200, ?mer Sinan A?acan wrote: > This won't work. Let's say there has been two keypresses and I called > handleKey two times. First time it updates the `dat` and returns it > but how can I pass that updated `dat` object to the same function in > second invocation? If you call 'handleKey', then it returns a new Widget with a new 'handleKey' function having a closure over the modified 'dat'. data Counter = Counter { increase :: Counter , draw :: IO () } someCounter :: Int -> Counter someCounter count = Counter { increase = someCounter $ count + 1 , draw = print count } *Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase someCounter *Main> draw c' 1 Greetings, Daniel From daniel.trstenjak at gmail.com Mon Mar 3 08:10:48 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 3 Mar 2014 09:10:48 +0100 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: <20140303080645.GB2069@machine> References: <20140302213802.GA17085@machine> <20140303080645.GB2069@machine> Message-ID: <20140303081048.GC2069@machine> > *Main> let c = someCounter 0 > *Main> draw c > 0 > *Main> let c' = increase someCounter > *Main> draw c' > 1 Sorry, the example should have been: *Main> let c = someCounter 0 *Main> draw c 0 *Main> let c' = increase c *Main> draw c' 1 Greetings, Daniel From omeragacan at gmail.com Mon Mar 3 09:17:30 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 3 Mar 2014 11:17:30 +0200 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: <20140303081048.GC2069@machine> References: <20140302213802.GA17085@machine> <20140303080645.GB2069@machine> <20140303081048.GC2069@machine> Message-ID: Ops, sorry. I misunderstand your code. Now that looks like solving my problem of updating widgets, and maybe I can use Data.Map.Map to keep widgets and update them when methods are called. Now this works but that explicit state updating and passing is not ideal for me. I know I can always hide that kind of things behind a state monad: > data Program = Program > { ... > , widgets :: (Map Int Widget, Int) > , ... > } > > > handleKey' :: Key -> State Program () > handleKey' key = do > programState at Program{(widgets, focusIdx)=widgets} <- get > let widget = fromJust $ lookup focusIdx widgets > widget' = handlekey widget key > > put programState{widgets=(M.insert focusIdx widget', focusIdx)} and I can even create a typeclass like `HasWidgets` which provides required methods for updating widget states and that would be even more flexible: > {-# LANGUAGE PackageImports, > MultiParamTypeClasses, > FlexibleInstance #-} > > import "mtl" Control.Monad.State > import qualified Data.Map as M > import Data.Maybe > > > type Key = Int > type Widget = Int -- placeholder > type FocusIdx = Int > > > data Program = Program > { widgets :: (M.Map Int Int, Int) > } > > class HasWidgets s where > getWidgets :: s -> (M.Map Int Widget, FocusIdx) > updateWidgets :: (M.Map Int Widget, FocusIdx) -> s -> s > > > class (MonadState s m, HasWidgets s) => Widgets s m where > handleKey_ :: Key -> m () > > > instance HasWidgets Program where > getWidgets = widgets > updateWidgets w p = p{widgets=w} > > > instance Monad m => Widgets Program (StateT Program m) where > handleKey_ key = do > programState at Program{widgets=(widgets, focusIdx)} <- get > let w = fromJust $ M.lookup focusIdx widgets > w' = undefined -- just call handleKey method of widget `w` > put programState{widgets=(M.insert focusIdx w' widgets, focusIdx)} > > > test :: State Program () > test = do > programState at Program{widgets=(widgets, focusIdx)} <- get > return () ... but is there a better way to do this? Maybe by using Lens(I'm not sure if something like that makes sense -- this just came to my mind because all I do here is to do nested record updates, which as far as I know where Lens shines) ? --- ?mer Sinan A?acan http://osa1.net 2014-03-03 10:10 GMT+02:00 Daniel Trstenjak : > >> *Main> let c = someCounter 0 >> *Main> draw c >> 0 >> *Main> let c' = increase someCounter >> *Main> draw c' >> 1 > > Sorry, the example should have been: > > *Main> let c = someCounter 0 > *Main> draw c > 0 > *Main> let c' = increase c > *Main> draw c' > 1 > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From omeragacan at gmail.com Mon Mar 3 09:37:05 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 3 Mar 2014 11:37:05 +0200 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: References: <20140302213802.GA17085@machine> <20140303080645.GB2069@machine> <20140303081048.GC2069@machine> Message-ID: Again, sorry, just pasted wrong code, correct version should be: > {-# LANGUAGE PackageImports, > MultiParamTypeClasses, > FlexibleInstances, > FlexibleContexts #-} > > import "mtl" Control.Monad.State > import "mtl" Control.Monad.Identity > import qualified Data.Map as M > import Data.Maybe > > > type Key = Int > type Widget = Int -- placeholder > type FocusIdx = Int > > > data Program = Program > { widgets :: (M.Map Int Int, Int) > } > > > class HasWidgets s where > getWidgets :: s -> (M.Map Int Widget, FocusIdx) > updateWidgets :: (M.Map Int Widget, FocusIdx) -> s -> s > > > instance HasWidgets Program where > getWidgets p = widgets p > updateWidgets w p = p{widgets=w} > > > handleKey :: (MonadState s m, HasWidgets s) => Key -> m () > handleKey key = do > p <- get > let (widgets, focusIdx) = getWidgets p > w = fromJust $ M.lookup focusIdx widgets > w' = undefined -- just update the widget > put $ updateWidgets (M.insert focusIdx w' widgets, focusIdx) p > > > test :: StateT Program Identity () > test = do > handleKey undefined > return () --- ?mer Sinan A?acan http://osa1.net 2014-03-03 11:17 GMT+02:00 ?mer Sinan A?acan : > Ops, sorry. I misunderstand your code. Now that looks like solving my > problem of updating widgets, and maybe I can use Data.Map.Map to keep > widgets and update them when methods are called. > > Now this works but that explicit state updating and passing is not > ideal for me. I know I can always hide that kind of things behind a > state monad: > >> data Program = Program >> { ... >> , widgets :: (Map Int Widget, Int) >> , ... >> } >> >> >> handleKey' :: Key -> State Program () >> handleKey' key = do >> programState at Program{(widgets, focusIdx)=widgets} <- get >> let widget = fromJust $ lookup focusIdx widgets >> widget' = handlekey widget key >> >> put programState{widgets=(M.insert focusIdx widget', focusIdx)} > > and I can even create a typeclass like `HasWidgets` which provides > required methods for updating widget states and that would be even > more flexible: > >> {-# LANGUAGE PackageImports, >> MultiParamTypeClasses, >> FlexibleInstance #-} >> >> import "mtl" Control.Monad.State >> import qualified Data.Map as M >> import Data.Maybe >> >> >> type Key = Int >> type Widget = Int -- placeholder >> type FocusIdx = Int >> >> >> data Program = Program >> { widgets :: (M.Map Int Int, Int) >> } >> >> class HasWidgets s where >> getWidgets :: s -> (M.Map Int Widget, FocusIdx) >> updateWidgets :: (M.Map Int Widget, FocusIdx) -> s -> s >> >> >> class (MonadState s m, HasWidgets s) => Widgets s m where >> handleKey_ :: Key -> m () >> >> >> instance HasWidgets Program where >> getWidgets = widgets >> updateWidgets w p = p{widgets=w} >> >> >> instance Monad m => Widgets Program (StateT Program m) where >> handleKey_ key = do >> programState at Program{widgets=(widgets, focusIdx)} <- get >> let w = fromJust $ M.lookup focusIdx widgets >> w' = undefined -- just call handleKey method of widget `w` >> put programState{widgets=(M.insert focusIdx w' widgets, focusIdx)} >> >> >> test :: State Program () >> test = do >> programState at Program{widgets=(widgets, focusIdx)} <- get >> return () > > > ... but is there a better way to do this? Maybe by using Lens(I'm not > sure if something like that makes sense -- this just came to my mind > because all I do here is to do nested record updates, which as far as > I know where Lens shines) ? > > --- > ?mer Sinan A?acan > http://osa1.net > > > 2014-03-03 10:10 GMT+02:00 Daniel Trstenjak : >> >>> *Main> let c = someCounter 0 >>> *Main> draw c >>> 0 >>> *Main> let c' = increase someCounter >>> *Main> draw c' >>> 1 >> >> Sorry, the example should have been: >> >> *Main> let c = someCounter 0 >> *Main> draw c >> 0 >> *Main> let c' = increase c >> *Main> draw c' >> 1 >> >> >> Greetings, >> Daniel >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe From daniel.trstenjak at gmail.com Mon Mar 3 10:14:41 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 3 Mar 2014 11:14:41 +0100 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: References: <20140302213802.GA17085@machine> <20140303080645.GB2069@machine> <20140303081048.GC2069@machine> Message-ID: <20140303101441.GA4636@machine> Hi ?mer, I don't think that you need the 'HasWidgets' class, it really doesn't give you a lot. Something like a function 'withFocused' would be a lot more useful: withFocused :: (Widget -> Widget) -> State Program () Greetings, Daniel From omeragacan at gmail.com Mon Mar 3 10:22:58 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 3 Mar 2014 12:22:58 +0200 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: <20140303101441.GA4636@machine> References: <20140302213802.GA17085@machine> <20140303080645.GB2069@machine> <20140303081048.GC2069@machine> <20140303101441.GA4636@machine> Message-ID: I think HasWidgets is useful because when focus is moved to another widget, I somehow need to find the widget that just got the focus in collection of widgets.. So I need to somehow search in widget map. I need a typeclass because I may have different types of widget containers and I want to be able to update them uniformly. --- ?mer Sinan A?acan http://osa1.net 2014-03-03 12:14 GMT+02:00 Daniel Trstenjak : > > Hi ?mer, > > I don't think that you need the 'HasWidgets' class, it really doesn't give you a lot. > Something like a function 'withFocused' would be a lot more useful: > > withFocused :: (Widget -> Widget) -> State Program () > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From stephen.tetley at gmail.com Mon Mar 3 12:28:02 2014 From: stephen.tetley at gmail.com (Stephen Tetley) Date: Mon, 3 Mar 2014 12:28:02 +0000 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: References: Message-ID: Hi ?mer A bit tangential, but you might find looking at Wolfram Kahl and his co-author's "Editor combinators" helpful: http://www.cas.mcmaster.ca/~kahl/Publications/TR/2000-01/ As you are using records to encapsulate functional "objects", your code strongly reminded me of editor combinators. Best wishes Stephen On 2 March 2014 19:54, ?mer Sinan A?acan wrote: > Hi all, > > I'm designing a ncurses based GUI library. > > I'm calling smallest GUI elements "widgets". > > A widget can have internal state of any type. Let's call this type > `s`. I want to be able to have something like this: > >> data Widget s = Widget >> { handleKey :: Key -> s -> s >> , draw :: Int -> Int -> Int -> Int -> IO () >> , getFocus :: s -> s >> , loseFocus :: s -> s >> -- more methods may be added in the future >> } > > I also want to be able to have container types like this: > >> data Container = Container [Widget s] > > but obviously this does not work because widgets may have different > types of states. > > So problem I'm trying to solve here is that I should somehow abstract > internal state used in a Widget but still be able to keep track of > that state so that I can pass it to methods in sequential invocations > of that methods. > > Also, once I have a container like this, updating widget states would > become a problem. I'd have to somehow keep all those states like: > >> data Container = Container [Widget] [WidgetState] > > or > >> data Container = Container [(Widget, WidgetState)] > > and then manually pass state to widgets when calling methods, and > update the list using return values of methods. > > In a sense I'm like trying to emulate something like closures with > mutable closed-over data in impure languages. > > I think one way to have a similar effect is to use closures with > closed-over IORefs. Then I could modify that state but then I'd need > to have methods with types `IO ()`. I want to have more "precise" > types. i.e. IO is a lot more general than what I'd like to have as my > widget methods. (side effect of a widget should be limited with > changes in it's internal state) > > Sorry for badly organized post, I'm a bit tired right now and I hope > my points are clear. I'm trying to figure out Haskell way of doing > something like this, without going into IO world. Ideas/suggestions > would be appreciated. > > Thanks, > > > --- > ?mer Sinan A?acan > http://osa1.net > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From haskell at nand.wakku.to Mon Mar 3 12:56:55 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Mon, 3 Mar 2014 13:56:55 +0100 Subject: [Haskell-cafe] I'm trying to design a GUI library -- a design question In-Reply-To: <20140303101441.GA4636@machine> Message-ID: <20140303135655.GA28584@nanodesu.talocan.mine.nu> <20140302213802.GA17085 at machine> <20140303080645.GB2069 at machine> <20140303081048.GC2069 at machine> <20140303101441.GA4636 at machine> On Mon, 3 Mar 2014 11:14:41 +0100, Daniel Trstenjak wrote: > > Hi ?mer, > > I don't think that you need the 'HasWidgets' class, it really doesn't give you a lot. > Something like a function 'withFocused' would be a lot more useful: > > withFocused :: (Widget -> Widget) -> State Program () > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe This looks like a use case for a lens to me. > focused :: Lens' Program Widget > over focused :: (Widget -> Widget) -> Program -> Program > (focused %=) :: MonadState Program m => (Widget -> Widget) -> m () > zoom focused :: (MonadState Widget m, MonadState Program n) => m a -> n a From dimitris at microsoft.com Mon Mar 3 14:53:34 2014 From: dimitris at microsoft.com (Dimitrios Vytiniotis) Date: Mon, 3 Mar 2014 14:53:34 +0000 Subject: [Haskell-cafe] [TYPES] OutsideIn(X) question In-Reply-To: References: Message-ID: Dear Alejandro, thanks for your notice! You are right, the entailment relation in the JFP paper is too weak for type classes. As we formulated it, the simplifier can take a type class reduction step but there is no way to show that the new set of constraints is equivalent to the original class constraint. There is nothing very deep going on, it's an oversight in the definition of entailment. The fix -- at least in the case of non-overlapping instances and vanilla multi-parameter type classes -- is to ensure that all axioms for type class instances form bi-implications. In fact in the constraint handling rules formulation of type classes, class instances always gave rise to such bi-implications. I will post the correction to the article on my web page in the next couple of weeks and let you know, but I thought I should send an update. Best regards, Dimitrios -----Original Message----- From: Types-list [mailto:types-list-bounces at lists.seas.upenn.edu] On Behalf Of Alejandro Serrano Mena Sent: Thursday, February 27, 2014 10:18 AM To: types-list at lists.seas.upenn.edu Subject: [TYPES] OutsideIn(X) question [ The Types Forum, http://lists.seas.upenn.edu/mailman/listinfo/types-list ] Dear Types List, I have a small question related to the "OutsideIn(X): Modular type inference with local assumptions" and was hoping that you could help me a bit. My question related about the proof of soundness and principality, specifically Lemma 7.2 (to be found in page 67). In that lemma, it's stated that QQ and \phi' Q_q ||- \phi Q_w <-> \phi' Q_w'. I'm trying to recover the proof (which is omitted in the text), but I stumble upon a wall when trying to work out what happens in the case an axiom is applied. In particular, I'm playing with an example where QQ (the set of axioms) = { forall. C a => D a } (where C and D are one-parameter type classes) Q_q = { } Q_w = { D Int } Thus, if I apply the rule DINSTW (to be found in page 65), I get a new Q_w' = { C Int } Now, if the lemma 7.2 is true, it should be the case that (1) QQ ||- C Int <-> D Int which in particular means that I have the two implications (2) { forall. C a => D a, C Int } ||- D Int (3) { forall. C a => D a, D Int } ||- C Int (2) follows easily by applying the AXIOM rule of ||- (as shown in page 54). However, I don't see how to make (3) work :( I think that understanding this example will be key for my understanding of the whole system. Anybody could point to the error in my reasoning or to places where I could find more information? Thanks in advance. From Graham.Hutton at nottingham.ac.uk Mon Mar 3 16:31:16 2014 From: Graham.Hutton at nottingham.ac.uk (Graham Hutton) Date: Mon, 3 Mar 2014 16:31:16 +0000 Subject: [Haskell-cafe] Journal of Functional Programming - Call for PhD Abstracts Message-ID: <685B31F5-BBBE-41EF-B898-6D5610D84371@exmail.nottingham.ac.uk> ============================================================ CALL FOR PHD ABSTRACTS Journal of Functional Programming Deadline: 30th April 2014 http://tinyurl.com/jfp-phd-abstracts ============================================================ PREAMBLE: Many students complete PhDs in functional programming each year, but there is currently no common location in which to promote and advertise the resulting work. The Journal of Functional Programming would like to change that! As a service to the community, JFP is launching a new feature, in the form of a yearly publication of abstracts from PhD dissertations that were completed during the previous year. To start this new feature off, we would like to reach back three years for the first round of abstracts. The abstracts will be freely available on the JFP website, i.e. not behind any paywall, and will not require any transfer for copyright, merely a license from the author. Please submit dissertation abstracts according to the instructions below. A dissertation is eligible if parts of it have or could appear in JFP, that is, if it is in the general area of functional programming. JFP will not have these abstracts reviewed. We welcome submissions from both the PhD student and PhD advisor/supervisor although we encourage them to coordinate. ============================================================ SUBMISSION: Please submit the following information to Graham Hutton by 30th April 2014. o Student: (full name) o Advisor/supervisor: (full names) o Dissertation title: (including any subtitle) o Dissertation abstract: (plain text, maximum 1000 words; you may use \emph{...} for emphasis, but we prefer no other markup or formatting in the abstract, but do get in touch if this causes significant problems) o Dissertation URL: (please provide a permanently accessible link to the dissertation if you have one, such as to an institutional repository or other public archive; links to personal web pages should be considered a last resort) o Awarding institution: (full name and location) o Date of PhD award: (depending on the institution, this may be the date of the viva, date when corrections were approved, date of graduation ceremony, or otherwise) Please do not submit a copy of the dissertation itself, as this is not required. JFP reserves the right to decline to publish abstracts that are not deemed appropriate. ============================================================ PHD ABSTRACT EDITOR: Graham Hutton School of Computer Science University of Nottingham Nottingham NG8 1BB United Kindgdom ============================================================ This message and any attachment are intended solely for the addressee and may contain confidential information. If you have received this message in error, please send it back to me, and immediately delete it. Please do not use, copy or disclose the information contained in this message or in any attachment. Any views or opinions expressed by the author of this email do not necessarily reflect the views of the University of Nottingham. This message has been checked for viruses but the contents of an attachment may still contain software viruses which could damage your computer system, you are advised to perform your own checks. Email communications with the University of Nottingham may be monitored as permitted by UK legislation. From ok at cs.otago.ac.nz Mon Mar 3 20:29:53 2014 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Tue, 4 Mar 2014 09:29:53 +1300 Subject: [Haskell-cafe] Type checking string literal in Haskell? In-Reply-To: References: Message-ID: <3F7F7F36-94AB-4CB2-A326-1B3BF7A7381D@cs.otago.ac.nz> On 3/03/2014, at 4:59 PM, John Lato wrote: > Yes. In Haskell, types are your friends. You should define new types liberally. I believe the original poster was asking about a *static* check. Newtypes with "smart constructors" are a good way to plug in a *dynamic* check, which is valuable but different. From vogt.adam at gmail.com Mon Mar 3 23:17:32 2014 From: vogt.adam at gmail.com (adam vogt) Date: Mon, 3 Mar 2014 18:17:32 -0500 Subject: [Haskell-cafe] question re: FFI and ensuring unwrapped values are present on stack In-Reply-To: References: Message-ID: Hello Charles, I don't know what can be done for your option 1, but I have two suggestions for your option 2: Did you consider making RValue a ForeignPtr and adding a FunPtr to rb_gc_unregister as the finalizer? That will end up being a bit less restrictive than your "withObject", in exchange for a weaker guarantee as to when the finalizer actually runs. Also you might use the same trick that Control.Monad.ST does to prevent references from leaking out. In other words, change your definitions to look more like: newtype RValue s = RValue (ForeignPtr ()) withObject :: (forall s. RValue s -> IO r) -> IO r With that trick, (withObject return) becomes a type error. Regards, Adam On Mon, Mar 3, 2014 at 12:41 AM, Charles Strahan wrote: > Hello all, > > This is probably going to be a pretty niche question, but I'm hoping someone > here can lend a hand. > > I'm working on a binding for the YARV Ruby VM, and I'm struggling to come up > a with a good interop story with respect to its GC implementation. I have > two options to prevent premature GC of Ruby object pointers: > > 1) Guarantee that the pointers reside on the stack or in registers, > 2) or copy the pointer itself to another static area of memory and register > that address with the GC. > > So, the big question is: is there a way to make #1 a reality, while > operating in the IO monad? > > I can picture something like the following: > > newtype RValue = RValue (Ptr RValue) deriving (Storable) > > withObject :: IO RValue -- e.g. result of some ccall, or some > further transformation thereof > -> (RValue -> IO a) -- the RValue is now on the stack (or in a > register), available for use without worry of premature GC > -> IO a -- the result of computation > > With Haskell being a non-strict language, I understand that there are a lot > of instances where a value could end up on the heap, with a thunk being > passed via stack/registers. For my needs, I'd need some way to guarantee > that the RValues being passed to and from withObject are at all times kept > unwrapped and off the heap, and likewise within the second argument. > > Given my rather limited knowledge of Haskell (I've been programming in > Haskell for about a month now), I think the best I can come up with is the > second option suggested above: > > withObject :: (Ptr RValue -> IO ()) -- e.g. void some_fun(VALUE* out) {...} > -> (RValue -> IO a) -- e.g. do something with `out` derefed > -> IO a > withObject f g = > alloca $ \ptr -> do > rb_gc_register_address ptr -- prevent GC > f ptr -- call wrapped native function > val <- peek ptr -- deref the VALUE* > res <- g val -- pass to function > rb_gc_unregister_address ptr -- clean up > res > > So, while the above would work, it's really, really ugly (IMO). That, and > I'd have to wrap all the native functions so that instead of returning > VALUE, they'd write to some out ptr and return void. And there's the > otherwise unnecessary alloca. > > I hope that was clear enough - any advice would be super duper appreciated! > > I'm assuming that there isn't a way I can get away with using the typical > monadic bind syntax while keeping the RValues off the heap; if I'm wrong, > and I can skip the whole withObject/HOF approach, I'd love to know it! I'm > not (yet) familiar enough with the compiler / language spec to know about > such guarantees, should they exist... > > - Charles > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From jwlato at gmail.com Mon Mar 3 23:46:01 2014 From: jwlato at gmail.com (John Lato) Date: Mon, 3 Mar 2014 15:46:01 -0800 Subject: [Haskell-cafe] Type checking string literal in Haskell? In-Reply-To: <3F7F7F36-94AB-4CB2-A326-1B3BF7A7381D@cs.otago.ac.nz> References: <3F7F7F36-94AB-4CB2-A326-1B3BF7A7381D@cs.otago.ac.nz> Message-ID: Ah yes, I'd missed the "string literal" part. In that case, I agree with Niklas that quasi-quoters seem the best option. Although, they require pretty much the same framework to operate (a custom data type and parser), so once you have a quasi-quoter it's usually easy to implement dynamic checks with the same tooling. On Mon, Mar 3, 2014 at 12:29 PM, Richard A. O'Keefe wrote: > > On 3/03/2014, at 4:59 PM, John Lato wrote: > > > Yes. In Haskell, types are your friends. You should define new types > liberally. > > I believe the original poster was asking about a *static* check. > > Newtypes with "smart constructors" are a good way to plug in > a *dynamic* check, which is valuable but different. > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rrnewton at gmail.com Tue Mar 4 00:22:18 2014 From: rrnewton at gmail.com (Ryan Newton) Date: Mon, 3 Mar 2014 17:22:18 -0700 Subject: [Haskell-cafe] CFP: FHPC 2014: 3rd workshop on Functional High-Performance Computing [w/ICFP] Message-ID: ===================================================================== CALL FOR PAPERS FHPC 2014 The 2nd ACM SIGPLAN Workshop on Functional High-Performance Computing Gothenburg, Sweden September 4, 2014 https://sites.google.com/site/fhpcworkshops/ Co-located with the International Conference on Functional Programming (ICFP 2014) Submission Deadline: Sunday, 15 May, 2014 (anywhere on earth) ===================================================================== The FHPC workshop aims at bringing together researchers exploring uses of functional (or more generally, declarative or high-level) programming technology in application domains where high performance is essential. The aim of the meeting is to enable sharing of results, experiences, and novel ideas about how high-level, declarative specifications of computationally challenging problems can serve as maintainable and portable code that approaches (or even exceeds) the performance of machine-oriented imperative implementations. All aspects of performance critical programming and parallel programming are in-scope for the workshop, irrespective of hardware target. This includes both traditional large-scale scientific computing (HPC), as well as work targeting single node systems with SMPs, GPUs, FPGAs, or embedded processors. It is becoming apparent that radically new and well founded methodologies for programming such systems are required to address their inherent complexity and to reconcile execution performance with programming productivity. Every year, the FHPC workshop has an application area as a theme. Papers touching on this topic are especially encouraged, though all in-scope papers are welcomed. For FHPC 2014, the theme is "Heterogeneous computing". In the systems and parallelism communities, there has been a lot of work on programming systems with CPUs and GPUs (or other mixed parallel architectures), but in the programming languages community this idea has not received as much attention. At their best, high-level languages can have the degrees of flexibility necessary to abstract over platform differences. Proceedings: ============ Accepted papers will be published by the ACM and will appear in the ACM Digital Library. * Submissions due: Sunday, 15 May, 2014 (anywhere on earth) * Author notification: Friday, 15 June, 2014 * Final copy due: Sunday, 22 June, 2014 Submitted papers must be in portable document format (PDF), formatted according to the ACM SIGPLAN style guidelines (2 column, 9pt format). See http://www.sigplan.org/authorInformation.htm for more information and style files. Typical papers are expected to be 8 pages (but up to four additional pages are permitted). Contributions to FHPC 2014 should be submitted via Easychair, at the following URL: * https://www.easychair.org/conferences/?conf=fhpc14 The submission site is now open. The FHPC workshops adhere to the ACM SIGPLAN policies regarding programme committee contributions and republication. Any paper submitted must adhere to ACM SIGPLAN's republication policy. PC member submissions are welcome, but will be reviewed to a higher standard. http://www.sigplan.org/Resources/Policies/Review http://www.sigplan.org/Resources/Policies/Republication Travel Support: =============== Student attendees with accepted papers can apply for a SIGPLAN PAC grant to help cover travel expenses. PAC also offers other support, such as for child-care expenses during the meeting or for travel costs for companions of SIGPLAN members with physical disabilities, as well as for travel from locations outside of North America and Europe. For details on the PAC programme, see its web page (http://www.sigplan.org/PAC.htm). Programme Committee: ==================== Mary Sheeran (co-chair), Chalmers University of Technology, SE Ryan Newton (co-chair), Indiana University, USA Lennart Augustsson, Standard Chartered Bank, UK Jost Berthold, University of Copenhagen, Denmark Guy Blelloch, Carnegie Mellon University, USA Marius Eriksen, Twitter, USA Clemens Grelck, University of Amsterdam, Netherlands Vinod Grover, Nvidia, USA Kevin Hammond, University of St. Andrews, UK Ben Lippmeier, University of New South Wales, Australia Liu (Paul) Hai, Intel, USA Rita Loogen, University of Marburg, Germany Greg Michaelson, Heriot-Watt University, UK Marc Pouzet, ENS Paris, France John Reppy, Univesity of Chicago, USA Tiark Rompf, Oracle Labs and EPFL, Switzerland Satnam Singh, Google, USA Dimitrios Vytiniotis, Microsoft Research, UK General Chairs: ==================== Jost Berthold University of Copenhagen -------------- next part -------------- An HTML attachment was scrubbed... URL: From charles.c.strahan at gmail.com Tue Mar 4 04:05:22 2014 From: charles.c.strahan at gmail.com (Charles Strahan) Date: Mon, 3 Mar 2014 23:05:22 -0500 Subject: [Haskell-cafe] question re: FFI and ensuring unwrapped values are present on stack In-Reply-To: References: Message-ID: Hello Adam, Thanks for the suggestions! I considered ForeignPtrs+finalizers, but I'd like to avoid that due to weak guarantees you cite. I do like the idea about using existentially quantified types to prevent leakage, and might give that more consideration (I can still see some use in allowing users to keep references to globals and such, granted they could just pull them out of the Ruby object graph again whenever they need a reference...). However, I think I have arrived at a design I'm fairly happy with; I've written an 'RBIO' monad that's just a newtype wrapper around (StateT RValue IO a). Now, when the Ruby interpreter calls into my Haskell method definitions, it passes along an array which is then used as the state in my RBIO monad. Now, any other monadic interactions with the Ruby interpreter append the resulting object references to the array, and since the array is placed on Ruby's stack, all of those referenced objects get marked. The end user API ends up looking something along the lines of: newtype RValue = RValue (Ptr RValue) deriving (Eq, Ord, Show, Typeable, Data, Storable) newtype RBIO a = RBIO { runRBIO :: StateT RValue IO a } deriving (Monad, MonadIO) evalRBIO :: RValue -- array (used to prevent GC) -> RBIO a -- RBIO to eval -> IO a defMethod :: RValue -- class -> String -- method name -> (RValue -> [RValue] -> Maybe RValue -> RBIO RValue) -- (self, args, block, result) -> RBIO () rbCall :: RValue -- self -> String -- method name -> [RValue] -- args -> Maybe RValue -- optional Ruby block/lambda -> RBIO RValue I'll follow up when I make the source available - so far, I think it's working out pretty well! -Charles On Mon, Mar 3, 2014 at 6:17 PM, adam vogt wrote: > Hello Charles, > > I don't know what can be done for your option 1, but I have two > suggestions for your option 2: > > Did you consider making RValue a ForeignPtr and adding a FunPtr to > rb_gc_unregister as the finalizer? That will end up being a bit less > restrictive than your "withObject", in exchange for a weaker guarantee > as to when the finalizer actually runs. > > Also you might use the same trick that Control.Monad.ST does to > prevent references from leaking out. In other words, change your > definitions to look more like: > > newtype RValue s = RValue (ForeignPtr ()) > > withObject :: (forall s. RValue s -> IO r) > -> IO r > > With that trick, (withObject return) becomes a type error. > > Regards, > Adam > > > On Mon, Mar 3, 2014 at 12:41 AM, Charles Strahan > wrote: > > Hello all, > > > > This is probably going to be a pretty niche question, but I'm hoping > someone > > here can lend a hand. > > > > I'm working on a binding for the YARV Ruby VM, and I'm struggling to > come up > > a with a good interop story with respect to its GC implementation. I have > > two options to prevent premature GC of Ruby object pointers: > > > > 1) Guarantee that the pointers reside on the stack or in registers, > > 2) or copy the pointer itself to another static area of memory and > register > > that address with the GC. > > > > So, the big question is: is there a way to make #1 a reality, while > > operating in the IO monad? > > > > I can picture something like the following: > > > > newtype RValue = RValue (Ptr RValue) deriving (Storable) > > > > withObject :: IO RValue -- e.g. result of some ccall, or some > > further transformation thereof > > -> (RValue -> IO a) -- the RValue is now on the stack (or in > a > > register), available for use without worry of premature GC > > -> IO a -- the result of computation > > > > With Haskell being a non-strict language, I understand that there are a > lot > > of instances where a value could end up on the heap, with a thunk being > > passed via stack/registers. For my needs, I'd need some way to guarantee > > that the RValues being passed to and from withObject are at all times > kept > > unwrapped and off the heap, and likewise within the second argument. > > > > Given my rather limited knowledge of Haskell (I've been programming in > > Haskell for about a month now), I think the best I can come up with is > the > > second option suggested above: > > > > withObject :: (Ptr RValue -> IO ()) -- e.g. void some_fun(VALUE* out) > {...} > > -> (RValue -> IO a) -- e.g. do something with `out` > derefed > > -> IO a > > withObject f g = > > alloca $ \ptr -> do > > rb_gc_register_address ptr -- prevent GC > > f ptr -- call wrapped native function > > val <- peek ptr -- deref the VALUE* > > res <- g val -- pass to function > > rb_gc_unregister_address ptr -- clean up > > res > > > > So, while the above would work, it's really, really ugly (IMO). That, and > > I'd have to wrap all the native functions so that instead of returning > > VALUE, they'd write to some out ptr and return void. And there's the > > otherwise unnecessary alloca. > > > > I hope that was clear enough - any advice would be super duper > appreciated! > > > > I'm assuming that there isn't a way I can get away with using the typical > > monadic bind syntax while keeping the RValues off the heap; if I'm wrong, > > and I can skip the whole withObject/HOF approach, I'd love to know it! > I'm > > not (yet) familiar enough with the compiler / language spec to know about > > such guarantees, should they exist... > > > > - Charles > > > > _______________________________________________ > > 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 rudy at matela.com.br Tue Mar 4 11:12:34 2014 From: rudy at matela.com.br (Rudy Matela) Date: Tue, 4 Mar 2014 11:12:34 +0000 Subject: [Haskell-cafe] Haskell Cheat Sheet Message-ID: Hello, All, Some time ago, I was looking for a Haskell Cheat Sheet, to help me remember Haskell's syntax and common functions. I've found one, but it was quite long (14 pages), not what I was looking for. So, I've started building a Haskell Cheat Sheet with the most common language features condensed in two pages. It still needs a lot of improvement (and some content). I'm using LaTeX and I've built a "cls" (so it can be used to create Sheets for other languages as well), it is kind of a hack for now. If someone wants to use it as a reference, the first version can be found on [1] and the TeX source can be found on GitHub [2]. I would appreciate help on it: feel free to fork and make pull requests with new additions (or mail me asking for push permissions). Regards, Rudy [1]: https://matela.com.br/pub/cheat-sheets/haskell-ucs-0.1.pdf [2]: https://github.com/rudymatela/ultimate-cheat-sheets From james at mansionfamily.plus.com Tue Mar 4 20:22:14 2014 From: james at mansionfamily.plus.com (james) Date: Tue, 04 Mar 2014 20:22:14 +0000 Subject: [Haskell-cafe] 2013.2 on Win8.1 64 bit Message-ID: <531635F6.9080801@mansionfamily.plus.com> Hi, Does the current latest Haskell Platform install on Win8.1? I don't seem to have luck. I have it installed on my portable, which runs Win7. On my desktop I have 8.1, and the installers asks me whether I want to stop and restart with elevated permissions. It does this however I start it, including from a command prompt running as administrator, or from the 'right click' run as administrator. Continuing then fails to write to Program Files (x86). Any ideas? James From byorgey at seas.upenn.edu Tue Mar 4 21:02:23 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Tue, 4 Mar 2014 16:02:23 -0500 Subject: [Haskell-cafe] Short survey re: use of haskell.org funds to drive development -- please help! Message-ID: <20140304210222.GA20275@seas.upenn.edu> The haskell.org committee is trying to figure out how to use some of its newfound power (the Power of Collecting Money) to best benefit the open-source Haskell community. You can help us by filling out a very short survey (it should only take you about 5 minutes): https://docs.google.com/forms/d/1rEobhHwFpjzPnra9L1TmrozWNFFyAVNPmdUMCcT--3Q/viewform Please do fill it out, especially if you have opinions about what parts of the Haskell open-source world need more work, and could benefit by having some people paid to work on them. Thanks! -Brent, for the haskell.org committee From rendel at informatik.uni-marburg.de Tue Mar 4 21:02:24 2014 From: rendel at informatik.uni-marburg.de (Tillmann Rendel) Date: Tue, 04 Mar 2014 22:02:24 +0100 Subject: [Haskell-cafe] 2013.2 on Win8.1 64 bit In-Reply-To: <531635F6.9080801@mansionfamily.plus.com> References: <531635F6.9080801@mansionfamily.plus.com> Message-ID: <53163F60.8020304@informatik.uni-marburg.de> Hi, James wrote: > Does the current latest Haskell Platform install on Win8.1? Works fine for me on two machines. > Continuing then fails to write to Program Files (x86). I always install to a path like "C:\Haskell\Platform\2013.2.0.0", maybe that works better for you, too. Tillmann PS. I then put a directory symlink from C:\Haskell\Platform\current to C:\Haskell\Platform\2013.2.0.0 so that I can add the C:\Haskell\Platform\current directory to the PATH environment variable and never have to change it again. And I configure all paths in my cabal configuration file to point to C:\Haskell\Platform\current\something, so I get a fresh start when I install a new Haskell platform and update the symlink. So far, this setup has served me well. From karl at karlv.net Tue Mar 4 21:19:24 2014 From: karl at karlv.net (Karl Voelker) Date: Tue, 4 Mar 2014 13:19:24 -0800 Subject: [Haskell-cafe] Haskell Cheat Sheet In-Reply-To: References: Message-ID: <238E0C52-B472-487D-B813-524EC4670EC5@karlv.net> I'm not in a position to make a PR right now, but I did notice that you describe Int as 32 bits, which is not necessarily true. From the Haskell 2010 Report section 6.4: "The finite-precision integer type Int covers at least the range [ ? 229, 229 ? 1]. As Int is an instance of the Bounded class, maxBound and minBound can be used to determine the exact Int range defined by an implementation." -Karl > On Mar 4, 2014, at 3:12 AM, Rudy Matela wrote: > > Hello, All, > > Some time ago, I was looking for a Haskell Cheat Sheet, to help me > remember Haskell's syntax and common functions. I've found one, but > it was quite long (14 pages), not what I was looking for. > > So, I've started building a Haskell Cheat Sheet with the most common > language features condensed in two pages. It still needs a lot of > improvement (and some content). I'm using LaTeX and I've built a > "cls" (so it can be used to create Sheets for other languages as > well), it is kind of a hack for now. > > If someone wants to use it as a reference, the first version can be > found on [1] and the TeX source can be found on GitHub [2]. > > I would appreciate help on it: feel free to fork and make pull > requests with new additions (or mail me asking for push permissions). > > Regards, > Rudy > > [1]: https://matela.com.br/pub/cheat-sheets/haskell-ucs-0.1.pdf > [2]: https://github.com/rudymatela/ultimate-cheat-sheets > _______________________________________________ > 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 james at mansionfamily.plus.com Tue Mar 4 21:20:27 2014 From: james at mansionfamily.plus.com (james) Date: Tue, 04 Mar 2014 21:20:27 +0000 Subject: [Haskell-cafe] 2013.2 on Win8.1 64 bit In-Reply-To: <53163F60.8020304@informatik.uni-marburg.de> References: <531635F6.9080801@mansionfamily.plus.com> <53163F60.8020304@informatik.uni-marburg.de> Message-ID: <5316439B.7060709@mansionfamily.plus.com> > I always install to a path like "C:\Haskell\Platform\2013.2.0.0", maybe that works better for you, too. Yes - thanks! How annoying. From qdunkan at gmail.com Tue Mar 4 21:33:51 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 4 Mar 2014 13:33:51 -0800 Subject: [Haskell-cafe] Haskell Cheat Sheet In-Reply-To: <238E0C52-B472-487D-B813-524EC4670EC5@karlv.net> References: <238E0C52-B472-487D-B813-524EC4670EC5@karlv.net> Message-ID: Indeed on both OS X and 64 bit linux: Prelude> logBase 2 (fromIntegral (maxBound :: Int)) 63.0 On a bit of a tangent, I always assumed that the 30bit Int range was intended for some pointer-tagging hack, and that maybe ocaml did something like that? But in practice GHC always had full 32 or 64 bits. Do other haskell compilers stash something in the Int high bit? On Tue, Mar 4, 2014 at 1:19 PM, Karl Voelker wrote: > I'm not in a position to make a PR right now, but I did notice that you > describe Int as 32 bits, which is not necessarily true. From the Haskell > 2010 Report section 6.4: > > "The finite-precision integer type Int covers at least the range [ ? 229, > 229 ? 1]. As Int is an instance of the Bounded class, maxBound and > minBound can be used to determine the exact Int range defined by an > implementation." > > -Karl > > On Mar 4, 2014, at 3:12 AM, Rudy Matela wrote: > > Hello, All, > > Some time ago, I was looking for a Haskell Cheat Sheet, to help me > remember Haskell's syntax and common functions. I've found one, but > it was quite long (14 pages), not what I was looking for. > > So, I've started building a Haskell Cheat Sheet with the most common > language features condensed in two pages. It still needs a lot of > improvement (and some content). I'm using LaTeX and I've built a > "cls" (so it can be used to create Sheets for other languages as > well), it is kind of a hack for now. > > If someone wants to use it as a reference, the first version can be > found on [1] and the TeX source can be found on GitHub [2]. > > I would appreciate help on it: feel free to fork and make pull > requests with new additions (or mail me asking for push permissions). > > Regards, > Rudy > > [1]: https://matela.com.br/pub/cheat-sheets/haskell-ucs-0.1.pdf > [2]: https://github.com/rudymatela/ultimate-cheat-sheets > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From tyler.huffman at tylerh.org Tue Mar 4 21:47:11 2014 From: tyler.huffman at tylerh.org (Tyler Huffman) Date: Tue, 4 Mar 2014 14:47:11 -0700 Subject: [Haskell-cafe] Short survey re: use of haskell.org funds to drive development -- please help! In-Reply-To: <20140304210222.GA20275@seas.upenn.edu> References: <20140304210222.GA20275@seas.upenn.edu> Message-ID: As a quick aside, it would be very handy if the donation page had a Bitcoin address for sending donations to. Randall Munroe of XKCD has a very unobtrusive Bitcoin address at the bottom of the page, and it seems to net a small income for him: ( http://blockchain.info/address/1NfBXWqseXc9rCBc3Cbbu6HjxYssFUgkH6) It isn't difficult to setup, and it would certainly make it easier for me to donate! Regards, Tyler Huffman On Tue, Mar 4, 2014 at 2:02 PM, Brent Yorgey wrote: > The haskell.org committee is trying to figure out how to use some of > its newfound power (the Power of Collecting Money) to best benefit the > open-source Haskell community. You can help us by filling out a very > short survey (it should only take you about 5 minutes): > > > https://docs.google.com/forms/d/1rEobhHwFpjzPnra9L1TmrozWNFFyAVNPmdUMCcT--3Q/viewform > > Please do fill it out, especially if you have opinions about what > parts of the Haskell open-source world need more work, and could > benefit by having some people paid to work on them. > > Thanks! > > -Brent, for the haskell.org committee > _______________________________________________ > 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 k at ioctl.it Wed Mar 5 21:43:47 2014 From: k at ioctl.it (k at ioctl.it) Date: Wed, 05 Mar 2014 13:43:47 -0800 Subject: [Haskell-cafe] question about show Message-ID: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> Hello! I'm sure this has been answered many times before, but I can't find an explanation for this behavior anywhere. The question I have is a general one regarding 'show'. Why does main = do putStrLn "?" ? ~ runhaskell test.hs ? and: main = do putStrLn $ show "?" ? ~ runhaskell test.hs "\252" Thank you all for an enlightening answer already! Best, k From cgaebel at uwaterloo.ca Wed Mar 5 21:46:48 2014 From: cgaebel at uwaterloo.ca (Clark Gaebel) Date: Wed, 5 Mar 2014 16:46:48 -0500 Subject: [Haskell-cafe] question about show In-Reply-To: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> Message-ID: "Show" is for debug output. It's not a generic "to_string". See this thread [1] from last week for more info. - Clark [1] https://groups.google.com/forum/#!topic/haskell-cafe/32EeI96b1VQ On Wed, Mar 5, 2014 at 4:43 PM, wrote: > Hello! > > I'm sure this has been answered many times before, but I can't find an > explanation for this behavior anywhere. The question I have is a general > one regarding 'show'. Why does > > main = do > putStrLn "?" > > ? ~ runhaskell test.hs > ? > > > and: > > main = do > putStrLn $ show "?" > > ? ~ runhaskell test.hs > "\252" > > Thank you all for an enlightening answer already! > > Best, > > k > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 -------------- next part -------------- An HTML attachment was scrubbed... URL: From k at ioctl.it Wed Mar 5 22:20:25 2014 From: k at ioctl.it (k at ioctl.it) Date: Wed, 05 Mar 2014 14:20:25 -0800 Subject: [Haskell-cafe] question about show In-Reply-To: References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> Message-ID: <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> Okay, it makes somewhat more sense now after reading that thread. But technically, why does show "?" not handle Unicode? Isn't the internal representation of [Char] actually still Unicode, as per [1]http://hackage.haskell.org/package/base-4.6.0.1/docs/Data-Char.html Thanks! k On Wed, Mar 5, 2014, at 01:46 PM, Clark Gaebel wrote: "Show" is for debug output. It's not a generic "to_string". See this thread [1] from last week for more info. - Clark [1] [2]https://groups.google.com/forum/#!topic/haskell-cafe/32EeI96b1VQ On Wed, Mar 5, 2014 at 4:43 PM, <[3]k at ioctl.it> wrote: Hello! I'm sure this has been answered many times before, but I can't find an explanation for this behavior anywhere. The question I have is a general one regarding 'show'. Why does main = do putStrLn "?" ? ~ runhaskell test.hs ? and: main = do putStrLn $ show "?" ? ~ runhaskell test.hs "\252" Thank you all for an enlightening answer already! Best, k _______________________________________________ Haskell-Cafe mailing list [4]Haskell-Cafe at haskell.org [5]http://www.haskell.org/mailman/listinfo/haskell-cafe -- Clark. Key ID : 0x78099922 Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 References 1. http://hackage.haskell.org/package/base-4.6.0.1/docs/Data-Char.html 2. https://groups.google.com/forum/#!topic/haskell-cafe/32EeI96b1VQ 3. mailto:k at ioctl.it 4. mailto:Haskell-Cafe at haskell.org 5. http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Wed Mar 5 22:26:34 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Wed, 5 Mar 2014 17:26:34 -0500 Subject: [Haskell-cafe] question about show In-Reply-To: <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> Message-ID: On Wed, Mar 5, 2014 at 5:20 PM, wrote: > Okay, it makes somewhat more sense now after reading that thread. But > technically, why does > > show "?" > > not handle Unicode? Isn't the internal representation of [Char] actually > still Unicode, as per > Historical reasons, I imagine; Unicode I/O support is still relatively recent in GHC, and I doubt anyone went back and revisited the Show instance for Char. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From dsf at seereason.com Thu Mar 6 03:53:55 2014 From: dsf at seereason.com (David Fox) Date: Wed, 5 Mar 2014 19:53:55 -0800 Subject: [Haskell-cafe] question about show In-Reply-To: <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> Message-ID: Show is supposed to convert its argument into a haskell expression which, when evaluated, returns the same value that was initially passed to show. So by this definition, "\252" is just as correct as "?". There are some Show instances out in the world that do not follow this rule, but they are bad. I'm looking at you, Network.URI! On Wed, Mar 5, 2014 at 2:20 PM, wrote: > Okay, it makes somewhat more sense now after reading that thread. But > technically, why does > > show "?" > > not handle Unicode? Isn't the internal representation of [Char] actually > still Unicode, as per > > http://hackage.haskell.org/package/base-4.6.0.1/docs/Data-Char.html > > Thanks! > > k > > > On Wed, Mar 5, 2014, at 01:46 PM, Clark Gaebel wrote: > > "Show" is for debug output. It's not a generic "to_string". See this > thread [1] from last week for more info. > > - Clark > > [1] https://groups.google.com/forum/#!topic/haskell-cafe/32EeI96b1VQ > > > On Wed, Mar 5, 2014 at 4:43 PM, wrote: > > Hello! > > I'm sure this has been answered many times before, but I can't find an > explanation for this behavior anywhere. The question I have is a general > one regarding 'show'. Why does > > main = do > putStrLn "?" > > ? ~ runhaskell test.hs > ? > > > and: > > main = do > putStrLn $ show "?" > > ? ~ runhaskell test.hs > "\252" > > Thank you all for an enlightening answer already! > > Best, > > k > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > Clark. > > Key ID : 0x78099922 > Fingerprint: B292 493C 51AE F3AB D016 DD04 E5E3 C36F 5534 F907 > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Thu Mar 6 04:21:22 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 06 Mar 2014 04:21:22 +0000 Subject: [Haskell-cafe] question about show In-Reply-To: References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> Message-ID: <5317F7C2.5020709@fuuzetsu.co.uk> On 06/03/14 03:53, David Fox wrote: > Show is supposed to convert its argument into a haskell expression which, > when evaluated, returns the same value that was initially passed to show. > So by this definition, "\252" is just as correct as "?". > > There are some Show instances out in the world that do not follow this > rule, but they are bad. I'm looking at you, Network.URI! > > What about instances where we can't have a reasonable Show that fulfills your requirement? Say, any structure which encapsulates a function. While I agree that ideally Show (or some other typeclass) would be used so that ?read? also works, it's not always possible. If people are expected to follow the implicit Show rules then perhaps base functions such as ?print :: Show a => a -> IO ()? shouldn't be using Show to begin with! It's inconvenient to not make Show instances/make the instances be readable if all the functions that actually let us have a look at the structures use ?Show?. ?print? is great and no one is going to abandon in because one of the 30 fields in their structure happens to be a function. -- Mateusz K. From kc1956 at gmail.com Thu Mar 6 05:07:52 2014 From: kc1956 at gmail.com (KC) Date: Wed, 5 Mar 2014 21:07:52 -0800 Subject: [Haskell-cafe] In Windows, it is better to install development environments outside of the Programs Files folder ... Message-ID: In Windows, it is better to install development environments outside of the Programs Files folder because Windows has protections on that folder plus some other folders. I suppose another alternative is to use the Wubi installer for Ubuntu or is there a better Linux one should be using. :) Oooops! The Wubi installer is not recommended for a computer sporting the Windows 8 logo or using UEFI firmware. -- -- Sent from an expensive device which will be obsolete in a few months! :D Casey -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Thu Mar 6 07:15:53 2014 From: ok at cs.otago.ac.nz (ok at cs.otago.ac.nz) Date: Thu, 6 Mar 2014 20:15:53 +1300 Subject: [Haskell-cafe] question about show In-Reply-To: <5317F7C2.5020709@fuuzetsu.co.uk> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> <5317F7C2.5020709@fuuzetsu.co.uk> Message-ID: <128dd6f6243b7397ad023e421bcc1b61.squirrel@chasm.otago.ac.nz> > On 06/03/14 03:53, David Fox wrote: > What about instances where we can't have a reasonable Show that fulfills > your requirement? Say, any structure which encapsulates a function. Then you write a custom show function that does the best it can. For what it's worth, Smalltalk has historically had thing printOn: stream write thing on stream for people to read thing storeOn: stream write thing on stream so that #readFrom: can read it back and functions (which Smalltalk calls 'blocks') basically defeat both of them. From simon at banquise.net Thu Mar 6 07:17:04 2014 From: simon at banquise.net (Simon Marechal) Date: Thu, 06 Mar 2014 08:17:04 +0100 Subject: [Haskell-cafe] question about show In-Reply-To: <5317F7C2.5020709@fuuzetsu.co.uk> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> <5317F7C2.5020709@fuuzetsu.co.uk> Message-ID: <531820F0.6030701@banquise.net> On 03/06/2014 05:21 AM, Mateusz Kowalczyk wrote: > ?print? is great and no one is going to abandon > in because one of the 30 fields in their structure happens to be a function. I write Pretty instances, it's much easier thanks to all the combinators, it is better suited for human consumption (some libraries have colours), and it's not confusing. Once you have good Pretty instances, you also have great logging and error messages, as opposed to some string that only makes sense to a developer. The only drawback are the orphan instances, if you really need to defined them for a type that's not yours (but you usually don't). From fuuzetsu at fuuzetsu.co.uk Thu Mar 6 07:20:15 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 06 Mar 2014 07:20:15 +0000 Subject: [Haskell-cafe] question about show In-Reply-To: <531820F0.6030701@banquise.net> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> <5317F7C2.5020709@fuuzetsu.co.uk> <531820F0.6030701@banquise.net> Message-ID: <531821AF.5090903@fuuzetsu.co.uk> On 06/03/14 07:17, Simon Marechal wrote: > On 03/06/2014 05:21 AM, Mateusz Kowalczyk wrote: >> ?print? is great and no one is going to abandon >> in because one of the 30 fields in their structure happens to be a function. > > I write Pretty instances, it's much easier thanks to all the > combinators, it is better suited for human consumption (some libraries > have colours), and it's not confusing. Once you have good Pretty > instances, you also have great logging and error messages, as opposed to > some string that only makes sense to a developer. > > The only drawback are the orphan instances, if you really need to > defined them for a type that's not yours (but you usually don't). > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Which package are you using for this? I'd like to add that in some cases (GHC, Haddock, any base libraries) it is not possible to add such a dependency which means that a lot of the time you're stuck with the stock stuff (Show, IsString). -- Mateusz K. From miroslav.karpis at gmail.com Thu Mar 6 09:05:04 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Thu, 6 Mar 2014 10:05:04 +0100 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) Message-ID: Hi, please can you help me with following: I'm unable to install gloss-raster. Output is: dev$ cabal install gloss-raster Resolving dependencies... Configuring gloss-raster-1.8.1.2... Building gloss-raster-1.8.1.2... Preprocessing library gloss-raster-1.8.1.2... [1 of 2] Compiling Graphics.Gloss.Raster.Array ( Graphics/Gloss/Raster/Array.hs, dist/build/Graphics/Gloss/Raster/Array.o ) : Warning: Couldn't figure out LLVM version! Make sure you have installed LLVM ghc: could not execute: opt Failed to install gloss-raster-1.8.1.2 cabal: Error: some packages failed to install: gloss-raster-1.8.1.2 failed during the building phase. The exception was: ExitFailure 1 llvm seems to be installed: $ brew install llvm Warning: llvm-3.3 already installed cheers, m. -------------- next part -------------- An HTML attachment was scrubbed... URL: From cpa at crans.org Thu Mar 6 09:25:11 2014 From: cpa at crans.org (Charles-Pierre Astolfi) Date: Thu, 6 Mar 2014 10:25:11 +0100 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) In-Reply-To: References: Message-ID: Since you use brew, I'll assume you're using osx. I had the same problem a few weeks ago. Here's how I solved it (be advised, it's an ugly hack): 1. Download llvm from the official website (binaries or source). If you download the source compile it. 2. Put all of the files somewhere you find convenient (I use ~/.llvm) 3. Edit ghc.conf (not sure if the name is correct), to add ~/.llvm/bin/llc (in my case) and ~/.llvm/bin/llvm where required. I don't remember the path, somewhere in lib in think. It's the file that is read when running ghc --info It should work afterwards. Note that llvm3.4 is the latest llvm but is not tested on ghc (llvm3.3 is). I use 3.4 w/o issues though. -- Cp On Thu, Mar 6, 2014 at 10:05 AM, Miro Karpis wrote: > Hi, please can you help me with following: I'm unable to install > gloss-raster. Output is: > > > dev$ cabal install gloss-raster > Resolving dependencies... > Configuring gloss-raster-1.8.1.2... > Building gloss-raster-1.8.1.2... > Preprocessing library gloss-raster-1.8.1.2... > [1 of 2] Compiling Graphics.Gloss.Raster.Array ( > Graphics/Gloss/Raster/Array.hs, dist/build/Graphics/Gloss/Raster/Array.o ) > > : > Warning: Couldn't figure out LLVM version! > Make sure you have installed LLVM > ghc: could not execute: opt > Failed to install gloss-raster-1.8.1.2 > cabal: Error: some packages failed to install: > gloss-raster-1.8.1.2 failed during the building phase. The exception was: > ExitFailure 1 > > > llvm seems to be installed: > > $ brew install llvm > Warning: llvm-3.3 already installed > > > cheers, > m. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jmacristovao at gmail.com Thu Mar 6 09:27:25 2014 From: jmacristovao at gmail.com (=?ISO-8859-1?B?Sm/jbyBDcmlzdPN2428=?=) Date: Thu, 6 Mar 2014 09:27:25 +0000 Subject: [Haskell-cafe] Haskell Cheat Sheet In-Reply-To: References: Message-ID: Hi Rudy, Your email gave the motivation to also release my own cheat sheet that I had been compiling for some time now... It is a bit more focused, namely it aims to ilustrate (some of) the differences among typeclasses, namely monoid, semigroup, alt, aplicative, monad, etc. But I agree, there's clear room for improvement over that 14 long pages version - that I hardly call a cheat sheet. http://fundeps.com/tables/FromSemigroupToMonads.pdf http://fundeps.com/posts/cheatsheets/2014-03-04-cheat-sheets/ Cheers, Jo?o 2014-03-04 11:12 GMT+00:00 Rudy Matela : > Hello, All, > > Some time ago, I was looking for a Haskell Cheat Sheet, to help me > remember Haskell's syntax and common functions. I've found one, but > it was quite long (14 pages), not what I was looking for. > > So, I've started building a Haskell Cheat Sheet with the most common > language features condensed in two pages. It still needs a lot of > improvement (and some content). I'm using LaTeX and I've built a > "cls" (so it can be used to create Sheets for other languages as > well), it is kind of a hack for now. > > If someone wants to use it as a reference, the first version can be > found on [1] and the TeX source can be found on GitHub [2]. > > I would appreciate help on it: feel free to fork and make pull > requests with new additions (or mail me asking for push permissions). > > Regards, > Rudy > > [1]: https://matela.com.br/pub/cheat-sheets/haskell-ucs-0.1.pdf > [2]: https://github.com/rudymatela/ultimate-cheat-sheets > _______________________________________________ > 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 simon at banquise.net Thu Mar 6 09:35:44 2014 From: simon at banquise.net (Simon Marechal) Date: Thu, 06 Mar 2014 10:35:44 +0100 Subject: [Haskell-cafe] question about show In-Reply-To: <531821AF.5090903@fuuzetsu.co.uk> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> <5317F7C2.5020709@fuuzetsu.co.uk> <531820F0.6030701@banquise.net> <531821AF.5090903@fuuzetsu.co.uk> Message-ID: <53184170.4030608@banquise.net> On 03/06/2014 08:20 AM, Mateusz Kowalczyk wrote: > Which package are you using for this? I use ansi-wl-pprint because it has colors. Unfortunately, I went overboard with it :) http://lpuppet.banquise.net/images/collision-error.png From k at ioctl.it Thu Mar 6 10:23:54 2014 From: k at ioctl.it (Karsten Gebbert) Date: Thu, 06 Mar 2014 11:23:54 +0100 Subject: [Haskell-cafe] question about show In-Reply-To: <531821AF.5090903@fuuzetsu.co.uk> References: <1394055827.20460.91052881.044C8154@webmail.messagingengine.com> <1394058025.29861.91066773.283E1FC9@webmail.messagingengine.com> <5317F7C2.5020709@fuuzetsu.co.uk> <531820F0.6030701@banquise.net> <531821AF.5090903@fuuzetsu.co.uk> Message-ID: <871tyf62x1.fsf@ioctl.it> > Which package are you using for this? > > I'd like to add that in some cases (GHC, Haddock, any base libraries) it > is not possible to add such a dependency which means that a lot of the > time you're stuck with the stock stuff (Show, IsString). I'd be interested to know too! Anyways, the purpose (and limitations) of Show in this case seem definitely clearer now, so thanks to you all for responding. From the perspective of a beginner, I have to admit that its definitely confusing though. Cheers, k -- Karsten Gebbert http://ioctl.it mob: 0049 (0) 176 61995110 From byorgey at seas.upenn.edu Thu Mar 6 14:08:25 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Thu, 6 Mar 2014 09:08:25 -0500 Subject: [Haskell-cafe] Short survey re: use of haskell.org funds to drive development -- please help! In-Reply-To: References: <20140304210222.GA20275@seas.upenn.edu> Message-ID: <20140306140825.GA20476@seas.upenn.edu> This is certainly something we're aware of; see here for a short explanation of the current status: http://www.reddit.com/r/haskell/comments/1y9e2x/thank_you_for_the_donations_to_haskellorg/cfjg5pm -Brent On Tue, Mar 04, 2014 at 02:47:11PM -0700, Tyler Huffman wrote: > As a quick aside, it would be very handy if the donation page had a Bitcoin > address for sending donations to. Randall Munroe of XKCD has a very > unobtrusive Bitcoin address at the bottom of the page, and it seems to net > a small income for him: ( > http://blockchain.info/address/1NfBXWqseXc9rCBc3Cbbu6HjxYssFUgkH6) > > It isn't difficult to setup, and it would certainly make it easier for me > to donate! > > > Regards, > Tyler Huffman > > > On Tue, Mar 4, 2014 at 2:02 PM, Brent Yorgey wrote: > > > The haskell.org committee is trying to figure out how to use some of > > its newfound power (the Power of Collecting Money) to best benefit the > > open-source Haskell community. You can help us by filling out a very > > short survey (it should only take you about 5 minutes): > > > > > > https://docs.google.com/forms/d/1rEobhHwFpjzPnra9L1TmrozWNFFyAVNPmdUMCcT--3Q/viewform > > > > Please do fill it out, especially if you have opinions about what > > parts of the Haskell open-source world need more work, and could > > benefit by having some people paid to work on them. > > > > Thanks! > > > > -Brent, for the haskell.org committee > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From carter.schonwald at gmail.com Thu Mar 6 14:39:35 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 6 Mar 2014 09:39:35 -0500 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) In-Reply-To: References: Message-ID: You want the ghc settings file. Make sure you point it to the absolute path. On Thursday, March 6, 2014, Charles-Pierre Astolfi wrote: > Since you use brew, I'll assume you're using osx. > > I had the same problem a few weeks ago. Here's how I solved it (be > advised, it's an ugly hack): > 1. Download llvm from the official website (binaries or source). If you > download the source compile it. > 2. Put all of the files somewhere you find convenient (I use ~/.llvm) > 3. Edit ghc.conf (not sure if the name is correct), to add ~/.llvm/bin/llc > (in my case) and ~/.llvm/bin/llvm where required. I don't remember the > path, somewhere in lib in think. It's the file that is read when running > ghc --info > > It should work afterwards. Note that llvm3.4 is the latest llvm but is not > tested on ghc (llvm3.3 is). I use 3.4 w/o issues though. > > -- > Cp > > > On Thu, Mar 6, 2014 at 10:05 AM, Miro Karpis > > wrote: > >> Hi, please can you help me with following: I'm unable to install >> gloss-raster. Output is: >> >> >> dev$ cabal install gloss-raster >> Resolving dependencies... >> Configuring gloss-raster-1.8.1.2... >> Building gloss-raster-1.8.1.2... >> Preprocessing library gloss-raster-1.8.1.2... >> [1 of 2] Compiling Graphics.Gloss.Raster.Array ( >> Graphics/Gloss/Raster/Array.hs, dist/build/Graphics/Gloss/Raster/Array.o ) >> >> : >> Warning: Couldn't figure out LLVM version! >> Make sure you have installed LLVM >> ghc: could not execute: opt >> Failed to install gloss-raster-1.8.1.2 >> cabal: Error: some packages failed to install: >> gloss-raster-1.8.1.2 failed during the building phase. The exception was: >> ExitFailure 1 >> >> >> llvm seems to be installed: >> >> $ brew install llvm >> Warning: llvm-3.3 already installed >> >> >> cheers, >> m. >> >> _______________________________________________ >> 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 miroslav.karpis at gmail.com Thu Mar 6 15:07:41 2014 From: miroslav.karpis at gmail.com (Miroslav Karpis) Date: Thu, 06 Mar 2014 16:07:41 +0100 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) In-Reply-To: References: Message-ID: Thanks,?. But still no luck With ghc settings file you mean the settings file in for example my case: /Library/Frameworks/GHC.framework/Versions/7.6.3-x86_64/usr/lib/ghc-7.6.3/se ttings In the file I can see following lines: ("LLVM llc command", "llc"), ("LLVM opt command", "opt") When I changed llc to "usr/bin/llvm-gcc" nothing happened. So I guess I should edit something else?,?. M. From: Carter Schonwald Date: Thursday, March 6, 2014 3:39 PM To: Charles-Pierre Astolfi Cc: Miroslav Karpis , Haskell Cafe Subject: Re: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) You want the ghc settings file. Make sure you point it to the absolute path. On Thursday, March 6, 2014, Charles-Pierre Astolfi wrote: > Since you use brew, I'll assume you're using osx. > > I had the same problem a few weeks ago. Here's how I solved it (be advised, > it's an ugly hack): > 1. Download llvm from the official website (binaries or source). If you > download the source compile it. > 2. Put all of the files somewhere you find convenient (I use ~/.llvm) > 3. Edit ghc.conf (not sure if the name is correct), to add ~/.llvm/bin/llc (in > my case) and ~/.llvm/bin/llvm where required. I don't remember the path, > somewhere in lib in think. It's the file that is read when running ghc --info > > It should work afterwards. Note that llvm3.4 is the latest llvm but is not > tested on ghc (llvm3.3 is). I use 3.4 w/o issues though. > > -- > Cp > > > On Thu, Mar 6, 2014 at 10:05 AM, Miro Karpis > wrote: >> Hi, please can you help me with following: I'm unable to install >> gloss-raster. Output is: >> >> >> dev$ cabal install gloss-raster >> Resolving dependencies... >> Configuring gloss-raster-1.8.1.2... >> Building gloss-raster-1.8.1.2... >> Preprocessing library gloss-raster-1.8.1.2... >> [1 of 2] Compiling Graphics.Gloss.Raster.Array ( >> Graphics/Gloss/Raster/Array.hs, dist/build/Graphics/Gloss/Raster/Array.o ) >> >> : >> Warning: Couldn't figure out LLVM version! >> Make sure you have installed LLVM >> ghc: could not execute: opt >> Failed to install gloss-raster-1.8.1.2 >> cabal: Error: some packages failed to install: >> gloss-raster-1.8.1.2 failed during the building phase. The exception was: >> ExitFailure 1 >> >> >> llvm seems to be installed: >> >> $ brew install llvm >> Warning: llvm-3.3 already installed >> >> >> cheers, >> m. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Thu Mar 6 15:12:27 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Thu, 6 Mar 2014 10:12:27 -0500 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) In-Reply-To: References: Message-ID: On Thu, Mar 6, 2014 at 10:07 AM, Miroslav Karpis wrote: > In the file I can see following lines: > ("LLVM llc command", "llc"), > ("LLVM opt command", "opt") > > When I changed llc to "usr/bin/llvm-gcc" nothing happened. So I guess I > should edit something else?,?. > llc is not llvm-gcc (and even if it were, the leading / on /usr/bin is not optional). If you have LLVM installed via brew, you are probably looking for /usr/local/bin/llc and /usr/local/bin/opt for those two. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Mar 6 15:30:30 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 6 Mar 2014 10:30:30 -0500 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) In-Reply-To: References: Message-ID: Alternatively you could just remove the fllvm flag from the gloss raster cabal file. I actually spoke with Ben about this, and he insists that the performance different is large enough to be worth only supporting fllvm for his lib. On Thursday, March 6, 2014, Brandon Allbery wrote: > On Thu, Mar 6, 2014 at 10:07 AM, Miroslav Karpis < > miroslav.karpis at gmail.com > > wrote: > >> In the file I can see following lines: >> ("LLVM llc command", "llc"), >> ("LLVM opt command", "opt") >> >> When I changed llc to "usr/bin/llvm-gcc" nothing happened. So I guess I >> should edit something else?,?. >> > > llc is not llvm-gcc (and even if it were, the leading / on /usr/bin is not > optional). If you have LLVM installed via brew, you are probably looking > for /usr/local/bin/llc and /usr/local/bin/opt for those two. > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Thu Mar 6 15:44:59 2014 From: miroslav.karpis at gmail.com (Miroslav Karpis) Date: Thu, 06 Mar 2014 16:44:59 +0100 Subject: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) In-Reply-To: References: Message-ID: Many thanks! It turned out that llc and opt is installed in: usr/local/Cellar/llvm/3.3/bin/ After changing ghc settings, gloss-raster installed correctly ;-) Thanks m. From: Brandon Allbery Date: Thursday, March 6, 2014 4:12 PM To: Miroslav Karpis Cc: Carter Schonwald , Charles-Pierre Astolfi , Haskell Cafe Subject: Re: [Haskell-cafe] gloss-raster: Couldn't figure out LLVM version! (osx 10.8.5) On Thu, Mar 6, 2014 at 10:07 AM, Miroslav Karpis wrote: > In the file I can see following lines: > ("LLVM llc command", "llc"), > ("LLVM opt command", "opt") > > When I changed llc to "usr/bin/llvm-gcc" nothing happened. So I guess I should > edit something else?,?. llc is not llvm-gcc (and even if it were, the leading / on /usr/bin is not optional). If you have LLVM installed via brew, you are probably looking for /usr/local/bin/llc and /usr/local/bin/opt for those two. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From kolar at fit.vutbr.cz Fri Mar 7 06:57:09 2014 From: kolar at fit.vutbr.cz (=?iso-8859-2?b?S29s4fgg?= =?iso-8859-2?b?RHW5YW4=?=) Date: Fri, 07 Mar 2014 07:57:09 +0100 Subject: [Haskell-cafe] Overcome type restrictions? Message-ID: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> Hello Caf?, Is there any way to overcome this other way then by introducing some helper data types etc. etc.? We have: Prelude> :t ([head, last, head, last, head, last]) ([head, last, head, last, head, last]) :: [[a] -> a] Prelude> :t (\(h:t) -> head t) (\(h:t) -> head t) :: [a] -> a Prelude> :t ((\(h:t) -> head t) [head, last, head, last, head, last]) ((\(h:t) -> head t) [head, last, head, last, head, last]) :: [a] -> a But we have an error of infinite type construction for Prelude> :t ((\(h:t) -> h t) [head,tail, head, tail, head, tail]) Well I can overcome this by encoding functions into data types and then performing "conversion" back and forth, nevertheless, is there any way how to overcome this? My real problem is not about head/tail, but head/tail is the simplest way how to explain. Thanks for any references, Du?an From hjgtuyl at chello.nl Fri Mar 7 07:40:36 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Fri, 07 Mar 2014 08:40:36 +0100 Subject: [Haskell-cafe] Overcome type restrictions? In-Reply-To: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> Message-ID: On Fri, 07 Mar 2014 07:57:09 +0100, Kol?? Du?an wrote: : : > But we have an error of infinite type construction for > > Prelude> :t ((\(h:t) -> h t) [head,tail, head, tail, head, tail]) > > Well I can overcome this by encoding functions into data types and then > performing "conversion" back and forth, nevertheless, is there any way > how to overcome this? It seems like you need heterogenous collections[0] Regards, Henk-Jan van Tuyl [0] http://www.haskell.org/haskellwiki/Heterogenous_collections -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From kolar at fit.vutbr.cz Fri Mar 7 08:14:05 2014 From: kolar at fit.vutbr.cz (=?iso-8859-2?b?S29s4fgg?= =?iso-8859-2?b?RHW5YW4=?=) Date: Fri, 07 Mar 2014 09:14:05 +0100 Subject: [Haskell-cafe] Overcome type restrictions? In-Reply-To: References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> Message-ID: <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> Well my fault, the example should have been like this: We have and error of infinite type for Prelude> :t ((\(h:t) -> h t) [head, last, head, last, head, last]) Of course, head and tail are incompatible on type level... Du?an > On Fri, 07 Mar 2014 07:57:09 +0100, Kol?? Du?an wrote: > > : > : >> But we have an error of infinite type construction for >> >> Prelude> :t ((\(h:t) -> h t) [head,tail, head, tail, head, tail]) >> >> Well I can overcome this by encoding functions into data types and >> then performing "conversion" back and forth, nevertheless, is there >> any way how to overcome this? > > It seems like you need heterogenous collections[0] > > Regards, > Henk-Jan van Tuyl > > > [0] http://www.haskell.org/haskellwiki/Heterogenous_collections > > > -- > Folding at home > What if you could share your unused computer power to help find a > cure? In just 5 minutes you can join the world's biggest networked > computer and get us closer sooner. Watch the video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > From vbeffara at ens-lyon.fr Fri Mar 7 08:33:44 2014 From: vbeffara at ens-lyon.fr (Vincent Beffara) Date: Fri, 07 Mar 2014 09:33:44 +0100 Subject: [Haskell-cafe] Overcome type restrictions? References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> Message-ID: > We have and error of infinite type for > Prelude> :t ((\(h:t) -> h t) [head, last, head, last, head, last]) > > Of course, head and tail are incompatible on type level... >> >> It seems like you need heterogenous collections[0] Well the error pops up much earlier than that, see: Prelude> :t (\(h:t) -> h t) >> >> Regards, >> Henk-Jan van Tuyl >> >> >> [0] http://www.haskell.org/haskellwiki/Heterogenous_collections >> >> >> -- >> Folding at home >> What if you could share your unused computer power to help find a >> cure? In just 5 minutes you can join the world's biggest networked >> computer and get us closer sooner. Watch the video. >> http://folding.stanford.edu/ >> >> >> http://Van.Tuyl.eu/ >> http://members.chello.nl/hjgtuyl/tourdemonad.html >> Haskell programming >> -- >> -- | | UMPA - ENS Lyon | M?l: vbeffara at ens-lyon.fr | | Vincent Beffara | 46 all?e d'Italie | T?l: (+33) 4 72 72 85 25 | | | 69364 Lyon Cedex 07 | Fax: (+33) 4 72 72 84 80 | From tob.brandt at googlemail.com Fri Mar 7 09:37:39 2014 From: tob.brandt at googlemail.com (Tobias Brandt) Date: Fri, 7 Mar 2014 10:37:39 +0100 Subject: [Haskell-cafe] Overcome type restrictions? In-Reply-To: <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> Message-ID: The problem is, that the type parameter 'a' of the functions in the list is fixed. You can work around that with RankNTypes: newtype Wrap = Wrap { unwrap :: forall a. [a] -> a } unwrap $ (\(h:t) -> (unwrap h) t) [Wrap head, Wrap last] This specializes the type of the functions at every point of use separately. On 7 March 2014 09:14, Kol?? Du?an wrote: > Well my fault, the example should have been like this: > > We have and error of infinite type for > Prelude> :t ((\(h:t) -> h t) [head, last, head, last, head, last]) > > Of course, head and tail are incompatible on type level... > > Du?an > > > > On Fri, 07 Mar 2014 07:57:09 +0100, Kol?? Du?an >> wrote: >> >> : >> : >> >>> But we have an error of infinite type construction for >>> >>> Prelude> :t ((\(h:t) -> h t) [head,tail, head, tail, head, tail]) >>> >>> Well I can overcome this by encoding functions into data types and then >>> performing "conversion" back and forth, nevertheless, is there any way how >>> to overcome this? >>> >> >> It seems like you need heterogenous collections[0] >> >> Regards, >> Henk-Jan van Tuyl >> >> >> [0] http://www.haskell.org/haskellwiki/Heterogenous_collections >> >> >> -- >> Folding at home >> What if you could share your unused computer power to help find a cure? >> In just 5 minutes you can join the world's biggest networked computer and >> get us closer sooner. Watch the video. >> http://folding.stanford.edu/ >> >> >> http://Van.Tuyl.eu/ >> http://members.chello.nl/hjgtuyl/tourdemonad.html >> Haskell programming >> -- >> >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kolar at fit.vutbr.cz Fri Mar 7 09:39:59 2014 From: kolar at fit.vutbr.cz (=?ISO-8859-2?Q?Du=B9an_Kol=E1=F8?=) Date: Fri, 07 Mar 2014 10:39:59 +0100 Subject: [Haskell-cafe] Overcome type restrictions? In-Reply-To: References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> Message-ID: <531993EF.8040808@fit.vutbr.cz> Yes, it is. the reason is, as I think, the following from application h t we can derive t :: a h :: t1 -> t2 after unification t :: a h :: a -> t2 now (h:t) t :: [e] h :: e merging t:: a ~ [e] -> a == [e] and it follows h :: [e] -> t2 h :: e which would give infinite type for unification. Nevertheless, from the example it is obvious, that for particular case, it is fine. We can explicitly type: h :: [a] -> a t :: [[a] -> a] for (h:t) it is OK h :: e ~ [a]->a and t :: [e] ~ [[a]->a] e.g. e == [a]->a and h :: e and t ::[e], which is fine Now, h t h :: [a] -> a t :: [[b] -> b] and it is fine, as type a == [b] -> b of course, monomorphism restriction would lead to infinite type again. So, the question is, how for the particular case force the inference this way, to break the restriction... Du?an On 03/07/2014 09:33 AM, Vincent Beffara wrote: >> We have and error of infinite type for >> Prelude> :t ((\(h:t) -> h t) [head, last, head, last, head, last]) >> >> Of course, head and tail are incompatible on type level... >>> It seems like you need heterogenous collections[0] > Well the error pops up much earlier than that, see: > > Prelude> :t (\(h:t) -> h t) > >>> Regards, >>> Henk-Jan van Tuyl >>> >>> >>> [0] http://www.haskell.org/haskellwiki/Heterogenous_collections >>> >>> >>> -- >>> Folding at home >>> What if you could share your unused computer power to help find a >>> cure? In just 5 minutes you can join the world's biggest networked >>> computer and get us closer sooner. Watch the video. >>> http://folding.stanford.edu/ >>> >>> >>> http://Van.Tuyl.eu/ >>> http://members.chello.nl/hjgtuyl/tourdemonad.html >>> Haskell programming >>> -- >>> From kolar at fit.vutbr.cz Fri Mar 7 09:43:58 2014 From: kolar at fit.vutbr.cz (=?ISO-8859-2?Q?Du=B9an_Kol=E1=F8?=) Date: Fri, 07 Mar 2014 10:43:58 +0100 Subject: [Haskell-cafe] Overcome type restrictions? In-Reply-To: References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> Message-ID: <531994DE.3050701@fit.vutbr.cz> Thanks. I think this is the simplest solution. Du?an On 03/07/2014 10:37 AM, Tobias Brandt wrote: > The problem is, that the type parameter 'a' of the functions in the > list is fixed. You can work around that with RankNTypes: > > newtype Wrap = Wrap { unwrap :: forall a. [a] -> a } > > unwrap $ (\(h:t) -> (unwrap h) t) [Wrap head, Wrap last] > > This specializes the type of the functions at every point of use > separately. > > > On 7 March 2014 09:14, Kol?? Du?an > wrote: > > Well my fault, the example should have been like this: > > We have and error of infinite type for > Prelude> :t ((\(h:t) -> h t) [head, last, head, last, head, last]) > > Of course, head and tail are incompatible on type level... > > Du?an > > > > On Fri, 07 Mar 2014 07:57:09 +0100, Kol?? Du?an > > wrote: > > : > : > > But we have an error of infinite type construction for > > Prelude> :t ((\(h:t) -> h t) [head,tail, head, tail, head, > tail]) > > Well I can overcome this by encoding functions into data > types and then performing "conversion" back and forth, > nevertheless, is there any way how to overcome this? > > > It seems like you need heterogenous collections[0] > > Regards, > Henk-Jan van Tuyl > > > [0] http://www.haskell.org/haskellwiki/Heterogenous_collections > > > -- > Folding at home > What if you could share your unused computer power to help > find a cure? In just 5 minutes you can join the world's > biggest networked computer and get us closer sooner. Watch the > video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From kumoyuki at gmail.com Fri Mar 7 10:05:24 2014 From: kumoyuki at gmail.com (David Rush) Date: Fri, 7 Mar 2014 10:05:24 +0000 (UTC) Subject: [Haskell-cafe] SystemF, universal quantification, and rigid type variables Message-ID: In short, I'm trying to decide if there is a real difference between the types: (forall a.a) -> b a -> b and frankly, I'm not seeing a difference. But ghc apparently does *SystemF.Tests> :t ((\u (x::forall a. a) y -> u x y) (\x y -> y)) True :1:49: Couldn't match type `a' with `Bool' `a' is a rigid type variable bound by a type expected by the context: a at :1:1 In the second argument of `\ u (x :: forall a. a) y -> u x y', namely `True' In the expression: ((\ u (x :: forall a. a) y -> u x y) (\ x y -> y)) True *SystemF.Tests> Since this is a 'rigid type variable' complaint, I am inclined to think that this is a limitation of ghc, rather than a particular issue with the logic of System F. I'd actually love to be wrong. Is there an actual difference between the types? - david rush From r.koot at uu.nl Fri Mar 7 10:35:05 2014 From: r.koot at uu.nl (Ruud Koot) Date: Fri, 7 Mar 2014 11:35:05 +0100 Subject: [Haskell-cafe] SystemF, universal quantification, and rigid type variables In-Reply-To: References: Message-ID: In a strict language (forall a.a) -> b and a -> b would be "the same" in the sense that they are both uninhabited and thus isomorphic in a trivial sense. However isomorphic types are generally not considered identical by a programming language. In a lazy language these types are inhabited, but by a different number of terms and can thus not be isomorphic in the strict sense: f : a -> b is only inhabited by "undefined" and "\x -> undefined" f : (forall. a) ->b is also inhabited by \x -> x, although calling it with any argument other than undefined will prove difficult. Ruud On Fri, Mar 7, 2014 at 11:05 AM, David Rush wrote: > In short, I'm trying to decide if there is a real difference between the > types: > > (forall a.a) -> b > a -> b > > and frankly, I'm not seeing a difference. But ghc apparently does > > *SystemF.Tests> :t ((\u (x::forall a. a) y -> u x y) (\x y -> y)) True > > :1:49: > Couldn't match type `a' with `Bool' > `a' is a rigid type variable bound by > a type expected by the context: a at :1:1 > In the second argument of `\ u (x :: forall a. a) y > -> u x y', namely > `True' > In the expression: > ((\ u (x :: forall a. a) y -> u x y) (\ x y -> y)) True > *SystemF.Tests> > > Since this is a 'rigid type variable' complaint, I am inclined to think that > this is a limitation of ghc, rather than a particular issue with the logic of > System F. I'd actually love to be wrong. Is there an actual difference > between the types? > > - david rush > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From nickolay.kudasov at gmail.com Fri Mar 7 10:37:20 2014 From: nickolay.kudasov at gmail.com (Nickolay Kudasov) Date: Fri, 7 Mar 2014 14:37:20 +0400 Subject: [Haskell-cafe] SystemF, universal quantification, and rigid type variables In-Reply-To: References: Message-ID: Hi David, There certainly is a difference between those types. Let's reveal their full form: - forall b. (forall a. a) -> b - forall a b. a -> b The first one takes a polymorphic value of type (forall a. a). This means we could instantiate it to be of any type (e.g. b). The second one takes a value of any type (not the value of a polymorphic type). Thus you cannot apply function with first type to True, because True has a concrete type Bool and is not polymorphic. Consider another example: - forall b. Num b => (forall a. Num a => a) -> b - forall a b. (Num a, Num b) => a -> b Here in first case function takes a polymorphic numeric value and returns another, you could define it to be f x = x + 1. But this function can only be applied to a polymorphic value (forall a. Num a => a). E.g. f (fromIntegral 2). In second case you already have some numeric value and, unfortunately, you cannot use it: you have no way to convert Num types between each other. Best regards, Nick 2014-03-07 14:05 GMT+04:00 David Rush : > In short, I'm trying to decide if there is a real difference between the > types: > > (forall a.a) -> b > a -> b > > and frankly, I'm not seeing a difference. But ghc apparently does > > *SystemF.Tests> :t ((\u (x::forall a. a) y -> u x y) (\x y -> y)) True > > :1:49: > Couldn't match type `a' with `Bool' > `a' is a rigid type variable bound by > a type expected by the context: a at :1:1 > In the second argument of `\ u (x :: forall a. a) y > -> u x y', namely > `True' > In the expression: > ((\ u (x :: forall a. a) y -> u x y) (\ x y -> y)) True > *SystemF.Tests> > > Since this is a 'rigid type variable' complaint, I am inclined to think > that > this is a limitation of ghc, rather than a particular issue with the logic > of > System F. I'd actually love to be wrong. Is there an actual difference > between the types? > > - david rush > > _______________________________________________ > 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 kumoyuki at gmail.com Fri Mar 7 12:01:12 2014 From: kumoyuki at gmail.com (David Rush) Date: Fri, 7 Mar 2014 12:01:12 +0000 (UTC) Subject: [Haskell-cafe] =?utf-8?q?SystemF=2C_universal_quantification=2C?= =?utf-8?q?=09and_rigid_type_variables?= References: Message-ID: So I posted: > In short, I'm trying to decide if there is a real difference between the > types: > > (forall a.a) -> b > a -> b > > and frankly, I'm not seeing a difference... I'd actually love to be wrong. > Is there an actual difference between the types? And Ruud Koot and Nikolay Kudasov both told me: > YES. Thanks, y'all. That actually means I was doing it right :) - d From kolar at fit.vutbr.cz Fri Mar 7 12:17:01 2014 From: kolar at fit.vutbr.cz (=?ISO-8859-2?Q?Du=B9an_Kol=E1=F8?=) Date: Fri, 07 Mar 2014 13:17:01 +0100 Subject: [Haskell-cafe] Overcome type restrictions? In-Reply-To: References: <20140307075709.13691abxilc4rj5x@email.fit.vutbr.cz> <20140307091405.174162451hbtk53h@email.fit.vutbr.cz> Message-ID: <5319B8BD.4070900@fit.vutbr.cz> Well, for the case, we even do not need RankNTypes, as the type of the list is known, so newtype Wrap = Wrap { unwrap :: [Wrap] -> Wrap } wself (h:t) = unwr $ unwr h t will work, which is not too far from encoding function into data :-) This solution saves space, of course. Best regards, Du?an On 03/07/2014 10:35 AM, Tobias Brandt wrote: > The problem is, that the type parameter 'a' of the functions in the > list is fixed. You can work around that with RankNTypes: > > newtype Wrap = Wrap { unwrap :: forall a. [a] -> a } > > unwrap $ (\(h:t) -> (unwrap h) t) [Wrap head, Wrap last] > > This specializes the type of the functions at every point of use > separately. > > > On 7 March 2014 09:14, Kol?? Du?an > wrote: > > Well my fault, the example should have been like this: > > We have and error of infinite type for > Prelude> :t ((\(h:t) -> h t) [head, last, head, last, head, last]) > > Of course, head and tail are incompatible on type level... > > Du?an > > > > On Fri, 07 Mar 2014 07:57:09 +0100, Kol?? Du?an > > wrote: > > : > : > > But we have an error of infinite type construction for > > Prelude> :t ((\(h:t) -> h t) [head,tail, head, tail, head, > tail]) > > Well I can overcome this by encoding functions into data > types and then performing "conversion" back and forth, > nevertheless, is there any way how to overcome this? > > > It seems like you need heterogenous collections[0] > > Regards, > Henk-Jan van Tuyl > > > [0] http://www.haskell.org/haskellwiki/Heterogenous_collections > > > -- > Folding at home > What if you could share your unused computer power to help > find a cure? In just 5 minutes you can join the world's > biggest networked computer and get us closer sooner. Watch the > video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From rudy at matela.com.br Fri Mar 7 19:53:32 2014 From: rudy at matela.com.br (Rudy Matela) Date: Fri, 7 Mar 2014 19:53:32 +0000 Subject: [Haskell-cafe] Haskell Cheat Sheet In-Reply-To: References: Message-ID: Hi, All, New version 0.3, with suggestions and patches from some people applied. https://matela.com.br/pub/cheat-sheets/haskell-ucs-0.3.pdf https://github.com/rudymatela/ultimate-cheat-sheets Regards, Rudy On Thu, Mar 6, 2014 at 9:27 AM, Jo?o Crist?v?o wrote: > Hi Rudy, > > Your email gave the motivation to also release my own cheat sheet that I had > been compiling for some time now... > It is a bit more focused, namely it aims to ilustrate (some of) the > differences among typeclasses, namely monoid, semigroup, alt, aplicative, > monad, etc. > > But I agree, there's clear room for improvement over that 14 long pages > version - that I hardly call a cheat sheet. > > http://fundeps.com/tables/FromSemigroupToMonads.pdf > > http://fundeps.com/posts/cheatsheets/2014-03-04-cheat-sheets/ > > Cheers, > Jo?o > > > 2014-03-04 11:12 GMT+00:00 Rudy Matela : >> >> Hello, All, >> >> Some time ago, I was looking for a Haskell Cheat Sheet, to help me >> remember Haskell's syntax and common functions. I've found one, but >> it was quite long (14 pages), not what I was looking for. >> >> So, I've started building a Haskell Cheat Sheet with the most common >> language features condensed in two pages. It still needs a lot of >> improvement (and some content). I'm using LaTeX and I've built a >> "cls" (so it can be used to create Sheets for other languages as >> well), it is kind of a hack for now. >> >> If someone wants to use it as a reference, the first version can be >> found on [1] and the TeX source can be found on GitHub [2]. >> >> I would appreciate help on it: feel free to fork and make pull >> requests with new additions (or mail me asking for push permissions). >> >> Regards, >> Rudy >> >> [1]: https://matela.com.br/pub/cheat-sheets/haskell-ucs-0.1.pdf >> [2]: https://github.com/rudymatela/ultimate-cheat-sheets >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > From corentin.dupont at gmail.com Sat Mar 8 20:01:23 2014 From: corentin.dupont at gmail.com (Corentin Dupont) Date: Sat, 8 Mar 2014 21:01:23 +0100 Subject: [Haskell-cafe] Fwd: facebook exception In-Reply-To: References: Message-ID: Hi, I am posting here in case one of you got this error. It's an old bug in my game that I was never able to solve. I use happstack-authenticate, but when I select facebook to login with, I get: FacebookException {fbeType = " ()", fbeMessage = ""} However, it seems well configured. I put: facebookAuth = Credentials {appName = "Nomyx", appId = "161007670738608", appSecret = } On the facebook website, I have the application configured: application Id: 161007670738608 secret key: Display Name: Nomyx NameSpace: nomyx-app App Domains: www.nomyx.net URL: http://www.nomyx.net:8000/ Do you have any hints? Thanks a lot!! Corentin -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Sat Mar 8 21:47:33 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Sat, 8 Mar 2014 23:47:33 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs Message-ID: Does anyone have any example alex+happy programs that uses location location annotated tokens and location information of token while reporting parse errors? I already wrote lexer and my function type is something like: > runLexer :: String -> [(Token, AlexPosn)] where AlexPosn type contains location information. But I have no idea how can I use that in happy to parse and use location information in parse error messages. There are lots of examples in interwebs but as far as I can see none of them works on location-annotated tokens. Thanks.. --- ?mer Sinan A?acan http://osa1.net From fuuzetsu at fuuzetsu.co.uk Sun Mar 9 07:49:02 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sun, 09 Mar 2014 07:49:02 +0000 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: Message-ID: <531C1CEE.5030202@fuuzetsu.co.uk> On 08/03/14 21:47, ?mer Sinan A?acan wrote: > Does anyone have any example alex+happy programs that uses location > location annotated tokens and location information of token while > reporting parse errors? > > I already wrote lexer and my function type is something like: > >> runLexer :: String -> [(Token, AlexPosn)] > > where AlexPosn type contains location information. But I have no idea > how can I use that in happy to parse and use location information in > parse error messages. There are lots of examples in interwebs but as > far as I can see none of them works on location-annotated tokens. > > Thanks.. > > --- > ?mer Sinan A?acan > http://osa1.net > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > I believe GHC does this. See the compiler/parser directory of the GHC repo. Perhaps it's not the most lightweight example but it's the only readily available one that I can think of. -- Mateusz K. From mle+hs at mega-nerd.com Sun Mar 9 08:47:07 2014 From: mle+hs at mega-nerd.com (Erik de Castro Lopo) Date: Sun, 9 Mar 2014 19:47:07 +1100 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: Message-ID: <20140309194707.51841d3947920a369c75872d@mega-nerd.com> ?mer Sinan A?acan wrote: > Does anyone have any example alex+happy programs that uses location > location annotated tokens and location information of token while > reporting parse errors? > > I already wrote lexer and my function type is something like: > > > runLexer :: String -> [(Token, AlexPosn)] > > where AlexPosn type contains location information. But I have no idea > how can I use that in happy to parse and use location information in > parse error messages. There are lots of examples in interwebs but as > far as I can see none of them works on location-annotated tokens. Also look at the DDC codebase: https://github.com/DDCSF/ddc Erik -- ---------------------------------------------------------------------- Erik de Castro Lopo http://www.mega-nerd.com/ From omeragacan at gmail.com Sun Mar 9 11:15:02 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Sun, 9 Mar 2014 13:15:02 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: <531C1CEE.5030202@fuuzetsu.co.uk> References: <531C1CEE.5030202@fuuzetsu.co.uk> Message-ID: I think GHC uses alex+happy in very different way than explained in the docs.. For example it doesn't use "posn", "monadUserState" etc. wrappers as explained in alex documentations. I also can't figure out how does it keep track of token locations.. I guess It's just too complicated for me to understand without spending several hours. --- ?mer Sinan A?acan http://osa1.net 2014-03-09 9:49 GMT+02:00 Mateusz Kowalczyk : > On 08/03/14 21:47, ?mer Sinan A?acan wrote: >> Does anyone have any example alex+happy programs that uses location >> location annotated tokens and location information of token while >> reporting parse errors? >> >> I already wrote lexer and my function type is something like: >> >>> runLexer :: String -> [(Token, AlexPosn)] >> >> where AlexPosn type contains location information. But I have no idea >> how can I use that in happy to parse and use location information in >> parse error messages. There are lots of examples in interwebs but as >> far as I can see none of them works on location-annotated tokens. >> >> Thanks.. >> >> --- >> ?mer Sinan A?acan >> http://osa1.net >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > I believe GHC does this. See the compiler/parser directory of the GHC > repo. Perhaps it's not the most lightweight example but it's the only > readily available one that I can think of. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From omeragacan at gmail.com Sun Mar 9 11:31:38 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Sun, 9 Mar 2014 13:31:38 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: <20140309194707.51841d3947920a369c75872d@mega-nerd.com> References: <20140309194707.51841d3947920a369c75872d@mega-nerd.com> Message-ID: I don't think DDC uses alex/happy for parsing: ``` ? ddc git:(master) find . -iname "*.y" ? ddc git:(master) find . -iname "*.x" ``` and there are some Parsec parsers in `packages/ddc-core/DDC/Core/Parser`. --- ?mer Sinan A?acan http://osa1.net 2014-03-09 10:47 GMT+02:00 Erik de Castro Lopo : > ?mer Sinan A?acan wrote: > >> Does anyone have any example alex+happy programs that uses location >> location annotated tokens and location information of token while >> reporting parse errors? >> >> I already wrote lexer and my function type is something like: >> >> > runLexer :: String -> [(Token, AlexPosn)] >> >> where AlexPosn type contains location information. But I have no idea >> how can I use that in happy to parse and use location information in >> parse error messages. There are lots of examples in interwebs but as >> far as I can see none of them works on location-annotated tokens. > > Also look at the DDC codebase: > > https://github.com/DDCSF/ddc > > Erik > -- > ---------------------------------------------------------------------- > Erik de Castro Lopo > http://www.mega-nerd.com/ > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From fuuzetsu at fuuzetsu.co.uk Sun Mar 9 11:44:54 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sun, 09 Mar 2014 11:44:54 +0000 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> Message-ID: <531C5436.9000904@fuuzetsu.co.uk> On 09/03/14 11:15, ?mer Sinan A?acan wrote: > I think GHC uses alex+happy in very different way than explained in > the docs.. For example it doesn't use "posn", "monadUserState" etc. > wrappers as explained in alex documentations. I also can't figure out > how does it keep track of token locations.. I guess It's just too > complicated for me to understand without spending several hours. > > --- > ?mer Sinan A?acan > http://osa1.net It doesn't use the wrappers provided, it instead uses its own data structures to do what the wrappers let you do and more. You can look for the data types defined in those modules to try and shed some light on how it's all done. I did mention it's not the most lightweight example ;) -- Mateusz K. From omeragacan at gmail.com Sun Mar 9 16:45:26 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Sun, 9 Mar 2014 18:45:26 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: <531C5436.9000904@fuuzetsu.co.uk> References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Ha! I finally managed to use any kinds of tokens in Happy parsers ... Will post the code soon. --- ?mer Sinan A?acan http://osa1.net 2014-03-09 13:44 GMT+02:00 Mateusz Kowalczyk : > On 09/03/14 11:15, ?mer Sinan A?acan wrote: >> I think GHC uses alex+happy in very different way than explained in >> the docs.. For example it doesn't use "posn", "monadUserState" etc. >> wrappers as explained in alex documentations. I also can't figure out >> how does it keep track of token locations.. I guess It's just too >> complicated for me to understand without spending several hours. >> >> --- >> ?mer Sinan A?acan >> http://osa1.net > > It doesn't use the wrappers provided, it instead uses its own data > structures to do what the wrappers let you do and more. You can look for > the data types defined in those modules to try and shed some light on > how it's all done. I did mention it's not the most lightweight example ;) > > -- > Mateusz K. From omeragacan at gmail.com Sun Mar 9 19:18:24 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Sun, 9 Mar 2014 21:18:24 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Okay guys, I finally did it and it turned out that Happy is actually very easy to use .. only problem is that IMO documentation is not great(or maybe I didn't pay enough attention reading it .. reading docs is boring). Anyway, here's a short explanation(link for code is also below): Let's say you already wrote the lexer that returns `[TokPos]` where data Token = ... your tokens ... type TokPos = (Token, AlexPosn) (AlexPosn contains location information) and after telling Happy your token types, all you need to do is to declare how tokens used in left-hand side of productions are matched against tokens. Let's say I have this tokens: data Token = A String | B Int | C I'll need to add this token declarations in Happy file: %token a { (A $$, _) } b { (B $$, _) } c { (C, _) } notice how I'm using ordinary pattern syntax. I didn't know this part before. After that I can use a, b and c in left-hand side parts of productions, like: Exp : a b { SomeConstructor $1 $2 } | c { SomeOtherConstructor } and that's it. I hope that helps somebody. Working code: * Lexer(Alex): https://github.com/osa1/minCaml.hs/blob/master/src/Lexer.x * Parser(Happy): https://github.com/osa1/minCaml.hs/blob/master/src/Parser.y --- ?mer Sinan A?acan http://osa1.net 2014-03-09 18:45 GMT+02:00 ?mer Sinan A?acan : > Ha! I finally managed to use any kinds of tokens in Happy parsers ... > Will post the code soon. > > --- > ?mer Sinan A?acan > http://osa1.net > > > 2014-03-09 13:44 GMT+02:00 Mateusz Kowalczyk : >> On 09/03/14 11:15, ?mer Sinan A?acan wrote: >>> I think GHC uses alex+happy in very different way than explained in >>> the docs.. For example it doesn't use "posn", "monadUserState" etc. >>> wrappers as explained in alex documentations. I also can't figure out >>> how does it keep track of token locations.. I guess It's just too >>> complicated for me to understand without spending several hours. >>> >>> --- >>> ?mer Sinan A?acan >>> http://osa1.net >> >> It doesn't use the wrappers provided, it instead uses its own data >> structures to do what the wrappers let you do and more. You can look for >> the data types defined in those modules to try and shed some light on >> how it's all done. I did mention it's not the most lightweight example ;) >> >> -- >> Mateusz K. From stephen.tetley at gmail.com Sun Mar 9 20:47:53 2014 From: stephen.tetley at gmail.com (Stephen Tetley) Date: Sun, 9 Mar 2014 20:47:53 +0000 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Hi ?mer Are you rewriting Eijiro Sumii's MinCaml in Haskell? I did the same a couple of years ago, though I used Parsec for parsing and only implemented the higher transformations (beta reduction, inlining, constant folding, useless variable elimination). As I have no access to a Sparc machine, I didn't go as far as closure conversion and code generation. The code was only for my personal learning as MinCaml was the nicest / smallest real compiler I could find. Code is in my Google repository - it might be useful for reference, obviously for a learning exercise you'd want to do-it-yourself: https://code.google.com/p/copperbox/source/browse/ >> trunk >> compiler >> HMinCaml Best wishes Stephen On 9 March 2014 19:18, ?mer Sinan A?acan wrote: [Snip] > > Working code: > * Lexer(Alex): https://github.com/osa1/minCaml.hs/blob/master/src/Lexer.x > * Parser(Happy): https://github.com/osa1/minCaml.hs/blob/master/src/Parser.y > From omeragacan at gmail.com Sun Mar 9 22:07:20 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 10 Mar 2014 00:07:20 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Hi Stephen, > Are you rewriting Eijiro Sumii's MinCaml in Haskell? Yes! > I did the same a couple of years ago, though I used Parsec for parsing > and only implemented the higher transformations (beta reduction, > inlining, constant folding, useless variable elimination). As I have > no access to a Sparc machine, I didn't go as far as closure conversion > and code generation. At first I also used Parsec, but I wasn't happy with the parser. The original grammar has 4 left-recursive productions and I had to manually eliminate them(I guess you also did that). But after that the grammar was still not LL(1) so I had to place some `try`s very carefully. It worked fine, but resulting parser was parsing nested lets in exponential time. For example, this program took about a minute to parse: https://github.com/esumii/min-caml/blob/master/test/spill.ml . So I rewrote it in Happy and now it works great. (I still need to work on error messages though. Also, I did not resolve all ambiguities so Happy reports lots of shift-reduce conficts) I guess that problem with Parsec parser could also be fixed but I just prefer implementation to be similar to original definitions. (also, I always wanted to learn Happy since GHC is using it and I want to start contributing to GHC in the future) I love starting with some tutorials and then improving final product by adding more features etc. I started learning Haskell 3 years ago with "write yourself a Scheme" tutorial and then I added continuations/call-cc, exceptions and several other features. It helped me a lot and it was very fun way to learn. I'm currently planning to do something similar, I want to implement more features once I have compiler for the original language working. I also don't have a Sparc machine, so I'm planning to compile to x86-64. I only know basics of x86-64, so I want to first compile to C. After I have that working correctly, by looking to generated ASM from the generated C sources, I want to implement x86-64 code generator. So I also aim to learn x86-64 assembly. At some point I also want to implement a garbage collector.. AFAIK no heap allocation is done in the original language, so I may need some more data types.. Maybe sum-types or records like in Haskell. > The code was only for my personal learning as MinCaml was the nicest / > smallest real compiler I could find. Code is in my Google repository - > it might be useful for reference, obviously for a learning exercise > you'd want to do-it-yourself: > > https://code.google.com/p/copperbox/source/browse/ >> trunk >> > compiler >> HMinCaml Thanks! I may give it a look if I get stuck at some point. --- ?mer Sinan A?acan http://osa1.net From sean at functionaljobs.com Mon Mar 10 06:00:06 2014 From: sean at functionaljobs.com (Functional Jobs) Date: Mon, 10 Mar 2014 02:00:06 -0400 Subject: [Haskell-cafe] New Functional Programming Job Opportunities Message-ID: <531d54ef823ae@functionaljobs.com> Here are some functional programming job opportunities that were posted recently: Developer at Northwestern University http://functionaljobs.com/jobs/8690-developer-at-northwestern-university Cheers, Sean Murphy FunctionalJobs.com From fuuzetsu at fuuzetsu.co.uk Mon Mar 10 11:01:14 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 10 Mar 2014 11:01:14 +0000 Subject: [Haskell-cafe] Extensible Binary-Meta-Language libraries Message-ID: <531D9B7A.5040202@fuuzetsu.co.uk> Greetings, Does anyone know if there are any libraries to work with Extensible Binary Meta-Language (used by Matroska)? I find mentions of such a thing in IRC logs from years ago by a person going by ?ksf? but he/she has disappeared from IRC about 5 weeks ago and I can not find their e-mail address. Is anyone interested in such a library? I am planning to implement it anyway but it'd be nice to know if there's any interest. Thanks -- Mateusz K. From semen at trygub.com Mon Mar 10 13:11:25 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Mon, 10 Mar 2014 13:11:25 +0000 Subject: [Haskell-cafe] Read instance for constructors? Message-ID: <20140310131125.GA53715@inanna.trygub.com> Dear Haskell-cafe, When deriving (Read), only values can be read in. If one wants to be able to read in constructors, too, is there an easy way out? E.g., the code below works, but the extra book-keeping f "A" = A ... is unpleasant ? perhaps there's a simpler solution? {-# LANGUAGE FlexibleInstances #-} data D = A Int | B Int deriving (Show,Read) instance Read (Int -> D) where readsPrec = \_ s -> [(f s,"")] where f "A" = A f "B" = B f x = error $ "Invalid constructor " ++ x main = do let x = read "A 1" :: D print x let g s = read s :: (Int -> D) print $ g "B" 2 print $ g "C" 3 Many thanks in advance, Semen -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From haskell at nand.wakku.to Mon Mar 10 13:54:14 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Mon, 10 Mar 2014 14:54:14 +0100 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140310131125.GA53715@inanna.trygub.com> References: <20140310131125.GA53715@inanna.trygub.com> Message-ID: <20140310145414.GA22863@nanodesu.talocan.mine.nu> On Mon, 10 Mar 2014 13:11:25 +0000, Semen Trygubenko / ????? ?????????? wrote: > Dear Haskell-cafe, > > When deriving (Read), only values can be read in. > If one wants to be able to read in constructors, too, is there an easy way out? > E.g., the code below works, but the extra book-keeping > > f "A" = A > ... > > is unpleasant ? perhaps there's a simpler solution? You can derive Data using the DeriveDataTypeable extension and then use the toConstr :: Data a => a -> Constr method to obtain the Constr (which has a Show instance that in this case just returns "A", "B" etc.) From haskell at nand.wakku.to Mon Mar 10 13:59:36 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Mon, 10 Mar 2014 14:59:36 +0100 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140310145414.GA22863@nanodesu.talocan.mine.nu> References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> Message-ID: <20140310145936.GA22969@nanodesu.talocan.mine.nu> On Mon, 10 Mar 2014 14:54:14 +0100, Niklas Haas wrote: > You can derive Data using the DeriveDataTypeable extension and then use > the toConstr :: Data a => a -> Constr method to obtain the Constr (which > has a Show instance that in this case just returns "A", "B" etc.) Oops, you are asking about the other direction. Well, you're in luck here too - Data has readConstr :: DataType -> String -> Maybe Constr. From fuuzetsu at fuuzetsu.co.uk Mon Mar 10 15:09:49 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 10 Mar 2014 15:09:49 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 Message-ID: <531DD5BD.8090005@fuuzetsu.co.uk> Greetings, GSOC 2014 proposal period opens in ~4 hours and I'm hoping to participate this year as well. This time around I'd quite like to work on Yi. As we did last year, I think it's worthwhile to put up the proposals on caf? for people to comment on before they are submitted on Google's site. I paste it in full below so that it is easier to respond to parts of it (although I do ask that you don't quote the whole thing if it's not necessary). In case any changes happen, the most up-to-date version should be at https://gist.github.com/Fuuzetsu/9462709 Please feel free to nitpick on anything, throw in suggestions and ask for clarifications. I will give 5 days of discussion period on this after which point I'll submit it on Google's site. I appreciate all feedback. Thanks! Yi concurrency, usability and hackability ------------------------------------------ * What is the goal of the project you propose to do? There are two main goals of the project: the first is to implement concurrency in the Yi text editor. The second aim is to start bringing Yi into the territory of usable and hackable editors. Dmitry Ivanov who's currently in charge of Yi has agreed to mentor this project. * In what ways will this project benefit the wider Haskell community? While the project itself isn't one of the core ones (such as GHC, Haddock and Cabal), I feel that there are a couple of benefits to the community: 1. Work on Yi (now and in the future) will undoubtedly spawn new Haskell libraries usable in other projects. My personal experience with Yi shows that it's actually very comfortable to write a generic library which does what we need and then having a separate package which uses the library to actually interact with Yi. 2. Haskellers come closer to escaping the ELisp/vimscript hell. We can get a nicer programming environment, made and extensible in the language of our choice and get to use all the libraries that we're used to while we're at it. 3. We'll have more Real World? Haskell applications. On a more serious note, it can serve as a good example of how to do certain things with Haskell: off the top of my head, it demonstrates the use of dyre and gtk2hs in a real-world scenario rather than a 5 line example on the Haskell wiki. If the project is successful, we can add concurrency to this. Other than the Haskell community in general, this project should benefit anyone with some interest in text editors. I think it's safe to say that happens to be a large majority of Haskellers: most of us want nicer integration with Haskell tools and libraries[citation needed] and now it'll be possible through direct, type-checked library access. * Can you give some more detailed design of what precisely you intend to achieve? The concurrency goal will involve careful study of Yi's inner workings in order to try and accommodate concurrency in Yi's editor state. There are various ways to do concurrency and the first part of the project will concentrate on settling for one. An example of two different ways is to extend the existing Yi engine with classical tools (MVars, channels) to accommodate for concurrency that way. An alternative way would be to modify the engine so that concurrency support is natural. Such experiment was started [here](https://github.com/ethercrow/y) using the sodium FRP package which would give us concurrency ?for free?. The experiment is not complete and this is the kind of thing that will first be explored. Of course once we settle for a method, time will be spent implementing it. In the end, this should allow us to do things such as fire Yi events periodically or do network transfers without having to halt the whole editor. Editors such as emacs which are single-threaded effectively hop back-and-forth between tasks on a single thread. We aim to provide the ability to simply have tasks on different threads which allows us to take advantage of system resources much better. The second part of the project is to make Yi more usable and hackable. Usability here involves fixing bugs apparent to the user and hackability involves bugs apparent to developers. Further, as part of usability, I plan to implement as many editor modes as I find time for. Specifically, here are some open bugs that I hope to either fix or to make a considerate progress on: #445, #397, #517, #519, #515, #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. All the bug numbers can be viewed on [GitHub](https://github.com/yi-editor/yi/issues/). Please note that some of these are documentation bugs: Yi suffers from poor documentation and I believe that's what the main problems in gaining developers and users has been. When time or area I'm working on allows, missing documentation will be written. If I find any issue that have been fixed or are no longer applicable, the reports will simply be closed. The issues are very varied: unicode problems, keymap problems, highlighter problems, reloading problems, testing problems, mode problems? There is certainly enough work to entertain anyone for a longer amount of time while making Yi visibly better. The list of issues is simply an indicator of which problems the second goal of the project will concentrate on, rather than as a promise of which bugs are guaranteed to be fixed by the end of it. Alongside this goal, I'll write any modes for Yi as I find time for them. The completion of concurrency part of the project allows us to write many of the modes frequently requested by people wishing to use Yi which are currently impossible/unfeasible to write. * What deliverables do you think are reasonable targets? Can you outline an approximate schedule of milestones? The plan is based on the GSoC time line: 20 April - 19 May ? while this is a bonding period, I'm already a part of the Yi community and have a fair grasp of it. I'd start to look into this project as early as this period (and in fact I plan to make steps towards it before this date which means some of the outlined issues might get fixed early ;) ). 19 May - 23 June ? coding period; by this point I expect to have decided on which concurrency model we'll use and have a good idea of how it'll be implemented. By the end of this period, concurrency should either be completed or nearly done, depending on any unexpected problems that might come up. The deliverable would be Yi with (at least some) concurrency support. 24 June - 11 August ? second part of the coding period; work on any of the listed (or unlisted bugs) and finish up concurrency if it is still not done. Write extra Yi modes, libraries and documentation as time allows. 11 August - 18 August ? post-coding period; write any missing documentation, promote any cool new stuff we wrote ;) While I can not think of a specific deliverable, many bugs should now be fixed, Yi should have a lot more documentation, tests and modes. As a final note regarding the time line, it is not strictly necessary that the project implements concurrency first: while some bugs might need such support, many simply do not. If it's convenient to fix something that I had originally planned to for the second part of the project, I'll do so. * What relevant experience do you have? e.g. Have you coded anything in Haskell? Have you contributed to any other open source software? Been studying advanced courses in a related topic? Second year CS student. I program on regular basis using Haskell. I contribute to a bunch of FOSS projects as it seems necessary (see [my GitHub](https://github.com/Fuuzetsu)). I have successfully completed GSOC in 2013 which involved working on Haddock. To this day I help out with Haddock which often involves looking at the large GHC code base. * In what ways do you envisage interacting with the wider Haskell community during your project? e.g. How would you seek help on something your mentor wasn't able to deal with? How will you get others interested in what you are doing? I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated onto Haskell Planet. I'm active on IRC and many Haskell-related mailing lists. IRC, mailing lists and any relevant literature is where I'd seek help were I to get stuck on something my mentor can't help me with. I find that news about Yi are very popular and get propagated by the community itself very easily so I doubt there will be any problem getting people interested. I'm very easily reachable over e-mail and IRC and all the development is done in public. * Why do you think you would be the best person to tackle this project? I've been interested in Yi for a couple of months and have already wrote some commits, closed quite a few issues and filed even more issues on my own. I have access to the Yi repository and I help anyone looking to get started with Yi. I have about 2 years of Haskell experience and had my fair share of staring at library code. As mentioned before, I'm active as a member of the community and help out with one of the core Haskell projects (Haddock). -- Mateusz K. From mantkiew at gsd.uwaterloo.ca Mon Mar 10 15:28:16 2014 From: mantkiew at gsd.uwaterloo.ca (Michal Antkiewicz) Date: Mon, 10 Mar 2014 11:28:16 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531DD5BD.8090005@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: Hi Mateusz, An interesting application is always what drives development. There's a need to have a good IDE with strong editing support for Haskell written in Haskell. There's Leksah and there's Yi. Perhaps they could be integrated? Just an idea.. Cheers, Michal On Mon, Mar 10, 2014 at 11:09 AM, Mateusz Kowalczyk wrote: > Greetings, > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > participate this year as well. This time around I'd quite like to work > on Yi. As we did last year, I think it's worthwhile to put up the > proposals on caf? for people to comment on before they are submitted on > Google's site. > > I paste it in full below so that it is easier to respond to parts of it > (although I do ask that you don't quote the whole thing if it's not > necessary). In case any changes happen, the most up-to-date version > should be at https://gist.github.com/Fuuzetsu/9462709 > > Please feel free to nitpick on anything, throw in suggestions and ask > for clarifications. I will give 5 days of discussion period on this > after which point I'll submit it on Google's site. I appreciate all > feedback. > > Thanks! > > > Yi concurrency, usability and hackability > ------------------------------------------ > > * What is the goal of the project you propose to do? > > There are two main goals of the project: the first is to implement > concurrency in the Yi text editor. The second aim is to start > bringing Yi into the territory of usable and hackable editors. > > Dmitry Ivanov who's currently in charge of Yi has agreed to mentor > this project. > > * In what ways will this project benefit the wider Haskell community? > > While the project itself isn't one of the core ones (such as GHC, > Haddock and Cabal), I feel that there are a couple of benefits to the > community: > > 1. Work on Yi (now and in the future) will undoubtedly spawn new > Haskell libraries usable in other projects. My personal > experience with Yi shows that it's actually very comfortable to > write a generic library which does what we need and then having > a separate package which uses the library to actually interact > with Yi. > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. We > can get a nicer programming environment, made and extensible in > the language of our choice and get to use all the libraries > that we're used to while we're at it. > > 3. We'll have more Real World? Haskell applications. On a more > serious note, it can serve as a good example of how to do > certain things with Haskell: off the top of my head, it > demonstrates the use of dyre and gtk2hs in a real-world > scenario rather than a 5 line example on the Haskell wiki. If > the project is successful, we can add concurrency to this. > > Other than the Haskell community in general, this project should > benefit anyone with some interest in text editors. I think it's > safe to say that happens to be a large majority of Haskellers: > most of us want nicer integration with Haskell tools and > libraries[citation needed] and now it'll be possible through > direct, type-checked library access. > > * Can you give some more detailed design of what precisely you intend > to achieve? > > The concurrency goal will involve careful study of Yi's inner > workings in order to try and accommodate concurrency in Yi's > editor state. There are various ways to do concurrency and the > first part of the project will concentrate on settling for one. An > example of two different ways is to extend the existing Yi engine > with classical tools (MVars, channels) to accommodate for > concurrency that way. An alternative way would be to modify the > engine so that concurrency support is natural. Such experiment was > started [here](https://github.com/ethercrow/y) using the sodium > FRP package which would give us concurrency ?for free?. The > experiment is not complete and this is the kind of thing that will > first be explored. > > Of course once we settle for a method, time will be spent > implementing it. In the end, this should allow us to do things > such as fire Yi events periodically or do network transfers > without having to halt the whole editor. Editors such as emacs > which are single-threaded effectively hop back-and-forth between > tasks on a single thread. We aim to provide the ability to simply > have tasks on different threads which allows us to take advantage > of system resources much better. > > The second part of the project is to make Yi more usable and > hackable. Usability here involves fixing bugs apparent to the user > and hackability involves bugs apparent to developers. Further, > as part of usability, I plan to implement as many editor modes as > I find time for. > > Specifically, here are some open bugs that I hope to either fix or > to make a considerate progress on: #445, #397, #517, #519, #515, > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > All the bug numbers can be viewed on > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > that some of these are documentation bugs: Yi suffers from poor > documentation and I believe that's what the main problems in > gaining developers and users has been. When time or area I'm > working on allows, missing documentation will be written. > > If I find any issue that have been fixed or are no longer > applicable, the reports will simply be closed. The issues are very > varied: unicode problems, keymap problems, highlighter problems, > reloading problems, testing problems, mode problems? There is > certainly enough work to entertain anyone for a longer amount of > time while making Yi visibly better. > > The list of issues is simply an indicator of which problems the > second goal of the project will concentrate on, rather than as a > promise of which bugs are guaranteed to be fixed by the end of it. > > Alongside this goal, I'll write any modes for Yi as I find time > for them. The completion of concurrency part of the project allows > us to write many of the modes frequently requested by people > wishing to use Yi which are currently impossible/unfeasible to > write. > > * What deliverables do you think are reasonable targets? Can you > outline an approximate schedule of milestones? > > The plan is based on the GSoC time line: > 20 April - 19 May ? while this is a bonding period, I'm already a > part of the Yi community and have a fair grasp of it. I'd start to > look into this project as early as this period (and in fact I plan > to make steps towards it before this date which means some of the > outlined issues might get fixed early ;) ). > > 19 May - 23 June ? coding period; by this point I expect to have > decided on which concurrency model we'll use and have a good idea > of how it'll be implemented. By the end of this period, > concurrency should either be completed or nearly done, depending > on any unexpected problems that might come up. The deliverable > would be Yi with (at least some) concurrency support. > > 24 June - 11 August ? second part of the coding period; work on > any of the listed (or unlisted bugs) and finish up concurrency if > it is still not done. Write extra Yi modes, libraries and > documentation as time allows. > > 11 August - 18 August ? post-coding period; write any missing > documentation, promote any cool new stuff we wrote ;) While I can > not think of a specific deliverable, many bugs should now be > fixed, Yi should have a lot more documentation, tests and modes. > > As a final note regarding the time line, it is not strictly > necessary that the project implements concurrency first: while > some bugs might need such support, many simply do not. If it's > convenient to fix something that I had originally planned to for > the second part of the project, I'll do so. > > * What relevant experience do you have? e.g. Have you coded anything > in Haskell? Have you contributed to any other open source software? > Been studying advanced courses in a related topic? > > Second year CS student. I program on regular basis using Haskell. > I contribute to a bunch of FOSS projects as it seems necessary > (see [my GitHub](https://github.com/Fuuzetsu)). > I have successfully completed GSOC in 2013 which involved working > on Haddock. To this day I help out with Haddock which often > involves looking at the large GHC code base. > > * In what ways do you envisage interacting with the wider Haskell > community during your project? e.g. How would you seek help on > something your mentor wasn't able to deal with? How will you get > others interested in what you are doing? > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated > onto Haskell Planet. I'm active on IRC and many Haskell-related > mailing lists. IRC, mailing lists and any relevant literature is > where I'd seek help were I to get stuck on something my mentor > can't help me with. I find that news about Yi are very popular and > get propagated by the community itself very easily so I doubt > there will be any problem getting people interested. > > I'm very easily reachable over e-mail and IRC and all the > development is done in public. > > * Why do you think you would be the best person to tackle this > project? > > I've been interested in Yi for a couple of months and have already > wrote some commits, closed quite a few issues and filed even more > issues on my own. I have access to the Yi repository and > I help anyone looking to get started with Yi. I have about 2 years of > Haskell experience and had my fair share of staring at library > code. > > As mentioned before, I'm active as a member of the community and > help out with one of the core Haskell projects (Haddock). > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Michal Antkiewicz, M.Sc., Ph.D Research Engineer Network for the Engineering of Complex Software-Intensive Systems (NECSIS) University of Waterloo http://gsd.uwaterloo.ca/mantkiew mantkiew at gsd.uwaterloo.ca -------------- next part -------------- An HTML attachment was scrubbed... URL: From kyle.marek.spartz at gmail.com Mon Mar 10 15:29:37 2014 From: kyle.marek.spartz at gmail.com (Kyle Marek-Spartz) Date: Mon, 10 Mar 2014 10:29:37 -0500 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: Michal, Yi is an extensible text editor, not an IDE. There?s room for both. -- Kyle Marek-Spartz On March 10, 2014 at 10:28:35 AM, Michal Antkiewicz (mantkiew at gsd.uwaterloo.ca) wrote: > Hi Mateusz, > > An interesting application is always what drives development. There's a > need to have a good IDE with strong editing support for Haskell written in > Haskell. There's Leksah and there's Yi. Perhaps they could be integrated? > > Just an idea.. > > Cheers, > Michal > > > On Mon, Mar 10, 2014 at 11:09 AM, Mateusz Kowalczyk > > wrote: > > > Greetings, > > > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > > participate this year as well. This time around I'd quite like to work > > on Yi. As we did last year, I think it's worthwhile to put up the > > proposals on caf? for people to comment on before they are submitted on > > Google's site. > > > > I paste it in full below so that it is easier to respond to parts of it > > (although I do ask that you don't quote the whole thing if it's not > > necessary). In case any changes happen, the most up-to-date version > > should be at https://gist.github.com/Fuuzetsu/9462709 > > > > Please feel free to nitpick on anything, throw in suggestions and ask > > for clarifications. I will give 5 days of discussion period on this > > after which point I'll submit it on Google's site. I appreciate all > > feedback. > > > > Thanks! > > > > > > Yi concurrency, usability and hackability > > ------------------------------------------ > > > > * What is the goal of the project you propose to do? > > > > There are two main goals of the project: the first is to implement > > concurrency in the Yi text editor. The second aim is to start > > bringing Yi into the territory of usable and hackable editors. > > > > Dmitry Ivanov who's currently in charge of Yi has agreed to mentor > > this project. > > > > * In what ways will this project benefit the wider Haskell community? > > > > While the project itself isn't one of the core ones (such as GHC, > > Haddock and Cabal), I feel that there are a couple of benefits to the > > community: > > > > 1. Work on Yi (now and in the future) will undoubtedly spawn new > > Haskell libraries usable in other projects. My personal > > experience with Yi shows that it's actually very comfortable to > > write a generic library which does what we need and then having > > a separate package which uses the library to actually interact > > with Yi. > > > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. We > > can get a nicer programming environment, made and extensible in > > the language of our choice and get to use all the libraries > > that we're used to while we're at it. > > > > 3. We'll have more Real World? Haskell applications. On a more > > serious note, it can serve as a good example of how to do > > certain things with Haskell: off the top of my head, it > > demonstrates the use of dyre and gtk2hs in a real-world > > scenario rather than a 5 line example on the Haskell wiki. If > > the project is successful, we can add concurrency to this. > > > > Other than the Haskell community in general, this project should > > benefit anyone with some interest in text editors. I think it's > > safe to say that happens to be a large majority of Haskellers: > > most of us want nicer integration with Haskell tools and > > libraries[citation needed] and now it'll be possible through > > direct, type-checked library access. > > > > * Can you give some more detailed design of what precisely you intend > > to achieve? > > > > The concurrency goal will involve careful study of Yi's inner > > workings in order to try and accommodate concurrency in Yi's > > editor state. There are various ways to do concurrency and the > > first part of the project will concentrate on settling for one. An > > example of two different ways is to extend the existing Yi engine > > with classical tools (MVars, channels) to accommodate for > > concurrency that way. An alternative way would be to modify the > > engine so that concurrency support is natural. Such experiment was > > started [here](https://github.com/ethercrow/y) using the sodium > > FRP package which would give us concurrency ?for free?. The > > experiment is not complete and this is the kind of thing that will > > first be explored. > > > > Of course once we settle for a method, time will be spent > > implementing it. In the end, this should allow us to do things > > such as fire Yi events periodically or do network transfers > > without having to halt the whole editor. Editors such as emacs > > which are single-threaded effectively hop back-and-forth between > > tasks on a single thread. We aim to provide the ability to simply > > have tasks on different threads which allows us to take advantage > > of system resources much better. > > > > The second part of the project is to make Yi more usable and > > hackable. Usability here involves fixing bugs apparent to the user > > and hackability involves bugs apparent to developers. Further, > > as part of usability, I plan to implement as many editor modes as > > I find time for. > > > > Specifically, here are some open bugs that I hope to either fix or > > to make a considerate progress on: #445, #397, #517, #519, #515, > > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, > > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > > > All the bug numbers can be viewed on > > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > > that some of these are documentation bugs: Yi suffers from poor > > documentation and I believe that's what the main problems in > > gaining developers and users has been. When time or area I'm > > working on allows, missing documentation will be written. > > > > If I find any issue that have been fixed or are no longer > > applicable, the reports will simply be closed. The issues are very > > varied: unicode problems, keymap problems, highlighter problems, > > reloading problems, testing problems, mode problems? There is > > certainly enough work to entertain anyone for a longer amount of > > time while making Yi visibly better. > > > > The list of issues is simply an indicator of which problems the > > second goal of the project will concentrate on, rather than as a > > promise of which bugs are guaranteed to be fixed by the end of it. > > > > Alongside this goal, I'll write any modes for Yi as I find time > > for them. The completion of concurrency part of the project allows > > us to write many of the modes frequently requested by people > > wishing to use Yi which are currently impossible/unfeasible to > > write. > > > > * What deliverables do you think are reasonable targets? Can you > > outline an approximate schedule of milestones? > > > > The plan is based on the GSoC time line: > > 20 April - 19 May ? while this is a bonding period, I'm already a > > part of the Yi community and have a fair grasp of it. I'd start to > > look into this project as early as this period (and in fact I plan > > to make steps towards it before this date which means some of the > > outlined issues might get fixed early ;) ). > > > > 19 May - 23 June ? coding period; by this point I expect to have > > decided on which concurrency model we'll use and have a good idea > > of how it'll be implemented. By the end of this period, > > concurrency should either be completed or nearly done, depending > > on any unexpected problems that might come up. The deliverable > > would be Yi with (at least some) concurrency support. > > > > 24 June - 11 August ? second part of the coding period; work on > > any of the listed (or unlisted bugs) and finish up concurrency if > > it is still not done. Write extra Yi modes, libraries and > > documentation as time allows. > > > > 11 August - 18 August ? post-coding period; write any missing > > documentation, promote any cool new stuff we wrote ;) While I can > > not think of a specific deliverable, many bugs should now be > > fixed, Yi should have a lot more documentation, tests and modes. > > > > As a final note regarding the time line, it is not strictly > > necessary that the project implements concurrency first: while > > some bugs might need such support, many simply do not. If it's > > convenient to fix something that I had originally planned to for > > the second part of the project, I'll do so. > > > > * What relevant experience do you have? e.g. Have you coded anything > > in Haskell? Have you contributed to any other open source software? > > Been studying advanced courses in a related topic? > > > > Second year CS student. I program on regular basis using Haskell. > > I contribute to a bunch of FOSS projects as it seems necessary > > (see [my GitHub](https://github.com/Fuuzetsu)). > > I have successfully completed GSOC in 2013 which involved working > > on Haddock. To this day I help out with Haddock which often > > involves looking at the large GHC code base. > > > > * In what ways do you envisage interacting with the wider Haskell > > community during your project? e.g. How would you seek help on > > something your mentor wasn't able to deal with? How will you get > > others interested in what you are doing? > > > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated > > onto Haskell Planet. I'm active on IRC and many Haskell-related > > mailing lists. IRC, mailing lists and any relevant literature is > > where I'd seek help were I to get stuck on something my mentor > > can't help me with. I find that news about Yi are very popular and > > get propagated by the community itself very easily so I doubt > > there will be any problem getting people interested. > > > > I'm very easily reachable over e-mail and IRC and all the > > development is done in public. > > > > * Why do you think you would be the best person to tackle this > > project? > > > > I've been interested in Yi for a couple of months and have already > > wrote some commits, closed quite a few issues and filed even more > > issues on my own. I have access to the Yi repository and > > I help anyone looking to get started with Yi. I have about 2 years of > > Haskell experience and had my fair share of staring at library > > code. > > > > As mentioned before, I'm active as a member of the community and > > help out with one of the core Haskell projects (Haddock). > > > > > > -- > > Mateusz K. > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > Michal Antkiewicz, M.Sc., Ph.D > Research Engineer > Network for the Engineering of Complex Software-Intensive Systems (NECSIS) > > University of Waterloo > http://gsd.uwaterloo.ca/mantkiew > mantkiew at gsd.uwaterloo.ca > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From doaitse at swierstra.net Mon Mar 10 15:40:54 2014 From: doaitse at swierstra.net (S D Swierstra) Date: Mon, 10 Mar 2014 16:40:54 +0100 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140310131125.GA53715@inanna.trygub.com> References: <20140310131125.GA53715@inanna.trygub.com> Message-ID: Why not use: http://hackage.haskell.org/package/ChristmasTree which supports even infix constructors and runs in linear time, Doaitse Swierstra On 10 Mar 2014, at 14:11 , Semen Trygubenko / ????? ?????????? wrote: > Dear Haskell-cafe, > > When deriving (Read), only values can be read in. > If one wants to be able to read in constructors, too, is there an easy way out? > E.g., the code below works, but the extra book-keeping > > f "A" = A > ... > > is unpleasant ? perhaps there's a simpler solution? > > {-# LANGUAGE FlexibleInstances #-} > > data D = A Int > | B Int > deriving (Show,Read) > > instance Read (Int -> D) where > readsPrec = \_ s -> [(f s,"")] > where f "A" = A > f "B" = B > f x = error $ "Invalid constructor " ++ x > > main = do let x = read "A 1" :: D > print x > let g s = read s :: (Int -> D) > print $ g "B" 2 > print $ g "C" 3 > > Many thanks in advance, > Semen > > > > -- > ????? ?????????? http://trygub.com > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mantkiew at gsd.uwaterloo.ca Mon Mar 10 15:41:57 2014 From: mantkiew at gsd.uwaterloo.ca (mantkiew at gsd.uwaterloo.ca) Date: Mon, 10 Mar 2014 11:41:57 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: <20140310154157.6008979.23400.4513@gsd.uwaterloo.ca> Yes, absolutely. What I meant was that having Yi used in Leksah could provide more momentum for development. ?I didn't mean to merge the two projects into one.? Michal ? Original Message ? From: Kyle Marek-Spartz Sent: Monday, March 10, 2014 11:29 AM To: Mateusz Kowalczyk; Michal Antkiewicz Cc: haskell-cafe Subject: Re: [Haskell-cafe] Yi project proposal for GSOC 2014 Michal, Yi is an extensible text editor, not an IDE. There?s room for both. -- Kyle Marek-Spartz On March 10, 2014 at 10:28:35 AM, Michal Antkiewicz (mantkiew at gsd.uwaterloo.ca) wrote: > Hi Mateusz, > > An interesting application is always what drives development. There's a > need to have a good IDE with strong editing support for Haskell written in > Haskell. There's Leksah and there's Yi. Perhaps they could be integrated? > > Just an idea.. > > Cheers, > Michal > > > On Mon, Mar 10, 2014 at 11:09 AM, Mateusz Kowalczyk > > wrote: > > > Greetings, > > > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > > participate this year as well. This time around I'd quite like to work > > on Yi. As we did last year, I think it's worthwhile to put up the > > proposals on caf? for people to comment on before they are submitted on > > Google's site. > > > > I paste it in full below so that it is easier to respond to parts of it > > (although I do ask that you don't quote the whole thing if it's not > > necessary). In case any changes happen, the most up-to-date version > > should be at https://gist.github.com/Fuuzetsu/9462709 > > > > Please feel free to nitpick on anything, throw in suggestions and ask > > for clarifications. I will give 5 days of discussion period on this > > after which point I'll submit it on Google's site. I appreciate all > > feedback. > > > > Thanks! > > > > > > Yi concurrency, usability and hackability > > ------------------------------------------ > > > > * What is the goal of the project you propose to do? > > > > There are two main goals of the project: the first is to implement > > concurrency in the Yi text editor. The second aim is to start > > bringing Yi into the territory of usable and hackable editors. > > > > Dmitry Ivanov who's currently in charge of Yi has agreed to mentor > > this project. > > > > * In what ways will this project benefit the wider Haskell community? > > > > While the project itself isn't one of the core ones (such as GHC, > > Haddock and Cabal), I feel that there are a couple of benefits to the > > community: > > > > 1. Work on Yi (now and in the future) will undoubtedly spawn new > > Haskell libraries usable in other projects. My personal > > experience with Yi shows that it's actually very comfortable to > > write a generic library which does what we need and then having > > a separate package which uses the library to actually interact > > with Yi. > > > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. We > > can get a nicer programming environment, made and extensible in > > the language of our choice and get to use all the libraries > > that we're used to while we're at it. > > > > 3. We'll have more Real World? Haskell applications. On a more > > serious note, it can serve as a good example of how to do > > certain things with Haskell: off the top of my head, it > > demonstrates the use of dyre and gtk2hs in a real-world > > scenario rather than a 5 line example on the Haskell wiki. If > > the project is successful, we can add concurrency to this. > > > > Other than the Haskell community in general, this project should > > benefit anyone with some interest in text editors. I think it's > > safe to say that happens to be a large majority of Haskellers: > > most of us want nicer integration with Haskell tools and > > libraries[citation needed] and now it'll be possible through > > direct, type-checked library access. > > > > * Can you give some more detailed design of what precisely you intend > > to achieve? > > > > The concurrency goal will involve careful study of Yi's inner > > workings in order to try and accommodate concurrency in Yi's > > editor state. There are various ways to do concurrency and the > > first part of the project will concentrate on settling for one. An > > example of two different ways is to extend the existing Yi engine > > with classical tools (MVars, channels) to accommodate for > > concurrency that way. An alternative way would be to modify the > > engine so that concurrency support is natural. Such experiment was > > started [here](https://github.com/ethercrow/y) using the sodium > > FRP package which would give us concurrency ?for free?. The > > experiment is not complete and this is the kind of thing that will > > first be explored. > > > > Of course once we settle for a method, time will be spent > > implementing it. In the end, this should allow us to do things > > such as fire Yi events periodically or do network transfers > > without having to halt the whole editor. Editors such as emacs > > which are single-threaded effectively hop back-and-forth between > > tasks on a single thread. We aim to provide the ability to simply > > have tasks on different threads which allows us to take advantage > > of system resources much better. > > > > The second part of the project is to make Yi more usable and > > hackable. Usability here involves fixing bugs apparent to the user > > and hackability involves bugs apparent to developers. Further, > > as part of usability, I plan to implement as many editor modes as > > I find time for. > > > > Specifically, here are some open bugs that I hope to either fix or > > to make a considerate progress on: #445, #397, #517, #519, #515, > > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, > > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > > > All the bug numbers can be viewed on > > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > > that some of these are documentation bugs: Yi suffers from poor > > documentation and I believe that's what the main problems in > > gaining developers and users has been. When time or area I'm > > working on allows, missing documentation will be written. > > > > If I find any issue that have been fixed or are no longer > > applicable, the reports will simply be closed. The issues are very > > varied: unicode problems, keymap problems, highlighter problems, > > reloading problems, testing problems, mode problems? There is > > certainly enough work to entertain anyone for a longer amount of > > time while making Yi visibly better. > > > > The list of issues is simply an indicator of which problems the > > second goal of the project will concentrate on, rather than as a > > promise of which bugs are guaranteed to be fixed by the end of it. > > > > Alongside this goal, I'll write any modes for Yi as I find time > > for them. The completion of concurrency part of the project allows > > us to write many of the modes frequently requested by people > > wishing to use Yi which are currently impossible/unfeasible to > > write. > > > > * What deliverables do you think are reasonable targets? Can you > > outline an approximate schedule of milestones? > > > > The plan is based on the GSoC time line: > > 20 April - 19 May ? while this is a bonding period, I'm already a > > part of the Yi community and have a fair grasp of it. I'd start to > > look into this project as early as this period (and in fact I plan > > to make steps towards it before this date which means some of the > > outlined issues might get fixed early ;) ). > > > > 19 May - 23 June ? coding period; by this point I expect to have > > decided on which concurrency model we'll use and have a good idea > > of how it'll be implemented. By the end of this period, > > concurrency should either be completed or nearly done, depending > > on any unexpected problems that might come up. The deliverable > > would be Yi with (at least some) concurrency support. > > > > 24 June - 11 August ? second part of the coding period; work on > > any of the listed (or unlisted bugs) and finish up concurrency if > > it is still not done. Write extra Yi modes, libraries and > > documentation as time allows. > > > > 11 August - 18 August ? post-coding period; write any missing > > documentation, promote any cool new stuff we wrote ;) While I can > > not think of a specific deliverable, many bugs should now be > > fixed, Yi should have a lot more documentation, tests and modes. > > > > As a final note regarding the time line, it is not strictly > > necessary that the project implements concurrency first: while > > some bugs might need such support, many simply do not. If it's > > convenient to fix something that I had originally planned to for > > the second part of the project, I'll do so. > > > > * What relevant experience do you have? e.g. Have you coded anything > > in Haskell? Have you contributed to any other open source software? > > Been studying advanced courses in a related topic? > > > > Second year CS student. I program on regular basis using Haskell. > > I contribute to a bunch of FOSS projects as it seems necessary > > (see [my GitHub](https://github.com/Fuuzetsu)). > > I have successfully completed GSOC in 2013 which involved working > > on Haddock. To this day I help out with Haddock which often > > involves looking at the large GHC code base. > > > > * In what ways do you envisage interacting with the wider Haskell > > community during your project? e.g. How would you seek help on > > something your mentor wasn't able to deal with? How will you get > > others interested in what you are doing? > > > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated > > onto Haskell Planet. I'm active on IRC and many Haskell-related > > mailing lists. IRC, mailing lists and any relevant literature is > > where I'd seek help were I to get stuck on something my mentor > > can't help me with. I find that news about Yi are very popular and > > get propagated by the community itself very easily so I doubt > > there will be any problem getting people interested. > > > > I'm very easily reachable over e-mail and IRC and all the > > development is done in public. > > > > * Why do you think you would be the best person to tackle this > > project? > > > > I've been interested in Yi for a couple of months and have already > > wrote some commits, closed quite a few issues and filed even more > > issues on my own. I have access to the Yi repository and > > I help anyone looking to get started with Yi. I have about 2 years of > > Haskell experience and had my fair share of staring at library > > code. > > > > As mentioned before, I'm active as a member of the community and > > help out with one of the core Haskell projects (Haddock). > > > > > > -- > > Mateusz K. > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > Michal Antkiewicz, M.Sc., Ph.D > Research Engineer > Network for the Engineering of Complex Software-Intensive Systems (NECSIS) > > University of Waterloo > http://gsd.uwaterloo.ca/mantkiew > mantkiew at gsd.uwaterloo.ca > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From daniel.trstenjak at gmail.com Mon Mar 10 15:53:12 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 10 Mar 2014 16:53:12 +0100 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <20140310154157.6008979.23400.4513@gsd.uwaterloo.ca> References: <531DD5BD.8090005@fuuzetsu.co.uk> <20140310154157.6008979.23400.4513@gsd.uwaterloo.ca> Message-ID: <20140310155312.GA18979@machine> On Mon, Mar 10, 2014 at 11:41:57AM -0400, mantkiew at gsd.uwaterloo.ca wrote: > Yes, absolutely. What I meant was that having Yi used in Leksah could > provide more momentum for development. ?I didn't mean to merge > the two projects into one.? > > Michal > ? Original Message ? > From: Kyle Marek-Spartz > Sent: Monday, March 10, 2014 11:29 AM > To: Mateusz Kowalczyk; Michal Antkiewicz > Cc: haskell-cafe > Subject: Re: [Haskell-cafe] Yi project proposal for GSOC 2014 > > Michal, > > Yi is an extensible text editor, not an IDE. There?s room for both. > > -- > Kyle Marek-Spartz > > On March 10, 2014 at 10:28:35 AM, Michal Antkiewicz (mantkiew at gsd.uwaterloo.ca) wrote: > > Hi Mateusz, > > > > An interesting application is always what drives development. There's a > > need to have a good IDE with strong editing support for Haskell written in > > Haskell. There's Leksah and there's Yi. Perhaps they could be integrated? > > > > Just an idea.. > > > > Cheers, > > Michal > > > > > > On Mon, Mar 10, 2014 at 11:09 AM, Mateusz Kowalczyk > > wrote: > > > > > Greetings, > > > > > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > > > participate this year as well. This time around I'd quite like to work > > > on Yi. As we did last year, I think it's worthwhile to put up the > > > proposals on caf? for people to comment on before they are submitted on > > > Google's site. > > > > > > I paste it in full below so that it is easier to respond to parts of it > > > (although I do ask that you don't quote the whole thing if it's not > > > necessary). In case any changes happen, the most up-to-date version > > > should be at https://gist.github.com/Fuuzetsu/9462709 > > > > > > Please feel free to nitpick on anything, throw in suggestions and ask > > > for clarifications. I will give 5 days of discussion period on this > > > after which point I'll submit it on Google's site. I appreciate all > > > feedback. > > > > > > Thanks! > > > > > > > > > Yi concurrency, usability and hackability > > > ------------------------------------------ > > > > > > * What is the goal of the project you propose to do? > > > > > > There are two main goals of the project: the first is to implement > > > concurrency in the Yi text editor. The second aim is to start > > > bringing Yi into the territory of usable and hackable editors. > > > > > > Dmitry Ivanov who's currently in charge of Yi has agreed to mentor > > > this project. > > > > > > * In what ways will this project benefit the wider Haskell community? > > > > > > While the project itself isn't one of the core ones (such as GHC, > > > Haddock and Cabal), I feel that there are a couple of benefits to the > > > community: > > > > > > 1. Work on Yi (now and in the future) will undoubtedly spawn new > > > Haskell libraries usable in other projects. My personal > > > experience with Yi shows that it's actually very comfortable to > > > write a generic library which does what we need and then having > > > a separate package which uses the library to actually interact > > > with Yi. > > > > > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. We > > > can get a nicer programming environment, made and extensible in > > > the language of our choice and get to use all the libraries > > > that we're used to while we're at it. > > > > > > 3. We'll have more Real World? Haskell applications. On a more > > > serious note, it can serve as a good example of how to do > > > certain things with Haskell: off the top of my head, it > > > demonstrates the use of dyre and gtk2hs in a real-world > > > scenario rather than a 5 line example on the Haskell wiki. If > > > the project is successful, we can add concurrency to this. > > > > > > Other than the Haskell community in general, this project should > > > benefit anyone with some interest in text editors. I think it's > > > safe to say that happens to be a large majority of Haskellers: > > > most of us want nicer integration with Haskell tools and > > > libraries[citation needed] and now it'll be possible through > > > direct, type-checked library access. > > > > > > * Can you give some more detailed design of what precisely you intend > > > to achieve? > > > > > > The concurrency goal will involve careful study of Yi's inner > > > workings in order to try and accommodate concurrency in Yi's > > > editor state. There are various ways to do concurrency and the > > > first part of the project will concentrate on settling for one. An > > > example of two different ways is to extend the existing Yi engine > > > with classical tools (MVars, channels) to accommodate for > > > concurrency that way. An alternative way would be to modify the > > > engine so that concurrency support is natural. Such experiment was > > > started [here](https://github.com/ethercrow/y) using the sodium > > > FRP package which would give us concurrency ?for free?. The > > > experiment is not complete and this is the kind of thing that will > > > first be explored. > > > > > > Of course once we settle for a method, time will be spent > > > implementing it. In the end, this should allow us to do things > > > such as fire Yi events periodically or do network transfers > > > without having to halt the whole editor. Editors such as emacs > > > which are single-threaded effectively hop back-and-forth between > > > tasks on a single thread. We aim to provide the ability to simply > > > have tasks on different threads which allows us to take advantage > > > of system resources much better. > > > > > > The second part of the project is to make Yi more usable and > > > hackable. Usability here involves fixing bugs apparent to the user > > > and hackability involves bugs apparent to developers. Further, > > > as part of usability, I plan to implement as many editor modes as > > > I find time for. > > > > > > Specifically, here are some open bugs that I hope to either fix or > > > to make a considerate progress on: #445, #397, #517, #519, #515, > > > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > > > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, > > > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > > > > > All the bug numbers can be viewed on > > > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > > > that some of these are documentation bugs: Yi suffers from poor > > > documentation and I believe that's what the main problems in > > > gaining developers and users has been. When time or area I'm > > > working on allows, missing documentation will be written. > > > > > > If I find any issue that have been fixed or are no longer > > > applicable, the reports will simply be closed. The issues are very > > > varied: unicode problems, keymap problems, highlighter problems, > > > reloading problems, testing problems, mode problems? There is > > > certainly enough work to entertain anyone for a longer amount of > > > time while making Yi visibly better. > > > > > > The list of issues is simply an indicator of which problems the > > > second goal of the project will concentrate on, rather than as a > > > promise of which bugs are guaranteed to be fixed by the end of it. > > > > > > Alongside this goal, I'll write any modes for Yi as I find time > > > for them. The completion of concurrency part of the project allows > > > us to write many of the modes frequently requested by people > > > wishing to use Yi which are currently impossible/unfeasible to > > > write. > > > > > > * What deliverables do you think are reasonable targets? Can you > > > outline an approximate schedule of milestones? > > > > > > The plan is based on the GSoC time line: > > > 20 April - 19 May ? while this is a bonding period, I'm already a > > > part of the Yi community and have a fair grasp of it. I'd start to > > > look into this project as early as this period (and in fact I plan > > > to make steps towards it before this date which means some of the > > > outlined issues might get fixed early ;) ). > > > > > > 19 May - 23 June ? coding period; by this point I expect to have > > > decided on which concurrency model we'll use and have a good idea > > > of how it'll be implemented. By the end of this period, > > > concurrency should either be completed or nearly done, depending > > > on any unexpected problems that might come up. The deliverable > > > would be Yi with (at least some) concurrency support. > > > > > > 24 June - 11 August ? second part of the coding period; work on > > > any of the listed (or unlisted bugs) and finish up concurrency if > > > it is still not done. Write extra Yi modes, libraries and > > > documentation as time allows. > > > > > > 11 August - 18 August ? post-coding period; write any missing > > > documentation, promote any cool new stuff we wrote ;) While I can > > > not think of a specific deliverable, many bugs should now be > > > fixed, Yi should have a lot more documentation, tests and modes. > > > > > > As a final note regarding the time line, it is not strictly > > > necessary that the project implements concurrency first: while > > > some bugs might need such support, many simply do not. If it's > > > convenient to fix something that I had originally planned to for > > > the second part of the project, I'll do so. > > > > > > * What relevant experience do you have? e.g. Have you coded anything > > > in Haskell? Have you contributed to any other open source software? > > > Been studying advanced courses in a related topic? > > > > > > Second year CS student. I program on regular basis using Haskell. > > > I contribute to a bunch of FOSS projects as it seems necessary > > > (see [my GitHub](https://github.com/Fuuzetsu)). > > > I have successfully completed GSOC in 2013 which involved working > > > on Haddock. To this day I help out with Haddock which often > > > involves looking at the large GHC code base. > > > > > > * In what ways do you envisage interacting with the wider Haskell > > > community during your project? e.g. How would you seek help on > > > something your mentor wasn't able to deal with? How will you get > > > others interested in what you are doing? > > > > > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated > > > onto Haskell Planet. I'm active on IRC and many Haskell-related > > > mailing lists. IRC, mailing lists and any relevant literature is > > > where I'd seek help were I to get stuck on something my mentor > > > can't help me with. I find that news about Yi are very popular and > > > get propagated by the community itself very easily so I doubt > > > there will be any problem getting people interested. > > > > > > I'm very easily reachable over e-mail and IRC and all the > > > development is done in public. > > > > > > * Why do you think you would be the best person to tackle this > > > project? > > > > > > I've been interested in Yi for a couple of months and have already > > > wrote some commits, closed quite a few issues and filed even more > > > issues on my own. I have access to the Yi repository and > > > I help anyone looking to get started with Yi. I have about 2 years of > > > Haskell experience and had my fair share of staring at library > > > code. > > > > > > As mentioned before, I'm active as a member of the community and > > > help out with one of the core Haskell projects (Haddock). > > > > > > > > > -- > > > Mateusz K. > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > -- > > Michal Antkiewicz, M.Sc., Ph.D > > Research Engineer > > Network for the Engineering of Complex Software-Intensive Systems (NECSIS) > > > > University of Waterloo > > http://gsd.uwaterloo.ca/mantkiew > > mantkiew at gsd.uwaterloo.ca > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From daniel.trstenjak at gmail.com Mon Mar 10 15:58:51 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 10 Mar 2014 16:58:51 +0100 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <20140310154157.6008979.23400.4513@gsd.uwaterloo.ca> References: <531DD5BD.8090005@fuuzetsu.co.uk> <20140310154157.6008979.23400.4513@gsd.uwaterloo.ca> Message-ID: <20140310155851.GA19068@machine> On Mon, Mar 10, 2014 at 11:41:57AM -0400, mantkiew at gsd.uwaterloo.ca wrote: > Yes, absolutely. What I meant was that having Yi used in Leksah could > provide more momentum for development. ?I didn't mean to merge > the two projects into one.? But then you would have to write an interface between Yi and Leksah and these kind of big interfaces IMHO never really work that well. I think it makes more sense to have libraries which are shared by Yi and Leksah, which could also be used by other applications and therefore are a bigger win for the whole Haskell ecosystem. Greetings, Daniel From vagif.verdi at gmail.com Mon Mar 10 16:04:22 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Mon, 10 Mar 2014 09:04:22 -0700 (PDT) Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531DD5BD.8090005@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> I do not think we need more haskell aware editors and IDEs. There's more than enough already: emacs, vim, Eclipse, Leksah, Yi. What we need though is a IDE backend so any editor can use it to provide hakell IDE features. As it stands right now all haskell IDEs reinvent the wheel in some incompatible manner. EclipseFp has scion, some emacs modes develop ghc-mod backend. Leksah lives in its own world. ghci added some IDE support features recently. This fragmentation hurts us. I would say making ghci a full-blown IDE backend akin lisps slime-swank or clojure nrepl would be the best approach. On Monday, March 10, 2014 8:09:49 AM UTC-7, Mateusz Kowalczyk wrote: > > Greetings, > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > participate this year as well. This time around I'd quite like to work > on Yi. As we did last year, I think it's worthwhile to put up the > proposals on caf? for people to comment on before they are submitted on > Google's site. > > I paste it in full below so that it is easier to respond to parts of it > (although I do ask that you don't quote the whole thing if it's not > necessary). In case any changes happen, the most up-to-date version > should be at https://gist.github.com/Fuuzetsu/9462709 > > Please feel free to nitpick on anything, throw in suggestions and ask > for clarifications. I will give 5 days of discussion period on this > after which point I'll submit it on Google's site. I appreciate all > feedback. > > Thanks! > > > Yi concurrency, usability and hackability > ------------------------------------------ > > * What is the goal of the project you propose to do? > > There are two main goals of the project: the first is to implement > concurrency in the Yi text editor. The second aim is to start > bringing Yi into the territory of usable and hackable editors. > > Dmitry Ivanov who's currently in charge of Yi has agreed to mentor > this project. > > * In what ways will this project benefit the wider Haskell community? > > While the project itself isn't one of the core ones (such as GHC, > Haddock and Cabal), I feel that there are a couple of benefits to the > community: > > 1. Work on Yi (now and in the future) will undoubtedly spawn new > Haskell libraries usable in other projects. My personal > experience with Yi shows that it's actually very comfortable to > write a generic library which does what we need and then having > a separate package which uses the library to actually interact > with Yi. > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. We > can get a nicer programming environment, made and extensible in > the language of our choice and get to use all the libraries > that we're used to while we're at it. > > 3. We'll have more Real World? Haskell applications. On a more > serious note, it can serve as a good example of how to do > certain things with Haskell: off the top of my head, it > demonstrates the use of dyre and gtk2hs in a real-world > scenario rather than a 5 line example on the Haskell wiki. If > the project is successful, we can add concurrency to this. > > Other than the Haskell community in general, this project should > benefit anyone with some interest in text editors. I think it's > safe to say that happens to be a large majority of Haskellers: > most of us want nicer integration with Haskell tools and > libraries[citation needed] and now it'll be possible through > direct, type-checked library access. > > * Can you give some more detailed design of what precisely you intend > to achieve? > > The concurrency goal will involve careful study of Yi's inner > workings in order to try and accommodate concurrency in Yi's > editor state. There are various ways to do concurrency and the > first part of the project will concentrate on settling for one. An > example of two different ways is to extend the existing Yi engine > with classical tools (MVars, channels) to accommodate for > concurrency that way. An alternative way would be to modify the > engine so that concurrency support is natural. Such experiment was > started [here](https://github.com/ethercrow/y) using the sodium > FRP package which would give us concurrency ?for free?. The > experiment is not complete and this is the kind of thing that will > first be explored. > > Of course once we settle for a method, time will be spent > implementing it. In the end, this should allow us to do things > such as fire Yi events periodically or do network transfers > without having to halt the whole editor. Editors such as emacs > which are single-threaded effectively hop back-and-forth between > tasks on a single thread. We aim to provide the ability to simply > have tasks on different threads which allows us to take advantage > of system resources much better. > > The second part of the project is to make Yi more usable and > hackable. Usability here involves fixing bugs apparent to the user > and hackability involves bugs apparent to developers. Further, > as part of usability, I plan to implement as many editor modes as > I find time for. > > Specifically, here are some open bugs that I hope to either fix or > to make a considerate progress on: #445, #397, #517, #519, #515, > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > All the bug numbers can be viewed on > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > that some of these are documentation bugs: Yi suffers from poor > documentation and I believe that's what the main problems in > gaining developers and users has been. When time or area I'm > working on allows, missing documentation will be written. > > If I find any issue that have been fixed or are no longer > applicable, the reports will simply be closed. The issues are very > varied: unicode problems, keymap problems, highlighter problems, > reloading problems, testing problems, mode problems? There is > certainly enough work to entertain anyone for a longer amount of > time while making Yi visibly better. > > The list of issues is simply an indicator of which problems the > second goal of the project will concentrate on, rather than as a > promise of which bugs are guaranteed to be fixed by the end of it. > > Alongside this goal, I'll write any modes for Yi as I find time > for them. The completion of concurrency part of the project allows > us to write many of the modes frequently requested by people > wishing to use Yi which are currently impossible/unfeasible to > write. > > * What deliverables do you think are reasonable targets? Can you > outline an approximate schedule of milestones? > > The plan is based on the GSoC time line: > 20 April - 19 May ? while this is a bonding period, I'm already a > part of the Yi community and have a fair grasp of it. I'd start to > look into this project as early as this period (and in fact I plan > to make steps towards it before this date which means some of the > outlined issues might get fixed early ;) ). > > 19 May - 23 June ? coding period; by this point I expect to have > decided on which concurrency model we'll use and have a good idea > of how it'll be implemented. By the end of this period, > concurrency should either be completed or nearly done, depending > on any unexpected problems that might come up. The deliverable > would be Yi with (at least some) concurrency support. > > 24 June - 11 August ? second part of the coding period; work on > any of the listed (or unlisted bugs) and finish up concurrency if > it is still not done. Write extra Yi modes, libraries and > documentation as time allows. > > 11 August - 18 August ? post-coding period; write any missing > documentation, promote any cool new stuff we wrote ;) While I can > not think of a specific deliverable, many bugs should now be > fixed, Yi should have a lot more documentation, tests and modes. > > As a final note regarding the time line, it is not strictly > necessary that the project implements concurrency first: while > some bugs might need such support, many simply do not. If it's > convenient to fix something that I had originally planned to for > the second part of the project, I'll do so. > > * What relevant experience do you have? e.g. Have you coded anything > in Haskell? Have you contributed to any other open source software? > Been studying advanced courses in a related topic? > > Second year CS student. I program on regular basis using Haskell. > I contribute to a bunch of FOSS projects as it seems necessary > (see [my GitHub](https://github.com/Fuuzetsu)). > I have successfully completed GSOC in 2013 which involved working > on Haddock. To this day I help out with Haddock which often > involves looking at the large GHC code base. > > * In what ways do you envisage interacting with the wider Haskell > community during your project? e.g. How would you seek help on > something your mentor wasn't able to deal with? How will you get > others interested in what you are doing? > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated > onto Haskell Planet. I'm active on IRC and many Haskell-related > mailing lists. IRC, mailing lists and any relevant literature is > where I'd seek help were I to get stuck on something my mentor > can't help me with. I find that news about Yi are very popular and > get propagated by the community itself very easily so I doubt > there will be any problem getting people interested. > > I'm very easily reachable over e-mail and IRC and all the > development is done in public. > > * Why do you think you would be the best person to tackle this > project? > > I've been interested in Yi for a couple of months and have already > wrote some commits, closed quite a few issues and filed even more > issues on my own. I have access to the Yi repository and > I help anyone looking to get started with Yi. I have about 2 years of > Haskell experience and had my fair share of staring at library > code. > > As mentioned before, I'm active as a member of the community and > help out with one of the core Haskell projects (Haddock). > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Mon Mar 10 16:05:33 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 10 Mar 2014 16:05:33 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <20140310155851.GA19068@machine> References: <531DD5BD.8090005@fuuzetsu.co.uk> <20140310154157.6008979.23400.4513@gsd.uwaterloo.ca> <20140310155851.GA19068@machine> Message-ID: <531DE2CD.7030903@fuuzetsu.co.uk> On 10/03/14 15:58, Daniel Trstenjak wrote: > > On Mon, Mar 10, 2014 at 11:41:57AM -0400, mantkiew at gsd.uwaterloo.ca wrote: >> Yes, absolutely. What I meant was that having Yi used in Leksah could >> provide more momentum for development. ?I didn't mean to merge >> the two projects into one. > > But then you would have to write an interface between Yi and Leksah > and these kind of big interfaces IMHO never really work that well. > > I think it makes more sense to have libraries which are shared > by Yi and Leksah, which could also be used by other applications > and therefore are a bigger win for the whole Haskell ecosystem. > > > Greetings, > Daniel > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Actually, I hear that it's possible to embed Yi inside of Leksah. I have never tried Leksah out but perhaps that's more of what you're after. But yes, generic libraries (that can be used by Yi and Leksah) are certainly a thing that gets written while implementing something (at least from my experience). It is listed as one of the benefits. It's a nice side effect I suppose. -- Mateusz K. From roma at ro-che.info Mon Mar 10 16:13:47 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 10 Mar 2014 18:13:47 +0200 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531DD5BD.8090005@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: <20140310161347.GA25759@sniper> * Mateusz Kowalczyk [2014-03-10 15:09:49+0000] > Greetings, > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > participate this year as well. This time around I'd quite like to work > on Yi. As we did last year, I think it's worthwhile to put up the > proposals on caf? for people to comment on before they are submitted on > Google's site. > > I paste it in full below so that it is easier to respond to parts of it > (although I do ask that you don't quote the whole thing if it's not > necessary). In case any changes happen, the most up-to-date version > should be at https://gist.github.com/Fuuzetsu/9462709 > > Please feel free to nitpick on anything, throw in suggestions and ask > for clarifications. I will give 5 days of discussion period on this > after which point I'll submit it on Google's site. I appreciate all > feedback. From what I've seen, the less uncertainty there is in a GSoC project, the better it works. For example, the situation in your past GSoC project where it was decided in the middle that instead of implementing markdown syntax you're going to do other things is undesirable, IMO. 3 months is a very short time for a research project. (By research I mean not academic research, but finding a way (or the best way) to do something.) And here you're basically saying "there are several ways to do that, we'll figure out what to do as we go". If, on the other hand, it was already decided what the right architecture for concurrency in Yi should be, and it was just a matter of someone doing the work, it would be a good project. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From andy at adradh.org.uk Mon Mar 10 16:16:08 2014 From: andy at adradh.org.uk (Andy Morris) Date: Mon, 10 Mar 2014 17:16:08 +0100 Subject: [Haskell-cafe] [GSOC] haskell-type-exts? Message-ID: On the GSOC ideas page for haskell.org is haskell-type-exts[1], which?as the name may suggest :)?is a proposal for a typechecker for haskell-src-exts. It doesn't seem to have got much attention, having only a single comment from two years ago, and I haven't seen anyone talking about it here or elsewhere. I guess this is still something that would be useful, so unless anyone has a reason why not, I'd like to apply to do it. I'll probably start working on the application later today unless some objections surface :) (Is Niklas Broberg subscribed to this list? If so: would you still be willing to mentor this project?) [1] https://ghc.haskell.org/trac/summer-of-code/ticket/1620 From mantkiew at gsd.uwaterloo.ca Mon Mar 10 16:22:16 2014 From: mantkiew at gsd.uwaterloo.ca (Michal Antkiewicz) Date: Mon, 10 Mar 2014 12:22:16 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: > > I would say making ghci a full-blown IDE backend akin lisps slime-swank or > clojure nrepl would be the best approach. > there's already hdevtools which plays that role - it provides all sorts of information to an IDE, like types, location of declarations, etc. It's a background process and it's quite responsive (tries to be incremental). I don't know how it is implemented and whether it is a wrapper around GHCi. But I agree that all IDEs should simply use GHCi as the official IDE backend. Maybe some parts from scion/hdevtools/ghc-mod/etc. could be pulled back into GHCi? Michal > > > > On Monday, March 10, 2014 8:09:49 AM UTC-7, Mateusz Kowalczyk wrote: > >> Greetings, >> >> GSOC 2014 proposal period opens in ~4 hours and I'm hoping to >> participate this year as well. This time around I'd quite like to work >> on Yi. As we did last year, I think it's worthwhile to put up the >> proposals on caf? for people to comment on before they are submitted on >> Google's site. >> >> I paste it in full below so that it is easier to respond to parts of it >> (although I do ask that you don't quote the whole thing if it's not >> necessary). In case any changes happen, the most up-to-date version >> should be at https://gist.github.com/Fuuzetsu/9462709 >> >> Please feel free to nitpick on anything, throw in suggestions and ask >> for clarifications. I will give 5 days of discussion period on this >> after which point I'll submit it on Google's site. I appreciate all >> feedback. >> >> Thanks! >> >> >> Yi concurrency, usability and hackability >> ------------------------------------------ >> >> * What is the goal of the project you propose to do? >> >> There are two main goals of the project: the first is to implement >> concurrency in the Yi text editor. The second aim is to start >> bringing Yi into the territory of usable and hackable editors. >> >> Dmitry Ivanov who's currently in charge of Yi has agreed to mentor >> this project. >> >> * In what ways will this project benefit the wider Haskell community? >> >> While the project itself isn't one of the core ones (such as GHC, >> Haddock and Cabal), I feel that there are a couple of benefits to the >> community: >> >> 1. Work on Yi (now and in the future) will undoubtedly spawn new >> Haskell libraries usable in other projects. My personal >> experience with Yi shows that it's actually very comfortable to >> write a generic library which does what we need and then having >> a separate package which uses the library to actually interact >> with Yi. >> >> 2. Haskellers come closer to escaping the ELisp/vimscript hell. We >> can get a nicer programming environment, made and extensible in >> the language of our choice and get to use all the libraries >> that we're used to while we're at it. >> >> 3. We'll have more Real World? Haskell applications. On a more >> serious note, it can serve as a good example of how to do >> certain things with Haskell: off the top of my head, it >> demonstrates the use of dyre and gtk2hs in a real-world >> scenario rather than a 5 line example on the Haskell wiki. If >> the project is successful, we can add concurrency to this. >> >> Other than the Haskell community in general, this project should >> benefit anyone with some interest in text editors. I think it's >> safe to say that happens to be a large majority of Haskellers: >> most of us want nicer integration with Haskell tools and >> libraries[citation needed] and now it'll be possible through >> direct, type-checked library access. >> >> * Can you give some more detailed design of what precisely you intend >> to achieve? >> >> The concurrency goal will involve careful study of Yi's inner >> workings in order to try and accommodate concurrency in Yi's >> editor state. There are various ways to do concurrency and the >> first part of the project will concentrate on settling for one. An >> example of two different ways is to extend the existing Yi engine >> with classical tools (MVars, channels) to accommodate for >> concurrency that way. An alternative way would be to modify the >> engine so that concurrency support is natural. Such experiment was >> started [here](https://github.com/ethercrow/y) using the sodium >> FRP package which would give us concurrency ?for free?. The >> experiment is not complete and this is the kind of thing that will >> first be explored. >> >> Of course once we settle for a method, time will be spent >> implementing it. In the end, this should allow us to do things >> such as fire Yi events periodically or do network transfers >> without having to halt the whole editor. Editors such as emacs >> which are single-threaded effectively hop back-and-forth between >> tasks on a single thread. We aim to provide the ability to simply >> have tasks on different threads which allows us to take advantage >> of system resources much better. >> >> The second part of the project is to make Yi more usable and >> hackable. Usability here involves fixing bugs apparent to the user >> and hackability involves bugs apparent to developers. Further, >> as part of usability, I plan to implement as many editor modes as >> I find time for. >> >> Specifically, here are some open bugs that I hope to either fix or >> to make a considerate progress on: #445, #397, #517, #519, #515, >> #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, >> #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, >> #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. >> >> All the bug numbers can be viewed on >> [GitHub](https://github.com/yi-editor/yi/issues/). Please note >> that some of these are documentation bugs: Yi suffers from poor >> documentation and I believe that's what the main problems in >> gaining developers and users has been. When time or area I'm >> working on allows, missing documentation will be written. >> >> If I find any issue that have been fixed or are no longer >> applicable, the reports will simply be closed. The issues are very >> varied: unicode problems, keymap problems, highlighter problems, >> reloading problems, testing problems, mode problems? There is >> certainly enough work to entertain anyone for a longer amount of >> time while making Yi visibly better. >> >> The list of issues is simply an indicator of which problems the >> second goal of the project will concentrate on, rather than as a >> promise of which bugs are guaranteed to be fixed by the end of it. >> >> Alongside this goal, I'll write any modes for Yi as I find time >> for them. The completion of concurrency part of the project allows >> us to write many of the modes frequently requested by people >> wishing to use Yi which are currently impossible/unfeasible to >> write. >> >> * What deliverables do you think are reasonable targets? Can you >> outline an approximate schedule of milestones? >> >> The plan is based on the GSoC time line: >> 20 April - 19 May ? while this is a bonding period, I'm already a >> part of the Yi community and have a fair grasp of it. I'd start to >> look into this project as early as this period (and in fact I plan >> to make steps towards it before this date which means some of the >> outlined issues might get fixed early ;) ). >> >> 19 May - 23 June ? coding period; by this point I expect to have >> decided on which concurrency model we'll use and have a good idea >> of how it'll be implemented. By the end of this period, >> concurrency should either be completed or nearly done, depending >> on any unexpected problems that might come up. The deliverable >> would be Yi with (at least some) concurrency support. >> >> 24 June - 11 August ? second part of the coding period; work on >> any of the listed (or unlisted bugs) and finish up concurrency if >> it is still not done. Write extra Yi modes, libraries and >> documentation as time allows. >> >> 11 August - 18 August ? post-coding period; write any missing >> documentation, promote any cool new stuff we wrote ;) While I can >> not think of a specific deliverable, many bugs should now be >> fixed, Yi should have a lot more documentation, tests and modes. >> >> As a final note regarding the time line, it is not strictly >> necessary that the project implements concurrency first: while >> some bugs might need such support, many simply do not. If it's >> convenient to fix something that I had originally planned to for >> the second part of the project, I'll do so. >> >> * What relevant experience do you have? e.g. Have you coded anything >> in Haskell? Have you contributed to any other open source software? >> Been studying advanced courses in a related topic? >> >> Second year CS student. I program on regular basis using Haskell. >> I contribute to a bunch of FOSS projects as it seems necessary >> (see [my GitHub](https://github.com/Fuuzetsu)). >> I have successfully completed GSOC in 2013 which involved working >> on Haddock. To this day I help out with Haddock which often >> involves looking at the large GHC code base. >> >> * In what ways do you envisage interacting with the wider Haskell >> community during your project? e.g. How would you seek help on >> something your mentor wasn't able to deal with? How will you get >> others interested in what you are doing? >> >> I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated >> onto Haskell Planet. I'm active on IRC and many Haskell-related >> mailing lists. IRC, mailing lists and any relevant literature is >> where I'd seek help were I to get stuck on something my mentor >> can't help me with. I find that news about Yi are very popular and >> get propagated by the community itself very easily so I doubt >> there will be any problem getting people interested. >> >> I'm very easily reachable over e-mail and IRC and all the >> development is done in public. >> >> * Why do you think you would be the best person to tackle this >> project? >> >> I've been interested in Yi for a couple of months and have already >> wrote some commits, closed quite a few issues and filed even more >> issues on my own. I have access to the Yi repository and >> I help anyone looking to get started with Yi. I have about 2 years of >> Haskell experience and had my fair share of staring at library >> code. >> >> As mentioned before, I'm active as a member of the community and >> help out with one of the core Haskell projects (Haddock). >> >> >> -- >> Mateusz K. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskel... at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Michal Antkiewicz, M.Sc., Ph.D Research Engineer Network for the Engineering of Complex Software-Intensive Systems (NECSIS) University of Waterloo http://gsd.uwaterloo.ca/mantkiew mantkiew at gsd.uwaterloo.ca -------------- next part -------------- An HTML attachment was scrubbed... URL: From omeragacan at gmail.com Mon Mar 10 16:22:19 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Mon, 10 Mar 2014 18:22:19 +0200 Subject: [Haskell-cafe] [GSOC] haskell-type-exts? In-Reply-To: References: Message-ID: This is actually very interesting project, IMO. I'll be applying to another idea( https://ghc.haskell.org/trac/summer-of-code/ticket/1608 ) but I'll keep an eye on this project too, just to see how it's going. I hope your proposal gets accepted and you finish this before the deadline :-) --- ?mer Sinan A?acan http://osa1.net 2014-03-10 18:16 GMT+02:00 Andy Morris : > On the GSOC ideas page for haskell.org is haskell-type-exts[1], which--as the name may suggest :)--is a proposal for a typechecker for haskell-src-exts. > > It doesn't seem to have got much attention, having only a single comment from two years ago, and I haven't seen anyone talking about it here or elsewhere. I guess this is still something that would be useful, so unless anyone has a reason why not, I'd like to apply to do it. I'll probably start working on the application later today unless some objections surface :) > > (Is Niklas Broberg subscribed to this list? If so: would you still be willing to mentor this project?) > > [1] https://ghc.haskell.org/trac/summer-of-code/ticket/1620 > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From fuuzetsu at fuuzetsu.co.uk Mon Mar 10 16:27:33 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 10 Mar 2014 16:27:33 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <20140310161347.GA25759@sniper> References: <531DD5BD.8090005@fuuzetsu.co.uk> <20140310161347.GA25759@sniper> Message-ID: <531DE7F5.7020005@fuuzetsu.co.uk> On 10/03/14 16:13, Roman Cheplyaka wrote: > * Mateusz Kowalczyk [2014-03-10 15:09:49+0000] >> Greetings, >> >> GSOC 2014 proposal period opens in ~4 hours and I'm hoping to >> participate this year as well. This time around I'd quite like to work >> on Yi. As we did last year, I think it's worthwhile to put up the >> proposals on caf? for people to comment on before they are submitted on >> Google's site. >> >> I paste it in full below so that it is easier to respond to parts of it >> (although I do ask that you don't quote the whole thing if it's not >> necessary). In case any changes happen, the most up-to-date version >> should be at https://gist.github.com/Fuuzetsu/9462709 >> >> Please feel free to nitpick on anything, throw in suggestions and ask >> for clarifications. I will give 5 days of discussion period on this >> after which point I'll submit it on Google's site. I appreciate all >> feedback. > > From what I've seen, the less uncertainty there is in a GSoC project, the better > it works. For example, the situation in your past GSoC project where it was > decided in the middle that instead of implementing markdown syntax you're going > to do other things is undesirable, IMO. That was indeed unfortunate. Well, technically Markdown was only part of the project and ?the other things? were the other part of the project. I do understand where you're coming from however. > 3 months is a very short time for a research project. (By research I mean not > academic research, but finding a way (or the best way) to do something.) > And here you're basically saying "there are several ways to do that, we'll > figure out what to do as we go". We're aware of this. The problem is that if I were to conduct this research starting today and it takes a week to settle on which approach we'll take, we end up with close to no discussion period as the proposal submissions are open for 10 days. I left it open like this because it's an implementation detail: after playing with it for a few days, it might turn out that the FRP approach is actually amazing and we should do that. I'd rather not tie myself to a specific implementation before even considering other options. If I state today that we'll use STM, I'm stuck with STM even if it turns out a terrible idea. In the end the goal is to allow for concurrency in the editor state, and that much should be clear. > If, on the other hand, it was already decided what the right architecture for > concurrency in Yi should be, and it was just a matter of someone doing the work, > it would be a good project. In this case, deciding on the right architecture is part of doing the work. > Roman > -- Mateusz K. From vagif.verdi at gmail.com Mon Mar 10 16:28:50 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Mon, 10 Mar 2014 09:28:50 -0700 (PDT) Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: >there's already hdevtools There you go. Another one! See what i'm saying? So much wasted effort and a dozen of half baked programs all of which implement low hanging fruit of the same set of basic features and have no resources left to deliver truly powerful and polished capabilities. On Monday, March 10, 2014 9:22:16 AM UTC-7, Michal Antkiewicz wrote: > > > >> I would say making ghci a full-blown IDE backend akin lisps slime-swank >> or clojure nrepl would be the best approach. >> > there's already hdevtools which plays that role - it provides all sorts of > information to an IDE, like types, location of declarations, etc. It's a > background process and it's quite responsive (tries to be incremental). I > don't know how it is implemented and whether it is a wrapper around GHCi. > > But I agree that all IDEs should simply use GHCi as the official IDE > backend. Maybe some parts from scion/hdevtools/ghc-mod/etc. could be pulled > back into GHCi? > > Michal > > >> >> >> >> On Monday, March 10, 2014 8:09:49 AM UTC-7, Mateusz Kowalczyk wrote: >> >>> Greetings, >>> >>> GSOC 2014 proposal period opens in ~4 hours and I'm hoping to >>> participate this year as well. This time around I'd quite like to work >>> on Yi. As we did last year, I think it's worthwhile to put up the >>> proposals on caf? for people to comment on before they are submitted on >>> Google's site. >>> >>> I paste it in full below so that it is easier to respond to parts of it >>> (although I do ask that you don't quote the whole thing if it's not >>> necessary). In case any changes happen, the most up-to-date version >>> should be at https://gist.github.com/Fuuzetsu/9462709 >>> >>> Please feel free to nitpick on anything, throw in suggestions and ask >>> for clarifications. I will give 5 days of discussion period on this >>> after which point I'll submit it on Google's site. I appreciate all >>> feedback. >>> >>> Thanks! >>> >>> >>> Yi concurrency, usability and hackability >>> ------------------------------------------ >>> >>> * What is the goal of the project you propose to do? >>> >>> There are two main goals of the project: the first is to implement >>> concurrency in the Yi text editor. The second aim is to start >>> bringing Yi into the territory of usable and hackable editors. >>> >>> Dmitry Ivanov who's currently in charge of Yi has agreed to mentor >>> this project. >>> >>> * In what ways will this project benefit the wider Haskell community? >>> >>> While the project itself isn't one of the core ones (such as GHC, >>> Haddock and Cabal), I feel that there are a couple of benefits to >>> the >>> community: >>> >>> 1. Work on Yi (now and in the future) will undoubtedly spawn new >>> Haskell libraries usable in other projects. My personal >>> experience with Yi shows that it's actually very comfortable to >>> write a generic library which does what we need and then having >>> a separate package which uses the library to actually interact >>> with Yi. >>> >>> 2. Haskellers come closer to escaping the ELisp/vimscript hell. We >>> can get a nicer programming environment, made and extensible in >>> the language of our choice and get to use all the libraries >>> that we're used to while we're at it. >>> >>> 3. We'll have more Real World? Haskell applications. On a more >>> serious note, it can serve as a good example of how to do >>> certain things with Haskell: off the top of my head, it >>> demonstrates the use of dyre and gtk2hs in a real-world >>> scenario rather than a 5 line example on the Haskell wiki. If >>> the project is successful, we can add concurrency to this. >>> >>> Other than the Haskell community in general, this project should >>> benefit anyone with some interest in text editors. I think it's >>> safe to say that happens to be a large majority of Haskellers: >>> most of us want nicer integration with Haskell tools and >>> libraries[citation needed] and now it'll be possible through >>> direct, type-checked library access. >>> >>> * Can you give some more detailed design of what precisely you intend >>> to achieve? >>> >>> The concurrency goal will involve careful study of Yi's inner >>> workings in order to try and accommodate concurrency in Yi's >>> editor state. There are various ways to do concurrency and the >>> first part of the project will concentrate on settling for one. An >>> example of two different ways is to extend the existing Yi engine >>> with classical tools (MVars, channels) to accommodate for >>> concurrency that way. An alternative way would be to modify the >>> engine so that concurrency support is natural. Such experiment was >>> started [here](https://github.com/ethercrow/y) using the sodium >>> FRP package which would give us concurrency ?for free?. The >>> experiment is not complete and this is the kind of thing that will >>> first be explored. >>> >>> Of course once we settle for a method, time will be spent >>> implementing it. In the end, this should allow us to do things >>> such as fire Yi events periodically or do network transfers >>> without having to halt the whole editor. Editors such as emacs >>> which are single-threaded effectively hop back-and-forth between >>> tasks on a single thread. We aim to provide the ability to simply >>> have tasks on different threads which allows us to take advantage >>> of system resources much better. >>> >>> The second part of the project is to make Yi more usable and >>> hackable. Usability here involves fixing bugs apparent to the user >>> and hackability involves bugs apparent to developers. Further, >>> as part of usability, I plan to implement as many editor modes as >>> I find time for. >>> >>> Specifically, here are some open bugs that I hope to either fix or >>> to make a considerate progress on: #445, #397, #517, #519, #515, >>> #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, >>> #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, >>> #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. >>> >>> All the bug numbers can be viewed on >>> [GitHub](https://github.com/yi-editor/yi/issues/). Please note >>> that some of these are documentation bugs: Yi suffers from poor >>> documentation and I believe that's what the main problems in >>> gaining developers and users has been. When time or area I'm >>> working on allows, missing documentation will be written. >>> >>> If I find any issue that have been fixed or are no longer >>> applicable, the reports will simply be closed. The issues are very >>> varied: unicode problems, keymap problems, highlighter problems, >>> reloading problems, testing problems, mode problems? There is >>> certainly enough work to entertain anyone for a longer amount of >>> time while making Yi visibly better. >>> >>> The list of issues is simply an indicator of which problems the >>> second goal of the project will concentrate on, rather than as a >>> promise of which bugs are guaranteed to be fixed by the end of it. >>> >>> Alongside this goal, I'll write any modes for Yi as I find time >>> for them. The completion of concurrency part of the project allows >>> us to write many of the modes frequently requested by people >>> wishing to use Yi which are currently impossible/unfeasible to >>> write. >>> >>> * What deliverables do you think are reasonable targets? Can you >>> outline an approximate schedule of milestones? >>> >>> The plan is based on the GSoC time line: >>> 20 April - 19 May ? while this is a bonding period, I'm already a >>> part of the Yi community and have a fair grasp of it. I'd start to >>> look into this project as early as this period (and in fact I plan >>> to make steps towards it before this date which means some of the >>> outlined issues might get fixed early ;) ). >>> >>> 19 May - 23 June ? coding period; by this point I expect to have >>> decided on which concurrency model we'll use and have a good idea >>> of how it'll be implemented. By the end of this period, >>> concurrency should either be completed or nearly done, depending >>> on any unexpected problems that might come up. The deliverable >>> would be Yi with (at least some) concurrency support. >>> >>> 24 June - 11 August ? second part of the coding period; work on >>> any of the listed (or unlisted bugs) and finish up concurrency if >>> it is still not done. Write extra Yi modes, libraries and >>> documentation as time allows. >>> >>> 11 August - 18 August ? post-coding period; write any missing >>> documentation, promote any cool new stuff we wrote ;) While I can >>> not think of a specific deliverable, many bugs should now be >>> fixed, Yi should have a lot more documentation, tests and modes. >>> >>> As a final note regarding the time line, it is not strictly >>> necessary that the project implements concurrency first: while >>> some bugs might need such support, many simply do not. If it's >>> convenient to fix something that I had originally planned to for >>> the second part of the project, I'll do so. >>> >>> * What relevant experience do you have? e.g. Have you coded anything >>> in Haskell? Have you contributed to any other open source software? >>> Been studying advanced courses in a related topic? >>> >>> Second year CS student. I program on regular basis using Haskell. >>> I contribute to a bunch of FOSS projects as it seems necessary >>> (see [my GitHub](https://github.com/Fuuzetsu)). >>> I have successfully completed GSOC in 2013 which involved working >>> on Haddock. To this day I help out with Haddock which often >>> involves looking at the large GHC code base. >>> >>> * In what ways do you envisage interacting with the wider Haskell >>> community during your project? e.g. How would you seek help on >>> something your mentor wasn't able to deal with? How will you get >>> others interested in what you are doing? >>> >>> I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated >>> onto Haskell Planet. I'm active on IRC and many Haskell-related >>> mailing lists. IRC, mailing lists and any relevant literature is >>> where I'd seek help were I to get stuck on something my mentor >>> can't help me with. I find that news about Yi are very popular and >>> get propagated by the community itself very easily so I doubt >>> there will be any problem getting people interested. >>> >>> I'm very easily reachable over e-mail and IRC and all the >>> development is done in public. >>> >>> * Why do you think you would be the best person to tackle this >>> project? >>> >>> I've been interested in Yi for a couple of months and have already >>> wrote some commits, closed quite a few issues and filed even more >>> issues on my own. I have access to the Yi repository and >>> I help anyone looking to get started with Yi. I have about 2 years >>> of >>> Haskell experience and had my fair share of staring at library >>> code. >>> >>> As mentioned before, I'm active as a member of the community and >>> help out with one of the core Haskell projects (Haddock). >>> >>> >>> -- >>> Mateusz K. >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskel... at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskel... at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > > -- > Michal Antkiewicz, M.Sc., Ph.D > Research Engineer > Network for the Engineering of Complex Software-Intensive Systems (NECSIS) > > University of Waterloo > http://gsd.uwaterloo.ca/mantkiew > mant... at gsd.uwaterloo.ca > -------------- next part -------------- An HTML attachment was scrubbed... URL: From roma at ro-che.info Mon Mar 10 16:29:06 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 10 Mar 2014 18:29:06 +0200 Subject: [Haskell-cafe] [GSOC] haskell-type-exts? In-Reply-To: References: Message-ID: <20140310162906.GA26069@sniper> * Andy Morris [2014-03-10 17:16:08+0100] > On the GSOC ideas page for haskell.org is haskell-type-exts[1], which?as the name may suggest :)?is a proposal for a typechecker for haskell-src-exts. > > It doesn't seem to have got much attention, having only a single comment from two years ago, and I haven't seen anyone talking about it here or elsewhere. I guess this is still something that would be useful, so unless anyone has a reason why not, I'd like to apply to do it. I'll probably start working on the application later today unless some objections surface :) > > (Is Niklas Broberg subscribed to this list? If so: would you still be willing to mentor this project?) > > [1] https://ghc.haskell.org/trac/summer-of-code/ticket/1620 It was already accepted for GSoC (and worked on) a couple of years ago. Sadly, it hasn't got much attention since then. http://cleantypecheck.wordpress.com/ Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From fuuzetsu at fuuzetsu.co.uk Mon Mar 10 16:40:34 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 10 Mar 2014 16:40:34 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: <531DEB02.5060400@fuuzetsu.co.uk> On 10/03/14 16:28, Vagif Verdi wrote: >> there's already hdevtools > > There you go. Another one! See what i'm saying? So much wasted effort and a > dozen of half baked programs all of which implement low hanging fruit of > the same set of basic features and have no resources left to deliver truly > powerful and polished capabilities. > > FYI, Yi doesn't aim to be an editor for Haskell (although we certainly strive to support it for obvious reasons). It aims to be written and ?scriptable? in Haskell but in the end that's more or less where it ends. Yi certainly doesn't aim to be a Haskell IDE! We have in fact some support for variety of things. Here are the just the lexers that Yi currently has. -rw-r--r-- 1 shana shana 3135 Dec 23 23:53 Abella.x -rw-r--r-- 1 shana shana 6192 Mar 10 12:19 Alex.hs -rw-r--r-- 1 shana shana 460 Dec 13 04:29 BasicTemplate.x -rw-r--r-- 1 shana shana 4396 Mar 10 12:19 Cabal.x -rw-r--r-- 1 shana shana 3804 Jan 7 18:51 common.hsinc -rw-r--r-- 1 shana shana 1172 Mar 10 12:19 Compilation.x -rw-r--r-- 1 shana shana 4294 Mar 10 12:19 Cplusplus.x -rw-r--r-- 1 shana shana 4294 Mar 10 12:19 C.x -rw-r--r-- 1 shana shana 3360 Dec 13 04:29 GitCommit.x -rw-r--r-- 1 shana shana 5995 Mar 10 12:19 GNUMake.x -rw-r--r-- 1 shana shana 10378 Mar 10 12:19 Haskell.x -rw-r--r-- 1 shana shana 9664 Dec 23 23:53 JavaScript.x -rw-r--r-- 1 shana shana 4229 Mar 10 12:19 Java.x -rw-r--r-- 1 shana shana 1806 Mar 10 12:19 JSON.x -rw-r--r-- 1 shana shana 16615 Mar 10 12:19 Latex.x -rw-r--r-- 1 shana shana 9427 Dec 13 04:29 LiterateHaskell.x -rw-r--r-- 1 shana shana 4466 Mar 10 12:19 ObjectiveC.x -rw-r--r-- 1 shana shana 4263 Dec 23 23:53 OCaml.x -rw-r--r-- 1 shana shana 3438 Mar 10 12:19 Ott.x -rw-r--r-- 1 shana shana 15750 Mar 10 12:19 Perl.x -rw-r--r-- 1 shana shana 3520 Mar 10 12:19 Python.x -rw-r--r-- 1 shana shana 4179 Mar 10 12:19 Ruby.x -rw-r--r-- 1 shana shana 3191 Mar 10 12:19 Srmc.x -rw-r--r-- 1 shana shana 914 Mar 10 12:19 SVNCommit.x -rw-r--r-- 1 shana shana 648 Jan 15 10:16 Whitespace.x To further reinforce what I'm trying to say, if we ever needed some IDE-like features for Haskell, we could certainly use hdevtools: they are 2 completely different projects, without any real overlap. I hope this clears it up. -- Mateusz K. From semen at trygub.com Mon Mar 10 16:54:36 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Mon, 10 Mar 2014 16:54:36 +0000 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140310145936.GA22969@nanodesu.talocan.mine.nu> References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> Message-ID: <20140310165436.GA54191@inanna.trygub.com> Hi Niklas, On Mon, Mar 10, 2014 at 02:59:36PM +0100, Niklas Haas wrote: > On Mon, 10 Mar 2014 14:54:14 +0100, Niklas Haas wrote: > > You can derive Data using the DeriveDataTypeable extension and then use > > the toConstr :: Data a => a -> Constr method to obtain the Constr (which > > has a Show instance that in this case just returns "A", "B" etc.) > > Oops, you are asking about the other direction. Well, you're in luck > here too - Data has readConstr :: DataType -> String -> Maybe Constr. Great! But how do I recover the actual constructor? E.g., f :: String -> Constr f s = fromMaybe (error "error in f") $ readConstr (dataTypeOf $ B 1) s gives me back Data.Data.Constr (not D). I was hoping for something along the lines f "A" $ 1 to get back a value A 1 of type D, etc. Many thanks, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From allbery.b at gmail.com Mon Mar 10 17:05:41 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Mon, 10 Mar 2014 13:05:41 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: On Mon, Mar 10, 2014 at 12:28 PM, Vagif Verdi wrote: > >there's already hdevtools > > There you go. Another one! See what i'm saying? So much wasted effort and > a dozen of half baked programs all of which implement low hanging fruit of > the same set of basic features and have no resources left to deliver truly > powerful and polished capabilities. > And what exactly stops your one-to-rule-them-all from just becoming yet another one? (Or: what exactly means that the world will flock to your proposal instead of continuing to do what it already does?) As far as I can see, it is based on wishful thinking alone. Build a consensus *first* and make sure you're serving everyone else's needs and that everyone else is interested. Otherwise you end up with https://xkcd.com/927/. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From vagif.verdi at gmail.com Mon Mar 10 17:19:33 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Mon, 10 Mar 2014 10:19:33 -0700 (PDT) Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: <33c64001-efa1-4ef7-9b6f-7364bba5d71a@googlegroups.com> >And what exactly stops your one-to-rule-them-all from just becoming yet another one? We are not discussing here what tool is the best and try to mandate everyone to use it. We are discussing how to efficiently use the scarce development resources (time, money) for the benefit of haskell community. It does not matter if the specific tool will succeed in adoption or not. Trying to create one is still the best course of action. >Build a consensus *first* The consensus is already there. It is obvious the demand for such tool is high, hence many (failed) attempts. Failed because of the lack of resources and coordination. >As far as I can see, it is based on wishful thinking alone. I already pointed at existing successful implementations (clojure's nrepl and lisps slime-swank). If they can do it, so can we. On Monday, March 10, 2014 10:05:41 AM UTC-7, Brandon Allbery wrote: > > On Mon, Mar 10, 2014 at 12:28 PM, Vagif Verdi > > wrote: > >> >there's already hdevtools >> >> There you go. Another one! See what i'm saying? So much wasted effort and >> a dozen of half baked programs all of which implement low hanging fruit of >> the same set of basic features and have no resources left to deliver truly >> powerful and polished capabilities. >> > > And what exactly stops your one-to-rule-them-all from just becoming yet > another one? (Or: what exactly means that the world will flock to your > proposal instead of continuing to do what it already does?) As far as I can > see, it is based on wishful thinking alone. > > Build a consensus *first* and make sure you're serving everyone else's > needs and that everyone else is interested. Otherwise you end up with > https://xkcd.com/927/. > > -- > brandon s allbery kf8nh sine nomine > associates > allb... at gmail.com > ball... at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > [image: Close] Read more >> Options >> [image: Visit Answers.com] -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Mon Mar 10 17:27:50 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Mon, 10 Mar 2014 18:27:50 +0100 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: <20140310172750.GA23431@machine> On Mon, Mar 10, 2014 at 09:28:50AM -0700, Vagif Verdi wrote: > There you go. Another one! See what i'm saying? So much wasted effort and a > dozen of half baked programs all of which implement low hanging fruit of the > same set of basic features and have no resources left to deliver truly powerful > and polished capabilities. Sorry, but I don't like this kind of attitude. Wasted effort? People having fun hacking around and perhaps don't want to coordinate with several people to get something done, because that's what they already have to do at their day job. It's a lot of work to get something powerful and polished, and in a lot of cases this doesn't even happen in a commercial setting and even fewer people will do it in their spare time. > > > On Monday, March 10, 2014 9:22:16 AM UTC-7, Michal Antkiewicz wrote: > > > > > I would say making ghci a full-blown IDE backend akin lisps slime-swank > or clojure nrepl would be the best approach. > > there's already hdevtools which plays that role - it provides all sorts of > information to an IDE, like types, location of declarations, etc. It's a > background process and it's quite responsive (tries to be incremental). I > don't know how it is implemented and whether it is a wrapper around GHCi. > > But I agree that all IDEs should simply use GHCi as the official IDE > backend. Maybe some parts from scion/hdevtools/ghc-mod/etc. could be pulled > back into GHCi? > > Michal > > > > > > On Monday, March 10, 2014 8:09:49 AM UTC-7, Mateusz Kowalczyk wrote: > > Greetings, > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > participate this year as well. This time around I'd quite like to > work > on Yi. As we did last year, I think it's worthwhile to put up the > proposals on caf? for people to comment on before they are > submitted on > Google's site. > > I paste it in full below so that it is easier to respond to parts > of it > (although I do ask that you don't quote the whole thing if it's not > necessary). In case any changes happen, the most up-to-date version > should be at https://gist.github.com/Fuuzetsu/9462709 > > Please feel free to nitpick on anything, throw in suggestions and > ask > for clarifications. I will give 5 days of discussion period on this > after which point I'll submit it on Google's site. I appreciate all > feedback. > > Thanks! > > > Yi concurrency, usability and hackability > ------------------------------------------ > > * What is the goal of the project you propose to do? > > There are two main goals of the project: the first is to > implement > concurrency in the Yi text editor. The second aim is to start > bringing Yi into the territory of usable and hackable editors. > > Dmitry Ivanov who's currently in charge of Yi has agreed to > mentor > this project. > > * In what ways will this project benefit the wider Haskell > community? > > While the project itself isn't one of the core ones (such as > GHC, > Haddock and Cabal), I feel that there are a couple of benefits > to the > community: > > 1. Work on Yi (now and in the future) will undoubtedly spawn > new > Haskell libraries usable in other projects. My personal > experience with Yi shows that it's actually very comfortable > to > write a generic library which does what we need and then > having > a separate package which uses the library to actually > interact > with Yi. > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. > We > can get a nicer programming environment, made and extensible > in > the language of our choice and get to use all the libraries > that we're used to while we're at it. > > 3. We'll have more Real World? Haskell applications. On a more > serious note, it can serve as a good example of how to do > certain things with Haskell: off the top of my head, it > demonstrates the use of dyre and gtk2hs in a real-world > scenario rather than a 5 line example on the Haskell wiki. > If > the project is successful, we can add concurrency to this. > > Other than the Haskell community in general, this project > should > benefit anyone with some interest in text editors. I think it's > safe to say that happens to be a large majority of Haskellers: > most of us want nicer integration with Haskell tools and > libraries[citation needed] and now it'll be possible through > direct, type-checked library access. > > * Can you give some more detailed design of what precisely you > intend > to achieve? > > The concurrency goal will involve careful study of Yi's inner > workings in order to try and accommodate concurrency in Yi's > editor state. There are various ways to do concurrency and the > first part of the project will concentrate on settling for one. > An > example of two different ways is to extend the existing Yi > engine > with classical tools (MVars, channels) to accommodate for > concurrency that way. An alternative way would be to modify the > engine so that concurrency support is natural. Such experiment > was > started [here](https://github.com/ethercrow/y) using the sodium > FRP package which would give us concurrency ?for free?. The > experiment is not complete and this is the kind of thing that > will > first be explored. > > Of course once we settle for a method, time will be spent > implementing it. In the end, this should allow us to do things > such as fire Yi events periodically or do network transfers > without having to halt the whole editor. Editors such as emacs > which are single-threaded effectively hop back-and-forth > between > tasks on a single thread. We aim to provide the ability to > simply > have tasks on different threads which allows us to take > advantage > of system resources much better. > > The second part of the project is to make Yi more usable and > hackable. Usability here involves fixing bugs apparent to the > user > and hackability involves bugs apparent to developers. Further, > as part of usability, I plan to implement as many editor modes > as > I find time for. > > Specifically, here are some open bugs that I hope to either fix > or > to make a considerate progress on: #445, #397, #517, #519, # > 515, > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, # > 390, > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > All the bug numbers can be viewed on > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > that some of these are documentation bugs: Yi suffers from poor > documentation and I believe that's what the main problems in > gaining developers and users has been. When time or area I'm > working on allows, missing documentation will be written. > > If I find any issue that have been fixed or are no longer > applicable, the reports will simply be closed. The issues are > very > varied: unicode problems, keymap problems, highlighter > problems, > reloading problems, testing problems, mode problems? There is > certainly enough work to entertain anyone for a longer amount > of > time while making Yi visibly better. > > The list of issues is simply an indicator of which problems the > second goal of the project will concentrate on, rather than as > a > promise of which bugs are guaranteed to be fixed by the end of > it. > > Alongside this goal, I'll write any modes for Yi as I find time > for them. The completion of concurrency part of the project > allows > us to write many of the modes frequently requested by people > wishing to use Yi which are currently impossible/unfeasible to > write. > > * What deliverables do you think are reasonable targets? Can you > outline an approximate schedule of milestones? > > The plan is based on the GSoC time line: > 20 April - 19 May ? while this is a bonding period, I'm already > a > part of the Yi community and have a fair grasp of it. I'd start > to > look into this project as early as this period (and in fact I > plan > to make steps towards it before this date which means some of > the > outlined issues might get fixed early ;) ). > > 19 May - 23 June ? coding period; by this point I expect to > have > decided on which concurrency model we'll use and have a good > idea > of how it'll be implemented. By the end of this period, > concurrency should either be completed or nearly done, > depending > on any unexpected problems that might come up. The deliverable > would be Yi with (at least some) concurrency support. > > 24 June - 11 August ? second part of the coding period; work on > any of the listed (or unlisted bugs) and finish up concurrency > if > it is still not done. Write extra Yi modes, libraries and > documentation as time allows. > > 11 August - 18 August ? post-coding period; write any missing > documentation, promote any cool new stuff we wrote ;) While I > can > not think of a specific deliverable, many bugs should now be > fixed, Yi should have a lot more documentation, tests and > modes. > > As a final note regarding the time line, it is not strictly > necessary that the project implements concurrency first: while > some bugs might need such support, many simply do not. If it's > convenient to fix something that I had originally planned to > for > the second part of the project, I'll do so. > > * What relevant experience do you have? e.g. Have you coded > anything > in Haskell? Have you contributed to any other open source > software? > Been studying advanced courses in a related topic? > > Second year CS student. I program on regular basis using > Haskell. > I contribute to a bunch of FOSS projects as it seems necessary > (see [my GitHub](https://github.com/Fuuzetsu)). > I have successfully completed GSOC in 2013 which involved > working > on Haddock. To this day I help out with Haddock which often > involves looking at the large GHC code base. > > * In what ways do you envisage interacting with the wider Haskell > community during your project? e.g. How would you seek help on > something your mentor wasn't able to deal with? How will you get > others interested in what you are doing? > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets > propagated > onto Haskell Planet. I'm active on IRC and many Haskell-related > mailing lists. IRC, mailing lists and any relevant literature > is > where I'd seek help were I to get stuck on something my mentor > can't help me with. I find that news about Yi are very popular > and > get propagated by the community itself very easily so I doubt > there will be any problem getting people interested. > > I'm very easily reachable over e-mail and IRC and all the > development is done in public. > > * Why do you think you would be the best person to tackle this > project? > > I've been interested in Yi for a couple of months and have > already > wrote some commits, closed quite a few issues and filed even > more > issues on my own. I have access to the Yi repository and > I help anyone looking to get started with Yi. I have about 2 > years of > Haskell experience and had my fair share of staring at library > code. > > As mentioned before, I'm active as a member of the community > and > help out with one of the core Haskell projects (Haddock). > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > -- > Michal Antkiewicz, M.Sc., Ph.D > Research Engineer > Network for the Engineering of Complex Software-Intensive Systems (NECSIS) > > University of Waterloo > http://gsd.uwaterloo.ca/mantkiew > mant... at gsd.uwaterloo.ca > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mail at nh2.me Mon Mar 10 17:35:19 2014 From: mail at nh2.me (=?ISO-8859-1?Q?Niklas_Hamb=FCchen?=) Date: Mon, 10 Mar 2014 17:35:19 +0000 Subject: [Haskell-cafe] On Haskell IDEs Message-ID: <531DF7D7.3060304@nh2.me> On 10/03/14 16:22, Michal Antkiewicz wrote:> > > I would say making ghci a full-blown IDE backend akin lisps > slime-swank or clojure nrepl would be the best approach. > > there's already hdevtools which plays that role - it provides all sorts > of information to an IDE, like types, location of declarations, etc. > It's a background process and it's quite responsive (tries to be > incremental). I don't know how it is implemented and whether it is a > wrapper around GHCi. > > But I agree that all IDEs should simply use GHCi as the official IDE > backend. Maybe some parts from scion/hdevtools/ghc-mod/etc. could be > pulled back into GHCi? > > Michal Mateusz just clarified that his proposal is more about improving Yi as an editor than making it more of a Haskell IDE, so I am replying to this in a new thread. Alexandr Ruchkin and me maintain SublimeHaskell, the most-used Haskell plugin for Sublime Text. It integrates ghc-mod, hdevtools, cabal etc. and can do things like showing compile errors, completing imports, displaying the type of an expression in the buffer or insert it over a function declaration. When we want to change a Haskell file's content, we get the relevant info from, say, ghc-mod and then do the actual modification logic in the editor scripting language (in our case Python). We recognise that this logic is duplicated in pretty much every editor with such Haskell features, and at the same think that Haskell is a much nicer language to program this logic. Technically, it is also less error prone to work with ghc-mod's API than with its command line interface. That's why we seem to move more and more to do the actual modifications in an external Haskell program, and have the part in the actual editor be as minimal as possible. Alexandr started a project called "hsdev" (https://github.com/mvoidex/hsdev) for that. It is very editor-agnostic and we think that sharing something like that across editors makes sense since it could save plugin writers a lot of time. The ideas is that you would tell this tool to perform an action, e.g. "import missing imports" or "go to declaration", and it would do it for you instead implementing the buffer changes in your editor plugin. There is one problem with that: Editors don't deal well with other programs editing currently opened files. In Sublime's case, the buffer will automatically refresh, but it is very well possible that your caret position and undo history get lost, which totally interrupts the work flow. So I was wondering what the most minimal interface would be that allows your editor to be aware of the changes that an external program (HaRE, hsdev, etc.) would like to make to your code base. At the moment we consider having hsdev outputting a diff format that describes the changes, and then each editor would have to implement a simple interpreter that goes through the files, applying the changes. That way we can avoid an external file change and the problems that come with it. The Sublime-related discussion about this is at https://github.com/SublimeHaskell/SublimeHaskell/pull/132#issuecomment-33888678. I think that IDE-style "smart language features" might have a better place in cross-editor tools than in the editors themselves. ghc-mod is a successful example. I also think that most Haskell-IDE maintainers would agree (please correct me otherwise) that doing program transformation features is much more pleasant to do in Haskell than in Elisp, Vimscript, Python or Java, and that specifying out a cross-editor "modification description" and implementing the smart parts in a shareable tool might save us all a lot of time. It looks like Scion (http://code.google.com/p/scion-lib/) followed similar goals, but doesn't seem to have found wide adoption and no real development for multiple years. I would welcome a discussion about why past attempts to this failed, whether you think that having a monolithic Haskell-IDE-tool output diffs for any editor to apply would lower the barriers for making editors Haskell-smart, and if you are an editor plugin maintainer, if you agree that sharing common functionality is worth it. From vagif.verdi at gmail.com Mon Mar 10 18:41:15 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Mon, 10 Mar 2014 11:41:15 -0700 (PDT) Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <531DF7D7.3060304@nh2.me> References: <531DF7D7.3060304@nh2.me> Message-ID: <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> >It integrates ghc-mod, hdevtools, cabal ... > Alexandr started a project called "hsdev" (https://github.com/mvoidex/hsdev) This is an excellent illustration of how fragmentation in this specific area hurts community. Not only you are forced to use 3 different tools (ghc-mod, hdevtools, cabal) each of which basically provides the same service but in an incompatible and incomplete way. But you decided to create yet another one instead of contributing to the ones you already use (they are all open source) The problem here is that most of IDE features require some environment that loads and keeps track of the entire project information. Unfortunately approach of creating separate small utilities not gonna work in this case, because each utility would have to load entire project to be able to provide some useful functionality. This is clearly the case where concerted community effort is required, similar to cabal. And we do have a good base for it: ghci On Monday, March 10, 2014 10:35:19 AM UTC-7, Niklas Hamb?chen wrote: > > On 10/03/14 16:22, Michal Antkiewicz wrote:> > > > > I would say making ghci a full-blown IDE backend akin lisps > > slime-swank or clojure nrepl would be the best approach. > > > > there's already hdevtools which plays that role - it provides all sorts > > of information to an IDE, like types, location of declarations, etc. > > It's a background process and it's quite responsive (tries to be > > incremental). I don't know how it is implemented and whether it is a > > wrapper around GHCi. > > > > But I agree that all IDEs should simply use GHCi as the official IDE > > backend. Maybe some parts from scion/hdevtools/ghc-mod/etc. could be > > pulled back into GHCi? > > > > Michal > > Mateusz just clarified that his proposal is more about improving Yi as > an editor than making it more of a Haskell IDE, so I am replying to this > in a new thread. > > Alexandr Ruchkin and me maintain SublimeHaskell, the most-used Haskell > plugin for Sublime Text. > > It integrates ghc-mod, hdevtools, cabal etc. and can do things like > showing compile errors, completing imports, displaying the type of an > expression in the buffer or insert it over a function declaration. > > When we want to change a Haskell file's content, we get the relevant > info from, say, ghc-mod and then do the actual modification logic in the > editor scripting language (in our case Python). > We recognise that this logic is duplicated in pretty much every editor > with such Haskell features, and at the same think that Haskell is a much > nicer language to program this logic. Technically, it is also less error > prone to work with ghc-mod's API than with its command line interface. > > That's why we seem to move more and more to do the actual modifications > in an external Haskell program, and have the part in the actual editor > be as minimal as possible. Alexandr started a project called "hsdev" > (https://github.com/mvoidex/hsdev) for that. It is very editor-agnostic > and we think that sharing something like that across editors makes sense > since it could save plugin writers a lot of time. The ideas is that you > would tell this tool to perform an action, e.g. "import missing imports" > or "go to declaration", and it would do it for you instead implementing > the buffer changes in your editor plugin. > > There is one problem with that: Editors don't deal well with other > programs editing currently opened files. In Sublime's case, the buffer > will automatically refresh, but it is very well possible that your caret > position and undo history get lost, which totally interrupts the work > flow. > > So I was wondering what the most minimal interface would be that allows > your editor to be aware of the changes that an external program (HaRE, > hsdev, etc.) would like to make to your code base. > > At the moment we consider having hsdev outputting a diff format that > describes the changes, and then each editor would have to implement a > simple interpreter that goes through the files, applying the changes. > > That way we can avoid an external file change and the problems that come > with it. > > The Sublime-related discussion about this is at > > https://github.com/SublimeHaskell/SublimeHaskell/pull/132#issuecomment-33888678. > > > I think that IDE-style "smart language features" might have a better > place in cross-editor tools than in the editors themselves. ghc-mod is a > successful example. > > I also think that most Haskell-IDE maintainers would agree (please > correct me otherwise) that doing program transformation features is much > more pleasant to do in Haskell than in Elisp, Vimscript, Python or Java, > and that specifying out a cross-editor "modification description" and > implementing the smart parts in a shareable tool might save us all a lot > of time. > > It looks like Scion (http://code.google.com/p/scion-lib/) followed > similar goals, but doesn't seem to have found wide adoption and no real > development for multiple years. > > I would welcome a discussion about why past attempts to this failed, > whether you think that having a monolithic Haskell-IDE-tool output diffs > for any editor to apply would lower the barriers for making editors > Haskell-smart, and if you are an editor plugin maintainer, if you agree > that sharing common functionality is worth it. > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Mar 10 19:20:25 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 10 Mar 2014 15:20:25 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <20140310172750.GA23431@machine> References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> <20140310172750.GA23431@machine> Message-ID: guys, move the yak shaving / shedding to another thread please, lets Help give Mateusz feedback for his proposal on contributing to a haskell editor. What are some ancillary sub tasks you can do independent of the concurrency piece? Concurrency is hard and evil and tricky. It'd be great if you work that out, but *IF* that blows up into a thorny mess, what are some other sub projects you plan to do either way? -Carter On Mon, Mar 10, 2014 at 1:27 PM, Daniel Trstenjak < daniel.trstenjak at gmail.com> wrote: > > On Mon, Mar 10, 2014 at 09:28:50AM -0700, Vagif Verdi wrote: > > There you go. Another one! See what i'm saying? So much wasted effort > and a > > dozen of half baked programs all of which implement low hanging fruit of > the > > same set of basic features and have no resources left to deliver truly > powerful > > and polished capabilities. > > Sorry, but I don't like this kind of attitude. > > Wasted effort? People having fun hacking around and perhaps don't want > to coordinate with several people to get something done, because that's > what they already have to do at their day job. > > It's a lot of work to get something powerful and polished, and in a lot > of cases this doesn't even happen in a commercial setting and even > fewer people will do it in their spare time. > > > > > > > > > > > > > > > On Monday, March 10, 2014 9:22:16 AM UTC-7, Michal Antkiewicz wrote: > > > > > > > > > > I would say making ghci a full-blown IDE backend akin lisps > slime-swank > > or clojure nrepl would be the best approach. > > > > there's already hdevtools which plays that role - it provides all > sorts of > > information to an IDE, like types, location of declarations, etc. > It's a > > background process and it's quite responsive (tries to be > incremental). I > > don't know how it is implemented and whether it is a wrapper around > GHCi. > > > > But I agree that all IDEs should simply use GHCi as the official IDE > > backend. Maybe some parts from scion/hdevtools/ghc-mod/etc. could be > pulled > > back into GHCi? > > > > Michal > > > > > > > > > > > > On Monday, March 10, 2014 8:09:49 AM UTC-7, Mateusz Kowalczyk > wrote: > > > > Greetings, > > > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > > participate this year as well. This time around I'd quite > like to > > work > > on Yi. As we did last year, I think it's worthwhile to put > up the > > proposals on caf? for people to comment on before they are > > submitted on > > Google's site. > > > > I paste it in full below so that it is easier to respond to > parts > > of it > > (although I do ask that you don't quote the whole thing if > it's not > > necessary). In case any changes happen, the most up-to-date > version > > should be at https://gist.github.com/Fuuzetsu/9462709 > > > > Please feel free to nitpick on anything, throw in > suggestions and > > ask > > for clarifications. I will give 5 days of discussion period > on this > > after which point I'll submit it on Google's site. I > appreciate all > > feedback. > > > > Thanks! > > > > > > Yi concurrency, usability and hackability > > ------------------------------------------ > > > > * What is the goal of the project you propose to do? > > > > There are two main goals of the project: the first is to > > implement > > concurrency in the Yi text editor. The second aim is to > start > > bringing Yi into the territory of usable and hackable > editors. > > > > Dmitry Ivanov who's currently in charge of Yi has agreed > to > > mentor > > this project. > > > > * In what ways will this project benefit the wider Haskell > > community? > > > > While the project itself isn't one of the core ones > (such as > > GHC, > > Haddock and Cabal), I feel that there are a couple of > benefits > > to the > > community: > > > > 1. Work on Yi (now and in the future) will undoubtedly > spawn > > new > > Haskell libraries usable in other projects. My > personal > > experience with Yi shows that it's actually very > comfortable > > to > > write a generic library which does what we need and > then > > having > > a separate package which uses the library to actually > > interact > > with Yi. > > > > 2. Haskellers come closer to escaping the > ELisp/vimscript hell. > > We > > can get a nicer programming environment, made and > extensible > > in > > the language of our choice and get to use all the > libraries > > that we're used to while we're at it. > > > > 3. We'll have more Real World? Haskell applications. On > a more > > serious note, it can serve as a good example of how > to do > > certain things with Haskell: off the top of my head, > it > > demonstrates the use of dyre and gtk2hs in a > real-world > > scenario rather than a 5 line example on the Haskell > wiki. > > If > > the project is successful, we can add concurrency to > this. > > > > Other than the Haskell community in general, this project > > should > > benefit anyone with some interest in text editors. I > think it's > > safe to say that happens to be a large majority of > Haskellers: > > most of us want nicer integration with Haskell tools and > > libraries[citation needed] and now it'll be possible > through > > direct, type-checked library access. > > > > * Can you give some more detailed design of what precisely > you > > intend > > to achieve? > > > > The concurrency goal will involve careful study of Yi's > inner > > workings in order to try and accommodate concurrency in > Yi's > > editor state. There are various ways to do concurrency > and the > > first part of the project will concentrate on settling > for one. > > An > > example of two different ways is to extend the existing > Yi > > engine > > with classical tools (MVars, channels) to accommodate for > > concurrency that way. An alternative way would be to > modify the > > engine so that concurrency support is natural. Such > experiment > > was > > started [here](https://github.com/ethercrow/y) using > the sodium > > FRP package which would give us concurrency ?for free?. > The > > experiment is not complete and this is the kind of thing > that > > will > > first be explored. > > > > Of course once we settle for a method, time will be spent > > implementing it. In the end, this should allow us to do > things > > such as fire Yi events periodically or do network > transfers > > without having to halt the whole editor. Editors such as > emacs > > which are single-threaded effectively hop back-and-forth > > between > > tasks on a single thread. We aim to provide the ability > to > > simply > > have tasks on different threads which allows us to take > > advantage > > of system resources much better. > > > > The second part of the project is to make Yi more usable > and > > hackable. Usability here involves fixing bugs apparent > to the > > user > > and hackability involves bugs apparent to developers. > Further, > > as part of usability, I plan to implement as many editor > modes > > as > > I find time for. > > > > Specifically, here are some open bugs that I hope to > either fix > > or > > to make a considerate progress on: #445, #397, #517, > #519, # > > 515, > > #516, #513 (concurrency), #512, #507, #504, #502, #501, > #499, > > #497, #493, #487, #478, #477, #468, #465, #399, #396, > #391, # > > 390, > > #382, #322, #295, #172, #160, #106, #145, #112, #82, > #509. > > > > All the bug numbers can be viewed on > > [GitHub](https://github.com/yi-editor/yi/issues/). > Please note > > that some of these are documentation bugs: Yi suffers > from poor > > documentation and I believe that's what the main > problems in > > gaining developers and users has been. When time or area > I'm > > working on allows, missing documentation will be written. > > > > If I find any issue that have been fixed or are no longer > > applicable, the reports will simply be closed. The > issues are > > very > > varied: unicode problems, keymap problems, highlighter > > problems, > > reloading problems, testing problems, mode problems? > There is > > certainly enough work to entertain anyone for a longer > amount > > of > > time while making Yi visibly better. > > > > The list of issues is simply an indicator of which > problems the > > second goal of the project will concentrate on, rather > than as > > a > > promise of which bugs are guaranteed to be fixed by the > end of > > it. > > > > Alongside this goal, I'll write any modes for Yi as I > find time > > for them. The completion of concurrency part of the > project > > allows > > us to write many of the modes frequently requested by > people > > wishing to use Yi which are currently > impossible/unfeasible to > > write. > > > > * What deliverables do you think are reasonable targets? Can > you > > outline an approximate schedule of milestones? > > > > The plan is based on the GSoC time line: > > 20 April - 19 May ? while this is a bonding period, I'm > already > > a > > part of the Yi community and have a fair grasp of it. > I'd start > > to > > look into this project as early as this period (and in > fact I > > plan > > to make steps towards it before this date which means > some of > > the > > outlined issues might get fixed early ;) ). > > > > 19 May - 23 June ? coding period; by this point I expect > to > > have > > decided on which concurrency model we'll use and have a > good > > idea > > of how it'll be implemented. By the end of this period, > > concurrency should either be completed or nearly done, > > depending > > on any unexpected problems that might come up. The > deliverable > > would be Yi with (at least some) concurrency support. > > > > 24 June - 11 August ? second part of the coding period; > work on > > any of the listed (or unlisted bugs) and finish up > concurrency > > if > > it is still not done. Write extra Yi modes, libraries and > > documentation as time allows. > > > > 11 August - 18 August ? post-coding period; write any > missing > > documentation, promote any cool new stuff we wrote ;) > While I > > can > > not think of a specific deliverable, many bugs should > now be > > fixed, Yi should have a lot more documentation, tests and > > modes. > > > > As a final note regarding the time line, it is not > strictly > > necessary that the project implements concurrency first: > while > > some bugs might need such support, many simply do not. > If it's > > convenient to fix something that I had originally > planned to > > for > > the second part of the project, I'll do so. > > > > * What relevant experience do you have? e.g. Have you coded > > anything > > in Haskell? Have you contributed to any other open source > > software? > > Been studying advanced courses in a related topic? > > > > Second year CS student. I program on regular basis using > > Haskell. > > I contribute to a bunch of FOSS projects as it seems > necessary > > (see [my GitHub](https://github.com/Fuuzetsu)). > > I have successfully completed GSOC in 2013 which involved > > working > > on Haddock. To this day I help out with Haddock which > often > > involves looking at the large GHC code base. > > > > * In what ways do you envisage interacting with the wider > Haskell > > community during your project? e.g. How would you seek > help on > > something your mentor wasn't able to deal with? How will > you get > > others interested in what you are doing? > > > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets > > propagated > > onto Haskell Planet. I'm active on IRC and many > Haskell-related > > mailing lists. IRC, mailing lists and any relevant > literature > > is > > where I'd seek help were I to get stuck on something my > mentor > > can't help me with. I find that news about Yi are very > popular > > and > > get propagated by the community itself very easily so I > doubt > > there will be any problem getting people interested. > > > > I'm very easily reachable over e-mail and IRC and all the > > development is done in public. > > > > * Why do you think you would be the best person to tackle > this > > project? > > > > I've been interested in Yi for a couple of months and > have > > already > > wrote some commits, closed quite a few issues and filed > even > > more > > issues on my own. I have access to the Yi repository and > > I help anyone looking to get started with Yi. I have > about 2 > > years of > > Haskell experience and had my fair share of staring at > library > > code. > > > > As mentioned before, I'm active as a member of the > community > > and > > help out with one of the core Haskell projects (Haddock). > > > > > > -- > > Mateusz K. > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskel... at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskel... at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > > > -- > > Michal Antkiewicz, M.Sc., Ph.D > > Research Engineer > > Network for the Engineering of Complex Software-Intensive Systems > (NECSIS) > > > > University of Waterloo > > http://gsd.uwaterloo.ca/mantkiew > > mant... at gsd.uwaterloo.ca > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Mon Mar 10 19:32:25 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Mon, 10 Mar 2014 19:32:25 +0000 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> Message-ID: <531E1349.8070003@nh2.me> On 10/03/14 18:41, Vagif Verdi wrote: > This is an excellent illustration of how fragmentation in this specific > area hurts community. Not only you are forced to use 3 different tools > (ghc-mod, hdevtools, cabal) each of which basically provides the same > service but in an incompatible and incomplete way. But you decided to > create yet another one instead of contributing to the ones you already > use (they are all open source) I'm not sure what you mean to say; ghc-mod and cabal certainly do not do the same. Hsdev doesn't either, and claiming that we don't contribute to these projects is strange. From vagif.verdi at gmail.com Mon Mar 10 19:44:23 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Mon, 10 Mar 2014 12:44:23 -0700 (PDT) Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <531E1349.8070003@nh2.me> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> Message-ID: Sorry, i meant ghci not cabal. As for hsdev, in order to provide its features it will have to load and keep track of entire project information which is already done by ghc-mod and hdevtools separately. So you ushould see how much effort is wasted on doing the same thing again and again in each of 4 different tools (ghci, ghc-mod, hdevtools and hsdev) On Monday, March 10, 2014 12:32:25 PM UTC-7, Niklas Hamb?chen wrote: > > On 10/03/14 18:41, Vagif Verdi wrote: > > This is an excellent illustration of how fragmentation in this specific > > area hurts community. Not only you are forced to use 3 different tools > > (ghc-mod, hdevtools, cabal) each of which basically provides the same > > service but in an incompatible and incomplete way. But you decided to > > create yet another one instead of contributing to the ones you already > > use (they are all open source) > > I'm not sure what you mean to say; ghc-mod and cabal certainly do not do > the same. Hsdev doesn't either, and claiming that we don't contribute to > these projects is strange. > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mantkiew at gsd.uwaterloo.ca Mon Mar 10 20:53:51 2014 From: mantkiew at gsd.uwaterloo.ca (Michal Antkiewicz) Date: Mon, 10 Mar 2014 16:53:51 -0400 Subject: [Haskell-cafe] Fwd: On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> Message-ID: Vagif, it's all about separation of concerns and low coupling. There's no point adding all possible functionality into GHCi because it'll become too big and most users won't use most of it (ever used MSoft Word?). The ecosystem can be architected in some service-oriented way, in which some tools will be data providers and others will provide some added layers of functionality. That does not imply that all tools will need to maintain their own independent copies of information about the project. There largest overlap, as far as I can see, is between ghc-mod and hdevtools. Both are proofs of concept. Maybe parts could actually be incorporated into GHCi. hsdev seems to be specialized to source file editing and should remain separate but it can use the other ones as data sources (incl. Cabal and GHCi). Re: wasted effort. I don't agree. hdevtools was made to make a point that running a process in the background which maintains data and answers queries is much more responsive to the user than otherwise. And it has proven that point. Now, GHCi can learn that lesson and provide something similar, if that indeed belongs to GHCi's scope. Finally, all this is just speculation since I don't know exactly what the actual overlap among the tools is. It might be smaller than we think. Cheers, Michal On Mon, Mar 10, 2014 at 3:44 PM, Vagif Verdi wrote: > Sorry, i meant ghci not cabal. > > As for hsdev, in order to provide its features it will have to load and > keep track of entire project information which is already done by ghc-mod > and hdevtools separately. So you ushould see how much effort is wasted on > doing the same thing again and again in each of 4 different tools (ghci, > ghc-mod, hdevtools and hsdev) > > > On Monday, March 10, 2014 12:32:25 PM UTC-7, Niklas Hamb?chen wrote: > >> On 10/03/14 18:41, Vagif Verdi wrote: >> > This is an excellent illustration of how fragmentation in this specific >> > area hurts community. Not only you are forced to use 3 different tools >> > (ghc-mod, hdevtools, cabal) each of which basically provides the same >> > service but in an incompatible and incomplete way. But you decided to >> > create yet another one instead of contributing to the ones you already >> > use (they are all open source) >> >> I'm not sure what you mean to say; ghc-mod and cabal certainly do not do >> the same. Hsdev doesn't either, and claiming that we don't contribute to >> these projects is strange. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskel... at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Michal Antkiewicz, M.Sc., Ph.D Research Engineer Network for the Engineering of Complex Software-Intensive Systems (NECSIS) University of Waterloo http://gsd.uwaterloo.ca/mantkiew mantkiew at gsd.uwaterloo.ca -------------- next part -------------- An HTML attachment was scrubbed... URL: From achudnov at gmail.com Mon Mar 10 20:59:36 2014 From: achudnov at gmail.com (Andrey Chudnov) Date: Mon, 10 Mar 2014 16:59:36 -0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> Message-ID: <531E27B8.3050902@gmail.com> While I do not condone Mr. Verdi's verbal bashing of the efforts of the Haskell community to provide development tools, I do feel his pain. There is quite a bit of divided effort which seems to result in having multiple inferior solutions. My all-time favorite is ghc-mod because "it just works", but it can be very slow for large projects, especially involving template-haskell (and there are no easy fixes for that). HDevTools, in theory, is great: a persistent server, allowing incremental builds/checks etc., but it's oblivious to .cabal files, let alone sandboxes, which makes it completely impractical for any degree of serious Haskell development (on that note, how come pull request 30 [1] is still open?! /rant). Finally, GHCi is supposed to be enough for IDE support in editors. However, as I understand it, the problem is that its output is not easily parsed and, hence, consumed by editors; on top of that, using it with .cabal files and sandboxes requires calling 'cabal repl', so using another tool. So, maybe, GHCi could be augmented with an easily consumed output format (like JSON), and 'cabal' be given support for that mode as well? Since it's that time of the year again (I mean, the GSoC proposal time :)), maybe, someone would look into this idea? [1] https://github.com/bitc/hdevtools/pull/30 /Andrey On 03/10/2014 03:44 PM, Vagif Verdi wrote: > Sorry, i meant ghci not cabal. > > As for hsdev, in order to provide its features it will have to load > and keep track of entire project information which is already done by > ghc-mod and hdevtools separately. So you ushould see how much effort > is wasted on doing the same thing again and again in each of 4 > different tools (ghci, ghc-mod, hdevtools and hsdev) > > On Monday, March 10, 2014 12:32:25 PM UTC-7, Niklas Hamb?chen wrote: > > On 10/03/14 18:41, Vagif Verdi wrote: > > This is an excellent illustration of how fragmentation in this > specific > > area hurts community. Not only you are forced to use 3 different > tools > > (ghc-mod, hdevtools, cabal) each of which basically provides the > same > > service but in an incompatible and incomplete way. But you > decided to > > create yet another one instead of contributing to the ones you > already > > use (they are all open source) > > I'm not sure what you mean to say; ghc-mod and cabal certainly do > not do > the same. Hsdev doesn't either, and claiming that we don't > contribute to > these projects is strange. > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From mantkiew at gsd.uwaterloo.ca Mon Mar 10 21:11:55 2014 From: mantkiew at gsd.uwaterloo.ca (Michal Antkiewicz) Date: Mon, 10 Mar 2014 17:11:55 -0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <531E27B8.3050902@gmail.com> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> Message-ID: Cabal repl is absolutely great! Are there any reasons why it couldn't provide all information that ghc-mod and hdevtools do? It could be run as a background process, right? It knows about sandboxes as well. That would be a great SoC project - extend cabal repls to subsume ghc-mod and hdevtools. Michal On Mon, Mar 10, 2014 at 4:59 PM, Andrey Chudnov wrote: > While I do not condone Mr. Verdi's verbal bashing of the efforts of the > Haskell community to provide development tools, I do feel his pain. There > is quite a bit of divided effort which seems to result in having multiple > inferior solutions. > > My all-time favorite is ghc-mod because "it just works", but it can be > very slow for large projects, especially involving template-haskell (and > there are no easy fixes for that). > > HDevTools, in theory, is great: a persistent server, allowing incremental > builds/checks etc., but it's oblivious to .cabal files, let alone > sandboxes, which makes it completely impractical for any degree of serious > Haskell development (on that note, how come pull request 30 [1] is still > open?! /rant). > > Finally, GHCi is supposed to be enough for IDE support in editors. > However, as I understand it, the problem is that its output is not easily > parsed and, hence, consumed by editors; on top of that, using it with > .cabal files and sandboxes requires calling 'cabal repl', so using another > tool. > > So, maybe, GHCi could be augmented with an easily consumed output format > (like JSON), and 'cabal' be given support for that mode as well? Since it's > that time of the year again (I mean, the GSoC proposal time :)), maybe, > someone would look into this idea? > > [1] https://github.com/bitc/hdevtools/pull/30 > > /Andrey > > > On 03/10/2014 03:44 PM, Vagif Verdi wrote: > > Sorry, i meant ghci not cabal. > > As for hsdev, in order to provide its features it will have to load and > keep track of entire project information which is already done by ghc-mod > and hdevtools separately. So you ushould see how much effort is wasted on > doing the same thing again and again in each of 4 different tools (ghci, > ghc-mod, hdevtools and hsdev) > > On Monday, March 10, 2014 12:32:25 PM UTC-7, Niklas Hamb?chen wrote: >> >> On 10/03/14 18:41, Vagif Verdi wrote: >> > This is an excellent illustration of how fragmentation in this specific >> > area hurts community. Not only you are forced to use 3 different tools >> > (ghc-mod, hdevtools, cabal) each of which basically provides the same >> > service but in an incompatible and incomplete way. But you decided to >> > create yet another one instead of contributing to the ones you already >> > use (they are all open source) >> >> I'm not sure what you mean to say; ghc-mod and cabal certainly do not do >> the same. Hsdev doesn't either, and claiming that we don't contribute to >> these projects is strange. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskel... at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing listHaskell-Cafe at haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From achudnov at gmail.com Mon Mar 10 21:22:23 2014 From: achudnov at gmail.com (Andrey Chudnov) Date: Mon, 10 Mar 2014 17:22:23 -0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> Message-ID: <531E2D0F.7000201@gmail.com> If we go down that road, it's not cabal-repl that would need to be extended. AFAIK, it's just a wrapper around GHCi that calls that latter with package info extracted from the cabal file and, optionally, the sandbox. So, really, it's GHCi that would need to be extended. I think, something as simple as adding an option to output JSON (or some other structured format with wide support in editors) instead of plain text would go a long way to allow editors to consume it's output: they could just pipe commands via stdin and read the JSON output via stdout, parse it and display the info in the buffer. Depending on how GHCi looks inside and how amenable it is to such modifications, it might actually be a doable summer project. Am I missing any technical gotchas? /Andrey On 03/10/2014 05:11 PM, Michal Antkiewicz wrote: > Cabal repl is absolutely great! Are there any reasons why it couldn't > provide all information that ghc-mod and hdevtools do? It could be run > as a background process, right? It knows about sandboxes as well. > > That would be a great SoC project - extend cabal repls to subsume > ghc-mod and hdevtools. > > Michal > > > On Mon, Mar 10, 2014 at 4:59 PM, Andrey Chudnov > wrote: > > While I do not condone Mr. Verdi's verbal bashing of the efforts > of the Haskell community to provide development tools, I do feel > his pain. There is quite a bit of divided effort which seems to > result in having multiple inferior solutions. > > My all-time favorite is ghc-mod because "it just works", but it > can be very slow for large projects, especially involving > template-haskell (and there are no easy fixes for that). > > HDevTools, in theory, is great: a persistent server, allowing > incremental builds/checks etc., but it's oblivious to .cabal > files, let alone sandboxes, which makes it completely impractical > for any degree of serious Haskell development (on that note, how > come pull request 30 [1] is still open?! /rant). > > Finally, GHCi is supposed to be enough for IDE support in editors. > However, as I understand it, the problem is that its output is not > easily parsed and, hence, consumed by editors; on top of that, > using it with .cabal files and sandboxes requires calling 'cabal > repl', so using another tool. > > So, maybe, GHCi could be augmented with an easily consumed output > format (like JSON), and 'cabal' be given support for that mode as > well? Since it's that time of the year again (I mean, the GSoC > proposal time :)), maybe, someone would look into this idea? > > [1] https://github.com/bitc/hdevtools/pull/30 > > /Andrey > > > On 03/10/2014 03:44 PM, Vagif Verdi wrote: >> Sorry, i meant ghci not cabal. >> >> As for hsdev, in order to provide its features it will have to >> load and keep track of entire project information which is >> already done by ghc-mod and hdevtools separately. So you ushould >> see how much effort is wasted on doing the same thing again and >> again in each of 4 different tools (ghci, ghc-mod, hdevtools and >> hsdev) >> >> On Monday, March 10, 2014 12:32:25 PM UTC-7, Niklas Hamb?chen wrote: >> >> On 10/03/14 18:41, Vagif Verdi wrote: >> > This is an excellent illustration of how fragmentation in >> this specific >> > area hurts community. Not only you are forced to use 3 >> different tools >> > (ghc-mod, hdevtools, cabal) each of which basically >> provides the same >> > service but in an incompatible and incomplete way. But you >> decided to >> > create yet another one instead of contributing to the ones >> you already >> > use (they are all open source) >> >> I'm not sure what you mean to say; ghc-mod and cabal >> certainly do not do >> the same. Hsdev doesn't either, and claiming that we don't >> contribute to >> these projects is strange. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskel... at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From ekmett at gmail.com Mon Mar 10 22:18:22 2014 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 10 Mar 2014 18:18:22 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> Message-ID: Yi isn't a tool designed solely to edit Haskell source code any more than vim is designed solely to edit vim-script. As far as I'm aware the only editor to swallow its tail to that point where editing other file types is largly a side-goal is emacs. ;) Leksah and Yi have very different goals. Yi could profitably exist without *any* integration with ghci for editing other languages, as its stated goal is to be an editor scriptable with Haskell, much like emacs is an editor scriptable with elisp. Leksah aspires to be an IDE. Lashing out at the existence of Yi, because it might be used by someone some day to edit Haskell seems misguided and rather off topic to the subject of working on the concurrency aspects of a text editor. -Edward On Mon, Mar 10, 2014 at 12:04 PM, Vagif Verdi wrote: > I do not think we need more haskell aware editors and IDEs. There's more > than enough already: emacs, vim, Eclipse, Leksah, Yi. What we need though > is a IDE backend so any editor can use it to provide hakell IDE features. > As it stands right now all haskell IDEs reinvent the wheel in some > incompatible manner. EclipseFp has scion, some emacs modes develop ghc-mod > backend. Leksah lives in its own world. ghci added some IDE support > features recently. This fragmentation hurts us. > > I would say making ghci a full-blown IDE backend akin lisps slime-swank or > clojure nrepl would be the best approach. > > > > On Monday, March 10, 2014 8:09:49 AM UTC-7, Mateusz Kowalczyk wrote: > >> Greetings, >> >> GSOC 2014 proposal period opens in ~4 hours and I'm hoping to >> participate this year as well. This time around I'd quite like to work >> on Yi. As we did last year, I think it's worthwhile to put up the >> proposals on caf? for people to comment on before they are submitted on >> Google's site. >> >> I paste it in full below so that it is easier to respond to parts of it >> (although I do ask that you don't quote the whole thing if it's not >> necessary). In case any changes happen, the most up-to-date version >> should be at https://gist.github.com/Fuuzetsu/9462709 >> >> Please feel free to nitpick on anything, throw in suggestions and ask >> for clarifications. I will give 5 days of discussion period on this >> after which point I'll submit it on Google's site. I appreciate all >> feedback. >> >> Thanks! >> >> >> Yi concurrency, usability and hackability >> ------------------------------------------ >> >> * What is the goal of the project you propose to do? >> >> There are two main goals of the project: the first is to implement >> concurrency in the Yi text editor. The second aim is to start >> bringing Yi into the territory of usable and hackable editors. >> >> Dmitry Ivanov who's currently in charge of Yi has agreed to mentor >> this project. >> >> * In what ways will this project benefit the wider Haskell community? >> >> While the project itself isn't one of the core ones (such as GHC, >> Haddock and Cabal), I feel that there are a couple of benefits to the >> community: >> >> 1. Work on Yi (now and in the future) will undoubtedly spawn new >> Haskell libraries usable in other projects. My personal >> experience with Yi shows that it's actually very comfortable to >> write a generic library which does what we need and then having >> a separate package which uses the library to actually interact >> with Yi. >> >> 2. Haskellers come closer to escaping the ELisp/vimscript hell. We >> can get a nicer programming environment, made and extensible in >> the language of our choice and get to use all the libraries >> that we're used to while we're at it. >> >> 3. We'll have more Real World? Haskell applications. On a more >> serious note, it can serve as a good example of how to do >> certain things with Haskell: off the top of my head, it >> demonstrates the use of dyre and gtk2hs in a real-world >> scenario rather than a 5 line example on the Haskell wiki. If >> the project is successful, we can add concurrency to this. >> >> Other than the Haskell community in general, this project should >> benefit anyone with some interest in text editors. I think it's >> safe to say that happens to be a large majority of Haskellers: >> most of us want nicer integration with Haskell tools and >> libraries[citation needed] and now it'll be possible through >> direct, type-checked library access. >> >> * Can you give some more detailed design of what precisely you intend >> to achieve? >> >> The concurrency goal will involve careful study of Yi's inner >> workings in order to try and accommodate concurrency in Yi's >> editor state. There are various ways to do concurrency and the >> first part of the project will concentrate on settling for one. An >> example of two different ways is to extend the existing Yi engine >> with classical tools (MVars, channels) to accommodate for >> concurrency that way. An alternative way would be to modify the >> engine so that concurrency support is natural. Such experiment was >> started [here](https://github.com/ethercrow/y) using the sodium >> FRP package which would give us concurrency ?for free?. The >> experiment is not complete and this is the kind of thing that will >> first be explored. >> >> Of course once we settle for a method, time will be spent >> implementing it. In the end, this should allow us to do things >> such as fire Yi events periodically or do network transfers >> without having to halt the whole editor. Editors such as emacs >> which are single-threaded effectively hop back-and-forth between >> tasks on a single thread. We aim to provide the ability to simply >> have tasks on different threads which allows us to take advantage >> of system resources much better. >> >> The second part of the project is to make Yi more usable and >> hackable. Usability here involves fixing bugs apparent to the user >> and hackability involves bugs apparent to developers. Further, >> as part of usability, I plan to implement as many editor modes as >> I find time for. >> >> Specifically, here are some open bugs that I hope to either fix or >> to make a considerate progress on: #445, #397, #517, #519, #515, >> #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, >> #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, >> #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. >> >> All the bug numbers can be viewed on >> [GitHub](https://github.com/yi-editor/yi/issues/). Please note >> that some of these are documentation bugs: Yi suffers from poor >> documentation and I believe that's what the main problems in >> gaining developers and users has been. When time or area I'm >> working on allows, missing documentation will be written. >> >> If I find any issue that have been fixed or are no longer >> applicable, the reports will simply be closed. The issues are very >> varied: unicode problems, keymap problems, highlighter problems, >> reloading problems, testing problems, mode problems? There is >> certainly enough work to entertain anyone for a longer amount of >> time while making Yi visibly better. >> >> The list of issues is simply an indicator of which problems the >> second goal of the project will concentrate on, rather than as a >> promise of which bugs are guaranteed to be fixed by the end of it. >> >> Alongside this goal, I'll write any modes for Yi as I find time >> for them. The completion of concurrency part of the project allows >> us to write many of the modes frequently requested by people >> wishing to use Yi which are currently impossible/unfeasible to >> write. >> >> * What deliverables do you think are reasonable targets? Can you >> outline an approximate schedule of milestones? >> >> The plan is based on the GSoC time line: >> 20 April - 19 May ? while this is a bonding period, I'm already a >> part of the Yi community and have a fair grasp of it. I'd start to >> look into this project as early as this period (and in fact I plan >> to make steps towards it before this date which means some of the >> outlined issues might get fixed early ;) ). >> >> 19 May - 23 June ? coding period; by this point I expect to have >> decided on which concurrency model we'll use and have a good idea >> of how it'll be implemented. By the end of this period, >> concurrency should either be completed or nearly done, depending >> on any unexpected problems that might come up. The deliverable >> would be Yi with (at least some) concurrency support. >> >> 24 June - 11 August ? second part of the coding period; work on >> any of the listed (or unlisted bugs) and finish up concurrency if >> it is still not done. Write extra Yi modes, libraries and >> documentation as time allows. >> >> 11 August - 18 August ? post-coding period; write any missing >> documentation, promote any cool new stuff we wrote ;) While I can >> not think of a specific deliverable, many bugs should now be >> fixed, Yi should have a lot more documentation, tests and modes. >> >> As a final note regarding the time line, it is not strictly >> necessary that the project implements concurrency first: while >> some bugs might need such support, many simply do not. If it's >> convenient to fix something that I had originally planned to for >> the second part of the project, I'll do so. >> >> * What relevant experience do you have? e.g. Have you coded anything >> in Haskell? Have you contributed to any other open source software? >> Been studying advanced courses in a related topic? >> >> Second year CS student. I program on regular basis using Haskell. >> I contribute to a bunch of FOSS projects as it seems necessary >> (see [my GitHub](https://github.com/Fuuzetsu)). >> I have successfully completed GSOC in 2013 which involved working >> on Haddock. To this day I help out with Haddock which often >> involves looking at the large GHC code base. >> >> * In what ways do you envisage interacting with the wider Haskell >> community during your project? e.g. How would you seek help on >> something your mentor wasn't able to deal with? How will you get >> others interested in what you are doing? >> >> I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated >> onto Haskell Planet. I'm active on IRC and many Haskell-related >> mailing lists. IRC, mailing lists and any relevant literature is >> where I'd seek help were I to get stuck on something my mentor >> can't help me with. I find that news about Yi are very popular and >> get propagated by the community itself very easily so I doubt >> there will be any problem getting people interested. >> >> I'm very easily reachable over e-mail and IRC and all the >> development is done in public. >> >> * Why do you think you would be the best person to tackle this >> project? >> >> I've been interested in Yi for a couple of months and have already >> wrote some commits, closed quite a few issues and filed even more >> issues on my own. I have access to the Yi repository and >> I help anyone looking to get started with Yi. I have about 2 years of >> Haskell experience and had my fair share of staring at library >> code. >> >> As mentioned before, I'm active as a member of the community and >> help out with one of the core Haskell projects (Haddock). >> >> >> -- >> Mateusz K. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskel... at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From stephen.tetley at gmail.com Mon Mar 10 22:26:39 2014 From: stephen.tetley at gmail.com (Stephen Tetley) Date: Mon, 10 Mar 2014 22:26:39 +0000 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Hi ?mer Sounds good, good luck with the project. One thing I struggled with was re-implementing the type checker as the Caml implementation uses ref cells. Fortunately there are a lot of tutorials on the web covering type checking with a good few using Haskell and greater or lesser degree of assignment. On 9 March 2014 22:07, ?mer Sinan A?acan wrote: > Hi Stephen, > >> Are you rewriting Eijiro Sumii's MinCaml in Haskell? > > Yes! > [Snip] From jwlato at gmail.com Mon Mar 10 23:43:39 2014 From: jwlato at gmail.com (John Lato) Date: Mon, 10 Mar 2014 16:43:39 -0700 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531DD5BD.8090005@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: I think this has potential to be a good proposal, although I have a few concerns: 1. It's a bifurcated proposal, with two major components. I think the proposal would be stronger if you address more either how adding concurrency will help with all those tickets, or other features that should be supported in yi but can't with the current design. You give a few examples further down, but at present it reads (to me) as though you want to add concurrency just for the sake of it. 2. Despite the well-known fact that Concurrency is Hard, in many ways Haskell provides better tools to manage concurrency than many other languages. There are so many options, that sometimes people have difficulty knowing what to pick. This work seems to provide an obvious benefit to the Haskell community in that others can see what you chose, why, and how it worked in practice (including any pitfalls). Out of your benefits to the Haskell community, IMHO 2) and 3) are solid but 1) is rather general and conceivably would apply to any proposal. Unless you have specific library deliverables in mind, I'd suggest starting with your third point. These aren't really technical concerns, rather they're about the language/focus of your proposal. Although I do think this is an ambitious project, the scope as you've defined it might be manageable within a GSOC. That said, I wouldn't be surprised if adding concurrency takes more time than you've allocated, or is a source of new bugs that you'll have to fix, thereby preventing you from working on the bugs you've already identified. Cheers, John L. On Mon, Mar 10, 2014 at 8:09 AM, Mateusz Kowalczyk wrote: > Greetings, > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > participate this year as well. This time around I'd quite like to work > on Yi. As we did last year, I think it's worthwhile to put up the > proposals on caf? for people to comment on before they are submitted on > Google's site. > > I paste it in full below so that it is easier to respond to parts of it > (although I do ask that you don't quote the whole thing if it's not > necessary). In case any changes happen, the most up-to-date version > should be at https://gist.github.com/Fuuzetsu/9462709 > > Please feel free to nitpick on anything, throw in suggestions and ask > for clarifications. I will give 5 days of discussion period on this > after which point I'll submit it on Google's site. I appreciate all > feedback. > > Thanks! > > > Yi concurrency, usability and hackability > ------------------------------------------ > > * What is the goal of the project you propose to do? > > There are two main goals of the project: the first is to implement > concurrency in the Yi text editor. The second aim is to start > bringing Yi into the territory of usable and hackable editors. > > Dmitry Ivanov who's currently in charge of Yi has agreed to mentor > this project. > > * In what ways will this project benefit the wider Haskell community? > > While the project itself isn't one of the core ones (such as GHC, > Haddock and Cabal), I feel that there are a couple of benefits to the > community: > > 1. Work on Yi (now and in the future) will undoubtedly spawn new > Haskell libraries usable in other projects. My personal > experience with Yi shows that it's actually very comfortable to > write a generic library which does what we need and then having > a separate package which uses the library to actually interact > with Yi. > > 2. Haskellers come closer to escaping the ELisp/vimscript hell. We > can get a nicer programming environment, made and extensible in > the language of our choice and get to use all the libraries > that we're used to while we're at it. > > 3. We'll have more Real World(tm) Haskell applications. On a more > serious note, it can serve as a good example of how to do > certain things with Haskell: off the top of my head, it > demonstrates the use of dyre and gtk2hs in a real-world > scenario rather than a 5 line example on the Haskell wiki. If > the project is successful, we can add concurrency to this. > > Other than the Haskell community in general, this project should > benefit anyone with some interest in text editors. I think it's > safe to say that happens to be a large majority of Haskellers: > most of us want nicer integration with Haskell tools and > libraries[citation needed] and now it'll be possible through > direct, type-checked library access. > > * Can you give some more detailed design of what precisely you intend > to achieve? > > The concurrency goal will involve careful study of Yi's inner > workings in order to try and accommodate concurrency in Yi's > editor state. There are various ways to do concurrency and the > first part of the project will concentrate on settling for one. An > example of two different ways is to extend the existing Yi engine > with classical tools (MVars, channels) to accommodate for > concurrency that way. An alternative way would be to modify the > engine so that concurrency support is natural. Such experiment was > started [here](https://github.com/ethercrow/y) using the sodium > FRP package which would give us concurrency 'for free'. The > experiment is not complete and this is the kind of thing that will > first be explored. > > Of course once we settle for a method, time will be spent > implementing it. In the end, this should allow us to do things > such as fire Yi events periodically or do network transfers > without having to halt the whole editor. Editors such as emacs > which are single-threaded effectively hop back-and-forth between > tasks on a single thread. We aim to provide the ability to simply > have tasks on different threads which allows us to take advantage > of system resources much better. > > The second part of the project is to make Yi more usable and > hackable. Usability here involves fixing bugs apparent to the user > and hackability involves bugs apparent to developers. Further, > as part of usability, I plan to implement as many editor modes as > I find time for. > > Specifically, here are some open bugs that I hope to either fix or > to make a considerate progress on: #445, #397, #517, #519, #515, > #516, #513 (concurrency), #512, #507, #504, #502, #501, #499, > #497, #493, #487, #478, #477, #468, #465, #399, #396, #391, #390, > #382, #322, #295, #172, #160, #106, #145, #112, #82, #509. > > All the bug numbers can be viewed on > [GitHub](https://github.com/yi-editor/yi/issues/). Please note > that some of these are documentation bugs: Yi suffers from poor > documentation and I believe that's what the main problems in > gaining developers and users has been. When time or area I'm > working on allows, missing documentation will be written. > > If I find any issue that have been fixed or are no longer > applicable, the reports will simply be closed. The issues are very > varied: unicode problems, keymap problems, highlighter problems, > reloading problems, testing problems, mode problems... There is > certainly enough work to entertain anyone for a longer amount of > time while making Yi visibly better. > > The list of issues is simply an indicator of which problems the > second goal of the project will concentrate on, rather than as a > promise of which bugs are guaranteed to be fixed by the end of it. > > Alongside this goal, I'll write any modes for Yi as I find time > for them. The completion of concurrency part of the project allows > us to write many of the modes frequently requested by people > wishing to use Yi which are currently impossible/unfeasible to > write. > > * What deliverables do you think are reasonable targets? Can you > outline an approximate schedule of milestones? > > The plan is based on the GSoC time line: > 20 April - 19 May - while this is a bonding period, I'm already a > part of the Yi community and have a fair grasp of it. I'd start to > look into this project as early as this period (and in fact I plan > to make steps towards it before this date which means some of the > outlined issues might get fixed early ;) ). > > 19 May - 23 June - coding period; by this point I expect to have > decided on which concurrency model we'll use and have a good idea > of how it'll be implemented. By the end of this period, > concurrency should either be completed or nearly done, depending > on any unexpected problems that might come up. The deliverable > would be Yi with (at least some) concurrency support. > > 24 June - 11 August - second part of the coding period; work on > any of the listed (or unlisted bugs) and finish up concurrency if > it is still not done. Write extra Yi modes, libraries and > documentation as time allows. > > 11 August - 18 August - post-coding period; write any missing > documentation, promote any cool new stuff we wrote ;) While I can > not think of a specific deliverable, many bugs should now be > fixed, Yi should have a lot more documentation, tests and modes. > > As a final note regarding the time line, it is not strictly > necessary that the project implements concurrency first: while > some bugs might need such support, many simply do not. If it's > convenient to fix something that I had originally planned to for > the second part of the project, I'll do so. > > * What relevant experience do you have? e.g. Have you coded anything > in Haskell? Have you contributed to any other open source software? > Been studying advanced courses in a related topic? > > Second year CS student. I program on regular basis using Haskell. > I contribute to a bunch of FOSS projects as it seems necessary > (see [my GitHub](https://github.com/Fuuzetsu)). > I have successfully completed GSOC in 2013 which involved working > on Haddock. To this day I help out with Haddock which often > involves looking at the large GHC code base. > > * In what ways do you envisage interacting with the wider Haskell > community during your project? e.g. How would you seek help on > something your mentor wasn't able to deal with? How will you get > others interested in what you are doing? > > I have a [blog](http://fuuzetsu.co.uk/blog) which gets propagated > onto Haskell Planet. I'm active on IRC and many Haskell-related > mailing lists. IRC, mailing lists and any relevant literature is > where I'd seek help were I to get stuck on something my mentor > can't help me with. I find that news about Yi are very popular and > get propagated by the community itself very easily so I doubt > there will be any problem getting people interested. > > I'm very easily reachable over e-mail and IRC and all the > development is done in public. > > * Why do you think you would be the best person to tackle this > project? > > I've been interested in Yi for a couple of months and have already > wrote some commits, closed quite a few issues and filed even more > issues on my own. I have access to the Yi repository and > I help anyone looking to get started with Yi. I have about 2 years of > Haskell experience and had my fair share of staring at library > code. > > As mentioned before, I'm active as a member of the community and > help out with one of the core Haskell projects (Haddock). > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gbwey9 at gmail.com Mon Mar 10 22:47:26 2014 From: gbwey9 at gmail.com (gb) Date: Mon, 10 Mar 2014 22:47:26 +0000 (UTC) Subject: [Haskell-cafe] Read instance for constructors? References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> <20140310165436.GA54191@inanna.trygub.com> Message-ID: > > Great! But how do I recover the actual constructor? E.g., > > f :: String -> Constr > f s = fromMaybe (error "error in f") $ readConstr (dataTypeOf $ B 1) s > > gives me back Data.Data.Constr (not D). I was hoping for something along the lines > > f "A" $ 1 > > to get back a value > > A 1 > > of type D, etc. > > Many thanks, > S. > Here's one way: import qualified Data.Generics.Builders as B import Data.Generics.Aliases fromConstrB (B.empty `extB` (12::Int)) (f "B")::D >>> B 12 fromConstrB B.empty (f "B")::D >>> B 0 From mightybyte at gmail.com Tue Mar 11 02:39:59 2014 From: mightybyte at gmail.com (MightyByte) Date: Mon, 10 Mar 2014 22:39:59 -0400 Subject: [Haskell-cafe] Haskell Hackathon in NYC, April 4-6 (last reminder) Message-ID: Greetings, We're just under a month out from the first Hac NYC, so I wanted to send out one more reminder to the community. For the full details see the previous announcement. http://www.haskell.org/pipermail/haskell-cafe/2014-January/112362.html Once again, if you plan on coming, you must officially register by filling out our registration form [1]. Other details for travel, lodging, etc can be found on the Hac NYC wiki [2]. And if you would like to give a talk, please let us know [3] so we can schedule them. We're looking forward to seeing you here. -The Hac NYC Team [1] https://docs.google.com/forms/d/1taZtjgYozFNebLt1TR2VnKv-ovD2Yv5sOdSZzmi_xFo/viewform [2] http://www.haskell.org/haskellwiki/Hac_NYC [3] http://www.haskell.org/haskellwiki/Hac_NYC/Talks From allanegardner at gmail.com Tue Mar 11 04:31:02 2014 From: allanegardner at gmail.com (Allan Gardner) Date: Mon, 10 Mar 2014 22:31:02 -0600 Subject: [Haskell-cafe] GSOC Project Ideas Message-ID: I went through the GSOC trac, most of the Haskell IRC logs, and the Haskell idea reddit. So now I have a list of ideas (grouped by category): infrastructure: - C++ integration (e.g. finish https://github.com/ofan/hqt https://github.com/ofan/fficxx ) - Ada/Python/... integration - gobject bindings (gtk2hs stuff) - cabal improvements - Haddock flags ( https://github.com/haskell/cabal/issues/1585), custom setup improvements (https://github.com/haskell/cabal/issues/948), some sort of plugin system for tests/docs/other random things (BNFC), clean up and merge parallel build code, package management, ... - Hackage2 improvements - voting, rewrite auth system, speed up reverse-deps enough to enable on main site, package wiki/comments, deprecations w/ links, create haddock even if the package doesn't build, ... - scale up Hoogle so it can search all of hackage by default - scoutess work (integration with with hackage, ghc snapshots, ...) libraries: - email/PIM library (MIME, imap, ical, XMPP, WebDav, ... probably make use of a lot of old HaskellNet code) - comprehensive Date/Time API - there are lots of Hackage libs, but none do e.g. internationalization - aim to be backwards-compatible with time - highlight code using inferred types - HsColour + haskell-src/type-exts ? (maybe not enough for a GSOC?) - implement miscellaneous concurrent data structures - darcs improvements (performance, storage, ...) - fix pandoc conversion issues - ... (there were a lot of other libraries, but one of the blog posts said not do a library project because hackage already has too many and designing a good API from scratch is hard) GHC project ideas: - package improvements - finish multiple package stuff, sign and verify packages, ... - port GHC build system to shake (faster, progress indicators, written in Haskell, ...) - implement something like ccache or distcc for GHC - rewrite the GHC pattern overlap/exhaustiveness analysis ( https://ghc.haskell.org/trac/ghc/ticket/595, 10 years old!) - make GHC deterministic (refactor Unique + other nondeterminism sources, make a pure parser and/or typechecker API) - port Hat to the GHC api and integrate it into GHCi's :trace mode so omniscient debugging is available by default - implement typed core as another IL, either above or below old-core ("Types are Calling Conventions" paper) - other type-level programming library/project (units, extended arithmetic solver, true dependent types, linear types, ...) GHC backend-ish: - customizable RTS - remove unused RTS functions, write your own concurrency primitives, ... - resurrect Immix patches and try to get incremental GC - implement loop unrolling in GHC - allow LLVM phases to be written in Haskell (bindings already used, so it's just dealing with the FFI's and GHC's options handling...) I've tried putting these by two people (edwardk and carter) on #haskell-gsoc, and they both said that all the GHC ideas are too hard for a GSOC. Can I get a third opinion? Also, please tell me if I left anything important out (I see a Yi proposal on this mailing list; that would be in the ... in libraries). Finally, some sort of idea of which ideas are most likely to get accepted would be helpful. https://docs.google.com/forms/d/1rEobhHwFpjzPnra9L1TmrozWNFFyAVNPmdUMCcT--3Q/viewanalyticssays the top priorities are GHC, Cabal, and Hackage, so since GHC is (apparently) out I guess that means I should look more at my Cabal, Hackage, and Hoogle ideas... is this sensible? -- Allan Gardner -------------- next part -------------- An HTML attachment was scrubbed... URL: From cesarn at mindtouch.com Tue Mar 11 04:59:36 2014 From: cesarn at mindtouch.com (Cesar Lopez) Date: Mon, 10 Mar 2014 21:59:36 -0700 Subject: [Haskell-cafe] ANNOUNCE: San Diego Haskell User Group. Message-ID: Hello everyone: I would like to announce the creation and meeting of the *San Diego Haskell User Group*, the first meeting will be held on Wednesday March 19th. 2014 at 60:30PM at MindTouch, Inc's office in downtown San Diego. Please join us! *Information about the group:* The San Diego Haskell User Group aims to bring together academics, hobbyists, and software developers to discuss real world usage of the Haskell programming language. You can follow us on twitter @loshaskelleros Information about the first meeting. *Unconference style Haskell meeting #1:* http://www.meetup.com/SanDiegoHUG/events/168606962/ Cheers cesar -------------- next part -------------- An HTML attachment was scrubbed... URL: From dagitj at gmail.com Tue Mar 11 05:39:19 2014 From: dagitj at gmail.com (Jason Dagit) Date: Mon, 10 Mar 2014 22:39:19 -0700 Subject: [Haskell-cafe] GSOC Project Ideas In-Reply-To: References: Message-ID: On Mon, Mar 10, 2014 at 9:31 PM, Allan Gardner wrote: > > I've tried putting these by two people (edwardk and carter) on > #haskell-gsoc, and they both said that all the GHC ideas are too hard for a > GSOC. Can I get a third opinion? > I absolutely agree. The thing about GSoC is that the time is short and relative to that the proposals tend to be ambitious. To make the best of the time you have, it's really important to understand what changes need to be made and to have a pretty solid idea of how you'll implement it. Of course, that's not the full story. GSoC is also an important mentoring opportunity as well. So you're not expected to know everything or all the technical details. Just keep in mind the time goes fast and that you probably won't have much time left if you need to spend time getting up to speed. The exception would be if you have previous experience with modifying ghc. In that case, it might be reasonable to do a ghc-based proposal. I hope that helps, Jason -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Mar 11 06:22:11 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 11 Mar 2014 06:22:11 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> <20140310172750.GA23431@machine> Message-ID: <531EAB93.9070200@fuuzetsu.co.uk> On 10/03/14 19:20, Carter Schonwald wrote: > guys, move the yak shaving / shedding to another thread please, > > lets Help give Mateusz feedback for his proposal on contributing to a > haskell editor. > > What are some ancillary sub tasks you can do independent of the concurrency > piece? Concurrency is hard and evil and tricky. It'd be great if you work > that out, but *IF* that blows up into a thorny mess, what are some other > sub projects you plan to do either way? > > -Carter > There are a lot. Nearly all of the other part (see the mentioned tickets) can be done without concurrency being in place which is I mention that the project isn't linear. The concurrency is not a blocker for everything else. The only thing that the concurrency blocks are editor modes that I'd like to write iff there is time, however if I do find time that means concurrency is done ;). -- Mateusz K. From carlo at carlo-hamalainen.net Tue Mar 11 06:25:35 2014 From: carlo at carlo-hamalainen.net (Carlo Hamalainen) Date: Tue, 11 Mar 2014 07:25:35 +0100 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <531E2D0F.7000201@gmail.com> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> Message-ID: <531EAC5F.9020300@carlo-hamalainen.net> On 10/03/14 22:22, Andrey Chudnov wrote: > If we go down that road, it's not cabal-repl that would need to be > extended. AFAIK, it's just a wrapper around GHCi that calls that > latter with package info extracted from the cabal file and, > optionally, the sandbox. So, really, it's GHCi that would need to be > extended. I think, something as simple as adding an option to output > JSON (or some other structured format with wide support in editors) > instead of plain text would go a long way to allow editors to consume > it's output: they could just pipe commands via stdin and read the JSON > output via stdout, parse it and display the info in the buffer. > Depending on how GHCi looks inside and how amenable it is to such > modifications, it might actually be a doable summer project. Am I > missing any technical gotchas? Regarding the data format, ghc-mod uses the GHC API to get the de-sugared and type-checked representation of a module, e.g. https://github.com/kazu-yamamoto/ghc-mod/blob/master/Language/Haskell/GhcMod/Gap.hs#L326-L337 Or, my tool ghc-imported-from needs to get the "guts" from the GHC API to get the global reader environment: https://github.com/carlohamalainen/ghc-imported-from/blob/master/Language/Haskell/GhcImportedFrom.hs#L343-L373 So my feeling is that we'd need to pass Haskell values back and forth, not just JSON. Personally I would love it if GHCi was extended in the way that you are suggesting, as it would make my tool much faster. Ditto for ghc-mod. -- Carlo Hamalainen http://carlo-hamalainen.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Mar 11 06:42:38 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 11 Mar 2014 06:42:38 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: <531EB05E.9050500@fuuzetsu.co.uk> On 10/03/14 23:43, John Lato wrote: > I think this has potential to be a good proposal, although I have a few > concerns: > > 1. It's a bifurcated proposal, with two major components. I think the > proposal would be stronger if you address more either how adding > concurrency will help with all those tickets, or other features that should > be supported in yi but can't with the current design. You give a few > examples further down, but at present it reads (to me) as though you want > to add concurrency just for the sake of it. Actually, the tickets mentioned are not affected (much) by concurrency being implemented or not. Here are some things that lack of concurrency does affect at the moment: * Can't do periodic events * Can't wait for a process output in the background (an easy test is to ask Yi to run a ?sleep 2000? system command). This is a big deal for interacting with things like flyspell or ghc-mod. * Can't do networking * Can't do When I say it can't do it, I mean ?can't do it without stopping everything else including the interface?. This is a big problem for an editor because it means we can't write many, many of the editor modes that people pretty much require nowadays: flyspell, flycheck, compilation, . What Yi can do are ?static? modes such as dired: they do not require background updates or anything of the sort so they are fine in a single thread most of the time. Any longer editor actions effectively lock up the interface for the user. I'd wager that your own text editor performs some of these actions that we couldn't feasibly implement in Yi right now. > 2. Despite the well-known fact that Concurrency is Hard, in many ways > Haskell provides better tools to manage concurrency than many other > languages. There are so many options, that sometimes people have > difficulty knowing what to pick. This work seems to provide an obvious > benefit to the Haskell community in that others can see what you chose, > why, and how it worked in practice (including any pitfalls). > > Out of your benefits to the Haskell community, IMHO 2) and 3) are solid but > 1) is rather general and conceivably would apply to any proposal. Unless > you have specific library deliverables in mind, I'd suggest starting with > your third point. In hindsight I also think that 1) should be moved down and 2) and 3) up. I think it was simply the first thing to come to my mind. I mention it because it may seem surprising to some people that in fact, even if they are not interested in Yi, they might still benefit from new libraries if nothing else. I don't have any specific deliverables here so I'll probably switch the points around as you recommend. > These aren't really technical concerns, rather they're about the > language/focus of your proposal. Although I do think this is an ambitious > project, the scope as you've defined it might be manageable within a GSOC. > That said, I wouldn't be surprised if adding concurrency takes more time > than you've allocated, or is a source of new bugs that you'll have to fix, > thereby preventing you from working on the bugs you've already identified. I also think concurrency might take a rather long time but as I already am involved with Yi, I do not plan to put it off to the day 1 of coding period which should give me a good head start. While it's technically not part of the proposal, I don't really plan on sitting doing nothing with Yi until the project starts and then be swarmed with work. I think that the >1 month of the coding period I allocated will be enough at that point. It is a fair point about any new bugs which is why I say that I do not guarantee every single bug I mentioned will be closed but rather serve as a guideline of what I'll work on in the second part. > Cheers, > John L. -- Mateusz K. From maxim.kulkin at gmail.com Tue Mar 11 07:19:34 2014 From: maxim.kulkin at gmail.com (Maxim Kulkin) Date: Tue, 11 Mar 2014 11:19:34 +0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <531EAC5F.9020300@carlo-hamalainen.net> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: I played a bit with GHC API and Cabal (and even implemented .cabal support for hdevtools) and now I see issues with this approach: 1. GHC depends on Cabal (rly?) and this is most likely some old version of Cabal, not the one you use currently (e.g. I use cabal-install and Cabal 1.18, but GHC 7.6.3 -- the latest stable -- depends on Cabal 1.16). This makes it hard to develop tools that both use GHC API and latest Cabal. Hopefully this dependency will be removed in future versions of GHC. 2. Sometimes you get stuck with types and can't get source code compile and GHC API-based tools are of no help in this situation, because they won't be able to provide type for some variable in source file because this source file contains a syntax/type error in some other part. I'm not sure if GHC API can be tweaked to bypass errors and do the best effort of parsing/desugaring of other parts of sources with errors. Maybe some external parser (haskell-src-exts) should be used for source inspection. On Tue, Mar 11, 2014 at 10:25 AM, Carlo Hamalainen < carlo at carlo-hamalainen.net> wrote: > On 10/03/14 22:22, Andrey Chudnov wrote: > > If we go down that road, it's not cabal-repl that would need to be > extended. AFAIK, it's just a wrapper around GHCi that calls that latter > with package info extracted from the cabal file and, optionally, the > sandbox. So, really, it's GHCi that would need to be extended. I think, > something as simple as adding an option to output JSON (or some other > structured format with wide support in editors) instead of plain text would > go a long way to allow editors to consume it's output: they could just pipe > commands via stdin and read the JSON output via stdout, parse it and > display the info in the buffer. Depending on how GHCi looks inside and how > amenable it is to such modifications, it might actually be a doable summer > project. Am I missing any technical gotchas? > > > Regarding the data format, ghc-mod uses the GHC API to get the de-sugared > and type-checked representation of a module, e.g. > > > https://github.com/kazu-yamamoto/ghc-mod/blob/master/Language/Haskell/GhcMod/Gap.hs#L326-L337 > > Or, my tool ghc-imported-from needs to get the "guts" from the GHC API to > get the global reader environment: > > > https://github.com/carlohamalainen/ghc-imported-from/blob/master/Language/Haskell/GhcImportedFrom.hs#L343-L373 > > So my feeling is that we'd need to pass Haskell values back and forth, not > just JSON. > > Personally I would love it if GHCi was extended in the way that you are > suggesting, as it would make my tool much faster. Ditto for ghc-mod. > > -- > Carlo Hamalainenhttp://carlo-hamalainen.net > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Mar 11 07:26:30 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 11 Mar 2014 07:26:30 +0000 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: <531EBAA6.8030900@fuuzetsu.co.uk> On 11/03/14 07:19, Maxim Kulkin wrote: > I played a bit with GHC API and Cabal (and even implemented .cabal support > for hdevtools) and now I see issues with this approach: > > 1. GHC depends on Cabal (rly?) and this is most likely some old version of > Cabal, not the one you use currently (e.g. I use cabal-install and Cabal > 1.18, but GHC 7.6.3 -- the latest stable -- depends on Cabal 1.16). This > makes it hard to develop tools that both use GHC API and latest Cabal. > Hopefully this dependency will be removed in future versions of GHC. Actually, 1.16 was the bleeding edge release when 7.6.3 came out so technically it was new. Old compiler depends on an old version, I don't see why you find this odd. 7.8 will ship with a newer version (whether we like this or not). Having said that, I don't think GHC API depends on Cabal API, does it? > 2. Sometimes you get stuck with types and can't get source code compile and > GHC API-based tools are of no help in this situation, because they won't be > able to provide type for some variable in source file because this source > file contains a syntax/type error in some other part. I'm not sure if GHC > API can be tweaked to bypass errors and do the best effort of > parsing/desugaring of other parts of sources with errors. Maybe some > external parser (haskell-src-exts) should be used for source inspection. > -- Mateusz K. From joakim at comex.se Tue Mar 11 07:27:46 2014 From: joakim at comex.se (joakim at comex.se) Date: Tue, 11 Mar 2014 07:27:46 +0000 Subject: [Haskell-cafe] pure ghc Message-ID: Hello, If I compile my source code two time I would like to get the same binary. But currently when I run echo "main = return ()" > c.hs && ghc -fforce-recomp c.hs && xxd c > c1.hex && ghc -fforce-recomp c.hs && xxd c > c2.hex && diff c1.hex c2.hex my output is [1 of 1] Compiling Main ( c.hs, c.o ) Linking c ... [1 of 1] Compiling Main ( c.hs, c.o ) Linking c ... 55494c55494 < 00d8c50: 7400 6768 6333 3130 3830 5f30 2e63 0073 t.ghc31080_0.c.s --- > 00d8c50: 7400 6768 6333 3130 3935 5f30 2e63 0073 t.ghc31095_0.c.s So why does the binary differ? Is there a way to compile with ghc and get the same binary? Even though only one byte differ, the checksum (sha,md5,..) is completely changed... I'm running Linux and ghc 7.6.3. Regards, Joakim -------------- next part -------------- An HTML attachment was scrubbed... URL: From maxim.kulkin at gmail.com Tue Mar 11 07:28:51 2014 From: maxim.kulkin at gmail.com (Maxim Kulkin) Date: Tue, 11 Mar 2014 11:28:51 +0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <531EBAA6.8030900@fuuzetsu.co.uk> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> <531EBAA6.8030900@fuuzetsu.co.uk> Message-ID: ghc package depends on exact version of Cabal pacakge. I understand why old package depends on some other old package. I just don't understand why GHC depends on Cabal. On Tue, Mar 11, 2014 at 11:26 AM, Mateusz Kowalczyk wrote: > On 11/03/14 07:19, Maxim Kulkin wrote: > > I played a bit with GHC API and Cabal (and even implemented .cabal > support > > for hdevtools) and now I see issues with this approach: > > > > 1. GHC depends on Cabal (rly?) and this is most likely some old version > of > > Cabal, not the one you use currently (e.g. I use cabal-install and Cabal > > 1.18, but GHC 7.6.3 -- the latest stable -- depends on Cabal 1.16). This > > makes it hard to develop tools that both use GHC API and latest Cabal. > > Hopefully this dependency will be removed in future versions of GHC. > > Actually, 1.16 was the bleeding edge release when 7.6.3 came out so > technically it was new. Old compiler depends on an old version, I don't > see why you find this odd. 7.8 will ship with a newer version (whether > we like this or not). > > Having said that, I don't think GHC API depends on Cabal API, does it? > > > 2. Sometimes you get stuck with types and can't get source code compile > and > > GHC API-based tools are of no help in this situation, because they won't > be > > able to provide type for some variable in source file because this source > > file contains a syntax/type error in some other part. I'm not sure if GHC > > API can be tweaked to bypass errors and do the best effort of > > parsing/desugaring of other parts of sources with errors. Maybe some > > external parser (haskell-src-exts) should be used for source inspection. > > > > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Mar 11 08:04:03 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 11 Mar 2014 04:04:03 -0400 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531EB05E.9050500@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> <531EB05E.9050500@fuuzetsu.co.uk> Message-ID: I should point out that the ways Vim and Emacs (and others like Sublime / Textmate) do those plugins is they often run them in a subprocess. Now i agree that having in process multi threading would be a good thing, I merely point out that there are ways to add the plugins you outline that need not depend on fully resolving the concurrency story. Yes, not calling a subprocess and stuff will be much better, just pointing out there are *ungodly* but feasible alternative hacks. :) -Carter On Tue, Mar 11, 2014 at 2:42 AM, Mateusz Kowalczyk wrote: > On 10/03/14 23:43, John Lato wrote: > > I think this has potential to be a good proposal, although I have a few > > concerns: > > > > 1. It's a bifurcated proposal, with two major components. I think the > > proposal would be stronger if you address more either how adding > > concurrency will help with all those tickets, or other features that > should > > be supported in yi but can't with the current design. You give a few > > examples further down, but at present it reads (to me) as though you want > > to add concurrency just for the sake of it. > > Actually, the tickets mentioned are not affected (much) by concurrency > being implemented or not. Here are some things that lack of concurrency > does affect at the moment: > > * Can't do periodic events > > * Can't wait for a process output in the background (an easy test is to > ask Yi to run a ?sleep 2000? system command). This is a big deal for > interacting with things like flyspell or ghc-mod. > > * Can't do networking > > * Can't do > > When I say it can't do it, I mean ?can't do it without stopping > everything else including the interface?. This is a big problem for an > editor because it means we can't write many, many of the editor modes > that people pretty much require nowadays: flyspell, flycheck, > compilation, . What Yi can do are > ?static? modes such as dired: they do not require background updates or > anything of the sort so they are fine in a single thread most of the > time. Any longer editor actions effectively lock up the interface for > the user. I'd wager that your own text editor performs some of these > actions that we couldn't feasibly implement in Yi right now. > > > 2. Despite the well-known fact that Concurrency is Hard, in many ways > > Haskell provides better tools to manage concurrency than many other > > languages. There are so many options, that sometimes people have > > difficulty knowing what to pick. This work seems to provide an obvious > > benefit to the Haskell community in that others can see what you chose, > > why, and how it worked in practice (including any pitfalls). > > > > Out of your benefits to the Haskell community, IMHO 2) and 3) are solid > but > > 1) is rather general and conceivably would apply to any proposal. Unless > > you have specific library deliverables in mind, I'd suggest starting with > > your third point. > > In hindsight I also think that 1) should be moved down and 2) and 3) up. > I think it was simply the first thing to come to my mind. I mention it > because it may seem surprising to some people that in fact, even if they > are not interested in Yi, they might still benefit from new libraries if > nothing else. I don't have any specific deliverables here so I'll > probably switch the points around as you recommend. > > > These aren't really technical concerns, rather they're about the > > language/focus of your proposal. Although I do think this is an > ambitious > > project, the scope as you've defined it might be manageable within a > GSOC. > > That said, I wouldn't be surprised if adding concurrency takes more time > > than you've allocated, or is a source of new bugs that you'll have to > fix, > > thereby preventing you from working on the bugs you've already > identified. > > I also think concurrency might take a rather long time but as I already > am involved with Yi, I do not plan to put it off to the day 1 of coding > period which should give me a good head start. While it's technically > not part of the proposal, I don't really plan on sitting doing nothing > with Yi until the project starts and then be swarmed with work. > > I think that the >1 month of the coding period I allocated will be > enough at that point. It is a fair point about any new bugs which is why > I say that I do not guarantee every single bug I mentioned will be > closed but rather serve as a guideline of what I'll work on in the > second part. > > > Cheers, > > John L. > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Tue Mar 11 08:04:57 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 11 Mar 2014 04:04:57 -0400 Subject: [Haskell-cafe] Haskell Hackathon in NYC, April 4-6 (last reminder) In-Reply-To: References: Message-ID: Indeed, Please register / consider coming! On Mon, Mar 10, 2014 at 10:39 PM, MightyByte wrote: > Greetings, > > We're just under a month out from the first Hac NYC, so I wanted to > send out one more reminder to the community. For the full details see > the previous announcement. > > http://www.haskell.org/pipermail/haskell-cafe/2014-January/112362.html > > Once again, if you plan on coming, you must officially register by > filling out our registration form [1]. Other details for travel, > lodging, etc can be found on the Hac NYC wiki [2]. > > And if you would like to give a talk, please let us know [3] so we can > schedule them. > > We're looking forward to seeing you here. > > -The Hac NYC Team > > [1] > https://docs.google.com/forms/d/1taZtjgYozFNebLt1TR2VnKv-ovD2Yv5sOdSZzmi_xFo/viewform > [2] http://www.haskell.org/haskellwiki/Hac_NYC > [3] http://www.haskell.org/haskellwiki/Hac_NYC/Talks > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alan.zimm at gmail.com Tue Mar 11 08:08:42 2014 From: alan.zimm at gmail.com (AlanKim Zimmerman) Date: Tue, 11 Mar 2014 10:08:42 +0200 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: HaRe gets around the cabal version mismatch by making sure that the return types from the relevant ghc-mod calls are types that are not exported by cabal. e.g. http://hackage.haskell.org/package/ghc-mod-3.1.4/docs/Language-Haskell-GhcMod-Internal.html#v:cabalAllTargetsreturns [String] for the target names. This could perhaps be extended to either use a separate library of stable types to be used by both cabal and ghc, or to return e.g. json Alan On Tue, Mar 11, 2014 at 9:19 AM, Maxim Kulkin wrote: > I played a bit with GHC API and Cabal (and even implemented .cabal support > for hdevtools) and now I see issues with this approach: > > 1. GHC depends on Cabal (rly?) and this is most likely some old version of > Cabal, not the one you use currently (e.g. I use cabal-install and Cabal > 1.18, but GHC 7.6.3 -- the latest stable -- depends on Cabal 1.16). This > makes it hard to develop tools that both use GHC API and latest Cabal. > Hopefully this dependency will be removed in future versions of GHC. > > 2. Sometimes you get stuck with types and can't get source code compile > and GHC API-based tools are of no help in this situation, because they > won't be able to provide type for some variable in source file because this > source file contains a syntax/type error in some other part. I'm not sure > if GHC API can be tweaked to bypass errors and do the best effort of > parsing/desugaring of other parts of sources with errors. Maybe some > external parser (haskell-src-exts) should be used for source inspection. > > > On Tue, Mar 11, 2014 at 10:25 AM, Carlo Hamalainen < > carlo at carlo-hamalainen.net> wrote: > >> On 10/03/14 22:22, Andrey Chudnov wrote: >> >> If we go down that road, it's not cabal-repl that would need to be >> extended. AFAIK, it's just a wrapper around GHCi that calls that latter >> with package info extracted from the cabal file and, optionally, the >> sandbox. So, really, it's GHCi that would need to be extended. I think, >> something as simple as adding an option to output JSON (or some other >> structured format with wide support in editors) instead of plain text would >> go a long way to allow editors to consume it's output: they could just pipe >> commands via stdin and read the JSON output via stdout, parse it and >> display the info in the buffer. Depending on how GHCi looks inside and how >> amenable it is to such modifications, it might actually be a doable summer >> project. Am I missing any technical gotchas? >> >> >> Regarding the data format, ghc-mod uses the GHC API to get the de-sugared >> and type-checked representation of a module, e.g. >> >> >> https://github.com/kazu-yamamoto/ghc-mod/blob/master/Language/Haskell/GhcMod/Gap.hs#L326-L337 >> >> Or, my tool ghc-imported-from needs to get the "guts" from the GHC API to >> get the global reader environment: >> >> >> https://github.com/carlohamalainen/ghc-imported-from/blob/master/Language/Haskell/GhcImportedFrom.hs#L343-L373 >> >> So my feeling is that we'd need to pass Haskell values back and forth, >> not just JSON. >> >> Personally I would love it if GHCi was extended in the way that you are >> suggesting, as it would make my tool much faster. Ditto for ghc-mod. >> >> -- >> Carlo Hamalainenhttp://carlo-hamalainen.net >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Mar 11 08:11:44 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 11 Mar 2014 08:11:44 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <531EB05E.9050500@fuuzetsu.co.uk> Message-ID: <531EC540.2060608@fuuzetsu.co.uk> On 11/03/14 08:04, Carter Schonwald wrote: > I should point out that the ways Vim and Emacs (and others like Sublime / > Textmate) do those plugins is they often run them in a subprocess. > > Now i agree that having in process multi threading would be a good thing, I > merely point out that there are ways to add the plugins you outline that > need not depend on fully resolving the concurrency story. > > Yes, not calling a subprocess and stuff will be much better, just pointing > out there are *ungodly* but feasible alternative hacks. > > :) > -Carter > I am far too well aware of this ;P The reason why I'm not even mentioning this as a possibility is because it is a terrible thing to do and requires a lot of juggling to behave more or less like you'd want it. Even today I have my emacs freeze up when I run cabal repl inside of it for the first time. Also as I mentioned, we have no means to periodically run things, which means we can't periodically query our subprocess. There is no mechanism for such scheduling and while doing it in a single thread like emacs and vim do is *a* way to do it, you yourself point out that it's sub-par. So yeah, I'm not even starting to consider that option, I don't want to end up with yet another editor that doesn't do actual concurrency. -- Mateusz K. From maxim.kulkin at gmail.com Tue Mar 11 08:17:12 2014 From: maxim.kulkin at gmail.com (Maxim Kulkin) Date: Tue, 11 Mar 2014 12:17:12 +0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: The thing is not with types: I would like to use a version of cabal in my tool, but dependency on GHC API (which I also use) dictates me other (older) version of Cabal for an unknown and unobvious reason. I want user of my tool to pick arbitrary Cabal version, the one that he actually uses. I'm even ok to write different implementations to support differencies in Cabal API. I once googled a mailing discussion on that GHC uses methods for parsing and printing some types like package ids or something and they introduced a dependency for that reason. On Tue, Mar 11, 2014 at 12:08 PM, AlanKim Zimmerman wrote: > HaRe gets around the cabal version mismatch by making sure that the return > types from the relevant ghc-mod calls are types that are not exported by > cabal. > > e.g. > http://hackage.haskell.org/package/ghc-mod-3.1.4/docs/Language-Haskell-GhcMod-Internal.html#v:cabalAllTargetsreturns [String] for the target names. > > This could perhaps be extended to either use a separate library of stable > types to be used by both cabal and ghc, or to return e.g. json > > Alan > > > On Tue, Mar 11, 2014 at 9:19 AM, Maxim Kulkin wrote: > >> I played a bit with GHC API and Cabal (and even implemented .cabal >> support for hdevtools) and now I see issues with this approach: >> >> 1. GHC depends on Cabal (rly?) and this is most likely some old version >> of Cabal, not the one you use currently (e.g. I use cabal-install and Cabal >> 1.18, but GHC 7.6.3 -- the latest stable -- depends on Cabal 1.16). This >> makes it hard to develop tools that both use GHC API and latest Cabal. >> Hopefully this dependency will be removed in future versions of GHC. >> >> 2. Sometimes you get stuck with types and can't get source code compile >> and GHC API-based tools are of no help in this situation, because they >> won't be able to provide type for some variable in source file because this >> source file contains a syntax/type error in some other part. I'm not sure >> if GHC API can be tweaked to bypass errors and do the best effort of >> parsing/desugaring of other parts of sources with errors. Maybe some >> external parser (haskell-src-exts) should be used for source inspection. >> >> >> On Tue, Mar 11, 2014 at 10:25 AM, Carlo Hamalainen < >> carlo at carlo-hamalainen.net> wrote: >> >>> On 10/03/14 22:22, Andrey Chudnov wrote: >>> >>> If we go down that road, it's not cabal-repl that would need to be >>> extended. AFAIK, it's just a wrapper around GHCi that calls that latter >>> with package info extracted from the cabal file and, optionally, the >>> sandbox. So, really, it's GHCi that would need to be extended. I think, >>> something as simple as adding an option to output JSON (or some other >>> structured format with wide support in editors) instead of plain text would >>> go a long way to allow editors to consume it's output: they could just pipe >>> commands via stdin and read the JSON output via stdout, parse it and >>> display the info in the buffer. Depending on how GHCi looks inside and how >>> amenable it is to such modifications, it might actually be a doable summer >>> project. Am I missing any technical gotchas? >>> >>> >>> Regarding the data format, ghc-mod uses the GHC API to get the >>> de-sugared and type-checked representation of a module, e.g. >>> >>> >>> https://github.com/kazu-yamamoto/ghc-mod/blob/master/Language/Haskell/GhcMod/Gap.hs#L326-L337 >>> >>> Or, my tool ghc-imported-from needs to get the "guts" from the GHC API >>> to get the global reader environment: >>> >>> >>> https://github.com/carlohamalainen/ghc-imported-from/blob/master/Language/Haskell/GhcImportedFrom.hs#L343-L373 >>> >>> So my feeling is that we'd need to pass Haskell values back and forth, >>> not just JSON. >>> >>> Personally I would love it if GHCi was extended in the way that you are >>> suggesting, as it would make my tool much faster. Ditto for ghc-mod. >>> >>> -- >>> Carlo Hamalainenhttp://carlo-hamalainen.net >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jpmoresmau at gmail.com Tue Mar 11 08:20:55 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Tue, 11 Mar 2014 09:20:55 +0100 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: Unifying all the different tools underlying IDEs has been talked again before, because the pain is real. For example, see https://github.com/fpco/haskell-ide/wiki. I've written about the GHC API in that wiki, and some of the issues that it has for such tools. Currently EclipseFP uses buildwrapper, which is a backend I wrote because I was dissatisfied with scion. It integrates the GHC API and Cabal, so that it aims to give the same results that running cabal configure/build. It usually run as a shortlived executable but for performance reason it is possible to have a long lived session to avoid reloading the modules in GHC all the times. Yes, GHC depends on the Cabal API for some types, which causes untold woes when you use buildwrapper after upgrading Cabal, for example. There is a bug report to remove that dependency but I had no time yet to work on it, so far I've used dynamic-cabal in buildwrapper to allow a newer version of Cabal, at the price of more complexity. But a complete tool would need to integrate both, so it can't be ghci only, otherwise Cabal and GHC would become really stuck together. The GHC API uses some global settings, which means you sometimes have no choice (if stcouldatic flags change) than to respawn a new process. This could probably be improved since it's not really the way a well behaved Haskell program should act. Memory usage is also a concern. So I think there should be two lines of work here: one would be to improve the GHC API and/or the ghci interface, to make it more IDE friendly, the other would be to unify all these tools like scion/buildwrapper/ghc-mod in one tool that would hopefully provide all services an IDE needs, and that would allow easy plugin of additional functionality (so for example HaRe could easily add its refactoring capabilities to it). I would happily switch from buildwrapper to another community supported tool if all the functionality I currently have is kept in one form or another. JP On Tue, Mar 11, 2014 at 9:17 AM, Maxim Kulkin wrote: > The thing is not with types: I would like to use a version of cabal in my > tool, but dependency on GHC API (which I also use) dictates me other > (older) version of Cabal for an unknown and unobvious reason. I want user > of my tool to pick arbitrary Cabal version, the one that he actually uses. > I'm even ok to write different implementations to support differencies in > Cabal API. > > I once googled a mailing discussion on that GHC uses methods for parsing > and printing some types like package ids or something and they introduced a > dependency for that reason. > > > > On Tue, Mar 11, 2014 at 12:08 PM, AlanKim Zimmerman wrote: > >> HaRe gets around the cabal version mismatch by making sure that the >> return types from the relevant ghc-mod calls are types that are not >> exported by cabal. >> >> e.g. >> http://hackage.haskell.org/package/ghc-mod-3.1.4/docs/Language-Haskell-GhcMod-Internal.html#v:cabalAllTargetsreturns [String] for the target names. >> >> This could perhaps be extended to either use a separate library of stable >> types to be used by both cabal and ghc, or to return e.g. json >> >> Alan >> >> >> On Tue, Mar 11, 2014 at 9:19 AM, Maxim Kulkin wrote: >> >>> I played a bit with GHC API and Cabal (and even implemented .cabal >>> support for hdevtools) and now I see issues with this approach: >>> >>> 1. GHC depends on Cabal (rly?) and this is most likely some old version >>> of Cabal, not the one you use currently (e.g. I use cabal-install and Cabal >>> 1.18, but GHC 7.6.3 -- the latest stable -- depends on Cabal 1.16). This >>> makes it hard to develop tools that both use GHC API and latest Cabal. >>> Hopefully this dependency will be removed in future versions of GHC. >>> >>> 2. Sometimes you get stuck with types and can't get source code compile >>> and GHC API-based tools are of no help in this situation, because they >>> won't be able to provide type for some variable in source file because this >>> source file contains a syntax/type error in some other part. I'm not sure >>> if GHC API can be tweaked to bypass errors and do the best effort of >>> parsing/desugaring of other parts of sources with errors. Maybe some >>> external parser (haskell-src-exts) should be used for source inspection. >>> >>> >>> On Tue, Mar 11, 2014 at 10:25 AM, Carlo Hamalainen < >>> carlo at carlo-hamalainen.net> wrote: >>> >>>> On 10/03/14 22:22, Andrey Chudnov wrote: >>>> >>>> If we go down that road, it's not cabal-repl that would need to be >>>> extended. AFAIK, it's just a wrapper around GHCi that calls that latter >>>> with package info extracted from the cabal file and, optionally, the >>>> sandbox. So, really, it's GHCi that would need to be extended. I think, >>>> something as simple as adding an option to output JSON (or some other >>>> structured format with wide support in editors) instead of plain text would >>>> go a long way to allow editors to consume it's output: they could just pipe >>>> commands via stdin and read the JSON output via stdout, parse it and >>>> display the info in the buffer. Depending on how GHCi looks inside and how >>>> amenable it is to such modifications, it might actually be a doable summer >>>> project. Am I missing any technical gotchas? >>>> >>>> >>>> Regarding the data format, ghc-mod uses the GHC API to get the >>>> de-sugared and type-checked representation of a module, e.g. >>>> >>>> >>>> https://github.com/kazu-yamamoto/ghc-mod/blob/master/Language/Haskell/GhcMod/Gap.hs#L326-L337 >>>> >>>> Or, my tool ghc-imported-from needs to get the "guts" from the GHC API >>>> to get the global reader environment: >>>> >>>> >>>> https://github.com/carlohamalainen/ghc-imported-from/blob/master/Language/Haskell/GhcImportedFrom.hs#L343-L373 >>>> >>>> So my feeling is that we'd need to pass Haskell values back and forth, >>>> not just JSON. >>>> >>>> Personally I would love it if GHCi was extended in the way that you are >>>> suggesting, as it would make my tool much faster. Ditto for ghc-mod. >>>> >>>> -- >>>> Carlo Hamalainenhttp://carlo-hamalainen.net >>>> >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From P.Achten at cs.ru.nl Tue Mar 11 08:37:51 2014 From: P.Achten at cs.ru.nl (Peter Achten) Date: Tue, 11 Mar 2014 09:37:51 +0100 Subject: [Haskell-cafe] [TFP2014] Final Call For Papers Message-ID: <531ECB5F.8080601@cs.ru.nl> --------------------------------- F I N A L C A L L F O R P A P E R S --------------------------------- ======== TFP 2014 =========== 15th Symposium on Trends in Functional Programming May 26-28, 2014 Utrecht University Soesterberg, The Netherlands http://www.cs.uu.nl/wiki/TFP2014/WebHome *** Submission for TFP 2014 is now open: please direct your browser to *** http://www.cs.uu.nl/wiki/TFP2014/PaperSubmission The symposium on Trends in Functional Programming (TFP) is an international forum for researchers with interests in all aspects of functional programming, taking a broad view of current and future trends in the area. It aspires to be a lively environment for presenting the latest research results, and other contributions (see below), described in draft papers submitted prior to the symposium. A formal post-symposium refereeing process then selects a subset of the articles presented at the symposium and submitted for formal publication. Selected revised papers will be published as a Springer Lecture Notes in Computer Science (LNCS) volume. TFP 2014 will be the main event of a pair of functional programming events. The other is the International Workshop on Trends in Functional Programming in Education (TFPIE). TFPIE will take place on May 25th. Its website is located at http://www.cs.uwyo.edu/~jlc/tfpie14/ The TFP symposium is the heir of the successful series of Scottish Functional Programming Workshops. Previous TFP symposia were held in Edinburgh (Scotland) in 2003, in Munich (Germany) in 2004, in Tallinn (Estonia) in 2005, in Nottingham (UK) in 2006, in New York (USA) in 2007, in Nijmegen (The Netherlands) in 2008, in Komarno (Slovakia) in 2009, in Oklahoma (USA) in 2010, in Madrid (Spain) in 2011, St. Andrews (UK) in 2012 and Provo (Utah, USA) in 2013. For further general information about TFP please see the TFP homepage. INVITED SPEAKERS TFP is pleased to announce talks by the following two invited speakers: John Hughes of Chalmers, Goteborg, Sweden, is well-known as author of Why Functional Programming Matters, and as one of the designers of QuickCheck (together with Koen Claessen); the paper on QuickCheck won the ICFP Most Influential Paper Award in 2010. Currently he divides his time between his professorship and Quviq, a company that performs property-based testing of software with a tool implemented in Erlang. Dr. Geoffrey Mainland received his PhD from Harvard University where he was advised by Greg Morrisett and Matt Welsh. After a two year postdoc with the Programming Principles and Tools group at Microsoft Research Cambridge, he is now an assistant professor at Drexel University. His research focuses on high-level programming language and runtime support for non-general purpose computation. SCOPE The symposium recognizes that new trends may arise through various routes. As part of the Symposium's focus on trends we therefore identify the following five article categories. High-quality articles are solicited in any of these categories: Research Articles: leading-edge, previously unpublished research work Position Articles: on what new trends should or should not be Project Articles: descriptions of recently started new projects Evaluation Articles: what lessons can be drawn from a finished project Overview Articles: summarizing work with respect to a trendy subject Articles must be original and not submitted for simultaneous publication to any other forum. They may consider any aspect of functional programming: theoretical, implementation-oriented, or more experience-oriented. Applications of functional programming techniques to other languages are also within the scope of the symposium. Topics suitable for the symposium include: Functional programming and multicore/manycore computing Functional programming in the cloud High performance functional computing Extra-functional (behavioural) properties of functional programs Dependently typed functional programming Validation and verification of functional programs Using functional techniques to reason about imperative/object-oriented programs Debugging for functional languages Functional programming in different application areas: security, mobility, telecommunications applications, embedded systems, global computing, grids, etc. Interoperability with imperative programming languages Novel memory management techniques Program analysis and transformation techniques Empirical performance studies Abstract/virtual machines and compilers for functional languages (Embedded) domain specific languages New implementation strategies Any new emerging trend in the functional programming area If you are in doubt on whether your article is within the scope of TFP, please contact the TFP 2014 program chair, Jurriaan Hage at J.Hage at uu.nl. BEST PAPER AWARDS To reward excellent contributions, TFP awards a prize for the best paper accepted for the formal proceedings. TFP traditionally pays special attention to research students, acknowledging that students are almost by definition part of new subject trends. A student paper is one for which the authors state that the paper is mainly the work of students, the students are listed as first authors, and a student would present the paper. A prize for the best student paper is awarded each year. In both cases, it is the PC of TFP that awards the prize. In case the best paper happens to be a student paper, that paper will then receive both prizes. FINANCIAL SUPPORT TFP is financially supported by the Department of Information and Computing Sciences of Utrecht University, NWO (Netherlands Organisation for Scientific Research), Well-Typed and Erlang Solutions. PAPER SUBMISSIONS Acceptance of articles for presentation at the symposium is based on a lightweight peer review process of extended abstracts (4 to 10 pages in length) or full papers (16 pages). The submission must clearly indicate which category it belongs to: research, position, project, evaluation, or overview paper. It should also indicate whether the main author or authors are research students. In the case of a FULL STUDENT paper, the draft paper will receive additional feedback by one of the PC members shortly after the symposium has taken place. For the preproceedings, papers can be in any format (inclduing LNCS, IEEE and ACM style), but papers submitted to the postrefereeing process must be in LNCS style, and are bound by the limitations on paper length. We use EasyChair for the refereeing process. IMPORTANT DATES Submission of draft papers: March 17, 2014 Notification: March 24, 2014 Registration: April 7, 2014 TFP Symposium: May 26-28, 2014 Student papers feedback: June 9th, 2014 Submission for formal review: July 1st, 2014 Notification of acceptance: September 8th, 2014 Camera ready paper: October 8th, 2014 PROGRAM COMMITTEE Peter Achten Radboud University Nijmegen Emil Axelsson Chalmers Lucilia Camarao de Figueiredo Universidade Federal de Ouro Preto Laura Castro University of A Coruna Frank Huch Christian-Albrechts-University of Kiel Matthew Fluet Rochester Institute of Technology Jurriaan Hage (chair) University of Utrecht Yukiyoshi Kameyama University of Tsukuba Andrew Kennedy Microsoft Research Tamas Kozsik Eotvos Lorand University Ben Lippmeier University of New South Wales Luc Maranget INRIA Jay McCarthy (co-chair) Brigham Young University Marco T. Morazan Seton Hall University Ricardo Pena Universidad Complutense de Madrid Alexey Rodriguez LiquidM Sven-Bodo Scholz Heriot-Watt University Manuel Serrano INRIA Sophia Antipolis Simon Thompson University of Kent Tarmo Uustalu Inst of Cybernetics David Van Horn University of Maryland Janis Voigtlaender University of Bonn From semen at trygub.com Tue Mar 11 12:08:29 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Tue, 11 Mar 2014 12:08:29 +0000 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> <20140310165436.GA54191@inanna.trygub.com> Message-ID: <20140311120829.GA62991@inanna.trygub.com> On Mon, Mar 10, 2014 at 10:47:26PM +0000, gb wrote: > > > > > Great! But how do I recover the actual constructor? E.g., > > > > f :: String -> Constr > > f s = fromMaybe (error "error in f") $ readConstr (dataTypeOf $ B 1) s > > > > gives me back Data.Data.Constr (not D). I was hoping for something along > the lines > > > > f "A" $ 1 > > > > to get back a value > > > > A 1 > > > > of type D, etc. > > > > Many thanks, > > S. > > > > Here's one way: > > import qualified Data.Generics.Builders as B > import Data.Generics.Aliases > > fromConstrB (B.empty `extB` (12::Int)) (f "B")::D > >>> B 12 > > fromConstrB B.empty (f "B")::D > >>> B 0 Thank you very much ? it works! [and many new useful functions discovered along the way :-)]. I'm fairly happy with this solution (using readConstr as suggested by Niklas, and fromConstrB, as per above). The only wrinkle now is with this term in the definition of f : dataTypeOf $ B 1 We provide a value here (B 1) ? is there a way to make it take the constructor (B) instead, or, alternatively, make f aware of the signature of the constructor (Int -> D) and/or the resulting data type (D) somehow? I've hoogled it and also looked through Data.Data with no luck? It's just that constructing a full-blown value of type D might be non-trivial if D is complex, but it seems a bit wasteful as we are after the outer constructor alone. And of course, if D or types D depends on change we need to modify f? Thank you, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From omeragacan at gmail.com Tue Mar 11 12:08:47 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Tue, 11 Mar 2014 14:08:47 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Hi Stephen, > Sounds good, good luck with the project. Thanks! > One thing I struggled with was re-implementing the type checker as the > Caml implementation uses ref cells. Fortunately there are a lot of > tutorials on the web covering type checking with a good few using > Haskell and greater or lesser degree of assignment. I think ref cells used in OCaml code can be emulated in Haskell using a map from ints to types. This more-or-less corresponds to managing your own heap, where pointers point to types. I have something like this in mind: type Unifications = M.Map TyVar Ty -- TyVar is basically an int data UnificationError = OccursCheck Ty Ty -- circular definition | UnificationError Ty Ty -- can't unify types | StrErr String -- required for Error instance deriving (Show) instance Error UnificationError where strMsg = StrErr -- | Unification monad that keeps track of unifications. newtype Unify a = Unify { unwrapUnify :: StateT Unifications (ErrorT UnificationError Identity) a } deriving (Functor, Applicative, Monad, MonadState Unifications, MonadError UnificationError) type TyEnv = M.Map Id Ty -- map from identifiers to types -- | Follow chains of type variables in the heap and remove type variables -- by connecting type variables in the type to final types in the chain. -- e.g. 1 |-> TyVar 2 -- 2 |-> TyVar 3 -- 3 |-> TyBool -- after `prune (TyVar 1)`, heap should be like: -- 1 |-> TyBool -- 2 |-> TyVar 3 -- 3 |-> TyBool prune :: Ty -> Unify Ty prune = ... -- | Unify two types. unify :: TyEnv -> Ty -> Ty -> Unify () unify = ... -- | Infer type of an expression. typeCheck :: TyEnv -> Exp -> Unify Ty typeCheck = ... I didn't implement it yet but it seems to me that this shouuld work. Another approach might be using STRefs. --- ?mer Sinan A?acan http://osa1.net From haskell at nand.wakku.to Tue Mar 11 12:21:01 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Tue, 11 Mar 2014 13:21:01 +0100 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140311120829.GA62991@inanna.trygub.com> References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> <20140310165436.GA54191@inanna.trygub.com> <20140311120829.GA62991@inanna.trygub.com> Message-ID: <20140311132101.GA32646@nanodesu.talocan.mine.nu> > Thank you very much ? it works! [and many new useful functions discovered along the way :-)]. > > I'm fairly happy with this solution (using readConstr as suggested by Niklas, > and fromConstrB, as per above). The only wrinkle now is with this term in the definition of f : > > dataTypeOf $ B 1 > > We provide a value here (B 1) ? is there a way to make it take the constructor (B) > instead, or, alternatively, make f aware of the signature of the constructor (Int -> D) and/or the resulting > data type (D) somehow? I've hoogled it and also looked through Data.Data with no luck? > > It's just that constructing a full-blown value of type D might be non-trivial if D is complex, > but it seems a bit wasteful as we are after the outer constructor alone. > And of course, if D or types D depends on change we need to modify f? > > Thank you, > S. The idiomatic way to handle this kind of stuff normally is to pass an abstract proxy that carries the type as a type argument, rather than passing a value of that type itself, eg.: > data Proxy a = Proxy > > dataTypeOf :: Data a => Proxy a -> DataTypeOf or even a more polymorphic version: > dataTypeOf :: Data a => f a -> DataTypeOf which can be instantiated at any ?f?, including Proxy, [], Maybe or others. Unfortunately, it does not seem that Data.Data.Data has gone for this route, so my feedback is a bit useless. You could still provide your own wrapper function (that uses ?undefined? internally, which we know here to be safe even though it's ugly), though. From stegeman at gmail.com Tue Mar 11 13:04:14 2014 From: stegeman at gmail.com (Luite Stegeman) Date: Wed, 12 Mar 2014 02:04:14 +1300 Subject: [Haskell-cafe] GSOC Project Ideas In-Reply-To: References: Message-ID: I've compiled a list of ideas for my current pet project, GHCJS [1] (Haskell to JavaScript compiler). While it's not exactly a central part of the Haskell ecosystem, it could be a fun compiler project to work on. Since it's a cabal package and the RTS is written in JavaScript, it's much more accessible than GHC itself. GHCJS' evaluation model is quite close to GHC's, with lightweight threads, dynamically growing stacks, (async) exceptions, lazy IO, MVar, weak refs and all. This year I'm hoping to get some extra tooling for GHCJS that can also benefit Haskell in general. One of the projects on the list is tracing/stepping through Haskell code, compiled by GHCJS, in the browser. I did a one evening experiment last year (with a now ancient GHCJS) and that already looked quite interesting [2]. The goal is to add interactivity and a nice user interface, with better rendering of the heap and stack data structures. Another useful thing would be profiling support: In the browser it'd be much easier to build a GUI that lets you pause a running program and collect memory allocation data from some specific thing you're interested in (for example pushing a single event through an FRP system). The new tools would go well with Dan Frumin's last year's interactive-diagrams [3] GSoC project that runs or compiles Haskell code in a sandbox on the server. If we just upgrade the tools in the sandbox, users could paste some Haskell in the pastebin and immediately step/trace through the evaluation for example. Interactive-diagrams already has the ability to automatically show input fields or select boxes for users to supply the arguments if the input is a function. While not for beginners, I think that students with reasonably good Haskell and JavaScript skills and some interest in RTS internals should be able to build something that's useful (and I have a good idea of what's going to be involved in both projects). The list [1] has more ideas, if anyone is interested in discussing projects, come to IRC, #ghcjs or #haskell-gsoc on freenode, github tickets / email also welcome. luite [1] https://github.com/ghcjs/ghcjs/wiki/GHCJS-Google-Summer-of-Code-project-ideas [2] http://hdiff.luite.com/reduce/ [3] http://paste.hskll.org/ (sorry if it's down, one of the hdds in the server died recently, i'm moving everything over to a faster new server) On Tue, Mar 11, 2014 at 5:31 PM, Allan Gardner wrote: > I went through the GSOC trac, most of the Haskell IRC logs, and the > Haskell idea reddit. So now I have a list of ideas (grouped by category): > > infrastructure: > > - C++ integration (e.g. finish https://github.com/ofan/hqt > https://github.com/ofan/fficxx ) > - Ada/Python/... integration > - gobject bindings (gtk2hs stuff) > - cabal improvements - Haddock flags ( > https://github.com/haskell/cabal/issues/1585), custom setup > improvements (https://github.com/haskell/cabal/issues/948), some sort > of plugin system for tests/docs/other random things (BNFC), clean up and > merge parallel build code, package management, ... > - Hackage2 improvements - voting, rewrite auth system, speed up > reverse-deps enough to enable on main site, package wiki/comments, > deprecations w/ links, create haddock even if the package doesn't build, ... > - scale up Hoogle so it can search all of hackage by default > - scoutess work (integration with with hackage, ghc snapshots, ...) > > libraries: > > - email/PIM library (MIME, imap, ical, XMPP, WebDav, ... probably make > use of a lot of old HaskellNet code) > - comprehensive Date/Time API - there are lots of Hackage libs, but > none do e.g. internationalization - aim to be backwards-compatible with time > - highlight code using inferred types - HsColour + > haskell-src/type-exts ? (maybe not enough for a GSOC?) > - implement miscellaneous concurrent data structures > - darcs improvements (performance, storage, ...) > - fix pandoc conversion issues > - ... (there were a lot of other libraries, but one of the blog posts > said not do a library project because hackage already has too many and > designing a good API from scratch is hard) > > GHC project ideas: > > - package improvements - finish multiple package stuff, sign and > verify packages, ... > - port GHC build system to shake (faster, progress indicators, written > in Haskell, ...) > - implement something like ccache or distcc for GHC > - rewrite the GHC pattern overlap/exhaustiveness analysis ( > https://ghc.haskell.org/trac/ghc/ticket/595, 10 years old!) > - make GHC deterministic (refactor Unique + other nondeterminism > sources, make a pure parser and/or typechecker API) > - port Hat to the GHC api and integrate it into GHCi's :trace mode so > omniscient debugging is available by default > - implement typed core as another IL, either above or below old-core > ("Types are Calling Conventions" paper) > - other type-level programming library/project (units, extended > arithmetic solver, true dependent types, linear types, ...) > > GHC backend-ish: > > - customizable RTS - remove unused RTS functions, write your own > concurrency primitives, ... > - resurrect Immix patches and try to get incremental GC > - implement loop unrolling in GHC > - allow LLVM phases to be written in Haskell (bindings already used, > so it's just dealing with the FFI's and GHC's options handling...) > > I've tried putting these by two people (edwardk and carter) on > #haskell-gsoc, and they both said that all the GHC ideas are too hard for a > GSOC. Can I get a third opinion? > > Also, please tell me if I left anything important out (I see a Yi proposal > on this mailing list; that would be in the ... in libraries). > > Finally, some sort of idea of which ideas are most likely to get accepted > would be helpful. > https://docs.google.com/forms/d/1rEobhHwFpjzPnra9L1TmrozWNFFyAVNPmdUMCcT--3Q/viewanalyticssays the top priorities are GHC, Cabal, and Hackage, so since GHC is > (apparently) out I guess that means I should look more at my Cabal, > Hackage, and Hoogle ideas... is this sensible? > > -- Allan Gardner > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Tue Mar 11 14:32:23 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Tue, 11 Mar 2014 10:32:23 -0400 Subject: [Haskell-cafe] pure ghc In-Reply-To: References: Message-ID: On Tue, Mar 11, 2014 at 3:27 AM, wrote: > < 00d8c50: 7400 6768 6333 3130 3830 5f30 2e63 0073 t.ghc31080_0.c.s > > --- > > > 00d8c50: 7400 6768 6333 3130 3935 5f30 2e63 0073 t.ghc31095_0.c.s > > > > So why does the binary differ? Is there a way to compile with ghc and get > the same binary? > That's a filename symbol in the debug info. Using a deterministic filename has potential problems, although I note that it's still fairly deterministic anyway. A C compile that uses temporary files will also have symbols that change this way (usually referring to assembler temporary files). There is not a lot to be done about this, as you're at cross purposes with the system linker and with people who want to be able to debug programs. -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Tue Mar 11 14:37:04 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Tue, 11 Mar 2014 14:37:04 +0000 Subject: [Haskell-cafe] pure ghc In-Reply-To: References: Message-ID: <531F1F90.8020809@nh2.me> There is a GHC bug dealing with such things: https://ghc.haskell.org/trac/ghc/ticket/4012 From byorgey at seas.upenn.edu Tue Mar 11 15:27:31 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Tue, 11 Mar 2014 11:27:31 -0400 Subject: [Haskell-cafe] GSOC Project Ideas In-Reply-To: References: Message-ID: <20140311152731.GA21157@seas.upenn.edu> I'd like to point out that we also have a list of diagrams-related projects here: http://www.haskell.org/haskellwiki/Diagrams/Projects Some (though not all) of them would make good GSoC projects, especially those that push diagrams more in the direction of being a useful general-purpose tool for other Haskellers, or result in spinning off useful general-purpose Haskell packages. Diagrams is a lot of fun to work on and we had two successful diagrams-related GSoC projects last summer (one creating an interactive diagrams pastebin, http://paste.hskell.org/, which also resulted in spinning off several libraries; and one adding a diagrams backend for the Chart library). Some particularly good potential projects include: - Implementing a general graph-drawing library on top of diagrams (note this doesn't include doing graph *layout*, just drawing; but could include making it easy to e.g. use graphviz to do the graph layout and diagrams to do the drawing). - Converting SVG files to diagrams and/or improving diagrams' SVG output (optimizing the size of generated files, adding features like grouping for transparency, node ids, etc.) - Adding the ability to edit diagrams (e.g. "make everything black and white" or "make all the circles 50% bigger"); this is a big missing feature and would involve some fun gymnastics with zippers and lenses. We're happy to discuss these or other ideas on the #diagrams IRC channel. -Brent On Mon, Mar 10, 2014 at 10:31:02PM -0600, Allan Gardner wrote: > I went through the GSOC trac, most of the Haskell IRC logs, and the Haskell > idea reddit. So now I have a list of ideas (grouped by category): > > infrastructure: > > - C++ integration (e.g. finish https://github.com/ofan/hqt > https://github.com/ofan/fficxx ) > - Ada/Python/... integration > - gobject bindings (gtk2hs stuff) > - cabal improvements - Haddock flags ( > https://github.com/haskell/cabal/issues/1585), custom setup improvements > (https://github.com/haskell/cabal/issues/948), some sort of plugin > system for tests/docs/other random things (BNFC), clean up and merge > parallel build code, package management, ... > - Hackage2 improvements - voting, rewrite auth system, speed up > reverse-deps enough to enable on main site, package wiki/comments, > deprecations w/ links, create haddock even if the package doesn't build, ... > - scale up Hoogle so it can search all of hackage by default > - scoutess work (integration with with hackage, ghc snapshots, ...) > > libraries: > > - email/PIM library (MIME, imap, ical, XMPP, WebDav, ... probably make > use of a lot of old HaskellNet code) > - comprehensive Date/Time API - there are lots of Hackage libs, but none > do e.g. internationalization - aim to be backwards-compatible with time > - highlight code using inferred types - HsColour + haskell-src/type-exts > ? (maybe not enough for a GSOC?) > - implement miscellaneous concurrent data structures > - darcs improvements (performance, storage, ...) > - fix pandoc conversion issues > - ... (there were a lot of other libraries, but one of the blog posts > said not do a library project because hackage already has too many and > designing a good API from scratch is hard) > > GHC project ideas: > > - package improvements - finish multiple package stuff, sign and verify > packages, ... > - port GHC build system to shake (faster, progress indicators, written > in Haskell, ...) > - implement something like ccache or distcc for GHC > - rewrite the GHC pattern overlap/exhaustiveness analysis ( > https://ghc.haskell.org/trac/ghc/ticket/595, 10 years old!) > - make GHC deterministic (refactor Unique + other nondeterminism > sources, make a pure parser and/or typechecker API) > - port Hat to the GHC api and integrate it into GHCi's :trace mode so > omniscient debugging is available by default > - implement typed core as another IL, either above or below old-core > ("Types are Calling Conventions" paper) > - other type-level programming library/project (units, extended > arithmetic solver, true dependent types, linear types, ...) > > GHC backend-ish: > > - customizable RTS - remove unused RTS functions, write your own > concurrency primitives, ... > - resurrect Immix patches and try to get incremental GC > - implement loop unrolling in GHC > - allow LLVM phases to be written in Haskell (bindings already used, so > it's just dealing with the FFI's and GHC's options handling...) > > I've tried putting these by two people (edwardk and carter) on > #haskell-gsoc, and they both said that all the GHC ideas are too hard for a > GSOC. Can I get a third opinion? > > Also, please tell me if I left anything important out (I see a Yi proposal > on this mailing list; that would be in the ... in libraries). > > Finally, some sort of idea of which ideas are most likely to get accepted > would be helpful. > https://docs.google.com/forms/d/1rEobhHwFpjzPnra9L1TmrozWNFFyAVNPmdUMCcT--3Q/viewanalyticssays > the top priorities are GHC, Cabal, and Hackage, so since GHC is > (apparently) out I guess that means I should look more at my Cabal, > Hackage, and Hoogle ideas... is this sensible? > > -- Allan Gardner > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From bgamari.foss at gmail.com Tue Mar 11 15:34:31 2014 From: bgamari.foss at gmail.com (Ben Gamari) Date: Tue, 11 Mar 2014 11:34:31 -0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> <531EBAA6.8030900@fuuzetsu.co.uk> Message-ID: <87mwgwlpfc.fsf@gmail.com> Maxim Kulkin writes: > ghc package depends on exact version of Cabal pacakge. I understand why old > package depends on some other old package. I just don't understand why GHC > depends on Cabal. > I believe GHC uses a few types from Cabal. Namely InstalledPackageInfo and a few related types, $ git grep 'import Distribution' compiler compiler/ghci/Linker.lhs:import Distribution.Package hiding (depends, PackageId) compiler/main/Finder.lhs:import Distribution.Text compiler/main/Finder.lhs:import Distribution.Package hiding (PackageId) compiler/main/PackageConfig.hs:import Distribution.InstalledPackageInfo compiler/main/PackageConfig.hs:import Distribution.ModuleName compiler/main/PackageConfig.hs:import Distribution.Package hiding (PackageId) compiler/main/PackageConfig.hs:import Distribution.Text compiler/main/PackageConfig.hs:import Distribution.Version compiler/main/Packages.lhs:import Distribution.InstalledPackageInfo compiler/main/Packages.lhs:import Distribution.InstalledPackageInfo.Binary compiler/main/Packages.lhs:import Distribution.Package hiding (PackageId,depends) At one point I believe there was a proposal to move these to a separate package but I don't have a reference on hand. Cheers, - Ben -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 489 bytes Desc: not available URL: From jpmoresmau at gmail.com Tue Mar 11 15:40:54 2014 From: jpmoresmau at gmail.com (JP Moresmau) Date: Tue, 11 Mar 2014 16:40:54 +0100 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: <87mwgwlpfc.fsf@gmail.com> References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> <531EBAA6.8030900@fuuzetsu.co.uk> <87mwgwlpfc.fsf@gmail.com> Message-ID: Ben, https://ghc.haskell.org/trac/ghc/ticket/8244 is what you're referring to, I think. JP On Tue, Mar 11, 2014 at 4:34 PM, Ben Gamari wrote: > Maxim Kulkin writes: > > > ghc package depends on exact version of Cabal pacakge. I understand why > old > > package depends on some other old package. I just don't understand why > GHC > > depends on Cabal. > > > I believe GHC uses a few types from Cabal. Namely InstalledPackageInfo > and a few related types, > > $ git grep 'import Distribution' compiler > compiler/ghci/Linker.lhs:import Distribution.Package hiding (depends, > PackageId) > compiler/main/Finder.lhs:import Distribution.Text > compiler/main/Finder.lhs:import Distribution.Package hiding (PackageId) > compiler/main/PackageConfig.hs:import Distribution.InstalledPackageInfo > compiler/main/PackageConfig.hs:import Distribution.ModuleName > compiler/main/PackageConfig.hs:import Distribution.Package hiding > (PackageId) > compiler/main/PackageConfig.hs:import Distribution.Text > compiler/main/PackageConfig.hs:import Distribution.Version > compiler/main/Packages.lhs:import Distribution.InstalledPackageInfo > compiler/main/Packages.lhs:import > Distribution.InstalledPackageInfo.Binary > compiler/main/Packages.lhs:import Distribution.Package hiding > (PackageId,depends) > > At one point I believe there was a proposal to move these to a separate > package but I don't have a reference on hand. > > Cheers, > > - Ben > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- JP Moresmau http://jpmoresmau.blogspot.com/ -------------- next part -------------- An HTML attachment was scrubbed... URL: From mail at nh2.me Tue Mar 11 15:42:12 2014 From: mail at nh2.me (=?UTF-8?B?TmlrbGFzIEhhbWLDvGNoZW4=?=) Date: Tue, 11 Mar 2014 15:42:12 +0000 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> <531EBAA6.8030900@fuuzetsu.co.uk> <87mwgwlpfc.fsf@gmail.com> Message-ID: <531F2ED4.7010505@nh2.me> On Tue 11 Mar 2014 15:40:54 GMT, JP Moresmau wrote: > Ben, https://ghc.haskell.org/trac/ghc/ticket/8244 is what you're > referring to, I think. Quoting from Simon Peyton-Jones: > I would love to remove this dependency. Having it implies that GHC depends on heavy-duty Cabal functionality, but of course it doesn't at all. It means that we have to compile all 60+ modules of Cabal before even starting on GHC. It seems wrong. > So, more power to you! I have no opinions about the details -- just wanting to be encouraging. We just need to do it. From byorgey at seas.upenn.edu Tue Mar 11 15:55:48 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Tue, 11 Mar 2014 11:55:48 -0400 Subject: [Haskell-cafe] GSOC Project Ideas In-Reply-To: <20140311152731.GA21157@seas.upenn.edu> References: <20140311152731.GA21157@seas.upenn.edu> Message-ID: <20140311155548.GA28156@seas.upenn.edu> On Tue, Mar 11, 2014 at 11:27:31AM -0400, Brent Yorgey wrote: > projects last summer (one creating an interactive diagrams pastebin, > http://paste.hskell.org/, which also resulted in spinning off several Whoops, that should be http://paste.hskll.org Although it's (temporarily) down at the moment, oh well. =) -Brent From tomahawkins at gmail.com Tue Mar 11 16:30:44 2014 From: tomahawkins at gmail.com (Tom Hawkins) Date: Tue, 11 Mar 2014 11:30:44 -0500 Subject: [Haskell-cafe] ANN: engineering-units-0.0.1 Message-ID: Hi, I just uploaded a handy library for managing engineering units. It provides a Num type that allows you to mix units into calculations. It also converts between units automatically and will error out if you try to mix values with inconsistent units. Here's an example that computes the horsepower of a hydraulic pump (power = pressure * flow): flow = 20 * gpm -- Gallons per minute. pressure = 3000 * psi -- Pounds per square inch. power = pressure * flow powerHP = value power hp -- Get the value in horsepower. powerKW = value power kw -- Get the value in Kilowatts. If you don't see your units in the library, it's easy to add new ones: mm :: Value mm = 0.001 * m Wish I had this back in college. -Tom http://hackage.haskell.org/package/engineering-units -------------- next part -------------- An HTML attachment was scrubbed... URL: From spam at scientician.net Tue Mar 11 18:48:50 2014 From: spam at scientician.net (Bardur Arantsson) Date: Tue, 11 Mar 2014 19:48:50 +0100 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: On 2014-03-11 09:20, JP Moresmau wrote: > Unifying all the different tools underlying IDEs has been talked again > before, because the pain is real. For example, see > https://github.com/fpco/haskell-ide/wiki. I've written about the GHC API in > that wiki, and some of the issues that it has for such tools. > Currently EclipseFP uses buildwrapper, which is a backend I wrote because I > was dissatisfied with scion. It integrates the GHC API and Cabal, so that > it aims to give the same results that running cabal configure/build. It > usually run as a shortlived executable but for performance reason it is > possible to have a long lived session to avoid reloading the modules in GHC > all the times. > Yes, GHC depends on the Cabal API for some types, which causes untold woes > when you use buildwrapper after upgrading Cabal, for example. There is a > bug report to remove that dependency but I had no time yet to work on it, > so far I've used dynamic-cabal in buildwrapper to allow a newer version of > Cabal, at the price of more complexity. But a complete tool would need to > integrate both, so it can't be ghci only, otherwise Cabal and GHC would > become really stuck together. > The GHC API uses some global settings, which means you sometimes have no > choice (if stcouldatic flags change) than to respawn a new process. This > could probably be improved since it's not really the way a well behaved > Haskell program should act. Memory usage is also a concern. > > So I think there should be two lines of work here: one would be to improve > the GHC API and/or the ghci interface, to make it more IDE friendly, the > other would be to unify all these tools like scion/buildwrapper/ghc-mod in > one tool that would hopefully provide all services an IDE needs, and that > would allow easy plugin of additional functionality (so for example HaRe > could easily add its refactoring capabilities to it). I would happily > switch from buildwrapper to another community supported tool if all the > functionality I currently have is kept in one form or another. > Since you've obviously been doing a lot of investigation here, I thought I might ask: What is GHC using Cabal for in *functional terms*, i.e. what actual functionality is it using? Is it just parsing package information files? What is it using that information for? Would it be possible to supply that information via other mechanisms than GHC snooping in the files? I'm thinking something along the lines of pkg-config here. (I understand the build system is a different issue, let's just ignore that completely.) Regards, From semen at trygub.com Tue Mar 11 19:41:57 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Tue, 11 Mar 2014 19:41:57 +0000 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140311132101.GA32646@nanodesu.talocan.mine.nu> References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> <20140310165436.GA54191@inanna.trygub.com> <20140311120829.GA62991@inanna.trygub.com> <20140311132101.GA32646@nanodesu.talocan.mine.nu> Message-ID: <20140311194157.GA66072@inanna.trygub.com> On Tue, Mar 11, 2014 at 01:21:01PM +0100, Niklas Haas wrote: > > Thank you very much ? it works! [and many new useful functions discovered along the way :-)]. > > > > I'm fairly happy with this solution (using readConstr as suggested by Niklas, > > and fromConstrB, as per above). The only wrinkle now is with this term in the definition of f : > > > > dataTypeOf $ B 1 > > > > We provide a value here (B 1) ? is there a way to make it take the constructor (B) > > instead, or, alternatively, make f aware of the signature of the constructor (Int -> D) and/or the resulting > > data type (D) somehow? I've hoogled it and also looked through Data.Data with no luck? > > > > It's just that constructing a full-blown value of type D might be non-trivial if D is complex, > > but it seems a bit wasteful as we are after the outer constructor alone. > > And of course, if D or types D depends on change we need to modify f? > > > > Thank you, > > S. > > The idiomatic way to handle this kind of stuff normally is to pass an > abstract proxy that carries the type as a type argument, rather than > passing a value of that type itself, eg.: > > > data Proxy a = Proxy > > > > dataTypeOf :: Data a => Proxy a -> DataTypeOf > > or even a more polymorphic version: > > > dataTypeOf :: Data a => f a -> DataTypeOf > > which can be instantiated at any ?f?, including Proxy, [], Maybe or > others. > > Unfortunately, it does not seem that Data.Data.Data has gone for this > route, so my feedback is a bit useless. You could still provide your own > wrapper function (that uses ?undefined? internally, which we know here > to be safe even though it's ugly), though. Thank you for your reply ? I've read it many times, but couldn't translate it into code as of yet. I don't mind ugly as long as it's safe. Specifically, how am I to construct an entity of type DataType (see Data.Data; DataType needs to be fed into readConstr) with the help of a wrapper function you are describing? If someone could in the direction of a skeleton for such a function I might be able to fill in the gaps on my own. But currently I'm stuck? :/ Thanks again, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From carter.schonwald at gmail.com Tue Mar 11 19:49:09 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 11 Mar 2014 15:49:09 -0400 Subject: [Haskell-cafe] On Haskell IDEs In-Reply-To: References: <531DF7D7.3060304@nh2.me> <0b138132-9559-4e6c-9762-4b8bbdb86d3d@googlegroups.com> <531E1349.8070003@nh2.me> <531E27B8.3050902@gmail.com> <531E2D0F.7000201@gmail.com> <531EAC5F.9020300@carlo-hamalainen.net> Message-ID: literally just for sharing the code for that parsing afaik. I think theres a ticket for doing this. On Tue, Mar 11, 2014 at 2:48 PM, Bardur Arantsson wrote: > On 2014-03-11 09:20, JP Moresmau wrote: > > Unifying all the different tools underlying IDEs has been talked again > > before, because the pain is real. For example, see > > https://github.com/fpco/haskell-ide/wiki. I've written about the GHC > API in > > that wiki, and some of the issues that it has for such tools. > > Currently EclipseFP uses buildwrapper, which is a backend I wrote > because I > > was dissatisfied with scion. It integrates the GHC API and Cabal, so that > > it aims to give the same results that running cabal configure/build. It > > usually run as a shortlived executable but for performance reason it is > > possible to have a long lived session to avoid reloading the modules in > GHC > > all the times. > > Yes, GHC depends on the Cabal API for some types, which causes untold > woes > > when you use buildwrapper after upgrading Cabal, for example. There is a > > bug report to remove that dependency but I had no time yet to work on it, > > so far I've used dynamic-cabal in buildwrapper to allow a newer version > of > > Cabal, at the price of more complexity. But a complete tool would need to > > integrate both, so it can't be ghci only, otherwise Cabal and GHC would > > become really stuck together. > > The GHC API uses some global settings, which means you sometimes have no > > choice (if stcouldatic flags change) than to respawn a new process. This > > could probably be improved since it's not really the way a well behaved > > Haskell program should act. Memory usage is also a concern. > > > > So I think there should be two lines of work here: one would be to > improve > > the GHC API and/or the ghci interface, to make it more IDE friendly, the > > other would be to unify all these tools like scion/buildwrapper/ghc-mod > in > > one tool that would hopefully provide all services an IDE needs, and that > > would allow easy plugin of additional functionality (so for example HaRe > > could easily add its refactoring capabilities to it). I would happily > > switch from buildwrapper to another community supported tool if all the > > functionality I currently have is kept in one form or another. > > > > Since you've obviously been doing a lot of investigation here, I thought > I might ask: > > What is GHC using Cabal for in *functional terms*, i.e. what actual > functionality is it using? Is it just parsing package information files? > What is it using that information for? Would it be possible to supply > that information via other mechanisms than GHC snooping in the files? > I'm thinking something along the lines of pkg-config here. > > (I understand the build system is a different issue, let's just ignore > that completely.) > > Regards, > > > _______________________________________________ > 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 miroslav.karpis at gmail.com Tue Mar 11 19:59:03 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Tue, 11 Mar 2014 20:59:03 +0100 Subject: [Haskell-cafe] Library for service(windows) / daemon(linux) Message-ID: Hi Cafe, I need to write a service that should run on windows and on linux (after recompilation of course). One option is to use Qt Service Framework, but I was hoping that I could use Haskell for this task. Unfortunately I can not find anything similar. Please does anybody know about a library that could fulfil more or less the requirement? Cheers, Miro -------------- next part -------------- An HTML attachment was scrubbed... URL: From iusty at k1024.org Tue Mar 11 20:03:13 2014 From: iusty at k1024.org (Iustin Pop) Date: Tue, 11 Mar 2014 21:03:13 +0100 Subject: [Haskell-cafe] ANN: engineering-units-0.0.1 In-Reply-To: References: Message-ID: <20140311200313.GB28974@teal.hq.k1024.org> On Tue, Mar 11, 2014 at 11:30:44AM -0500, Tom Hawkins wrote: > Hi, > > I just uploaded a handy library for managing engineering units. It > provides a Num type that allows you to mix units into calculations. It > also converts between units automatically and will error out if you try to > mix values with inconsistent units. > > Here's an example that computes the horsepower of a hydraulic pump (power = > pressure * flow): > > flow = 20 * gpm -- Gallons per minute. > pressure = 3000 * psi -- Pounds per square inch. > power = pressure * flow > > powerHP = value power hp -- Get the value in horsepower. > powerKW = value power kw -- Get the value in Kilowatts. > > If you don't see your units in the library, it's easy to add new ones: > > mm :: Value > mm = 0.001 * m Hi Tom, Looking at your documentation, I see a lot of sense behind implementing different units (Horsepower vs. Watts), but I'm not so sure about (for example) g/kg or m/cm/mm. These are just (SI) scaling factors, so should they be treated the same as individual units? For just the scaling factors, I released last year http://hackage.haskell.org/package/prefix-units, and I'm wondering if we couldn't somehow combine these two libraries. After all, "k" applies both to KG and KW :) thanks, iustin From carter.schonwald at gmail.com Tue Mar 11 20:05:42 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Tue, 11 Mar 2014 16:05:42 -0400 Subject: [Haskell-cafe] ANN: engineering-units-0.0.1 In-Reply-To: References: Message-ID: neat! Thanks for sharing. Seems like it'll be handy for sanity checking physics ideas before writing the fancy realizations On Tue, Mar 11, 2014 at 12:30 PM, Tom Hawkins wrote: > Hi, > > I just uploaded a handy library for managing engineering units. It > provides a Num type that allows you to mix units into calculations. It > also converts between units automatically and will error out if you try to > mix values with inconsistent units. > > Here's an example that computes the horsepower of a hydraulic pump (power > = pressure * flow): > > flow = 20 * gpm -- Gallons per minute. > pressure = 3000 * psi -- Pounds per square inch. > power = pressure * flow > > powerHP = value power hp -- Get the value in horsepower. > powerKW = value power kw -- Get the value in Kilowatts. > > If you don't see your units in the library, it's easy to add new ones: > > mm :: Value > mm = 0.001 * m > > Wish I had this back in college. > > -Tom > > http://hackage.haskell.org/package/engineering-units > > > _______________________________________________ > 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 mikesteele81 at gmail.com Tue Mar 11 20:15:09 2014 From: mikesteele81 at gmail.com (Michael Steele) Date: Tue, 11 Mar 2014 13:15:09 -0700 Subject: [Haskell-cafe] Library for service(windows) / daemon(linux) In-Reply-To: References: Message-ID: I'm the author of Win32-services [1]. There is a very simple example to show you what such a service looks like. Let me know if you have any questions. [1]: http://hackage.haskell.org/package/Win32-services -- Michael Steele On Tue, Mar 11, 2014 at 12:59 PM, Miro Karpis wrote: > Hi Cafe, > I need to write a service that should run on windows and on linux (after > recompilation of course). > > One option is to use Qt Service Framework, but I was hoping that I could > use Haskell for this task. Unfortunately I can not find anything similar. > > Please does anybody know about a library that could fulfil more or less > the requirement? > > Cheers, > Miro > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- -- Michael Steele -------------- next part -------------- An HTML attachment was scrubbed... URL: From mwm at mired.org Tue Mar 11 20:26:06 2014 From: mwm at mired.org (Mike Meyer) Date: Tue, 11 Mar 2014 16:26:06 -0400 Subject: [Haskell-cafe] ANN: engineering-units-0.0.1 In-Reply-To: <20140311200313.GB28974@teal.hq.k1024.org> References: <20140311200313.GB28974@teal.hq.k1024.org> Message-ID: On Tue, Mar 11, 2014 at 4:03 PM, Iustin Pop wrote: > Looking at your documentation, I see a lot of sense behind implementing > different units (Horsepower vs. Watts), but I'm not so sure about (for > example) g/kg or m/cm/mm. These are just (SI) scaling factors, so should > they be treated the same as individual units? Depends on if the difference shows up to the user. I've been using a calculator/scripting language (Frink) for years that has this kind of facility, and while I know that they are just scaling factors, I still treat them as different types of units. That may be because I grew up using imperial units, and inches/feet/yards/miles don't allow for being treated that way. > For just the scaling factors, I released last year > http://hackage.haskell.org/package/prefix-units, and I'm wondering if we > couldn't somehow combine these two libraries. After all, "k" applies > both to KG and KW :) Yes, but "KV" is not _always_ a kilovolt. When used on an electrical motor, it's a measure of how many thousands of RPM you can expect the motor to turn when for each volt of power it's fed. I'm hoping to get around to desiging the power system for a multirotor this year, and will be interesetd to see how various tools deal with this issue. From douglas.mcclean at gmail.com Tue Mar 11 20:36:30 2014 From: douglas.mcclean at gmail.com (Douglas McClean) Date: Tue, 11 Mar 2014 16:36:30 -0400 Subject: [Haskell-cafe] ANN: engineering-units-0.0.1 In-Reply-To: References: <20140311200313.GB28974@teal.hq.k1024.org> Message-ID: You may also be interested in the various flavors of Bj?rn Buckwalter's dimensional library. On hackage it's dimensional-tf (for type families, and my preference) or dimensional (for multi-parameter type classes). We are working on making a version that takes advantage of the new GHC DataKinds features to provide even more features, that's at https://github.com/bjornbm/dimensional-dk. -Doug On Tue, Mar 11, 2014 at 4:26 PM, Mike Meyer wrote: > > On Tue, Mar 11, 2014 at 4:03 PM, Iustin Pop wrote: > > Looking at your documentation, I see a lot of sense behind implementing > > different units (Horsepower vs. Watts), but I'm not so sure about (for > > example) g/kg or m/cm/mm. These are just (SI) scaling factors, so should > > they be treated the same as individual units? > > Depends on if the difference shows up to the user. I've been using a > calculator/scripting language (Frink) for years that has this kind of > facility, and while I know that they are just scaling factors, I still > treat them as different types of units. That may be because I grew up > using imperial units, and inches/feet/yards/miles don't allow for > being treated that way. > > > For just the scaling factors, I released last year > > http://hackage.haskell.org/package/prefix-units, and I'm wondering if we > > couldn't somehow combine these two libraries. After all, "k" applies > > both to KG and KW :) > > Yes, but "KV" is not _always_ a kilovolt. When used on an electrical > motor, it's a measure of how many thousands of RPM you can expect the > motor to turn when for each volt of power it's fed. I'm hoping to get > around to desiging the power system for a multirotor this year, and > will be interesetd to see how various tools deal with this issue. > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- J. Douglas McClean (781) 561-5540 (cell) -------------- next part -------------- An HTML attachment was scrubbed... URL: From qdunkan at gmail.com Tue Mar 11 20:46:38 2014 From: qdunkan at gmail.com (Evan Laforge) Date: Tue, 11 Mar 2014 13:46:38 -0700 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531EC540.2060608@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> <531EB05E.9050500@fuuzetsu.co.uk> <531EC540.2060608@fuuzetsu.co.uk> Message-ID: I support this idea for purely selfish reasons. I write haskell in vim, and I'm constantly bothered by vim bugs that will likely never be fixed, and I don't dare try to fix them myself because vim source is such a jungle. I have several extensions for syntactic manipulation written in vimscript and python, and they mostly work but not entirely reliably because vim extension is clumsy. I use tags and they also have problems, but once again I'm not about to go in and redo vim's tag support. Etc. etc. Yi is tempting because it promises to be a place where I could fix these things for real, but I've been discouraged in the past by immaturity (can't even get it to build) and lack of documentation. So I think some concentrated attention to the build, documentation, general cleanliness, and performance would be a great idea. I'm not too fussed about a lack of concurrency since I think there are more fundamental problems, but if it would result in improvements to those fundamental problems, I'm all for it. From vogt.adam at gmail.com Tue Mar 11 20:56:29 2014 From: vogt.adam at gmail.com (adam vogt) Date: Tue, 11 Mar 2014 16:56:29 -0400 Subject: [Haskell-cafe] ANN: engineering-units-0.0.1 In-Reply-To: References: <20140311200313.GB28974@teal.hq.k1024.org> Message-ID: Hello, There are many libraries mentioned here too: . I don't know of a good comparison of the various options for runtime and compile-time checked units. Regards, Adam On Tue, Mar 11, 2014 at 4:36 PM, Douglas McClean wrote: > You may also be interested in the various flavors of Bj?rn Buckwalter's > dimensional library. > > On hackage it's dimensional-tf (for type families, and my preference) or > dimensional (for multi-parameter type classes). > > We are working on making a version that takes advantage of the new GHC > DataKinds features to provide even more features, that's at > https://github.com/bjornbm/dimensional-dk. > > > -Doug > > > On Tue, Mar 11, 2014 at 4:26 PM, Mike Meyer wrote: >> >> >> On Tue, Mar 11, 2014 at 4:03 PM, Iustin Pop wrote: >> > Looking at your documentation, I see a lot of sense behind implementing >> > different units (Horsepower vs. Watts), but I'm not so sure about (for >> > example) g/kg or m/cm/mm. These are just (SI) scaling factors, so should >> > they be treated the same as individual units? >> >> Depends on if the difference shows up to the user. I've been using a >> calculator/scripting language (Frink) for years that has this kind of >> facility, and while I know that they are just scaling factors, I still >> treat them as different types of units. That may be because I grew up >> using imperial units, and inches/feet/yards/miles don't allow for >> being treated that way. >> >> > For just the scaling factors, I released last year >> > http://hackage.haskell.org/package/prefix-units, and I'm wondering if we >> > couldn't somehow combine these two libraries. After all, "k" applies >> > both to KG and KW :) >> >> Yes, but "KV" is not _always_ a kilovolt. When used on an electrical >> motor, it's a measure of how many thousands of RPM you can expect the >> motor to turn when for each volt of power it's fed. I'm hoping to get >> around to desiging the power system for a multirotor this year, and >> will be interesetd to see how various tools deal with this issue. >> >> > >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > -- > J. Douglas McClean > > (781) 561-5540 (cell) > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From fuuzetsu at fuuzetsu.co.uk Tue Mar 11 20:57:58 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 11 Mar 2014 20:57:58 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: References: <531DD5BD.8090005@fuuzetsu.co.uk> <531EB05E.9050500@fuuzetsu.co.uk> <531EC540.2060608@fuuzetsu.co.uk> Message-ID: <531F78D6.5030203@fuuzetsu.co.uk> On 11/03/14 20:46, Evan Laforge wrote: > I support this idea for purely selfish reasons. I write haskell in > vim, and I'm constantly bothered by vim bugs that will likely never be > fixed, and I don't dare try to fix them myself because vim source is > such a jungle. I have several extensions for syntactic manipulation > written in vimscript and python, and they mostly work but not entirely > reliably because vim extension is clumsy. I use tags and they also > have problems, but once again I'm not about to go in and redo vim's > tag support. Etc. etc. I do hope that this is where a lot of support for Yi will come from. > Yi is tempting because it promises to be a place where I could fix > these things for real, but I've been discouraged in the past by > immaturity (can't even get it to build) and lack of documentation. So > I think some concentrated attention to the build, documentation, > general cleanliness, and performance would be a great idea. I'm not > too fussed about a lack of concurrency since I think there are more > fundamental problems, but if it would result in improvements to those > fundamental problems, I'm all for it. > While there are more fundamental problems as you mention, we don't stand a chance without concurrency to come close to what existing editors can do. Certainly documentation will get written during the project. I don't explicitly mention it partly because it should implied that we document what we're doing and partly because Google doesn't allow for documentation projects so I didn't want to make it sound like one. PS: If you can't get it to build or are struggling otherwise, please pop into #yi on Freenode and we will almost certainly be able to help you (although you might have to wait for one of us to be online). There's also a mailing list although you might have to wait a bit longer (although a reply is more certain). If you have any specific issues (even if they are ?Please document XYZ?), please do make issues on GitHub! -- Mateusz K. From Coeus at gmx.de Tue Mar 11 23:38:33 2014 From: Coeus at gmx.de (Marc Ziegert) Date: Wed, 12 Mar 2014 00:38:33 +0100 Subject: [Haskell-cafe] pure ghc In-Reply-To: References: Message-ID: An HTML attachment was scrubbed... URL: From haskell at nand.wakku.to Wed Mar 12 00:10:19 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Wed, 12 Mar 2014 01:10:19 +0100 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140311194157.GA66072@inanna.trygub.com> References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> <20140310165436.GA54191@inanna.trygub.com> <20140311120829.GA62991@inanna.trygub.com> <20140311132101.GA32646@nanodesu.talocan.mine.nu> <20140311194157.GA66072@inanna.trygub.com> Message-ID: <20140312011019.GA1483@nanodesu.talocan.mine.nu> On Tue, 11 Mar 2014 19:41:57 +0000, Semen Trygubenko / ????? ?????????? wrote: > On Tue, Mar 11, 2014 at 01:21:01PM +0100, Niklas Haas wrote: > > The idiomatic way to handle this kind of stuff normally is to pass an > > abstract proxy that carries the type as a type argument, rather than > > passing a value of that type itself, eg.: > > > > > data Proxy a = Proxy > > > > > > dataTypeOf :: Data a => Proxy a -> DataTypeOf > > > > or even a more polymorphic version: > > > > > dataTypeOf :: Data a => f a -> DataTypeOf > > Thank you for your reply ? I've read it many times, but couldn't translate it into code > as of yet. > > I don't mind ugly as long as it's safe. > Specifically, how am I to construct an entity of type DataType (see Data.Data; DataType needs to be fed > into readConstr) with the help of a wrapper function you are describing? > > If someone could in the direction of a skeleton for > such a function I might be able to fill in the gaps on my own. > But currently I'm stuck? :/ > > Thanks again, > S. Oops, sorry, that was supposed to have been: > dataTypeOf :: Data a => Proxy a -> DataType or > dataTypeOf :: Data a => p a -> DataType As for the implementation, the simplest possible (ie. no language extensions) implementation I can think of looks like this: > dataTypeOf = Data.dataTypeOf . f > where f :: p a -> a > f _ = error "dataTypeOf: this should never be used" where Data.dataTypeOf refers to the ?original? version of that function. From semen at trygub.com Wed Mar 12 01:34:06 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Wed, 12 Mar 2014 01:34:06 +0000 Subject: [Haskell-cafe] Read instance for constructors? In-Reply-To: <20140312011019.GA1483@nanodesu.talocan.mine.nu> References: <20140310131125.GA53715@inanna.trygub.com> <20140310145414.GA22863@nanodesu.talocan.mine.nu> <20140310145936.GA22969@nanodesu.talocan.mine.nu> <20140310165436.GA54191@inanna.trygub.com> <20140311120829.GA62991@inanna.trygub.com> <20140311132101.GA32646@nanodesu.talocan.mine.nu> <20140311194157.GA66072@inanna.trygub.com> <20140312011019.GA1483@nanodesu.talocan.mine.nu> Message-ID: <20140312013406.GA67437@inanna.trygub.com> Dear Niklas, On Wed, Mar 12, 2014 at 01:10:19AM +0100, Niklas Haas wrote: > Oops, sorry, that was supposed to have been: > > > dataTypeOf :: Data a => Proxy a -> DataType > or > > dataTypeOf :: Data a => p a -> DataType > > As for the implementation, the simplest possible (ie. no language > extensions) implementation I can think of looks like this: > > > dataTypeOf = Data.dataTypeOf . f > > where f :: p a -> a > > f _ = error "dataTypeOf: this should never be used" > > where Data.dataTypeOf refers to the ?original? version of that function. Awesomeness! I see now what you meant by Proxy and that Data.dataTypeOf doesn't even get evaluated, i.e. its sole purpose is to ferry the type information across? Neat. Much obliged, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From danny.gratzer at gmail.com Wed Mar 12 05:49:32 2014 From: danny.gratzer at gmail.com (Danny Gratzer) Date: Wed, 12 Mar 2014 00:49:32 -0500 Subject: [Haskell-cafe] ANN: generic-church-0.1.0.1 Message-ID: Hi cafe! I'm happy to announce the first release of generic-church. A small library for converting types equipped with a [GHC.Generic] instance back and forth between their church representations automatically. For example > let x :: a -> (Int -> a) -> a; x = toChurch $ Just 1 > x False (const True) True And we can go the other way with [fromChurch] > fromChurch (\_ f -> f 1) :: Maybe Int 1 If you're interested in the typeclass/family hacking behind the scenes, I've blogged a few timesabout it. Cheers, Danny Gratzer -------------- next part -------------- An HTML attachment was scrubbed... URL: From joakim at comex.se Wed Mar 12 07:17:26 2014 From: joakim at comex.se (joakim at comex.se) Date: Wed, 12 Mar 2014 07:17:26 +0000 Subject: [Haskell-cafe] pure ghc In-Reply-To: References: Message-ID: Thank you, that works fine for me! Fr?n: Marc Ziegert [mailto:Coeus at gmx.de] Skickat: den 12 mars 2014 00:39 Till: Joakim Goldkuhl Kopia: haskell-cafe at haskell.org ?mne: Aw: [Haskell-cafe] pure ghc that time stamp is generated at link time, not compile time. to remove it, simply use the "strip" tool: echo "main = return ()" > c.hs && ghc -fforce-recomp c.hs && mv c c1 && ghc -fforce-recomp c.hs && mv c c2 && md5sum c1 c2 && strip c1 c2 && md5sum c1 c2 Gesendet: Dienstag, 11. M?rz 2014 um 08:27 Uhr Von: joakim at comex.se An: haskell-cafe at haskell.org Betreff: [Haskell-cafe] pure ghc Hello, If I compile my source code two time I would like to get the same binary. But currently when I run echo "main = return ()" > c.hs && ghc -fforce-recomp c.hs && xxd c > c1.hex && ghc -fforce-recomp c.hs && xxd c > c2.hex && diff c1.hex c2.hex my output is [1 of 1] Compiling Main ( c.hs, c.o ) Linking c ... [1 of 1] Compiling Main ( c.hs, c.o ) Linking c ... 55494c55494 < 00d8c50: 7400 6768 6333 3130 3830 5f30 2e63 0073 t.ghc31080_0.c.s --- > 00d8c50: 7400 6768 6333 3130 3935 5f30 2e63 0073 t.ghc31095_0.c.s So why does the binary differ? Is there a way to compile with ghc and get the same binary? Even though only one byte differ, the checksum (sha,md5,..) is completely changed? I?m running Linux and ghc 7.6.3. Regards, Joakim _______________________________________________ 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 w.s.swierstra at uu.nl Thu Mar 13 10:08:56 2014 From: w.s.swierstra at uu.nl (Wouter Swierstra) Date: Thu, 13 Mar 2014 11:08:56 +0100 Subject: [Haskell-cafe] Haskell Symposium 2014: Call for papers Message-ID: =================================================================== ACM SIGPLAN HASKELL SYMPOSIUM 2014 CALL FOR SUBMISSIONS Gothenburg, Sweden, 4-5 September 2014, directly after ICFP http://www.haskell.org/haskell-symposium/2014 haskell2014 at easychair.org =================================================================== The ACM SIGPLAN Haskell Symposium 2014 will be colocated with the 2014 International Conference on Functional Programming (ICFP) in Gothenburg, Sweden. Like last year, the symposium will last 2 days. Thanks to broader participation from a growing community, we will be able to include more regular papers as well as system demonstrations, while upholding the scientific quality of the symposium. The Haskell Symposium seeks to present original research on Haskell, to discuss practical experience and future development of the language, as well as to promote other forms of denotative programming. Topics of interest include * Language Design, with a focus on possible extensions and modifications of Haskell as well as critical discussions of the status quo; * Theory, such as formal semantics of the present language or future extensions, type systems, effects, metatheory, and foundations for program analysis and transformation; * Implementations, including program analysis and transformation, static and dynamic compilation for sequential, parallel, and distributed architectures, memory management, as well as foreign function and component interfaces; * Tools, such as profilers, tracers, debuggers, preprocessors, and testing tools; * Applications, to scientific and symbolic computing, databases, multimedia, telecommunication, the web, and so forth; * Functional Pearls, being elegant and instructive programming examples; * Experience Reports, to document general practice and experience in education, industry, or other contexts. Such reports are shorter than regular papers; they are limited to six pages. Papers in the latter two categories need not necessarily report original research results. They may report instead, for example, reusable programming idioms, elegant ways to approach a problem, or practical experience that will be useful to other users, implementors, or researchers. The key criterion for such a paper is that it makes a contribution from which other Haskellers can benefit. It is not enough simply to describe a program! Regular papers should explain their research contributions in both general and technical terms, identifying what has been accomplished, explaining why it is significant, and relating it to previous work (also for other languages where appropriate). In addition, we solicit proposals for * System Demonstrations (no longer than a regular paper talk), based on running (perhaps prototype) software rather than necessarily on novel research results. These proposals should summarize the system capabilities that would be demonstrated. The proposals should explain (and will be judged on) whether the ensuing session is likely to be important and interesting to the Haskell community at large, whether on grounds academic or industrial, theoretical or practical, technical or social. Please contact the program chair with any questions about the relevance of a proposal. Travel Support: =============== Student attendees with accepted papers can apply for a SIGPLAN PAC grant to help cover travel expenses. PAC also offers other support, such as for child-care expenses during the meeting or for travel costs for companions of SIGPLAN members with physical disabilities, as well as for travel from locations outside of North America and Europe. For details on the PAC programme, see its web page (http://www.sigplan.org/PAC.htm). Proceedings: ============ ACM Press will publish formal proceedings. Accepted papers will be included in the ACM Digital Library. Authors must grant ACM publication rights upon acceptance (http://authors.acm.org/main.html), but may retain copyright if they wish. Authors are encouraged to publish auxiliary material with their paper (source code, test data, and so forth). The proceedings will be freely available for download from the ACM Digital Library from one week before the start of the conference until two weeks after the conference. Accepted proposals for system demonstrations will be posted on the symposium web page, but not formally published in the proceedings. Submission Details: =================== Submitted papers should be in portable document format (PDF), formatted using the ACM SIGPLAN style guidelines (http://www.acm.org/sigs/sigplan/authorInformation.htm). The text should be in a 9-point font in two columns. The length is restricted to 12 pages, except for "Experience Report" papers, which are restricted to 6 pages. Papers need not fill the page limit. Each paper submission must adhere to SIGPLAN's republication policy, as explained on the web. Proposals for system demonstrations are limited to 2-page abstracts, in the same ACM format as papers. "Functional Pearls", "Experience Reports", and "Demo Proposals" should be marked as such with those words in the title at time of submission. The paper submission deadline and length limitations are firm. There will be no extensions, and papers violating the length limitations will be summarily rejected. Submission is via EasyChair: https://www.easychair.org/conferences/?conf=haskell14 * Abstract submission: Fri 09 May 2014 * Paper submission : Mon 12 May 2014 * Demo submission : Fri 30 May 2014 (prior abstract submission unnecessary) * Author notification: Wed 11 June 2014 * Final papers due : Sun 22 June 2014 All deadlines, except the final papers deadline, are in Standard Samoan Time. Programme Committee: ==================== George Giorgidze - Standard Chartered Bank Mauro Jaskelioff - Universidad Nacional de Rosario Mark Jones - Portland State University Lindsey Kuper - Indiana University Jos? Pedro Magalh?es - University of Oxford Geoffrey Mainland - Drexel University Simon Marlow - Facebook Shin Cheng Mu - Academia Sinica Keiko Nakata - Institute of Cybernetics, Tallinn University of Technology Bruno Oliveira - University of Hong Kong Lee Pike - Galois Josef Svenningsson - Chalmers University of Technology Wouter Swierstra - University of Utrecht (chair) Simon Thompson - University of Kent From silvio.frischi at gmail.com Thu Mar 13 16:15:42 2014 From: silvio.frischi at gmail.com (Silvio Frischknecht) Date: Thu, 13 Mar 2014 17:15:42 +0100 Subject: [Haskell-cafe] Track Exceptions Message-ID: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> Hi everyone, It's always very annoying not knowing what could go wrong (what exceptions might be thrown) when calling a library function. In java doc, for instance, you can usually see what exceptions can be thrown by a specific function. I was wondering if this could be achieved for haskell by tracing "throw" and "catch" calls. Silvio From r.koot at uu.nl Thu Mar 13 16:45:12 2014 From: r.koot at uu.nl (Ruud Koot) Date: Thu, 13 Mar 2014 17:45:12 +0100 Subject: [Haskell-cafe] Track Exceptions In-Reply-To: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> Message-ID: In theory, yes, but the situation becomes more complicated for higher-order languages such as Haskell than it is for first-order(ish) languages such as Java.* 1) Consider the higher-order function 'map'. With tracked exceptions you would probably want to give it a type such as: map :: forall a b e. (a -> b throws e) -> [a] -> [b] throws e I.e., you need some kind of exception polymorphism, or severely restrict the kind of functions you would be allowed to pass to map (basically those that are guaranteed to not raise any exceptions). 2) One of the most commonly encountered run-time exception in Haskell is a pattern-match failure. Whether or not these are triggered depends not only on the control flow within your program, but also on the data flow, making them harder to track. Some relevant references would be: - Kevin Glynn, Peter J. Stuckey, Martin Sulzmann & Harald S?ndergaard. "Exception analysis for non-strict languages". ICFP '02. http://dl.acm.org/citation.cfm?id=581488 - Ruud Koot & Jurriaan Hage. "Type-based exception analysis for higher-order non-strict languages with imprecise exception semantics". Submitted to ICFP '14. http://www.staff.science.uu.nl/~0422819/tbea/icfp14.pdf Ruud * Technically, object-oriented languages are also higher-order languages and one can find examples where the lack of exception polymorphism can cause trouble for Java's tracked exception mechanism. On Thu, Mar 13, 2014 at 5:15 PM, Silvio Frischknecht wrote: > Hi everyone, > > It's always very annoying not knowing what could go wrong (what exceptions > might be thrown) when calling a library function. In java doc, for instance, > you can usually see what exceptions can be thrown by a specific function. I was > wondering if this could be achieved for haskell by tracing "throw" and "catch" > calls. > > Silvio > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From roma at ro-che.info Thu Mar 13 16:54:59 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Thu, 13 Mar 2014 18:54:59 +0200 Subject: [Haskell-cafe] Track Exceptions In-Reply-To: References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> Message-ID: <20140313165459.GA11627@sniper> * Ruud Koot [2014-03-13 17:45:12+0100] > 1) Consider the higher-order function 'map'. With tracked exceptions > you would probably want to give it a type such as: > > map :: forall a b e. (a -> b throws e) -> [a] -> [b] throws e > > I.e., you need some kind of exception polymorphism, or severely > restrict the kind of functions you would be allowed to pass to map > (basically those that are guaranteed to not raise any exceptions). Simply instantiating b with b `Throws` e gives map :: (a -> b `Throws` e) -> [a] -> [b `Throws` e] Which is actually a more useful type than the one you proposed, because it shows that map itself doesn't throw exceptions (so that e.g. computing length is safe). Assuming "Throws e" is a monad, you could use mapM instead of map to get the behavior you want. In fact, Throws will probably need to be an indexed monad. Roman -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 819 bytes Desc: Digital signature URL: From danburton.email at gmail.com Thu Mar 13 16:59:14 2014 From: danburton.email at gmail.com (Dan Burton) Date: Thu, 13 Mar 2014 09:59:14 -0700 Subject: [Haskell-cafe] Track Exceptions In-Reply-To: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> Message-ID: If you want to read the literature on this topic, here's a place to start: http://homepages.inf.ed.ac.uk/wadler/topics/blame.html -- Dan Burton On Thu, Mar 13, 2014 at 9:15 AM, Silvio Frischknecht < silvio.frischi at gmail.com> wrote: > Hi everyone, > > It's always very annoying not knowing what could go wrong (what exceptions > might be thrown) when calling a library function. In java doc, for > instance, > you can usually see what exceptions can be thrown by a specific function. > I was > wondering if this could be achieved for haskell by tracing "throw" and > "catch" > calls. > > Silvio > _______________________________________________ > 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 r.koot at uu.nl Thu Mar 13 17:09:10 2014 From: r.koot at uu.nl (Ruud Koot) Date: Thu, 13 Mar 2014 18:09:10 +0100 Subject: [Haskell-cafe] Track Exceptions In-Reply-To: <20140313165459.GA11627@sniper> References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> <20140313165459.GA11627@sniper> Message-ID: On Thu, Mar 13, 2014 at 5:54 PM, Roman Cheplyaka wrote: > Simply instantiating b with b `Throws` e gives > > map :: (a -> b `Throws` e) -> [a] -> [b `Throws` e] > > Which is actually a more useful type than the one you proposed, because it shows > that map itself doesn't throw exceptions (so that e.g. computing length is > safe). > > Assuming "Throws e" is a monad, you could use mapM instead of map to get the > behavior you want. > > In fact, Throws will probably need to be an indexed monad. > > Roman Yes, lazyness complicates things even further. You can pass a function to map that produces an "exception value" of type b. These exceptions would be attached to the elements inside the list [b] as you suggest. But there might also be exceptional values hidden inside the spine of the second argument of type [a]. These would need to end up in the spine of the resulting list of type [b]. Ruud From carter.schonwald at gmail.com Thu Mar 13 19:34:51 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 13 Mar 2014 15:34:51 -0400 Subject: [Haskell-cafe] Track Exceptions In-Reply-To: References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> <20140313165459.GA11627@sniper> Message-ID: Well, Ghc 7.10 is planned to have Stack Traces, which should be exposed as part of the Exceptions data model once that gets added, I believe that will help quite a bit! -Carter On Thu, Mar 13, 2014 at 1:09 PM, Ruud Koot wrote: > On Thu, Mar 13, 2014 at 5:54 PM, Roman Cheplyaka wrote: > > Simply instantiating b with b `Throws` e gives > > > > map :: (a -> b `Throws` e) -> [a] -> [b `Throws` e] > > > > Which is actually a more useful type than the one you proposed, because > it shows > > that map itself doesn't throw exceptions (so that e.g. computing length > is > > safe). > > > > Assuming "Throws e" is a monad, you could use mapM instead of map to get > the > > behavior you want. > > > > In fact, Throws will probably need to be an indexed monad. > > > > Roman > > Yes, lazyness complicates things even further. You can pass a function > to map that produces an "exception value" of type b. These exceptions > would be attached to the elements inside the list [b] as you suggest. > But there might also be exceptional values hidden inside the spine of > the second argument of type [a]. These would need to end up in the > spine of the resulting list of type [b]. > > Ruud > _______________________________________________ > 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 jays at panix.com Thu Mar 13 22:01:02 2014 From: jays at panix.com (Jay Sulzberger) Date: Thu, 13 Mar 2014 18:01:02 -0400 (EDT) Subject: [Haskell-cafe] Track Exceptions In-Reply-To: References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> Message-ID: On Thu, 13 Mar 2014, Ruud Koot wrote: > In theory, yes, but the situation becomes more complicated for > higher-order languages such as Haskell than it is for first-order(ish) > languages such as Java.* > > 1) Consider the higher-order function 'map'. With tracked exceptions > you would probably want to give it a type such as: > > map :: forall a b e. (a -> b throws e) -> [a] -> [b] throws e Perhaps one should have a functor going from the category of badly instrumented source code to the category of instrumented source code. Or perhaps to the category of instrumented run time instances. oo--JS. > > I.e., you need some kind of exception polymorphism, or severely > restrict the kind of functions you would be allowed to pass to map > (basically those that are guaranteed to not raise any exceptions). > > 2) One of the most commonly encountered run-time exception in Haskell > is a pattern-match failure. Whether or not these are triggered depends > not only on the control flow within your program, but also on the data > flow, making them harder to track. > > Some relevant references would be: > > - Kevin Glynn, Peter J. Stuckey, Martin Sulzmann & Harald S?ndergaard. > "Exception analysis for non-strict languages". ICFP '02. > http://dl.acm.org/citation.cfm?id=581488 > - Ruud Koot & Jurriaan Hage. "Type-based exception analysis for > higher-order non-strict languages with imprecise exception semantics". > Submitted to ICFP '14. > http://www.staff.science.uu.nl/~0422819/tbea/icfp14.pdf > > > Ruud > > > > * Technically, object-oriented languages are also higher-order > languages and one can find examples where the lack of exception > polymorphism can cause trouble for Java's tracked exception mechanism. > > On Thu, Mar 13, 2014 at 5:15 PM, Silvio Frischknecht > wrote: >> Hi everyone, >> >> It's always very annoying not knowing what could go wrong (what exceptions >> might be thrown) when calling a library function. In java doc, for instance, >> you can usually see what exceptions can be thrown by a specific function. I was >> wondering if this could be achieved for haskell by tracing "throw" and "catch" >> calls. >> >> Silvio >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > From rendel at informatik.uni-marburg.de Thu Mar 13 22:49:38 2014 From: rendel at informatik.uni-marburg.de (Tillmann Rendel) Date: Thu, 13 Mar 2014 23:49:38 +0100 Subject: [Haskell-cafe] Track Exceptions In-Reply-To: References: <2171985.tJN9Zj6kTN@moviepc-fl377aa-uuz-m9451ch> Message-ID: <53223602.1000809@informatik.uni-marburg.de> Hi, Ruud Koot wrote: > 1) Consider the higher-order function 'map'. With tracked exceptions > you would probably want to give it a type such as: > > map :: forall a b e. (a -> b throws e) -> [a] -> [b] throws e To account for exceptions hidden in thunks, I would have expected something more like this: map :: forall a b e1 e2 e3 e4 . (forall e . a throws e -> b throws e1 e) throws e2 -> [a throws e3] throws e4 -> [b throws (e1 e3, e2)] throws e4 map f [] = [] map f (x :: xs) = f x :: map f xs Note that e1 is of kind "exception -> exception". If it is a constant function, f does not force its argument; if it is the identity function, f forces its argument but cannot throw any other exceptions; etc. Interestingly, exception tracking seems to feel like strictness analysis. Tillmann From hjgtuyl at chello.nl Thu Mar 13 23:17:13 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Fri, 14 Mar 2014 00:17:13 +0100 Subject: [Haskell-cafe] =?utf-8?b?z4AtZGF5?= Message-ID: Happy Pi Day! [0] Henk-Jan van Tuyl [0] http://en.wikipedia.org/wiki/Pi_day -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From fuuzetsu at fuuzetsu.co.uk Thu Mar 13 23:23:23 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 13 Mar 2014 23:23:23 +0000 Subject: [Haskell-cafe] =?utf-8?b?z4AtZGF5?= In-Reply-To: References: Message-ID: <53223DEB.9090608@fuuzetsu.co.uk> On 13/03/14 23:17, Henk-Jan van Tuyl wrote: > > Happy Pi Day! [0] > > Henk-Jan van Tuyl > > > [0] http://en.wikipedia.org/wiki/Pi_day > > Cue the ? fans. -- Mateusz K. From ivan.miljenovic at gmail.com Thu Mar 13 23:58:12 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Fri, 14 Mar 2014 10:58:12 +1100 Subject: [Haskell-cafe] =?utf-8?b?z4AtZGF5?= In-Reply-To: References: Message-ID: On 14 March 2014 10:17, Henk-Jan van Tuyl wrote: > > Happy Pi Day! [0] How does 14/3/2014 relate to pi in any fashion? :P > > Henk-Jan van Tuyl > > > [0] http://en.wikipedia.org/wiki/Pi_day > > > -- > Folding at home > What if you could share your unused computer power to help find a cure? In > just 5 minutes you can join the world's biggest networked computer and get > us closer sooner. Watch the video. > http://folding.stanford.edu/ > > > http://Van.Tuyl.eu/ > http://members.chello.nl/hjgtuyl/tourdemonad.html > Haskell programming > -- > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From vigalchin at gmail.com Fri Mar 14 02:12:35 2014 From: vigalchin at gmail.com (Vasili I. Galchin) Date: Thu, 13 Mar 2014 21:12:35 -0500 Subject: [Haskell-cafe] Fwd: WSJ.com - Coding isn't just for those IT guys anymore In-Reply-To: <2042480.868001394761693844.JavaMail.appadmin@sbkj2kpubp01> References: <2042480.868001394761693844.JavaMail.appadmin@sbkj2kpubp01> Message-ID: I wish Haskell could get this kind of media coverage .... ;<) Vasili ---------- Forwarded message ---------- From: vigalchin at gmail.com Date: Thu, Mar 13, 2014 at 8:48 PM Subject: WSJ.com - Coding isn't just for those IT guys anymore To: vigalchin at gmail.com Cc: vigalchin at gmail.com [image: The Wall Street Journal] * Please note, the sender's email address has not been verified You have received the following link from *vigalchin at gmail.com* :. WSJ.com - Coding isn't just for those IT guys anymore Subscriber-only content will be available to non-subscribers for up to seven days after it is emailed. This article can also be accessed if you copy and paste the entire address below into your web browser. http://online.wsj.com/news/article_email/SB30001424052702304709904579411354120634252-lMyQjAzMTA0MDEwMzExNDMyWj -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Mar 14 02:45:48 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 13 Mar 2014 22:45:48 -0400 Subject: [Haskell-cafe] Fwd: WSJ.com - Coding isn't just for those IT guys anymore In-Reply-To: References: <2042480.868001394761693844.JavaMail.appadmin@sbkj2kpubp01> Message-ID: then put int the time to talk with smart engineers you know and get them excited and learn! Its hard work, but if you (dear reader) don't do it, who will? Advocacy doesn't come from trees, it comes from member of the community talking to people in real life! :) -Carter On Thu, Mar 13, 2014 at 10:12 PM, Vasili I. Galchin wrote: > > I wish Haskell could get this kind of media coverage .... ;<) > > Vasili > > ---------- Forwarded message ---------- > From: vigalchin at gmail.com > Date: Thu, Mar 13, 2014 at 8:48 PM > Subject: WSJ.com - Coding isn't just for those IT guys anymore > To: vigalchin at gmail.com > Cc: vigalchin at gmail.com > > > [image: The Wall Street Journal] > > * Please note, the sender's email address has not been verified > > You have received the following link from *vigalchin at gmail.com* > :. > WSJ.com - Coding isn't just for those IT guys anymore > > Subscriber-only content will be available to non-subscribers for up to > seven days after it is emailed. > > This article can also be accessed if you copy and paste the entire address > below > > into your web browser. > > > http://online.wsj.com/news/article_email/SB30001424052702304709904579411354120634252-lMyQjAzMTA0MDEwMzExNDMyWj > > > _______________________________________________ > 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 dedgrant at gmail.com Fri Mar 14 07:55:25 2014 From: dedgrant at gmail.com (Darren Grant) Date: Fri, 14 Mar 2014 00:55:25 -0700 Subject: [Haskell-cafe] Fwd: WSJ.com - Coding isn't just for those IT guys anymore In-Reply-To: References: <2042480.868001394761693844.JavaMail.appadmin@sbkj2kpubp01> Message-ID: If any of you are in the Vancouver BC area, Polyglot is taking votes for a Haskell tutorial session this year. I'd love to see more here. Cheers, Darren On Mar 13, 2014 7:46 PM, "Carter Schonwald" wrote: > > then put int the time to talk with smart engineers you know and get them excited and learn! > > Its hard work, but if you (dear reader) don't do it, who will? Advocacy doesn't come from trees, it comes from member of the community talking to people in real life! > > :) > -Carter > > > On Thu, Mar 13, 2014 at 10:12 PM, Vasili I. Galchin wrote: >> >> >> I wish Haskell could get this kind of media coverage .... ;<) >> >> Vasili >> >> ---------- Forwarded message ---------- >> From: vigalchin at gmail.com >> Date: Thu, Mar 13, 2014 at 8:48 PM >> Subject: WSJ.com - Coding isn't just for those IT guys anymore >> To: vigalchin at gmail.com >> Cc: vigalchin at gmail.com >> >> >> * Please note, the sender's email address has not been verified >> >> You have received the following link from vigalchin at gmail.com:. >> >> WSJ.com - Coding isn't just for those IT guys anymore >> >> Subscriber-only content will be available to non-subscribers for up to seven days after it is emailed. >> >> This article can also be accessed if you copy and paste the entire address below >> >> into your web browser. >> >> http://online.wsj.com/news/article_email/SB30001424052702304709904579411354120634252-lMyQjAzMTA0MDEwMzExNDMyWj >> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From lutz at iks-jena.de Fri Mar 14 09:20:39 2014 From: lutz at iks-jena.de (Lutz Donnerhacke) Date: Fri, 14 Mar 2014 09:20:39 +0000 (UTC) Subject: [Haskell-cafe] =?utf-8?b?z4AtZGF5?= References: Message-ID: * Ivan Lazar Miljenovic wrote: > How does 14/3/2014 relate to pi in any fashion? :P Imperal Pi day is next year: 3/14/15 From michel at kuhlmanns.info Fri Mar 14 11:45:59 2014 From: michel at kuhlmanns.info (Michel Kuhlmann) Date: Fri, 14 Mar 2014 12:45:59 +0100 Subject: [Haskell-cafe] GSOC Project Ideas Message-ID: <20140314114558.GA12368@s15427742.onlinehome-server.info> I would like to see gitit2 [1] replacing gitit [2]. gitit2 uses yesod as a foundation; currently not all features of gitit are implemented yet; despite from that, it is not up-to-date with current yesod (not compiling). The old gitit has quite some bugs; and it is not easy to extent it. -Michel [1]: https://github.com/jgm/gitit2.git [2]: https://github.com/jgm/gitit.git From carter.schonwald at gmail.com Fri Mar 14 12:32:24 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 14 Mar 2014 08:32:24 -0400 Subject: [Haskell-cafe] GSOC Project Ideas In-Reply-To: <20140314114558.GA12368@s15427742.onlinehome-server.info> References: <20140314114558.GA12368@s15427742.onlinehome-server.info> Message-ID: I don't think gitit2 is ready for a Gsoc (and I say that as Somone who might be taking over working on it...) On Friday, March 14, 2014, Michel Kuhlmann wrote: > I would like to see gitit2 [1] replacing gitit [2]. > > gitit2 uses yesod as a foundation; currently not all features of gitit > are implemented yet; despite from that, it is not up-to-date with current > yesod (not compiling). > > The old gitit has quite some bugs; and it is not easy to extent it. > > -Michel > > [1]: https://github.com/jgm/gitit2.git > [2]: https://github.com/jgm/gitit.git > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From christianlaustsen at gmail.com Fri Mar 14 14:52:37 2014 From: christianlaustsen at gmail.com (Christian Laustsen) Date: Fri, 14 Mar 2014 14:52:37 +0000 (UTC) Subject: [Haskell-cafe] =?utf-8?b?z4AtZGF5?= References: Message-ID: Lutz Donnerhacke iks-jena.de> writes: > > * Ivan Lazar Miljenovic wrote: > > How does 14/3/2014 relate to pi in any fashion? :P > > Imperal Pi day is next year: 3/14/15 > Actually, Pi *day* is today, >>3/14<< (2014). You could say that pi year, or something like that, is next year. From amy at nualeargais.ie Fri Mar 14 16:03:09 2014 From: amy at nualeargais.ie (Amy de =?utf-8?b?QnVpdGzDqWly?=) Date: Fri, 14 Mar 2014 16:03:09 +0000 (UTC) Subject: [Haskell-cafe] Changes to cabal-install Message-ID: I have a couple of questions about the latest cabal-install release, and I haven't been able to find the release notes (checked GitHub, the Haskell.org wiki, googled, etc.) Here's what I'm running: amy at wombat$ cabal --version cabal-install version 1.18.0.3 using version 1.18.1.3 of the Cabal library Question 1 ---------- Until recently, the command cabal install --enable-tests used to build and run the tests. Now it seems I need to do cabal test which then compiles the tests and runs them. So is the --enable-tests flag doing anything, or is it now obsolete? Question 2 ---------- With my project, I do, in order: 1. cabal sandbox init --sandbox 2. cabal install --only-dependencies 3. cabal build --ghc-options=-Werror 4. cabal test But when I do step 3, I get a strange warning message: "The sandbox was created after the package was already configured." Huh? Creating the sandbox was the first thing I did! If instead, I replace step 3 with 3. cabal install --ghc-options=-Werror then I don't get the warning message until step 4. From the.dead.shall.rise at gmail.com Fri Mar 14 16:22:27 2014 From: the.dead.shall.rise at gmail.com (Mikhail Glushenkov) Date: Fri, 14 Mar 2014 17:22:27 +0100 Subject: [Haskell-cafe] Changes to cabal-install In-Reply-To: References: Message-ID: Hi, On 14 March 2014 17:03, Amy de Buitl?ir wrote: > > Question 1 > ---------- > Until recently, the command > > cabal install --enable-tests > > used to build and run the tests. Now it seems I need to do > > cabal test > > which then compiles the tests and runs them. So is the --enable-tests flag > doing anything, or is it now obsolete? Using 'cabal test' is preferable. You don't want to reinstall the package each time you run the test suite. > Question 2 > ---------- > With my project, I do, in order: > > 1. cabal sandbox init --sandbox > 2. cabal install --only-dependencies > 3. cabal build --ghc-options=-Werror > 4. cabal test > > But when I do step 3, I get a strange warning message: "The sandbox was > created after the package was already configured." Huh? Creating the sandbox > was the first thing I did! Does this still happen with cabal-install HEAD? If it does, please file an issue here: https://github.com/haskell/cabal/issues/new From PascalWittmann at gmx.net Fri Mar 14 16:33:43 2014 From: PascalWittmann at gmx.net (Pascal Wittmann) Date: Fri, 14 Mar 2014 17:33:43 +0100 Subject: [Haskell-cafe] Changes to cabal-install In-Reply-To: References: Message-ID: <53232F67.3030503@gmx.net> On 03/14/2014 05:03 PM, Amy de Buitl?ir wrote: > I have a couple of questions about the latest cabal-install release, and I > haven't been able to find the release notes (checked GitHub, the Haskell.org > wiki, googled, etc.) I have opened an issue [1] on github regarding the missing release notes/change log, but got there no response so far. Would be cool if the release notes could be continued. [1] https://github.com/haskell/cabal/issues/1657 -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 263 bytes Desc: OpenPGP digital signature URL: From the.dead.shall.rise at gmail.com Fri Mar 14 16:59:05 2014 From: the.dead.shall.rise at gmail.com (Mikhail Glushenkov) Date: Fri, 14 Mar 2014 17:59:05 +0100 Subject: [Haskell-cafe] Changes to cabal-install In-Reply-To: <53232F67.3030503@gmx.net> References: <53232F67.3030503@gmx.net> Message-ID: Hi, On 14 March 2014 17:33, Pascal Wittmann wrote: > > I have opened an issue [1] on github regarding the missing release > notes/change log, but got there no response so far. Would be cool if the > release notes could be continued. Release notes for 1.18 are available on my blog [1]. Yes, the official changelog should be updated, I just haven't got around to that yet. [1] http://coldwa.st/e/blog/2013-08-21-Cabal-1-18.html From omeragacan at gmail.com Fri Mar 14 16:59:53 2014 From: omeragacan at gmail.com (=?ISO-8859-9?Q?=D6mer_Sinan_A=F0acan?=) Date: Fri, 14 Mar 2014 18:59:53 +0200 Subject: [Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs In-Reply-To: References: <531C1CEE.5030202@fuuzetsu.co.uk> <531C5436.9000904@fuuzetsu.co.uk> Message-ID: Hi Stephen, I just finished implementing the type checker. I used the first method I mentioned in my previous mail, and it worked great. It may still contain some bugs but it works fine on current test suite. (test programs in original min-caml implementation). If you're still interested, source code is here https://github.com/osa1/minCaml.hs/blob/master/src/MinCaml/Typing.hs --- ?mer Sinan A?acan http://osa1.net From brandon.m.simmons at gmail.com Fri Mar 14 20:32:12 2014 From: brandon.m.simmons at gmail.com (Brandon Simmons) Date: Fri, 14 Mar 2014 16:32:12 -0400 Subject: [Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want? Message-ID: I've used TypeFamilies numerous times in code and library APIs to get more powerful and creative type-checking, and I seem to always use it in the same way that ends up feeling like abuse. For instance here's an example I started to sketch up for a talk I'm giving; this is to be a type-checked RPN calculator, used e.g. like `eval () (1,(2,((+),())))`: ``` {-# LANGUAGE TypeFamilies , MultiParamTypeClasses , FlexibleInstances , UndecidableInstances #-} type family EvaledStack x stack type instance EvaledStack Int st = (Int,st) type instance EvaledStack (Int -> x) (Int,st) = EvaledStack x st type family FinalStack string initialStack type instance FinalStack () st = st type instance FinalStack (x,xs) st = FinalStack xs (EvaledStack x st) class EvalStep x stack where evalStep :: x -> stack -> EvaledStack x stack instance (EvalStep x st)=> EvalStep (Int -> x) (Int,st) where evalStep f (int,st) = evalStep (f int) st instance EvalStep Int st where evalStep int st = (int,st) class Eval string initialStack where eval :: initialStack -> string -> FinalStack string initialStack instance Eval () st where eval st () = st instance (EvalStep x st, Eval xs (EvaledStack x st))=> Eval (x,xs) st where eval st (x, xs) = eval (evalStep x st) xs ``` The code above is just a WIP, but notice several things: 1) It's intended to be "closed" but I can't express that 2) I need to use UndecidableInstances for the nested type family instances, even though the recursion I'm doing is simple 3) The classes are "ugly" with arbitrary instance heads 4) If I want to support polymorphic operators/operands I need to use OverlappingInstances, which is another layer of hack 5) Users get an unhelpful error from the type-checker if their RPN expression is ill-typed I think what I'm trying to do is fundamentally pretty simple, but I only have the tools to do it in the very ad-hoc way I've described. I think the new closed type families help me here, but I'm wondering: - have there been any proposals or discussions about this use case, or a name given to it? - do closed type families provide an elegant solution and I just don't realize it yet? - do other people find themselves using this pattern as well, or have I just gotten caught up in a strange way of abusing these extensions? Thanks a lot, Brandon -------------- next part -------------- An HTML attachment was scrubbed... URL: From hjgtuyl at chello.nl Fri Mar 14 20:36:53 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Fri, 14 Mar 2014 21:36:53 +0100 Subject: [Haskell-cafe] =?utf-8?b?z4AtZGF5?= In-Reply-To: References: Message-ID: On Fri, 14 Mar 2014 15:52:37 +0100, Christian Laustsen wrote: > Lutz Donnerhacke iks-jena.de> writes: >> * Ivan Lazar Miljenovic wrote: >> > How does 14/3/2014 relate to pi in any fashion? :P >> >> Imperal Pi day is next year: 3/14/15 > > Actually, Pi *day* is today, >>3/14<< (2014). You could say that pi year, > or something like that, is next year. 3/14 (in m/yy notation) is Pi Month (so, this whole month). -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From walkiner at eecs.oregonstate.edu Fri Mar 14 21:19:40 2014 From: walkiner at eecs.oregonstate.edu (Eric Walkingshaw) Date: Fri, 14 Mar 2014 22:19:40 +0100 Subject: [Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want? In-Reply-To: References: Message-ID: I'm not sure if this answers your questions, but I think this particular problem has a cleaner solution with GADTs: {-# LANGUAGE GADTs #-} data Cmd s t where Push :: a -> Cmd s (a,s) F1 :: (a -> b) -> Cmd (a,s) (b,s) F2 :: (a -> b -> c) -> Cmd (a,(b,s)) (c,s) data Prog s t where (:.) :: Cmd s t -> Prog t u -> Prog s u End :: Prog s s infixr 5 :. cmd :: Cmd s t -> s -> t cmd (Push a) s = (a, s) cmd (F1 f) (a,s) = (f a, s) cmd (F2 f) (a,(b,s)) = (f a b, s) prog :: Prog s t -> s -> t prog (c :. p) s = prog p (cmd c s) prog End s = s run :: Prog () t -> t run p = prog p () Then from GHCi: > run (Push 3 :. Push 4 :. F2 (+) :. F1 show :. End) ("7",()) Maybe you really want GADTs? :) -Eric -------------- next part -------------- An HTML attachment was scrubbed... URL: From jake.mcarthur at gmail.com Fri Mar 14 21:52:03 2014 From: jake.mcarthur at gmail.com (Jake McArthur) Date: Fri, 14 Mar 2014 17:52:03 -0400 Subject: [Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want? In-Reply-To: References: Message-ID: A benefit of using type families and type classes instead of GADTs for this kind of thing when you can is they are usually cheaper. You can often write code that inlines perfectly with former but ends up being some recursive function that will never inline with the latter. - Jake On Mar 14, 2014 5:20 PM, "Eric Walkingshaw" wrote: > I'm not sure if this answers your questions, but I think this particular > problem has a cleaner solution with GADTs: > > {-# LANGUAGE GADTs #-} > > data Cmd s t where > Push :: a -> Cmd s (a,s) > F1 :: (a -> b) -> Cmd (a,s) (b,s) > F2 :: (a -> b -> c) -> Cmd (a,(b,s)) (c,s) > > data Prog s t where > (:.) :: Cmd s t -> Prog t u -> Prog s u > End :: Prog s s > > infixr 5 :. > > cmd :: Cmd s t -> s -> t > cmd (Push a) s = (a, s) > cmd (F1 f) (a,s) = (f a, s) > cmd (F2 f) (a,(b,s)) = (f a b, s) > > prog :: Prog s t -> s -> t > prog (c :. p) s = prog p (cmd c s) > prog End s = s > > run :: Prog () t -> t > run p = prog p () > > Then from GHCi: > > > run (Push 3 :. Push 4 :. F2 (+) :. F1 show :. End) > ("7",()) > > Maybe you really want GADTs? :) > > -Eric > > _______________________________________________ > 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 brandon.m.simmons at gmail.com Fri Mar 14 22:23:51 2014 From: brandon.m.simmons at gmail.com (jberryman) Date: Fri, 14 Mar 2014 15:23:51 -0700 (PDT) Subject: [Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want? In-Reply-To: References: Message-ID: On Friday, March 14, 2014 5:19:40 PM UTC-4, Eric Walkingshaw wrote: > > I'm not sure if this answers your questions, but I think this particular > problem has a cleaner solution with GADTs: > > {-# LANGUAGE GADTs #-} > > data Cmd s t where > Push :: a -> Cmd s (a,s) > F1 :: (a -> b) -> Cmd (a,s) (b,s) > F2 :: (a -> b -> c) -> Cmd (a,(b,s)) (c,s) > > data Prog s t where > (:.) :: Cmd s t -> Prog t u -> Prog s u > End :: Prog s s > > infixr 5 :. > > cmd :: Cmd s t -> s -> t > cmd (Push a) s = (a, s) > cmd (F1 f) (a,s) = (f a, s) > cmd (F2 f) (a,(b,s)) = (f a b, s) > > prog :: Prog s t -> s -> t > prog (c :. p) s = prog p (cmd c s) > prog End s = s > > run :: Prog () t -> t > run p = prog p () > > Then from GHCi: > > > run (Push 3 :. Push 4 :. F2 (+) :. F1 show :. End) > ("7",()) > > Maybe you really want GADTs? :) > > -Eric > That's a great point, thanks. I'll have to remember to interrogate myself on that next time I find myself reaching for this pattern. I wonder if your version can be made to work for functions of any arity? But in most (maybe not all) cases I really don't want to be defining new types. Thanks, Brandon -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Fri Mar 14 22:24:23 2014 From: miroslav.karpis at gmail.com (Miroslav Karpis) Date: Fri, 14 Mar 2014 23:24:23 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault Message-ID: Hi, please can you help me with following? I have a call to an external dll (via ffi) which if executed from ghci works fine. If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it I get 'Segmentation fault/access violation in generated code'. main = do let param = "FilePath" let value = "C:/dev/misc/haskell/services/FM" result <- liftIO $ FM.setmodulestring param value return "done" setmodulestring :: String -> String -> IO CInt setmodulestring param value = do let cParamLength = fromIntegral $ length param ::CInt cValueLength = fromIntegral $ length value ::CInt setVarInArray = (-1)::CInt alloca $ \cParam -> do alloca $ \cValue -> do result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray return result If I try also with following, the behaviour is the same: setmodulestring2 :: String -> String -> IO CInt setmodulestring2 param value = do cParam <- newCWString param cValue <- newCWString value let cParamLength = fromIntegral $ length param ::CInt cValueLength = fromIntegral $ length value ::CInt setVarInArray = (-1)::CInt result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray free cParam free cValue return res Any comments/ideas more than appreciated. Cheers, Miro -------------- next part -------------- An HTML attachment was scrubbed... URL: From branimir.maksimovic at gmail.com Fri Mar 14 23:14:24 2014 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Sat, 15 Mar 2014 00:14:24 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: Message-ID: <53238D50.7060204@gmail.com> On 03/14/2014 11:24 PM, Miroslav Karpis wrote: > Hi, please can you help me with following? > > I have a call to an external dll (via ffi) which if executed from ghci > works fine. > If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run > it I get 'Segmentation fault/access violation in generated code'. > > > > main = do > let param = "FilePath" > let value = "C:/dev/misc/haskell/services/FM" > result <- liftIO $ FM.setmodulestring param value > return "done" > > setmodulestring :: String -> String -> IO CInt > setmodulestring param value = do > let cParamLength = fromIntegral $ length param ::CInt > cValueLength = fromIntegral $ length value ::CInt > setVarInArray = (-1)::CInt > alloca $ \cParam -> do > alloca $ \cValue -> do > result <- c_setmodulestring cParam cParamLength cValue cValueLength > setVarInArray > return result > This does not seems correct (or incomplete). > If I try also with following, the behaviour is the same: > > setmodulestring2 :: String -> String -> IO CInt > setmodulestring2 param value = do > cParam <- newCWString param > cValue <- newCWString value > let cParamLength = fromIntegral $ length param ::CInt > cValueLength = fromIntegral $ length value ::CInt > setVarInArray = (-1)::CInt > result <- c_setmodulestring cParam cParamLength cValue cValueLength > setVarInArray > free cParam > free cValue > return res > This one may be correct but without, seeing C code (where it probably segfaults) I cannot say anything further. exact ffi declaration of c_setmodulestring would be usefull, too, to compare with C function. -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Fri Mar 14 23:23:44 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sat, 15 Mar 2014 00:23:44 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: <53238D50.7060204@gmail.com> References: <53238D50.7060204@gmail.com> Message-ID: here comes the c definition: int setmodulestring(char* parameter, int parameterLength, char* value, int valueLength, int setVarInArray); In ghci the main and setmodulestring functions works fine On Sat, Mar 15, 2014 at 12:14 AM, Branimir Maksimovic < branimir.maksimovic at gmail.com> wrote: > On 03/14/2014 11:24 PM, Miroslav Karpis wrote: > > Hi, please can you help me with following? > > I have a call to an external dll (via ffi) which if executed from ghci > works fine. > If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it I > get 'Segmentation fault/access violation in generated code'. > > > > main = do > let param = "FilePath" > let value = "C:/dev/misc/haskell/services/FM" > result <- liftIO $ FM.setmodulestring param value > return "done" > > setmodulestring :: String -> String -> IO CInt > setmodulestring param value = do > let cParamLength = fromIntegral $ length param ::CInt > cValueLength = fromIntegral $ length value ::CInt > setVarInArray = (-1)::CInt > alloca $ \cParam -> do > alloca $ \cValue -> do > result <- c_setmodulestring cParam cParamLength cValue cValueLength > setVarInArray > return result > > This does not seems correct (or incomplete). > > > If I try also with following, the behaviour is the same: > > setmodulestring2 :: String -> String -> IO CInt > setmodulestring2 param value = do > cParam <- newCWString param > cValue <- newCWString value > let cParamLength = fromIntegral $ length param ::CInt > cValueLength = fromIntegral $ length value ::CInt > setVarInArray = (-1)::CInt > result <- c_setmodulestring cParam cParamLength cValue cValueLength > setVarInArray > free cParam > free cValue > return res > > This one may be correct but without, seeing C code (where it probably > segfaults) I cannot say anything further. > exact ffi declaration of c_setmodulestring would be usefull, too, > to compare with C function. > > > > _______________________________________________ > 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 branimir.maksimovic at gmail.com Fri Mar 14 23:29:06 2014 From: branimir.maksimovic at gmail.com (Branimir Maksimovic) Date: Sat, 15 Mar 2014 00:29:06 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <53238D50.7060204@gmail.com> Message-ID: <532390C2.6020109@gmail.com> You are passing wchar_t* and function expects char*. On 03/15/2014 12:23 AM, Miro Karpis wrote: > here comes the c definition: > > int setmodulestring(char* parameter, int parameterLength, char* value, > int valueLength, int setVarInArray); > > > In ghci the main and setmodulestring functions works fine > > > On Sat, Mar 15, 2014 at 12:14 AM, Branimir Maksimovic > > > wrote: > > On 03/14/2014 11:24 PM, Miroslav Karpis wrote: >> Hi, please can you help me with following? >> >> I have a call to an external dll (via ffi) which if executed from >> ghci works fine. >> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and >> run it I get 'Segmentation fault/access violation in generated >> code'. >> >> >> >> main = do >> let param = "FilePath" >> let value = "C:/dev/misc/haskell/services/FM" >> result <- liftIO $ FM.setmodulestring param value >> return "done" >> >> setmodulestring :: String -> String -> IO CInt >> setmodulestring param value = do >> let cParamLength = fromIntegral $ length param ::CInt >> cValueLength = fromIntegral $ length value ::CInt >> setVarInArray = (-1)::CInt >> alloca $ \cParam -> do >> alloca $ \cValue -> do >> result <- c_setmodulestring cParam cParamLength cValue >> cValueLength setVarInArray >> return result >> > This does not seems correct (or incomplete). > > >> If I try also with following, the behaviour is the same: >> >> setmodulestring2 :: String -> String -> IO CInt >> setmodulestring2 param value = do >> cParam <- newCWString param >> cValue <- newCWString value >> let cParamLength = fromIntegral $ length param ::CInt >> cValueLength = fromIntegral $ length value ::CInt >> setVarInArray = (-1)::CInt >> result <- c_setmodulestring cParam cParamLength cValue >> cValueLength setVarInArray >> free cParam >> free cValue >> return res >> > This one may be correct but without, seeing C code (where it probably > segfaults) I cannot say anything further. > exact ffi declaration of c_setmodulestring would be usefull, too, > to compare with C function. > > > > _______________________________________________ > 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 rvollmert-lists at gmx.net Fri Mar 14 23:36:55 2014 From: rvollmert-lists at gmx.net (Robert Vollmert) Date: Sat, 15 Mar 2014 00:36:55 +0100 Subject: [Haskell-cafe] design problem, "varying intermediate types" Message-ID: Dear cafe, I?m working on a project that reads logic puzzle descriptions from yaml files and renders them using the Diagrams framework (https://github.com/robx/puzzle-draw), and am quite unsure what?s a good way of stringing things together. It?s a bit hard to even express the problem? I?ve tried to break it down with limited success, to the following task: 1. Read YAML data like type: ?three? x: 3 y: [3, 4, 5] Type is from a fixed (long) list of strings. This type determines the format of the fields x and y (x is required, y is optional). 2. Do something type-specific to produce output based on the parsed data. Two options, one that depends on the x field only, the second can also consult the y field. My problem is how I should deal with these intermediate types that vary based on the input. My current approach below has parsing and printing functions, and then one big function that strings the matching parsers and printers together. I?ve also thought about using one big sum type, or type classes (Parseable, Printable, but doesn?t really seem to help). So far, all of it has felt a bit awkward. Any suggestions for how to attack this much appreciated. Cheers Rob {-# LANGUAGE OverloadedStrings #-} import Control.Applicative import Data.Yaml type Parsers a b = (Value -> Parser a, Value -> Parser b) parse1 :: Parsers Int Double parse1 = (parseJSON, parseJSON) parse2 :: Parsers String Char parse2 = (parseJSON, parseJSON) -- parse3 :: Parsers Int [Int] -- ... lots more of these type Printers a b = (a -> IO (), a -> b -> IO ()) print1 :: Printers Int Double print1 = (print . show, \x y -> print (show y ++ "..." ++ show x)) print2 :: Printers String Char print2 = (const $ print "hello", \x y -> print (show y)) type Composed = (Value -> Parser (IO ()), Value -> Value -> Parser (IO ())) compose :: Parsers a b -> Printers a b -> Composed compose (pp, ps) (rp, rs) = (\v -> rp <$> pp v, \v w -> rs <$> pp v <*> ps w) composeType :: String -> Composed composeType t = case t of "one" -> compose parse1 print1 "two" -> compose parse2 print2 _ -> (f, const f) where f = fail $ "unknown type: " ++ t parseXY :: (String -> Value -> Value -> Parser a) -> Value -> Parser a parseXY f (Object v) = do t <- v .: "type" x <- v .: "x" y <- v .: "y" f t x y parseX :: (String -> Value -> Parser a) -> Value -> Parser a parseX f (Object v) = do t <- v .: "type" x <- v .: "x" f t x printA :: Value -> Parser (IO ()) printA = parseX (fst . composeType) printB :: Value -> Parser (IO ()) printB = parseXY (snd . composeType) main = do flagB <- return False -- command line flag let p = parseEither $ if flagB then printB else printA mv <- decodeFile "input.yaml" v <- maybe (fail "failed to parse yaml") return mv case p v of Left e -> fail $ "failed to parse data: " ++ e Right x -> x From walkiner at eecs.oregonstate.edu Sat Mar 15 00:29:00 2014 From: walkiner at eecs.oregonstate.edu (Eric Walkingshaw) Date: Sat, 15 Mar 2014 01:29:00 +0100 Subject: [Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want? In-Reply-To: References: Message-ID: > > That's a great point, thanks. I'll have to remember to interrogate >> myself on that next time I find myself reaching for this pattern. I wonder >> if your version can be made to work for functions of any arity? >> > Since functions get their arguments from the stack in reverse order, this implementation actually already supports functions of any arity if you just follow it with an appropriate number of `F2 ($)` commands. First, here's a nicer eval function: eval :: Prog () (a,()) eval p = fst (prog p ()) And here's how to apply the 3-ary function `zipWith` and the 4-ary function `zipWith3`: > eval (Push [1..3] :. Push [4..6] :. Push (,) :. F2 zipWith :. F2 ($) :. End) [(4,1),(5,2),(6,3)] > eval (Push [1..3] :. Push [4..6] :. Push [7..9] :. Push (,,) :. F2 zipWith3 :. F2 ($) :. F2 ($) :. End) [(7,4,1),(8,5,2),(9,6,3)] -Eric -------------- next part -------------- An HTML attachment was scrubbed... URL: From haskell at nand.wakku.to Sat Mar 15 00:44:26 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Sat, 15 Mar 2014 01:44:26 +0100 Subject: [Haskell-cafe] I seem to constantly abuse TypeFamilies; what do i really want? In-Reply-To: References: Message-ID: <20140315014426.GA19681@nanodesu.talocan.mine.nu> On Fri, 14 Mar 2014 22:19:40 +0100, Eric Walkingshaw wrote: > I'm not sure if this answers your questions, but I think this particular > problem has a cleaner solution with GADTs: > > {-# LANGUAGE GADTs #-} > > data Cmd s t where > Push :: a -> Cmd s (a,s) > F1 :: (a -> b) -> Cmd (a,s) (b,s) > F2 :: (a -> b -> c) -> Cmd (a,(b,s)) (c,s) > > data Prog s t where > (:.) :: Cmd s t -> Prog t u -> Prog s u > End :: Prog s s > > infixr 5 :. > > cmd :: Cmd s t -> s -> t > cmd (Push a) s = (a, s) > cmd (F1 f) (a,s) = (f a, s) > cmd (F2 f) (a,(b,s)) = (f a b, s) > > prog :: Prog s t -> s -> t > prog (c :. p) s = prog p (cmd c s) > prog End s = s > > run :: Prog () t -> t > run p = prog p () > > Then from GHCi: > > > run (Push 3 :. Push 4 :. F2 (+) :. F1 show :. End) > ("7",()) > > Maybe you really want GADTs? :) > > -Eric Of course, there's also: > start :: (() -> r) -> r > start f = f () > > end :: (a, s) -> a > end = fst > > push :: s -> a -> ((a, s) -> r) -> r > push s a f = f (a, s) > > op2 :: (a -> b -> c) -> (a, (b, s)) -> ((c, s) -> r) -> r > op2 o (a, (b, s)) f = f (a `o` b, s) > > add, mul :: Num a => (a, (a, s)) -> ((a, s) -> r) -> r > add = op2 (+) > mul = op2 (*) > > example :: Integer > example = -- 35 > start > push 2 > push 3 > add > push 7 > mul > end From allbery.b at gmail.com Sat Mar 15 02:30:50 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 14 Mar 2014 22:30:50 -0400 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <53238D50.7060204@gmail.com> Message-ID: On Fri, Mar 14, 2014 at 7:23 PM, Miro Karpis wrote: > here comes the c definition: > > int setmodulestring(char* parameter, int parameterLength, char* value, int valueLength, int setVarInArray); > > If you had included this before (or perhaps noted that I specified Win32 API, not general C function) then I wouldn't have raised the CWString issue. This declaration is not Win32 API and the original CString was correct for it. If you're still having issues... does this by any chance have any association with threads? ghci uses the threaded runtime *and* handles threads slightly differently from compiled code with -threaded (if it core dumps in ghci with -no-ghci-sandbox then this may be the issue)? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sat Mar 15 02:32:25 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Fri, 14 Mar 2014 22:32:25 -0400 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: <532390C2.6020109@gmail.com> References: <53238D50.7060204@gmail.com> <532390C2.6020109@gmail.com> Message-ID: On Fri, Mar 14, 2014 at 7:29 PM, Branimir Maksimovic < branimir.maksimovic at gmail.com> wrote: > You are passing wchar_t* and function expects char*. > FWIW they asked this before (possibly on a different list) and, absent the C information, I pointed out that Win32 API functions use CWString. This was apparently taken to mean that CWString was the only option.... Some awareness of one's platform conventions tends to be helpful when doing FFI. It seems to be absent here. :/ -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From lemming at henning-thielemann.de Sat Mar 15 13:35:51 2014 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Sat, 15 Mar 2014 14:35:51 +0100 Subject: [Haskell-cafe] HaL-9 - regional Haskell meeting in Halle/Saale, Germany, 2014-06-20 - Save the date Message-ID: <53245737.5000402@henning-thielemann.de> Save the date for our local Haskell meeting in Halle/Saale, Germany, presenting tutorials, talks, demonstrations ... everything you like. Workshop language is German (mainly), and English (by request). Switching to German: ------------------------------------------------- Was: Haskell-Treffen HaL-9 Wann: Freitag, 2014-06-20 Wo: Institut f?r Informatik an der Martin-Luther-Universit?t in Halle an der Saale Der offizielle Aufruf zum Einreichen von Beitr?gen folgt demn?chst. Mit besten Gr??en Henning Thielemann From silvio.frischi at gmail.com Sat Mar 15 14:21:36 2014 From: silvio.frischi at gmail.com (Silvio Frischknecht) Date: Sat, 15 Mar 2014 15:21:36 +0100 Subject: [Haskell-cafe] overlapping/Incoherent closed type families Message-ID: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> Hi I have been playing around a bit with closed type families. However, I somehow always bump my head at the fact that things usually doesn't work for Num without specifying the type. Here is an example. {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE OverlappingInstances #-} {-# LANGUAGE IncoherentInstances #-} module Main where import Data.Typeable type family UnMaybed a where UnMaybed (Maybe a) = a UnMaybed a = a class UnMaybe x where unMaybe :: x -> UnMaybed x instance UnMaybe (Maybe a) where unMaybe (Just a) = a instance (UnMaybed a ~ a) => UnMaybe a where unMaybe a = a main = do print $ unMaybe 'c' print $ unMaybe (1::Int) print $ unMaybe (Just 1) print $ unMaybe 1 -- this line does not compile everything except the last line will compile. ../Example.hs:23:17: Occurs check: cannot construct the infinite type: s0 ~ UnMaybed s0 The type variable ?s0? is ambiguous In the second argument of ?($)?, namely ?unMaybe 1? In a stmt of a 'do' block: print $ unMaybe 1 Now I know this is because numbers are polymorphic and (Maybe a) could be an instance of Num. I think for normal overlapping typeclasses this dilemma can be solved by using the IncoherentInstances PRAGMA. Anyway, I wanted to ask if there is a way to make this work in type families? I also thought about specifying Num explicitly in UnMaybed type family UnMaybed a where unMaybed (Num a => a) = a UnMaybed (Maybe a) = a UnMaybed a = a This compiles but i think the first case will never be matched this is probably a bug. Silvio From carter.schonwald at gmail.com Sat Mar 15 15:14:32 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sat, 15 Mar 2014 11:14:32 -0400 Subject: [Haskell-cafe] overlapping/Incoherent closed type families In-Reply-To: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> References: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> Message-ID: yeah... I dont think close type families can match on the first one, thought its interesting to ask if they should be able to.... On Sat, Mar 15, 2014 at 10:21 AM, Silvio Frischknecht < silvio.frischi at gmail.com> wrote: > Hi > > I have been playing around a bit with closed type families. However, I > somehow > always bump my head at the fact that things usually doesn't work for Num > without specifying the type. > > Here is an example. > > {-# LANGUAGE FlexibleInstances #-} > {-# LANGUAGE FlexibleContexts #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE UndecidableInstances #-} > {-# LANGUAGE OverlappingInstances #-} > {-# LANGUAGE IncoherentInstances #-} > module Main where > > import Data.Typeable > > type family UnMaybed a where > UnMaybed (Maybe a) = a > UnMaybed a = a > > class UnMaybe x where > unMaybe :: x -> UnMaybed x > > instance UnMaybe (Maybe a) where > unMaybe (Just a) = a > > instance (UnMaybed a ~ a) => UnMaybe a where > unMaybe a = a > > main = do > print $ unMaybe 'c' > print $ unMaybe (1::Int) > print $ unMaybe (Just 1) > print $ unMaybe 1 -- this line does not compile > > everything except the last line will compile. > > ../Example.hs:23:17: > Occurs check: cannot construct the infinite type: s0 ~ UnMaybed s0 > The type variable ?s0? is ambiguous > In the second argument of ?($)?, namely ?unMaybe 1? > In a stmt of a 'do' block: print $ unMaybe 1 > > Now I know this is because numbers are polymorphic and (Maybe a) could be > an > instance of Num. I think for normal overlapping typeclasses this dilemma > can > be solved by using the IncoherentInstances PRAGMA. Anyway, I wanted to ask > if > there is a way to make this work in type families? > > I also thought about specifying Num explicitly in UnMaybed > > type family UnMaybed a where > unMaybed (Num a => a) = a > UnMaybed (Maybe a) = a > UnMaybed a = a > > This compiles but i think the first case will never be matched this is > probably > a bug. > > Silvio > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From eir at cis.upenn.edu Sat Mar 15 15:38:19 2014 From: eir at cis.upenn.edu (Richard Eisenberg) Date: Sat, 15 Mar 2014 11:38:19 -0400 Subject: [Haskell-cafe] overlapping/Incoherent closed type families In-Reply-To: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> References: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> Message-ID: Hi Silvio, Yes, you've hit upon a limitation of closed type families, but the limitation is there for good reason. IncoherentInstances threatens coherence of type class instances, meaning that a constraint `UnMaybe <>` might be fulfilled differently in different places, even for the same <>. But, type class instance selection is purely a runtime-behavior effect. Choosing a different instance cannot affect the types in your program. Type families, on the other hand, directly affect the types. Allowing incoherence like the way IncoherentInstances works could be used to implement unsafeCoerce. So, I'm afraid you're out of luck. I've hit this exact same problem in my own work, and there's not much of a way around it without a type signature. (One possibility is to use RebindableSyntax essentially to disable number overloading, but that's a bit of a big hammer.) The fact that your last example (with UnMaybed (Num a => a)) even compiles is very much a bug that I will file shortly. I hope this explanation is helpful! Richard On Mar 15, 2014, at 10:21 AM, Silvio Frischknecht wrote: > Hi > > I have been playing around a bit with closed type families. However, I somehow > always bump my head at the fact that things usually doesn't work for Num > without specifying the type. > > Here is an example. > > {-# LANGUAGE FlexibleInstances #-} > {-# LANGUAGE FlexibleContexts #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE UndecidableInstances #-} > {-# LANGUAGE OverlappingInstances #-} > {-# LANGUAGE IncoherentInstances #-} > module Main where > > import Data.Typeable > > type family UnMaybed a where > UnMaybed (Maybe a) = a > UnMaybed a = a > > class UnMaybe x where > unMaybe :: x -> UnMaybed x > > instance UnMaybe (Maybe a) where > unMaybe (Just a) = a > > instance (UnMaybed a ~ a) => UnMaybe a where > unMaybe a = a > > main = do > print $ unMaybe 'c' > print $ unMaybe (1::Int) > print $ unMaybe (Just 1) > print $ unMaybe 1 -- this line does not compile > > everything except the last line will compile. > > ../Example.hs:23:17: > Occurs check: cannot construct the infinite type: s0 ~ UnMaybed s0 > The type variable ?s0? is ambiguous > In the second argument of ?($)?, namely ?unMaybe 1? > In a stmt of a 'do' block: print $ unMaybe 1 > > Now I know this is because numbers are polymorphic and (Maybe a) could be an > instance of Num. I think for normal overlapping typeclasses this dilemma can > be solved by using the IncoherentInstances PRAGMA. Anyway, I wanted to ask if > there is a way to make this work in type families? > > I also thought about specifying Num explicitly in UnMaybed > > type family UnMaybed a where > unMaybed (Num a => a) = a > UnMaybed (Maybe a) = a > UnMaybed a = a > > This compiles but i think the first case will never be matched this is probably > a bug. > > Silvio > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From brandon.m.simmons at gmail.com Sat Mar 15 15:52:44 2014 From: brandon.m.simmons at gmail.com (jberryman) Date: Sat, 15 Mar 2014 08:52:44 -0700 (PDT) Subject: [Haskell-cafe] overlapping/Incoherent closed type families In-Reply-To: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> References: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> Message-ID: On Saturday, March 15, 2014 10:21:36 AM UTC-4, Silvio Frischknecht wrote: > > Hi > > I have been playing around a bit with closed type families. However, I > somehow > always bump my head at the fact that things usually doesn't work for Num > without specifying the type. > > Here is an example. > > {-# LANGUAGE FlexibleInstances #-} > {-# LANGUAGE FlexibleContexts #-} > {-# LANGUAGE TypeFamilies #-} > {-# LANGUAGE DataKinds #-} > {-# LANGUAGE UndecidableInstances #-} > {-# LANGUAGE OverlappingInstances #-} > {-# LANGUAGE IncoherentInstances #-} > module Main where > > import Data.Typeable > > type family UnMaybed a where > UnMaybed (Maybe a) = a > UnMaybed a = a > > class UnMaybe x where > unMaybe :: x -> UnMaybed x > > instance UnMaybe (Maybe a) where > unMaybe (Just a) = a > > instance (UnMaybed a ~ a) => UnMaybe a where > unMaybe a = a > > main = do > print $ unMaybe 'c' > print $ unMaybe (1::Int) > print $ unMaybe (Just 1) > print $ unMaybe 1 -- this line does not compile > > everything except the last line will compile. > > ../Example.hs:23:17: > Occurs check: cannot construct the infinite type: s0 ~ UnMaybed s0 > The type variable ?s0? is ambiguous > In the second argument of ?($)?, namely ?unMaybe 1? > In a stmt of a 'do' block: print $ unMaybe 1 > > Now I know this is because numbers are polymorphic and (Maybe a) could be > an > instance of Num. I think for normal overlapping typeclasses this dilemma > can > be solved by using the IncoherentInstances PRAGMA. Anyway, I wanted to ask > if > there is a way to make this work in type families? > > I also thought about specifying Num explicitly in UnMaybed > > type family UnMaybed a where > unMaybed (Num a => a) = a > UnMaybed (Maybe a) = a > UnMaybed a = a > > This compiles but i think the first case will never be matched this is > probably > a bug. > > Silvio > > _______________________________________________ > Haskell-Cafe mailing list > Haskel... at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > I'm glad Richard Eisenberg responded here; I was going to point you to https://ghc.haskell.org/trac/ghc/wiki/NewAxioms with the caveat that I don't totally understand the details there. A couple things about your example: you actually don't need IncoherentInstances here; OverlappingInstances is sufficient, since the instance head `UnMaybe (Maybe a)` is more precise than `UnMaybe a`. Personally I'm *much* more comfortable with just OverlappingInstances than IncoherentInstances. The other thing to consider is that the only reason why e.g. `print 1` even compiles is because of defaulting rules, which are something of a hack. Maybe that makes you feel better about living with the limitation in your current code. Brandon -------------- next part -------------- An HTML attachment was scrubbed... URL: From silvio.frischi at gmail.com Sat Mar 15 16:34:28 2014 From: silvio.frischi at gmail.com (Silvio Frischknecht) Date: Sat, 15 Mar 2014 17:34:28 +0100 Subject: [Haskell-cafe] overlapping/Incoherent closed type families In-Reply-To: References: <1643016.OVKESzK6PK@moviepc-fl377aa-uuz-m9451ch> Message-ID: <1509967.uZL0UpWUb1@moviepc-fl377aa-uuz-m9451ch> Thanks for you answer. Silvio From mark.lentczner at gmail.com Sat Mar 15 17:53:28 2014 From: mark.lentczner at gmail.com (Mark Lentczner) Date: Sat, 15 Mar 2014 10:53:28 -0700 Subject: [Haskell-cafe] Save the date: BayHac '14 Message-ID: The Silicon Valley / San Francisco Bay Area Haskell Hackaton's 4th year! Save the date for a weekend of Haskell hacking: *BayHac '14* *May 16th ~ 18th,* *Hacker Dojo* *Mountain View, California* Details and registration will follow in few weeks. Wiki page for event: BayHac2014 - HaskellWiki ? Jonathan Fischoff & Mark Lentczner -------------- next part -------------- An HTML attachment was scrubbed... URL: From gbwey9 at gmail.com Sun Mar 16 00:05:48 2014 From: gbwey9 at gmail.com (grant weyburne) Date: Sat, 15 Mar 2014 20:05:48 -0400 Subject: [Haskell-cafe] [ANN] persistent-odbc Message-ID: Hi, This package contains Persistent-compatible database backends using ODBC. It currently supports the following databases: MSSQL, MySql, Oracle, Sqlite, DB2 and Postgres. https://github.com/gbwey/persistent-odbc http://hackage.haskell.org/package/persistent-odbc-0.1.2.0/candidate Let me know if you have any problems or suggestions to improve it. Thanks, Grant -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Sun Mar 16 06:31:41 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sun, 16 Mar 2014 07:31:41 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <53238D50.7060204@gmail.com> <532390C2.6020109@gmail.com> Message-ID: still no luck ;-( Everything works well under ghci but if I compile it with ghc I get seg. fault ghc version 7.6.3 I found out that when I load my ghci without any .o and .hi files ghci function calls works fine. If I then compile my code with ghc and restart my ghci (.o and .hi files now exists) the ghci crashes. I have tried compiling with: ghc -O --make Service.hs -L. -lmodel ghc --make Service.hs -L. -lmodel ghc -o service Service.hs -L. -lmodel I have tried to call ffi function with: setmodulestring1 param value = do let param = cParamLength = fromIntegral $ length param ::CInt cValueLength = fromIntegral $ length value ::CInt setVarInArray = (-1)::CInt B.useAsCString (B.pack "FilePath") $ \cParam -> do B.useAsCString (B.pack "C:/dev/misc/haskell/services/FM") $ \cValue -> do result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray return result or with this: setmodulestring :: String -> String -> IO CInt setmodulestring param value = do let param = "FilePath" let value = "C:/dev/misc/haskell/services/FM" cParam <- newCString param cValue <- newCString value let cParamLength = fromIntegral $ length param ::CInt cValueLength = fromIntegral $ length value ::CInt setVarInArray = (-1)::CInt result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray free cParam free cValue return result my main is: main = do let param = "FilePath" let value = "C:/dev/misc/haskell/services/FM" result <- liftIO $ FM.setmodulestring param value return "done" and still no luck - works in ghci and crashes as exe interfacing the same library from a c++ code: extern "C" int __stdcall setmodulestring(char* param,unsigned int length, char* valuein,unsigned int valuelength,int index); interfacing it from Haskell: foreign import ccall "setmodulestring" c_setmodulestring :: CString -> CInt -> CString -> CInt -> CInt -> IO CInt please any ideas? On Sat, Mar 15, 2014 at 4:48 PM, Miro Karpis wrote: > thank you very much so far and sorry for my not 100% understanding ;-). > The dll is an external software - I have no control over it. > > This is how I interface it from c++ program: > > extern "C" int __stdcall setmodulestring(char* param,unsigned int length, > char* valuein,unsigned int valuelength,int index); > > > And this is how I'm trying to interface it from Haskell (with the seg-fault): > > foreign import ccall "setmodulestring" c_setmodulestring :: Ptr Char -> CInt -> Ptr Char -> CInt -> CInt -> IO CInt > > m. > > > On Sat, Mar 15, 2014 at 3:32 AM, Brandon Allbery wrote: > >> On Fri, Mar 14, 2014 at 7:29 PM, Branimir Maksimovic < >> branimir.maksimovic at gmail.com> wrote: >> >>> You are passing wchar_t* and function expects char*. >>> >> >> FWIW they asked this before (possibly on a different list) and, absent >> the C information, I pointed out that Win32 API functions use CWString. >> This was apparently taken to mean that CWString was the only option.... >> >> Some awareness of one's platform conventions tends to be helpful when >> doing FFI. It seems to be absent here. :/ >> >> -- >> brandon s allbery kf8nh sine nomine >> associates >> allbery.b at gmail.com >> ballbery at sinenomine.net >> unix, openafs, kerberos, infrastructure, xmonad >> http://sinenomine.net >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From vagif.verdi at gmail.com Sun Mar 16 06:45:55 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Sat, 15 Mar 2014 23:45:55 -0700 (PDT) Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: Message-ID: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> I do not think i can help you, but my FFi to functions with similar signature looks like this: C definition: PDFLIB_API int PDFLIB_CALL PDF_begin_document(PDF *p, const char *filename, int len, const char *optlist); haskell FFI: c_beginDocument :: Pdf -> String -> String -> IO Int c_beginDocument pdf a2 a3 = withCString a2 $ \a2' -> withCString a3 $ c_beginDocument'_ pdf a2' 0 foreign import ccall safe "Pdflib.chs.h PDF_begin_document" c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int The difference as you see, i'm using withCString to convert from ahskell to C and i'm passing 0 as the string size. On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote: > > Hi, please can you help me with following? > > I have a call to an external dll (via ffi) which if executed from ghci > works fine. > If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it I > get 'Segmentation fault/access violation in generated code'. > > > > main = do > let param = "FilePath" > let value = "C:/dev/misc/haskell/services/FM" > result <- liftIO $ FM.setmodulestring param value > return "done" > > setmodulestring :: String -> String -> IO CInt > setmodulestring param value = do > let cParamLength = fromIntegral $ length param ::CInt > cValueLength = fromIntegral $ length value ::CInt > setVarInArray = (-1)::CInt > alloca $ \cParam -> do > alloca $ \cValue -> do > result <- c_setmodulestring cParam cParamLength cValue cValueLength > setVarInArray > return result > > If I try also with following, the behaviour is the same: > > setmodulestring2 :: String -> String -> IO CInt > setmodulestring2 param value = do > cParam <- newCWString param > cValue <- newCWString value > let cParamLength = fromIntegral $ length param ::CInt > cValueLength = fromIntegral $ length value ::CInt > setVarInArray = (-1)::CInt > result <- c_setmodulestring cParam cParamLength cValue cValueLength > setVarInArray > free cParam > free cValue > return res > > > Any comments/ideas more than appreciated. > > Cheers, > Miro > > > > > > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Sun Mar 16 08:40:48 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sun, 16 Mar 2014 09:40:48 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> Message-ID: thank you very much - I have tried also that but got the the same behaviour (seg fault) cheers, m. On Sun, Mar 16, 2014 at 7:45 AM, Vagif Verdi wrote: > I do not think i can help you, but my FFi to functions with similar > signature looks like this: > > C definition: > > PDFLIB_API int PDFLIB_CALL > PDF_begin_document(PDF *p, const char *filename, int len, const char > *optlist); > > haskell FFI: > > c_beginDocument :: Pdf -> String -> String -> IO Int > c_beginDocument pdf a2 a3 = > withCString a2 $ \a2' -> > withCString a3 $ c_beginDocument'_ pdf a2' 0 > > foreign import ccall safe "Pdflib.chs.h PDF_begin_document" > c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int > > The difference as you see, i'm using withCString to convert from ahskell > to C and i'm passing 0 as the string size. > > > > On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote: >> >> Hi, please can you help me with following? >> >> I have a call to an external dll (via ffi) which if executed from ghci >> works fine. >> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it I >> get 'Segmentation fault/access violation in generated code'. >> >> >> >> main = do >> let param = "FilePath" >> let value = "C:/dev/misc/haskell/services/FM" >> result <- liftIO $ FM.setmodulestring param value >> return "done" >> >> setmodulestring :: String -> String -> IO CInt >> setmodulestring param value = do >> let cParamLength = fromIntegral $ length param ::CInt >> cValueLength = fromIntegral $ length value ::CInt >> setVarInArray = (-1)::CInt >> alloca $ \cParam -> do >> alloca $ \cValue -> do >> result <- c_setmodulestring cParam cParamLength cValue cValueLength >> setVarInArray >> return result >> >> If I try also with following, the behaviour is the same: >> >> setmodulestring2 :: String -> String -> IO CInt >> setmodulestring2 param value = do >> cParam <- newCWString param >> cValue <- newCWString value >> let cParamLength = fromIntegral $ length param ::CInt >> cValueLength = fromIntegral $ length value ::CInt >> setVarInArray = (-1)::CInt >> result <- c_setmodulestring cParam cParamLength cValue cValueLength >> setVarInArray >> free cParam >> free cValue >> return res >> >> >> Any comments/ideas more than appreciated. >> >> Cheers, >> Miro >> >> >> >> >> >> >> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From martin.drautzburg at web.de Sun Mar 16 13:23:37 2014 From: martin.drautzburg at web.de (martin) Date: Sun, 16 Mar 2014 14:23:37 +0100 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) Message-ID: <5325A5D9.8070408@web.de> FPR is usually described as a way to model interactions with the real world. I believe the same ideas should be applicable to simulations. Instead of "real" events I would use fake events. This however only makes sense when the Time associated with the Events (and Behaviors) is not wallclock time, but some kind of virtual time. I looked briefly into Sodium and found no way to use "my own time". Steven Blackheath even said during a presentation, that Time in Sodium is just another Behavior. I am not sure if I understood this correctly, but it gives me the feeling, that the only Time available in Sodium is wallclock time, which would make it unsuitable for simulations. Could someone give me some insights whether or not FRP is suitable for simulations? Does my reasoning about Time make any sense? Do different libraries treat Time in different ways, such that some are suitable for simulations, while others are not? Martin From carter.schonwald at gmail.com Sun Mar 16 13:37:21 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 16 Mar 2014 09:37:21 -0400 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: <5325A5D9.8070408@web.de> References: <5325A5D9.8070408@web.de> Message-ID: Look up hydra and related tools. Simulation modeling tools are a bit different. There's also fewer public examplds, though I hope to change that soon. On Sunday, March 16, 2014, martin wrote: > FPR is usually described as a way to model interactions with the real > world. I believe the same ideas should be > applicable to simulations. Instead of "real" events I would use fake > events. This however only makes sense when the Time > associated with the Events (and Behaviors) is not wallclock time, but some > kind of virtual time. > > I looked briefly into Sodium and found no way to use "my own time". Steven > Blackheath even said during a presentation, > that Time in Sodium is just another Behavior. I am not sure if I > understood this correctly, but it gives me the feeling, > that the only Time available in Sodium is wallclock time, which would make > it unsuitable for simulations. > > Could someone give me some insights whether or not FRP is suitable for > simulations? > > Does my reasoning about Time make any sense? Do different libraries treat > Time in different ways, such that some are > suitable for simulations, while others are not? > > Martin > > _______________________________________________ > 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 vagif.verdi at gmail.com Sun Mar 16 16:09:59 2014 From: vagif.verdi at gmail.com (Vagif Verdi) Date: Sun, 16 Mar 2014 09:09:59 -0700 (PDT) Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> Message-ID: <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Notice that i have "safe" in my foreign import ccall. This makes it safe to run in threaded mode. Did you try that? Are you on windows? On Sunday, March 16, 2014 1:40:48 AM UTC-7, Miro Karpis wrote: > > thank you very much - I have tried also that but got the the same > behaviour (seg fault) > > cheers, > m. > > > On Sun, Mar 16, 2014 at 7:45 AM, Vagif Verdi > > wrote: > >> I do not think i can help you, but my FFi to functions with similar >> signature looks like this: >> >> C definition: >> >> PDFLIB_API int PDFLIB_CALL >> PDF_begin_document(PDF *p, const char *filename, int len, const char >> *optlist); >> >> haskell FFI: >> >> c_beginDocument :: Pdf -> String -> String -> IO Int >> c_beginDocument pdf a2 a3 = >> withCString a2 $ \a2' -> >> withCString a3 $ c_beginDocument'_ pdf a2' 0 >> >> foreign import ccall safe "Pdflib.chs.h PDF_begin_document" >> c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int >> >> The difference as you see, i'm using withCString to convert from ahskell >> to C and i'm passing 0 as the string size. >> >> >> >> On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote: >>> >>> Hi, please can you help me with following? >>> >>> I have a call to an external dll (via ffi) which if executed from ghci >>> works fine. >>> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it >>> I get 'Segmentation fault/access violation in generated code'. >>> >>> >>> >>> main = do >>> let param = "FilePath" >>> let value = "C:/dev/misc/haskell/services/FM" >>> result <- liftIO $ FM.setmodulestring param value >>> return "done" >>> >>> setmodulestring :: String -> String -> IO CInt >>> setmodulestring param value = do >>> let cParamLength = fromIntegral $ length param ::CInt >>> cValueLength = fromIntegral $ length value ::CInt >>> setVarInArray = (-1)::CInt >>> alloca $ \cParam -> do >>> alloca $ \cValue -> do >>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>> setVarInArray >>> return result >>> >>> If I try also with following, the behaviour is the same: >>> >>> setmodulestring2 :: String -> String -> IO CInt >>> setmodulestring2 param value = do >>> cParam <- newCWString param >>> cValue <- newCWString value >>> let cParamLength = fromIntegral $ length param ::CInt >>> cValueLength = fromIntegral $ length value ::CInt >>> setVarInArray = (-1)::CInt >>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>> setVarInArray >>> free cParam >>> free cValue >>> return res >>> >>> >>> Any comments/ideas more than appreciated. >>> >>> Cheers, >>> Miro >>> >>> >>> >>> >>> >>> >>> >>> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From edwards.benj at gmail.com Sun Mar 16 17:02:42 2014 From: edwards.benj at gmail.com (Benjamin Edwards) Date: Sun, 16 Mar 2014 17:02:42 +0000 Subject: [Haskell-cafe] Bound library + recovering de Bruijn indices Message-ID: Hi Cafe I am currently experimenting with the excellent bound library. I want to implement the simply typed lambda calc from TAPL (no type inference yet). When moving under a binder I want to extend my context and then look up bound terms by their indices using list indexing. I would have thought I could use something like foldMapScope to recover the bound variables, then write some function to calculate the depth of the "listy" type value returned and thus recover the index. However! The type returned is non-regular and I cannot for the life of me figure out anything that doesn't involve GHC complaining about infinite types. Any pointers on how this can be accomplished? For the record, this is what I have that works at the moment. http://lpaste.net/101279 -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Sun Mar 16 21:21:25 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sun, 16 Mar 2014 22:21:25 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Message-ID: thanks. Have tried with safe - still seg-fault. On Sun, Mar 16, 2014 at 5:09 PM, Vagif Verdi wrote: > Notice that i have "safe" in my foreign import ccall. This makes it safe > to run in threaded mode. Did you try that? > > Are you on windows? > > > On Sunday, March 16, 2014 1:40:48 AM UTC-7, Miro Karpis wrote: > >> thank you very much - I have tried also that but got the the same >> behaviour (seg fault) >> >> cheers, >> m. >> >> >> On Sun, Mar 16, 2014 at 7:45 AM, Vagif Verdi wrote: >> >>> I do not think i can help you, but my FFi to functions with similar >>> signature looks like this: >>> >>> C definition: >>> >>> PDFLIB_API int PDFLIB_CALL >>> PDF_begin_document(PDF *p, const char *filename, int len, const char >>> *optlist); >>> >>> haskell FFI: >>> >>> c_beginDocument :: Pdf -> String -> String -> IO Int >>> c_beginDocument pdf a2 a3 = >>> withCString a2 $ \a2' -> >>> withCString a3 $ c_beginDocument'_ pdf a2' 0 >>> >>> foreign import ccall safe "Pdflib.chs.h PDF_begin_document" >>> c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int >>> >>> The difference as you see, i'm using withCString to convert from ahskell >>> to C and i'm passing 0 as the string size. >>> >>> >>> >>> On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote: >>>> >>>> Hi, please can you help me with following? >>>> >>>> I have a call to an external dll (via ffi) which if executed from ghci >>>> works fine. >>>> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run it >>>> I get 'Segmentation fault/access violation in generated code'. >>>> >>>> >>>> >>>> main = do >>>> let param = "FilePath" >>>> let value = "C:/dev/misc/haskell/services/FM" >>>> result <- liftIO $ FM.setmodulestring param value >>>> return "done" >>>> >>>> setmodulestring :: String -> String -> IO CInt >>>> setmodulestring param value = do >>>> let cParamLength = fromIntegral $ length param ::CInt >>>> cValueLength = fromIntegral $ length value ::CInt >>>> setVarInArray = (-1)::CInt >>>> alloca $ \cParam -> do >>>> alloca $ \cValue -> do >>>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>>> setVarInArray >>>> return result >>>> >>>> If I try also with following, the behaviour is the same: >>>> >>>> setmodulestring2 :: String -> String -> IO CInt >>>> setmodulestring2 param value = do >>>> cParam <- newCWString param >>>> cValue <- newCWString value >>>> let cParamLength = fromIntegral $ length param ::CInt >>>> cValueLength = fromIntegral $ length value ::CInt >>>> setVarInArray = (-1)::CInt >>>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>>> setVarInArray >>>> free cParam >>>> free cValue >>>> return res >>>> >>>> >>>> Any comments/ideas more than appreciated. >>>> >>>> Cheers, >>>> Miro >>>> >>>> >>>> >>>> >>>> >>>> >>>> >>>> >> -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Sun Mar 16 22:20:27 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Sun, 16 Mar 2014 18:20:27 -0400 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Message-ID: what version of ghc and cabal? have you tried cabalizing the code and seeing what flags its passing? is it possible you're passing the wrong flags? On Sun, Mar 16, 2014 at 5:21 PM, Miro Karpis wrote: > thanks. Have tried with safe - still seg-fault. > > > On Sun, Mar 16, 2014 at 5:09 PM, Vagif Verdi wrote: > >> Notice that i have "safe" in my foreign import ccall. This makes it safe >> to run in threaded mode. Did you try that? >> >> Are you on windows? >> >> >> On Sunday, March 16, 2014 1:40:48 AM UTC-7, Miro Karpis wrote: >> >>> thank you very much - I have tried also that but got the the same >>> behaviour (seg fault) >>> >>> cheers, >>> m. >>> >>> >>> On Sun, Mar 16, 2014 at 7:45 AM, Vagif Verdi wrote: >>> >>>> I do not think i can help you, but my FFi to functions with similar >>>> signature looks like this: >>>> >>>> C definition: >>>> >>>> PDFLIB_API int PDFLIB_CALL >>>> PDF_begin_document(PDF *p, const char *filename, int len, const char >>>> *optlist); >>>> >>>> haskell FFI: >>>> >>>> c_beginDocument :: Pdf -> String -> String -> IO Int >>>> c_beginDocument pdf a2 a3 = >>>> withCString a2 $ \a2' -> >>>> withCString a3 $ c_beginDocument'_ pdf a2' 0 >>>> >>>> foreign import ccall safe "Pdflib.chs.h PDF_begin_document" >>>> c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int >>>> >>>> The difference as you see, i'm using withCString to convert from >>>> ahskell to C and i'm passing 0 as the string size. >>>> >>>> >>>> >>>> On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote: >>>>> >>>>> Hi, please can you help me with following? >>>>> >>>>> I have a call to an external dll (via ffi) which if executed from ghci >>>>> works fine. >>>>> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run >>>>> it I get 'Segmentation fault/access violation in generated code'. >>>>> >>>>> >>>>> >>>>> main = do >>>>> let param = "FilePath" >>>>> let value = "C:/dev/misc/haskell/services/FM" >>>>> result <- liftIO $ FM.setmodulestring param value >>>>> return "done" >>>>> >>>>> setmodulestring :: String -> String -> IO CInt >>>>> setmodulestring param value = do >>>>> let cParamLength = fromIntegral $ length param ::CInt >>>>> cValueLength = fromIntegral $ length value ::CInt >>>>> setVarInArray = (-1)::CInt >>>>> alloca $ \cParam -> do >>>>> alloca $ \cValue -> do >>>>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>>>> setVarInArray >>>>> return result >>>>> >>>>> If I try also with following, the behaviour is the same: >>>>> >>>>> setmodulestring2 :: String -> String -> IO CInt >>>>> setmodulestring2 param value = do >>>>> cParam <- newCWString param >>>>> cValue <- newCWString value >>>>> let cParamLength = fromIntegral $ length param ::CInt >>>>> cValueLength = fromIntegral $ length value ::CInt >>>>> setVarInArray = (-1)::CInt >>>>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>>>> setVarInArray >>>>> free cParam >>>>> free cValue >>>>> return res >>>>> >>>>> >>>>> Any comments/ideas more than appreciated. >>>>> >>>>> Cheers, >>>>> Miro >>>>> >>>>> >>>>> >>>>> >>>>> >>>>> >>>>> >>>>> >>> > > _______________________________________________ > 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 miroslav.karpis at gmail.com Sun Mar 16 22:38:03 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sun, 16 Mar 2014 23:38:03 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Message-ID: Hi, sorry, but not sure what you mean with 'cabalizing the code and seeing the flags its passing'. cabal-install version 1.16.0.2 using version 1.16.0 of the Cabal library ghc: version 7.6.3 after looking a bit more I can see that the ffi call does what it should do, but it crashes right after that. As mentioned before in ghci everything runs fine. On Sun, Mar 16, 2014 at 11:20 PM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > what version of ghc and cabal? > > have you tried cabalizing the code and seeing what flags its passing? is > it possible you're passing the wrong flags? > > > On Sun, Mar 16, 2014 at 5:21 PM, Miro Karpis wrote: > >> thanks. Have tried with safe - still seg-fault. >> >> >> On Sun, Mar 16, 2014 at 5:09 PM, Vagif Verdi wrote: >> >>> Notice that i have "safe" in my foreign import ccall. This makes it safe >>> to run in threaded mode. Did you try that? >>> >>> Are you on windows? >>> >>> >>> On Sunday, March 16, 2014 1:40:48 AM UTC-7, Miro Karpis wrote: >>> >>>> thank you very much - I have tried also that but got the the same >>>> behaviour (seg fault) >>>> >>>> cheers, >>>> m. >>>> >>>> >>>> On Sun, Mar 16, 2014 at 7:45 AM, Vagif Verdi wrote: >>>> >>>>> I do not think i can help you, but my FFi to functions with similar >>>>> signature looks like this: >>>>> >>>>> C definition: >>>>> >>>>> PDFLIB_API int PDFLIB_CALL >>>>> PDF_begin_document(PDF *p, const char *filename, int len, const char >>>>> *optlist); >>>>> >>>>> haskell FFI: >>>>> >>>>> c_beginDocument :: Pdf -> String -> String -> IO Int >>>>> c_beginDocument pdf a2 a3 = >>>>> withCString a2 $ \a2' -> >>>>> withCString a3 $ c_beginDocument'_ pdf a2' 0 >>>>> >>>>> foreign import ccall safe "Pdflib.chs.h PDF_begin_document" >>>>> c_beginDocument'_ :: Pdf -> Ptr CChar -> CInt -> Ptr CChar -> IO Int >>>>> >>>>> The difference as you see, i'm using withCString to convert from >>>>> ahskell to C and i'm passing 0 as the string size. >>>>> >>>>> >>>>> >>>>> On Friday, March 14, 2014 3:24:23 PM UTC-7, Miroslav Karpis wrote: >>>>>> >>>>>> Hi, please can you help me with following? >>>>>> >>>>>> I have a call to an external dll (via ffi) which if executed from >>>>>> ghci works fine. >>>>>> If I compile my code with 'ghc -o fm Mycode.hs -L. -lextdll' and run >>>>>> it I get 'Segmentation fault/access violation in generated code'. >>>>>> >>>>>> >>>>>> >>>>>> main = do >>>>>> let param = "FilePath" >>>>>> let value = "C:/dev/misc/haskell/services/FM" >>>>>> result <- liftIO $ FM.setmodulestring param value >>>>>> return "done" >>>>>> >>>>>> setmodulestring :: String -> String -> IO CInt >>>>>> setmodulestring param value = do >>>>>> let cParamLength = fromIntegral $ length param ::CInt >>>>>> cValueLength = fromIntegral $ length value ::CInt >>>>>> setVarInArray = (-1)::CInt >>>>>> alloca $ \cParam -> do >>>>>> alloca $ \cValue -> do >>>>>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>>>>> setVarInArray >>>>>> return result >>>>>> >>>>>> If I try also with following, the behaviour is the same: >>>>>> >>>>>> setmodulestring2 :: String -> String -> IO CInt >>>>>> setmodulestring2 param value = do >>>>>> cParam <- newCWString param >>>>>> cValue <- newCWString value >>>>>> let cParamLength = fromIntegral $ length param ::CInt >>>>>> cValueLength = fromIntegral $ length value ::CInt >>>>>> setVarInArray = (-1)::CInt >>>>>> result <- c_setmodulestring cParam cParamLength cValue cValueLength >>>>>> setVarInArray >>>>>> free cParam >>>>>> free cValue >>>>>> return res >>>>>> >>>>>> >>>>>> Any comments/ideas more than appreciated. >>>>>> >>>>>> Cheers, >>>>>> Miro >>>>>> >>>>>> >>>>>> >>>>>> >>>>>> >>>>>> >>>>>> >>>>>> >>>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From allbery.b at gmail.com Sun Mar 16 22:47:47 2014 From: allbery.b at gmail.com (Brandon Allbery) Date: Sun, 16 Mar 2014 18:47:47 -0400 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Message-ID: On Sun, Mar 16, 2014 at 6:38 PM, Miro Karpis wrote: > after looking a bit more I can see that the ffi call does what it should > do, but it crashes right after that. As mentioned before in ghci everything > runs fine. > I don't think I got an answer to this before: does it still work in ghci if you run it with ghci -fno-ghci-sandbox ? -- brandon s allbery kf8nh sine nomine associates allbery.b at gmail.com ballbery at sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net -------------- next part -------------- An HTML attachment was scrubbed... URL: From miroslav.karpis at gmail.com Sun Mar 16 22:57:15 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Sun, 16 Mar 2014 23:57:15 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Message-ID: sorry,...yes it works with -fno-ghci-sandbox (no seg.fault) On Sun, Mar 16, 2014 at 11:47 PM, Brandon Allbery wrote: > On Sun, Mar 16, 2014 at 6:38 PM, Miro Karpis wrote: > >> after looking a bit more I can see that the ffi call does what it should >> do, but it crashes right after that. As mentioned before in ghci everything >> runs fine. >> > > I don't think I got an answer to this before: does it still work in ghci > if you run it with > > ghci -fno-ghci-sandbox > > ? > > -- > brandon s allbery kf8nh sine nomine > associates > allbery.b at gmail.com > ballbery at sinenomine.net > unix, openafs, kerberos, infrastructure, xmonad > http://sinenomine.net > -------------- next part -------------- An HTML attachment was scrubbed... URL: From gcrosswhite at gmail.com Mon Mar 17 04:16:20 2014 From: gcrosswhite at gmail.com (Gregory Crosswhite) Date: Sun, 16 Mar 2014 21:16:20 -0700 (PDT) Subject: [Haskell-cafe] ANN: LogicGrowsOnTrees-1.1.0.2 Message-ID: <2f3924be-c8a2-45cb-ba53-c7becbcffa50@googlegroups.com> Dear Haskellers, First, for those eager to skip directly to the more detailed documentation you can find an FAQ after the list of files at http://github.com/gcross/LogicGrowsOnTrees as well as a tutorial and users guide in respectively TUTORIAL.mdand USERS_GUIDE.mdin the list of files. The Hackage page with the reference documentation is at: http://hackage.haskell.org/package/LogicGrowsOnTrees Like many other packages on Hackage, LogicGrowsOnTrees provides an implementation of logic programming using MonadPlus; in this sense it is nothing new. What sets it apart is that it has been designed from the beginning to work in a distributed environment, allowing it to be parallelized over large numbers of processors with no shared memory. The benchmarks I have run (using the N-Queens problem with 17-19 queens) showed essentially perfect speed-up all the way up to 256 cores, and the only reason why this number is not larger is because I haven't had the opportunity to run tests on a larger cluster. Furthermore, I know from personal experience that complicated interfaces can take even the most powerful system and make it impotent, so I have tried hard to design interfaces that are easy to use and well-documented with a tutorial and several examples. There are three packages that are sibling to this: - LogicGrowsOnTrees-processes - LogicGrowsOnTrees-network - LogicGrowsOnTrees-MPI The base package (LogicGrowsOnTrees) provides an "adapter" that allows one to use threads for parallelization; the other packages above provide adapters for, respectively: processes, a network, and MPI. Each one of these packages provides specialized functionality that can be used directly, but there is also an abstraction over all of them that can be used such that the only difference between the adapters for end-users is a single line of code. For more information, see the links at the top of the post. Thank you for your attention! :-) - Greg -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.sorokin at gmail.com Mon Mar 17 06:01:35 2014 From: david.sorokin at gmail.com (David Sorokin) Date: Mon, 17 Mar 2014 10:01:35 +0400 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: <5325A5D9.8070408@web.de> References: <5325A5D9.8070408@web.de> Message-ID: Martin, It depends on that how FRP is defined. So, in F# it is usually associated with the Async monad and IObservable interface. If we will follow in the same direction then the short answer is definitely yes. An example is my simulation library Aivika [1]. My Process monad allows describing the discontinuous processes (inspired by the Async monad from F#). There is also the Signal type (inspired by the .NET IObservable interface) that allows notifying about some (.NET-like) events such as an update of the variable. Then the characteristic function in a context of FRP would be the next one: processAwait :: Signal a -> Process a There is an opposite direction from the Process computation to signals through the Task type but it is a little bit complicated as the discontinuous process can be canceled, or an IO exception may arise within the computation. But the simulation field is too big and diverse to assert something general. Thanks, David [1] http://hackage.haskell.org/package/aivika On Sun, Mar 16, 2014 at 5:23 PM, martin wrote: > FPR is usually described as a way to model interactions with the real > world. I believe the same ideas should be > applicable to simulations. Instead of "real" events I would use fake > events. This however only makes sense when the Time > associated with the Events (and Behaviors) is not wallclock time, but some > kind of virtual time. > > I looked briefly into Sodium and found no way to use "my own time". Steven > Blackheath even said during a presentation, > that Time in Sodium is just another Behavior. I am not sure if I > understood this correctly, but it gives me the feeling, > that the only Time available in Sodium is wallclock time, which would make > it unsuitable for simulations. > > Could someone give me some insights whether or not FRP is suitable for > simulations? > > Does my reasoning about Time make any sense? Do different libraries treat > Time in different ways, such that some are > suitable for simulations, while others are not? > > Martin > > _______________________________________________ > 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 lambda.fairy at gmail.com Mon Mar 17 09:42:14 2014 From: lambda.fairy at gmail.com (Chris Wong) Date: Mon, 17 Mar 2014 22:42:14 +1300 Subject: [Haskell-cafe] Google Summer of Code? Message-ID: Hello Cafe, I'm currently considering applying for the Summer of Code. Johan Tibell's idea of improving the Hackage login system [1] looks compelling, since I have worked with Happstack before [2]. Is there enough time to start a proposal? I know it's a bit late now -- but I would very much like to participate. Thanks Chris [1] http://blog.johantibell.com/2014/03/google-summer-of-code-projects.html [2] https://github.com/lfairy/sparkle From miroslav.karpis at gmail.com Mon Mar 17 09:50:56 2014 From: miroslav.karpis at gmail.com (Miro Karpis) Date: Mon, 17 Mar 2014 10:50:56 +0100 Subject: [Haskell-cafe] ffi call works fine in ghci but not as ghc compiledsegfault In-Reply-To: References: <4d4ef90c-01fb-41c4-956e-255ef49f5c40@googlegroups.com> <4b4b887b-9293-46c3-ba3e-b35258c27c3a@googlegroups.com> Message-ID: I finally managed to fix the seg-fault. Brandon and Branimir you were as always right ;-) . Problem was in the external function definition. After changing it to 'stdcall' everything works fine. for further reference working code below: foreign import stdcall safe "setmodulestring" c_setmodulestring :: CString -> CUInt -> CString -> CUInt -> CInt -> IO CInt --all 3 versions work fine: setmodulestring param value = do cParam <- newCString param cValue <- newCString value let cParamLength = fromIntegral $ length param ::CUInt cValueLength = fromIntegral $ length value ::CUInt setVarInArray = (-1)::CInt result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray free cParam free cValue return result setmodulestring2 param value = do let cParamLength = fromIntegral $ length param ::CUInt cValueLength = fromIntegral $ length value ::CUInt setVarInArray = (-1)::CInt B.useAsCString (B.pack param) $ \cParam -> do B.useAsCString (B.pack value) $ \cValue -> do result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray return result setmodulestring3 param value = withCString param $ \cParam -> do withCString value $ \cValue -> do result <- c_setmodulestring cParam cParamLength cValue cValueLength setVarInArray return result where cParamLength = fromIntegral $ length param ::CUInt cValueLength = fromIntegral $ length value ::CUInt setVarInArray = (-1)::CInt thank you cafe, for helping me along this ;-) On Sun, Mar 16, 2014 at 11:57 PM, Miro Karpis wrote: > sorry,...yes it works with -fno-ghci-sandbox (no seg.fault) > > > On Sun, Mar 16, 2014 at 11:47 PM, Brandon Allbery wrote: > >> On Sun, Mar 16, 2014 at 6:38 PM, Miro Karpis wrote: >> >>> after looking a bit more I can see that the ffi call does what it should >>> do, but it crashes right after that. As mentioned before in ghci everything >>> runs fine. >>> >> >> I don't think I got an answer to this before: does it still work in ghci >> if you run it with >> >> ghci -fno-ghci-sandbox >> >> ? >> >> -- >> brandon s allbery kf8nh sine nomine >> associates >> allbery.b at gmail.com >> ballbery at sinenomine.net >> unix, openafs, kerberos, infrastructure, xmonad >> http://sinenomine.net >> > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johan.tibell at gmail.com Mon Mar 17 09:54:43 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 17 Mar 2014 10:54:43 +0100 Subject: [Haskell-cafe] Google Summer of Code? In-Reply-To: References: Message-ID: Hi Chris, The deadline [1] is 21 March, 19:00 UTC, so there's still time. Just make sure you get a proposal in before that time. 1. https://www.google-melange.com/gsoc/events/google/gsoc2014 On Mon, Mar 17, 2014 at 10:42 AM, Chris Wong wrote: > Hello Cafe, > > I'm currently considering applying for the Summer of Code. Johan > Tibell's idea of improving the Hackage login system [1] looks > compelling, since I have worked with Happstack before [2]. > > Is there enough time to start a proposal? I know it's a bit late now > -- but I would very much like to participate. > > Thanks > Chris > > [1] > http://blog.johantibell.com/2014/03/google-summer-of-code-projects.html > [2] https://github.com/lfairy/sparkle > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From johan.tibell at gmail.com Mon Mar 17 10:01:13 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 17 Mar 2014 11:01:13 +0100 Subject: [Haskell-cafe] Want to get paid to hack on Haskell for the summer. GSoC deadline is 21 March Message-ID: Hi, If you're a student and want to get paid to write Haskell this summer, it's time to apply for this year's Google Summer of Code. The deadline is 21 March, 19:00 UTC. Here are some project ideas: http://blog.johantibell.com/2014/03/google-summer-of-code-projects.html -- Johan -------------- next part -------------- An HTML attachment was scrubbed... URL: From sacha404 at gmail.com Mon Mar 17 10:02:31 2014 From: sacha404 at gmail.com (Sacha Sokoloski) Date: Mon, 17 Mar 2014 11:02:31 +0100 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: References: Message-ID: <5326C837.8080700@gmail.com> So I'm also doing a lot of simulations, and have experimented with FRP as a basic toolset for defining my simulations. I experimented with Netwire for a while, and while I still think it's a good library, I eventually threw it away to rely simply on Mealy Arrows (Netwire is Arrow based FRP). From what I've seen, the point of FRP libraries is to handle interactivity. That's what all the functions in the libraries are about. If you do have a virtual time stream that you can simply define at runtime and doesn't require side effects, you may find, as I did, that you'll create a simplified type synonym for the FRP structure that you're working with, and then not really using the libraries at all. The point is ultimately that, although pure simulations could nicely be part of any more complicated FRP program, if all you want is to do pure simulations, then you'll be introducing a fair bit of computational/structural overhead to fit it within the FRP framework, without any real payoff. Cheers, - Sacha On 17/03/14 10:50 AM, haskell-cafe-request at haskell.org wrote: > Message: 1 > Date: Sun, 16 Mar 2014 14:23:37 +0100 > From: martin > To:haskell-cafe at haskell.org > Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) > Message-ID:<5325A5D9.8070408 at web.de> > Content-Type: text/plain; charset=ISO-8859-15 > > FPR is usually described as a way to model interactions with the real world. I believe the same ideas should be > applicable to simulations. Instead of "real" events I would use fake events. This however only makes sense when the Time > associated with the Events (and Behaviors) is not wallclock time, but some kind of virtual time. > > I looked briefly into Sodium and found no way to use "my own time". Steven Blackheath even said during a presentation, > that Time in Sodium is just another Behavior. I am not sure if I understood this correctly, but it gives me the feeling, > that the only Time available in Sodium is wallclock time, which would make it unsuitable for simulations. > > Could someone give me some insights whether or not FRP is suitable for simulations? > > Does my reasoning about Time make any sense? Do different libraries treat Time in different ways, such that some are > suitable for simulations, while others are not? > > Martin From fuuzetsu at fuuzetsu.co.uk Mon Mar 17 10:40:52 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 17 Mar 2014 10:40:52 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <531DD5BD.8090005@fuuzetsu.co.uk> References: <531DD5BD.8090005@fuuzetsu.co.uk> Message-ID: <5326D134.8090505@fuuzetsu.co.uk> On 10/03/14 15:09, Mateusz Kowalczyk wrote: > Greetings, > > GSOC 2014 proposal period opens in ~4 hours and I'm hoping to > participate this year as well. This time around I'd quite like to work > on Yi. As we did last year, I think it's worthwhile to put up the > proposals on caf? for people to comment on before they are submitted on > Google's site. > > I paste it in full below so that it is easier to respond to parts of it > (although I do ask that you don't quote the whole thing if it's not > necessary). In case any changes happen, the most up-to-date version > should be at https://gist.github.com/Fuuzetsu/9462709 > > Please feel free to nitpick on anything, throw in suggestions and ask > for clarifications. I will give 5 days of discussion period on this > after which point I'll submit it on Google's site. I appreciate all > feedback. > > Thanks! > > > [snip] It was about 5 days now so I'll be submitting the proposal with minor changes we discussed. Thanks! -- Mateusz K. From tanielsen at gmail.com Mon Mar 17 10:58:59 2014 From: tanielsen at gmail.com (Tom Nielsen) Date: Mon, 17 Mar 2014 10:58:59 +0000 Subject: [Haskell-cafe] Two research positions in functional probabilistic programming Message-ID: Dear Cafe, Two positions involving substantial Haskell work are available for a project that seeks to combine functional and probabilistic programming. We are looking for two postdocs to work on a practical system for large-scale inference in scientific and clinical datasets using bayesian statistical models, embedded in a typed functional programming language and based on stochastic dynamical systems. * A typed hierarchical database that uses a Hindley-Milner-like typesystem (with records) to organise large, complex and heterogeneous data from a hospital. * Probabilistic inference over these complex datasets * Parallelizing Bayesian inference * Modelling clinical datasets (for instance ECG) using dynamical systems. Some of these ideas have been explored in our Baysig Language ( http://tinyurl.com/Baysig) and BayesHive project (https://BayesHive.com) - both Baysig and BayesHive are implemented in Haskell. However, these are academic research posts and there is scope for exploring different designs to meet the same aims. Here are the official adverts: http://ig5.i-grasp.com/fe/tpl_UniversityOfLeicester01.asp?newms=jj&id=85616&aid=14178 http://ig5.i-grasp.com/fe/tpl_UniversityOfLeicester01.asp?newms=jj&id=85615&aid=14178 The application deadline is April 10. If you think you may be interested, you are welcome to ask me (tanielsen at gmail.com or tomn at openbrain.org) or Tom Matheson (tm75 at le.ac.uk) any questions. Tom Nielsen OpenBrain Ltd http://openbrain.co.uk -------------- next part -------------- An HTML attachment was scrubbed... URL: From agocorona at gmail.com Mon Mar 17 11:50:24 2014 From: agocorona at gmail.com (Alberto G. Corona ) Date: Mon, 17 Mar 2014 12:50:24 +0100 Subject: [Haskell-cafe] GSOC and "scripting the inference process" .Was: Re: Haskell compilation errors break the complexity encapsulation on DSLs Message-ID: Now that GSOC comes again, I call you into attention one of the biggest problems that Haskell has to solve before being fully accepted in the IT industry: The (unnecessary) complexity of the DSL error messages. There is some work being done: http://dl.acm.org/citation.cfm?id=944707 The idea was to implement it in GHC after refining and testing it if I remember well. If some of this work can be carried out in a GSOC project, IMHO it should be given priority. In case that this work is not going to be available in the short-medium term, there is a ticket with some suggestions that can be carried out in a GSOC project, just in case any of you are interested into mentoring/carrying out this or any other solution to overcome this problem: http://hackage.haskell.org/trac/ghc/ticket/7870 2013-04-27 22:14 GMT+02:00 Ozgur Akgun : > Hi, > > On 27 April 2013 10:07, Alberto G. Corona wrote: > >> I created a ticket for the feature request: >> >> Ticket #7870 >> >> Teachers, newbies and people working in Industry: Please push it! >> > > A link to the ticket may be helpful for the lazy. > > http://hackage.haskell.org/trac/ghc/ticket/7870 > > I quite like this idea, and I think this is one thing people use TH for > now instead. > (Using quasi-quotes, you can produce any compilation error you like...) > It would be great if we didn't have to pull in the full power of TH (or > QQ) for this. > > > Cheers, > Ozgur > > -- Alberto. -------------- next part -------------- An HTML attachment was scrubbed... URL: From J.Hage at uu.nl Mon Mar 17 13:16:09 2014 From: J.Hage at uu.nl (Jurriaan Hage) Date: Mon, 17 Mar 2014 14:16:09 +0100 Subject: [Haskell-cafe] GSOC and "scripting the inference process" .Was: Re: Haskell compilation errors break the complexity encapsulation on DSLs In-Reply-To: References: Message-ID: Hello, I currently have a PhD student who is working on exactly this topic: extending the work of our Scripting the Type Inferencer paper to full Haskell. His name is Alejandro Serrano Mena. He started last November. I believe the complications of being able to deal with type system extensions currently available and in use in Haskell to be so invasive that it will take a few years to get the complete picture (considering type classes with extensions, GADTs, type families etc.). A Google Summer Of Code for the Haskell 98 subset (ie. implementing that in GHC) should be possible, I guess. Whether that implementation later scales to the full language may be something of a concern. We, ourselves, shall be prototyping the new things in the Utrecht Haskell Compiler, and the plan was that after Alejandro has finished his PhD and given a positive outcome of his work, that something should be arranged to make it available to the general Haskell programming audience by implementing it into GHC. best, Jurriaan On 17Mar, 2014, at 12:50, Alberto G. Corona wrote: > Now that GSOC comes again, I call you into attention one of the biggest problems that Haskell has to solve before being fully accepted in the IT industry: The (unnecessary) complexity of the DSL error messages. > > There is some work being done: > > http://dl.acm.org/citation.cfm?id=944707 > > > The idea was to implement it in GHC after refining and testing it if I remember well. If some of this work can be carried out in a GSOC project, IMHO it should be given priority. > > In case that this work is not going to be available in the short-medium term, > there is a ticket with some suggestions that can be carried out in a GSOC project, just in case any of you are interested into mentoring/carrying out this or any other solution to overcome this problem: > > http://hackage.haskell.org/trac/ghc/ticket/7870 > > > > 2013-04-27 22:14 GMT+02:00 Ozgur Akgun : > Hi, > > On 27 April 2013 10:07, Alberto G. Corona wrote: > I created a ticket for the feature request: > > Ticket #7870 > > Teachers, newbies and people working in Industry: Please push it! > > A link to the ticket may be helpful for the lazy. > > http://hackage.haskell.org/trac/ghc/ticket/7870 > > I quite like this idea, and I think this is one thing people use TH for now instead. > (Using quasi-quotes, you can produce any compilation error you like...) > It would be great if we didn't have to pull in the full power of TH (or QQ) for this. > > > Cheers, > Ozgur > > > > > -- > Alberto. From ketil at malde.org Mon Mar 17 13:17:20 2014 From: ketil at malde.org (Ketil Malde) Date: Mon, 17 Mar 2014 14:17:20 +0100 Subject: [Haskell-cafe] projects page Message-ID: <87bnx5x8v3.fsf@wespe.malde.org> I tried to follow the link from Google (Melange, http://www.google-melange.com/gsoc/org2/google/gsoc2014/haskell) to the ideas page - but it seems there are only outdated ideas there? Sorry if I wasn't paying attention in class, but how is this intended to work? Is there some other place I should look? -k -- If I haven't seen further, it is by standing in the footprints of giants From johan.tibell at gmail.com Mon Mar 17 13:43:31 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 17 Mar 2014 14:43:31 +0100 Subject: [Haskell-cafe] projects page In-Reply-To: <87bnx5x8v3.fsf@wespe.malde.org> References: <87bnx5x8v3.fsf@wespe.malde.org> Message-ID: Unfortunately there's no great central list of ideas. Most lists we have, such as the one you linked or http://www.reddit.com/r/haskell_proposals, are a bit outdated and haven't been sanity check*. Greg Weber posted some proposals at: http://www.yesodweb.com/blog/2014/03/gsoc-proposals I posted a few at: http://blog.johantibell.com/2014/03/google-summer-of-code-projects.html * You will find completely unfeasible projects like writing a web browser on these pages. On Mon, Mar 17, 2014 at 2:17 PM, Ketil Malde wrote: > > I tried to follow the link from Google (Melange, > http://www.google-melange.com/gsoc/org2/google/gsoc2014/haskell) to the > ideas page - but it seems there are only outdated ideas there? Sorry if > I wasn't paying attention in class, but how is this intended to work? Is > there some other place I should look? > > -k > -- > If I haven't seen further, it is by standing in the footprints of giants > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From konn.jinro at gmail.com Mon Mar 17 14:11:24 2014 From: konn.jinro at gmail.com (Hiromi ISHII) Date: Mon, 17 Mar 2014 23:11:24 +0900 Subject: [Haskell-cafe] [GSoC] A proposal for GSoC regarding computational algebra Message-ID: Hello, cafe I am a currently an undergraduate student and will enter the graduate school on April. As a student, I have a project to propose for the GSoC: purely functional computer algebra library. I've been working on computational-algebra library [1], but this library needs more improvements. Especially, it needs much more performance improvements for Groebner bases computation. I want to implement efficient algorithms called F4 and F5 [2, 3] as the GSoC project. These algorithms require efficient linear algebra algorithms, so this project also involves the development of efficient symbolic linear algebra library. This project is not on any ideas list as far as I know, and I want to directly propose to the GSoC and I'm looking for a mentor. Is there anyone interested in my proposal? [1]: http://github.com/konn/computational-algebra [2]: http://www-polsys.lip6.fr/~jcf/Papers/F99a.pdf [3]: http://www.risc.jku.at/Groebner-Bases-Bibliography/gbbib_files/publication_502.pdf -- Hiromi ISHII konn.jinro at gmail.com From ekmett at gmail.com Mon Mar 17 16:24:32 2014 From: ekmett at gmail.com (Edward Kmett) Date: Mon, 17 Mar 2014 12:24:32 -0400 Subject: [Haskell-cafe] [GSoC] A proposal for GSoC regarding computational algebra In-Reply-To: References: Message-ID: I suppose given your library's use of my algebra package and other components under the hood, etc. I'd probably be the most likely mentor. I'd be willing to work with you, and likely to fold it in/replace much of the existing algebra machinery, which I confess is woefully under-maintained. Usually, proposals to write a new library have a hard time getting accepted to GSOC, but you do already have a decent sized body of work there. -Edward On Mon, Mar 17, 2014 at 10:11 AM, Hiromi ISHII wrote: > Hello, cafe > > I am a currently an undergraduate student and will enter the graduate > school on April. > As a student, I have a project to propose for the GSoC: purely functional > computer algebra library. > > I've been working on computational-algebra library [1], but this library > needs more improvements. > Especially, it needs much more performance improvements for Groebner bases > computation. > I want to implement efficient algorithms called F4 and F5 [2, 3] as the > GSoC project. > These algorithms require efficient linear algebra algorithms, so this > project also involves the development of efficient symbolic linear algebra > library. > > This project is not on any ideas list as far as I know, and I want to > directly propose to the GSoC and I'm looking for a mentor. > Is there anyone interested in my proposal? > > [1]: http://github.com/konn/computational-algebra > [2]: http://www-polsys.lip6.fr/~jcf/Papers/F99a.pdf > [3]: > http://www.risc.jku.at/Groebner-Bases-Bibliography/gbbib_files/publication_502.pdf > > -- Hiromi ISHII > konn.jinro at gmail.com > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From martin.drautzburg at web.de Mon Mar 17 18:07:09 2014 From: martin.drautzburg at web.de (martin) Date: Mon, 17 Mar 2014 19:07:09 +0100 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: References: <5325A5D9.8070408@web.de> Message-ID: <532739CD.8050601@web.de> I stumbled across avika but haven't looked at it. One of my problems is to decide where to dive in. Should I look at yampa, sodium or avika when I want to do simulations? Am 03/17/2014 07:01 AM, schrieb David Sorokin: > Martin, > > It depends on that how FRP is defined. > > So, in F# it is usually associated with the Async monad and IObservable interface. > > If we will follow in the same direction then the short answer is definitely yes. An example is my simulation library > Aivika [1]. > > My Process monad allows describing the discontinuous processes (inspired by the Async monad from F#). There is also the > Signal type (inspired by the .NET IObservable interface) that allows notifying about some (.NET-like) events such as an > update of the variable. > > Then the characteristic function in a context of FRP would be the next one: > > processAwait :: Signal a -> Process a > > There is an opposite direction from the Process computation to signals through the Task type but it is a little bit > complicated as the discontinuous process can be canceled, or an IO exception may arise within the computation. > > But the simulation field is too big and diverse to assert something general. > > Thanks, > David > > [1] http://hackage.haskell.org/package/aivika From sean.leather at gmail.com Mon Mar 17 18:10:42 2014 From: sean.leather at gmail.com (Sean Leather) Date: Mon, 17 Mar 2014 20:10:42 +0200 Subject: [Haskell-cafe] Changes to cabal-install In-Reply-To: References: Message-ID: On Fri, Mar 14, 2014 at 6:22 PM, Mikhail Glushenkov wrote: > Hi, > > On 14 March 2014 17:03, Amy de Buitl?ir wrote: > > > > Question 1 > > ---------- > > Until recently, the command > > > > cabal install --enable-tests > > > > used to build and run the tests. Now it seems I need to do > > > > cabal test > > > > which then compiles the tests and runs them. So is the --enable-tests > flag > > doing anything, or is it now obsolete? > > Using 'cabal test' is preferable. You don't want to reinstall the > package each time you run the test suite. > This sounds related: https://github.com/haskell/cabal/issues/1647 Regards, Sean -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Mon Mar 17 19:07:57 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Mon, 17 Mar 2014 15:07:57 -0400 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: <532739CD.8050601@web.de> References: <5325A5D9.8070408@web.de> <532739CD.8050601@web.de> Message-ID: depends on the type of simulation! indeed, is your modelling needs "casual" or "acausall"? The latter would be say "i'm describing a circuit board" the former would be "given this change in inputs, respond like so". Not every simulation needs to be of the former sort! On Mon, Mar 17, 2014 at 2:07 PM, martin wrote: > I stumbled across avika but haven't looked at it. One of my problems is to > decide where to dive in. Should I look at > yampa, sodium or avika when I want to do simulations? > > Am 03/17/2014 07:01 AM, schrieb David Sorokin: > > Martin, > > > > It depends on that how FRP is defined. > > > > So, in F# it is usually associated with the Async monad and IObservable > interface. > > > > If we will follow in the same direction then the short answer is > definitely yes. An example is my simulation library > > Aivika [1]. > > > > My Process monad allows describing the discontinuous processes (inspired > by the Async monad from F#). There is also the > > Signal type (inspired by the .NET IObservable interface) that allows > notifying about some (.NET-like) events such as an > > update of the variable. > > > > Then the characteristic function in a context of FRP would be the next > one: > > > > processAwait :: Signal a -> Process a > > > > There is an opposite direction from the Process computation to signals > through the Task type but it is a little bit > > complicated as the discontinuous process can be canceled, or an IO > exception may arise within the computation. > > > > But the simulation field is too big and diverse to assert something > general. > > > > Thanks, > > David > > > > [1] http://hackage.haskell.org/package/aivika > > _______________________________________________ > 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 martin.drautzburg at web.de Mon Mar 17 20:31:58 2014 From: martin.drautzburg at web.de (martin) Date: Mon, 17 Mar 2014 21:31:58 +0100 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: <5326C837.8080700@gmail.com> References: <5326C837.8080700@gmail.com> Message-ID: <53275BBE.1020909@web.de> Thank you, thank you! I did wonder: "how hard can it be?" and "what could these libraries possibly do?", but I said to myself: "Martin, don't re-invent the wheel". You confirm my initial hunch. So, but where to go from where I am now? I hear the message, but I don't know what to do. Am 03/17/2014 11:02 AM, schrieb Sacha Sokoloski: > So I'm also doing a lot of simulations, and have experimented with FRP as a basic toolset for defining my simulations. > > I experimented with Netwire for a while, and while I still think it's a good library, I eventually threw it away to rely > simply on Mealy Arrows (Netwire is Arrow based FRP). > > From what I've seen, the point of FRP libraries is to handle interactivity. That's what all the functions in the > libraries are about. If you do have a virtual time stream that you can simply define at runtime and doesn't require side > effects, you may find, as I did, that you'll create a simplified type synonym for the FRP structure that you're working > with, and then not really using the libraries at all. The point is ultimately that, although pure simulations could > nicely be part of any more complicated FRP program, if all you want is to do pure simulations, then you'll be > introducing a fair bit of computational/structural overhead to fit it within the FRP framework, without any real payoff. From ketil at malde.org Mon Mar 17 20:58:30 2014 From: ketil at malde.org (Ketil Malde) Date: Mon, 17 Mar 2014 21:58:30 +0100 Subject: [Haskell-cafe] projects page In-Reply-To: References: <87bnx5x8v3.fsf@wespe.malde.org> Message-ID: <877g7sy234.fsf@wespe.malde.org> I wonder if there would be any interest in a fast and compact associative data structure (a.k.a. finite map)? I did a quick writeup here: http://biohaskell.org/GSOC/kmerindex and could also volunteer to mentor it (but would be happy to see somebody else do it, too). As I am often working with large data sets, the cost of the standard data structures (Data.Map and friends) are often causing problems. Judy arrays get me some of the way, but I'd like something more general. Although I want it for shamlessly selfish reasons, I think it would make a worthwhile addition to the Haskell ecosystem at large. Anyway - feel free to contact me if anything is unclear. -k -- If I haven't seen further, it is by standing in the footprints of giants From ketil at malde.org Mon Mar 17 21:10:11 2014 From: ketil at malde.org (Ketil Malde) Date: Mon, 17 Mar 2014 22:10:11 +0100 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <33c64001-efa1-4ef7-9b6f-7364bba5d71a@googlegroups.com> References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> <33c64001-efa1-4ef7-9b6f-7364bba5d71a@googlegroups.com> Message-ID: <871ty0y1jr.fsf@wespe.malde.org> > We are not discussing here what tool is the best and try to mandate > everyone to use it. We are discussing how to efficiently use the scarce > development resources (time, money) for the benefit of haskell community. Well, in the end the proposals will be voted over. Less general proposals are likely to get fewer votes. > The consensus is already there. It is obvious the demand for such tool is > high, hence many (failed) attempts. Failed because of the lack of resources > and coordination. Say what? I'm not familiar with the others, but Emacs and haskell-mode and ghc-mode and darcsum works pretty well for me - I'd certainly not call them failures. (Of course, I would rather see somebody spending GSoC working on them, but I accept that other people prefer other systems. But while I'm at it, some things I might like to see would be: - quickcheck/flymake support, so that funcitons with failing unit tests are highlighted automatically - code coverage highlighting in buffer - org-mode-like folding and refiling - automatic import/export list management - perhaps easy navigation between source and core? ) -k -- If I haven't seen further, it is by standing in the footprints of giants From dagit at galois.com Mon Mar 17 22:11:03 2014 From: dagit at galois.com (Jason Dagit) Date: Mon, 17 Mar 2014 15:11:03 -0700 Subject: [Haskell-cafe] [haskell-infrastructure] Hackage down? In-Reply-To: References: Message-ID: <998B3517-E22C-4A30-A139-36409A093F73@galois.com> On Mar 17, 2014, at 14:58, Iavor Diatchki wrote: > Hello, > > It looks like Hackage has stopped responding? (2:50pm PDT, 17 March 2014). Thanks for letting us know. The haskell-infrastructure team is on it. A reboot request has already been filed with hetzner. Jason -------------- next part -------------- A non-text attachment was scrubbed... Name: smime.p7s Type: application/pkcs7-signature Size: 2199 bytes Desc: not available URL: From iavor.diatchki at gmail.com Mon Mar 17 21:58:34 2014 From: iavor.diatchki at gmail.com (Iavor Diatchki) Date: Mon, 17 Mar 2014 14:58:34 -0700 Subject: [Haskell-cafe] Hackage down? Message-ID: Hello, It looks like Hackage has stopped responding? (2:50pm PDT, 17 March 2014). -Iavor -------------- next part -------------- An HTML attachment was scrubbed... URL: From matthewtpickering at gmail.com Tue Mar 18 01:16:14 2014 From: matthewtpickering at gmail.com (Matthew Pickering) Date: Tue, 18 Mar 2014 01:16:14 +0000 Subject: [Haskell-cafe] GSoC Proposal: Pandoc improvements including EPUB 3.0 reader Message-ID: I'm looking to submit a proposal to (mainly) add an EPUB reader to pandoc. I've spent the last few weeks getting to know the code base and wrote a proposal in the last few days. I would really appreciate any comments on the proposal and any further suggestions or things to look out for! Looking forward to doing some hacking on pandoc independent of this! Full proposal: https://www.dropbox.com/s/tdiimqa8mj22vq3/gsoc.pdf Has anyone looked into MathML -> Latex conversion? It would be nice to have this in the EPUB parser to deal with embedded equations. Below is a sketch outline of the suggested implementation. *Embedded Base64 images* - Replace Target in the Image constructor with a new constructor which can either be a Target as before or a base64 encoding. - Update HTML5 reader to read embedded images successfully. *EPUB 3.0 reader* - Utilise the HTML parser with rawTags enabled - Extract additional information about structure from walking over the AST -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Mon Mar 17 22:31:47 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Mon, 17 Mar 2014 22:31:47 +0000 Subject: [Haskell-cafe] Yi project proposal for GSOC 2014 In-Reply-To: <871ty0y1jr.fsf@wespe.malde.org> References: <531DD5BD.8090005@fuuzetsu.co.uk> <4d4d7b55-6797-4219-a453-9246e9c5b038@googlegroups.com> <33c64001-efa1-4ef7-9b6f-7364bba5d71a@googlegroups.com> <871ty0y1jr.fsf@wespe.malde.org> Message-ID: <532777D3.70406@fuuzetsu.co.uk> On 17/03/14 21:10, Ketil Malde wrote: > >> We are not discussing here what tool is the best and try to mandate >> everyone to use it. We are discussing how to efficiently use the scarce >> development resources (time, money) for the benefit of haskell community. > > Well, in the end the proposals will be voted over. Less general > proposals are likely to get fewer votes. > >> The consensus is already there. It is obvious the demand for such tool is >> high, hence many (failed) attempts. Failed because of the lack of resources >> and coordination. > > Say what? I'm not familiar with the others, but Emacs and haskell-mode > and ghc-mode and darcsum works pretty well for me - I'd certainly not > call them failures. > > (Of course, I would rather see somebody spending GSoC working on them, > but I accept that other people prefer other systems. But while I'm at > it, some things I might like to see would be: > > - quickcheck/flymake support, so that funcitons with failing unit > tests are highlighted automatically > - code coverage highlighting in buffer > - org-mode-like folding and refiling > - automatic import/export list management > - perhaps easy navigation between source and core? > ) > > -k > As I pointed out, Yi is not one of these attempts. The people in this sub-thread made their own thread (Haskell IDEs or something) so you might want to reply there. -- Mateusz K. From david.sorokin at gmail.com Tue Mar 18 04:40:11 2014 From: david.sorokin at gmail.com (David Sorokin) Date: Tue, 18 Mar 2014 08:40:11 +0400 Subject: [Haskell-cafe] FRP, Simulations and Time (Sodium et. al) In-Reply-To: References: <5325A5D9.8070408@web.de> <532739CD.8050601@web.de> Message-ID: <5327CE2B.30206@gmail.com> I agree that it depends on the type of simulation. As usual in the life, there is no universal method. 17.03.2014 23:07, Carter Schonwald ?????: > depends on the type of simulation! > > indeed, is your modelling needs "casual" or "acausall"? The latter > would be say "i'm describing a circuit board" the former would be > "given this change in inputs, respond like so". Not every simulation > needs to be of the former sort! > > > On Mon, Mar 17, 2014 at 2:07 PM, martin > wrote: > > I stumbled across avika but haven't looked at it. One of my > problems is to decide where to dive in. Should I look at > yampa, sodium or avika when I want to do simulations? > > Am 03/17/2014 07:01 AM, schrieb David Sorokin: > > Martin, > > > > It depends on that how FRP is defined. > > > > So, in F# it is usually associated with the Async monad and > IObservable interface. > > > > If we will follow in the same direction then the short answer is > definitely yes. An example is my simulation library > > Aivika [1]. > > > > My Process monad allows describing the discontinuous processes > (inspired by the Async monad from F#). There is also the > > Signal type (inspired by the .NET IObservable interface) that > allows notifying about some (.NET-like) events such as an > > update of the variable. > > > > Then the characteristic function in a context of FRP would be > the next one: > > > > processAwait :: Signal a -> Process a > > > > There is an opposite direction from the Process computation to > signals through the Task type but it is a little bit > > complicated as the discontinuous process can be canceled, or an > IO exception may arise within the computation. > > > > But the simulation field is too big and diverse to assert > something general. > > > > Thanks, > > David > > > > [1] http://hackage.haskell.org/package/aivika > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From lambda.fairy at gmail.com Tue Mar 18 08:30:39 2014 From: lambda.fairy at gmail.com (Chris Wong) Date: Tue, 18 Mar 2014 21:30:39 +1300 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system Message-ID: Hello Cafe, Like Matthew and Mateusz, I'm submitting a GSoC proposal as well! The initial draft is here: https://docs.google.com/document/d/1bcDiudULtaz3NFCqTHXD2WU6Ighsm199D7ojfS8quVI/edit It's not a long read, so please do. Any comments, suggestions, &c would be appreciated greatly. If all is well, I will submit this in 48 hours. As an aside: would anyone like to mentor this project? Again, apologies for the late response. Thanks Chris From edwards.benj at gmail.com Tue Mar 18 09:28:32 2014 From: edwards.benj at gmail.com (Benjamin Edwards) Date: Tue, 18 Mar 2014 09:28:32 +0000 Subject: [Haskell-cafe] Bound library + recovering de Bruijn indices References: Message-ID: On Sun Mar 16 2014 at 17:02:35, Benjamin Edwards wrote: > Hi Cafe > > I am currently experimenting with the excellent bound library. I want to > implement the simply typed lambda calc from TAPL (no type inference yet). > When moving under a binder I want to extend my context and then look up > bound terms by their indices using list indexing. I would have thought I > could use something like foldMapScope to recover the bound variables, then > write some function to calculate the depth of the "listy" type value > returned and thus recover the index. However! The type returned is > non-regular and I cannot for the life of me figure out anything that > doesn't involve GHC complaining about infinite types. > > Any pointers on how this can be accomplished? > > For the record, this is what I have that works at the moment. > > http://lpaste.net/101279 > I am currently trying to write a function using polymorphic recursion to get around the nested type but not having any luck. This is what I have so far (+the paste above): peel :: (forall a. Var () a -> Int) -> Var () r -> Int peel f x = f x g n (F (TVar x)) = peel (g (n + 1)) x g n (B ()) = 0 Var is iso to Either (from the bound library) And the idea is to count the level of nested Fs in the sum type. Can anyone give me any pointers? -------------- next part -------------- An HTML attachment was scrubbed... URL: From fuuzetsu at fuuzetsu.co.uk Tue Mar 18 10:04:29 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Tue, 18 Mar 2014 10:04:29 +0000 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: References: Message-ID: <53281A2D.6050301@fuuzetsu.co.uk> On 18/03/14 08:30, Chris Wong wrote: > Hello Cafe, > > Like Matthew and Mateusz, I'm submitting a GSoC proposal as well! > > The initial draft is here: > https://docs.google.com/document/d/1bcDiudULtaz3NFCqTHXD2WU6Ighsm199D7ojfS8quVI/edit > > It's not a long read, so please do. Any comments, suggestions, &c > would be appreciated greatly. If all is well, I will submit this in 48 > hours. > > As an aside: would anyone like to mentor this project? Again, > apologies for the late response. > > Thanks > Chris > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > Perhaps considering improving your ?why you think you're the best person for this? because I know there is another student submitting the proposal about the same topic! -- Mateusz K. From rvdalen at yahoo.co.uk Tue Mar 18 10:53:18 2014 From: rvdalen at yahoo.co.uk (Rouan van Dalen) Date: Tue, 18 Mar 2014 10:53:18 +0000 (GMT) Subject: [Haskell-cafe] linking warnings when using regex-posix package in GHCi 7.8.1 RC2 Message-ID: <1395139998.35417.YahooMailNeo@web171902.mail.ir2.yahoo.com> Hi Cafe, I have the following program: ========================= module Main where ? ?import Text.Regex.Posix ? ?main = do ? ? ? putStrLn "!!!" ========================= When I run the main function from within GHCi, I get the following output from GHCi: ========================= Loading package array-0.5.0.0 ... linking ... done. Loading package deepseq-1.3.0.2 ... linking ... done. Loading package containers-0.5.4.0 ... linking ... done. Loading package bytestring-0.10.4.0 ... linking ... done. Loading package transformers-0.3.0.0 ... linking ... done. Loading package mtl-2.1.2 ... linking ... done. Loading package regex-base-0.93.2 ... linking ... done. Loading package regex-posix-0.95.2 ... linking ...? : warning: isupper from msvcrt is linked instead of __imp_isupper : warning: toupper from msvcrt is linked instead of __imp_toupper : warning: tolower from msvcrt is linked instead of __imp_tolower : warning: isalpha from msvcrt is linked instead of __imp_isalpha : warning: isalpha from msvcrt is linked instead of __imp_isalpha : warning: isalpha from msvcrt is linked instead of __imp_isalpha : warning: iscntrl from msvcrt is linked instead of __imp_iscntrl : warning: isupper from msvcrt is linked instead of __imp_isupper : warning: isgraph from msvcrt is linked instead of __imp_isgraph : warning: isprint from msvcrt is linked instead of __imp_isprint : warning: ispunct from msvcrt is linked instead of __imp_ispunct : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalpha from msvcrt is linked instead of __imp_isalpha : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum : warning: isalnum from msvcrt is linked instead of __imp_isalnum done. !!! *Main> ========================= Does anyone have an idea why GHCi is even linking against msvcrt? And is there a way to fix this? I am using GHC 7.8.1 RC2 x64 on Windows 8 x64 Regards --Rouan -------------- next part -------------- An HTML attachment was scrubbed... URL: From dominic at steinitz.org Tue Mar 18 11:24:21 2014 From: dominic at steinitz.org (Dominic Steinitz) Date: Tue, 18 Mar 2014 11:24:21 +0000 (UTC) Subject: [Haskell-cafe] =?utf-8?q?=5BGSoC=5D_A_proposal_for_GSoC_regarding?= =?utf-8?q?_computational=09algebra?= References: Message-ID: Hiromi ISHII gmail.com> writes: > > Is there anyone interested in my proposal? > I might be. Can you give some use cases? I should point out I do a fair amount of numerical work and this typically involves linear algebra but from a numerical point of view. I am also quite interested in computational algebraic topology but I suspect you are not proposing to work on that? From kyrab at mail.ru Tue Mar 18 11:48:58 2014 From: kyrab at mail.ru (kyra) Date: Tue, 18 Mar 2014 15:48:58 +0400 Subject: [Haskell-cafe] linking warnings when using regex-posix package in GHCi 7.8.1 RC2 In-Reply-To: <1395139998.35417.YahooMailNeo@web171902.mail.ir2.yahoo.com> References: <1395139998.35417.YahooMailNeo@web171902.mail.ir2.yahoo.com> Message-ID: <532832AA.1070008@mail.ru> See more on this here: https://ghc.haskell.org/trac/ghc/ticket/2283, https://ghc.haskell.org/trac/ghc/ticket/7097. I'm the author of this. Unfortunately, this is broken in 7.8rc2. References are resolved correctly, and it is possible to load all modules (which was impossible before), but if any foreign code use them it segfaults. I've put a patch that fixes things here: https://ghc.haskell.org/trac/ghc/attachment/ticket/2283/indirect_link_windows.patch. Hope it will be committed and merged to 7.8 soon. Cheers, Kyra On 3/18/2014 14:53, Rouan van Dalen wrote: > Hi Cafe, > > I have the following program: > > ========================= > > module Main where > > import Text.Regex.Posix > > main = do > putStrLn "!!!" > > ========================= > > When I run the main function from within GHCi, I get the following > output from GHCi: > > ========================= > > Loading package array-0.5.0.0 ... linking ... done. > Loading package deepseq-1.3.0.2 ... linking ... done. > Loading package containers-0.5.4.0 ... linking ... done. > Loading package bytestring-0.10.4.0 ... linking ... done. > Loading package transformers-0.3.0.0 ... linking ... done. > Loading package mtl-2.1.2 ... linking ... done. > Loading package regex-base-0.93.2 ... linking ... done. > Loading package regex-posix-0.95.2 ... linking ... > : warning: isupper from msvcrt is linked instead of > __imp_isupper > : warning: toupper from msvcrt is linked instead of > __imp_toupper > : warning: tolower from msvcrt is linked instead of > __imp_tolower > : warning: isalpha from msvcrt is linked instead of > __imp_isalpha > : warning: isalpha from msvcrt is linked instead of > __imp_isalpha > : warning: isalpha from msvcrt is linked instead of > __imp_isalpha > : warning: iscntrl from msvcrt is linked instead of > __imp_iscntrl > : warning: isupper from msvcrt is linked instead of > __imp_isupper > : warning: isgraph from msvcrt is linked instead of > __imp_isgraph > : warning: isprint from msvcrt is linked instead of > __imp_isprint > : warning: ispunct from msvcrt is linked instead of > __imp_ispunct > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalpha from msvcrt is linked instead of > __imp_isalpha > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > : warning: isalnum from msvcrt is linked instead of > __imp_isalnum > done. > !!! > *Main> > > ========================= > > Does anyone have an idea why GHCi is even linking against msvcrt? > And is there a way to fix this? > > I am using GHC 7.8.1 RC2 x64 on Windows 8 x64 > > Regards > --Rouan > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From rvdalen at yahoo.co.uk Tue Mar 18 12:15:43 2014 From: rvdalen at yahoo.co.uk (Rouan van Dalen) Date: Tue, 18 Mar 2014 12:15:43 +0000 (GMT) Subject: [Haskell-cafe] linking warnings when using regex-posix Message-ID: <1395144943.68350.YahooMailNeo@web171905.mail.ir2.yahoo.com> Thanks Kyra, I appreciate the feedback. Good to know it is in the process of being fixed. Regards --Rouan -------------- next part -------------- An HTML attachment was scrubbed... URL: From konn.jinro at gmail.com Tue Mar 18 14:15:51 2014 From: konn.jinro at gmail.com (Hiromi ISHII) Date: Tue, 18 Mar 2014 23:15:51 +0900 Subject: [Haskell-cafe] [GSoC] A proposal for GSoC regarding computational algebra In-Reply-To: References: Message-ID: Hello cafe, I'm so happy to know that there are people interetested in my proposal! I really thank carter (in freenode chat), Edward and Dominic in advance. Edward: > I suppose given your library's use of my algebra package and other components under the hood, etc. I'd probably be the most likely mentor. > > I'd be willing to work with you, and likely to fold it in/replace much of the existing algebra machinery, which I confess is woefully under-maintained. Thanks! `algebra` packge provides fine-grained abstraction for algebraic structures (though it does not provide the class for noetherian rings), so I adopted for my purpose. I suppose that the `algebra` is more general purpose library than my `computational-algebra`, which is currently concentrated on computation in polynomial rings or quotient ring. > Usually, proposals to write a new library have a hard time getting accepted to GSOC, but you do already have a decent sized body of work there. Sounds great. Yes, in fact, my proposal is not building new library but to improve (my personal) existing library. Dominic: > I might be. Can you give some use cases? The current applications of my interest are elimination theory and solving multivariate nonlinear equation systems. Here are some example: https://github.com/konn/computational-algebra/blob/master/examples/solve.hs Another example is purely mathematical things: for example, we can calculate ideal operations in polynomial rings and basic operation in quotient ring. There are application also in the area of statistics, robotics and cryptology, but I don't know much about them. > I should point out I do a fair amount of numerical work and this typically involves linear > algebra but from a numerical point of view. That sounds interesting. Linear computations required by F4 and F5 algorithm is purely symbolic ones, but there might be common technique. > I am also quite interested in computational algebraic topology but I suspect you are not > proposing to work on that? Sadly not. I don't know much about *algebraic topology*, but my project can be applied to *algebraic geometry* because some computations in commutative algebra can be done with Groebner basis. -- Hiromi ISHII konn.jinro at gmail.com From davidleothomas at gmail.com Tue Mar 18 16:26:36 2014 From: davidleothomas at gmail.com (David Thomas) Date: Tue, 18 Mar 2014 09:26:36 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information Message-ID: Is there a way to extract this? I'm looking to make it easier for newcomers to my project to get things building across different linux distros. -------------- next part -------------- An HTML attachment was scrubbed... URL: From danburton.email at gmail.com Tue Mar 18 16:36:30 2014 From: danburton.email at gmail.com (Dan Burton) Date: Tue, 18 Mar 2014 09:36:30 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: I have wished for this on multiple occasions. I don't believe such a thing exists as of yet. -- Dan Burton On Tue, Mar 18, 2014 at 9:26 AM, David Thomas wrote: > Is there a way to extract this? I'm looking to make it easier for > newcomers to my project to get things building across different linux > distros. > > _______________________________________________ > 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 davidleothomas at gmail.com Tue Mar 18 17:59:09 2014 From: davidleothomas at gmail.com (David Thomas) Date: Tue, 18 Mar 2014 10:59:09 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: Ok, well, if that's the case I'd like to see about remedying that. Anyone have any thoughts as to how to best go about this? I'm not clear on exactly what info lives where, especially across systems. Entirely manual population would be a (barely) acceptable fallback. On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: > I have wished for this on multiple occasions. I don't believe such a thing > exists as of yet. > > -- Dan Burton > > > On Tue, Mar 18, 2014 at 9:26 AM, David Thomas wrote: > >> Is there a way to extract this? I'm looking to make it easier for >> newcomers to my project to get things building across different linux >> distros. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From daniel.trstenjak at gmail.com Tue Mar 18 17:59:27 2014 From: daniel.trstenjak at gmail.com (Daniel Trstenjak) Date: Tue, 18 Mar 2014 18:59:27 +0100 Subject: [Haskell-cafe] [ANN] cabal-cargs: A command line program for extracting compiler arguments from a cabal file. Message-ID: <20140318175927.GA6445@fly> Hi cafe, for further details please consult 'https://github.com/dan-t/cabal-cargs'. A little teaser, you can use cabal-cargs to make your default, non modified hdevtools aware of the settings in the cabal file and of a present cabal sandbox. Greetings, Daniel From mantkiew at gsd.uwaterloo.ca Tue Mar 18 18:16:32 2014 From: mantkiew at gsd.uwaterloo.ca (Michal Antkiewicz) Date: Tue, 18 Mar 2014 14:16:32 -0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: Certainly NIX is an interesting approach. It already comes with a large base of dependencies, a format for specifying them. NIX can be installed in any Linux distro and serve as an environment for building packages. That might provide a cross-distribution solution to the native dependency problem. See, a nice post by Oliver Charles http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html Michal On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: > Ok, well, if that's the case I'd like to see about remedying that. Anyone > have any thoughts as to how to best go about this? I'm not clear on > exactly what info lives where, especially across systems. Entirely manual > population would be a (barely) acceptable fallback. > > > On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: > >> I have wished for this on multiple occasions. I don't believe such a >> thing exists as of yet. >> >> -- Dan Burton >> >> >> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas wrote: >> >>> Is there a way to extract this? I'm looking to make it easier for >>> newcomers to my project to get things building across different linux >>> distros. >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mantkiew at gsd.uwaterloo.ca Tue Mar 18 18:29:17 2014 From: mantkiew at gsd.uwaterloo.ca (Michal Antkiewicz) Date: Tue, 18 Mar 2014 14:29:17 -0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: This is not an immediate solution but I can imagine listing NIX packages as dependencies inside a cabal file, then NIX would create a sandbox with these dependencies and cabal would build in that sandbox. The advantages are that you're not messing around with the underlying operating system's packages, NIX handles all dependencies transitively, and everything is specified declaratively. Sounds like a nice GSoC project :-) You could also do cross GHC version's builds as GHC itself can be sandboxed. Quite intriguing. Michal On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < mantkiew at gsd.uwaterloo.ca> wrote: > Certainly NIX is an interesting approach. It already comes with a large > base of dependencies, a format for specifying them. NIX can be installed in > any Linux distro and serve as an environment for building packages. That > might provide a cross-distribution solution to the native dependency > problem. > > See, a nice post by Oliver Charles > > http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html > > Michal > > > > On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: > >> Ok, well, if that's the case I'd like to see about remedying that. >> Anyone have any thoughts as to how to best go about this? I'm not clear on >> exactly what info lives where, especially across systems. Entirely manual >> population would be a (barely) acceptable fallback. >> >> >> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: >> >>> I have wished for this on multiple occasions. I don't believe such a >>> thing exists as of yet. >>> >>> -- Dan Burton >>> >>> >>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas wrote: >>> >>>> Is there a way to extract this? I'm looking to make it easier for >>>> newcomers to my project to get things building across different linux >>>> distros. >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>>> >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From davidleothomas at gmail.com Tue Mar 18 18:48:33 2014 From: davidleothomas at gmail.com (David Thomas) Date: Tue, 18 Mar 2014 11:48:33 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: One option that just occurred to me would be to allow passing a script to cabal that could be passed the extra-libraries (if any), and could install if it knew the relevant OS packages (or NIX packages), or abort with a cleaner error message. Actually, wrapping ghc might be sufficient (though not ideal). On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < mantkiew at gsd.uwaterloo.ca> wrote: > This is not an immediate solution but I can imagine listing NIX packages > as dependencies inside a cabal file, then NIX would create a sandbox with > these dependencies and cabal would build in that sandbox. The advantages > are that you're not messing around with the underlying operating system's > packages, NIX handles all dependencies transitively, and everything is > specified declaratively. Sounds like a nice GSoC project :-) You could > also do cross GHC version's builds as GHC itself can be sandboxed. Quite > intriguing. > > Michal > > > > On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < > mantkiew at gsd.uwaterloo.ca> wrote: > >> Certainly NIX is an interesting approach. It already comes with a large >> base of dependencies, a format for specifying them. NIX can be installed in >> any Linux distro and serve as an environment for building packages. That >> might provide a cross-distribution solution to the native dependency >> problem. >> >> See, a nice post by Oliver Charles >> >> http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html >> >> Michal >> >> >> >> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: >> >>> Ok, well, if that's the case I'd like to see about remedying that. >>> Anyone have any thoughts as to how to best go about this? I'm not clear on >>> exactly what info lives where, especially across systems. Entirely manual >>> population would be a (barely) acceptable fallback. >>> >>> >>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: >>> >>>> I have wished for this on multiple occasions. I don't believe such a >>>> thing exists as of yet. >>>> >>>> -- Dan Burton >>>> >>>> >>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas >>> > wrote: >>>> >>>>> Is there a way to extract this? I'm looking to make it easier for >>>>> newcomers to my project to get things building across different linux >>>>> distros. >>>>> >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> Haskell-Cafe at haskell.org >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>>> >>>>> >>>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> >> >> > > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tdammers at gmail.com Tue Mar 18 20:47:19 2014 From: tdammers at gmail.com (Tobias Dammers) Date: Tue, 18 Mar 2014 21:47:19 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: <20140318204718.GB6873@yemaya> Hmm, but then, not all package managers/repositories use the same names for packages. So even if there were a way to extract the required libraries from cabal, feeding that information to the package manager isn't going to be trivial at all. (And frankly, looking at build systems for other languages, I've never seen anything that does this - even autotools doesn't really do a lot more than check whether a library is available). That said, even if we could just get a list of required libraries out of cabal, in a somewhat human and machine readable format, that would be a huge win in itself. On Tue, Mar 18, 2014 at 11:48:33AM -0700, David Thomas wrote: > One option that just occurred to me would be to allow passing a script to > cabal that could be passed the extra-libraries (if any), and could install > if it knew the relevant OS packages (or NIX packages), or abort with a > cleaner error message. > > Actually, wrapping ghc might be sufficient (though not ideal). > > > > On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < > mantkiew at gsd.uwaterloo.ca> wrote: > > > This is not an immediate solution but I can imagine listing NIX packages > > as dependencies inside a cabal file, then NIX would create a sandbox with > > these dependencies and cabal would build in that sandbox. The advantages > > are that you're not messing around with the underlying operating system's > > packages, NIX handles all dependencies transitively, and everything is > > specified declaratively. Sounds like a nice GSoC project :-) You could > > also do cross GHC version's builds as GHC itself can be sandboxed. Quite > > intriguing. > > > > Michal > > > > > > > > On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < > > mantkiew at gsd.uwaterloo.ca> wrote: > > > >> Certainly NIX is an interesting approach. It already comes with a large > >> base of dependencies, a format for specifying them. NIX can be installed in > >> any Linux distro and serve as an environment for building packages. That > >> might provide a cross-distribution solution to the native dependency > >> problem. > >> > >> See, a nice post by Oliver Charles > >> > >> http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html > >> > >> Michal > >> > >> > >> > >> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: > >> > >>> Ok, well, if that's the case I'd like to see about remedying that. > >>> Anyone have any thoughts as to how to best go about this? I'm not clear on > >>> exactly what info lives where, especially across systems. Entirely manual > >>> population would be a (barely) acceptable fallback. > >>> > >>> > >>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: > >>> > >>>> I have wished for this on multiple occasions. I don't believe such a > >>>> thing exists as of yet. > >>>> > >>>> -- Dan Burton > >>>> > >>>> > >>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas >>>> > wrote: > >>>> > >>>>> Is there a way to extract this? I'm looking to make it easier for > >>>>> newcomers to my project to get things building across different linux > >>>>> distros. > >>>>> > >>>>> _______________________________________________ > >>>>> Haskell-Cafe mailing list > >>>>> Haskell-Cafe at haskell.org > >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >>>>> > >>>>> > >>>> > >>> > >>> _______________________________________________ > >>> Haskell-Cafe mailing list > >>> Haskell-Cafe at haskell.org > >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >>> > >>> > >> > >> > >> > > > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From creswick at gmail.com Tue Mar 18 20:59:51 2014 From: creswick at gmail.com (Rogan Creswick) Date: Tue, 18 Mar 2014 13:59:51 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: On Tue, Mar 18, 2014 at 11:48 AM, David Thomas wrote: > One option that just occurred to me would be to allow passing a script to > cabal that could be passed the extra-libraries (if any), and could install > if it knew the relevant OS packages (or NIX packages), or abort with a > cleaner error message. > > You can do this sort of thing in a custom Setup.hs (using build-type: custom). Depending on the hook you use, you can get access to the cabal file fields there directly. --Rogan > Actually, wrapping ghc might be sufficient (though not ideal). > > > > On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < > mantkiew at gsd.uwaterloo.ca> wrote: > >> This is not an immediate solution but I can imagine listing NIX packages >> as dependencies inside a cabal file, then NIX would create a sandbox with >> these dependencies and cabal would build in that sandbox. The advantages >> are that you're not messing around with the underlying operating system's >> packages, NIX handles all dependencies transitively, and everything is >> specified declaratively. Sounds like a nice GSoC project :-) You could >> also do cross GHC version's builds as GHC itself can be sandboxed. Quite >> intriguing. >> >> Michal >> >> >> >> On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < >> mantkiew at gsd.uwaterloo.ca> wrote: >> >>> Certainly NIX is an interesting approach. It already comes with a large >>> base of dependencies, a format for specifying them. NIX can be installed in >>> any Linux distro and serve as an environment for building packages. That >>> might provide a cross-distribution solution to the native dependency >>> problem. >>> >>> See, a nice post by Oliver Charles >>> >>> >>> http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html >>> >>> Michal >>> >>> >>> >>> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: >>> >>>> Ok, well, if that's the case I'd like to see about remedying that. >>>> Anyone have any thoughts as to how to best go about this? I'm not clear on >>>> exactly what info lives where, especially across systems. Entirely manual >>>> population would be a (barely) acceptable fallback. >>>> >>>> >>>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: >>>> >>>>> I have wished for this on multiple occasions. I don't believe such a >>>>> thing exists as of yet. >>>>> >>>>> -- Dan Burton >>>>> >>>>> >>>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas < >>>>> davidleothomas at gmail.com> wrote: >>>>> >>>>>> Is there a way to extract this? I'm looking to make it easier for >>>>>> newcomers to my project to get things building across different linux >>>>>> distros. >>>>>> >>>>>> _______________________________________________ >>>>>> Haskell-Cafe mailing list >>>>>> Haskell-Cafe at haskell.org >>>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>>>> >>>>>> >>>>> >>>> >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>>> >>> >>> >>> >> >> >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From davidleothomas at gmail.com Tue Mar 18 21:11:03 2014 From: davidleothomas at gmail.com (David Thomas) Date: Tue, 18 Mar 2014 14:11:03 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: Is that cabal file fields for the current project, or cabal file fields for all dependencies? On Tue, Mar 18, 2014 at 1:59 PM, Rogan Creswick wrote: > On Tue, Mar 18, 2014 at 11:48 AM, David Thomas wrote: > >> One option that just occurred to me would be to allow passing a script to >> cabal that could be passed the extra-libraries (if any), and could install >> if it knew the relevant OS packages (or NIX packages), or abort with a >> cleaner error message. >> >> > You can do this sort of thing in a custom Setup.hs (using build-type: > custom). Depending on the hook you use, you can get access to the cabal > file fields there directly. > > --Rogan > > >> Actually, wrapping ghc might be sufficient (though not ideal). >> >> >> >> On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < >> mantkiew at gsd.uwaterloo.ca> wrote: >> >>> This is not an immediate solution but I can imagine listing NIX packages >>> as dependencies inside a cabal file, then NIX would create a sandbox with >>> these dependencies and cabal would build in that sandbox. The advantages >>> are that you're not messing around with the underlying operating system's >>> packages, NIX handles all dependencies transitively, and everything is >>> specified declaratively. Sounds like a nice GSoC project :-) You could >>> also do cross GHC version's builds as GHC itself can be sandboxed. Quite >>> intriguing. >>> >>> Michal >>> >>> >>> >>> On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < >>> mantkiew at gsd.uwaterloo.ca> wrote: >>> >>>> Certainly NIX is an interesting approach. It already comes with a large >>>> base of dependencies, a format for specifying them. NIX can be installed in >>>> any Linux distro and serve as an environment for building packages. That >>>> might provide a cross-distribution solution to the native dependency >>>> problem. >>>> >>>> See, a nice post by Oliver Charles >>>> >>>> >>>> http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html >>>> >>>> Michal >>>> >>>> >>>> >>>> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas >>> > wrote: >>>> >>>>> Ok, well, if that's the case I'd like to see about remedying that. >>>>> Anyone have any thoughts as to how to best go about this? I'm not clear on >>>>> exactly what info lives where, especially across systems. Entirely manual >>>>> population would be a (barely) acceptable fallback. >>>>> >>>>> >>>>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton >>>> > wrote: >>>>> >>>>>> I have wished for this on multiple occasions. I don't believe such a >>>>>> thing exists as of yet. >>>>>> >>>>>> -- Dan Burton >>>>>> >>>>>> >>>>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas < >>>>>> davidleothomas at gmail.com> wrote: >>>>>> >>>>>>> Is there a way to extract this? I'm looking to make it easier for >>>>>>> newcomers to my project to get things building across different linux >>>>>>> distros. >>>>>>> >>>>>>> _______________________________________________ >>>>>>> Haskell-Cafe mailing list >>>>>>> Haskell-Cafe at haskell.org >>>>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>>>>> >>>>>>> >>>>>> >>>>> >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> Haskell-Cafe at haskell.org >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>>> >>>>> >>>> >>>> >>>> >>> >>> >>> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tdammers at gmail.com Tue Mar 18 21:54:49 2014 From: tdammers at gmail.com (Tobias Dammers) Date: Tue, 18 Mar 2014 22:54:49 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: <20140318204718.GB6873@yemaya> Message-ID: <20140318215448.GA31465@yemaya> On Wed, Mar 19, 2014 at 10:15:08AM +1300, Chris Wong wrote: > On Wed, Mar 19, 2014 at 9:47 AM, Tobias Dammers wrote: > > Hmm, but then, not all package managers/repositories use the same names > > for packages. So even if there were a way to extract the required > > libraries from cabal, feeding that information to the package manager > > isn't going to be trivial at all. > > It's not trivial, but I don't think it's difficult. > > For example, Debian Haskell packages all take the form > libghc-NAME-dev. Fedora uses haskell-NAME. Sure, there's a bit of hard > coding involved, but the set of prominent distributions is finite. I think installing *haskell* packages is not the problem; cabal already does a decent job at that. The problem we're facing is that cabal can *only* install haskell packages, but not any of the native libraries they depend on (usually through FFI, but other examples exist, such as the pg_config tool from PostgreSQL). Besides naming convention issues (which could be compensated for with lookup dictionaries; a brute-force solution, sure, but better than nothing), a bigger problem is that sometimes packages don't match 1:1 between distros, so one distro might just provide one monolithic foobar-dev package, while another might split it up into foobar-client-dev and foobar-server-dev, while yet another might provide more than one alternative. TL;DR: I think if we could just get a list of required native packages, we'd be a long way. > > One problem, though, would be versions. I know we often ask for the > latest and greatest packages, which may conflict with what the > distribution supplies. So the benefits may not be as high as they > seem. > > By the way -- has anyone looked into 0install? It hashes things, > similarly to Nix, but also tries to integrate with the existing > package manager. For example, if the user wishes to install GHC 7.6, > but the Debian repositories already supply it, it will invoke apt-get > instead of installing on its own. > > > (And frankly, looking at build systems > > for other languages, I've never seen anything that does this - even > > autotools doesn't really do a lot more than check whether a library is > > available). > > > > That said, even if we could just get a list of required libraries out of > > cabal, in a somewhat human and machine readable format, that would be a > > huge win in itself. > > > > On Tue, Mar 18, 2014 at 11:48:33AM -0700, David Thomas wrote: > >> One option that just occurred to me would be to allow passing a script to > >> cabal that could be passed the extra-libraries (if any), and could install > >> if it knew the relevant OS packages (or NIX packages), or abort with a > >> cleaner error message. > >> > >> Actually, wrapping ghc might be sufficient (though not ideal). > >> > >> > >> > >> On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < > >> mantkiew at gsd.uwaterloo.ca> wrote: > >> > >> > This is not an immediate solution but I can imagine listing NIX packages > >> > as dependencies inside a cabal file, then NIX would create a sandbox with > >> > these dependencies and cabal would build in that sandbox. The advantages > >> > are that you're not messing around with the underlying operating system's > >> > packages, NIX handles all dependencies transitively, and everything is > >> > specified declaratively. Sounds like a nice GSoC project :-) You could > >> > also do cross GHC version's builds as GHC itself can be sandboxed. Quite > >> > intriguing. > >> > > >> > Michal > >> > > >> > > >> > > >> > On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < > >> > mantkiew at gsd.uwaterloo.ca> wrote: > >> > > >> >> Certainly NIX is an interesting approach. It already comes with a large > >> >> base of dependencies, a format for specifying them. NIX can be installed in > >> >> any Linux distro and serve as an environment for building packages. That > >> >> might provide a cross-distribution solution to the native dependency > >> >> problem. > >> >> > >> >> See, a nice post by Oliver Charles > >> >> > >> >> http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html > >> >> > >> >> Michal > >> >> > >> >> > >> >> > >> >> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: > >> >> > >> >>> Ok, well, if that's the case I'd like to see about remedying that. > >> >>> Anyone have any thoughts as to how to best go about this? I'm not clear on > >> >>> exactly what info lives where, especially across systems. Entirely manual > >> >>> population would be a (barely) acceptable fallback. > >> >>> > >> >>> > >> >>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: > >> >>> > >> >>>> I have wished for this on multiple occasions. I don't believe such a > >> >>>> thing exists as of yet. > >> >>>> > >> >>>> -- Dan Burton > >> >>>> > >> >>>> > >> >>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas >> >>>> > wrote: > >> >>>> > >> >>>>> Is there a way to extract this? I'm looking to make it easier for > >> >>>>> newcomers to my project to get things building across different linux > >> >>>>> distros. > >> >>>>> > >> >>>>> _______________________________________________ > >> >>>>> Haskell-Cafe mailing list > >> >>>>> Haskell-Cafe at haskell.org > >> >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> >>>>> > >> >>>>> > >> >>>> > >> >>> > >> >>> _______________________________________________ > >> >>> Haskell-Cafe mailing list > >> >>> Haskell-Cafe at haskell.org > >> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> >>> > >> >>> > >> >> > >> >> > >> >> > >> > > >> > > >> > > > > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe From danburton.email at gmail.com Tue Mar 18 22:02:32 2014 From: danburton.email at gmail.com (Dan Burton) Date: Tue, 18 Mar 2014 15:02:32 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <20140318215448.GA31465@yemaya> References: <20140318204718.GB6873@yemaya> <20140318215448.GA31465@yemaya> Message-ID: I would imagine that the people working on Stackage may have already done some work in this area. https://github.com/fpco/stackage -- Dan Burton On Tue, Mar 18, 2014 at 2:54 PM, Tobias Dammers wrote: > On Wed, Mar 19, 2014 at 10:15:08AM +1300, Chris Wong wrote: > > On Wed, Mar 19, 2014 at 9:47 AM, Tobias Dammers > wrote: > > > Hmm, but then, not all package managers/repositories use the same names > > > for packages. So even if there were a way to extract the required > > > libraries from cabal, feeding that information to the package manager > > > isn't going to be trivial at all. > > > > It's not trivial, but I don't think it's difficult. > > > > For example, Debian Haskell packages all take the form > > libghc-NAME-dev. Fedora uses haskell-NAME. Sure, there's a bit of hard > > coding involved, but the set of prominent distributions is finite. > > I think installing *haskell* packages is not the problem; cabal already > does a decent job at that. The problem we're facing is that cabal can > *only* install haskell packages, but not any of the native libraries > they depend on (usually through FFI, but other examples exist, such as > the pg_config tool from PostgreSQL). > > Besides naming convention issues (which could be compensated for with > lookup dictionaries; a brute-force solution, sure, but better than > nothing), a bigger problem is that sometimes packages don't match 1:1 > between distros, so one distro might just provide one monolithic > foobar-dev package, while another might split it up into > foobar-client-dev and foobar-server-dev, while yet another might provide > more than one alternative. > > TL;DR: I think if we could just get a list of required native packages, > we'd be a long way. > > > > > One problem, though, would be versions. I know we often ask for the > > latest and greatest packages, which may conflict with what the > > distribution supplies. So the benefits may not be as high as they > > seem. > > > > By the way -- has anyone looked into 0install? It hashes things, > > similarly to Nix, but also tries to integrate with the existing > > package manager. For example, if the user wishes to install GHC 7.6, > > but the Debian repositories already supply it, it will invoke apt-get > > instead of installing on its own. > > > > > (And frankly, looking at build systems > > > for other languages, I've never seen anything that does this - even > > > autotools doesn't really do a lot more than check whether a library is > > > available). > > > > > > That said, even if we could just get a list of required libraries out > of > > > cabal, in a somewhat human and machine readable format, that would be a > > > huge win in itself. > > > > > > On Tue, Mar 18, 2014 at 11:48:33AM -0700, David Thomas wrote: > > >> One option that just occurred to me would be to allow passing a > script to > > >> cabal that could be passed the extra-libraries (if any), and could > install > > >> if it knew the relevant OS packages (or NIX packages), or abort with a > > >> cleaner error message. > > >> > > >> Actually, wrapping ghc might be sufficient (though not ideal). > > >> > > >> > > >> > > >> On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < > > >> mantkiew at gsd.uwaterloo.ca> wrote: > > >> > > >> > This is not an immediate solution but I can imagine listing NIX > packages > > >> > as dependencies inside a cabal file, then NIX would create a > sandbox with > > >> > these dependencies and cabal would build in that sandbox. The > advantages > > >> > are that you're not messing around with the underlying operating > system's > > >> > packages, NIX handles all dependencies transitively, and everything > is > > >> > specified declaratively. Sounds like a nice GSoC project :-) You > could > > >> > also do cross GHC version's builds as GHC itself can be sandboxed. > Quite > > >> > intriguing. > > >> > > > >> > Michal > > >> > > > >> > > > >> > > > >> > On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < > > >> > mantkiew at gsd.uwaterloo.ca> wrote: > > >> > > > >> >> Certainly NIX is an interesting approach. It already comes with a > large > > >> >> base of dependencies, a format for specifying them. NIX can be > installed in > > >> >> any Linux distro and serve as an environment for building > packages. That > > >> >> might provide a cross-distribution solution to the native > dependency > > >> >> problem. > > >> >> > > >> >> See, a nice post by Oliver Charles > > >> >> > > >> >> > http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html > > >> >> > > >> >> Michal > > >> >> > > >> >> > > >> >> > > >> >> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas < > davidleothomas at gmail.com>wrote: > > >> >> > > >> >>> Ok, well, if that's the case I'd like to see about remedying that. > > >> >>> Anyone have any thoughts as to how to best go about this? I'm > not clear on > > >> >>> exactly what info lives where, especially across systems. > Entirely manual > > >> >>> population would be a (barely) acceptable fallback. > > >> >>> > > >> >>> > > >> >>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton < > danburton.email at gmail.com>wrote: > > >> >>> > > >> >>>> I have wished for this on multiple occasions. I don't believe > such a > > >> >>>> thing exists as of yet. > > >> >>>> > > >> >>>> -- Dan Burton > > >> >>>> > > >> >>>> > > >> >>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas < > davidleothomas at gmail.com > > >> >>>> > wrote: > > >> >>>> > > >> >>>>> Is there a way to extract this? I'm looking to make it easier > for > > >> >>>>> newcomers to my project to get things building across different > linux > > >> >>>>> distros. > > >> >>>>> > > >> >>>>> _______________________________________________ > > >> >>>>> Haskell-Cafe mailing list > > >> >>>>> Haskell-Cafe at haskell.org > > >> >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe > > >> >>>>> > > >> >>>>> > > >> >>>> > > >> >>> > > >> >>> _______________________________________________ > > >> >>> Haskell-Cafe mailing list > > >> >>> Haskell-Cafe at haskell.org > > >> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > > >> >>> > > >> >>> > > >> >> > > >> >> > > >> >> > > >> > > > >> > > > >> > > > > > > >> _______________________________________________ > > >> Haskell-Cafe mailing list > > >> Haskell-Cafe at haskell.org > > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > _______________________________________________ > 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 lambda.fairy at gmail.com Tue Mar 18 22:14:08 2014 From: lambda.fairy at gmail.com (Chris Wong) Date: Wed, 19 Mar 2014 11:14:08 +1300 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: <53281A2D.6050301@fuuzetsu.co.uk> References: <53281A2D.6050301@fuuzetsu.co.uk> Message-ID: On Tue, Mar 18, 2014 at 11:04 PM, Mateusz Kowalczyk wrote: > Perhaps considering improving your ?why you think you're the best person > for this? because I know there is another student submitting the > proposal about the same topic! Sure thing. I've rewritten that paragraph; it should be better now. Out of curiosity, who's the other student? A cursory search shows nothing. > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From mantkiew at gsd.uwaterloo.ca Tue Mar 18 23:30:25 2014 From: mantkiew at gsd.uwaterloo.ca (mantkiew at gsd.uwaterloo.ca) Date: Tue, 18 Mar 2014 19:30:25 -0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <20140318215448.GA31465@yemaya> References: <20140318204718.GB6873@yemaya> <20140318215448.GA31465@yemaya> Message-ID: <20140318233025.6008979.51580.4913@gsd.uwaterloo.ca> Well, if naming is the problem then you need a cross-distribution package repository. The only one like that across linuxes and MacOS that I know of is NIX packages.? Building inside a NIX sandbox would shield Cabal from the OS packages as distros often come with older versions. Nix will also install all the dependencies transitively, so a cabal package only has to list the direct deps. Re: 0 install - haven't used it but might be an alternative if it is cross-distribution and for mac. Michal ? Original Message ? From: Tobias Dammers Sent: Tuesday, March 18, 2014 5:57 PM To: Chris Wong Cc: haskell-cafe at haskell.org Subject: Re: [Haskell-cafe] Listing native package requirements based on cabal information On Wed, Mar 19, 2014 at 10:15:08AM +1300, Chris Wong wrote: > On Wed, Mar 19, 2014 at 9:47 AM, Tobias Dammers wrote: > > Hmm, but then, not all package managers/repositories use the same names > > for packages. So even if there were a way to extract the required > > libraries from cabal, feeding that information to the package manager > > isn't going to be trivial at all. > > It's not trivial, but I don't think it's difficult. > > For example, Debian Haskell packages all take the form > libghc-NAME-dev. Fedora uses haskell-NAME. Sure, there's a bit of hard > coding involved, but the set of prominent distributions is finite. I think installing *haskell* packages is not the problem; cabal already does a decent job at that. The problem we're facing is that cabal can *only* install haskell packages, but not any of the native libraries they depend on (usually through FFI, but other examples exist, such as the pg_config tool from PostgreSQL). Besides naming convention issues (which could be compensated for with lookup dictionaries; a brute-force solution, sure, but better than nothing), a bigger problem is that sometimes packages don't match 1:1 between distros, so one distro might just provide one monolithic foobar-dev package, while another might split it up into foobar-client-dev and foobar-server-dev, while yet another might provide more than one alternative. TL;DR: I think if we could just get a list of required native packages, we'd be a long way. > > One problem, though, would be versions. I know we often ask for the > latest and greatest packages, which may conflict with what the > distribution supplies. So the benefits may not be as high as they > seem. > > By the way -- has anyone looked into 0install? It hashes things, > similarly to Nix, but also tries to integrate with the existing > package manager. For example, if the user wishes to install GHC 7.6, > but the Debian repositories already supply it, it will invoke apt-get > instead of installing on its own. > > > (And frankly, looking at build systems > > for other languages, I've never seen anything that does this - even > > autotools doesn't really do a lot more than check whether a library is > > available). > > > > That said, even if we could just get a list of required libraries out of > > cabal, in a somewhat human and machine readable format, that would be a > > huge win in itself. > > > > On Tue, Mar 18, 2014 at 11:48:33AM -0700, David Thomas wrote: > >> One option that just occurred to me would be to allow passing a script to > >> cabal that could be passed the extra-libraries (if any), and could install > >> if it knew the relevant OS packages (or NIX packages), or abort with a > >> cleaner error message. > >> > >> Actually, wrapping ghc might be sufficient (though not ideal). > >> > >> > >> > >> On Tue, Mar 18, 2014 at 11:29 AM, Michal Antkiewicz < > >> mantkiew at gsd.uwaterloo.ca> wrote: > >> > >> > This is not an immediate solution but I can imagine listing NIX packages > >> > as dependencies inside a cabal file, then NIX would create a sandbox with > >> > these dependencies and cabal would build in that sandbox. The advantages > >> > are that you're not messing around with the underlying operating system's > >> > packages, NIX handles all dependencies transitively, and everything is > >> > specified declaratively. Sounds like a nice GSoC project :-) You could > >> > also do cross GHC version's builds as GHC itself can be sandboxed. Quite > >> > intriguing. > >> > > >> > Michal > >> > > >> > > >> > > >> > On Tue, Mar 18, 2014 at 2:16 PM, Michal Antkiewicz < > >> > mantkiew at gsd.uwaterloo.ca> wrote: > >> > > >> >> Certainly NIX is an interesting approach. It already comes with a large > >> >> base of dependencies, a format for specifying them. NIX can be installed in > >> >> any Linux distro and serve as an environment for building packages. That > >> >> might provide a cross-distribution solution to the native dependency > >> >> problem. > >> >> > >> >> See, a nice post by Oliver Charles > >> >> > >> >> http://ocharles.org.uk/blog/posts/2014-02-04-how-i-develop-with-nixos.html > >> >> > >> >> Michal > >> >> > >> >> > >> >> > >> >> On Tue, Mar 18, 2014 at 1:59 PM, David Thomas wrote: > >> >> > >> >>> Ok, well, if that's the case I'd like to see about remedying that. > >> >>> Anyone have any thoughts as to how to best go about this? I'm not clear on > >> >>> exactly what info lives where, especially across systems. Entirely manual > >> >>> population would be a (barely) acceptable fallback. > >> >>> > >> >>> > >> >>> On Tue, Mar 18, 2014 at 9:36 AM, Dan Burton wrote: > >> >>> > >> >>>> I have wished for this on multiple occasions. I don't believe such a > >> >>>> thing exists as of yet. > >> >>>> > >> >>>> -- Dan Burton > >> >>>> > >> >>>> > >> >>>> On Tue, Mar 18, 2014 at 9:26 AM, David Thomas >> >>>> > wrote: > >> >>>> > >> >>>>> Is there a way to extract this? I'm looking to make it easier for > >> >>>>> newcomers to my project to get things building across different linux > >> >>>>> distros. > >> >>>>> > >> >>>>> _______________________________________________ > >> >>>>> Haskell-Cafe mailing list > >> >>>>> Haskell-Cafe at haskell.org > >> >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> >>>>> > >> >>>>> > >> >>>> > >> >>> > >> >>> _______________________________________________ > >> >>> Haskell-Cafe mailing list > >> >>> Haskell-Cafe at haskell.org > >> >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> >>> > >> >>> > >> >> > >> >> > >> >> > >> > > >> > > >> > > > > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe From chriswarbo at googlemail.com Tue Mar 18 23:48:13 2014 From: chriswarbo at googlemail.com (Chris Warburton) Date: Tue, 18 Mar 2014 23:48:13 +0000 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <20140318215448.GA31465@yemaya> (Tobias Dammers's message of "Tue, 18 Mar 2014 22:54:49 +0100") References: <20140318204718.GB6873@yemaya> <20140318215448.GA31465@yemaya> Message-ID: <86r45zkr0i.fsf@gmail.com> Tobias Dammers writes: > Besides naming convention issues (which could be compensated for with > lookup dictionaries; a brute-force solution, sure, but better than > nothing), a bigger problem is that sometimes packages don't match 1:1 > between distros, so one distro might just provide one monolithic > foobar-dev package, while another might split it up into > foobar-client-dev and foobar-server-dev, while yet another might provide > more than one alternative. > > TL;DR: I think if we could just get a list of required native packages, > we'd be a long way. Package naming/splitting/etc. is the one reason that working across distros is difficult. RPM/deb/etc. are trivial to convert between and most other incompatibilities have known solutions for working around (eg. look at any standalone app which offers a tar.gz). I've been down this route before, and it inevitably ends up checking individual filenames. Many RPMs depend on filenames rather than other RPMs. PackageKit tries to apply this in a more format-neutral way. It was a few years ago that I last looked, but the "just" is unwarranted since this is *the* difficult problem. Tools like alien and checkinstall can do the rest. Regards, Chris From fuuzetsu at fuuzetsu.co.uk Wed Mar 19 11:20:05 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Wed, 19 Mar 2014 11:20:05 +0000 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: References: <53281A2D.6050301@fuuzetsu.co.uk> Message-ID: <53297D65.6020406@fuuzetsu.co.uk> On 18/03/14 22:14, Chris Wong wrote: > On Tue, Mar 18, 2014 at 11:04 PM, Mateusz Kowalczyk > wrote: >> Perhaps considering improving your ?why you think you're the best person >> for this? because I know there is another student submitting the >> proposal about the same topic! > > Sure thing. I've rewritten that paragraph; it should be better now. > > Out of curiosity, who's the other student? A cursory search shows nothing. > >> -- >> Mateusz K. >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe Mateusz Lenik, he goes by ?mlen? on IRC. I have his proposal but I'm unsure whether I can post it as the gist is marked as private. -- Mateusz K. From mlen at mlen.pl Wed Mar 19 11:35:01 2014 From: mlen at mlen.pl (Mateusz Lenik) Date: Wed, 19 Mar 2014 12:35:01 +0100 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: <53297D65.6020406@fuuzetsu.co.uk> References: <53281A2D.6050301@fuuzetsu.co.uk> <53297D65.6020406@fuuzetsu.co.uk> Message-ID: <20140319113501.GB44891@polaris.local> On Wed, Mar 19, 2014 at 11:20:05AM +0000, Mateusz Kowalczyk wrote: > On 18/03/14 22:14, Chris Wong wrote: > > On Tue, Mar 18, 2014 at 11:04 PM, Mateusz Kowalczyk > > wrote: > >> Perhaps considering improving your ?why you think you're the best person > >> for this? because I know there is another student submitting the > >> proposal about the same topic! > > > > Sure thing. I've rewritten that paragraph; it should be better now. > > > > Out of curiosity, who's the other student? A cursory search shows nothing. > > > >> -- > >> Mateusz K. > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > Mateusz Lenik, he goes by ?mlen? on IRC. I have his proposal but I'm > unsure whether I can post it as the gist is marked as private. Hello everyone, Here's the URL. I mark most of my gists private, as they have no use for most of the people. This proposal is not private in any way. https://gist.github.com/mlen/543c95cac276a57fee39 I already contacted Chris in private to talk about the case. Best, Mateusz > > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 833 bytes Desc: not available URL: From alexander.vershilov at gmail.com Wed Mar 19 12:48:24 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Wed, 19 Mar 2014 16:48:24 +0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: In Gentoo Linux we use a common ebuild format that allowes to add native dependencies to packages. To create a ebuild from cabal file we use tool called hackport [1]. This approach allow to bump dependencies when some authors are to lazy to bump them themselves, even in presence of pull requests, and add compatibility patches. Also it's possible to create a desktop-icons, additional files, filter test/bench programs that should not be installed into system. Also it supports a dependency on package flags and profiling. However this approach doesn't scale on other distros in a easy way, one possibility is to create static packages using emerge, but this area require some more research. [1] http://hackage.haskell.org/package/hackport -- Alexander On 18 March 2014 20:26, David Thomas wrote: > Is there a way to extract this? I'm looking to make it easier for > newcomers to my project to get things building across different linux > distros. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Alexander -------------- next part -------------- An HTML attachment was scrubbed... URL: From davidleothomas at gmail.com Wed Mar 19 14:42:18 2014 From: davidleothomas at gmail.com (David Thomas) Date: Wed, 19 Mar 2014 07:42:18 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: Yeah, it seems that there are a number of potentially good options that are going to vary by distro and situation, which is why I've been thinking "hook to run arbitrary script". Sufficiently populating the lookup table for that script for any given (Project, Distro) shouldn't be hard, and collecting those we should be able to quickly 1) round the rough edges off of the more common cases without requiring too much manual intervention, and 2) have a reasonable path for the less common cases. On Wed, Mar 19, 2014 at 5:48 AM, Alexander V Vershilov < alexander.vershilov at gmail.com> wrote: > In Gentoo Linux we use a common ebuild format that allowes to add native > dependencies to packages. > To create a ebuild from cabal file we use tool called hackport [1]. > > This approach allow to bump dependencies when some authors are to lazy to > bump them themselves, > even in presence of pull requests, and add compatibility patches. Also > it's possible to create a desktop-icons, > additional files, filter test/bench programs that should not be installed > into system. Also it supports a dependency > on package flags and profiling. > > However this approach doesn't scale on other distros in a easy way, one > possibility is to create static > packages using emerge, but this area require some more research. > > [1] http://hackage.haskell.org/package/hackport > > -- > Alexander > > > On 18 March 2014 20:26, David Thomas wrote: > >> Is there a way to extract this? I'm looking to make it easier for >> newcomers to my project to get things building across different linux >> distros. >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > > -- > Alexander > -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander.vershilov at gmail.com Wed Mar 19 16:02:08 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Wed, 19 Mar 2014 20:02:08 +0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: References: Message-ID: I personally not sure about the one right solution, as there are a plenty of different approaches and rules that are applied system wide, and heavily depend on the underlying package system. Of cause implementation of the new nice features like running arbitrary script, but I personally don't know of many good examples that can make life much easier without introducing additional problems. I'll try to follow up this thread and ready to share our experience and solutions. -- Alexander On 19 March 2014 18:42, David Thomas wrote: > Yeah, it seems that there are a number of potentially good options that > are going to vary by distro and situation, which is why I've been thinking > "hook to run arbitrary script". Sufficiently populating the lookup table > for that script for any given (Project, Distro) shouldn't be hard, and > collecting those we should be able to quickly 1) round the rough edges off > of the more common cases without requiring too much manual intervention, > and 2) have a reasonable path for the less common cases. > > > On Wed, Mar 19, 2014 at 5:48 AM, Alexander V Vershilov < > alexander.vershilov at gmail.com> wrote: > >> In Gentoo Linux we use a common ebuild format that allowes to add native >> dependencies to packages. >> To create a ebuild from cabal file we use tool called hackport [1]. >> >> This approach allow to bump dependencies when some authors are to lazy to >> bump them themselves, >> even in presence of pull requests, and add compatibility patches. Also >> it's possible to create a desktop-icons, >> additional files, filter test/bench programs that should not be installed >> into system. Also it supports a dependency >> on package flags and profiling. >> >> However this approach doesn't scale on other distros in a easy way, one >> possibility is to create static >> packages using emerge, but this area require some more research. >> >> [1] http://hackage.haskell.org/package/hackport >> >> -- >> Alexander >> >> >> On 18 March 2014 20:26, David Thomas wrote: >> >>> Is there a way to extract this? I'm looking to make it easier for >>> newcomers to my project to get things building across different linux >>> distros. >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> >> >> -- >> Alexander >> > > -- Alexander -------------- next part -------------- An HTML attachment was scrubbed... URL: From simons at cryp.to Wed Mar 19 16:09:44 2014 From: simons at cryp.to (Peter Simons) Date: Wed, 19 Mar 2014 17:09:44 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information References: Message-ID: <87vbvadvav.fsf@write-only.cryp.to> Hi David, > Is there a way to extract this? I'm looking to make it easier for > newcomers to my project to get things building across different linux > distros. what exactly do you mean when by "package requirements"? Cabal descriptions list the required 3rd party libraries, header files, and pkgconfig snippets, so there is a lot of information readily available. What is missing in your opinion? Take care, Peter From gale at sefer.org Wed Mar 19 16:15:33 2014 From: gale at sefer.org (Yitzchak Gale) Date: Wed, 19 Mar 2014 18:15:33 +0200 Subject: [Haskell-cafe] ANN: timezone-olson V0.1.4 Message-ID: Version 0.1.4 of timezone-olson has been released on Hackage. This version adds support for version 3 olson timezone files, which are now beginning to appear in the wild. Thanks to Renzo Carbonara and Oliver Charles for providing this update. The timezone-olson package provides a parser and renderer for binary Olson timezone files whose format is specified by the tzfile(5) man page on Unix-like systems. For more information about this format, see: http://www.twinsun.com/tz/tz-link.htm Functions are provided for converting the parsed data into 'TimeZoneSeries' objects from the timezone-series package [1]. On many platforms, binary Olson timezone files suitable for use with this package are available in the directory /usr/share/zoneinfo and its subdirectories on your computer. Hackage: http://hackage.haskell.org/package/timezone-olson Home page: http://projects.haskell.org/time-ng/ Note that support for tzfile versions 2 and 3 is not complete. We parse all of the explicit clock transitions, but we do not yet support the textual POSIX-style time zone specifications that can be included; currently, those only affect clock transitions that are predicted to occur far in the future. We also do not yet support parsing the leap second tables that are now provided in olson files; see the function Data.Time.Clock.TAI.parseTAIUTCDATFile in Ashely Yakeley's time library [2] for an alternative. Regards, Yitz [1] http://hackage.haskell.org/package/timezone-series [2] http://hackage.haskell.org/package/time From alexander.vershilov at gmail.com Wed Mar 19 16:47:11 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Wed, 19 Mar 2014 20:47:11 +0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <87vbvadvav.fsf@write-only.cryp.to> References: <87vbvadvav.fsf@write-only.cryp.to> Message-ID: Some packages require existing executables, e.g. git-annex require lsof. There were some more examples of packages that doesn't have pkg-config but require additional programs to be installed. -- Alexander. On 19 March 2014 20:09, Peter Simons wrote: > Hi David, > > > Is there a way to extract this? I'm looking to make it easier for > > newcomers to my project to get things building across different linux > > distros. > > what exactly do you mean when by "package requirements"? > > Cabal descriptions list the required 3rd party libraries, header files, > and pkgconfig snippets, so there is a lot of information readily > available. > > What is missing in your opinion? > > Take care, > Peter > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Alexander -------------- next part -------------- An HTML attachment was scrubbed... URL: From davidleothomas at gmail.com Wed Mar 19 16:56:01 2014 From: davidleothomas at gmail.com (David Thomas) Date: Wed, 19 Mar 2014 09:56:01 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <87vbvadvav.fsf@write-only.cryp.to> References: <87vbvadvav.fsf@write-only.cryp.to> Message-ID: Well, the most important thing is to make sure people can successfully build things. Next most important is to minimize the manual intervention required (and the degree to which that manual intervention is spread out through time). Getting all the necessary 3rd party libraries *for this package and all dependencies* is a good start. Including, somehow, required utilities would also be worthwhile. Being able to automate all of that, appropriate to distro and project, would be optimal (but potentially more work than it's worth, depending). On Wed, Mar 19, 2014 at 9:09 AM, Peter Simons wrote: > Hi David, > > > Is there a way to extract this? I'm looking to make it easier for > > newcomers to my project to get things building across different linux > > distros. > > what exactly do you mean when by "package requirements"? > > Cabal descriptions list the required 3rd party libraries, header files, > and pkgconfig snippets, so there is a lot of information readily > available. > > What is missing in your opinion? > > Take care, > Peter > > _______________________________________________ > 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 simons at cryp.to Wed Mar 19 17:24:59 2014 From: simons at cryp.to (Peter Simons) Date: Wed, 19 Mar 2014 18:24:59 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information References: <87vbvadvav.fsf@write-only.cryp.to> Message-ID: <87r45y85jo.fsf@write-only.cryp.to> Hi Alexander, > Some packages require existing executables, e.g. git-annex require > lsof. There were some more examples of packages that doesn't have > pkg-config but require additional programs to be installed. if the package requires system resources that the Cabal file doesn't declare, then this is a bug in the Cabal file, no? Take care, Peter From alexander.vershilov at gmail.com Wed Mar 19 17:38:08 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Wed, 19 Mar 2014 21:38:08 +0400 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <87r45y85jo.fsf@write-only.cryp.to> References: <87vbvadvav.fsf@write-only.cryp.to> <87r45y85jo.fsf@write-only.cryp.to> Message-ID: Such requirement (dependency on executable) can't be covered by the cabal file (at least with 'simple' build type). It's possible to write custom setup.hs or use autotools to check such types of dependency. AFAIK there were other examples of dependencies, that can't be covered by existing approaches, but I can't show them from the scratch. -- Alexander On 19 March 2014 21:24, Peter Simons wrote: > Hi Alexander, > > > Some packages require existing executables, e.g. git-annex require > > lsof. There were some more examples of packages that doesn't have > > pkg-config but require additional programs to be installed. > > if the package requires system resources that the Cabal file doesn't > declare, then this is a bug in the Cabal file, no? > > Take care, > Peter > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Alexander -------------- next part -------------- An HTML attachment was scrubbed... URL: From simons at cryp.to Wed Mar 19 17:49:17 2014 From: simons at cryp.to (Peter Simons) Date: Wed, 19 Mar 2014 18:49:17 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information References: <87vbvadvav.fsf@write-only.cryp.to> Message-ID: <87k3bq84f6.fsf@write-only.cryp.to> Hi David, >> what exactly do you mean when by "package requirements"? > > Well, the most important thing is to make sure people can > successfully build things. Next most important is to minimize the > manual intervention required (and the degree to which that manual > intervention is spread out through time). I am sorry, but I still don't understand what exactly you mean. Could you please give a specific example of what exactly it is that you want? Let's use the package "attoparsec" as an example. Could you please write down the information you consider "package requirements" for that package? Take care, Peter From simons at cryp.to Wed Mar 19 17:55:14 2014 From: simons at cryp.to (Peter Simons) Date: Wed, 19 Mar 2014 18:55:14 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information References: <87vbvadvav.fsf@write-only.cryp.to> <87r45y85jo.fsf@write-only.cryp.to> Message-ID: <87bnx28459.fsf@write-only.cryp.to> Hi Alexander, > Such requirement (dependency on executable) can't be covered by the > cabal file (at least with 'simple' build type). it's true that Cabal lacks a field specifically for such run-time dependencies, but in the absence of such a stanza using "build-tools" is a good workaround. The build process can then determine the complete path of, say, lsof and bake it into the binary. It's a work-around, though, abusing build-tools in this way is far from ideal. Take care, Peter From davidleothomas at gmail.com Wed Mar 19 18:05:41 2014 From: davidleothomas at gmail.com (David Thomas) Date: Wed, 19 Mar 2014 11:05:41 -0700 Subject: [Haskell-cafe] Listing native package requirements based on cabal information In-Reply-To: <87k3bq84f6.fsf@write-only.cryp.to> References: <87vbvadvav.fsf@write-only.cryp.to> <87k3bq84f6.fsf@write-only.cryp.to> Message-ID: I don't think attoparsec or any of its dependencies have any native requirements, and some poking around seems to support this, although I don't have any easy way of telling for certain (which is part of what I'm looking for). On the other hand, something like postgresql-libpq clearly depends on the libpq C library (and possibly other things) as listed in the Extra-Libraries field in its cabal file, *as do anything that require postgresql-libpq* which fact does *not* directly show up in their cabal file. Walking the tree and pulling that info is a possibility, but it needs to be done after dependency-resolution in case requirements change version to version. On Wed, Mar 19, 2014 at 10:49 AM, Peter Simons wrote: > Hi David, > > >> what exactly do you mean when by "package requirements"? > > > > Well, the most important thing is to make sure people can > > successfully build things. Next most important is to minimize the > > manual intervention required (and the degree to which that manual > > intervention is spread out through time). > > I am sorry, but I still don't understand what exactly you mean. Could > you please give a specific example of what exactly it is that you want? > Let's use the package "attoparsec" as an example. Could you please write > down the information you consider "package requirements" for that > package? > > Take care, > Peter > > _______________________________________________ > 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 andres at well-typed.com Thu Mar 20 07:39:12 2014 From: andres at well-typed.com (=?ISO-8859-1?Q?Andres_L=F6h?=) Date: Thu, 20 Mar 2014 08:39:12 +0100 Subject: [Haskell-cafe] Well-Typed Haskell courses now include a "Type System" course Message-ID: Hi Haskell-Cafe. As you might already know, Well-Typed LLP are offering regular (commercial) Haskell courses in collaboration with Skills Matter in London for about 1.5 years now. The next courses will take place in the week from April 28 to May 2, 2014, and will for the first time include an all-new 1-day course on all the magic you can do with Haskell's (or more precisely GHC's) type system (taught by me, if that makes a difference). I hope this might be interesting to some on this list, and would certainly like to see many of you there. There's more info available here: http://www.well-typed.com/blog/88/ Here are direct links to the Skills Matter pages for each course. If you'd like to register, go to these: https://skillsmatter.com/courses/504-well-typed-s-guide-to-the-haskell-type-system https://skillsmatter.com/courses/464-well-typed-fast-track-to-haskell https://skillsmatter.com/courses/465-well-typed-advanced-haskell Cheers, Andres -- Andres L?h, Haskell Consultant Well-Typed LLP, http://www.well-typed.com From lambda.fairy at gmail.com Thu Mar 20 09:10:14 2014 From: lambda.fairy at gmail.com (Chris Wong) Date: Thu, 20 Mar 2014 22:10:14 +1300 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: <20140319113501.GB44891@polaris.local> References: <53281A2D.6050301@fuuzetsu.co.uk> <53297D65.6020406@fuuzetsu.co.uk> <20140319113501.GB44891@polaris.local> Message-ID: On Thu, Mar 20, 2014 at 12:35 AM, Mateusz Lenik wrote: > On Wed, Mar 19, 2014 at 11:20:05AM +0000, Mateusz Kowalczyk wrote: >> On 18/03/14 22:14, Chris Wong wrote: >> > On Tue, Mar 18, 2014 at 11:04 PM, Mateusz Kowalczyk >> > wrote: >> >> Perhaps considering improving your ?why you think you're the best person >> >> for this? because I know there is another student submitting the >> >> proposal about the same topic! >> > >> > Sure thing. I've rewritten that paragraph; it should be better now. >> > >> > Out of curiosity, who's the other student? A cursory search shows nothing. >> > >> >> -- >> >> Mateusz K. >> >> _______________________________________________ >> >> Haskell-Cafe mailing list >> >> Haskell-Cafe at haskell.org >> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> Mateusz Lenik, he goes by ?mlen? on IRC. I have his proposal but I'm >> unsure whether I can post it as the gist is marked as private. > > Hello everyone, > > Here's the URL. I mark most of my gists private, as they have no use for most > of the people. This proposal is not private in any way. > https://gist.github.com/mlen/543c95cac276a57fee39 Thanks for sharing. Since your proposal is quite comprehensive, I've opted to change mine instead. I'm going to focus on the UI -- hopefully that doesn't overlap with (what seems to be) backend work. Chris From vlatko.basic at gmail.com Thu Mar 20 09:12:52 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 20 Mar 2014 10:12:52 +0100 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: References: Message-ID: <532AB114.7020804@gmail.com> Hello Cafe, JuicyFruite library has two functions for creating images. One is pure "generateImage", and another monadic "withImage". I run some speed tests, and got the following results in microsecs: generateImage = 1.0 us withImage = 1501241.1 us This is the code for both functions, and the full code is at [1]. generateImage :: forall a. (Pixel a) => (Int -> Int -> a) -- ^ Generating function, with `x` and `y` params. -> Int -- ^ Width in pixels -> Int -- ^ Height in pixels -> Image a generateImage f w h = Image { imageWidth = w, imageHeight = h, imageData = generated } where compCount = componentCount (undefined :: a) generated = runST $ do arr <- M.new (w * h * compCount) let lineGenerator _ y | y >= h = return () lineGenerator lineIdx y = column lineIdx 0 where column idx x | x >= w = lineGenerator idx $ y + 1 column idx x = do unsafeWritePixel arr idx $ f x y column (idx + compCount) $ x + 1 lineGenerator 0 0 V.unsafeFreeze arr withImage :: forall m pixel. (Pixel pixel, PrimMonad m) => Int -- ^ Image width -> Int -- ^ Image height -> (Int -> Int -> m pixel) -- ^ Generating functions -> m (Image pixel) withImage width height pixelGenerator = do let pixelComponentCount = componentCount (undefined :: pixel) arr <- M.new (width * height * pixelComponentCount) let mutImage = MutableImage { mutableImageWidth = width , mutableImageHeight = height , mutableImageData = arr } let pixelPositions = [(x, y) | y <- [0 .. height-1], x <- [0..width-1]] sequence_ [pixelGenerator x y >>= unsafeWritePixel arr idx | ((x,y), idx) <- zip pixelPositions [0, pixelComponentCount ..]] unsafeFreezeImage mutImage The measurement times are for functions alone, without loading etc. The tests were done with same image(s) and same generating function in the same "main", one after another and in both orders, so laziness shouldn't be an issue. I'm looking at the code, but can't explain to myself why is the monadic one so, so much slower. One function is recursive and another uses sequence, but beside that they look quite similar. Can someone explain where does such large difference comes from? [1] http://hackage.haskell.org/package/JuicyPixels-3.1.4.1/docs/src/Codec-Picture-Types.html#withImage Best regards, vlatko From fuuzetsu at fuuzetsu.co.uk Thu Mar 20 10:26:14 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Thu, 20 Mar 2014 10:26:14 +0000 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: References: <53281A2D.6050301@fuuzetsu.co.uk> <53297D65.6020406@fuuzetsu.co.uk> <20140319113501.GB44891@polaris.local> Message-ID: <532AC246.3040204@fuuzetsu.co.uk> On 20/03/14 09:10, Chris Wong wrote: > On Thu, Mar 20, 2014 at 12:35 AM, Mateusz Lenik wrote: >> On Wed, Mar 19, 2014 at 11:20:05AM +0000, Mateusz Kowalczyk wrote: >>> On 18/03/14 22:14, Chris Wong wrote: >>>> On Tue, Mar 18, 2014 at 11:04 PM, Mateusz Kowalczyk >>>> wrote: >>>>> Perhaps considering improving your ?why you think you're the best person >>>>> for this? because I know there is another student submitting the >>>>> proposal about the same topic! >>>> >>>> Sure thing. I've rewritten that paragraph; it should be better now. >>>> >>>> Out of curiosity, who's the other student? A cursory search shows nothing. >>>> >>>>> -- >>>>> Mateusz K. >>>>> _______________________________________________ >>>>> Haskell-Cafe mailing list >>>>> Haskell-Cafe at haskell.org >>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> Mateusz Lenik, he goes by ?mlen? on IRC. I have his proposal but I'm >>> unsure whether I can post it as the gist is marked as private. >> >> Hello everyone, >> >> Here's the URL. I mark most of my gists private, as they have no use for most >> of the people. This proposal is not private in any way. >> https://gist.github.com/mlen/543c95cac276a57fee39 > > Thanks for sharing. Since your proposal is quite comprehensive, I've > opted to change mine instead. > > I'm going to focus on the UI -- hopefully that doesn't overlap with > (what seems to be) backend work. > > Chris > I've read your new proposal and I think you'll definitely need more solid specification on what you aim to do. An example is that you state 3 things for the ?rewrite the homepage? aim but the goals are ?rewrite/reword something, move an advertisement, add some links?. While these are perfectly fine goals, they do not fit your timescale at all! Just this aim alone you schedule for nearly a month! It sounds that it could be done in a day instead. By the way, I don't think that moving the advertisement is such a high priority that it needs to go into a proposal: if they're funding Hackage and want their ad on the front page, I don't see the problem. Existing Haskellers will rarely look at the front page and new ones will probably see it a few times. I doubt anyone would click on the About without a good reason to. If you have more things in mind then you should definitely write them down. Your specification of the search work is very lacking too. You don't say what's wrong with current search and how you aim to improve it. I believe Duncan Coutts was working on better search results by using better heuristics. I don't know the details but it's almost certainly worthwhile to contact him about it. Here are two things that I think need attention interface-wise. Note that even with these, you'll probably need to state more stuff: * Better report presentation: at the moment we (sometimes) can get a report log from Hackage about the build status of a package. At the moment one has to manually change the URL to then get to dumped ?Show? instance of a Cabal data type. Buttons should be added and the report should be presented in a much nicer way. Maybe even we could have a small indicator whether the build worked or not on Hackage. * Hackage exposes an API that lets us work with it. You can see it at [1]. While it's nice to have, there's functionality there that's only available through the API itself when it really should also be available through friendlier means on the site itself. A big thing that comes to my mind is the documentation uploads. If you search around the web, you'll see that uploading own documentation for a package is quite a mysterious process. It'd be much easier if we had a button which will take us to an upload page which also contains instructions for properly generating the documentation. Implementing a documentation checker (for example to check that cross-package links aren't broken, aren't pointing to local things, checks that index page works, all the common mistakes) could be a side project. Lastly, there are ~90 open bugs on the Hackage issue tracker[2]. Many of those are fairly easy and of pretty great benefit to Hackage users (a.k.a. pretty much everyone). Things like #74[3] could be implemented with relative ease and I feel that if you could propose to close some specific tickets and work on others, your proposal would be much, much stronger. Frankly, I think that moving the ad from the front page is much lower priority than many of the tickets there ;) I actually thing that if one were to concentrate on the tickets themselves and make (some of) the interface work a side goal, nearly all the tickets could be fixed. Of course some tickets are best fixed with interface changes so it's not like that's going on the back-burner. A friendly reminder that there are only about 32 hours to get your proposal in so make sure you don't miss it! Oh, I nearly forgot, did you find a mentor for this new project you're proposing? [1]: http://hackage.haskell.org/api [2]: https://github.com/haskell/hackage-server/issues [3]: https://github.com/haskell/hackage-server/issues/74 -- Mateusz K. From m.berg.10 at aberdeen.ac.uk Thu Mar 20 12:17:58 2014 From: m.berg.10 at aberdeen.ac.uk (Berg, Matias Juho) Date: Thu, 20 Mar 2014 12:17:58 +0000 Subject: [Haskell-cafe] Regular Expression Simplification Message-ID: ?Hi all, I am a final year undergraduate student at a university and I am doing my final honours project on natural language generation from regular expressions. For this to work efficiently I need to simplify the regular expressions before I translate them. It seems that there is some previous work done on this in Haskell but I have only been able to find this code (http://hackage.haskell.org/package/HaLeX-1.1/docs/src/Language-HaLex-RegExp.html?) which does some elementary simplification. Does anyone have any suggestions on where to look for more examples so I can see what kinds of attempts people have used to try and solve this problem? Also if someone has worked on this kind of problem was Kleene algebra a good starting point? Best regards, Matias -------------- next part -------------- An HTML attachment was scrubbed... URL: From joeyadams3.14159 at gmail.com Thu Mar 20 12:35:39 2014 From: joeyadams3.14159 at gmail.com (Joey Adams) Date: Thu, 20 Mar 2014 08:35:39 -0400 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: <532AB114.7020804@gmail.com> References: <532AB114.7020804@gmail.com> Message-ID: withImage creates intermediate lists, which is probably the main bottleneck. Also, is it any faster if you specialize withImage instead of making it generic in the monad, e.g. withImage :: (Pixel pixel) => Int -> Int -> (Int -> Int -> IO Pixel) -> IO (Image pixel) ? On Thu, Mar 20, 2014 at 5:12 AM, Vlatko Basic wrote: > Hello Cafe, > > JuicyFruite library has two functions for creating images. One is pure > "generateImage", and another monadic "withImage". > I run some speed tests, and got the following results in microsecs: > > generateImage = 1.0 us > withImage = 1501241.1 us > > This is the code for both functions, and the full code is at [1]. > > generateImage :: forall a. (Pixel a) > => (Int -> Int -> a) -- ^ Generating function, with `x` and > `y` params. > -> Int -- ^ Width in pixels > -> Int -- ^ Height in pixels > -> Image a > generateImage f w h = Image { imageWidth = w, imageHeight = h, imageData = > generated } > where compCount = componentCount (undefined :: a) > generated = runST $ do > arr <- M.new (w * h * compCount) > let lineGenerator _ y | y >= h = return () > lineGenerator lineIdx y = column lineIdx 0 > where column idx x | x >= w = lineGenerator idx $ y + 1 > column idx x = do > unsafeWritePixel arr idx $ f x y > column (idx + compCount) $ x + 1 > > lineGenerator 0 0 > V.unsafeFreeze arr > > > withImage :: forall m pixel. (Pixel pixel, PrimMonad m) > => Int -- ^ Image width > -> Int -- ^ Image height > -> (Int -> Int -> m pixel) -- ^ Generating functions > -> m (Image pixel) > withImage width height pixelGenerator = do > let pixelComponentCount = componentCount (undefined :: pixel) > arr <- M.new (width * height * pixelComponentCount) > let mutImage = MutableImage > { mutableImageWidth = width > , mutableImageHeight = height > , mutableImageData = arr > } > > let pixelPositions = [(x, y) | y <- [0 .. height-1], x <- [0..width-1]] > sequence_ [pixelGenerator x y >>= unsafeWritePixel arr idx > | ((x,y), idx) <- zip pixelPositions [0, > pixelComponentCount ..]] > unsafeFreezeImage mutImage > > > > The measurement times are for functions alone, without loading etc. > The tests were done with same image(s) and same generating function in the > same "main", one after another and in both orders, so laziness shouldn't be > an issue. > > I'm looking at the code, but can't explain to myself why is the monadic > one so, so much slower. > One function is recursive and another uses sequence, but beside that they > look quite similar. > > Can someone explain where does such large difference comes from? > > > [1] http://hackage.haskell.org/package/JuicyPixels-3.1.4.1/ > docs/src/Codec-Picture-Types.html#withImage > > > Best regards, > > vlatko > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From philip.dexter at gmail.com Thu Mar 20 13:53:50 2014 From: philip.dexter at gmail.com (Philip Dexter) Date: Thu, 20 Mar 2014 09:53:50 -0400 Subject: [Haskell-cafe] Regular Expression Simplification In-Reply-To: References: Message-ID: Doing a quick google search, I found this paper [1]. Also you might try searching for pushdown automata simplification or reduction [1] - https://dl.acm.org/citation.cfm?id=2166677 On Thu, Mar 20, 2014 at 8:17 AM, Berg, Matias Juho wrote: > ?Hi all, > > I am a final year undergraduate student at a university and I am doing > my final honours project on natural language generation from regular > expressions. For this to work efficiently I need to simplify the regular > expressions before I translate them. It seems that there is some previous > work done on this in Haskell but I have only been able to find this code ( > http://hackage.haskell.org/package/HaLeX-1.1/docs/src/Language-HaLex-RegExp.html?) > which does some elementary simplification. > > Does anyone have any suggestions on where to look for more examples so I > can see what kinds of attempts people have used to try and solve this > problem? Also if someone has worked on this kind of problem was Kleene > algebra a good starting point? > > Best regards, > > Matias > > > > _______________________________________________ > 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 alpmestan at gmail.com Thu Mar 20 14:43:17 2014 From: alpmestan at gmail.com (Alp Mestanogullari) Date: Thu, 20 Mar 2014 15:43:17 +0100 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: References: <532AB114.7020804@gmail.com> Message-ID: Could it be because you are calling withImage in IO whereas generateImage coes through ST? A lot of the nice performance numbers of JuicyPixels come from its carefully tailored ST usage, which in turn comes from theefficiency of unboxed mutable vectors (as in the "vector" package). So could you post the benchmark result for a version where you runST on the result of withImage? That should be a fairer comparison. Also, writing a criterion benchmark would help and make sure the functions are run properly without any of the two taking advantage of computations previsouly performed by the other. -------------- next part -------------- An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Thu Mar 20 16:33:53 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 20 Mar 2014 17:33:53 +0100 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: References: <532AB114.7020804@gmail.com> Message-ID: <532B1871.7060809@gmail.com> An HTML attachment was scrubbed... URL: From vlatko.basic at gmail.com Thu Mar 20 16:54:07 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Thu, 20 Mar 2014 17:54:07 +0100 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: References: <532AB114.7020804@gmail.com> Message-ID: <532B1D2F.4090806@gmail.com> An HTML attachment was scrubbed... URL: From martin.drautzburg at web.de Thu Mar 20 17:56:39 2014 From: martin.drautzburg at web.de (martin) Date: Thu, 20 Mar 2014 18:56:39 +0100 Subject: [Haskell-cafe] SQL-like DSL for haskell List of Records Message-ID: <532B2BD7.20101@web.de> Hello all, I am currently prototyping some DB-related ideas in haskell. To make the next step I would have to write some joins. I am happy to work with just Lists of Records. Is there any DSL which relieves me from writing nested loops and all that caboodle? Doesn't have to provide SQL syntax either, just some expressiveness which comes close to basic SQL. Data volume will be miniscule. From haskell at nand.wakku.to Thu Mar 20 18:12:31 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Thu, 20 Mar 2014 19:12:31 +0100 Subject: [Haskell-cafe] SQL-like DSL for haskell List of Records In-Reply-To: <532B2BD7.20101@web.de> References: <532B2BD7.20101@web.de> Message-ID: <20140320191231.GA20677@nanodesu.talocan.mine.nu> On Thu, 20 Mar 2014 18:56:39 +0100, martin wrote: > Hello all, > > I am currently prototyping some DB-related ideas in haskell. To make the next step I would have to write some joins. I > am happy to work with just Lists of Records. > > Is there any DSL which relieves me from writing nested loops and all that caboodle? Doesn't have to provide SQL syntax > either, just some expressiveness which comes close to basic SQL. Data volume will be miniscule. I'm not sure what precisely you're looking for but if you just want to throw around some data in an SQL-like model you can leverage the power of the TransformListComp extension: http://www.haskell.org/ghc/docs/latest/html/users_guide/syntax-extns.html#generalised-list-comprehensions This can be generalized to any monad using MonadComprehensions as well. From agocorona at gmail.com Thu Mar 20 20:37:50 2014 From: agocorona at gmail.com (Alberto G. Corona ) Date: Thu, 20 Mar 2014 21:37:50 +0100 Subject: [Haskell-cafe] GSOC and "scripting the inference process" .Was: Re: Haskell compilation errors break the complexity encapsulation on DSLs In-Reply-To: References: Message-ID: Jurriaan, Thanks for the info. Nice to hear that. But perhaps that project is too long term oriented. I think that we need it as soon as possible. If it is possible an early partial implementation for Haskell 98 that does ignore errors on extensions and only does his analysis restricted to the haskell 98 code, it perhaps would be very helpful both for you to have feedback from the haskell community and for the haskell community to create friendly non intimidating DSLs. Best. 2014-03-17 14:16 GMT+01:00 Jurriaan Hage : > Hello, > > I currently have a PhD student who is working on exactly this topic: > extending the work of our > Scripting the Type Inferencer paper to full Haskell. His name is > Alejandro Serrano Mena. He started last November. > > I believe the complications of being able to deal with type system > extensions currently available and in use in Haskell to be so invasive > that it will > take a few years to get the complete picture (considering type classes > with extensions, > GADTs, type families etc.). > > A Google Summer Of Code for the Haskell 98 subset (ie. implementing that > in GHC) > should be possible, I guess. Whether that implementation later scales to > the full > language may be something of a concern. > > We, ourselves, shall be prototyping the new things in the Utrecht > Haskell Compiler, and the plan was that after Alejandro has finished his > PhD and > given a positive outcome of his work, that something should be arranged to > make > it available to the general Haskell programming audience by implementing > it into GHC. > > best, > Jurriaan > > > > On 17Mar, 2014, at 12:50, Alberto G. Corona wrote: > > > Now that GSOC comes again, I call you into attention one of the biggest > problems that Haskell has to solve before being fully accepted in the IT > industry: The (unnecessary) complexity of the DSL error messages. > > > > There is some work being done: > > > > http://dl.acm.org/citation.cfm?id=944707 > > > > > > The idea was to implement it in GHC after refining and testing it if I > remember well. If some of this work can be carried out in a GSOC project, > IMHO it should be given priority. > > > > In case that this work is not going to be available in the short-medium > term, > > there is a ticket with some suggestions that can be carried out in a > GSOC project, just in case any of you are interested into > mentoring/carrying out this or any other solution to overcome this problem: > > > > http://hackage.haskell.org/trac/ghc/ticket/7870 > > > > > > > > 2013-04-27 22:14 GMT+02:00 Ozgur Akgun : > > Hi, > > > > On 27 April 2013 10:07, Alberto G. Corona wrote: > > I created a ticket for the feature request: > > > > Ticket #7870 > > > > Teachers, newbies and people working in Industry: Please push it! > > > > A link to the ticket may be helpful for the lazy. > > > > http://hackage.haskell.org/trac/ghc/ticket/7870 > > > > I quite like this idea, and I think this is one thing people use TH for > now instead. > > (Using quasi-quotes, you can produce any compilation error you like...) > > It would be great if we didn't have to pull in the full power of TH (or > QQ) for this. > > > > > > Cheers, > > Ozgur > > > > > > > > > > -- > > Alberto. > > -- Alberto. -------------- next part -------------- An HTML attachment was scrubbed... URL: From ok at cs.otago.ac.nz Thu Mar 20 21:41:16 2014 From: ok at cs.otago.ac.nz (Richard A. O'Keefe) Date: Fri, 21 Mar 2014 10:41:16 +1300 Subject: [Haskell-cafe] Regular Expression Simplification In-Reply-To: References: Message-ID: <63B3B763-D669-45F9-AA80-8D40E80CBB62@cs.otago.ac.nz> Perhaps the obvious question is "where do the regular expressions come from"? If they are generated somehow, instead of generating and then simplifying, you might find it useful to try to improve the generation process. I wonder if some of the work on grammar induction might be of use? From haskell at nand.wakku.to Fri Mar 21 05:00:08 2014 From: haskell at nand.wakku.to (Niklas Haas) Date: Fri, 21 Mar 2014 06:00:08 +0100 Subject: [Haskell-cafe] Regular Expression Simplification In-Reply-To: References: Message-ID: <20140321060008.GA22048@nanodesu.talocan.mine.nu> On Thu, 20 Mar 2014 12:17:58 +0000, "Berg, Matias Juho" wrote: > ?Hi all, > > I am a final year undergraduate student at a university and I am doing my final honours project on natural language generation from regular expressions. For this to work efficiently I need to simplify the regular expressions before I translate them. It seems that there is some previous work done on this in Haskell but I have only been able to find this code (http://hackage.haskell.org/package/HaLeX-1.1/docs/src/Language-HaLex-RegExp.html?) which does some elementary simplification. > > Does anyone have any suggestions on where to look for more examples so I can see what kinds of attempts people have used to try and solve this problem? Also if someone has worked on this kind of problem was Kleene algebra a good starting point? > > Best regards, > > Matias My first thought was: Maybe it would be possible to convert the regular expression to something like an NFA, and then use one of the existing known algorithms to generate a minimal NFA from that, and then turn that back into a regular expression somehow? Although I'm slightly worried that the overhead of converting to an NFA is far too great for complicated regular expressions (finite doesn't mean reasonable), and that the conversion from NFA to regular expression will generate very suboptimal regular expressions despite the NFA being minimal. Maybe a similar analog could be used for another type of regular machine? Or a regular grammar, perhaps? Those are also fairly easy to bring into a normalized form and then convert back to a regex. From shachaf at gmail.com Fri Mar 21 08:01:23 2014 From: shachaf at gmail.com (Shachaf Ben-Kiki) Date: Fri, 21 Mar 2014 01:01:23 -0700 Subject: [Haskell-cafe] Last call for Google Summer of Code 2014 applications Message-ID: Haskell.org is participating in Google Summer of Code again this year, and the student application deadline is nigh. Edward Kmett and I are the administrators this year. The deadline is 2014-03-21 at 19:00 UTC (noon PDT), or roughly 11 hours from now, so make sure to get your applications in before then. For a full timeline see . If you have any questions, feel free to ask on IRC (#haskell-gsoc on Freenode), or to contact me or Edward directly! Shachaf From torsten.grust at uni-tuebingen.de Fri Mar 21 08:18:29 2014 From: torsten.grust at uni-tuebingen.de (Torsten Grust) Date: Fri, 21 Mar 2014 09:18:29 +0100 Subject: [Haskell-cafe] SQL-like DSL for haskell List of Records In-Reply-To: <532B2BD7.20101@web.de> References: <532B2BD7.20101@web.de> Message-ID: <094C0BCB-CC25-4EDE-AF61-B84C7502C0FD@uni-tuebingen.de> Hi Martin, On 20 Mar 2014, at 18:56, martin wrote (with possible deletions): > Hello all, > > I am currently prototyping some DB-related ideas in haskell. To make > the next step I would have to write some joins. I > am happy to work with just Lists of Records. > > Is there any DSL which relieves me from writing nested loops and all > that caboodle? Doesn't have to provide SQL syntax > either, just some expressiveness which comes close to basic SQL. Data > volume will be miniscule. the following blog posting [in German, ugh] may be helpful in this context: http://funktionale-programmierung.de/2014/02/19/comprehending-queries.html Cheers, --Torsten -- | Prof. Dr. Torsten Grust | Database Systems ? Universit?t T?bingen (Germany) | torsten.grust at uni-tuebingen.de | db.inf.uni-tuebingen.de -------------- next part -------------- An HTML attachment was scrubbed... URL: From lambda.fairy at gmail.com Fri Mar 21 09:44:08 2014 From: lambda.fairy at gmail.com (Chris Wong) Date: Fri, 21 Mar 2014 22:44:08 +1300 Subject: [Haskell-cafe] RFC: GSoC proposal: Improve the Hackage login system In-Reply-To: <532AC246.3040204@fuuzetsu.co.uk> References: <53281A2D.6050301@fuuzetsu.co.uk> <53297D65.6020406@fuuzetsu.co.uk> <20140319113501.GB44891@polaris.local> <532AC246.3040204@fuuzetsu.co.uk> Message-ID: Wow, thank you for the comprehensive critique! I'll respond to your points individually. On Thu, Mar 20, 2014 at 11:26 PM, Mateusz Kowalczyk wrote: > I've read your new proposal and I think you'll definitely need more > solid specification on what you aim to do. An example is that you state > 3 things for the ?rewrite the homepage? aim but the goals are > ?rewrite/reword something, move an advertisement, add some links?. While > these are perfectly fine goals, they do not fit your timescale at all! > Just this aim alone you schedule for nearly a month! It sounds that it > could be done in a day instead. By the way, I don't think that moving > the advertisement is such a high priority that it needs to go into a > proposal: if they're funding Hackage and want their ad on the front > page, I don't see the problem. Existing Haskellers will rarely look at > the front page and new ones will probably see it a few times. I doubt > anyone would click on the About without a good reason to. Agreed. On looking further into the Hackage issues list, I found there's a lot more to be done. > Your specification of the search work is very lacking too. You don't say > what's wrong with current search and how you aim to improve it. I > believe Duncan Coutts was working on better search results by using > better heuristics. I don't know the details but it's almost certainly > worthwhile to contact him about it. Sure. He seems to be the go-to guy for everything Cabal/Hackage, so I agree it's a good idea to talk to him. > Here are two things that I think need attention interface-wise. Note > that even with these, you'll probably need to state more stuff: > > * Better report presentation: at the moment we (sometimes) can get a > report log from Hackage about the build status of a package. At the > moment one has to manually change the URL to then get to dumped ?Show? > instance of a Cabal data type. Buttons should be added and the report > should be presented in a much nicer way. Maybe even we could have a > small indicator whether the build worked or not on Hackage. > > * Hackage exposes an API that lets us work with it. You can see it at > [1]. While it's nice to have, there's functionality there that's only > available through the API itself when it really should also be available > through friendlier means on the site itself. A big thing that comes to > my mind is the documentation uploads. If you search around the web, > you'll see that uploading own documentation for a package is quite a > mysterious process. It'd be much easier if we had a button which will > take us to an upload page which also contains instructions for properly > generating the documentation. Implementing a documentation checker (for > example to check that cross-package links aren't broken, aren't pointing > to local things, checks that index page works, all the common mistakes) > could be a side project. I admit -- I didn't even know Hackage had either of these before today, when I saw them on your blog ;). Exposing them would be great. > Lastly, there are ~90 open bugs on the Hackage issue tracker[2]. Many of > those are fairly easy and of pretty great benefit to Hackage users > (a.k.a. pretty much everyone). Things like #74[3] could be implemented > with relative ease and I feel that if you could propose to close some > specific tickets and work on others, your proposal would be much, much > stronger. Frankly, I think that moving the ad from the front page is > much lower priority than many of the tickets there ;) I actually thing > that if one were to concentrate on the tickets themselves and make (some > of) the interface work a side goal, nearly all the tickets could be > fixed. Of course some tickets are best fixed with interface changes so > it's not like that's going on the back-burner. Thanks for the suggestion -- the proposal pretty much writes itself now, with each issue mapping to a task in the proposal. > A friendly reminder that there are only about 32 hours to get your > proposal in so make sure you don't miss it! Bring it on. It's Friday here, so I don't need to sleep ;) > Oh, I nearly forgot, did you find a mentor for this new project you're > proposing? Not yet -- but it's not too late to do that, right? I notice the other Mateusz has asked on cabal-devel; I might follow him when I'm more awake. Chris > [1]: http://hackage.haskell.org/api > [2]: https://github.com/haskell/hackage-server/issues > [3]: https://github.com/haskell/hackage-server/issues/74 > -- > Mateusz K. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From vlatko.basic at gmail.com Fri Mar 21 10:10:45 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Fri, 21 Mar 2014 11:10:45 +0100 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: References: <532AB114.7020804@gmail.com> Message-ID: <532C1025.5020907@gmail.com> An HTML attachment was scrubbed... URL: From j.stutterheim at me.com Fri Mar 21 10:16:14 2014 From: j.stutterheim at me.com (J. Stutterheim) Date: Fri, 21 Mar 2014 11:16:14 +0100 Subject: [Haskell-cafe] How to obtain an expression type in a GHC compiler plugin? Message-ID: <83AC875E-9002-4A7A-8251-0B001D590DB9@me.com> Hi all, I'm trying to familiarise myself with writing GHC compiler plugins, but the GHC API is rather overwhelming, hence my question here. During compilation, I'm trying to determine whether a top-level function in my program has a certain type. Initially, if this is the case, I just want to print the function name. For me to do this check, I have to obtain the type for each top-level function. How can I achieve this? I already have a plugin with which I can print the name for a Bind, so I'm mainly interested in knowing how to obtain its type. Cheers, Jurri?n From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Fri Mar 21 10:32:15 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Fri, 21 Mar 2014 10:32:15 +0000 Subject: [Haskell-cafe] SQL-like DSL for haskell List of Records In-Reply-To: <532B2BD7.20101@web.de> References: <532B2BD7.20101@web.de> Message-ID: <20140321103215.GN12779@weber> On Thu, Mar 20, 2014 at 06:56:39PM +0100, martin wrote: - I am currently prototyping some DB-related ideas in haskell. To make the - next step I would have to write some joins. I am happy to work with just - Lists of Records. - - Is there any DSL which relieves me from writing nested loops and all that - caboodle? Doesn't have to provide SQL syntax either, just some - expressiveness which comes close to basic SQL. Data volume will be - miniscule. This email is literate Haskell and also available here http://lpaste.net/4072439216418586624 Torsten and Niklas have suggested using Haskell's list comprehensions for doing relational algebra-like manipulations in Haskell. I'll give you a concrete example along similar lines, except it uses arrows in place of monads. The reason I chose arrows here is that I have a Haskell embedded relational query DSL that compiles to SQL and it seems that due to the limits of expressivity of SQL one must use arrows there. The API I present below is almost a direct translation of my relational query API. What I've written here could be done with monads, of course, but by the same "principle of least power" that tells me not to use 'do' notation and monads where applicatives would suffice, I'll do this in terms of arrows. It will also serve as a neat introduction for anyone who's interested in learning my relational query DSL. > {-# LANGUAGE Arrows #-} > > import Control.Arrow (Kleisli(Kleisli), runKleisli, returnA, arr, first, > (<<<)) We're going to be working with lists of "records". Here the records are just tuples, but you could use Haskell record syntax if you like. The important type is 'a -> [b]' and to make it an arrow we wrap it with 'Kleisli'. Recall that 'Kleisli m a b' is just 'a -> m b'. > type QueryArr = Kleisli [] > type Query = QueryArr () So a 'Query a' is just a (wrapped) '[a]'. 'fromList' is a trivial function that does the conversion and 'display' goes the other way to show the result of queries. > fromList :: [a] -> Query a > fromList = Kleisli . const > > display :: Query String -> IO () > display = mapM_ putStrLn . flip runKleisli () Now let's define a "table" of people > newtype PersonId = PersonId Int deriving Eq > > people :: Query (PersonId, String) > people = (fromList . map (first PersonId)) [ (1, "Tom") > , (2, "Duncan") > , (3, "Simon") ] and a mapping from people to their favourite feature of Haskell. > favouriteFeature :: Query (PersonId, String) > favouriteFeature = (fromList . map (first PersonId)) [ (1, "arrows") > , (2, "cabal") > , (3, "purity") ] We'd like to join 'people' to 'favouriteFeature' by requiring the "person ID" columns to be equal. For that we need two combinators. 'eq' just checks whether two columns are equal > eq :: Eq a => QueryArr (a, a) Bool > eq = Kleisli (\(x, y) -> [x == y]) and 'restrict' restricts the query to the case where its argument is 'True'. > restrict :: QueryArr Bool () > restrict = Kleisli guard > where guard = \cond -> if cond then [()] else [] > -- This is exactly Control.Monad.guard for [] Then we can write joins straightforwardly using arrow notation (which is rather similar to 'do' notation). > favourites :: Query String > favourites = proc () -> do > -- Corresponding to SQL's 'FROM ...' > (pid, name) <- people -< () > (pid', feature) <- favouriteFeature -< () > > -- Corresponding to SQL's 'WHERE ... = ...' > restrict <<< eq -< (pid, pid') > > -- Corresponding to SQL's 'SELECT ...' > returnA -< name ++ "'s favourite feature is " ++ feature ghci> display favourites Tom's favourite feature is arrows Duncan's favourite feature is cabal Simon's favourite feature is purity We can do joins on any conditions of course, not just equality. Here's a greater-than-or-equal-to predicate. > gte :: (Ord a, Eq a) => QueryArr (a, a) Bool > gte = Kleisli (\(x, y) -> [x >= y]) We can use it by comparing a person's skill level to that required to perform certain tasks. A person has this skill level > skillLevel :: Query (PersonId, Int) > skillLevel = (fromList . map (first PersonId)) [ (1, 5) > , (2, 9) > , (3, 10) ] and a role requires this skill level. > roleDifficulties :: Query (Int, String) > roleDifficulties = fromList [ (3, "write foldr") > , (8, "implement stream fusion") > , (10, "be god") ] A person thus has these abilities. > abilities :: Query String > abilities = proc () -> do > (pid, name) <- people -< () > (pid', skill) <- skillLevel -< () > (requiredSkill, role) <- roleDifficulties -< () > > restrict <<< eq -< (pid, pid') > restrict <<< gte -< (skill, requiredSkill) > > returnA -< name ++ " can " ++ role *Main> display abilities Tom can write foldr Duncan can write foldr Duncan can implement stream fusion Simon can write foldr Simon can implement stream fusion Simon can be god So far what we have is a somewhat awkward encoding of what we would have written in SQL. Where Haskell really shines, as usual, is in its power to abstract. I'll show you one of the abstractions now, which is to let queries have inputs as well as ouputs. We can write 'skillLevelOfPerson' which maps a 'PersonId' to that person's skill level. > skillLevelOfPerson :: QueryArr PersonId Int > skillLevelOfPerson = proc pid -> do > (pid', skill) <- skillLevel -< () > restrict <<< eq -< (pid, pid') > returnA -< skill In 'skillLevelOfPerson' the output depends functionally on the input, but in general this needn't hold. 'rolesOfSkillLevel' maps a skill level to the zero or more roles available at that skill level. > rolesOfSkillLevel :: QueryArr Int String > rolesOfSkillLevel = proc skill -> do > (requiredSkill, role) <- roleDifficulties -< () > restrict <<< gte -< (skill, requiredSkill) > returnA -< role The great benefit of abstracting out these two query arrows is that everything becomes much more composable. For example, we can now create a query arrow to map a person to the roles available to them > rolesOfPerson :: QueryArr PersonId String > rolesOfPerson = rolesOfSkillLevel <<< skillLevelOfPerson and use it reimplement 'abilities' > abilities' :: Query String > abilities' = proc () -> do > (pid, name) <- people -< () > role <- rolesOfPerson -< pid > returnA -< name ++ " can " ++ role *Main> display abilities' Tom can write foldr Duncan can write foldr Duncan can implement stream fusion Simon can write foldr Simon can implement stream fusion Simon can be god Once everything is written in this composable way, you may or may not find it more convenient to use arrow combinators directly. > abilities'' :: Query String > abilities'' = arr (\(role, name) -> name ++ " can " ++ role) > <<< first rolesOfPerson > <<< people *Main> display abilities'' Tom can write foldr Duncan can write foldr Duncan can implement stream fusion Simon can write foldr Simon can implement stream fusion Simon can be god Be careful using this implementation: every time you bring another "table" into scope you will do a linear scan over it. Thus the time complexity of running queries is exponential in the number of "tables"! If one wanted, one could use the same API with a much more intelligent query planning engine underneath. As I mentioned above, I have a Haskell relational query EDSL (called Opaleye) which has almost exactly this API and compiles to SQL. If anyone is interested in a type safe, composable relational query API please let me know and I'll discuss how you can get access (whilst in development it is not yet public). You can see the slides from a presentation I gave about it at Netherland FP Day 2014 here: http://staff.science.uva.nl/~grelck/nl-fp-day-2014.html Tom From mail at iagoabal.eu Fri Mar 21 10:33:08 2014 From: mail at iagoabal.eu (Iago Abal) Date: Fri, 21 Mar 2014 11:33:08 +0100 Subject: [Haskell-cafe] PhD position at IT University of Copenhagen Message-ID: The VARIETE project seeks an excellent PhD student to work on analysis methods for code and models found in highly configurable software systems (software product lines), especially in projects that use simple code generators and domain specific models. The objectives are to work on extensions of model checking and static analysis techniques for the verification of software systems implemented using model transformations. The ideal candidate has a solid background in semantics of programming languages and in algorithmic verification techniques (model checking, type checking, static analysis, satisfiability solving), combined with an appreciation for problem solving stemming from practice of software development. The project develops theories as well as tools. Functional programming skills are an advantage (but not essential). VARIETE is a highly prestigious research project awarded by the Danish Independent Research Council, within the Sapere Aude program. Project website: https://variete.wikit.itu.dk/ Positions are based in Copenhagen Denmark within the modern and lively research environment of IT University of Copenhagen (http://www.itu.dk ). The position comes with entry level public servant salary (ca. 2200 EUR per month after taxes are deducted), social benefits (like paid vacation time, health care and pension saving scheme) along with a travel budget and all other support funds required for executing the research project. Prospective starting date is in fall 2014. Duration of the scholarship is 3 or 4 years. Personal contact via email prior to applying is strongly encouraged. Contact: Associate Professor Andrzej W?sowski (wasowski at itu.dk), Postdoc Aleksandar Dimovski (adim at itu.dk) Research Group: Process and System Models < https://pure.itu.dk/portal/en/organisations/process-and-system-models%287804b276-a960-416f-9cb4-d6c141580289%29.html >; Software and Systems Section Deadline for application is April 23 at 23:59 CET. Please see the conditions of the call at https://delta.hr-manager.net/ApplicationInit.aspx?cid=119&ProjectId=168671&departmentId=3439&uiculture=en&MediaId=1282 Iago Abal Rivas -------------- next part -------------- An HTML attachment was scrubbed... URL: From adam at bergmark.nl Fri Mar 21 11:15:54 2014 From: adam at bergmark.nl (Adam Bergmark) Date: Fri, 21 Mar 2014 12:15:54 +0100 Subject: [Haskell-cafe] How to obtain an expression type in a GHC compiler plugin? In-Reply-To: <83AC875E-9002-4A7A-8251-0B001D590DB9@me.com> References: <83AC875E-9002-4A7A-8251-0B001D590DB9@me.com> Message-ID: This might be useful: https://github.com/faylang/fay/issues/269 On Fri, Mar 21, 2014 at 11:16 AM, J. Stutterheim wrote: > Hi all, > > I'm trying to familiarise myself with writing GHC compiler plugins, but > the GHC API is rather overwhelming, hence my question here. > > During compilation, I'm trying to determine whether a top-level function > in my program has a certain type. Initially, if this is the case, I just > want to print the function name. For me to do this check, I have to obtain > the type for each top-level function. How can I achieve this? I already > have a plugin with which I can print the name for a Bind, so I'm mainly > interested in knowing how to obtain its type. > > Cheers, > > Jurri?n > _______________________________________________ > 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 j.stutterheim at me.com Fri Mar 21 11:51:43 2014 From: j.stutterheim at me.com (J. Stutterheim) Date: Fri, 21 Mar 2014 12:51:43 +0100 Subject: [Haskell-cafe] How to obtain an expression type in a GHC compiler plugin? In-Reply-To: References: <83AC875E-9002-4A7A-8251-0B001D590DB9@me.com> Message-ID: <929633BE-17E1-40C4-9E39-DB0372AC6EF7@me.com> Thanks, it contained the hint I needed! The CoreUtils module contains the exprType :: CoreExpr -> Type function, which is exactly what I was looking for. On 21 Mar 2014, at 12:15, Adam Bergmark wrote: > This might be useful: https://github.com/faylang/fay/issues/269 > > > > > On Fri, Mar 21, 2014 at 11:16 AM, J. Stutterheim wrote: > Hi all, > > I'm trying to familiarise myself with writing GHC compiler plugins, but the GHC API is rather overwhelming, hence my question here. > > During compilation, I'm trying to determine whether a top-level function in my program has a certain type. Initially, if this is the case, I just want to print the function name. For me to do this check, I have to obtain the type for each top-level function. How can I achieve this? I already have a plugin with which I can print the name for a Bind, so I'm mainly interested in knowing how to obtain its type. > > Cheers, > > Jurri?n > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From peter.padawitz at udo.edu Fri Mar 21 12:53:22 2014 From: peter.padawitz at udo.edu (Peter Padawitz) Date: Fri, 21 Mar 2014 13:53:22 +0100 Subject: [Haskell-cafe] Regular Expression Simplification In-Reply-To: References: Message-ID: Hi Matias, Kleene algebra involves the equations that are valid in the interpretation of regular expressions as word languages. So, however a simplifier of regular expressions is defined, its input and output should be equivalent w.r.t. those equations. On the web page of my course on compiler construction (http://fldit-www.cs.tu-dortmund.de/ueb.html) you find a link to the Haskell module Compiler.hs, which includes data types, parsers and compilers for regular expressions. Among them is the algebra regNorm, which reduces regular expressions to a kind of additive normal form. Best regards, Peter Am 20.03.2014 um 13:17 schrieb "Berg, Matias Juho" : > ?Hi all, > > I am a final year undergraduate student at a university and I am doing my final honours project on natural language generation from regular expressions. For this to work efficiently I need to simplify the regular expressions before I translate them. It seems that there is some previous work done on this in Haskell but I have only been able to find this code (http://hackage.haskell.org/package/HaLeX-1.1/docs/src/Language-HaLex-RegExp.html?) which does some elementary simplification. > > Does anyone have any suggestions on where to look for more examples so I can see what kinds of attempts people have used to try and solve this problem? Also if someone has worked on this kind of problem was Kleene algebra a good starting point? > > Best regards, > > Matias > > _______________________________________________ > 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 doug at cs.dartmouth.edu Fri Mar 21 15:04:49 2014 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Fri, 21 Mar 2014 11:04:49 -0400 Subject: [Haskell-cafe] Regular Expression Simplification Message-ID: <201403211504.s2LF4nL2019241@stowe.cs.dartmouth.edu> = From doug at cs.dartmouth.edu Fri Mar 21 15:05:08 2014 From: doug at cs.dartmouth.edu (Doug McIlroy) Date: Fri, 21 Mar 2014 11:05:08 -0400 Subject: [Haskell-cafe] Regular Expression Simplification Message-ID: <201403211505.s2LF58Ro019251@stowe.cs.dartmouth.edu> Apropos of regular expression simplification, > My first thought was: Maybe it would be possible to convert the regular expression to something like an NFA, > I'm slightly worried that the overhead of converting to an NFA is far too great for complicated regular expressions "Far too great" is only quadratic in the number of nonterminal symbols (with repetitions counted) in the regular expression. And the result is a particularly nice NFA, with one state for each of those symbols, and no epsilon moves. So I think there's merit in the proposal. See my Functional Pearl, JFP 14 (2004) 503-518, http://www.cs.dartmouth.edu/~doug/pubs.html Doug McIlroy ok at cs.otago.ac.nz From martin.drautzburg at web.de Fri Mar 21 16:06:45 2014 From: martin.drautzburg at web.de (martin) Date: Fri, 21 Mar 2014 17:06:45 +0100 Subject: [Haskell-cafe] SQL-like DSL for haskell List of Records In-Reply-To: <20140321103215.GN12779@weber> References: <532B2BD7.20101@web.de> <20140321103215.GN12779@weber> Message-ID: <532C6395.1040600@web.de> Am 03/21/2014 11:32 AM, schrieb Tom Ellis: > I'll give you a concrete example along similar lines, except it uses arrows in place of monads. Thanks Tom, particularly for the elaborate example. Yes, this is what I was looking for. From waldmann at imn.htwk-leipzig.de Fri Mar 21 16:43:09 2014 From: waldmann at imn.htwk-leipzig.de (Johannes Waldmann) Date: Fri, 21 Mar 2014 16:43:09 +0000 (UTC) Subject: [Haskell-cafe] Regular Expression Simplification References: <201403211505.s2LF58Ro019251@stowe.cs.dartmouth.edu> Message-ID: > > I'm slightly worried that the overhead of converting to an NFA > is far too great for complicated regular expressions that's not where the complication is. it is in minimizing NFA (or regexeps) - both PSPACE-complete. This is known for a long time. Check any text on formal languages, or read the original sources, e.g., Meyer and Stockmeyer, 1972 http://people.csail.mit.edu/meyer/resume.shtml#publications for more recent results on (non)approximability, cf. Gramlich and Schnitger 1995 http://citeseerx.ist.psu.edu/viewdoc/summary?doi=10.1.1.60.5056 - J.W. From hjgtuyl at chello.nl Fri Mar 21 22:48:36 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Fri, 21 Mar 2014 23:48:36 +0100 Subject: [Haskell-cafe] ANNOUNCE: wxHaskell 0.90.1.0 Message-ID: L.S., I am happy to announce a new version of wxHaskell. This version binds to wxWidgets 2.9 [0]. What is it? ----------- wxHaskell is a portable and native GUI library for Haskell. The goal of the project is to provide an industrial strength GUI library for Haskell, but without the burden of developing (and maintaining) one ourselves. wxHaskell is therefore built on top of wxWidgets ? a comprehensive C++ library that is portable across all major GUI platforms; including GTK, Windows, X11, and MacOS X. Furthermore, it is a mature library (in development since 1992) that supports a wide range of widgets with the native look-and-feel. What's new? ----------- - Added functionality: wxGrid: cell spans, cell renderers (numeric, auto string wrapping), wxScrolledWindow, wxSplitterWindow - Reanimated wxToggleButton, added wxBitmapToggleButton - Solved problem with spaces in pathnames (installation procedure, Windows) - Increased max version of dependencies - The external preprocessor (CPP) is now used - The presence of the wx-config executable is checked at installation time - The bitness of the wxWidgets dynamic libraries is compared to the bitness of the wxHaskell libraries to generate, at installation time; a warning is given when the bitness is incompatible - Documentation improvements - Bugs fixed Links ----- See the homepage of wxHaskell for more information: https://www.haskell.org/haskellwiki/WxHaskell The packages are: - wxc https://hackage.haskell.org/package/wxc - wxdirect https://hackage.haskell.org/package/wxdirect - wxcore https://hackage.haskell.org/package/wxcore - wx https://hackage.haskell.org/package/wx Regards, Henk-Jan van Tuyl [0] https://www.wxwidgets.org/ -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From simons at cryp.to Sat Mar 22 08:56:05 2014 From: simons at cryp.to (Peter Simons) Date: Sat, 22 Mar 2014 09:56:05 +0100 Subject: [Haskell-cafe] Listing native package requirements based on cabal information References: <87vbvadvav.fsf@write-only.cryp.to> <87k3bq84f6.fsf@write-only.cryp.to> Message-ID: <8738iak3x6.fsf@write-only.cryp.to> Hi David, > postgresql-libpq clearly depends on the libpq C library (and possibly > other things) as listed in the Extra-Libraries field in its cabal > file, *as do anything that require postgresql-libpq* which fact does > *not* directly show up in their cabal file. Walking the tree and > pulling that info is a possibility, but it needs to be done after > dependency-resolution in case requirements change version to version. yes, it's a complicated situation. The information stored in a Cabal file must be "finalized" before Cabal can use it to install the package. According to [1], this process depends on the following parameters: - Cabal flags chosen by the user, - the set of installed (or install-able) packages, - the current architecture and operating system, - the Haskell compiler used to build the package, and - version constraints chosen by the user. Thus, a given package may depend on an external library 'foo' if you compile it with GHC 7.6.3, but it depends on 'bar' if you compile it with GHC 7.4.2, and the same variance occurs recursively in all its dependencies. It would be nice to know the list of external dependencies for any given package, but in fact it's not "the list" -- it's many possible lists, because the outcome depends on the exact environment in which the package is built. A rough estimate of these external dependencies is available from Nix, though. The package postgresql-libpq, for example, has its Hackage home page at [2]. That page links to the NixOS build information at [3], which shows the following dependencies: acl-2.2.52 attr-2.4.47 bash-4.2-p45 binutils-2.23.1 coreutils-8.21 gcc-4.8.2 gcc-wrapper-4.8.2 ghc-7.6.3 glibc-2.18 gmp-5.1.3 gnutar-1.27.1 linux-headers-3.7.1 ncurses-5.9 perl-5.16.3 postgresql-9.2.7 readline-6.2 zlib-1.2.8 That list is not be accurate for all environments, but it's a start. Take care, Peter [1] http://hackage.haskell.org/package/Cabal-1.18.1.2/docs/Distribution-PackageDescription-Configuration.html#v:finalizePackageDescription [2] http://hackage.haskell.org/package/postgresql-libpq [3] http://hydra.nixos.org/build/9708550#tabs-runtime-deps From martin.drautzburg at web.de Sat Mar 22 11:50:14 2014 From: martin.drautzburg at web.de (martin) Date: Sat, 22 Mar 2014 12:50:14 +0100 Subject: [Haskell-cafe] No instance for (Eq v) trouble Message-ID: <532D78F6.8060109@web.de> Hello all, how can I make a type an instance of the Show class, if the functions used to implement show require e.g. Eq ? -------------------------------------------- I have a class: class Behavior b where at :: b a -> Day -> a and an instance data Change v = Change v [(Day,v)] deriving(Show) instance Behavior Change where ... and another instance (a Behavior of Behavior) data WeekdayPattern v = WeekdayPattern (Change v) instance Behavior WeekdayPattern where at (WeekdayPattern change) day = at change (day `mod` 7) And I wanted to write my own show function for WeekdayPattern. I started off like this: instance Show (WeekdayPattern v) where show wdp = show $ groupBy sameValue expanded where expanded = zip (map (at wdp) [0..6]) [0..6] sameValue x y = (fst x) == (fst y) ------------------------------------------ But I get: No instance for (Eq v) arising from a use of `sameValue' I believe the compiler wants to tell me, that it has no reason to assume that the values (the "v"s) can be compared for equality. Indeed the class itself and its "at" function do not require this (but it wouldn't hurt to add a constraint) I tried inserting an (Eq v) => in various places of the class or data declaration, but the compiler either didn't like that or it did not solve the problem. There is no problem just writing a show-like method as in xshow :: (Eq v, Show v) => (WeekdayPattern v) -> String but I cannot make this the "show" function of the Show class. From hesselink at gmail.com Sat Mar 22 11:58:21 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Sat, 22 Mar 2014 12:58:21 +0100 Subject: [Haskell-cafe] No instance for (Eq v) trouble In-Reply-To: <532D78F6.8060109@web.de> References: <532D78F6.8060109@web.de> Message-ID: Doesn't 'instance Eq v => Show (WeekdayPattern v)' work? Erik On Sat, Mar 22, 2014 at 12:50 PM, martin wrote: > Hello all, > > how can I make a type an instance of the Show class, if the functions used to implement show require e.g. Eq ? > > -------------------------------------------- > I have a class: > > class Behavior b where > at :: b a -> Day -> a > > and an instance > > data Change v = Change v [(Day,v)] > deriving(Show) > > instance Behavior Change where ... > > and another instance (a Behavior of Behavior) > > data WeekdayPattern v = WeekdayPattern (Change v) > > instance Behavior WeekdayPattern where > at (WeekdayPattern change) day = at change (day `mod` 7) > > And I wanted to write my own show function for WeekdayPattern. I started off like this: > > instance Show (WeekdayPattern v) where > show wdp = show $ groupBy sameValue expanded > where > expanded = zip (map (at wdp) [0..6]) [0..6] > sameValue x y = (fst x) == (fst y) > > ------------------------------------------ > > But I get: > > No instance for (Eq v) > arising from a use of `sameValue' > > > I believe the compiler wants to tell me, that it has no reason to assume that the values (the "v"s) can be compared for > equality. Indeed the class itself and its "at" function do not require this (but it wouldn't hurt to add a constraint) > > I tried inserting an (Eq v) => in various places of the class or data declaration, but the compiler either didn't like > that or it did not solve the problem. There is no problem just writing a show-like method as in > > xshow :: (Eq v, Show v) => (WeekdayPattern v) -> String > > but I cannot make this the "show" function of the Show class. > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sat Mar 22 12:02:41 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sat, 22 Mar 2014 12:02:41 +0000 Subject: [Haskell-cafe] No instance for (Eq v) trouble In-Reply-To: <532D78F6.8060109@web.de> References: <532D78F6.8060109@web.de> Message-ID: <20140322120241.GW12779@weber> On Sat, Mar 22, 2014 at 12:50:14PM +0100, martin wrote: > instance Show (WeekdayPattern v) where > show wdp = show $ groupBy sameValue expanded > where > expanded = zip (map (at wdp) [0..6]) [0..6] > sameValue x y = (fst x) == (fst y) [...] > I tried inserting an (Eq v) => in various places of the class or data > declaration, but the compiler either didn't like > that or it did not solve the problem. There is no problem just writing a > show-like method as in What's wrong with instance (Show v, Eq v) => Show (WeekdayPattern v) where .... Tom PS It helps answerers if you can post the smallest *complete* code that demonstrates the problem, without commentary interspersed. From simons at cryp.to Sat Mar 22 12:01:43 2014 From: simons at cryp.to (Peter Simons) Date: Sat, 22 Mar 2014 13:01:43 +0100 Subject: [Haskell-cafe] ANNOUNCE: wxHaskell 0.90.1.0 References: Message-ID: <877g7m8ms8.fsf@write-only.cryp.to> Hi Henk-Jan, > I am happy to announce a new version of wxHaskell. This version binds to > wxWidgets 2.9 [0]. unfortunately, the files in the release tarball found on Hackage claim to be from the year 2029, which causes some trouble when trying to build this package: . Take care, Peter From martin.drautzburg at web.de Sat Mar 22 12:30:05 2014 From: martin.drautzburg at web.de (martin) Date: Sat, 22 Mar 2014 13:30:05 +0100 Subject: [Haskell-cafe] No instance for (Eq v) trouble In-Reply-To: <20140322120241.GW12779@weber> References: <532D78F6.8060109@web.de> <20140322120241.GW12779@weber> Message-ID: <532D824D.1020507@web.de> Am 03/22/2014 01:02 PM, schrieb Tom Ellis: > What's wrong with > > instance (Show v, Eq v) => Show (WeekdayPattern v) where Thanks Tom and Erik, that solves my problem. From martin.drautzburg at web.de Sat Mar 22 16:51:55 2014 From: martin.drautzburg at web.de (martin) Date: Sat, 22 Mar 2014 17:51:55 +0100 Subject: [Haskell-cafe] groupBy without Ord? Message-ID: <532DBFAB.7080908@web.de> Hello all, when I groupBy a list in order to cluster elements which satisfy some sort of equality, I usually have to sort the list first, which requires Ord. However groupBy itself does not require Ord, but just Eq. How can I groupBy a List whose elements are only instances of Eq but not of Ord? From fuuzetsu at fuuzetsu.co.uk Sat Mar 22 17:15:26 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sat, 22 Mar 2014 17:15:26 +0000 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <532DBFAB.7080908@web.de> References: <532DBFAB.7080908@web.de> Message-ID: <532DC52E.2010509@fuuzetsu.co.uk> On 22/03/14 16:51, martin wrote: > Hello all, > > when I groupBy a list in order to cluster elements which satisfy some sort of equality, I usually have to sort the list > first, which requires Ord. However groupBy itself does not require Ord, but just Eq. > > How can I groupBy a List whose elements are only instances of Eq but not of Ord? > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > group(By) is not concerned with grouping elements from the whole list together. It is only concerned about grouping elements that fulfill the equality that are already next to each other. | > group [1, 2, 1] | [[1], [2], [1]] If you want it to group the elements from the whole list, it as as you mention, you have to sort the list first or arrange it otherwise so that equal elements are next to each other. So to answer your question, you can groupBy Eq a => [a] simply by calling groupBy. If you want groupBy to group elements from the whole list, you need to arrange for such elements to be next to each other in the list. The Ord instance is normally used for this. Alternatively you can write a function which will simply go through the list for each distinctive element and collect the groups that way. This is _not_ what groupBy does: you're looking at the wrong function. -- Mateusz K. From byorgey at seas.upenn.edu Sat Mar 22 17:16:58 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Sat, 22 Mar 2014 13:16:58 -0400 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <532DBFAB.7080908@web.de> References: <532DBFAB.7080908@web.de> Message-ID: <20140322171658.GA19608@seas.upenn.edu> On Sat, Mar 22, 2014 at 05:51:55PM +0100, martin wrote: > Hello all, > > when I groupBy a list in order to cluster elements which satisfy some sort of equality, I usually have to sort the list > first, which requires Ord. However groupBy itself does not require Ord, but just Eq. > > How can I groupBy a List whose elements are only instances of Eq but not of Ord? Well, you can just call groupBy on it. =) But I assume you mean that you still want to group together all equal elements. You could do something like groupEq [] = [] groupEq (a:rest) = (a:as) : groupEq bs where (as,bs) = partition (==a) rest and you could easily generalize it to take a binary predicate, like groupBy, as well. If you want to get a little fancier and avoid the explicit recursion, you can use Data.List.Split.chop (from the 'split' package), which provides a generic way of recursively processing a list: chop :: ([a] -> (b,[a])) -> [a] -> [b] like so: import Data.List.Split (chop) import Control.Arrow (first) groupEq = chop (\(a:rest) -> first (a:) (partition (==a) rest)) -Brent From ky3 at atamo.com Sat Mar 22 17:40:05 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Sun, 23 Mar 2014 00:40:05 +0700 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <532DBFAB.7080908@web.de> References: <532DBFAB.7080908@web.de> Message-ID: On Sat, Mar 22, 2014 at 11:51 PM, martin wrote: > How can I groupBy a List whose elements are only instances of Eq but not > of Ord? If you take a look at the code for groupBy: groupBy :: (a -> a -> Bool) -> [a] -> [[a]] groupBy _ [] = [] groupBy eq (x:xs) = (x:ys) : groupBy eq zs where (ys,zs) = span (eq x) xs and replace 'span' by 'partition' you'd get what you want. You'd need a new name for your different groupBy of course. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From martin.drautzburg at web.de Sat Mar 22 18:29:02 2014 From: martin.drautzburg at web.de (martin) Date: Sat, 22 Mar 2014 19:29:02 +0100 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: References: <532DBFAB.7080908@web.de> Message-ID: <532DD66E.3020303@web.de> Am 03/22/2014 06:40 PM, schrieb Kim-Ee Yeoh: > > On Sat, Mar 22, 2014 at 11:51 PM, martin > wrote: > > How can I groupBy a List whose elements are only instances of Eq but not of Ord? > > > If you take a look at the code for groupBy: > > groupBy :: (a -> a -> Bool) -> [a] -> [[a]] > groupBy _ [] = [] > groupBy eq (x:xs) = (x:ys) : groupBy eq zs Cool! I have a database background and the SQL "group by" does of course not assume any ordering. So I often wonder, where you would use Haskell's groupBy WITHOUT sorting first, but I assume there are situations, where this is useful. From fuuzetsu at fuuzetsu.co.uk Sat Mar 22 18:39:55 2014 From: fuuzetsu at fuuzetsu.co.uk (Mateusz Kowalczyk) Date: Sat, 22 Mar 2014 18:39:55 +0000 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <532DD66E.3020303@web.de> References: <532DBFAB.7080908@web.de> <532DD66E.3020303@web.de> Message-ID: <532DD8FB.9090404@fuuzetsu.co.uk> On 22/03/14 18:29, martin wrote: > Am 03/22/2014 06:40 PM, schrieb Kim-Ee Yeoh: >> >> On Sat, Mar 22, 2014 at 11:51 PM, martin > wrote: >> >> How can I groupBy a List whose elements are only instances of Eq but not of Ord? >> >> >> If you take a look at the code for groupBy: >> >> groupBy :: (a -> a -> Bool) -> [a] -> [[a]] >> groupBy _ [] = [] >> groupBy eq (x:xs) = (x:ys) : groupBy eq zs > > Cool! > > I have a database background and the SQL "group by" does of course not assume any ordering. So I often wonder, where you > would use Haskell's groupBy WITHOUT sorting first, but I assume there are situations, where this is useful. > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > One example that comes to mind is filtering consecutive-same elements: | Prelude Data.List> map head $ group "hello world!!!" | "helo world!" -- Mateusz K. From ky3 at atamo.com Sat Mar 22 19:23:25 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Sun, 23 Mar 2014 02:23:25 +0700 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <532DD66E.3020303@web.de> References: <532DBFAB.7080908@web.de> <532DD66E.3020303@web.de> Message-ID: On Sun, Mar 23, 2014 at 1:29 AM, martin wrote: > So I often wonder, where you > would use Haskell's groupBy WITHOUT sorting first, but I assume there are > situations, where this is useful. > But if you sorted first, then there must be an Ord-er on the elements, yes? In which case you could then apply (sqlGroup = group . sort) as originally desired. I'm sure groupBy is useful standalone (dim memories of some functional pearl) but your hunch is right in that I normally use it after a sorting step. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From winterkoninkje at gmail.com Sat Mar 22 22:19:05 2014 From: winterkoninkje at gmail.com (wren romano) Date: Sat, 22 Mar 2014 18:19:05 -0400 Subject: [Haskell-cafe] Regular Expression Simplification In-Reply-To: References: Message-ID: On Thu, Mar 20, 2014 at 8:17 AM, Berg, Matias Juho wrote: > Does anyone have any suggestions on where to look for more examples so I can > see what kinds of attempts people have used to try and solve this problem? > Also if someone has worked on this kind of problem was Kleene algebra a good > starting point? It's not Haskell-specific, but you should look at the work done by Xerox on XFST/OpenFST. One of the major issues they needed to tackle is how to avoid the exponential blowup that can arise from manipulating FSTs. I don't recall how much simplification they do, but their main goal and use case was also dealing with natural language. -- Live well, ~wren From vlatko.basic at gmail.com Sun Mar 23 08:38:00 2014 From: vlatko.basic at gmail.com (Vlatko Basic) Date: Sun, 23 Mar 2014 09:38:00 +0100 Subject: [Haskell-cafe] JuicyFruit - explanation of speed difference of pure and monadic image generation In-Reply-To: <532C1025.5020907@gmail.com> References: <532AB114.7020804@gmail.com> <532C1025.5020907@gmail.com> Message-ID: <532E9D68.2020805@gmail.com> An HTML attachment was scrubbed... URL: From jwlato at gmail.com Sun Mar 23 23:34:42 2014 From: jwlato at gmail.com (John Lato) Date: Sun, 23 Mar 2014 16:34:42 -0700 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <532DBFAB.7080908@web.de> References: <532DBFAB.7080908@web.de> Message-ID: I would keep in mind that, given the constraints - you want to group together all equal elements from the entire list - the only operation you can perform on elements is comparison for equality your function will have quadratic complexity (at least I can't see any way around it). If there's any way of sorting the elements, even if the order is entirely arbitrary, you should consider it. John L. On Sat, Mar 22, 2014 at 9:51 AM, martin wrote: > Hello all, > > when I groupBy a list in order to cluster elements which satisfy some sort > of equality, I usually have to sort the list > first, which requires Ord. However groupBy itself does not require Ord, > but just Eq. > > How can I groupBy a List whose elements are only instances of Eq but not > of Ord? > -------------- next part -------------- An HTML attachment was scrubbed... URL: From omari at smileystation.com Mon Mar 24 02:04:36 2014 From: omari at smileystation.com (Omari Norman) Date: Sun, 23 Mar 2014 22:04:36 -0400 Subject: [Haskell-cafe] [ANN] rainbox - print colorful text boxes - good for tabular data Message-ID: Rainbox helps you create (possibly) colorful text boxes for printing to a UNIX terminal. It uses the rainbow [1] library to permit use of 8 or 256 colors. Rainbox is great for formatting tabular data. One module, Rainbox, permits you to make simple grids--like spreadsheets that do not allow you to split or merge cells. Another module, Rainbox.Box, lets you create boxes of arbitrary complexity. Rainbox is similar to the boxes library [2] but unlike Boxes it's easy to use colors with Rainbox. The Haddocks for both modules will get you started; there is also a tutorial for the simple grid model in the Rainbox.Tutorial module. That file is written in literate Haskell, which HsColour does not fare so well with, so it makes more sense in your text editor or on Github: https://github.com/massysett/rainbox/blob/master/lib/Rainbox/Tutorial.lhs Rainbox is here: http://hackage.haskell.org/package/rainbox --Omari [1] http://hackage.haskell.org/package/rainbow [2] http://hackage.haskell.org/package/boxes From arjenvanweelden at gmail.com Mon Mar 24 10:50:51 2014 From: arjenvanweelden at gmail.com (Arjen) Date: Mon, 24 Mar 2014 11:50:51 +0100 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: References: <532DBFAB.7080908@web.de> Message-ID: <53300E0B.4030904@gmail.com> Hi, Have you considered using a "dictionary" of key-value pairs to group the elements? HashTable requires only Eq and a hash function but no Ord. First insert all element into the hashtable and them iterate over the keys in the hashtable where you can find all elements per group. You could tests whether the (somewhat constant) overhead of the hashtable is significant in your use cases. On second thought, this might introduce an overloading dependency on the Hash class/function. Maybe you know something about the key type such that this dependency can be resolved elsewhere? kind regards, Arjen. On 03/24/2014 12:34 AM, John Lato wrote: > I would keep in mind that, given the constraints > > - you want to group together all equal elements from the entire list > - the only operation you can perform on elements is comparison for > equality > > your function will have quadratic complexity (at least I can't see any > way around it). If there's any way of sorting the elements, even if the > order is entirely arbitrary, you should consider it. > > John L. > > On Sat, Mar 22, 2014 at 9:51 AM, martin > wrote: > > Hello all, > > when I groupBy a list in order to cluster elements which satisfy > some sort of equality, I usually have to sort the list > first, which requires Ord. However groupBy itself does not require > Ord, but just Eq. > > How can I groupBy a List whose elements are only instances of Eq but > not of Ord? > > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From rustompmody at gmail.com Mon Mar 24 13:22:04 2014 From: rustompmody at gmail.com (Rustom Mody) Date: Mon, 24 Mar 2014 18:52:04 +0530 Subject: [Haskell-cafe] Regular Expression Simplification In-Reply-To: References: Message-ID: On Thu, Mar 20, 2014 at 5:47 PM, Berg, Matias Juho wrote: > Hi all, > > > I am a final year undergraduate student at a university and I am doing my > final honours project on natural language generation from regular > expressions. For this to work efficiently I need to simplify the regular > expressions before I translate them. It seems that there is some previous > work done on this in Haskell but I have only been able to find this code > (http://hackage.haskell.org/package/HaLeX-1.1/docs/src/Language-HaLex-RegExp.html) > which does some elementary simplification. > > Does anyone have any suggestions on where to look for more examples so I can > see what kinds of attempts people have used to try and solve this problem? Have not followed this thread closely so please excuse if this is already mentioned or is unfitting to your requirement Have you seen the Berry-Sethi algo?? www2.in.tum.de/hp/file?fid=571 From djsamperi at gmail.com Mon Mar 24 14:40:17 2014 From: djsamperi at gmail.com (Dominick Samperi) Date: Mon, 24 Mar 2014 10:40:17 -0400 Subject: [Haskell-cafe] Cabal robustness Message-ID: I have seen the dreaded "ExitFailure 1" many times when a package fails to install (under Linux or Windows), and I wonder why something more helpful cannot be printed? Sometimes one gets a variant of this where the message is "this system is not compatible with this package," but the user must study the foo.cabal file to determine what is missing. Also, it seems that the only way to determine if a package will install under Windows is to try and hope for the best (often getting "ExitFailure 1" if it fails). Wouldn't it make more sense to tag packages with the OS and other dependencies and fail with a helpful message like "Windows not supported" if appropriate? It appears that some packages (like lens-4.1) have version dependencies that cannot be satisfied (at least not on my Linux and Windows boxes), so it appears that the Hackage hosting process suffers from a variant of the well-known "dll hell" problem. I tried the new (Cabal 1.18.0) sandbox feature but this did not help in my case. Any comments on these issues would be appreciated. Thanks, Dominick From johan.tibell at gmail.com Mon Mar 24 14:43:59 2014 From: johan.tibell at gmail.com (Johan Tibell) Date: Mon, 24 Mar 2014 15:43:59 +0100 Subject: [Haskell-cafe] Cabal robustness In-Reply-To: References: Message-ID: Hi Dominick, An "ExitFailure 1" is definitely not helpful and we should generally try to figure out what went wrong and print something more specific. One example where this happens if I recall correctly is if GHC runs out of RAM and exits, something that we could detect. I think the best way forward right now is to file bugs for concrete cases where the error reporting is bad. Include what (you think) went wrong and what kind of error information would have been useful to you. The bug tracker is at https://github.com/haskell/cabal/issues On Mon, Mar 24, 2014 at 3:40 PM, Dominick Samperi wrote: > I have seen the dreaded "ExitFailure 1" many times when a package fails to > install (under Linux or Windows), and I wonder why something more helpful > cannot be printed? Sometimes one gets a variant of this where the message > is "this system is not compatible with this package," but the user must > study the foo.cabal file to determine what is missing. > > Also, it seems that the only way to determine if a package will install > under > Windows is to try and hope for the best (often getting "ExitFailure 1" if > it > fails). Wouldn't it make more sense to tag packages with the OS and > other dependencies and fail with a helpful message like "Windows not > supported" if appropriate? > > It appears that some packages (like lens-4.1) have version dependencies > that cannot be satisfied (at least not on my Linux and Windows boxes), > so it appears that the Hackage hosting process suffers from a variant of > the well-known "dll hell" problem. > > I tried the new (Cabal 1.18.0) sandbox feature but this did not help in my > case. > > Any comments on these issues would be appreciated. > > Thanks, > Dominick > _______________________________________________ > 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 lemming at henning-thielemann.de Mon Mar 24 22:00:29 2014 From: lemming at henning-thielemann.de (Henning Thielemann) Date: Mon, 24 Mar 2014 23:00:29 +0100 Subject: [Haskell-cafe] HaL-9 - Call for Contributions Message-ID: <5330AAFD.1070504@henning-thielemann.de> HaL ist ein lokaler Haskell-Workshop mit ?berregionaler Bedeutung, der nun bereits das 9. Mal stattfindet. Dieses Jahr laden wir f?r den 20. Juni ins Institut f?r Informatik an der Martin-Luther-Universit?t Halle-Wittenberg ein. Wir suchen Beitr?ge zu Haskell im Besonderen und der funktionalen Programmierung im Allgemeinen, aber auch Ankn?pfungen an andere Programmierparadigmen. Dabei interessieren wir uns unter anderem f?r die Themenbereiche * Neues von Sprache, Bibliotheken, Werkzeugen, * Anwendungen von Kunst bis Industrie, * Lehre und Forschung an Schulen und Hochschulen. Die Beitr?ge k?nnen pr?sentiert werden als * Tutorium (etwa 90 min) * Vortrag (etwa 30 min) * Demonstration, k?nstlerische Auff?hrung Die Veranstaltungssprache ist Deutsch, nach Absprache auch Englisch. Presentations will be given in German but we can switch to English if requested. Bitte reichen Sie Kurzfassungen der Beitr?ge ein (max. 3 Seiten), die dem Programmkomitee eine Einsch?tzung erm?glichen, sowie eine knappe Zusammenfassung von etwa 100 W?rtern. Teilnehmer des Workshops sind Interessenten (keine Erfahrung mit Haskell oder funktionaler Programmierung), Anf?nger (wenig Erfahrung) und Experten. Wir bitten die Vortragenden, die Zielgruppe des Beitrags anzugeben und die n?tigen Vorkenntnisse zu beschreiben. Bei Tutorien sollen Teilnehmer auf eigenen Rechnern arbeiten. Bitte beschreiben Sie dazu die vorher zu installierende Software. Senden Sie die Beitragsvorschl?ge als PDF-Dokument bis zum 27. April 2014 an hal-committee at iba-cg.de Wir werden Ihnen bis zum 9. Mai mitteilen, ob wir Ihren Beitrag in das Programm aufnehmen. F?r das Organisationsteam Henning Thielemann From hjgtuyl at chello.nl Mon Mar 24 23:57:20 2014 From: hjgtuyl at chello.nl (Henk-Jan van Tuyl) Date: Tue, 25 Mar 2014 00:57:20 +0100 Subject: [Haskell-cafe] Cabal robustness In-Reply-To: References: Message-ID: On Mon, 24 Mar 2014 15:40:17 +0100, Dominick Samperi wrote: > I have seen the dreaded "ExitFailure 1" many times when a package fails > to > install (under Linux or Windows), and I wonder why something more helpful > cannot be printed? Sometimes one gets a variant of this where the message > is "this system is not compatible with this package," but the user must > study the foo.cabal file to determine what is missing. > > Also, it seems that the only way to determine if a package will install > under > Windows is to try and hope for the best (often getting "ExitFailure 1" > if it > fails). Wouldn't it make more sense to tag packages with the OS and > other dependencies and fail with a helpful message like "Windows not > supported" if appropriate? A faster way to discover if a package can be installed on Windows: cabal install lens-4.1 --dry-run If the package depends on the package unix, it's not Windows compatible. This is of course not always sufficient, e.g. if you need to install non-Haskell software first. Regards, Henk-Jan van Tuyl -- Folding at home What if you could share your unused computer power to help find a cure? In just 5 minutes you can join the world's biggest networked computer and get us closer sooner. Watch the video. http://folding.stanford.edu/ http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming -- From kai at kzhang.org Tue Mar 25 03:58:48 2014 From: kai at kzhang.org (Kai Zhang) Date: Mon, 24 Mar 2014 20:58:48 -0700 Subject: [Haskell-cafe] Haskell practice -- Plotting library Message-ID: Hi, I've been playing with Haskell for a while. In order to improve my Haskell skills and also due to the lack of an intuitive plotting library, I decided to write a simplified plotting interface for the haskell-chart library. Any comments or suggestions would be very welcome! https://github.com/kaizhang/haskell-plot Kai -------------- next part -------------- An HTML attachment was scrubbed... URL: From dhelta.diaz at gmail.com Tue Mar 25 13:46:27 2014 From: dhelta.diaz at gmail.com (=?UTF-8?Q?Daniel_D=C3=ADaz_Casanueva?=) Date: Tue, 25 Mar 2014 14:46:27 +0100 Subject: [Haskell-cafe] [ANN] haskintex 0.4.0.0 - Haskell code inside a LaTeX document, now with IO! Message-ID: Hello haskellers. Good news for the users of haskintex. This release opens new possibilities and solves some frustrations we had in the past. For those who don't know what haskintex is, here is an overview. Haskintex is a program that reads a LaTeX file and evaluates Haskell expressions contained in some specific commands and environments. For example, if you save the file "foo.htex" with: -- foo.htex \documentclass{article} \begin{document} I have \evalhaskell{2+3} fingers in my right hand. \end{document} -- ...and run "haskintex foo", you will get the following output: \documentclass{article} \begin{document} I have \verb`5` fingers in my right hand. \end{document} Just as you expected. If you want to know more details, visit the haskintex site at: http://daniel-diaz.github.io/projects/haskintex What is new in this release? We have added two new features: * \iohatex{t}, where t :: IO LaTeX. It works exactly as the \hatex command does, but it expects an input of type IO LaTeX. This means you can perform IO computations now! * \begin{haskellpragmas}...\end{haskellpragmas} This will allow to include pragmas in the temporal Haskell module. In addition to these two features, a new flag can be passed to the program: -debug. It writes down in a file the representation of the input that haskintex uses internally. It can be useful in those cases that you are not getting the output you expect. And that's it for now. The code didn't grow much (and I want it to stay small) but I think possibilities have grown substantially. If you want to give it try, run "cabal update" followed by "cabal install haskintex". Good luck, Daniel D?az. -------------- next part -------------- An HTML attachment was scrubbed... URL: From tim at dockerz.net Wed Mar 26 08:54:49 2014 From: tim at dockerz.net (Tim Docker) Date: Wed, 26 Mar 2014 19:54:49 +1100 Subject: [Haskell-cafe] Haskell practice -- Plotting library In-Reply-To: References: Message-ID: The current chart API is verbose, and its nice to see people thinking about improving it. The best place to discuss this is probably on the chart mailing list: http://projects.haskell.org/cgi-bin/mailman/listinfo/chart Tim On 25 Mar 2014 14:58, "Kai Zhang" wrote: > Hi, > > I've been playing with Haskell for a while. In order to improve my Haskell > skills and also due to the lack of an intuitive plotting library, I decided > to write a simplified plotting interface for the haskell-chart library. Any > comments or suggestions would be very welcome! > https://github.com/kaizhang/haskell-plot > > Kai > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From Andrew.Butterfield at scss.tcd.ie Wed Mar 26 08:58:14 2014 From: Andrew.Butterfield at scss.tcd.ie (Andrew Butterfield) Date: Wed, 26 Mar 2014 08:58:14 +0000 Subject: [Haskell-cafe] [wxhaskell-users] ANNOUNCE: wxHaskell 0.90.1.0 In-Reply-To: References: Message-ID: On 21 Mar 2014, at 22:48, Henk-Jan van Tuyl wrote: > > L.S., > > I am happy to announce a new version of wxHaskell. This version binds to > wxWidgets 2.9 [0]. I tried an install - got some strange errors, so cleaned out my Haskell installation using uninstall-hs, re-installed latest platform Edited .cabal/config to have global installation and to use sudo when required cabal update cabal install cabal-install cabal install wx cacal-macosx (on Mac OS X 9.2, by the way) Both cabal-install and wx were reported as being installed , but in both cases it ended with an error message like this: ?? console log excerpt starts ?? Installed wx-0.90.1.0 Error while Error while updating world-file. : /Users/butrfeld/Library/Haskell/logs/world: openFile: permission denied (Permission denied) Warning: could not create a symlink in /Users/butrfeld/Library/Haskell/bin for wxdirect because the file exists there already but is not managed by cabal. You can create a symlink for this executable manually if you wish. The executable file has been installed at /Library/Haskell/ghc-7.6.3/lib/wxdirect-0.90.1.1/bin/wxdirect ? console log ecxeprt ends ?? Can i ignore these, or do I need to fix something? like the symlink that is mentioned? (PS - I also did the ghc-clang-wrapper thing?) -------------------------------------------------------------------- Andrew Butterfield Tel: +353-1-896-2517 Fax: +353-1-677-2204 Lero at TCD, Head of Foundations & Methods Research Group Director of Teaching and Learning - Undergraduate, School of Computer Science and Statistics, Room G.39, O'Reilly Institute, Trinity College, University of Dublin http://www.scss.tcd.ie/Andrew.Butterfield/ -------------------------------------------------------------------- From hoerdegen at funktional.info Wed Mar 26 09:58:32 2014 From: hoerdegen at funktional.info (=?ISO-8859-15?Q?Heinrich_H=F6rdegen?=) Date: Wed, 26 Mar 2014 10:58:32 +0100 Subject: [Haskell-cafe] Munich Haskell Meeting Message-ID: <5332A4C8.9070906@funktional.info> Dear all, our next Haskell meeting in Munich is scheduled for the 31st of March. Exceptionally, we will meet at 19h30 at Theresienstrasse 39 Room A027, 80333 Munich Rene Brunner will present his inaugural speech on Big Data for us. See also the announcment on our site. Afterwards, we will meet at Cafe Puck, as usually. Please help to reserve enough tables by going to http://www.haskell-munich.de/dates and clicking the button. Until then, have a nice time! Heinrich From ivanperezdominguez at gmail.com Wed Mar 26 18:03:45 2014 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Wed, 26 Mar 2014 19:03:45 +0100 Subject: [Haskell-cafe] Help getting hcwiid to work Message-ID: Hi Caf?, I'm trying to get the wiimote bindings to work (hcwiid). I can compile them just fine, but trying to open the wiimote with the demo application included in the repo returns a null. I tried using C apps directly (wmgui, etc.) and they work for me. I googled as much as I could, but found no solution there. I tried using previous versions of the package, going back in the history of the repo, but it seems to be "just broken". The maintainer of this package cannot offer any help at this moment. Has any haskeller been able to make this work? Best Ivan -------------- next part -------------- An HTML attachment was scrubbed... URL: From semen at trygub.com Thu Mar 27 02:36:44 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Thu, 27 Mar 2014 02:36:44 +0000 Subject: [Haskell-cafe] strange error message In-Reply-To: References: Message-ID: <20140327023644.GD34466@inanna.trygub.com> Dear Haskell-Cafe, Every now and then I get error messages when compiling Haskell code :). Sometimes of the sort: test.hs:10:15: Couldn't match type `[[a2]]' with `Int' Expected type: Int -> Int Actual type: [[a2]] -> Int The function `length . head' is applied to one argument, but its type `[[a2]] -> Int' has only one In the first argument of `(==)', namely `(length . head) r' In the expression: (length . head) r == 0 Is the middle part of the error message (The function `length . head' is applied to one argument, but its type `[[a2]] -> Int' has only one) expected to be confusing like that sometimes? The line in question, FWIW, is Right r -> if (length . head) r == 0 It appears as one of the two entries in a case statement, pattern matching on Right constructor. Many thanks, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From james at mansionfamily.plus.com Thu Mar 27 06:29:48 2014 From: james at mansionfamily.plus.com (james) Date: Thu, 27 Mar 2014 06:29:48 +0000 Subject: [Haskell-cafe] Best Actor system? Message-ID: <5333C55C.7050104@mansionfamily.plus.com> Having been introduced to actors by looking at Erlang, I discovered Akka. It seems that the performance is pretty impressive and I like the model. There seem to be several basic Actor libraries in Hackage, but they don't seem to be very actively developed. I'm more interested in the model for programming within a single runtime than I am for distributed systems, but message and dispatch performance definitely is important. Can anyone share experiences with the different packages? Is any one of them stand-out? Thanks James From cma at bitemyapp.com Thu Mar 27 06:32:38 2014 From: cma at bitemyapp.com (Christopher Allen) Date: Thu, 27 Mar 2014 01:32:38 -0500 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <5333C55C.7050104@mansionfamily.plus.com> References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: Have you looked at the Async library or Marlow's book? http://hackage.haskell.org/package/async http://chimera.labs.oreilly.com/books/1230000000929/ Neither involve actors but I think many Haskellers, myself included, are skeptical of actor/agent systems. I've written a fair bit of Clojure and Scala code and don't much care for the model. If all you really need is message passing/dispatch, you don't strictly speaking need actors. Channels, messages, and dataflow might very well be enough. Perhaps look into functional reactive programming as well? Cheers, hope this helps. --- Chris On Thu, Mar 27, 2014 at 1:29 AM, james wrote: > Having been introduced to actors by looking at Erlang, I discovered Akka. > > It seems that the performance is pretty impressive and I like the model. > > There seem to be several basic Actor libraries in Hackage, but they don't > seem > to be very actively developed. > > I'm more interested in the model for programming within a single runtime > than I am for distributed systems, but message and dispatch performance > definitely is important. > > Can anyone share experiences with the different packages? Is any one > of them stand-out? > > Thanks > James > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Mar 27 07:32:54 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 27 Mar 2014 03:32:54 -0400 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: I'm inclined to agree with Chris, in the shared heap setting, you really should try those other approaches first! On Thu, Mar 27, 2014 at 2:32 AM, Christopher Allen wrote: > Have you looked at the Async library or Marlow's book? > > http://hackage.haskell.org/package/async > > http://chimera.labs.oreilly.com/books/1230000000929/ > > Neither involve actors but I think many Haskellers, myself included, are > skeptical of actor/agent systems. I've written a fair bit of Clojure and > Scala code and don't much care for the model. > > If all you really need is message passing/dispatch, you don't strictly > speaking need actors. Channels, messages, and dataflow might very well be > enough. Perhaps look into functional reactive programming as well? > > Cheers, hope this helps. > > --- Chris > > > > On Thu, Mar 27, 2014 at 1:29 AM, james wrote: > >> Having been introduced to actors by looking at Erlang, I discovered Akka. >> >> It seems that the performance is pretty impressive and I like the model. >> >> There seem to be several basic Actor libraries in Hackage, but they don't >> seem >> to be very actively developed. >> >> I'm more interested in the model for programming within a single runtime >> than I am for distributed systems, but message and dispatch performance >> definitely is important. >> >> Can anyone share experiences with the different packages? Is any one >> of them stand-out? >> >> Thanks >> James >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From iago.abal at gmail.com Thu Mar 27 10:18:16 2014 From: iago.abal at gmail.com (Iago Abal) Date: Thu, 27 Mar 2014 11:18:16 +0100 Subject: [Haskell-cafe] ANN: Haskell bindings for Z3: package z3 0.3.2 released Message-ID: I am happy to announce a new version of the z3 package http://hackage.haskell.org/package/z3 the (unofficial) Haskell bindings for Microsoft's Z3 theorem prover. We didn't announce this package before, but we believe that now it is stable enough to be useful for a broader audience. These bindings are especially appropriate in the following cases: * If your program runs lot of queries, and probably would benefit from incremental solving. Here the performance benefit w.r.t. translating each query to SMT-LIB and calling an external solver should be significant. * If you need to extract interpretations for arrays and functions. * If you need to access specific Z3 features such as Quantifiers or Solvers. We offer three different interfaces: * Z3.Base: a low-level interface, it just performs marshalling. * Z3.Monad: introduces a class MonadZ3 and a concrete monad Z3 that does some bookkeeping for you. Most people seem to be using this interface. * Z3.Lang: a high-level interface in the form of an embedded language. This interface has been deprecated in the current release, we will continue to develop it, but it will be in separate package. The bindings are still incomplete as there are some API functions that have not been added yet. The infrastructure is there, and adding support for new API functions is (most of the times) straightforward. We appreciate that, if you fork the project and add extra functions, then you send the changes back to us. These bindings still use the old Z3 API of Z3 3.x versions, but there is some support for the new API that some people is using satisfactorily. (Z3 4.0 was released while we were still exploring the design of the library and we preferred not to switch to the new API at that time). Full support for the new API should come in the next release. Iago -------------- next part -------------- An HTML attachment was scrubbed... URL: From a.s.chapman.10 at aberdeen.ac.uk Thu Mar 27 10:58:45 2014 From: a.s.chapman.10 at aberdeen.ac.uk (Chapman, Anthony Sergio) Date: Thu, 27 Mar 2014 10:58:45 +0000 Subject: [Haskell-cafe] Main function variables made global. In-Reply-To: <47a0a6d2c368496f96d59c48521e007d@DBXPR01MB015.eurprd01.prod.exchangelabs.com> References: <47a0a6d2c368496f96d59c48521e007d@DBXPR01MB015.eurprd01.prod.exchangelabs.com> Message-ID: <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> ?Hello, My problem is as follows (not actual code), I declare a function outside of the main function func w = w * var I get the value of 'var' from a text file in the main function (as the user types the name of the file into terminal) I need a way for 'func' to see what 'var' is without having to change it's type (ie make it into a function which take a 'w' and a 'var'. The reason I can't change the type is that I then pass the function to a PSO module which has strict declarations of a function and I would rather not change the PSO module. I also can't put 'func' into main because 'w' isn't specified. The PSO will find the best w so I don't get it a value. I have thought about making a dummy function which has an input of 'w' and 'var' and an output of a function of just 'w'. Something like: func w = func' w var. I got the function for PSO to optimise and the function to get the data I want from a text file working great, they both do what they're supposed to do. I just need the function of PSO to see the data I get from the file. If you need any more information (sorry if I've been too vague) please let me know. Thank you for your time.? -------------- next part -------------- An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Thu Mar 27 11:08:55 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 27 Mar 2014 11:08:55 +0000 Subject: [Haskell-cafe] Main function variables made global. In-Reply-To: <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> References: <47a0a6d2c368496f96d59c48521e007d@DBXPR01MB015.eurprd01.prod.exchangelabs.com> <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> Message-ID: <20140327110855.GF26219@weber> On Thu, Mar 27, 2014 at 10:58:45AM +0000, Chapman, Anthony Sergio wrote: > func w = w * var > > I get the value of 'var' from a text file in the main function (as the > user types the name of the file into terminal) > > I need a way for 'func' to see what 'var' is without having to change > it's type (ie make it into a function which take a 'w' and a 'var'. > > The reason I can't change the type is that I then pass the function to a > PSO module which has strict declarations of a function and I would rather > not change the PSO module. It's not quite clear to me what you're asking, but won't something like this do? do var <- readVar let func w = w * var let result = psoFunction func Tom From ivanperezdominguez at gmail.com Thu Mar 27 11:28:33 2014 From: ivanperezdominguez at gmail.com (Ivan Perez) Date: Thu, 27 Mar 2014 11:28:33 +0000 Subject: [Haskell-cafe] strange error message In-Reply-To: <20140327023644.GD34466@inanna.trygub.com> References: <20140327023644.GD34466@inanna.trygub.com> Message-ID: Hi, My two cents: What is the type of head? What is the type of length? What is the type of length.head? What is the type of r? Best Ivan On 27 March 2014 02:36, Semen Trygubenko / ????? ?????????? < semen at trygub.com> wrote: > Dear Haskell-Cafe, > > Every now and then I get error messages when compiling Haskell code :). > Sometimes of the sort: > > test.hs:10:15: > Couldn't match type `[[a2]]' with `Int' > Expected type: Int -> Int > Actual type: [[a2]] -> Int > The function `length . head' is applied to one argument, > but its type `[[a2]] -> Int' has only one > In the first argument of `(==)', namely `(length . head) r' > In the expression: (length . head) r == 0 > > Is the middle part of the error message > > (The function `length . head' is applied to one argument, > but its type `[[a2]] -> Int' has only one) > > expected to be confusing like that sometimes? > > The line in question, FWIW, is > > Right r -> if (length . head) r == 0 > > It appears as one of the two entries in a case statement, pattern matching > on Right constructor. > > Many thanks, > S. > > > > -- > ????? ?????????? http://trygub.com > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From mantkiew at gsd.uwaterloo.ca Thu Mar 27 11:39:37 2014 From: mantkiew at gsd.uwaterloo.ca (mantkiew at gsd.uwaterloo.ca) Date: Thu, 27 Mar 2014 07:39:37 -0400 Subject: [Haskell-cafe] Main function variables made global. In-Reply-To: <20140327110855.GF26219@weber> References: <47a0a6d2c368496f96d59c48521e007d@DBXPR01MB015.eurprd01.prod.exchangelabs.com> <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> <20140327110855.GF26219@weber> Message-ID: <20140327113937.6004884.72506.5248@gsd.uwaterloo.ca> Anthony, maybe simply add var as a parameter and partially apply func in main? That'll give you the right type. Michal ? Original Message ? From: Tom Ellis Sent: Thursday, March 27, 2014 7:06 AM To: haskell-cafe at haskell.org Subject: Re: [Haskell-cafe] Main function variables made global. On Thu, Mar 27, 2014 at 10:58:45AM +0000, Chapman, Anthony Sergio wrote: > func w = w * var > > I get the value of 'var' from a text file in the main function (as the > user types the name of the file into terminal) > > I need a way for 'func' to see what 'var' is without having to change > it's type (ie make it into a function which take a 'w' and a 'var'. > > The reason I can't change the type is that I then pass the function to a > PSO module which has strict declarations of a function and I would rather > not change the PSO module. It's not quite clear to me what you're asking, but won't something like this do? do var <- readVar let func w = w * var let result = psoFunction func Tom _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe at haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe From edofic at gmail.com Thu Mar 27 12:06:45 2014 From: edofic at gmail.com (=?UTF-8?Q?Andra=C5=BE_Bajt?=) Date: Thu, 27 Mar 2014 05:06:45 -0700 (PDT) Subject: [Haskell-cafe] Why does not Haskell have built-in memoization support? In-Reply-To: <23c68acf-89b9-4db0-995b-62c522af5e1b@googlegroups.com> References: <23c68acf-89b9-4db0-995b-62c522af5e1b@googlegroups.com> Message-ID: <709f81b9-111e-4788-b2f4-038c2f4465b2@googlegroups.com> Because that would imply you store all calls(parameters and results) during the program execution. And that would require potentialy infinite memory. You might argue that only some need to be memoized. And this is precisely the case. But this reasoning(which to memoize) cannot be fully automated(yet). On Wednesday, March 26, 2014 8:42:32 AM UTC+1, Cosmia Luna wrote: > > Hi everyone, I'm new to Haskell. > > I'm confused about the pure function and lazy evaluation in Haskell. Why > there is not built-in support for memoization, with the fact that calls > with same parameters returns the same result? > > > ---- > Cosmia > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From semen at trygub.com Thu Mar 27 12:09:25 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Thu, 27 Mar 2014 12:09:25 +0000 Subject: [Haskell-cafe] strange error message In-Reply-To: References: <20140327023644.GD34466@inanna.trygub.com> Message-ID: <20140327120925.GB38345@inanna.trygub.com> Hi Ivan, On Thu, Mar 27, 2014 at 11:28:33AM +0000, Ivan Perez wrote: > What is the type of head? > What is the type of length? > What is the type of length.head? > What is the type of r? Prelude> :t head head :: [a] -> a Prelude> :t length length :: [a] -> Int Prelude> :t (length . head) (length . head) :: [[a]] -> Int Prelude> r is of type Int. [Apologies ? I thought the above is deducable from the error message I've included (below).] Clearly, this is a type error as Int is passed in where [[a]] is expected. However, my question is relating to the middle bit of the error message, namely: (The function `length . head' is applied to one argument, but its type `[[a2]] -> Int' has only one) Many thanks, S. > On 27 March 2014 02:36, Semen Trygubenko / ????? ?????????? < > semen at trygub.com> wrote: > > > Dear Haskell-Cafe, > > > > Every now and then I get error messages when compiling Haskell code :). > > Sometimes of the sort: > > > > test.hs:10:15: > > Couldn't match type `[[a2]]' with `Int' > > Expected type: Int -> Int > > Actual type: [[a2]] -> Int > > The function `length . head' is applied to one argument, > > but its type `[[a2]] -> Int' has only one > > In the first argument of `(==)', namely `(length . head) r' > > In the expression: (length . head) r == 0 > > > > Is the middle part of the error message > > > > (The function `length . head' is applied to one argument, > > but its type `[[a2]] -> Int' has only one) > > > > expected to be confusing like that sometimes? > > > > The line in question, FWIW, is > > > > Right r -> if (length . head) r == 0 > > > > It appears as one of the two entries in a case statement, pattern matching > > on Right constructor. > > > > Many thanks, > > S. > > > > > > > > -- > > ????? ?????????? http://trygub.com > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From hesselink at gmail.com Thu Mar 27 12:16:03 2014 From: hesselink at gmail.com (Erik Hesselink) Date: Thu, 27 Mar 2014 13:16:03 +0100 Subject: [Haskell-cafe] strange error message In-Reply-To: <20140327120925.GB38345@inanna.trygub.com> References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> Message-ID: Could you create a code snippet that reproduces the error? Erik On Thu, Mar 27, 2014 at 1:09 PM, Semen Trygubenko / ????? ?????????? wrote: > Hi Ivan, > > On Thu, Mar 27, 2014 at 11:28:33AM +0000, Ivan Perez wrote: >> What is the type of head? >> What is the type of length? >> What is the type of length.head? >> What is the type of r? > > Prelude> :t head > head :: [a] -> a > Prelude> :t length > length :: [a] -> Int > Prelude> :t (length . head) > (length . head) :: [[a]] -> Int > Prelude> > > r is of type Int. > > [Apologies ? I thought the above is deducable from the error message I've included (below).] > > Clearly, this is a type error as Int is passed in where [[a]] is expected. > However, my question is relating to the middle bit of the error message, > namely: > > (The function `length . head' is applied to one argument, > but its type `[[a2]] -> Int' has only one) > > Many thanks, > S. > > > > >> On 27 March 2014 02:36, Semen Trygubenko / ????? ?????????? < >> semen at trygub.com> wrote: >> >> > Dear Haskell-Cafe, >> > >> > Every now and then I get error messages when compiling Haskell code :). >> > Sometimes of the sort: >> > >> > test.hs:10:15: >> > Couldn't match type `[[a2]]' with `Int' >> > Expected type: Int -> Int >> > Actual type: [[a2]] -> Int >> > The function `length . head' is applied to one argument, >> > but its type `[[a2]] -> Int' has only one >> > In the first argument of `(==)', namely `(length . head) r' >> > In the expression: (length . head) r == 0 >> > >> > Is the middle part of the error message >> > >> > (The function `length . head' is applied to one argument, >> > but its type `[[a2]] -> Int' has only one) >> > >> > expected to be confusing like that sometimes? >> > >> > The line in question, FWIW, is >> > >> > Right r -> if (length . head) r == 0 >> > >> > It appears as one of the two entries in a case statement, pattern matching >> > on Right constructor. >> > >> > Many thanks, >> > S. >> > >> > >> > >> > -- >> > ????? ?????????? http://trygub.com >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> > > > -- > ????? ?????????? http://trygub.com > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From alois.cochard at gmail.com Thu Mar 27 12:21:35 2014 From: alois.cochard at gmail.com (Alois Cochard) Date: Thu, 27 Mar 2014 12:21:35 +0000 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <5333C55C.7050104@mansionfamily.plus.com> References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: I have good experience with actors (Scala/Akka), and I can tell you that you should avoid them as much as possible. I think the model is good if you need to do some low level concurrency coding on a language that don't have effect tracking in types. Having used the Async library from Marlow, I highly recommend it... and it probably cover a big percentage of traditional concurrency use cases. You still have Haskell Cloud if you want distributed messaging. Cheers On 27 March 2014 06:29, james wrote: > Having been introduced to actors by looking at Erlang, I discovered Akka. > > It seems that the performance is pretty impressive and I like the model. > > There seem to be several basic Actor libraries in Hackage, but they don't > seem > to be very actively developed. > > I'm more interested in the model for programming within a single runtime > than I am for distributed systems, but message and dispatch performance > definitely is important. > > Can anyone share experiences with the different packages? Is any one > of them stand-out? > > Thanks > James > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- *Alois Cochard* http://aloiscochard.blogspot.com http://twitter.com/aloiscochard http://github.com/aloiscochard -------------- next part -------------- An HTML attachment was scrubbed... URL: From shumovichy at gmail.com Thu Mar 27 12:23:35 2014 From: shumovichy at gmail.com (Yuras Shumovich) Date: Thu, 27 Mar 2014 15:23:35 +0300 Subject: [Haskell-cafe] strange error message In-Reply-To: References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> Message-ID: <1395923015.4670.0.camel@shum-lt> Hi, It seems to be already fixed: https://ghc.haskell.org/trac/ghc/changeset/b988dc39a06278acc2373ba9a40ee08da0127411/ghc Thanks, Yuras On Thu, 2014-03-27 at 13:16 +0100, Erik Hesselink wrote: > Could you create a code snippet that reproduces the error? > > Erik > > On Thu, Mar 27, 2014 at 1:09 PM, Semen Trygubenko / ????? ?????????? > wrote: > > Hi Ivan, > > > > On Thu, Mar 27, 2014 at 11:28:33AM +0000, Ivan Perez wrote: > >> What is the type of head? > >> What is the type of length? > >> What is the type of length.head? > >> What is the type of r? > > > > Prelude> :t head > > head :: [a] -> a > > Prelude> :t length > > length :: [a] -> Int > > Prelude> :t (length . head) > > (length . head) :: [[a]] -> Int > > Prelude> > > > > r is of type Int. > > > > [Apologies ? I thought the above is deducable from the error message I've included (below).] > > > > Clearly, this is a type error as Int is passed in where [[a]] is expected. > > However, my question is relating to the middle bit of the error message, > > namely: > > > > (The function `length . head' is applied to one argument, > > but its type `[[a2]] -> Int' has only one) > > > > Many thanks, > > S. > > > > > > > > > >> On 27 March 2014 02:36, Semen Trygubenko / ????? ?????????? < > >> semen at trygub.com> wrote: > >> > >> > Dear Haskell-Cafe, > >> > > >> > Every now and then I get error messages when compiling Haskell code :). > >> > Sometimes of the sort: > >> > > >> > test.hs:10:15: > >> > Couldn't match type `[[a2]]' with `Int' > >> > Expected type: Int -> Int > >> > Actual type: [[a2]] -> Int > >> > The function `length . head' is applied to one argument, > >> > but its type `[[a2]] -> Int' has only one > >> > In the first argument of `(==)', namely `(length . head) r' > >> > In the expression: (length . head) r == 0 > >> > > >> > Is the middle part of the error message > >> > > >> > (The function `length . head' is applied to one argument, > >> > but its type `[[a2]] -> Int' has only one) > >> > > >> > expected to be confusing like that sometimes? > >> > > >> > The line in question, FWIW, is > >> > > >> > Right r -> if (length . head) r == 0 > >> > > >> > It appears as one of the two entries in a case statement, pattern matching > >> > on Right constructor. > >> > > >> > Many thanks, > >> > S. > >> > > >> > > >> > > >> > -- > >> > ????? ?????????? http://trygub.com > >> > > >> > _______________________________________________ > >> > Haskell-Cafe mailing list > >> > Haskell-Cafe at haskell.org > >> > http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > > >> > > > > > -- > > ????? ?????????? http://trygub.com > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From semen at trygub.com Thu Mar 27 14:50:07 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Thu, 27 Mar 2014 14:50:07 +0000 Subject: [Haskell-cafe] strange error message In-Reply-To: <1395923015.4670.0.camel@shum-lt> References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> <1395923015.4670.0.camel@shum-lt> Message-ID: <20140327145007.GA39257@inanna.trygub.com> On Thu, Mar 27, 2014 at 03:23:35PM +0300, Yuras Shumovich wrote: > It seems to be already fixed: > https://ghc.haskell.org/trac/ghc/changeset/b988dc39a06278acc2373ba9a40ee08da0127411/ghc Ah! Great ? in ghc 7.8. Until then let's ignore the middle statement (indeed I thought it might be a bug) ? I've replaced it with " below: test.hs:10:15: Couldn't match type `[[a2]]' with `Int' Expected type: Int -> Int Actual type: [[a2]] -> Int In the first argument of `(==)', namely `(length . head) r' In the expression: (length . head) r == 0 (1) Why are we biasing the programmer to expect one thing (the function is wrong) and not the other (r is wrong)? I.e., would the programmer benefit from inclusion of the "alternative view" as well? (2) Is it worth stating the context next to the "expected type" message, so that it is clearer what "[[a2]] -> Int" and "expected type" refer to? E.g., test.hs:10:15: Couldn't match type `[[a2]]' with `Int' Actual type (length . head) :: [[a2]] -> Int Expected type :: Int -> Int OR Actual type r :: Int Expected type :: [[a2]] In the first argument of `(==)', namely `(length . head) r' In the expression: (length . head) r == 0 Many thanks for your kind hel4p, S. > > > Thanks, > Yuras > > On Thu, 2014-03-27 at 13:16 +0100, Erik Hesselink wrote: > > Could you create a code snippet that reproduces the error? > > > > Erik > > > > On Thu, Mar 27, 2014 at 1:09 PM, Semen Trygubenko / ????? ?????????? > > wrote: > > > Hi Ivan, > > > > > > On Thu, Mar 27, 2014 at 11:28:33AM +0000, Ivan Perez wrote: > > >> What is the type of head? > > >> What is the type of length? > > >> What is the type of length.head? > > >> What is the type of r? > > > > > > Prelude> :t head > > > head :: [a] -> a > > > Prelude> :t length > > > length :: [a] -> Int > > > Prelude> :t (length . head) > > > (length . head) :: [[a]] -> Int > > > Prelude> > > > > > > r is of type Int. > > > > > > [Apologies ? I thought the above is deducible from the error message I've included (below).] > > > > > > Clearly, this is a type error as Int is passed in where [[a]] is expected. > > > However, my question is relating to the middle bit of the error message, > > > namely: > > > > > > (The function `length . head' is applied to one argument, > > > but its type `[[a2]] -> Int' has only one) > > > > > > Many thanks, > > > S. > > > > > > > > > > > > > > >> On 27 March 2014 02:36, Semen Trygubenko / ????? ?????????? < > > >> semen at trygub.com> wrote: > > >> > > >> > Dear Haskell-Cafe, > > >> > > > >> > Every now and then I get error messages when compiling Haskell code :). > > >> > Sometimes of the sort: > > >> > > > >> > test.hs:10:15: > > >> > Couldn't match type `[[a2]]' with `Int' > > >> > Expected type: Int -> Int > > >> > Actual type: [[a2]] -> Int > > >> > The function `length . head' is applied to one argument, > > >> > but its type `[[a2]] -> Int' has only one > > >> > In the first argument of `(==)', namely `(length . head) r' > > >> > In the expression: (length . head) r == 0 > > >> > > > >> > Is the middle part of the error message > > >> > > > >> > (The function `length . head' is applied to one argument, > > >> > but its type `[[a2]] -> Int' has only one) > > >> > > > >> > expected to be confusing like that sometimes? > > >> > > > >> > The line in question, FWIW, is > > >> > > > >> > Right r -> if (length . head) r == 0 > > >> > > > >> > It appears as one of the two entries in a case statement, pattern matching > > >> > on Right constructor. > > >> > > > >> > Many thanks, > > >> > S. > > >> > > > >> > > > >> > > > >> > -- > > >> > ????? ?????????? http://trygub.com > > >> > > > >> > _______________________________________________ > > >> > Haskell-Cafe mailing list > > >> > Haskell-Cafe at haskell.org > > >> > http://www.haskell.org/mailman/listinfo/haskell-cafe > > >> > > > >> > > > > > > > -- > > > ????? ?????????? http://trygub.com > > > > > > _______________________________________________ > > > Haskell-Cafe mailing list > > > Haskell-Cafe at haskell.org > > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From carette at mcmaster.ca Thu Mar 27 16:49:02 2014 From: carette at mcmaster.ca (Jacques Carette) Date: Thu, 27 Mar 2014 12:49:02 -0400 Subject: [Haskell-cafe] 2 PhD positions at McMaster Message-ID: <5334567E.5010200@mcmaster.ca> [The underlying tools in this work will most likely be done in Haskell] PhD Positions Available in the Computing and Software Department at McMaster University For excellent candidates, two PhD positions are available in the Computing and Software Department at McMaster University, in Hamilton, Ontario, Canada. The positions will focus on developing certifiable scientific and engineering software using a Literate Process that eliminates duplication between software artifacts and explicitly incorporates traceability between these artifacts. The motivating case study for the research will be nuclear safety analysis software. Applicants should have a strong background in software engineering or computer science, mathematical maturity and experience with technology and software development. Knowledge of computational mathematics and physics will be considered an asset. Due to the funding model, preference will be given to domestic students or landed immigrants in Canada. Interested candidates should apply for graduate studies with the Computing and Software Department (http://www.cas.mcmaster.ca/cas/0template1.php?1002) and they should send an e-mail expressing interest to one of the project supervisors: Dr. Spencer Smith (smiths at mcmaster.ca), Dr. Jacques Carette (carette at mcmaster.ca) or Dr. Ned Nedialkov (nedialk at mcmaster.ca). Applicants will be accepted until the two positions are filled. The projected start date is September 2014, but this is negotiable. Please feel free to forward this advertisement to any potentially interested candidates. -- Jacques -------------- next part -------------- An HTML attachment was scrubbed... URL: From zongheng.y at gmail.com Thu Mar 27 17:21:08 2014 From: zongheng.y at gmail.com (Zongheng Yang) Date: Thu, 27 Mar 2014 10:21:08 -0700 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: Can anyone give some detailed cons of Akka / actor model? On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard wrote: > I have good experience with actors (Scala/Akka), and I can tell you that you > should avoid them as much as possible. > I think the model is good if you need to do some low level concurrency > coding on a language that don't have effect tracking in types. > > Having used the Async library from Marlow, I highly recommend it... and it > probably cover a big percentage of traditional concurrency use cases. > > You still have Haskell Cloud if you want distributed messaging. > > Cheers > > > > On 27 March 2014 06:29, james wrote: >> >> Having been introduced to actors by looking at Erlang, I discovered Akka. >> >> It seems that the performance is pretty impressive and I like the model. >> >> There seem to be several basic Actor libraries in Hackage, but they don't >> seem >> to be very actively developed. >> >> I'm more interested in the model for programming within a single runtime >> than I am for distributed systems, but message and dispatch performance >> definitely is important. >> >> Can anyone share experiences with the different packages? Is any one >> of them stand-out? >> >> Thanks >> James >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > -- > Alois Cochard > http://aloiscochard.blogspot.com > http://twitter.com/aloiscochard > http://github.com/aloiscochard > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From cma at bitemyapp.com Thu Mar 27 17:22:15 2014 From: cma at bitemyapp.com (Christopher Allen) Date: Thu, 27 Mar 2014 12:22:15 -0500 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: To make the point more explicit. Usually people use actors or agents because they want effect isolation, but in Haskell nothing is going to escape your notice on that front. If you want to expand the scope of what in your codebase is *pure*, thereby relegating side-effects to only the functions that *have* to be side-effecting, then you might consider turning your problem into a Free Monad, where there's a pure DSL and pure functions that manipulate only the DSL with a separate effectful interpreter for execution. New people without a firm grasp of monadic DSLs can sometimes find the concept alien, so it's not something you should feel is obligatory. I would first seek to simply write code that solves your problem in Haskell, maybe with the use of Async, then refine afterward with a couple of tests written. Relevant links: http://www.haskellforall.com/2012/06/you-could-have-invented-free-monads.html https://www.fpcomplete.com/user/dolio/many-roads-to-free-monads http://www.haskellforall.com/2012/07/purify-code-using-free-monads.html http://www.haskellforall.com/2012/07/free-monad-transformers.html Cheers, Chris On Thu, Mar 27, 2014 at 2:32 AM, Carter Schonwald < carter.schonwald at gmail.com> wrote: > I'm inclined to agree with Chris, > in the shared heap setting, you really should try those other approaches > first! > > > On Thu, Mar 27, 2014 at 2:32 AM, Christopher Allen wrote: > >> Have you looked at the Async library or Marlow's book? >> >> http://hackage.haskell.org/package/async >> >> http://chimera.labs.oreilly.com/books/1230000000929/ >> >> Neither involve actors but I think many Haskellers, myself included, are >> skeptical of actor/agent systems. I've written a fair bit of Clojure and >> Scala code and don't much care for the model. >> >> If all you really need is message passing/dispatch, you don't strictly >> speaking need actors. Channels, messages, and dataflow might very well be >> enough. Perhaps look into functional reactive programming as well? >> >> Cheers, hope this helps. >> >> --- Chris >> >> >> >> On Thu, Mar 27, 2014 at 1:29 AM, james wrote: >> >>> Having been introduced to actors by looking at Erlang, I discovered Akka. >>> >>> It seems that the performance is pretty impressive and I like the model. >>> >>> There seem to be several basic Actor libraries in Hackage, but they >>> don't seem >>> to be very actively developed. >>> >>> I'm more interested in the model for programming within a single runtime >>> than I am for distributed systems, but message and dispatch performance >>> definitely is important. >>> >>> Can anyone share experiences with the different packages? Is any one >>> of them stand-out? >>> >>> Thanks >>> James >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > -------------- next part -------------- An HTML attachment was scrubbed... URL: From cma at bitemyapp.com Thu Mar 27 17:28:00 2014 From: cma at bitemyapp.com (Christopher Allen) Date: Thu, 27 Mar 2014 12:28:00 -0500 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: I don't actually want to get drawn into this, but one point would be that it's really just the same fallacies as OOP in general, but concurrent. The idea that isolation behind an interface (message passing or not) is going to prevent unnecessary mutation or side effects from getting out of control. In practice, it doesn't do that at all and the fact that you're making your inter-dependencies more implicit, rather than explicit, through the use of isolated buckets of side-effecting state and mutation is going to make it harder rather than easier to debug the program when it invariably breaks. I'd rather get a call-stack if I'm going to abandon Haskell-y goodness. And your Actors *will* get into a bad state, so you'll end up writing Inspector and Debugger mixins just to keep a handle on the complexity when they get into that bad state. It's not impossible for Actors to make sense. I used agents (which are not full-blown Actors per se) in Clojure for side-effect isolation, serialization, and thread safety to good effect, but I kept how much "work" they did to a bare minimum and tried to keep everything in pure functions as long as I could. It's just that I see programmers with a shiny new hammer looking for every nail they can find. On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang wrote: > Can anyone give some detailed cons of Akka / actor model? > > On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard > wrote: > > I have good experience with actors (Scala/Akka), and I can tell you that > you > > should avoid them as much as possible. > > I think the model is good if you need to do some low level concurrency > > coding on a language that don't have effect tracking in types. > > > > Having used the Async library from Marlow, I highly recommend it... and > it > > probably cover a big percentage of traditional concurrency use cases. > > > > You still have Haskell Cloud if you want distributed messaging. > > > > Cheers > > > > > > > > On 27 March 2014 06:29, james wrote: > >> > >> Having been introduced to actors by looking at Erlang, I discovered > Akka. > >> > >> It seems that the performance is pretty impressive and I like the model. > >> > >> There seem to be several basic Actor libraries in Hackage, but they > don't > >> seem > >> to be very actively developed. > >> > >> I'm more interested in the model for programming within a single runtime > >> than I am for distributed systems, but message and dispatch performance > >> definitely is important. > >> > >> Can anyone share experiences with the different packages? Is any one > >> of them stand-out? > >> > >> Thanks > >> James > >> > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > -- > > Alois Cochard > > http://aloiscochard.blogspot.com > > http://twitter.com/aloiscochard > > http://github.com/aloiscochard > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From nithande at student.chalmers.se Thu Mar 27 17:51:26 2014 From: nithande at student.chalmers.se (Victor Nithander) Date: Thu, 27 Mar 2014 18:51:26 +0100 Subject: [Haskell-cafe] Feedback/Ideas for a Master Thesis about creating a Querying Tool for Hackage Message-ID: Hi, My name is Victor Nithander and I am currently doing my Master Thesis at the Computer Science and Engineering department at Chalmers in Gothenburg and would like to ask you for some help. My Master Thesis is about creating a querying tool for Hackage written in Haskell and I would like to know what kind of features you would like the querying tool to have. My plan is to design and implement an embedded language for queries to be expressed in and then implement a backend which accordingly takes care of those queries. I then plan to packet the tool as a package using Cabal and upload it to Hackage. Any feedback/ideas on features or other things about the tool would be greatly appreciated as I want to make a tool which benefits the community as much as possible. Examples of queries I'm thinking of to implement is: - Which language features (such as typeclass instances) does a certain package use? - How many packages uses a certain language feature? - Which packages does a certain package depend on? - Which packages depends on a certain package? Of course, this in no way limits what other type of queries could be made. I will also post this at the Haskell Section of reddit at http://www.reddit.com/r/haskell/, sorry for the redundancy. Feel free to respond to this either at this mailing list, at reddit, or as a personal email at nithande at student.chalmers.se though I think the best would be to have an open discussion about it. Thanks in advance! / Victor -------------- next part -------------- An HTML attachment was scrubbed... URL: From ky3 at atamo.com Thu Mar 27 18:47:02 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Fri, 28 Mar 2014 01:47:02 +0700 Subject: [Haskell-cafe] strange error message In-Reply-To: <20140327145007.GA39257@inanna.trygub.com> References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> <1395923015.4670.0.camel@shum-lt> <20140327145007.GA39257@inanna.trygub.com> Message-ID: On Thu, Mar 27, 2014 at 9:50 PM, Semen Trygubenko / ????? ?????????? < semen at trygub.com> wrote: > (1) Why are we biasing the programmer to expect > one thing (the function is wrong) and not the other (r is wrong)? > I.e., would the programmer benefit from inclusion of the "alternative > view" as well? > The error message isn't really pointing blame, it's just saying, "Yo, I'm stuck at this stage of the inference algorithm so I'm sending the ball back into your court." But you do have a point. That said, after a certain amount of experience with ghc, one learns to quickly scan the errors for key bits. The 'alternative view' repeats essentially the same info twice and including it doubles the amount of spew-out. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From Coeus at gmx.de Thu Mar 27 19:07:59 2014 From: Coeus at gmx.de (Marc Ziegert) Date: Thu, 27 Mar 2014 20:07:59 +0100 Subject: [Haskell-cafe] Main function variables made global. In-Reply-To: <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> References: <47a0a6d2c368496f96d59c48521e007d@DBXPR01MB015.eurprd01.prod.exchangelabs.com>, <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> Message-ID: An HTML attachment was scrubbed... URL: From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Thu Mar 27 19:16:52 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Thu, 27 Mar 2014 19:16:52 +0000 Subject: [Haskell-cafe] Main function variables made global. In-Reply-To: References: <47a0a6d2c368496f96d59c48521e007d@DBXPR01MB015.eurprd01.prod.exchangelabs.com> <803f9ef02a1c4e98a9b2db4c8a4d151f@DBXPR01MB015.eurprd01.prod.exchangelabs.com> Message-ID: <20140327191652.GI26219@weber> On Thu, Mar 27, 2014 at 08:07:59PM +0100, Marc Ziegert wrote: > It seems to me you are asking for this unsafePerformIO hack [...] I don't think that's the case at all. It seems to be a simple case of lifting a partial application into the IO monad. There's nothing strange about it. Tom From james at mansionfamily.plus.com Thu Mar 27 21:40:59 2014 From: james at mansionfamily.plus.com (james) Date: Thu, 27 Mar 2014 21:40:59 +0000 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> Message-ID: <53349AEB.2000808@mansionfamily.plus.com> On 27/03/2014 17:28, Christopher Allen wrote: > I don't actually want to get drawn into this, but one point would be > that it's really just the same fallacies as OOP in general, but > concurrent. Well, horses for courses, I've been writing distributed C++ apps since cfront was shiny and new. I find writing off OOP as distasteful as writing off functional, and there are people in both camps. I have ordered Simon's book and will take care to read it. In the mean time - does anyone have an answer to the question I asked? James > The idea that isolation behind an interface (message passing or not) > is going to prevent unnecessary mutation or side effects from getting > out of control. > > In practice, it doesn't do that at all and the fact that you're making > your inter-dependencies more implicit, rather than explicit, through > the use of isolated buckets of side-effecting state and mutation is > going to make it harder rather than easier to debug the program when > it invariably breaks. I'd rather get a call-stack if I'm going to > abandon Haskell-y goodness. And your Actors *will* get into a bad > state, so you'll end up writing Inspector and Debugger mixins just to > keep a handle on the complexity when they get into that bad state. > > It's not impossible for Actors to make sense. I used agents (which are > not full-blown Actors per se) in Clojure for side-effect isolation, > serialization, and thread safety to good effect, but I kept how much > "work" they did to a bare minimum and tried to keep everything in pure > functions as long as I could. > > It's just that I see programmers with a shiny new hammer looking for > every nail they can find. > > > > On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang > wrote: > > Can anyone give some detailed cons of Akka / actor model? > > On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard > > wrote: > > I have good experience with actors (Scala/Akka), and I can tell > you that you > > should avoid them as much as possible. > > I think the model is good if you need to do some low level > concurrency > > coding on a language that don't have effect tracking in types. > > > > Having used the Async library from Marlow, I highly recommend > it... and it > > probably cover a big percentage of traditional concurrency use > cases. > > > > You still have Haskell Cloud if you want distributed messaging. > > > > Cheers > > > > > > > > On 27 March 2014 06:29, james > wrote: > >> > >> Having been introduced to actors by looking at Erlang, I > discovered Akka. > >> > >> It seems that the performance is pretty impressive and I like > the model. > >> > >> There seem to be several basic Actor libraries in Hackage, but > they don't > >> seem > >> to be very actively developed. > >> > >> I'm more interested in the model for programming within a > single runtime > >> than I am for distributed systems, but message and dispatch > performance > >> definitely is important. > >> > >> Can anyone share experiences with the different packages? Is > any one > >> of them stand-out? > >> > >> Thanks > >> James > >> > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > > > > > > > > > > -- > > Alois Cochard > > http://aloiscochard.blogspot.com > > http://twitter.com/aloiscochard > > http://github.com/aloiscochard > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Thu Mar 27 21:46:46 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Thu, 27 Mar 2014 17:46:46 -0400 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <53349AEB.2000808@mansionfamily.plus.com> References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> Message-ID: the various "actor" libs are all different, and they make different trade offs, theres no "this is best" (yet). I'm personally unsatisfied with the solutions i've seen in haskell and other languages personally, so i'm sorely tempted to yak have my own and thus contribute to the confusion even more :) On Thu, Mar 27, 2014 at 5:40 PM, james wrote: > On 27/03/2014 17:28, Christopher Allen wrote: > > I don't actually want to get drawn into this, but one point would be > that it's really just the same fallacies as OOP in general, but concurrent. > > > Well, horses for courses, I've been writing distributed C++ apps since > cfront was shiny and new. > > I find writing off OOP as distasteful as writing off functional, and there > are people in both camps. > > I have ordered Simon's book and will take care to read it. > > In the mean time - does anyone have an answer to the question I asked? > > James > > > The idea that isolation behind an interface (message passing or not) is > going to prevent unnecessary mutation or side effects from getting out of > control. > > In practice, it doesn't do that at all and the fact that you're making > your inter-dependencies more implicit, rather than explicit, through the > use of isolated buckets of side-effecting state and mutation is going to > make it harder rather than easier to debug the program when it invariably > breaks. I'd rather get a call-stack if I'm going to abandon Haskell-y > goodness. And your Actors *will* get into a bad state, so you'll end up > writing Inspector and Debugger mixins just to keep a handle on the > complexity when they get into that bad state. > > It's not impossible for Actors to make sense. I used agents (which are > not full-blown Actors per se) in Clojure for side-effect isolation, > serialization, and thread safety to good effect, but I kept how much "work" > they did to a bare minimum and tried to keep everything in pure functions > as long as I could. > > It's just that I see programmers with a shiny new hammer looking for > every nail they can find. > > > > On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang wrote: > >> Can anyone give some detailed cons of Akka / actor model? >> >> On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard >> wrote: >> > I have good experience with actors (Scala/Akka), and I can tell you >> that you >> > should avoid them as much as possible. >> > I think the model is good if you need to do some low level concurrency >> > coding on a language that don't have effect tracking in types. >> > >> > Having used the Async library from Marlow, I highly recommend it... and >> it >> > probably cover a big percentage of traditional concurrency use cases. >> > >> > You still have Haskell Cloud if you want distributed messaging. >> > >> > Cheers >> > >> > >> > >> > On 27 March 2014 06:29, james wrote: >> >> >> >> Having been introduced to actors by looking at Erlang, I discovered >> Akka. >> >> >> >> It seems that the performance is pretty impressive and I like the >> model. >> >> >> >> There seem to be several basic Actor libraries in Hackage, but they >> don't >> >> seem >> >> to be very actively developed. >> >> >> >> I'm more interested in the model for programming within a single >> runtime >> >> than I am for distributed systems, but message and dispatch performance >> >> definitely is important. >> >> >> >> Can anyone share experiences with the different packages? Is any one >> >> of them stand-out? >> >> >> >> Thanks >> >> James >> >> >> >> >> >> _______________________________________________ >> >> Haskell-Cafe mailing list >> >> Haskell-Cafe at haskell.org >> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> > >> > >> > >> > -- >> > Alois Cochard >> > http://aloiscochard.blogspot.com >> > http://twitter.com/aloiscochard >> > http://github.com/aloiscochard >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From semen at trygub.com Thu Mar 27 22:12:58 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Thu, 27 Mar 2014 22:12:58 +0000 Subject: [Haskell-cafe] strange error message In-Reply-To: References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> <1395923015.4670.0.camel@shum-lt> <20140327145007.GA39257@inanna.trygub.com> Message-ID: <20140327221258.GA41469@inanna.trygub.com> Hi Kim-Ee, On Fri, Mar 28, 2014 at 01:47:02AM +0700, Kim-Ee Yeoh wrote: > On Thu, Mar 27, 2014 at 9:50 PM, Semen Trygubenko / ????? ?????????? < > semen at trygub.com> wrote: > > > (1) Why are we biasing the programmer to expect > > one thing (the function is wrong) and not the other (r is wrong)? > > I.e., would the programmer benefit from inclusion of the "alternative > > view" as well? > > > > The error message isn't really pointing blame, it's just saying, "Yo, I'm > stuck at this stage of the inference algorithm so I'm sending the ball back > into your court." Yet it is using words "actual" and "expected" in the output, which can be taken as a gospel by newbies [ or professionals in an emergency ;) ]. > But you do have a point. Thanks! > That said, after a certain amount of experience with ghc, one learns to > quickly scan the errors for key bits. I agree ? all the information is there, it's just hard to see it sometimes. :) E.g., earlier in this thread someone was asking about types of entities involved. Anything that can decrease the amount of staring at the type error is good, IMHO. And this is such a cheap modification ? changing the way the type checker output looks! > The 'alternative view' repeats > essentially the same info twice and including it doubles the amount of > spew-out. Good point (re amount of spew-out). However, I believe both types should be mentioned, as one is as likely to be wrong as the other. If we are outputting it like that (i.e., one of the two, not both) and care about the amount of output, why are we not outputting the less complex type of the two types involved in a mismatch? r would certainly win that contest. IMHO, I don't think word "expected" is a great word to use here. (length . head) expects to be fed [[a2]] as much as r expects it should be passed into to functions that take Int. ghc should "expect" us to change (length . head) to take Int as much as it "expects" us to fix r to be of type [[a2]]. How about this: test.hs:10:15: Couldn't match type `[[a2]]' with `Int' (length . head) :: [[a2]] -> Int r :: Int In the first argument of `(==)', namely `(length . head) r' In the expression: (length . head) r == 0 ? Thank you, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From amindfv at gmail.com Thu Mar 27 22:34:53 2014 From: amindfv at gmail.com (amindfv at gmail.com) Date: Thu, 27 Mar 2014 18:34:53 -0400 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <53349AEB.2000808@mansionfamily.plus.com> References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> Message-ID: <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> Unfortunately I can't help with recommending an actor library. I think peoples' responses of "you should never want to do that" are, um, unhelpful. That said, i've written both haskell and erlang professionally, and never had a need for actors/message passing in haskell. It may be the wrong tool for most haskell jobs. The main things erlang-style concurrency gets you are - lightweight threads (in haskell by default -- 'forkIO' creates lightweight threads) - limited shared mutable state (haskell's pure) - spreading computation over cores (in haskell you want parallelism not concurrency -- check out the Par monad) - computation over boxes (see distributed-process) To do "message passing", check out MVars (and later, STM) Tom El Mar 27, 2014, a las 17:40, james escribi?: > On 27/03/2014 17:28, Christopher Allen wrote: >> I don't actually want to get drawn into this, but one point would be that it's really just the same fallacies as OOP in general, but concurrent. > > Well, horses for courses, I've been writing distributed C++ apps since cfront was shiny and new. > > I find writing off OOP as distasteful as writing off functional, and there are people in both camps. > > I have ordered Simon's book and will take care to read it. > > In the mean time - does anyone have an answer to the question I asked? > > James > >> The idea that isolation behind an interface (message passing or not) is going to prevent unnecessary mutation or side effects from getting out of control. >> >> In practice, it doesn't do that at all and the fact that you're making your inter-dependencies more implicit, rather than explicit, through the use of isolated buckets of side-effecting state and mutation is going to make it harder rather than easier to debug the program when it invariably breaks. I'd rather get a call-stack if I'm going to abandon Haskell-y goodness. And your Actors *will* get into a bad state, so you'll end up writing Inspector and Debugger mixins just to keep a handle on the complexity when they get into that bad state. >> >> It's not impossible for Actors to make sense. I used agents (which are not full-blown Actors per se) in Clojure for side-effect isolation, serialization, and thread safety to good effect, but I kept how much "work" they did to a bare minimum and tried to keep everything in pure functions as long as I could. >> >> It's just that I see programmers with a shiny new hammer looking for every nail they can find. >> >> >> >> On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang wrote: >>> Can anyone give some detailed cons of Akka / actor model? >>> >>> On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard wrote: >>> > I have good experience with actors (Scala/Akka), and I can tell you that you >>> > should avoid them as much as possible. >>> > I think the model is good if you need to do some low level concurrency >>> > coding on a language that don't have effect tracking in types. >>> > >>> > Having used the Async library from Marlow, I highly recommend it... and it >>> > probably cover a big percentage of traditional concurrency use cases. >>> > >>> > You still have Haskell Cloud if you want distributed messaging. >>> > >>> > Cheers >>> > >>> > >>> > >>> > On 27 March 2014 06:29, james wrote: >>> >> >>> >> Having been introduced to actors by looking at Erlang, I discovered Akka. >>> >> >>> >> It seems that the performance is pretty impressive and I like the model. >>> >> >>> >> There seem to be several basic Actor libraries in Hackage, but they don't >>> >> seem >>> >> to be very actively developed. >>> >> >>> >> I'm more interested in the model for programming within a single runtime >>> >> than I am for distributed systems, but message and dispatch performance >>> >> definitely is important. >>> >> >>> >> Can anyone share experiences with the different packages? Is any one >>> >> of them stand-out? >>> >> >>> >> Thanks >>> >> James >>> >> >>> >> >>> >> _______________________________________________ >>> >> Haskell-Cafe mailing list >>> >> Haskell-Cafe at haskell.org >>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> > >>> > >>> > >>> > >>> > -- >>> > Alois Cochard >>> > http://aloiscochard.blogspot.com >>> > http://twitter.com/aloiscochard >>> > http://github.com/aloiscochard >>> > >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > Haskell-Cafe at haskell.org >>> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> > >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander.vershilov at gmail.com Thu Mar 27 23:03:29 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Fri, 28 Mar 2014 03:03:29 +0400 Subject: [Haskell-cafe] [ANN] network-transport-zeromq-0.1. Message-ID: Hi, I'm happy to announce a new network-transport backend based on the 0MQ brokerless protocol [1]. This implementation makes it possible to the wealth of ZeroMQ transports through a simple and shared API. In particular, ZeroMQ supports authenticated communication channels, encryption, efficient multicast and throughput enhancement techniques such as message batching. Wrapping a subset of the ZeroMQ API behind the network-transport API makes it possible for a wealth of higher-level libraries such as distributed-process and HdpH to communicate over ZeroMQ seamlessly, with little to no modification necessary. Network transport zeromq provides: * basic network transport API, ability to use channels and send messages over reliable connections between endpoints. * multicasting. Multicasting reliable and ordered in absence of a long network failures, i.e. if message A is send before message B, then message A will be delivered before message B to every subscriber in multicast group. * basic plain text authorization. * 0mq driven reliability. (automatic connection restart without message loose). * ability mark connections as broken, this may be required to stop automatic reconnect. We currently have a few performance issues that cause a consistent 30% slowdown in performance of network-transport-zmq over TCP, but we?re working on it. ZeroMQ should in fact *improve* performance over raw TCP in many use cases thanks to intelligent batching of queued messages. Current approach is an early release of the library in order to gather feedback. There is a large TODO list with a set of features that may be useful for a big set of use cases like different authorization mechanisms including certificate based, support of connection encryption, support for unreliable connections, heartbeating and service discovery support. This features will be implemented in short milestones. While we believe network-transport-zmq to be useful in its own right, it is only a stepping stone towards making the rich communication patterns implemented in ZeroMQ available through distributed-process. This will allow for writing ZeroMQ applications with all the power of the Process monad, supervision hierarchies, powerful type based matching abstractions and intuitive message sending primitives. All feedback are appreciated. If you have a commercial interest around this project then feel free to contact [2]. [1] http://zeromq.org/ [2] mailto:sales at tweag.io -- Alexander Vershilov mail-to: alexander.vershilov at tweag.io -- Alexander From patrick.john.wheeler at gmail.com Thu Mar 27 23:22:12 2014 From: patrick.john.wheeler at gmail.com (Patrick Wheeler) Date: Thu, 27 Mar 2014 23:22:12 +0000 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> Message-ID: @tom - forkIO and freineds works great for lightweight local threads, what about non-local threads though in a distributed setting. Is there anything in haskell that you think replaces that functionality in erlang? On Thu, Mar 27, 2014 at 10:34 PM, wrote: > Unfortunately I can't help with recommending an actor library. I think > peoples' responses of "you should never want to do that" are, um, unhelpful. > > That said, i've written both haskell and erlang professionally, and never > had a need for actors/message passing in haskell. It may be the wrong tool > for most haskell jobs. > > The main things erlang-style concurrency gets you are > - lightweight threads (in haskell by default -- 'forkIO' creates > lightweight threads) > - limited shared mutable state (haskell's pure) > - spreading computation over cores (in haskell you want parallelism not > concurrency -- check out the Par monad) > - computation over boxes (see distributed-process) > > To do "message passing", check out MVars (and later, STM) > > Tom > > > El Mar 27, 2014, a las 17:40, james > escribi?: > > On 27/03/2014 17:28, Christopher Allen wrote: > > I don't actually want to get drawn into this, but one point would be > that it's really just the same fallacies as OOP in general, but concurrent. > > > Well, horses for courses, I've been writing distributed C++ apps since > cfront was shiny and new. > > I find writing off OOP as distasteful as writing off functional, and there > are people in both camps. > > I have ordered Simon's book and will take care to read it. > > In the mean time - does anyone have an answer to the question I asked? > > James > > The idea that isolation behind an interface (message passing or not) is > going to prevent unnecessary mutation or side effects from getting out of > control. > > In practice, it doesn't do that at all and the fact that you're making > your inter-dependencies more implicit, rather than explicit, through the > use of isolated buckets of side-effecting state and mutation is going to > make it harder rather than easier to debug the program when it invariably > breaks. I'd rather get a call-stack if I'm going to abandon Haskell-y > goodness. And your Actors *will* get into a bad state, so you'll end up > writing Inspector and Debugger mixins just to keep a handle on the > complexity when they get into that bad state. > > It's not impossible for Actors to make sense. I used agents (which are > not full-blown Actors per se) in Clojure for side-effect isolation, > serialization, and thread safety to good effect, but I kept how much "work" > they did to a bare minimum and tried to keep everything in pure functions > as long as I could. > > It's just that I see programmers with a shiny new hammer looking for > every nail they can find. > > > > On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang wrote: > >> Can anyone give some detailed cons of Akka / actor model? >> >> On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard >> wrote: >> > I have good experience with actors (Scala/Akka), and I can tell you >> that you >> > should avoid them as much as possible. >> > I think the model is good if you need to do some low level concurrency >> > coding on a language that don't have effect tracking in types. >> > >> > Having used the Async library from Marlow, I highly recommend it... and >> it >> > probably cover a big percentage of traditional concurrency use cases. >> > >> > You still have Haskell Cloud if you want distributed messaging. >> > >> > Cheers >> > >> > >> > >> > On 27 March 2014 06:29, james wrote: >> >> >> >> Having been introduced to actors by looking at Erlang, I discovered >> Akka. >> >> >> >> It seems that the performance is pretty impressive and I like the >> model. >> >> >> >> There seem to be several basic Actor libraries in Hackage, but they >> don't >> >> seem >> >> to be very actively developed. >> >> >> >> I'm more interested in the model for programming within a single >> runtime >> >> than I am for distributed systems, but message and dispatch performance >> >> definitely is important. >> >> >> >> Can anyone share experiences with the different packages? Is any one >> >> of them stand-out? >> >> >> >> Thanks >> >> James >> >> >> >> >> >> _______________________________________________ >> >> Haskell-Cafe mailing list >> >> Haskell-Cafe at haskell.org >> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> > >> > >> > >> > -- >> > Alois Cochard >> > http://aloiscochard.blogspot.com >> > http://twitter.com/aloiscochard >> > http://github.com/aloiscochard >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- Patrick Wheeler Patrick.John.Wheeler at gmail.com Patrick.J.Wheeler at rice.edu Patrick.Wheeler at colorado.edu -------------- next part -------------- An HTML attachment was scrubbed... URL: From alexander.vershilov at gmail.com Fri Mar 28 01:28:54 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Fri, 28 Mar 2014 05:28:54 +0400 Subject: [Haskell-cafe] [ANN] network-transport-zeromq-0.1. In-Reply-To: References: Message-ID: Sorry, forgot to add a links: hackage: http://hackage.haskell.org/package/network-transport-zeromq github: https://github.com/tweag/network-transport-zeromq -- Alexander On 28 March 2014 03:03, Alexander V Vershilov wrote: > Hi, > > I'm happy to announce a new network-transport backend based on the 0MQ > brokerless protocol [1]. This implementation makes it possible to the > wealth of ZeroMQ transports through a simple and shared API. In > particular, ZeroMQ supports authenticated communication channels, > encryption, efficient multicast and throughput enhancement techniques > such as message batching. > > Wrapping a subset of the ZeroMQ API behind the network-transport API > makes it possible for a wealth of higher-level libraries such as > distributed-process and HdpH to communicate over ZeroMQ seamlessly, > with little to no modification necessary. > > Network transport zeromq provides: > * basic network transport API, ability to use channels and send > messages over reliable connections between endpoints. > * multicasting. Multicasting reliable and ordered in absence of a long > network failures, i.e. if message A is send before message B, then > message A will be delivered before message B to every subscriber in > multicast group. > * basic plain text authorization. > * 0mq driven reliability. (automatic connection restart without message > loose). > * ability mark connections as broken, this may be required to stop > automatic reconnect. > > We currently have a few performance issues that cause a consistent 30% > slowdown in performance of network-transport-zmq over TCP, but we?re > working on it. ZeroMQ should in fact *improve* performance over raw TCP > in many use cases thanks to intelligent batching of queued messages. > > Current approach is an early release of the library in order to gather > feedback. There is a large TODO list with a set of features that may be useful > for a big set of use cases like different authorization mechanisms including > certificate based, support of connection encryption, support for unreliable > connections, heartbeating and service discovery support. This features > will be implemented in short milestones. > > While we believe network-transport-zmq to be useful in its own right, > it is only a stepping stone towards making the rich communication > patterns implemented in ZeroMQ available through distributed-process. > This will allow for writing ZeroMQ applications with all the power of the > Process monad, supervision hierarchies, powerful type based matching > abstractions and intuitive message sending primitives. > > All feedback are appreciated. If you have a commercial interest around this > project then feel free to contact [2]. > > [1] http://zeromq.org/ > [2] mailto:sales at tweag.io > > -- > Alexander Vershilov > mail-to: alexander.vershilov at tweag.io > > > -- > Alexander -- Alexander From cam at uptoisomorphism.net Fri Mar 28 02:07:34 2014 From: cam at uptoisomorphism.net (Casey McCann) Date: Thu, 27 Mar 2014 22:07:34 -0400 Subject: [Haskell-cafe] strange error message In-Reply-To: <20140327221258.GA41469@inanna.trygub.com> References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> <1395923015.4670.0.camel@shum-lt> <20140327145007.GA39257@inanna.trygub.com> <20140327221258.GA41469@inanna.trygub.com> Message-ID: On Thu, Mar 27, 2014 at 6:12 PM, Semen Trygubenko / ????? ?????????? wrote: > However, I believe both types should be mentioned, as one is as likely to be wrong as the other. > If we are outputting it like that (i.e., one of the two, not both) and care about the amount > of output, why are we not outputting the less complex type of the two types involved in a mismatch? > r would certainly win that contest. > > IMHO, I don't think word "expected" is a great word to use here. > (length . head) expects to be fed [[a2]] as much as r expects > it should be passed into to functions that take Int. ghc should "expect" us > to change (length . head) to take Int as much as it "expects" us to fix > r to be of type [[a2]]. I agree that the terms used are less than ideal, but there IS a difference between the two types that's worth communicating. The cause of this error is because you have a thingie and a place to put a thingie and they don't fit together. It's essentially a "square peg in a round hole" error, and "Can't fit 'square peg' into 'round hole'" is much easier to understand than "Can't match 'square' with 'round'. Expected shape: round Actual shape: square". But 'round' and 'square' aren't interchangeable so they shouldn't be treated as such in the message. While it's easy to learn and interpret what the current message means, I think it would be far more helpful for newcomers if it was reported more clearly that 1) they have an expression known to have some type 'A' 2) which they've used in a context that expects some type 'B' and 3) GHC can't unify A and B to get some type C that works for both. Perhaps even displaying the surrounding context with the offending subexpression replaced with '_'? Sort of mimicking the way the typed holes stuff looks, I guess. If nothing else though, it would probably help to clarify that it's the surrounding code that 'expects' a particular type, rather than giving the impression that GHC has an opinion on the matter and expects a particular type. GHC just wants them to match, that's all. - C. From vigalchin at gmail.com Fri Mar 28 03:20:29 2014 From: vigalchin at gmail.com (Vasili I. Galchin) Date: Thu, 27 Mar 2014 22:20:29 -0500 Subject: [Haskell-cafe] Haskell article from a friend ... . Message-ID: -------------- next part -------------- An HTML attachment was scrubbed... URL: From vigalchin at gmail.com Fri Mar 28 04:06:11 2014 From: vigalchin at gmail.com (Vasili I. Galchin) Date: Thu, 27 Mar 2014 23:06:11 -0500 Subject: [Haskell-cafe] Haskell article from a friend ... . In-Reply-To: References: Message-ID: http://engineering.imvu.com/2014/03/24/what-its-like-to-use-haskell/ .. my bad .. I forgot to paste URL ... On Thu, Mar 27, 2014 at 10:20 PM, Vasili I. Galchin wrote: > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From dedgrant at gmail.com Fri Mar 28 04:23:38 2014 From: dedgrant at gmail.com (Darren Grant) Date: Thu, 27 Mar 2014 21:23:38 -0700 Subject: [Haskell-cafe] Haskell article from a friend ... . In-Reply-To: References: Message-ID: I enjoyed this Andy's even-handed report; this is a valuable review to me because it addresses the controlled introduction of services into live ops. Haskell clearly has real strengths in highly concurrent shared memory services, but it is important to understand the current pain points as well. I've also really appreciated Simon Marlow's candor in this respect. The 'total comprehension' makes Haskell a much stronger contender. Thank you! Cheers, Darren On Thu, Mar 27, 2014 at 9:06 PM, Vasili I. Galchin wrote: > http://engineering.imvu.com/2014/03/24/what-its-like-to-use-haskell/ .. > my bad .. I forgot to paste URL ... > > > On Thu, Mar 27, 2014 at 10:20 PM, Vasili I. Galchin wrote: > >> >> > > _______________________________________________ > 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 sgeoster at gmail.com Fri Mar 28 04:25:53 2014 From: sgeoster at gmail.com (Sgeo) Date: Fri, 28 Mar 2014 00:25:53 -0400 Subject: [Haskell-cafe] Happstack website down? Message-ID: http://www.happstack.com/ is now giving a default-looking "It works!" page. Anyone know why? -------------- next part -------------- An HTML attachment was scrubbed... URL: From charles.c.strahan at gmail.com Fri Mar 28 05:23:37 2014 From: charles.c.strahan at gmail.com (Charles Strahan) Date: Fri, 28 Mar 2014 01:23:37 -0400 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara Message-ID: A question for you all: what would be a good name for a Haskell version of Ruby's Capybara web testing framework? I'm about to start hacking on some better web testing tools for Haskell, but I'm afraid I'm terrible at coming up with concise, revealing names for things. Any suggestions would be very welcome! -Charles -------------- next part -------------- An HTML attachment was scrubbed... URL: From carter.schonwald at gmail.com Fri Mar 28 05:30:44 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 28 Mar 2014 01:30:44 -0400 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara In-Reply-To: References: Message-ID: hcapybara webtestthingy toomuchDOMTest nodeHS.js -- powered by ghcjs i kid i kid (been a long day hacking) honestly, make up a dumb name, then ask for feedback after its ready for use by others, but before you push to hackage! :) -Carter On Fri, Mar 28, 2014 at 1:23 AM, Charles Strahan < charles.c.strahan at gmail.com> wrote: > A question for you all: what would be a good name for a Haskell version of > Ruby's Capybara web testing framework? > > I'm about to start hacking on some better web testing tools for Haskell, > but I'm afraid I'm terrible at coming up with concise, revealing names for > things. > > Any suggestions would be very welcome! > > -Charles > > _______________________________________________ > 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 maydwell at gmail.com Fri Mar 28 05:34:29 2014 From: maydwell at gmail.com (Lyndon Maydwell) Date: Fri, 28 Mar 2014 16:34:29 +1100 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara In-Reply-To: References: Message-ID: happybara On Fri, Mar 28, 2014 at 4:30 PM, Carter Schonwald wrote: > hcapybara > > webtestthingy > > toomuchDOMTest > > nodeHS.js -- powered by ghcjs > > i kid i kid (been a long day hacking) > > > honestly, make up a dumb name, then ask for feedback after its ready for use > by others, but before you push to hackage! > > :) > -Carter > > > On Fri, Mar 28, 2014 at 1:23 AM, Charles Strahan > wrote: >> >> A question for you all: what would be a good name for a Haskell version of >> Ruby's Capybara web testing framework? >> >> I'm about to start hacking on some better web testing tools for Haskell, >> but I'm afraid I'm terrible at coming up with concise, revealing names for >> things. >> >> Any suggestions would be very welcome! >> >> -Charles >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From gagliardi.curtis at gmail.com Fri Mar 28 06:36:02 2014 From: gagliardi.curtis at gmail.com (Curtis Gagliardi) Date: Thu, 27 Mar 2014 23:36:02 -0700 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara In-Reply-To: References: Message-ID: I second happybara. On Thu, Mar 27, 2014 at 10:34 PM, Lyndon Maydwell wrote: > happybara > > On Fri, Mar 28, 2014 at 4:30 PM, Carter Schonwald > wrote: > > hcapybara > > > > webtestthingy > > > > toomuchDOMTest > > > > nodeHS.js -- powered by ghcjs > > > > i kid i kid (been a long day hacking) > > > > > > honestly, make up a dumb name, then ask for feedback after its ready for > use > > by others, but before you push to hackage! > > > > :) > > -Carter > > > > > > On Fri, Mar 28, 2014 at 1:23 AM, Charles Strahan > > wrote: > >> > >> A question for you all: what would be a good name for a Haskell version > of > >> Ruby's Capybara web testing framework? > >> > >> I'm about to start hacking on some better web testing tools for Haskell, > >> but I'm afraid I'm terrible at coming up with concise, revealing names > for > >> things. > >> > >> Any suggestions would be very welcome! > >> > >> -Charles > >> > >> _______________________________________________ > >> Haskell-Cafe mailing list > >> Haskell-Cafe at haskell.org > >> http://www.haskell.org/mailman/listinfo/haskell-cafe > >> > > > > > > _______________________________________________ > > Haskell-Cafe mailing list > > Haskell-Cafe at haskell.org > > http://www.haskell.org/mailman/listinfo/haskell-cafe > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From charles.c.strahan at gmail.com Fri Mar 28 08:10:30 2014 From: charles.c.strahan at gmail.com (Charles Strahan) Date: Fri, 28 Mar 2014 04:10:30 -0400 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara In-Reply-To: References: Message-ID: Ha! I considered Hapybara/Happybara, but thought the cheese factor might have been to high. Looks like I'll probably go with the latter :). Thanks! -Charles On Fri, Mar 28, 2014 at 2:36 AM, Curtis Gagliardi < gagliardi.curtis at gmail.com> wrote: > I second happybara. > > > On Thu, Mar 27, 2014 at 10:34 PM, Lyndon Maydwell wrote: > >> happybara >> >> On Fri, Mar 28, 2014 at 4:30 PM, Carter Schonwald >> wrote: >> > hcapybara >> > >> > webtestthingy >> > >> > toomuchDOMTest >> > >> > nodeHS.js -- powered by ghcjs >> > >> > i kid i kid (been a long day hacking) >> > >> > >> > honestly, make up a dumb name, then ask for feedback after its ready >> for use >> > by others, but before you push to hackage! >> > >> > :) >> > -Carter >> > >> > >> > On Fri, Mar 28, 2014 at 1:23 AM, Charles Strahan >> > wrote: >> >> >> >> A question for you all: what would be a good name for a Haskell >> version of >> >> Ruby's Capybara web testing framework? >> >> >> >> I'm about to start hacking on some better web testing tools for >> Haskell, >> >> but I'm afraid I'm terrible at coming up with concise, revealing names >> for >> >> things. >> >> >> >> Any suggestions would be very welcome! >> >> >> >> -Charles >> >> >> >> _______________________________________________ >> >> Haskell-Cafe mailing list >> >> Haskell-Cafe at haskell.org >> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> > >> > >> > _______________________________________________ >> > Haskell-Cafe mailing list >> > Haskell-Cafe at haskell.org >> > http://www.haskell.org/mailman/listinfo/haskell-cafe >> > >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> > > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -------------- next part -------------- An HTML attachment was scrubbed... URL: From tanielsen at gmail.com Fri Mar 28 10:07:55 2014 From: tanielsen at gmail.com (Tom Nielsen) Date: Fri, 28 Mar 2014 10:07:55 +0000 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara In-Reply-To: References: Message-ID: you may be interested in http://hackage.haskell.org/package/http-test. I haven't really announced its existence, but it exists. This only uses http client calls and doesn't have a DOM/JS interpreter - I'd be very interested in having this in Haskell, a lot of the existing tools are extremely poor (e.g. fails 20% of the time for no good reason and thus useless as acceptance tests.) Tom On Fri, Mar 28, 2014 at 5:23 AM, Charles Strahan < charles.c.strahan at gmail.com> wrote: > A question for you all: what would be a good name for a Haskell version of > Ruby's Capybara web testing framework? > > I'm about to start hacking on some better web testing tools for Haskell, > but I'm afraid I'm terrible at coming up with concise, revealing names for > things. > > Any suggestions would be very welcome! > > -Charles > > _______________________________________________ > 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 rvdalen at yahoo.co.uk Fri Mar 28 10:59:43 2014 From: rvdalen at yahoo.co.uk (Rouan van Dalen) Date: Fri, 28 Mar 2014 10:59:43 +0000 (GMT) Subject: [Haskell-cafe] Domain Events in haskell Message-ID: <1396004383.91685.YahooMailNeo@web171906.mail.ir2.yahoo.com> Hi Cafe, I am trying to write a very simple implementation of an event publisher pattern but I am stuck and do not know how to do this in Haskell. I have the following code: ======================== {-# LANGUAGE RankNTypes, NamedFieldPuns #-} module Domain.DomainEventPublisher where ? ?import Control.Monad (forM_) ? ?import HsFu.Data.DateTime ? ?import Domain.Client ? ?data DomainEvent =?ClientChangeAgeDomainEvent ? ?data DomainEventContext = ? ? ? DomainEventContext { domainEventContext_event ? ? ?:: DomainEvent ? ? ? ? ? ? ? ? ? ? ? ? ?, domainEventContext_occurredOn :: DateTime ? ? ? ? ? ? ? ? ? ? ? ? ?} deriving (Show) ? ?data DomainEventPublisher = DomainEventPublisher { domainEventPublisher_subscribers :: [DomainEventContext -> IO ()] } ? ?mkEventPublisher :: DomainEventPublisher ? ?mkEventPublisher = DomainEventPublisher [] ? ?subscribe :: DomainEventPublisher -> (DomainEventContext -> IO ()) -> DomainEventPublisher ? ?subscribe publisher eventHandler = ? ? ? DomainEventPublisher { domainEventPublisher_subscribers = eventHandler : (domainEventPublisher_subscribers publisher) } ? ?publish :: DomainEventPublisher -> DomainEventContext -> IO () ? ?publish DomainEventPublisher{ domainEventPublisher_subscribers } event = ? ? ? forM_ domainEventPublisher_subscribers ($ event) ======================== My problem is that the publish method returns IO (), which means that events can only be published from the IO monad, but I would like events to be 'publish-able' from pure code. I can live with event handlers (passed into the subscribe function) being in the IO monad. Is there a better way to implement this pattern in Haskell? I have been racking my brain on this for a while now and cannot seem to come up with a good implementation. Regards --Rouan. From semen at trygub.com Fri Mar 28 11:32:26 2014 From: semen at trygub.com (Semen Trygubenko / =?utf-8?B?0KHQtdC80LXQvSDQotGA0LjQs9GD0LHQtdC9?= =?utf-8?B?0LrQvg==?=) Date: Fri, 28 Mar 2014 11:32:26 +0000 Subject: [Haskell-cafe] strange error message In-Reply-To: References: <20140327023644.GD34466@inanna.trygub.com> <20140327120925.GB38345@inanna.trygub.com> <1395923015.4670.0.camel@shum-lt> <20140327145007.GA39257@inanna.trygub.com> <20140327221258.GA41469@inanna.trygub.com> Message-ID: <20140328113226.GA47995@inanna.trygub.com> Hi Casey, Thanks for your reply. On Thu, Mar 27, 2014 at 10:07:34PM -0400, Casey McCann wrote: > On Thu, Mar 27, 2014 at 6:12 PM, Semen Trygubenko / ????? ?????????? > wrote: > > However, I believe both types should be mentioned, as one is as likely to be wrong as the other. > > If we are outputting it like that (i.e., one of the two, not both) and care about the amount > > of output, why are we not outputting the less complex type of the two types involved in a mismatch? > > r would certainly win that contest. > > > > IMHO, I don't think word "expected" is a great word to use here. > > (length . head) expects to be fed [[a2]] as much as r expects > > it should be passed into to functions that take Int. ghc should "expect" us > > to change (length . head) to take Int as much as it "expects" us to fix > > r to be of type [[a2]]. > > I agree that the terms used are less than ideal, but there IS a > difference between the two types that's worth communicating. > > The cause of this error is because you have a thingie and a place to > put a thingie and they don't fit together. It's essentially a "square > peg in a round hole" error, and "Can't fit 'square peg' into 'round > hole'" is much easier to understand than "Can't match 'square' with > 'round'. I agree. Presently the header of the ghc error message reads: "Can't match 'square' with 'round'. > Expected shape: round Actual shape: square". But 'round' and > 'square' aren't interchangeable so they shouldn't be treated as such > in the message. There is a symmetry though. Using your analogy, one can try to make the square peg round, or one can try and make the round hole square. Both are equally valid. I just wanted to improve the current type error message by ensuring (1) the type is visually close to the expression it refers to and (2) it is clear in the output that the peg could be made round OR the hole could be made square for the expression to typecheck. Presently the header of the type error says: "Couldn't match square with round. I expect square, but in actuality 'it' is round". Expression for 'it' is listed later, and then the context in which 'it' is interacting with 'something else' that is as likely to be the cause of error as 'it'. IIANM, no type for 'something else' is given explicitly though, it is left to be deduced, and the expression for 'something else' is not available in isolation either, only as part of the context. > While it's easy to learn and interpret what the current message means, > I think it would be far more helpful for newcomers if it was reported > more clearly that 1) they have an expression known to have some type > 'A' 2) which they've used in a context that expects some type 'B' and > 3) GHC can't unify A and B to get some type C that works for both. > > Perhaps even displaying the surrounding context with the offending > subexpression replaced with '_'? Sort of mimicking the way the typed > holes stuff looks, I guess. > > If nothing else though, it would probably help to clarify that it's > the surrounding code that 'expects' a particular type, rather than > giving the impression that GHC has an opinion on the matter and > expects a particular type. GHC just wants them to match, that's all. I agree. What do people think of the following output then: test.hs:10:15: Couldn't match type `[[a2]]' with `Int' (length . head) :: [[a2]] -> Int r :: Int In the first argument of `(==)', namely `(length . head) r' In the expression: (length . head) r == 0 Does it help to achieve the above? Many thanks, S. -- ????? ?????????? http://trygub.com -------------- next part -------------- A non-text attachment was scrubbed... Name: not available Type: application/pgp-signature Size: 196 bytes Desc: not available URL: From alois.cochard at gmail.com Fri Mar 28 11:39:32 2014 From: alois.cochard at gmail.com (Alois Cochard) Date: Fri, 28 Mar 2014 11:39:32 +0000 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> Message-ID: As mentioned before, there is Cloud Haskell: http://www.haskell.org/haskellwiki/Cloud_Haskell On 27 March 2014 23:22, Patrick Wheeler wrote: > @tom - forkIO and freineds works great for lightweight local threads, what > about non-local threads though in a distributed setting. Is there anything > in haskell that you think replaces that functionality in erlang? > > > On Thu, Mar 27, 2014 at 10:34 PM, wrote: > >> Unfortunately I can't help with recommending an actor library. I think >> peoples' responses of "you should never want to do that" are, um, unhelpful. >> >> That said, i've written both haskell and erlang professionally, and never >> had a need for actors/message passing in haskell. It may be the wrong tool >> for most haskell jobs. >> >> The main things erlang-style concurrency gets you are >> - lightweight threads (in haskell by default -- 'forkIO' creates >> lightweight threads) >> - limited shared mutable state (haskell's pure) >> - spreading computation over cores (in haskell you want parallelism not >> concurrency -- check out the Par monad) >> - computation over boxes (see distributed-process) >> >> To do "message passing", check out MVars (and later, STM) >> >> Tom >> >> >> El Mar 27, 2014, a las 17:40, james >> escribi?: >> >> On 27/03/2014 17:28, Christopher Allen wrote: >> >> I don't actually want to get drawn into this, but one point would be >> that it's really just the same fallacies as OOP in general, but concurrent. >> >> >> Well, horses for courses, I've been writing distributed C++ apps since >> cfront was shiny and new. >> >> I find writing off OOP as distasteful as writing off functional, and >> there are people in both camps. >> >> I have ordered Simon's book and will take care to read it. >> >> In the mean time - does anyone have an answer to the question I asked? >> >> James >> >> The idea that isolation behind an interface (message passing or not) is >> going to prevent unnecessary mutation or side effects from getting out of >> control. >> >> In practice, it doesn't do that at all and the fact that you're making >> your inter-dependencies more implicit, rather than explicit, through the >> use of isolated buckets of side-effecting state and mutation is going to >> make it harder rather than easier to debug the program when it invariably >> breaks. I'd rather get a call-stack if I'm going to abandon Haskell-y >> goodness. And your Actors *will* get into a bad state, so you'll end up >> writing Inspector and Debugger mixins just to keep a handle on the >> complexity when they get into that bad state. >> >> It's not impossible for Actors to make sense. I used agents (which are >> not full-blown Actors per se) in Clojure for side-effect isolation, >> serialization, and thread safety to good effect, but I kept how much "work" >> they did to a bare minimum and tried to keep everything in pure functions >> as long as I could. >> >> It's just that I see programmers with a shiny new hammer looking for >> every nail they can find. >> >> >> >> On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang wrote: >> >>> Can anyone give some detailed cons of Akka / actor model? >>> >>> On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard >>> wrote: >>> > I have good experience with actors (Scala/Akka), and I can tell you >>> that you >>> > should avoid them as much as possible. >>> > I think the model is good if you need to do some low level concurrency >>> > coding on a language that don't have effect tracking in types. >>> > >>> > Having used the Async library from Marlow, I highly recommend it... >>> and it >>> > probably cover a big percentage of traditional concurrency use cases. >>> > >>> > You still have Haskell Cloud if you want distributed messaging. >>> > >>> > Cheers >>> > >>> > >>> > >>> > On 27 March 2014 06:29, james wrote: >>> >> >>> >> Having been introduced to actors by looking at Erlang, I discovered >>> Akka. >>> >> >>> >> It seems that the performance is pretty impressive and I like the >>> model. >>> >> >>> >> There seem to be several basic Actor libraries in Hackage, but they >>> don't >>> >> seem >>> >> to be very actively developed. >>> >> >>> >> I'm more interested in the model for programming within a single >>> runtime >>> >> than I am for distributed systems, but message and dispatch >>> performance >>> >> definitely is important. >>> >> >>> >> Can anyone share experiences with the different packages? Is any one >>> >> of them stand-out? >>> >> >>> >> Thanks >>> >> James >>> >> >>> >> >>> >> _______________________________________________ >>> >> Haskell-Cafe mailing list >>> >> Haskell-Cafe at haskell.org >>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> > >>> > >>> > >>> > >>> > -- >>> > Alois Cochard >>> > http://aloiscochard.blogspot.com >>> > http://twitter.com/aloiscochard >>> > http://github.com/aloiscochard >>> > >>> > _______________________________________________ >>> > Haskell-Cafe mailing list >>> > Haskell-Cafe at haskell.org >>> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>> > >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > > -- > Patrick Wheeler > Patrick.John.Wheeler at gmail.com > Patrick.J.Wheeler at rice.edu > Patrick.Wheeler at colorado.edu > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > -- *Alois Cochard* http://aloiscochard.blogspot.com http://twitter.com/aloiscochard http://github.com/aloiscochard -------------- next part -------------- An HTML attachment was scrubbed... URL: From david.sorokin at gmail.com Fri Mar 28 12:31:48 2014 From: david.sorokin at gmail.com (David Sorokin) Date: Fri, 28 Mar 2014 16:31:48 +0400 Subject: [Haskell-cafe] Domain Events in haskell In-Reply-To: <1396004383.91685.YahooMailNeo@web171906.mail.ir2.yahoo.com> References: <1396004383.91685.YahooMailNeo@web171906.mail.ir2.yahoo.com> Message-ID: Hi Rouan, I like how a similar concept is implemented in F# and I did a similar Signal type in my simulation library Aivika [1]. Only in my case the signals (events) are bound up with the modeling time. The publish function can be indeed and should be pure. Moreover, I personally preferred the IObservable concept above the Event one as the former seems to be more functional-like. Just in F# they introduce also the event source and treat the events and their sources differently. Therefore, the publish function, being defined for the event source, is pure. Thanks, David [1] http://hackage.haskell.org/package/aivika On Fri, Mar 28, 2014 at 2:59 PM, Rouan van Dalen wrote: > Hi Cafe, > > I am trying to write a very simple implementation of an event publisher > pattern but I am stuck and do > not know how to do this in Haskell. > > I have the following code: > > ======================== > > > {-# LANGUAGE RankNTypes, NamedFieldPuns #-} > > module Domain.DomainEventPublisher where > > import Control.Monad (forM_) > > import HsFu.Data.DateTime > import Domain.Client > > > data DomainEvent = ClientChangeAgeDomainEvent > > > data DomainEventContext = > DomainEventContext { domainEventContext_event :: DomainEvent > , domainEventContext_occurredOn :: DateTime > } deriving (Show) > > > data DomainEventPublisher = DomainEventPublisher { > domainEventPublisher_subscribers :: [DomainEventContext -> IO ()] } > > > mkEventPublisher :: DomainEventPublisher > mkEventPublisher = DomainEventPublisher [] > > > subscribe :: DomainEventPublisher -> (DomainEventContext -> IO ()) -> > DomainEventPublisher > subscribe publisher eventHandler = > DomainEventPublisher { domainEventPublisher_subscribers = > eventHandler : (domainEventPublisher_subscribers publisher) } > > > publish :: DomainEventPublisher -> DomainEventContext -> IO () > publish DomainEventPublisher{ domainEventPublisher_subscribers } event = > forM_ domainEventPublisher_subscribers ($ event) > > ======================== > > > My problem is that the publish method returns IO (), which means that > events can only be > published from the IO monad, but I would like events to be 'publish-able' > from pure code. > > I can live with event handlers (passed into the subscribe function) being > in the IO monad. > > Is there a better way to implement this pattern in Haskell? > > I have been racking my brain on this for a while now and cannot seem to > come up with a > good implementation. > > Regards > --Rouan. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From jeremy at n-heptane.com Fri Mar 28 15:26:01 2014 From: jeremy at n-heptane.com (Jeremy Shaw) Date: Fri, 28 Mar 2014 10:26:01 -0500 Subject: [Haskell-cafe] Happstack website down? In-Reply-To: References: Message-ID: Seems someone upgraded some debian packages on the server and ignored the fact that the upgrade removed the server packages for happstack.com and clckwrks.com... Looks like something needs to be rebuilt. Looking into it now. - jeremy On Thu, Mar 27, 2014 at 11:25 PM, Sgeo wrote: > http://www.happstack.com/ > is now giving a default-looking "It works!" page. Anyone know why? > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > From jeremy at n-heptane.com Fri Mar 28 17:08:30 2014 From: jeremy at n-heptane.com (Jeremy Shaw) Date: Fri, 28 Mar 2014 12:08:30 -0500 Subject: [Haskell-cafe] Happstack website down? In-Reply-To: References: Message-ID: Back up. Not exactly sure how things transpired, but the set of packages available to the server was in an inconsistent state, and someone decided to upgrade some packages anyway and force the happstack.com and clckwrks.com servers off the system. This is obviously operator error and not an issue with the servers themselves :) Thanks for the notice! In theory I should set up some sort of monitoring, but this doesn't happen often and so there are other higher priority tasks on my mind. - jeremy On Fri, Mar 28, 2014 at 10:26 AM, Jeremy Shaw wrote: > Seems someone upgraded some debian packages on the server and ignored > the fact that the upgrade removed the server packages for > happstack.com and clckwrks.com... > > Looks like something needs to be rebuilt. Looking into it now. > > - jeremy > > On Thu, Mar 27, 2014 at 11:25 PM, Sgeo wrote: >> http://www.happstack.com/ >> is now giving a default-looking "It works!" page. Anyone know why? >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> From patrick.john.wheeler at gmail.com Fri Mar 28 18:46:59 2014 From: patrick.john.wheeler at gmail.com (Patrick Wheeler) Date: Fri, 28 Mar 2014 13:46:59 -0500 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> Message-ID: Thanks Alois, I have recently been using Cloud Haskell for multi-machine programs. > i've written both haskell and erlang professionally, and never had a need for actors/message passing Even though Tom made a mention of distributed-process, part of Cloud Haskell, I wanted to find out if their were other viable approaches to distributed computing being explored by the Haskell community. Patrick On Fri, Mar 28, 2014 at 6:39 AM, Alois Cochard wrote: > As mentioned before, there is Cloud Haskell: > http://www.haskell.org/haskellwiki/Cloud_Haskell > > > On 27 March 2014 23:22, Patrick Wheeler wrote: > >> @tom - forkIO and freineds works great for lightweight local threads, >> what about non-local threads though in a distributed setting. Is there >> anything in haskell that you think replaces that functionality in erlang? >> >> >> On Thu, Mar 27, 2014 at 10:34 PM, wrote: >> >>> Unfortunately I can't help with recommending an actor library. I think >>> peoples' responses of "you should never want to do that" are, um, unhelpful. >>> >>> That said, i've written both haskell and erlang professionally, and >>> never had a need for actors/message passing in haskell. It may be the wrong >>> tool for most haskell jobs. >>> >>> The main things erlang-style concurrency gets you are >>> - lightweight threads (in haskell by default -- 'forkIO' creates >>> lightweight threads) >>> - limited shared mutable state (haskell's pure) >>> - spreading computation over cores (in haskell you want parallelism not >>> concurrency -- check out the Par monad) >>> - computation over boxes (see distributed-process) >>> >>> To do "message passing", check out MVars (and later, STM) >>> >>> Tom >>> >>> >>> El Mar 27, 2014, a las 17:40, james >>> escribi?: >>> >>> On 27/03/2014 17:28, Christopher Allen wrote: >>> >>> I don't actually want to get drawn into this, but one point would be >>> that it's really just the same fallacies as OOP in general, but concurrent. >>> >>> >>> Well, horses for courses, I've been writing distributed C++ apps since >>> cfront was shiny and new. >>> >>> I find writing off OOP as distasteful as writing off functional, and >>> there are people in both camps. >>> >>> I have ordered Simon's book and will take care to read it. >>> >>> In the mean time - does anyone have an answer to the question I asked? >>> >>> James >>> >>> The idea that isolation behind an interface (message passing or not) >>> is going to prevent unnecessary mutation or side effects from getting out >>> of control. >>> >>> In practice, it doesn't do that at all and the fact that you're making >>> your inter-dependencies more implicit, rather than explicit, through the >>> use of isolated buckets of side-effecting state and mutation is going to >>> make it harder rather than easier to debug the program when it invariably >>> breaks. I'd rather get a call-stack if I'm going to abandon Haskell-y >>> goodness. And your Actors *will* get into a bad state, so you'll end up >>> writing Inspector and Debugger mixins just to keep a handle on the >>> complexity when they get into that bad state. >>> >>> It's not impossible for Actors to make sense. I used agents (which are >>> not full-blown Actors per se) in Clojure for side-effect isolation, >>> serialization, and thread safety to good effect, but I kept how much "work" >>> they did to a bare minimum and tried to keep everything in pure functions >>> as long as I could. >>> >>> It's just that I see programmers with a shiny new hammer looking for >>> every nail they can find. >>> >>> >>> >>> On Thu, Mar 27, 2014 at 12:21 PM, Zongheng Yang wrote: >>> >>>> Can anyone give some detailed cons of Akka / actor model? >>>> >>>> On Thu, Mar 27, 2014 at 5:21 AM, Alois Cochard >>>> wrote: >>>> > I have good experience with actors (Scala/Akka), and I can tell you >>>> that you >>>> > should avoid them as much as possible. >>>> > I think the model is good if you need to do some low level concurrency >>>> > coding on a language that don't have effect tracking in types. >>>> > >>>> > Having used the Async library from Marlow, I highly recommend it... >>>> and it >>>> > probably cover a big percentage of traditional concurrency use cases. >>>> > >>>> > You still have Haskell Cloud if you want distributed messaging. >>>> > >>>> > Cheers >>>> > >>>> > >>>> > >>>> > On 27 March 2014 06:29, james wrote: >>>> >> >>>> >> Having been introduced to actors by looking at Erlang, I discovered >>>> Akka. >>>> >> >>>> >> It seems that the performance is pretty impressive and I like the >>>> model. >>>> >> >>>> >> There seem to be several basic Actor libraries in Hackage, but they >>>> don't >>>> >> seem >>>> >> to be very actively developed. >>>> >> >>>> >> I'm more interested in the model for programming within a single >>>> runtime >>>> >> than I am for distributed systems, but message and dispatch >>>> performance >>>> >> definitely is important. >>>> >> >>>> >> Can anyone share experiences with the different packages? Is any one >>>> >> of them stand-out? >>>> >> >>>> >> Thanks >>>> >> James >>>> >> >>>> >> >>>> >> _______________________________________________ >>>> >> Haskell-Cafe mailing list >>>> >> Haskell-Cafe at haskell.org >>>> >> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> > >>>> > >>>> > >>>> > >>>> > -- >>>> > Alois Cochard >>>> > http://aloiscochard.blogspot.com >>>> > http://twitter.com/aloiscochard >>>> > http://github.com/aloiscochard >>>> > >>>> > _______________________________________________ >>>> > Haskell-Cafe mailing list >>>> > Haskell-Cafe at haskell.org >>>> > http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> > >>>> _______________________________________________ >>>> Haskell-Cafe mailing list >>>> Haskell-Cafe at haskell.org >>>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>>> >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >>> _______________________________________________ >>> Haskell-Cafe mailing list >>> Haskell-Cafe at haskell.org >>> http://www.haskell.org/mailman/listinfo/haskell-cafe >>> >>> >> >> >> -- >> Patrick Wheeler >> Patrick.John.Wheeler at gmail.com >> Patrick.J.Wheeler at rice.edu >> Patrick.Wheeler at colorado.edu >> >> _______________________________________________ >> Haskell-Cafe mailing list >> Haskell-Cafe at haskell.org >> http://www.haskell.org/mailman/listinfo/haskell-cafe >> >> > > > -- > *Alois Cochard* > http://aloiscochard.blogspot.com > http://twitter.com/aloiscochard > http://github.com/aloiscochard > -- Patrick Wheeler Patrick.John.Wheeler at gmail.com Patrick.J.Wheeler at rice.edu Patrick.Wheeler at colorado.edu -------------- next part -------------- An HTML attachment was scrubbed... URL: From james at mansionfamily.plus.com Fri Mar 28 19:13:06 2014 From: james at mansionfamily.plus.com (james) Date: Fri, 28 Mar 2014 19:13:06 +0000 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> Message-ID: <5335C9C2.5080703@mansionfamily.plus.com> (Isn't it nice to be on a list where peopel top-post? ;-)) Actually I already have Haskell-like code at work where I have actor-like processing with (event, state) -> (state', actions) and these are mostly pure. And I like the model. I'm NOT looking for spreading over boxes. What I'm interested in is optimisation of the flow of control: - if an actor has a deep queue of input events, I want it to spin in-cache efficiently. - if an actor makes an RPC-like transaction against a dormant peer, then I want the flow of control on the bound thread to go from one to the other and back, and not result in general scheduling - I want the performance of general messaging to be somewhat like that of the work-stealing pool we see working well in Akka and JActor I would be surprised if general LWP scheduling will really be up to it, in terms of competing, particularly in the case of RPC interactions or pipelines where we'd really want to stay cache-hot for either the code (for an actor spinning on a deep queue) or the data (for a pipeline or RPC). I'm also interested in terms of how a channel can effectively (and efficiently) handle messages where the channel is carrying a union of message types that can evolve as the system is built. I'm quite happy to do explicit networking between processes in different NUMA zones or on different hosts. James (Not made my mind up about Erlang - I really like per-actor GC tho. Will try to play with Nimrod sometime) On 27/03/2014 22:34, amindfv at gmail.com wrote: > Unfortunately I can't help with recommending an actor library. I think > peoples' responses of "you should never want to do that" are, um, > unhelpful. > > That said, i've written both haskell and erlang professionally, and > never had a need for actors/message passing in haskell. It may be the > wrong tool for most haskell jobs. > > The main things erlang-style concurrency gets you are > - lightweight threads (in haskell by default -- 'forkIO' creates > lightweight threads) > - limited shared mutable state (haskell's pure) > - spreading computation over cores (in haskell you want parallelism > not concurrency -- check out the Par monad) > - computation over boxes (see distributed-process) > > To do "message passing", check out MVars (and later, STM) > > Tom From carter.schonwald at gmail.com Fri Mar 28 19:31:12 2014 From: carter.schonwald at gmail.com (Carter Schonwald) Date: Fri, 28 Mar 2014 15:31:12 -0400 Subject: [Haskell-cafe] Best Actor system? In-Reply-To: <5335C9C2.5080703@mansionfamily.plus.com> References: <5333C55C.7050104@mansionfamily.plus.com> <53349AEB.2000808@mansionfamily.plus.com> <31C4BA64-871F-47B6-A3B8-D4D26B29DE2C@gmail.com> <5335C9C2.5080703@mansionfamily.plus.com> Message-ID: For throughput base stuff, a careful mix of Some of the libs and tools that simon marlow espouses in his lovely book will get you very far. Which is very different from actors models as folks here will assume you mean. So just use asynch, monadpar, Ryan newtons concurrency libs, and a few other things. Ghc itself has a work stealing scheduler deque for sparked computations! On Friday, March 28, 2014, james wrote: > (Isn't it nice to be on a list where peopel top-post? ;-)) > > Actually I already have Haskell-like code at work where I have actor-like > processing with > (event, state) -> (state', actions) and these are mostly pure. And I like > the model. > > I'm NOT looking for spreading over boxes. What I'm interested in is > optimisation of the flow of control: > - if an actor has a deep queue of input events, I want it to spin > in-cache efficiently. > - if an actor makes an RPC-like transaction against a dormant peer, then > I want the flow of control > on the bound thread to go from one to the other and back, and not result > in general scheduling > - I want the performance of general messaging to be somewhat like that of > the work-stealing > pool we see working well in Akka and JActor > > I would be surprised if general LWP scheduling will really be up to it, in > terms of competing, > particularly in the case of RPC interactions or pipelines where we'd > really want to stay cache-hot > for either the code (for an actor spinning on a deep queue) or the data > (for a pipeline or RPC). > > I'm also interested in terms of how a channel can effectively (and > efficiently) handle messages where > the channel is carrying a union of message types that can evolve as the > system is built. > > I'm quite happy to do explicit networking between processes in different > NUMA zones or on > different hosts. > > James > > (Not made my mind up about Erlang - I really like per-actor GC tho. Will > try to play with > Nimrod sometime) > > On 27/03/2014 22:34, amindfv at gmail.com wrote: > >> Unfortunately I can't help with recommending an actor library. I think >> peoples' responses of "you should never want to do that" are, um, unhelpful. >> >> That said, i've written both haskell and erlang professionally, and never >> had a need for actors/message passing in haskell. It may be the wrong tool >> for most haskell jobs. >> >> The main things erlang-style concurrency gets you are >> - lightweight threads (in haskell by default -- 'forkIO' creates >> lightweight threads) >> - limited shared mutable state (haskell's pure) >> - spreading computation over cores (in haskell you want parallelism not >> concurrency -- check out the Par monad) >> - computation over boxes (see distributed-process) >> >> To do "message passing", check out MVars (and later, STM) >> >> Tom >> > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -------------- next part -------------- An HTML attachment was scrubbed... URL: From michael at orlitzky.com Fri Mar 28 23:41:02 2014 From: michael at orlitzky.com (Michael Orlitzky) Date: Fri, 28 Mar 2014 19:41:02 -0400 Subject: [Haskell-cafe] Naming/Bikeshedding: Haskell version of Capybara In-Reply-To: References: Message-ID: <5336088E.9010004@orlitzky.com> On 03/28/2014 01:23 AM, Charles Strahan wrote: > A question for you all: what would be a good name for a Haskell version > of Ruby's Capybara web testing framework? The scientific name for the capybara is "hydrochoerus hydrochaeris." That's TWO names that start with 'h'. Basically twice as many as one. From kai at kzhang.org Sat Mar 29 01:43:21 2014 From: kai at kzhang.org (Kai Zhang) Date: Fri, 28 Mar 2014 18:43:21 -0700 Subject: [Haskell-cafe] Inline makes program slow? Message-ID: Hi cafe, Inline sometimes can cause problems, at least in following case: import qualified Data.Vector as V import Data.List f ? String ? (String ? Int ? Char) ? [Int] ? String f str g idx = map (g str) idx h ? String ? Int ? Char *{-# INLINE h #-}* h s i = (V.fromList $ sort s) V.! i slow ? String ? [Int] ? String slow str = f str h fast ? String ? [Int] ? String fast str = map ((V.fromList $ sort str) V.!) main = do let testString = replicate 100000 'a' iterations = replicate 1000 100 putStrLn $ fast testString iterations putStrLn $ slow testString iterations Without inline (remove the inline pragma), "slow" would be much faster. I suspect this is because ghc can build a "persistent structure" for the partial applied function. After inline, each call of "g" will try to build a new vector. How can I tell ghc not to inline some specific functions? Or are there other ways to resolve this issue? -------------- next part -------------- An HTML attachment was scrubbed... URL: From ivan.miljenovic at gmail.com Sat Mar 29 02:09:22 2014 From: ivan.miljenovic at gmail.com (Ivan Lazar Miljenovic) Date: Sat, 29 Mar 2014 13:09:22 +1100 Subject: [Haskell-cafe] Inline makes program slow? In-Reply-To: References: Message-ID: On 29 March 2014 12:43, Kai Zhang wrote: > Hi cafe, > > Inline sometimes can cause problems, at least in following case: > > import qualified Data.Vector as V > import Data.List > > f ? String ? (String ? Int ? Char) ? [Int] ? String > f str g idx = map (g str) idx > > h ? String ? Int ? Char > {-# INLINE h #-} > h s i = (V.fromList $ sort s) V.! i > > slow ? String ? [Int] ? String > slow str = f str h > > fast ? String ? [Int] ? String > fast str = map ((V.fromList $ sort str) V.!) > > main = do > let testString = replicate 100000 'a' > iterations = replicate 1000 100 > putStrLn $ fast testString iterations > putStrLn $ slow testString iterations > > Without inline (remove the inline pragma), "slow" would be much faster. I > suspect this is because ghc can build a "persistent structure" for the > partial applied function. After inline, each call of "g" will try to build a > new vector. How can I tell ghc not to inline some specific functions? Or are > there other ways to resolve this issue? There's the NOINLINE and INLINEABLE pragmas. Though I'm going through some of my own code where I waved the INLINE-hammer around rather heavily only to find that whilst it doesn't make much of a difference on my main x86_64 machine, on the x86 laptop I tested it on it made the code much slower. So I'm also interested in finding better ways of determining where and when INLINE is helpful (rather than blindly removing some INLINEs and re-profiling to see what difference it makes, as in many cases it *does* require the INLINE for performance). > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > -- Ivan Lazar Miljenovic Ivan.Miljenovic at gmail.com http://IvanMiljenovic.wordpress.com From acuzzio at gmail.com Sat Mar 29 16:15:46 2014 From: acuzzio at gmail.com (Alessio Valentini) Date: Sat, 29 Mar 2014 17:15:46 +0100 Subject: [Haskell-cafe] Parsec Preprocessor Message-ID: Dear Haskellers This is gonna be my first post on here : ) . I am developing some tools to interact with Chemistry packages, and I basically have to write input files for those programs. I would like to be able to write those input in a better way inside the hs code. For example this would be perfect ( {{{+ and +}}} are just labels to mark the "special syntax"): --------------a.hs-------------------------------- main = do writeFile "inputOfChemPack" string string = {{{+ This is the actual input file Formatted like this with some %variable +}}} variable = "foo" -------------------------------------------------- I have written a parser that is reading the code and outputs a file like this (it can handle special characters and variables that are not strings, but let's keep it simple here): ----------------b.hs------------------------------ main = do writeFile "inputOfChemPack" string string = "This is the actual input file\nFormatted like this\nwith some " ++ variable ++ " " variable = "foo" -------------------------------------------------- Now... this file can be compiled and it does exactly what I want: it prints a file like this: --------inputOfChemPack----- This is the actual input file Formatted like this with some foo -------------------------------------- Now the big question... right now I am doing this with some bash scripts (run the parser on the file and then compile its output)... but... is it possible to automatize this using my parser as a sort of preprocessor? the "dream" would be to make an extension that just applies the parser automatically before compilation, such as: -----------------a.hs----------------------------- {-# extensionName #-} main = do writeFile "inputOfChemPack" string string = {{{+ This is the actual input file Formatted like this with some %variable +}}} variable = "foo" -------------------------------------------------- $ ghci a.hs GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help Loading package ghc-prim ... linking ... done. Loading package integer-gmp ... linking ... done. Loading package base ... linking ... done. [1 of 1] Compiling Main ( a.hs, interpreted ) Ok, modules loaded: Main. *Main> string "This is the actual input file\nFormatted like this\nwith some foo" I have been browsing stuffs about quasiquotation and preprocessors, but I have the feeling that is a quite simple task compared to those solutions. Any ideas? How can I solve this problem? Thank you Alessio -------------- next part -------------- An HTML attachment was scrubbed... URL: From bob at redivi.com Sat Mar 29 16:57:22 2014 From: bob at redivi.com (Bob Ippolito) Date: Sat, 29 Mar 2014 09:57:22 -0700 Subject: [Haskell-cafe] Parsec Preprocessor In-Reply-To: References: Message-ID: You don't need to build your own QuasiQuoter, a number of suitable ones exist on Hackage already. Just search for interpolation or quasi-quoter and you'll find something appropriate to use for your application. Using a pre-processor is almost certainly not going to be simpler. On Sat, Mar 29, 2014 at 9:15 AM, Alessio Valentini wrote: > Dear Haskellers > > This is gonna be my first post on here : ) . > > I am developing some tools to interact with Chemistry packages, and I > basically have to write input files for those programs. > > I would like to be able to write those input in a better way inside the hs > code. For example this would be perfect ( {{{+ and +}}} are just labels to > mark the "special syntax"): > > --------------a.hs-------------------------------- > main = do > writeFile "inputOfChemPack" string > > string = {{{+ > This is the actual input file > Formatted like this > with some %variable > +}}} > > variable = "foo" > -------------------------------------------------- > > I have written a parser that is reading the code and outputs a file like > this (it can handle special characters and variables that are not strings, > but let's keep it simple here): > > ----------------b.hs------------------------------ > main = do > writeFile "inputOfChemPack" string > > string = "This is the actual input file\nFormatted like this\nwith some " > ++ variable ++ " " > > variable = "foo" > -------------------------------------------------- > > Now... this file can be compiled and it does exactly what I want: it > prints a file like this: > > --------inputOfChemPack----- > This is the actual input file > Formatted like this > with some foo > -------------------------------------- > > Now the big question... right now I am doing this with some bash scripts > (run the parser on the file and then compile its output)... but... is it > possible to automatize this using my parser as a sort of preprocessor? > > the "dream" would be to make an extension that just applies the parser > automatically before compilation, such as: > > -----------------a.hs----------------------------- > {-# extensionName #-} > > main = do > writeFile "inputOfChemPack" string > > string = {{{+ > This is the actual input file > Formatted like this > with some %variable > +}}} > > variable = "foo" > -------------------------------------------------- > > $ ghci a.hs > GHCi, version 7.6.3: http://www.haskell.org/ghc/ :? for help > Loading package ghc-prim ... linking ... done. > Loading package integer-gmp ... linking ... done. > Loading package base ... linking ... done. > [1 of 1] Compiling Main ( a.hs, interpreted ) > Ok, modules loaded: Main. > *Main> string > "This is the actual input file\nFormatted like this\nwith some foo" > > I have been browsing stuffs about quasiquotation and preprocessors, but I > have the feeling that is a quite simple task compared to those solutions. > > Any ideas? How can I solve this problem? > > Thank you > > Alessio > > _______________________________________________ > 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 winterkoninkje at gmail.com Sun Mar 30 06:56:27 2014 From: winterkoninkje at gmail.com (wren romano) Date: Sun, 30 Mar 2014 02:56:27 -0400 Subject: [Haskell-cafe] Inline makes program slow? In-Reply-To: References: Message-ID: On Fri, Mar 28, 2014 at 9:43 PM, Kai Zhang wrote: > Without inline (remove the inline pragma), "slow" would be much faster. I > suspect this is because ghc can build a "persistent structure" for the > partial applied function. After inline, each call of "g" will try to build a > new vector. How can I tell ghc not to inline some specific functions? Or are > there other ways to resolve this issue? For what it's worth, I don't think this is an inlining issue, per se; rather, it's an issue with the fact that eta-conversion does not preserve performance characteristics. That is, when we inline h and perform as much beta-reduction as we can, we're left with the lambda expression: \i -> (V.fromList $ sort str) V.! i Which is not necessarily the same thing, performance-wise, as: ((V.fromList $ sort str) V.!) The problem is that, implicitly, the whole body of the lambda abstraction (might) depend on the value of i and therefore cannot be performed until we know what i is. If we wanted to make it explicit that sorting the string is independent of the value of i, we could write: let s = V.fromList $ sort str in \i -> s V.! i By using let-binding to lift most of the computation out of the body of the lambda abstraction, we ensure that the sorting will only be done once, rather than (possibly) being done every time this function is called. The reason I say "might" and "possibly" is because, in theory, the compiler could choose to perform this transformation for you. And sometimes it does (as apparently it does in your fast code). The problem is that, in practice, performing this transformation everywhere can slow things down horribly by taking too much memory because you're trying to hold onto too many things. Thus, the compiler must rely on heuristics to decide when it should float computations out from under lambdas and when it shouldn't. -- Live well, ~wren From martin.drautzburg at web.de Sun Mar 30 14:06:24 2014 From: martin.drautzburg at web.de (martin) Date: Sun, 30 Mar 2014 16:06:24 +0200 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: References: <532DBFAB.7080908@web.de> Message-ID: <533824E0.5010001@web.de> Am 03/24/2014 12:34 AM, schrieb John Lato: > I would keep in mind that, given the constraints > > - you want to group together all equal elements from the entire list > - the only operation you can perform on elements is comparison for equality > > your function will have quadratic complexity (at least I can't see any way around it). Wouldn't a modified quicksort give n*log(n) complexity. Something like: groupEq [] = [] groupEq (x:xs) = (groupEq a) ++ [x] ++ (groupEq b) where a = filter (==x) xs b = filter (/= x) xs This is indeed much slower than the built-in sort, but it slower too whern I replace "==" with ">", resulting in a texbook quicksort. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Mar 30 14:12:32 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 30 Mar 2014 15:12:32 +0100 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <533824E0.5010001@web.de> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> Message-ID: <20140330141232.GM29562@weber> On Sun, Mar 30, 2014 at 04:06:24PM +0200, martin wrote: > Am 03/24/2014 12:34 AM, schrieb John Lato: > > I would keep in mind that, given the constraints > > > > - you want to group together all equal elements from the entire list > > - the only operation you can perform on elements is comparison for equality > > > > your function will have quadratic complexity (at least I can't see any way around it). > > Wouldn't a modified quicksort give n*log(n) complexity. Something like: Quicksort is O(n^2) in the worst case. From ky3 at atamo.com Sun Mar 30 16:00:19 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Sun, 30 Mar 2014 23:00:19 +0700 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <533824E0.5010001@web.de> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> Message-ID: On Sun, Mar 30, 2014 at 9:06 PM, martin wrote: > groupEq (x:xs) = (groupEq a) ++ [x] ++ (groupEq b) > where > a = filter (==x) xs > b = filter (/= x) xs > Why the need to recurse on "a"? It's a list of identical elements! -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From rethab at rethab.ch Sun Mar 30 16:02:47 2014 From: rethab at rethab.ch (=?ISO-8859-1?Q?Reto_Habl=FCtzel?=) Date: Sun, 30 Mar 2014 18:02:47 +0200 Subject: [Haskell-cafe] TLS Handshake fails with 'invalid header type: 1\nFrom:\theader\n\n"' Message-ID: Hello, I'm trying to a establish a TLS connection with the hs-tls library. I got most of the code from the Stunnel.hs, but what I am trying do here is to be able to pass either 'Client' or 'Server' as argument and then, depending on which one it is, act as either one in the handshake. This is the code, that tries to make the handshake: client :: Socket -> IO () client sock = do addr <- sockaddr _ <- connect sock addr ctx <- myCCtx sock contextHookSetLogging ctx logging handshake ctx server :: Socket -> IO () server sock = do sockaddr >>= bind sock listen sock 1 (peer, _) <- accept sock ctx <- mySCtx peer contextHookSetLogging ctx logging handshake ctx The rest of it would probably too much to fit into an email, so I am linking it from here: http://lpaste.net/102014 When I run it, the client fails to parse the handshake: Error_Packet_Parsing "Failed reading: invalid header type: 1\nFrom:\theader\n\n" Whereas the server says 'server hello done' right before it receives the alert from the client. How can this happen? That 'From:\theader...' doesn't even exist as a string in the hs-tls library.. Is there anywhere an example for the hs-tls library with a client as well as a server? Thanks a lot! - Reto -------------- next part -------------- An HTML attachment was scrubbed... URL: From djsamperi at gmail.com Sun Mar 30 16:57:39 2014 From: djsamperi at gmail.com (Dominick Samperi) Date: Sun, 30 Mar 2014 12:57:39 -0400 Subject: [Haskell-cafe] Inline makes program slow? In-Reply-To: References: Message-ID: Compiler optimization levels are also important. The attached program compiles and runs ok using: ghc -O fibmustopt.hs ./fibmustopt But if the '-O' option is omitted all of the available memory is used and it fails. On Sun, Mar 30, 2014 at 2:56 AM, wren romano wrote: > On Fri, Mar 28, 2014 at 9:43 PM, Kai Zhang wrote: >> Without inline (remove the inline pragma), "slow" would be much faster. I >> suspect this is because ghc can build a "persistent structure" for the >> partial applied function. After inline, each call of "g" will try to build a >> new vector. How can I tell ghc not to inline some specific functions? Or are >> there other ways to resolve this issue? > > For what it's worth, I don't think this is an inlining issue, per se; > rather, it's an issue with the fact that eta-conversion does not > preserve performance characteristics. That is, when we inline h and > perform as much beta-reduction as we can, we're left with the lambda > expression: > > \i -> (V.fromList $ sort str) V.! i > > Which is not necessarily the same thing, performance-wise, as: > > ((V.fromList $ sort str) V.!) > > The problem is that, implicitly, the whole body of the lambda > abstraction (might) depend on the value of i and therefore cannot be > performed until we know what i is. If we wanted to make it explicit > that sorting the string is independent of the value of i, we could > write: > > let s = V.fromList $ sort str in \i -> s V.! i > > By using let-binding to lift most of the computation out of the body > of the lambda abstraction, we ensure that the sorting will only be > done once, rather than (possibly) being done every time this function > is called. > > The reason I say "might" and "possibly" is because, in theory, the > compiler could choose to perform this transformation for you. And > sometimes it does (as apparently it does in your fast code). The > problem is that, in practice, performing this transformation > everywhere can slow things down horribly by taking too much memory > because you're trying to hold onto too many things. Thus, the compiler > must rely on heuristics to decide when it should float computations > out from under lambdas and when it shouldn't. > > -- > Live well, > ~wren > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe -------------- next part -------------- A non-text attachment was scrubbed... Name: fibmustopt.hs Type: text/x-haskell Size: 156 bytes Desc: not available URL: From grrwlf at gmail.com Sun Mar 30 19:04:12 2014 From: grrwlf at gmail.com (Sergey Mironov) Date: Sun, 30 Mar 2014 23:04:12 +0400 Subject: [Haskell-cafe] [ANN] cake3-0.4.0.0 released Message-ID: Hi! I'm glad to announce a new version of cake3 the Makefile generator. http://hackage.haskell.org/package/cake3 https://github.com/grwlf/cake3 Cake3 is a EDSL for building Makefiles, written in Haskell. With cake3, developer can write their build logic in Haskell, obtain clean and safe Makefile and distribute it among the non-Haskell-aware users. Currenly, GNU Make is the only backend supported. === Chagnes === - Automatically generate the 'clean' rule - New genFile and genTmpFile functions embed text files into the Makefile. - The Ur/Web extension improved === The sample program === module Cakefile where import Development.Cake3 import Cakefile_P main = writeMake (file "Makefile") $ do selfUpdate cs <- return $ [file "main.c", file "second.c"] d <- rule $ do shell [cmd|gcc -M $cs -MF @(file "depend.mk")|] os <- forM cs $ \c -> do rule $ do shell [cmd| gcc -c $(extvar "CFLAGS") -o @(c.="o") $c |] elf <- rule $ do shell [cmd| gcc -o @(file "main.elf") $os |] rule $ do phony "all" depend elf includeMakefile d Regards, Sergey From martin.drautzburg at web.de Sun Mar 30 19:47:18 2014 From: martin.drautzburg at web.de (martin) Date: Sun, 30 Mar 2014 21:47:18 +0200 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> Message-ID: <533874C6.6080608@web.de> Am 03/30/2014 06:00 PM, schrieb Kim-Ee Yeoh: > > On Sun, Mar 30, 2014 at 9:06 PM, martin > wrote: > > groupEq (x:xs) = (groupEq a) ++ [x] ++ (groupEq b) > where > a = filter (==x) xs > b = filter (/= x) xs > > > Why the need to recurse on "a"? It's a list of identical elements! Silly me. I had just mechanically modified the textbook quicksort. From fvillanustre at gmail.com Sun Mar 30 20:34:13 2014 From: fvillanustre at gmail.com (Flavio Villanustre) Date: Sun, 30 Mar 2014 16:34:13 -0400 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <20140330141232.GM29562@weber> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> <20140330141232.GM29562@weber> Message-ID: Martin might have meant merge sort... :) Flavio Sent from my iPhone > On Mar 30, 2014, at 10:12 AM, Tom Ellis wrote: > >> On Sun, Mar 30, 2014 at 04:06:24PM +0200, martin wrote: >> Am 03/24/2014 12:34 AM, schrieb John Lato: >>> I would keep in mind that, given the constraints >>> >>> - you want to group together all equal elements from the entire list >>> - the only operation you can perform on elements is comparison for equality >>> >>> your function will have quadratic complexity (at least I can't see any way around it). >> >> Wouldn't a modified quicksort give n*log(n) complexity. Something like: > > Quicksort is O(n^2) in the worst case. > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe at haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe From martin.drautzburg at web.de Sun Mar 30 20:50:54 2014 From: martin.drautzburg at web.de (martin) Date: Sun, 30 Mar 2014 22:50:54 +0200 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <20140330141232.GM29562@weber> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> <20140330141232.GM29562@weber> Message-ID: <533883AE.100@web.de> Am 03/24/2014 12:34 AM, schrieb John Lato:> I would keep in mind that, given the constraints > > - you want to group together all equal elements from the entire list > - the only operation you can perform on elements is comparison for equality > > your function will have quadratic complexity (at least I can't see any way around it). If there's any way of > sorting the elements, even if the order is entirely arbitrary, you should consider it. Am 03/30/2014 04:12 PM, schrieb Tom Ellis: > > Quicksort is O(n^2) in the worst case. > I just took the sort function from Data.List and replaced all occurences of cmp x == GT by (==) and all others by (/=). I didn't even bother to understand the algorithm. What I got is a reordered list where all equal elements are aligned next to each other. I have no reason to assume that this aligning is more expensive than true sorting. Unlike my naive quicksort, it has no problem with millions of elements. But of course it makes little sense to implement an aligning function and then use the native groupBy, when you can easily roll your own fast groupEq as Brent Yorgey pointed out: groupEq :: Eq a => [a] -> [[a]] groupEq [] = [] groupEq (a:rest) = (a:as) : groupEq bs where (as,bs) = partition (==a) rest This one is even a bit faster than my modifed sort. So all in all there seems to be no benefit of sorting the list fist and asking for (Ord=>) when Eq is sufficient. From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Sun Mar 30 21:15:56 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Sun, 30 Mar 2014 22:15:56 +0100 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <533883AE.100@web.de> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> <20140330141232.GM29562@weber> <533883AE.100@web.de> Message-ID: <20140330211556.GQ29562@weber> On Sun, Mar 30, 2014 at 10:50:54PM +0200, martin wrote: > I just took the sort function from Data.List and replaced all occurences > of cmp x == GT by (==) and all others by (/=). I didn't even bother to > understand the algorithm. What I got is a reordered list where all equal > elements are aligned Data.List.sort is a merge sort and the merge phase of this will not carry over to a correct 'groupBy'. Please check your implementation again! > But of course it makes little sense to implement an aligning function and > then use the native groupBy, when you can > easily roll your own fast groupEq as Brent Yorgey pointed out: > groupEq :: Eq a => [a] -> [[a]] > groupEq [] = [] > groupEq (a:rest) = (a:as) : groupEq bs > where (as,bs) = partition (==a) rest This is O(n^2). Tom From itz at buug.org Sun Mar 30 23:53:54 2014 From: itz at buug.org (Ian Zimmerman) Date: Sun, 30 Mar 2014 16:53:54 -0700 Subject: [Haskell-cafe] GHC and platform versions Message-ID: <20140330165354.55d3aaef.itz@buug.org> On the Haskell Platform webpage, it tells me what GHC version I need for the latest/current version of the platform. Also, there are links to downloads for prior versions of the platform. But, how can I find out what GHC version I need for one of those older platform versions? That information doesn't seem to be on the page, and I see no README or similar file in the platform source tarball itself. -- Please *no* private copies of mailing list or newsgroup messages. gpg public key: 2048R/984A8AE4 fingerprint: 7953 ADA1 0E8E AB57 FB79 FFD2 360A 88B2 984A 8AE4 Funny pic: http://bit.ly/ZNE2MX From roma at ro-che.info Mon Mar 31 08:31:26 2014 From: roma at ro-che.info (Roman Cheplyaka) Date: Mon, 31 Mar 2014 11:31:26 +0300 Subject: [Haskell-cafe] Haskell Weekly News In-Reply-To: <1396251370106-5746682.post@n5.nabble.com> References: <1396251370106-5746682.post@n5.nabble.com> Message-ID: <20140331083126.GA7206@sniper> (This was submitted to glasgow-haskell-users, probably by mistake. Redirecting to cafe.) * harry [2014-03-31 00:36:10-0700] > There hasn't been a HWN since mid-December. I've emailed the editor with no > response, and there doesn't seem to have been any (public) online activity > from him since. > > I hope he's OK, but either way, it seems that HWN needs a new editor. Any > volunteers? While we're at it, I suggest to potential editors to look up how HWN looked back when Brent Yorgey was the editor. IMO it was much more interesting to read than a mechanically compiled list of reddit and SO posts which HWN has become lately. That style is more time and effort consuming, though. (http://ro-che.info/ccc/06) Roman From martin.drautzburg at web.de Mon Mar 31 09:27:47 2014 From: martin.drautzburg at web.de (martin) Date: Mon, 31 Mar 2014 11:27:47 +0200 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <20140330211556.GQ29562@weber> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> <20140330141232.GM29562@weber> <533883AE.100@web.de> <20140330211556.GQ29562@weber> Message-ID: <53393513.9020803@web.de> Am 03/30/2014 11:15 PM, schrieb Tom Ellis: >> groupEq :: Eq a => [a] -> [[a]] >> groupEq [] = [] >> groupEq (a:rest) = (a:as) : groupEq bs >> where (as,bs) = partition (==a) rest > > This is O(n^2). I understood, that you suggested to go ahead and sort the list, instead of just aligning equal elements next to each other. So far all my attempts to prove you wrong failed. But I still have trouble to believe, that sorting (Ord=>) is cheaper than aligning (Eq=>) because sorting does aligning plus some more. Does (Ord=>) make life so much easier, or why do you think this is the case? From tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk Mon Mar 31 10:19:09 2014 From: tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk (Tom Ellis) Date: Mon, 31 Mar 2014 11:19:09 +0100 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <53393513.9020803@web.de> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> <20140330141232.GM29562@weber> <533883AE.100@web.de> <20140330211556.GQ29562@weber> <53393513.9020803@web.de> Message-ID: <20140331101909.GV29562@weber> On Mon, Mar 31, 2014 at 11:27:47AM +0200, martin wrote: > Am 03/30/2014 11:15 PM, schrieb Tom Ellis: > >> groupEq :: Eq a => [a] -> [[a]] > >> groupEq [] = [] > >> groupEq (a:rest) = (a:as) : groupEq bs > >> where (as,bs) = partition (==a) rest > > > > This is O(n^2). > > I understood, that you suggested to go ahead and sort the list, instead of just aligning equal elements next to each > other. So far all my attempts to prove you wrong failed. > > But I still have trouble to believe, that sorting (Ord=>) is cheaper than aligning (Eq=>) because sorting does aligning > plus some more. Does (Ord=>) make life so much easier, or why do you think this is the case? An Ord instance is a total order on your datatype and gives you extra properties to work. Seemingly these properties help a lot! However, I'm not sure I'd say sorting does "aligning plus some more". Depending on what you want to do, sorting might be seen as "aligning minus some". When sorting, the whole collection comes out in sorted order not just in grouped blocks. That is, the range of a sorting function is strictly smaller (exponentially smaller I guess) than the range of a grouping function. Thus sorting loses a lot of information. Tom From alexander.vershilov at gmail.com Mon Mar 31 11:55:26 2014 From: alexander.vershilov at gmail.com (Alexander V Vershilov) Date: Mon, 31 Mar 2014 15:55:26 +0400 Subject: [Haskell-cafe] [ANN] network-transport-zeromq-0.1. In-Reply-To: References: Message-ID: Hi, On 31 March 2014 15:41, Mathieu Boespflug wrote: > Hi Edsko, > > no worries. > >> Have you tried running Cloud Haskell on top of 0MQ, or are >> you using Network.Transport for something else? > > We're at a point where all distributed-process-tests pass, not just > network-transport-tests (Alexander can confirm). I need to add a correction, some tests, that implies connection break doesn't work, i.e. they are locking (but very rarely they are passing), and I didn't found a valid reason for it. I will try to prepare a email with description of this problem and everything I've found out in a next few days. -- Alexander From ky3 at atamo.com Mon Mar 31 16:45:05 2014 From: ky3 at atamo.com (Kim-Ee Yeoh) Date: Mon, 31 Mar 2014 23:45:05 +0700 Subject: [Haskell-cafe] Haskell Weekly News In-Reply-To: <20140331083126.GA7206@sniper> References: <1396251370106-5746682.post@n5.nabble.com> <20140331083126.GA7206@sniper> Message-ID: On Mon, Mar 31, 2014 at 3:31 PM, Roman Cheplyaka wrote: > While we're at it, I suggest to potential editors to look up how HWN > looked back > when Brent Yorgey was the editor. IMO it was much more interesting to read > than a mechanically compiled list of reddit and SO posts which HWN has > become lately. > It can be a thankless task publishing HWN, so all the same I'd like to thank the current editor, Daniel Santa Cruz, for his diligence carrying out the duty for over 3 years. Also, before Brent, there was Don Stewart, and before him, there was John Goerzen. I think all 3 of them set very high standards for the rest to follow. A big thanks to them for providing so much entertaining and profitable reading. If no one else wants HWN, I'll do it. -- Kim-Ee -------------- next part -------------- An HTML attachment was scrubbed... URL: From klao at nilcons.com Mon Mar 31 18:15:43 2014 From: klao at nilcons.com (Mihaly Barasz) Date: Mon, 31 Mar 2014 20:15:43 +0200 Subject: [Haskell-cafe] Towards a better time library (announcing tz) Message-ID: <20140331181543.GA20036@cs.elte.hu> I would like to propose reforming the 'time' [1] library. Initially, I was just planning to announce my new 'tz' [2] library, but realized that I have a more important agenda. Namely: Haskell needs a better time library! Let me summarize what are ? in my view ? the biggest deficiencies of 'time': 1. Inefficient data structures and implementations. 2. Ad-hoc API which is hard to remember and frustrating to work with. 3. Conceptually wrong representations and/or missing concepts. The wonderful thyme [3] package (by Liyang HU) improves a lot on #1 by choosing better data structures and careful implementations and on #2 by lensifying the API. But, it was the #3 that caused me the most frustration lately; most importantly the time zone handling. There is a TimeZone data type in 'time', but it is a misnomer, it basically represents a fixed time difference (with a label and a DST flag). 'time' basically adapts the broken approach from libc: you can work with one time zone at a time, which is defined globally for your program (via the TZ environment variable). So, the transformation between UTCTime and LocalTime which should have been a pure function can only be done in IO now. Like this: do tz <- getTimeZone ut return $ utcToLocalTime tz ut Oh, and just to hammer down on the point #1 from the list above. This code runs in about 6100 ns on my machine. The drop-in replacement from tz: utcToLocalTimeTZ [4] (which is actually pure) runs in 2300 ns. While this is a significant improvement, it's easy to miss the point where the bulk of the inefficiency comes from the data structures. In my main project we represent times as Int64 (raw nanoseconds since UNIX epoch; and similar representation for zoned times). And to convert those to and from different time zones we need 40 ns. That's right, a 150 _times_ improvement! (There are many other interesting benchmark results that I could mention. An exciting bottom line: we can actually beat the libc in many use-cases!) The 'tz' package is still very much in flux. I will try to solidify the API soon, but until then it should be considered more of a proof of concept. There is some missing functionality, for example. On the other hand, there are the 'timezone-series' [5] and 'timezone-olson' [6] packages that together provide about the same functionality as 'tz' (minus the efficiency), and I'd like to explore if we could remove some of the overlap. But, all kind of suggestions and requests are welcome! More importantly, I'd like to hear the opinions of the community about the general issue of a better time library! Do we need one? How should we proceed about it? I think, Haskell could potentially have one of the best time libraries, but the current de-facto standard is mediocre at best. Unfortunately, designing a good time library is very far from trivial, as many existing examples demonstrate. And I definitely don't know enough for it. (I understand time zone info files, now that I wrote tz, but that's just a tiny fraction of what's needed.) So, if you think you can contribute to the design (have important use-cases in mind, know good examples of API, have some experience working with dates and time, etc. etc.) ? speak up! Mihaly Footnotes: [1] http://hackage.haskell.org/package/time [2] http://hackage.haskell.org/package/tz [3] http://hackage.haskell.org/package/thyme [4] http://hackage.haskell.org/package/tz-0.0.0.1/docs/Data-Time-Zones.html#v:utcToLocalTimeTZ [5] http://hackage.haskell.org/package/timezone-series [6] http://hackage.haskell.org/package/timezone-olson -------------- next part -------------- A non-text attachment was scrubbed... Name: signature.asc Type: application/pgp-signature Size: 481 bytes Desc: Digital signature URL: From byorgey at seas.upenn.edu Mon Mar 31 21:15:58 2014 From: byorgey at seas.upenn.edu (Brent Yorgey) Date: Mon, 31 Mar 2014 17:15:58 -0400 Subject: [Haskell-cafe] Haskell Weekly News In-Reply-To: References: <1396251370106-5746682.post@n5.nabble.com> <20140331083126.GA7206@sniper> Message-ID: <20140331211558.GA7886@seas.upenn.edu> On Mon, Mar 31, 2014 at 11:45:05PM +0700, Kim-Ee Yeoh wrote: > On Mon, Mar 31, 2014 at 3:31 PM, Roman Cheplyaka wrote: > > > While we're at it, I suggest to potential editors to look up how HWN > > looked back > > when Brent Yorgey was the editor. IMO it was much more interesting to read > > than a mechanically compiled list of reddit and SO posts which HWN has > > become lately. > > > > It can be a thankless task publishing HWN, so all the same I'd like to > thank the current editor, Daniel Santa Cruz, for his diligence carrying out > the duty for over 3 years. > > Also, before Brent, there was Don Stewart, and before him, there was John > Goerzen. Don't forget Joe Fredette who also did it for a year! -Brent From kazu at iij.ad.jp Mon Mar 31 21:52:34 2014 From: kazu at iij.ad.jp (Kazu Yamamoto (=?iso-2022-jp?B?GyRCOzNLXE9CSScbKEI=?=)) Date: Tue, 01 Apr 2014 06:52:34 +0900 (JST) Subject: [Haskell-cafe] ghc-mod v4.0.0 Message-ID: <20140401.065234.47953475024487326.kazu@iij.ad.jp> Hello, I'm happy to announce the release of ghc-mod v4.0.0. You can see its changelog here: http://hackage.haskell.org/package/ghc-mod-4.0.0/changelog This version provides an interactive command called ghc-modi. As you can guess, this makes syntax error highlighting much faster. The Emacs front-end resolves the "import hell". If you are an Emacs user, probably it is worth reading this page: http://mew.org/~kazu/proj/ghc-mod/en/emacs.html The entire documentation was re-written. Please give a look at it if you are interested: http://mew.org/~kazu/proj/ghc-mod/en/ P.S. This is not April fool. --Kazu From rendel at informatik.uni-marburg.de Mon Mar 31 22:00:31 2014 From: rendel at informatik.uni-marburg.de (Tillmann Rendel) Date: Tue, 01 Apr 2014 00:00:31 +0200 Subject: [Haskell-cafe] groupBy without Ord? In-Reply-To: <53393513.9020803@web.de> References: <532DBFAB.7080908@web.de> <533824E0.5010001@web.de> <20140330141232.GM29562@weber> <533883AE.100@web.de> <20140330211556.GQ29562@weber> <53393513.9020803@web.de> Message-ID: <5339E57F.3080305@informatik.uni-marburg.de> Hi, martin wrote: > But I still have trouble to believe, that sorting (Ord=>) is cheaper than aligning (Eq=>) because sorting does aligning > plus some more. Does (Ord=>) make life so much easier [...]? Yes, it does. For example, if you know that x < y and you know that y < z, you immediately also know that x < z without having to call (<) a third time. But if you know that x /= y and you know that y /= z, you don't know anything about whether x /= z or not. To learn this, you have to call (/=) a third time. Many sorting algorithms exploit this by cleverly comparing elements in such an order that no matter how they compare, we get to safe some of the calls to (<). This situation is typical in programming: A seemingly harder problem can be easier to solve than an seemingly easier variant, because partial solutions of the seemingly harder problem contain more information than partial solutions of the seemingly easier variant of the problem. In this case, the partial solutions are the results of x < y and y < z, and if they are both true, they contain enough information to also know x < z without computing anything. So if you cannot solve a problem, sometimes you have to make it harder in order to make it easier. Tillmann