extensions-0.0.0.1: Parse Haskell Language Extensions
Copyright(c) 2020 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Extensions.Module

Description

Parser for Haskell Modules to get all Haskell Language Extensions used.

Synopsis

Documentation

parseFile :: FilePath -> IO (Either ModuleParseError ParsedExtensions) Source #

By the given file path, reads the file and returns ParsedExtensions, if parsing succeeds.

parseSource :: ByteString -> Either ModuleParseError ParsedExtensions Source #

By the given file source content, returns ParsedExtensions, if parsing succeeds.

parseSourceWithPath :: FilePath -> ByteString -> Either ModuleParseError ParsedExtensions Source #

By the given file path and file source content, returns ParsedExtensions, if parsing succeeds.

This function takes a path to a Haskell source file. The path is only used for error message. Pass empty string or use parseSource, if you don't have a path to a Haskell module.

Internal Parsers

extensionsP :: Parser [ParsedExtension] Source #

The main parser of ParsedExtension.

It parses language pragmas or comments until end of file or the first line with the functionimportmodule name.

singleExtensionsP :: Parser [ParsedExtension] Source #

Single LANGUAGE pragma parser.

 {-# LANGUAGE XXX
  , YYY ,
  ZZZ
 #-}

extensionP :: Parser ParsedExtension Source #

Parses all known and unknown OnOffExtensions or SafeHaskellExtensions.

languagePragmaP :: Parser a -> Parser a Source #

Parser for standard language pragma keywords: {-# LANGUAGE XXX #-}

optionsGhcP :: Parser [a] Source #

Parser for GHC options pragma keywords: {-# OPTIONS_GHC YYY #-}

pragmaP :: Parser () -> Parser a -> Parser a Source #

Parser for GHC pragmas with a given pragma word.

commentP :: Parser [a] Source #

Haskell comment parser. Supports both single-line comments:

 -- I am a single comment
 

and multi-line comments:

 {- I
 AM
 MULTILINE
 -}
 

cppP :: Parser [a] Source #

CPP syntax parser.

 #if __GLASGOW_HASKELL__ < 810
 -- Could be more Language pragmas that should be parsed
 #endif