
FWIW, state monad works fine. And I imagine the QuasiQuote extension
could get get rid of the double quotes on strings (and recover the use
of the colon?).
module Sugar ((~>), build, Builder) where
import Data.Map (Map); import qualified Data.Map as Map
import Control.Monad.State
(~>) :: Ord k => k -> a -> Builder k a
k ~> a = do
m <- get
let m' = Map.insert k a m
put m'
return m'
type Builder k a = State (Map k a) (Map k a)
build :: Builder k a -> Map k a
build x = evalState x Map.empty
m = build $ "zero" ~> 0 >> "one" ~> 1 >> "two" ~> 2
n = build $ do
"zero" ~> 0
"one" ~> 1
"two" ~> 2
o = build $ do { "zero" ~> 0; "one" ~> 1; "two" ~> 2 }
On Sun, Dec 21, 2008 at 7:28 PM, Wolfgang Jeltsch
Am Sonntag, 14. Dezember 2008 15:35 schrieb Neil Mitchell:
I am fairly certain someone could write the necessary magic so:
do {'a' ~> 1; 'b' ~> 2}
becomes a map without any changes to the language at all. It seems like throwing syntax at a problem should be a last resort. I often do:
let (*) = (,) in ['a' * 1, 'b' * 2]
I find that quite elegant as an associative list, which you can then convert to a map, a hash table, use as an associative list etc.
I also think that those who are looking for Haskell will have their mind so blown by lazy evaluation that keeping their maps similar isn't so necessary :-)
Thanks
Neil
+1 _______________________________________________ Haskell-prime mailing list Haskell-prime@haskell.org http://www.haskell.org/mailman/listinfo/haskell-prime