Andrey,
Thanks for your attempt, but it doesn't seem to work. The easy part is the headline, but the content makes trouble.
Let me write the code a bit more explicit, so you can copy and paste it:
------------------------------------------
{-# LANGUAGE FlexibleContexts #-}
module Main where
import Text.Parsec
data Top = Top String deriving (Show)
data Content = Content String deriving (Show)
data Section = Section Top Content deriving (Show)
headline :: Stream s m Char => ParsecT s u m Top
headline = manyTill anyChar (char ':' >> newline) >>= return . Top
content :: Stream s m Char => ParsecT s u m Content
content = manyTill anyChar (try headline) >>= return . Content
section :: Stream s m Char => ParsecT s u m Section
section = do {h <- headline; c <- content; return (Section h c)}
------------------------------------------
Assume the following example text is stored in "/tmp/test.txt":
---------------------------
top 1:
some text ... bla
top 2:
more text ... bla bla
---------------------------
Now I run the section parser in ghci against the above mentioned example text stored in "/tmp/test.txt":
*Main> parseFromFile section "/tmp/test.txt"
Right (Section (Top "top 1") (Content ""))
I don't understand the behaviour of the content parser here. Why does it return ""? Or perhaps more generally, I don't understand the manyTill combinator (though I read the docs).