ormolu-0.7.4.0: A formatter for Haskell source code
Safe HaskellSafe-Inferred
LanguageGHC2021

Ormolu.Utils.Cabal

Synopsis

Documentation

data CabalSearchResult Source #

The result of searching for a .cabal file.

Since: 0.5.3.0

Constructors

CabalNotFound

Cabal file could not be found

CabalDidNotMention CabalInfo

Cabal file was found, but it did not mention the source file in question

CabalFound CabalInfo

Cabal file was found and it mentions the source file in question

data CabalInfo Source #

Cabal information of interest to Ormolu.

Constructors

CabalInfo 

Fields

Instances

Instances details
Show CabalInfo Source # 
Instance details

Defined in Ormolu.Utils.Cabal

Eq CabalInfo Source # 
Instance details

Defined in Ormolu.Utils.Cabal

data Extension #

This represents language extensions beyond a base Language definition (such as Haskell98) that are supported by some implementations, usually in some special mode.

Where applicable, references are given to an implementation's official documentation.

Constructors

EnableExtension KnownExtension

Enable a known extension

DisableExtension KnownExtension

Disable a known extension

UnknownExtension String

An unknown extension, identified by the name of its LANGUAGE pragma.

Instances

Instances details
Parsec Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

parsec :: CabalParsing m => m Extension #

Pretty Extension 
Instance details

Defined in Language.Haskell.Extension

Structured Extension 
Instance details

Defined in Language.Haskell.Extension

Data Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Extension -> c Extension #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Extension #

toConstr :: Extension -> Constr #

dataTypeOf :: Extension -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Extension) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Extension) #

gmapT :: (forall b. Data b => b -> b) -> Extension -> Extension #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Extension -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Extension -> r #

gmapQ :: (forall d. Data d => d -> u) -> Extension -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Extension -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Extension -> m Extension #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Extension -> m Extension #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Extension -> m Extension #

Generic Extension 
Instance details

Defined in Language.Haskell.Extension

Associated Types

type Rep Extension :: Type -> Type #

Read Extension 
Instance details

Defined in Language.Haskell.Extension

Show Extension 
Instance details

Defined in Language.Haskell.Extension

Binary Extension 
Instance details

Defined in Language.Haskell.Extension

NFData Extension 
Instance details

Defined in Language.Haskell.Extension

Methods

rnf :: Extension -> () #

Eq Extension 
Instance details

Defined in Language.Haskell.Extension

Ord Extension 
Instance details

Defined in Language.Haskell.Extension

type Rep Extension 
Instance details

Defined in Language.Haskell.Extension

getCabalInfoForSourceFile Source #

Arguments

:: MonadIO m 
=> FilePath

Haskell source file

-> m CabalSearchResult

Extracted cabal info, if any

Locate a .cabal file corresponding to the given Haskell source file and obtain CabalInfo from it.

findCabalFile Source #

Arguments

:: MonadIO m 
=> FilePath

Path to a Haskell source file in a project with a .cabal file

-> m (Maybe FilePath)

Absolute path to the .cabal file, if available

Find the path to an appropriate .cabal file for a Haskell source file, if available.

parseCabalInfo Source #

Arguments

:: MonadIO m 
=> FilePath

Location of the .cabal file

-> FilePath

Location of the source file we are formatting

-> m (Bool, CabalInfo)

Indication if the source file was mentioned in the Cabal file and the extracted CabalInfo

Parse CabalInfo from a .cabal file at the given FilePath.