Using ghc-3.01, if one does
mkdependHS t.lhs
where t.lhs is
----------------------------
\begin{code}
module T where
\end{code}
\begin{code}
mediaTypeP :: Parser MediaType
mediaTypeP =
(litP "*/*" >> return AnyType) +++
(tokenP >>= \t -> msp >> charP '/' >>
maybeP tokenP >>= \st ->
many parameterP >>= \ps ->
return (AType t st ps))
\end{code}
---------------------------------------
it complains, saying
:8: unterminated comment
This doesn't happen if one changes the two asterisks in the program for,
say '%' (!), or if one writes the "*/*" string as '*':'/':'*':[] ...
-- m
-----------------------------------------------------------------------
Mariano Suarez Alvarez The introduction of
Departamento de Matematica numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250 A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
-----------------------------------------------------------------------