fourmolu-0.10.1.0: A formatter for Haskell source code
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ormolu.Utils.Cabal

Synopsis

Documentation

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

defaultCabalInfo :: CabalInfo Source #

Cabal info that is used by default when no .cabal file can be found.

data PackageName #

A package name.

Use mkPackageName and unPackageName to convert from/to a String.

This type is opaque since Cabal-2.0

Since: Cabal-syntax-2.0.0.2

Instances

Instances details
Parsec PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

parsec :: CabalParsing m => m PackageName #

Pretty PackageName 
Instance details

Defined in Distribution.Types.PackageName

Structured PackageName 
Instance details

Defined in Distribution.Types.PackageName

Data PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

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

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

toConstr :: PackageName -> Constr #

dataTypeOf :: PackageName -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString PackageName

mkPackageName

Since: Cabal-syntax-2.0.0.2

Instance details

Defined in Distribution.Types.PackageName

Generic PackageName 
Instance details

Defined in Distribution.Types.PackageName

Associated Types

type Rep PackageName :: Type -> Type #

Read PackageName 
Instance details

Defined in Distribution.Types.PackageName

Show PackageName 
Instance details

Defined in Distribution.Types.PackageName

Binary PackageName 
Instance details

Defined in Distribution.Types.PackageName

NFData PackageName 
Instance details

Defined in Distribution.Types.PackageName

Methods

rnf :: PackageName -> () #

Eq PackageName 
Instance details

Defined in Distribution.Types.PackageName

Ord PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName 
Instance details

Defined in Distribution.Types.PackageName

type Rep PackageName = D1 ('MetaData "PackageName" "Distribution.Types.PackageName" "Cabal-syntax-3.8.1.0-FNxuhpWohYgHG4qaNSQ3WD" 'True) (C1 ('MetaCons "PackageName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ShortText)))

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

type Rep Extension = D1 ('MetaData "Extension" "Language.Haskell.Extension" "Cabal-syntax-3.8.1.0-FNxuhpWohYgHG4qaNSQ3WD" 'False) (C1 ('MetaCons "EnableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: (C1 ('MetaCons "DisableExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KnownExtension)) :+: C1 ('MetaCons "UnknownExtension" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))

getCabalInfoForSourceFile Source #

Arguments

:: MonadIO m 
=> FilePath

Haskell source file

-> m CabalInfo

Extracted cabal info

Locate .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 CabalInfo

Extracted cabal info

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