[Haskell-cafe] Up and Down the Latter of Abstraction
Hi Cafe. I came across an interesting page about interactive abstraction called "Up and Down the Latter of Abstraction" [1] while browsing hacker-news. Under the appendix "Tools & Implementation" Bret Victor ponders: "Perhaps language theorists will stop messing around with arrows and dependent types, and start inventing languages suitable for interactive development and discovery." I don't subscribe to the idea that static guarantees and functional characteristics are mutually exclusive to interactive development and discovery and I think they may actually complement each other extremely well, but this page certainly does sell the interactive aspect very effectively. The closest I've seen to this proces from Haskell seems to have come from "luite" and co (correct me if I'm wrong) and their work on the Diagrams package and its surrounding infrastructure [2], however, their interactive demonstrations no longer seem to be online. Still, the dominant interface seems to be web-based, and I feel that a native environment for this kind of explorative interactive programming would be more effective. Other languages that seem to be especially effective at this kind of development are Processing [3] and Mathematica [4]. Has anyone had experience with interactive development in Haskell? [1] - http://worrydream.com/LadderOfAbstraction/ -- "Appendix: Tools & Implementation" [2] - http://pnyf.inf.elte.hu/fp/Diagrams_en.xml [3] - http://processing.org/ [4] - http://www.wolfram.com/mathematica/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANNOUNCE: simple-actors 0.1.0 - an eDSL library for actor model concurrency
On Tue, Oct 11, 2011 at 2:37 PM, Brandon Simmons wrote: > I'm happy to announce the release of my library 'simple-actors', a > DSL-style library for more structured concurrent programs based on the > Actor Model. It offers an alternative to ad-hoc use of Chans that > allows for tight control of side-effects and message passing, and is > especially suited to applications such as simulations of > communicating processes. Pretty interesting! > Here is an example of a system of actors working as a binary tree, > supporting insert and query operations: [snip] I'm kind of spoiled after having used Haskell for a long time, so I couldn't ignore the fact that your example is tied to Ints and don't store a value =). So I've changed the example, as seen below. It's somewhat more complex, but I like the fact that now 'branch' has to deal with updating the value of its key =). -8<-BEGIN-EXAMPLE-8< module Main where import Control.Concurrent.Actors import Control.Applicative import Control.Concurrent.MVar type Node k v = Mailbox (Operation k v) -- operations supported by the network: data Operation k v = Insert { key :: k , val :: v } | Query { key:: k , sigVar :: MVar (Maybe v) } -- the actor equivalent of a Nil leaf node: nil :: Ord k => Behavior (Operation k v) nil = Receive $ do (Query _key var) <- received send var Nothing -- signal that key is not present in tree return nil -- await next message <|> do -- else, Insert received l <- spawn nil -- spawn child nodes r <- spawn nil (Insert key val) <- received return $ branch l r key val -- create branch from inserted val -- a "branch" node with a key-value pair and two children branch :: Ord k => Node k v -> Node k v -> k -> v -> Behavior (Operation k v) branch l r k = go where go v = Receive $ do m <- received case compare (key m) k of LT -> send l m >> cont v GT -> send r m >> cont v EQ -> case m of (Query _ var) -> send var (Just v) >> cont v (Insert _ val) -> cont val cont = return . go insert :: Node k v -> (k, v) -> IO () insert t (k,v) = send t (Insert k v) -- MVar is in the 'SplitChan' class so actors can 'send' to it: query :: Node k v -> k -> IO (Maybe v) query t k = do v <- newEmptyMVar send t (Query k v) takeMVar v main :: IO () main = do t <- spawn nil mapM_ (insert t) [(5, "five"), (3, "three"), (7, "seven"), (2, "two"), (4, "four"), (6, "six"), (8, "eight"), (5, "BOO!")] mapM (query t) [1,2,5,7] >>= print -8<-END-EXAMPLE-8< Cheers, -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] haskell i18n best practices
On Tue, Oct 11, 2011 at 5:03 PM, Edward Kmett wrote: > I'll admit I have only ever really tested this with a joke en@lolcat > translation, which I auto-translate with perl, though I admit if I could > find a nice perl module for generating zalgo-style text, en@zalgo would be > pretty neat to auto-generate as well. Using Yesod's approach and assuming lolspeak :: String -> String you could have render_en_lolcat = lolspeak . render_en_US Pretty neat! ;-D Cheers, -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hunit Testing
On Wed, Oct 12, 2011 at 03:55:43AM +0530, mukesh tiwari wrote: > Hello everyone > I was going through this tutorial > http://hunit.sourceforge.net/HUnit-1.0/Guide.html and just wrote some simple > code but i am getting error > > ghci>let test1 = TestCase (assertEqual " equal " 3 ( id 3 )) ghci>let > tests = [ TestLabel "test 1" test1 ]ghci>runTestTT tests > :0:11: > Couldn't match expected type `Test' with actual type `[Test]' > In the first argument of `runTestTT', namely `tests' > In the expression: runTestTT tests > In an equation for `it': it = runTestTT tests > > > Could some one please tell me what is wrong with this code. This is something you should be able to figure out yourself. The error message is actually quite good. It says that it expects 'tests' to have type 'Test', but it actually has type '[Test]'. We can see why it has type [Test]: it is defined as tests = [ TestLabel ... ] that is, a list with a single element. So why is its type *expected* to be 'Test'? Well, look at the type of runTestTT: runTestTT :: Test -> IO Counts It expects a Test as its argument. So, that is what is wrong. The right way to fix it is not as obvious, but Ivan already covered that. -Brent ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hunit Testing
Thank you On Oct 12, 3:35 am, Ivan Lazar Miljenovic wrote: > On 12 October 2011 09:25, mukesh tiwari wrote: > > > Hello everyone > > I was going through this > > tutorial http://hunit.sourceforge.net/HUnit-1.0/Guide.html and just wrote > > some simple code but i am getting error > > > ghci>let test1 = TestCase (assertEqual " equal " 3 ( id 3 )) > > ghci>let tests = [ TestLabel "test 1" test1 ] > > This should be: ghci>let tests = TestList [ TestLabel "test 1" test1 ] > Notice the missing "TestList" constructor! > > -- > Ivan Lazar Miljenovic > ivan.miljeno...@gmail.com > IvanMiljenovic.wordpress.com > > ___ > Haskell-Cafe mailing list > Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Best bit LIST data structure
On Sun, Oct 9, 2011 at 6:18 AM, Ryan Newton wrote: > > Yep, it is simple. But I prefer to only use well-tested data structure > libraries where I can! Here's an example simple implementation (partial -- > missing some common functions): > > > module Data.BitList > ( BitList > , cons, head, tail, empty > , pack, unpack, length, drop > ) > where > > import Data.Int > import Data.Bits > import Prelude as P hiding (head,tail,drop,length) > import qualified Data.List as L > import Test.HUnit > > data BitList = One {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 > | More {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 BitList > I suggest data BitTail = Zero | More {-# UNPACK #-} !Int64 BitTail data BitList = Head {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 BitTail empty = Head 0 0 Zero or else just data BitList = Head {-# UNPACK #-} !Int {-# UNPACK #-} !Int64 [Int64] empty = Head 0 0 [] length (Head n _ xs) = n + 64 * List.length xs unpack :: BitList -> [Bool] > unpack (One 0 _) = [] > unpack (One i bv)= (bv `testBit` (i-1)) : unpack (One (i-1) bv) > unpack (More 0 _ r) = unpack r > unpack (More i bv r) = (bv `testBit` (i-1)) : unpack (More (i-1) bv r) > I'd implement as view :: BitList -> Maybe (Bool, BitList) view (One 0 _) = Nothing view bl = Just (head bl, tail bl) unpack = unfoldr view > drop :: Int -> BitList -> BitList > drop 0 bl = bl > drop n bl | n >= 64 = case bl of > One _ _-> error "drop: not enough elements in BitList" > More i _ r -> drop (n-i) r > drop n bl = case bl of > One i bv -> One (i-n) bv > More i bv r -> More (i-n) bv r > This is wrong. drop 5 (More 1 0 (One 64 0)) -> More (-4) 0 (One 64 0) Fixed version (also gives same behavior as List.drop when n > length l) drop :: Int -> BitList -> BitList drop n (One i bv) | n >= i = empty | otherwise = One (i - n) bv drop n (More i bv r) | n >= i = drop (n - i) r | otherwise = More (i - n) bv r -- ryan ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Hunit Testing
On 12 October 2011 09:25, mukesh tiwari wrote: > Hello everyone > I was going through this > tutorial http://hunit.sourceforge.net/HUnit-1.0/Guide.html and just wrote > some simple code but i am getting error > > ghci>let test1 = TestCase (assertEqual " equal " 3 ( id 3 )) > ghci>let tests = [ TestLabel "test 1" test1 ] This should be: ghci>let tests = TestList [ TestLabel "test 1" test1 ] Notice the missing "TestList" constructor! -- Ivan Lazar Miljenovic ivan.miljeno...@gmail.com IvanMiljenovic.wordpress.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Trouble using State Monad.
Your filter type isn't a Monad. In particular bind :: (a -> EitherT e (State FilterState) a) -> (a -> b -> EitherT e (State FilterState) b) -> b -> EitherT e (State FilterState) b can't be implemented, as you have no place to grab an 'a' to pass to the initial computation. If you fix the input type, you can do newtype Filter r e a = F { runFilter :: r -> EitherT e (State FilterState) a } which is isomorphic to newtype Filter r e a = F { runFilter :: ReaderT r (EitherT e (State FilterState)) a } which newtype deriving will be able to deal with easily. -- ryan On Sat, Oct 8, 2011 at 4:28 PM, Captain Freako wrote: > Hi all, > > I'm trying to use the State Monad to help implement a digital filter: > > 17 newtype Filter e a = F { > 18 runFilter :: a -> EitherT e (State FilterState) a > 19 } deriving (Monad, MonadState FilterState) > > but I'm getting these compiler errors: > > Filter.hs:19:14: > Can't make a derived instance of `Monad (Filter e)' > (even with cunning newtype deriving): > cannot eta-reduce the representation type enough > In the newtype declaration for `Filter' > > Filter.hs:19:21: > Can't make a derived instance of > `MonadState FilterState (Filter e)' > (even with cunning newtype deriving): > cannot eta-reduce the representation type enough > In the newtype declaration for `Filter' > > If I change the code to this: > > 17 newtype Filter e a = F { > * 18 runFilter :: EitherT e (State FilterState) a > ** * 19 } deriving (Monad, MonadState FilterState) > > it compiles, but I can't figure out how I'd feed the input to the filter, > in that case. > > In comparing this to the tricks used in constructing the State Monad based > version of the `Parser' type, > I notice that Parser gets around this issue, by having the input (i.e. - > input stream) be a part of the initial state, > but I'm not sure that's appropriate for a digital filter. > > Thanks, > -db > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Hunit Testing
Hello everyone I was going through this tutorial http://hunit.sourceforge.net/HUnit-1.0/Guide.html and just wrote some simple code but i am getting error ghci>let test1 = TestCase (assertEqual " equal " 3 ( id 3 )) ghci>let tests = [ TestLabel "test 1" test1 ]ghci>runTestTT tests :0:11: Couldn't match expected type `Test' with actual type `[Test]' In the first argument of `runTestTT', namely `tests' In the expression: runTestTT tests In an equation for `it': it = runTestTT tests Could some one please tell me what is wrong with this code. Regards Mukesh Tiwari ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] hackage-cabal.tar.gz error
I've installed hoogle and when i type hoogle data, this comes out Extracting tarball... gzip: ../hackage-cabal.tar.gz: invalid compressed data--format violated hoogle: System command failed: gzip --decompress --force ../hackage-cabal.tar.gz What is going wrong? -- View this message in context: http://haskell.1045720.n5.nabble.com/hackage-cabal-tar-gz-error-tp4893434p4893434.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The best way to call Java from Haskell?
Jerzy Karczmarczuk writes: > Don't worry, my friend. Haskell is lazy, so there is no problem in > "handling" those infinite modules. It will just take you an infinite > amount of time before you get any money from such a work. But this is > a general problem elsewhere as well. I guess you must be thinking of Haskell being increasingly used in banks? It must have been some bank manager who, after hiring one too many Haskell programmers, invented a scheme that would generate an infinite amount of money. He didn't realize before it was too late that the actual value of the scheme would be bottom... -k -- If I haven't seen further, it is by standing in the footprints of giants ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] haskell i18n best practices
On Thu, Sep 29, 2011 at 6:54 PM, Paulo Pocinho wrote: > Hello list. > > I've been trying to figure a nice method to provide localisation. An > application is deployed using a conventional installer. The end-user > is not required to have the Haskell runtimes, compiler or platform. > The application should bundle ready to use translation data. What I am > after is simple; an intuitive way that an interested translator, with > little knowledge of Haskell, can look at and create valid translation > data. > I've been meaning to bundle up some i18n/l10n code that I have lying around from previous compiler projects. What I was using was a gettext/printf template haskell function that can be hunted for with xgettext, which expands to code that reads translated .po files for the current module at two different times. Once at compile time to check that any printf-style format strings are compatible across each translation, and again later at runtime to allow for additional translations to be added. The biggest headache I have is that doing all this requires a pretty hairy .cabal file, and I haven't yet figured out how to package that up nicely for use in libraries. I'll admit I have only ever really tested this with a joke en@lolcattranslation, which I auto-translate with perl, though I admit if I could find a nice perl module for generating zalgo-style text, en@zalgo would be pretty neat to auto-generate as well. I'm not sure its considered "best practice", since I haven't bundled it up for third party use yet, but its *my* practice. ;) -Edward Kmett > This is what I've been looking at lately. The first thing I noticed > was the GNU gettext implementation for Haskell. The wiki page [1] has > a nice explanation by Aufheben. The hgettext package is found here > [2]. > > I don't know if this is a bad habit, but I had already separated the > dialogue text in the code with variables holding the respective > strings. At this time, I thought there could be some other way than > gettext. Then I figured how to import localisation data, that the > program loads, from external files. The data type is basically a tuple > with variable-names associated with strings. This is bit like the > file-embed package [3]. > > Still uncomfortable with i18n, I learned about the article "I18N in > Haskell" in yesod blog [4]. I'd like to hear more about it. > > What is considered the best practice for localisation? > > -- > [1] > http://www.haskell.org/haskellwiki/Internationalization_of_Haskell_programs > [2] http://hackage.haskell.org/packages/archive/hgettext/ > [3] http://hackage.haskell.org/package/file-embed > [4] http://www.yesodweb.com/blog/2011/01/i18n-in-haskell > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] wxhaskell : how to generate an event?
Dmitriy Nikitinskiy bel.ru> writes: > http://snipplr.com/view/17538/ Looks good, and seems to work. Thanks! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] ANNOUNCE: simple-actors 0.1.0 - an eDSL library for actor model concurrency
I'm happy to announce the release of my library 'simple-actors', a DSL-style library for more structured concurrent programs based on the Actor Model. It offers an alternative to ad-hoc use of Chans that allows for tight control of side-effects and message passing, and is especially suited to applications such as simulations of communicating processes. You can try it with a $ cabal install simple-actors and view the documentation here: http://hackage.haskell.org/package/simple-actors or check out the repo here: https://github.com/jberryman/simple-actors Here is an example of a system of actors working as a binary tree, supporting insert and query operations: EXAMPLE module Main where import Control.Concurrent.Actors import Control.Applicative import Control.Concurrent.MVar type Node = Mailbox Operation -- operations supported by the network: data Operation = Insert { val :: Int } | Query { val :: Int , sigVar :: MVar Bool } -- the actor equivalent of a Nil leaf node: nil :: Behavior Operation nil = Receive $ do (Query _ var) <- received send var False -- signal that Int is not present in tree return nil -- await next message <|> do -- else, Insert received l <- spawn nil -- spawn child nodes r <- spawn nil branch l r . val <$> received -- create branch from inserted val -- a "branch" node with an Int value 'v' and two children branch :: Node -> Node -> Int -> Behavior Operation branch l r v = loop where loop = Receive $ do m <- received case compare (val m) v of LT -> send l m GT -> send r m EQ -> case m of -- signal Int present in tree: (Query _ var) -> send var True _ -> return () return loop insert :: Node -> Int -> IO () insert t = send t . Insert -- MVar is in the 'SplitChan' class so actors can 'send' to it: query :: Node -> Int -> IO Bool query t a = do v <- newEmptyMVar send t (Query a v) takeMVar v main = do t <- spawn nil mapM_ (insert t) [5,3,7,2,4,6,8] mapM (query t) [1,5,0,7] >>= print END EXAMPLE I need to do some work on the documentation and performance testing. If anyone has anyone questions or comments, I would love to hear them. Thanks, Brandon http://coder.bsimmons.name ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The best way to call Java from Haskell?
On Tue, Oct 11, 2011 at 1:56 AM, dokondr wrote: > On Tue, Oct 11, 2011 at 12:42 PM, Yitzchak Gale wrote: >> >> Just out of curiosity, why do you not consider GF >> at all similar? To an outsider like me, there does >> appear to be quite a bit of similarity. > > As I understand GF is well suited for parsing well defined formal languages. > Not sure that GF can be used as NLP parser for blog messages that I need. That is correct - more or less. GF is a very expressive language, and it can handle a great deal of natural language, but it /does/ require that the input be grammatically correct, and it is difficult to work in unexpected vocabulary. GF is fantastic for making flexible Controlled Natural Languages, and it excels at producing human-readable text, but it is an entirely different beast from a statistical natural language parser, such as Stanford's. re: the original question -- The best method I've found for interfacing Haskell / Java for NLP is to share data with some common format, such as UIMAs CAS serialization. We really ought to start up a group of people interested in that over on the Haskell NLP list and see what we have if we pool all our efforts. --Rogan > Please correct me if I am wrong. > As a general note, Java has tons of useful libraries that will take infinite > time to re-implement in Haskell. To my mind it makes a lot of sense to have > a reliable mechanism to call Java from Haskell. > BTW, yet another way to do this: wrap Java library in RESTFUL web service ) > -- > All the best, > Dmitri O. Kondratiev > > "This is what keeps me going: discovery" > doko...@gmail.com > http://sites.google.com/site/dokondr/welcome > > > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The best way to call Java from Haskell?
Felipe Almeida Lessa cites and comments: > useful libraries that will take infinite time to re-implement in Haskell My brain just exploded. I can't handle infinite-length modules. Don't worry, my friend. Haskell is lazy, so there is no problem in "handling" those infinite modules. It will just take you an anfinite amount of time before you get any money from such a work. But this is a general problem elsewhere as well. Jerzy Karczmarczuk ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell vs. Dart
Heinrich Apfelmus wrote: > I didn't look very carefully, but from a Haskeller's point of view, I > can't see any significant difference between Dart and JavaScript, > except perhaps for the name. By comparison, CoffeeScript is a way more > innovative venture. If you want a useful client-side browser language, which is not just the same as JavaScript with a different syntax, look into Haxe [1]. That one is a statically, strongly typed language, which can be compiled down to JavaScript and other targets (PHP, ActionScript, SWF, C++, etc.). Some of the interesting features of it are algebraic data types, pattern matching, a module system and a rich standard library with lots of functionality which you always missed in JavaScript. It is also a great alternative, if you are forced to deploy PHP code and, like me, can't even find words strong enough to express the intensity of your absolute hate against that "programming language". [1] http://haxe.org/ Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell vs. Dart
I disagree. They added types and interfaces to the language, giving it at least some type-safety (preventing me from making stupid mistakes that will only show up at runtime). I didn't look much further, but they _are_ extending the language itself. Coffeescript on the other hand, is just a different syntax for javascript, not really adding any features. I love coffeescript, it's way more readable and concise, but it's just that, a different syntax. I do like your suggestion about a bytecode language for browsers. Although I must say that haskell didn't get very far (as in: usable) on the other 2 big bytecode platforms (java/.net) yet, but probably browsers are a much more wanted target. Mathijs On Tue, Oct 11, 2011 at 1:10 PM, Heinrich Apfelmus wrote: > Kevin Jardine wrote: >> >> After Google's disappointing Dart announcement yesterday, I decided to >> tweak >> them a bit and mention Haskell and functional programming languages as an >> alternative: >> >> https://plus.google.com/u/0/111705054912446689620/posts/UcyLBH7RLXs >> >> Comments on the post are welcome! > > I didn't look very carefully, but from a Haskeller's point of view, I can't > see any significant difference between Dart and JavaScript, except perhaps > for the name. By comparison, CoffeeScript is a way more innovative venture. > > A far more useful thing for Google to do would be a standardized bytecode > language for the browser; something that can be JITted efficiently while > guaranteeing safety/security. This way, the compilation chain > > Haskell -> bytecode -> browser > > would finally be viable. > > > Best regards, > Heinrich Apfelmus > > -- > http://apfelmus.nfshost.com > > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Arrow based re-definition of `StateT' included in `Control.Arrow.'?
Control.Arrow.Transformer.State.StateArrow? Отправлено с iPad 11.10.2011, в 17:02, Captain Freako написал(а): > Hi all, > > Is the Arrow-based re-definition of `StateT' included somewhere in the > `Control.Arrow.' stack, or do you put the code into your program explicitly? > > Thanks, > -db > > ___ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Is there a DFA library?
On Fri, 7 Oct 2011 15:29:50 -0400, Alex Rozenshteyn wrote: > I'm looking for things like minimization, completion, etc. kinda like > http://www.cis.upenn.edu/~cis639/docs/xfst.html This library's main purpose seems to be educational, but perhaps it's useful to you anyway: http://www3.di.uminho.pt/~jas/Research/HaLeX/HaLeX.html http://hackage.haskell.org/package/HaLeX Cheers, Daniel pgpN2L7oYwudk.pgp Description: PGP signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The best way to call Java from Haskell?
On Tue, Oct 11, 2011 at 5:56 AM, dokondr wrote: > useful libraries that will take infinite time to re-implement in Haskell My brain just exploded. I can't handle infinite-length modules. In the e-mail thread The best way to call Java from Haskell? In the mailing list: haskell-cafe -- Felipe. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Arrow based re-definition of `StateT' included in `Control.Arrow.'?
Hi all, Is the Arrow-based re-definition of `StateT' included somewhere in the `Control.Arrow.' stack, or do you put the code into your program explicitly? Thanks, -db ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] ANN: ircbot 0.1.1
Jeremy Shaw wrote: > 1. The library is based around the old String based irc library. Would > be nice to upgrade to something that used ByteStrings+Text+Builder. > Practically speaking.. it's IRC. The maximum line length is 510 > characters, and the bot typically needs to handle, at most, a few > messages per second. So, space and time issues would only be a > practical concern if your bot is joining hundreds of channels. But, > that is no excused not to use Text :) Perhaps the fastirc library? Hello there, I'm the author of the fastirc library. Even though it does address the problem of the old String-based 'irc' library, I wouldn't say that I'm very happy with the way it works. The library is a product of my early attempts to write fast, secure networking code in Haskell back in spring 2010. The protocol parser is based on attoparsec and is fast, but it doesn't work the way I would like it to work. It has a somewhat fragile way to ensure that lines don't get too long. Another shortcoming is the very weak session code, so if you want to use fastirc, you should only use the parser. I have started a new library based on attoparsec and the enumerator library, which is faster and handles line splitting properly with an enumeratee (that one is already on Hackage in the 'netlines' package). Also it will have good support for sessions using an FRP approach with the netwire library. However, be prepared to wait one or two weeks, until I have time to reach a point, where I can make an official release. Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] Haskell vs. Dart
Kevin Jardine wrote: After Google's disappointing Dart announcement yesterday, I decided to tweak them a bit and mention Haskell and functional programming languages as an alternative: https://plus.google.com/u/0/111705054912446689620/posts/UcyLBH7RLXs Comments on the post are welcome! I didn't look very carefully, but from a Haskeller's point of view, I can't see any significant difference between Dart and JavaScript, except perhaps for the name. By comparison, CoffeeScript is a way more innovative venture. A far more useful thing for Google to do would be a standardized bytecode language for the browser; something that can be JITted efficiently while guaranteeing safety/security. This way, the compilation chain Haskell -> bytecode -> browser would finally be viable. Best regards, Heinrich Apfelmus -- http://apfelmus.nfshost.com ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] PEPM'12 Deadline Extension
Apologies for multiple postings of this announcement. PEPM'12 - DEADLINE EXTENSION Due to a number of requests for extensions, the deadline for submission to PEPM'12 has been extended until 23:59 GMT on Sunday 16 October. We would like to remind you about three aspects of PEPM. Journal Special Issue There will be a journal special issue for PEPM'12. PEPM'09 has already appeared in Higher-order and Symbolic Computation (HOSC, online-first edition this year), and the special issue based on PEPM'10 papers has just been delivered to the HOSC editorial team. Short papers We're looking for short papers (up to 4pp) and tool papers as well as full research papers. All categories of papers will appear in the formal ACM proceedings. Tool papers The main purpose of a tool paper is to display other researchers in the PEPM community a completed, robust and well-documented tool; more guidance on the format and expected contact is given on the PEPM 2012 web site. In contrast with regular PEPM submissions, PEPM tool demo papers may include work that has been published elsewhere. In the ideal case, the technical foundations of the tool will have been published previously, and the submitted PEPM tool paper will report on follow-on work that has produced a robust tool that has been applied to interesting examples. The PEPM program committee will consider accepting tool demo papers that describe tools that have been presented at other conferences/ workshops if these conferences/ workshops belong to a different community (the authors should acknowledge the previous demos and justify the benefits of presenting the tool again for the PEPM audience). Call For Papers ACM SIGPLAN 2012 Workshop on Partial Evaluation and Program Manipulation January 23-24, 2012. Philadelphia, Pennsylvania, USA (co-located with POPL'12) http://www.program-transformation.org/PEPM12 Paper submission deadline: Sunday, October 16, 2011, 23:59, GMT The PEPM Symposium/Workshop series aims to bring together researchers and practitioners working in the broad area of program transformation, which spans from refactoring, partial evaluation, supercompilation, fusion and other metaprogramming to model-driven development, program analyses including termination, inductive programming, program generation and applications of machine learning and probabilistic search. PEPM focuses on techniques, supporting theory, tools, and applications of the analysis and manipulation of programs. Each technique or tool of program manipulation should have a clear, although perhaps informal, statement of desired properties, along with an argument how these properties could be achieved. Topics of interest for PEPM'12 include, but are not limited to: - Program and model manipulation techniques such as: supercompilation, partial evaluation, fusion, on-the-fly program adaptation, active libraries, program inversion, slicing, symbolic execution, refactoring, decompilation, and obfuscation. - Program analysis techniques that are used to drive program/model manipulation such as: abstract interpretation, termination checking, binding-time analysis, constraint solving, type systems, automated testing and test case generation. - Techniques that treat programs/models as data objects including metaprogramming, generative programming, embedded domain-specific languages, program synthesis by sketching and inductive programming, staged computation, and model-driven program generation and transformation. - Application of the above techniques including case studies of program manipulation in real-world (industrial, open-source) projects and software development processes, descriptions of robust tools capable of effectively handling realistic applications, benchmarking. Examples of application domains include legacy program understanding and transformation, DSL implementations, visual languages and end-user programming, scientific computing, middleware frameworks and infrastructure needed for distributed and web-based applications, resource-limited computation, and security. To maintain the dynamic and interactive nature of PEPM, we will continue the category of `short papers' for tool demonstrations and for presentations of exciting if not fully polished research, and of interesting academic, industrial and open-source applications that are new or unfamiliar. Student attendants with accepted papers can apply for a SIGPLAN PAC grant to help cover travel expenses and other support. All accepted papers, short papers included, will appear in formal proceedings published by ACM Press and will be included in the ACM Digital Library. Selected papers may later on be invited for a journal special issue dedicated to PEPM'12. Submission Categories and Guidelines Authors are strongly encouraged to consult the advice for authoring research papers and tool papers before submitting. The PC Chairs welcome any inquiries about the authoring advice.
Re: [Haskell-cafe] The best way to call Java from Haskell?
On Tue, Oct 11, 2011 at 12:42 PM, Yitzchak Gale wrote: > Dmitri wrote: > > I need to call Stanford NLP Parser from Haskell > > (unfortunately Haskell does not have a similar one)... > > Just out of curiosity, why do you not consider GF > at all similar? To an outsider like me, there does > appear to be quite a bit of similarity. > > http://www.grammaticalframework.org/ > > Thanks, > Yitz > As I understand GF is well suited for parsing well defined formal languages. Not sure that GF can be used as NLP parser for blog messages that I need. Please correct me if I am wrong. As a general note, Java has tons of useful libraries that will take infinite time to re-implement in Haskell. To my mind it makes a lot of sense to have a reliable mechanism to call Java from Haskell. BTW, yet another way to do this: wrap Java library in RESTFUL web service ) -- All the best, Dmitri O. Kondratiev "This is what keeps me going: discovery" doko...@gmail.com http://sites.google.com/site/dokondr/welcome ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The best way to call Java from Haskell?
Dmitri wrote: > I need to call Stanford NLP Parser from Haskell > (unfortunately Haskell does not have a similar one)... Just out of curiosity, why do you not consider GF at all similar? To an outsider like me, there does appear to be quite a bit of similarity. http://www.grammaticalframework.org/ Thanks, Yitz ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
[Haskell-cafe] Haskell vs. Dart
After Google's disappointing Dart announcement yesterday, I decided to tweak them a bit and mention Haskell and functional programming languages as an alternative: https://plus.google.com/u/0/111705054912446689620/posts/UcyLBH7RLXs Comments on the post are welcome! ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Re: [Haskell-cafe] The best way to call Java from Haskell?
On Tue, Oct 11, 2011 at 8:53 AM, Karel Gardas wrote: > On 10/11/11 08:23 AM, Michael Snoyman wrote: >> >> So for my use case, I don't care at all about interacting with Java >> code, I simply want to be able to turn my existing Haskell code into a >> JAR file. This seems like a much simpler undertaking, but I'm still >> not aware of any way to get this to happen right now either. > > LambdaVM do exactly what you like, but is experimental and unfortunately > out-dated. It's based on pre ghc 6.8: > > $ ./compiler/stage1/ghc-inplace --version > The Glorious Glasgow Haskell Compilation System, version 6.7.20081028 > > anyway, for hello world like examples it's working well, although > benchmarking shows that it's slower on the same code then frege for example > (testing just naive fib to compare recursion speed) > > I've contacted author several times and asked for updating or help with > updating it to latest GHC HEAD but received no reply so far and > unfortunately my Haskell knowledge is kind of enough to write just this > hello world... > > Karel > Yes, I really wish LambdaVM were alive and kicking. I've never actually hacked on GHC itself, but this might be the impetus to get me started. I might have some time to look at this in more depth a few months from now. Michael ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe