Re: Suggestion: Syntactic sugar for Maps!

bulat.ziganshin:
Hello circ,
Thursday, November 27, 2008, 9:59:08 PM, you wrote:
So why not {"hello": 1, "there": 2} ?
mymap "hello:1 there:2"
where mymap implementation is left to the reader :)
Hey, well, even easier: {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE FlexibleInstances #-} import Data.Map import Data.String import Text.JSON instance IsString (Map Int Bool) where fromString = fromList . read -- or, say, JSON syntax for assoc lists. {- fromString s = case resultToEither (decode s) of Right a -> a Left s -> error s -} test :: Map Int Bool test = "[(7, True), (1, False)]" main = print test -- Don

In all fairness, this basically forces you to say "trust me" to the compiler for something that should be verifiable statically. A typo results in a runtime error -- in a way, this is worse than Perl. Quasi-quotes are really the "right answer" but hardly simple in this case... -- _jsn

Don Stewart wrote:
bulat.ziganshin:
Hello circ,
Thursday, November 27, 2008, 9:59:08 PM, you wrote:
So why not {"hello": 1, "there": 2} ? mymap "hello:1 there:2"
where mymap implementation is left to the reader :)
I can't see the context of the beginning of this thread, but I've always found: fromList [("hello",1),("there",2)] to be a relatively simple syntax, and still checked at compile time. Anonymous sum + product types plus lists are a pretty good approximation for lots of concrete syntax, and they're type checks. (Anonymous sum, Either, is slightly more syntactically heavy than you'd like, though...) Jules

On Fri, Nov 28, 2008 at 12:04 AM, Jules Bean
I can't see the context of the beginning of this thread, but I've always found:
fromList [("hello",1),("there",2)]
to be a relatively simple syntax, and still checked at compile time.
I never liked that. Too much syntax overhead. But this clears it right up: foo = fromList [ "hello" >: 1, "there" >: 2 ] where (:>) = (,) And also I haven't been following the thread, so this may not be any kind of answer. Luke
participants (4)
-
Don Stewart
-
Jason Dusek
-
Jules Bean
-
Luke Palmer