Hi,
 
Just as we can define infix operators as syntactic sugar, could we not also have a similar mechanism for programmable fancy brackets?
 
There could be a keyword for the bracket declaration and a function definition, in this way ana- and catamorphisms, Template Haskell-like syntax, and set notation could become a regular feature of the language. I am more interested in the general idea than the syntax of this specific example:
 
\begin{code}
bracket (( _ )) :: a -> Ana a
bracket (| _ |) :: a -> Cata a
bracket [ _ | _ |] :: Char -> b -> Splice -- or whatever  
bracket {[ _ , .. ]} :: [a] -> SList a
 
((( _ ))) :: a -> Ana a
(( x )) = Ana x
 
((| _ |)) :: a -> Cata a
(| x |) = Cata x
 
([ _ | _ |]) :: Char -> b -> Splice
[ c | t |] = case c of
               b -> doC t
               d -> doD t -- or whatever
 
-- the idea of this bracket is to create a user-defined list-type structure
--    {[ "the" , "lambda" , "calculus" ]}
-- would have the value
--    (SCons "the" (SCons "lambda" (SCons "calculus" SEmpty)))
({[ _ , .. ]} :: [a] -> SList a
{[ [] ]}     = sempty
{[ x:xs ]} = scons x {[ xs ]}
 
\end{code}
 
Any thoughts?
 
Vivian
 
 
 
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to