----------------------------------------------------------------------------- -- | -- Module : Lentil.Parse.Syntaxes -- Copyright : © 2015 Francesco Ariis, Tomislav -- License : GPLv3 (see the LICENSE file) -- -- Languages descriptors ----------------------------------------------------------------------------- module Lentil.Parse.Syntaxes where import Lentil.Parse.Source import Text.Parsec import Control.Applicative hiding (many) import Prelude import qualified System.FilePath as SF -- TODO: add langparsers che sia estensibile e leggibile -- a compilazione [u:2] [feature:intermediate] langParser :: String -> Maybe (ParSource [CommentString]) langParser fp | ext `elem` [".hs", ".lhs"] = Just haskell | ext `elem` [".c", ".h"] = Just c | ext `elem` [".cpp", ".hpp"] = Just c -- C++ | ext `elem` [".java"] = Just c -- Java | ext `elem` [".js"] = Just javascript | ext `elem` [".pas", ".pp", ".inc"] = Just pascal | ext `elem` [".py"] = Just python | ext `elem` [".rb"] = Just ruby | ext `elem` [".pl", ".pm", ".t"] = Just perl | ext `elem` [".sh"] = Just perl -- shell | ext `elem` [".nix"] = Just nix | ext `elem` [".txt"] = Just text | otherwise = Nothing where ext = SF.takeExtension fp -- todo multiline signature? [lint] -- todo tag at the beginning too? [design] haskell, c, javascript, pascal, python, ruby :: ParSource [CommentString] perl, nix :: ParSource [CommentString] text :: ParSource [CommentString] haskell = source $ ParSyntax ["--"] [("{-", "-}")] ClangLike ['"'] ['\''] c = source $ ParSyntax ["//"] [("/*", "*/")] ClangLike ['"'] ['\''] javascript = source $ ParSyntax ["//"] [("/*", "*/")] ClangLike ['"', '\''] [] pascal = source $ ParSyntax ["//"] [("{", "}" ), ("(*", "*)")] SQLLike ['\''] [] python = source $ ParSyntax ["#"] [("\"\"\"", "\"\"\"")] ClangLike ['"', '\''] [] ruby = source $ ParSyntax ["#"] [("=begin", "=end")] ClangLike ['"', '\''] [] perl = source $ ParSyntax ["#"] [] ClangLike ['"', '\''] [] nix = source $ ParSyntax ["#"] [("/*", "*/")] ClangLike ['"'] ['\''] text = (:[]) . MultiLine 1 <$> many anyChar