----------------------------------------------------------------------------- -- | -- Module : Lentil.Helpers -- Copyright : © 2015 Francesco Ariis -- License : GPLv3 (see the LICENSE file) -- -- Ancillaries for other modules ----------------------------------------------------------------------------- module Lentil.Helpers where import Lentil.Types import qualified System.IO as I import qualified Text.Parsec as P import qualified Text.Parsec.String as PS import Control.Applicative hiding ( (<|>), optional, many ) import Prelude -- 7.8 hack -- output errors (to stderr) perr :: String -> IO () perr cs = I.hPutStrLn I.stderr cs -- output errors (to stderr), but without newline *and* calling /r -- (erase what's before) first perrEph :: String -> IO () perrEph cs = I.hPutStr I.stderr ("\r" ++ cs) ------------- -- PARSING -- ------------- -- like many1 for manyTill manyTill1 :: PS.Parser a -> PS.Parser b -> PS.Parser [a] manyTill1 p ed = (:) <$> p <*> P.manyTill p ed -- parse an extension alias "aa->bc" -> Just ("aa", "bc") aliasp :: String -> Maybe Alias aliasp s = either (const Nothing) Just (P.parse p "" s) where p = manyTill1 P.anyChar (P.string aliasSign) >>= \a -> P.many P.anyChar >>= \b -> return ('.':a, '.':b)