ormolu-0.5.3.0: A formatter for Haskell source code
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ormolu.Fixity

Description

Definitions for fixity analysis.

Synopsis

Documentation

data OpName Source #

An operator name.

Instances

Instances details
IsString OpName Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Methods

fromString :: String -> OpName #

Show OpName Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Binary OpName Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Methods

put :: OpName -> Put #

get :: Get OpName #

putList :: [OpName] -> Put #

Eq OpName Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Methods

(==) :: OpName -> OpName -> Bool #

(/=) :: OpName -> OpName -> Bool #

Ord OpName Source # 
Instance details

Defined in Ormolu.Fixity.Internal

pattern OpName :: Text -> OpName Source #

unOpName :: OpName -> Text Source #

Convert an OpName to Text.

occOpName :: OccName -> OpName Source #

Convert an 'OccName to an OpName.

data FixityDirection Source #

Fixity direction.

Constructors

InfixL 
InfixR 
InfixN 

Instances

Instances details
Generic FixityDirection Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Associated Types

type Rep FixityDirection :: Type -> Type #

Show FixityDirection Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Binary FixityDirection Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Eq FixityDirection Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Ord FixityDirection Source # 
Instance details

Defined in Ormolu.Fixity.Internal

type Rep FixityDirection Source # 
Instance details

Defined in Ormolu.Fixity.Internal

type Rep FixityDirection = D1 ('MetaData "FixityDirection" "Ormolu.Fixity.Internal" "ormolu-0.5.3.0-AnPnPiffES06d3yqkU3KCH" 'False) (C1 ('MetaCons "InfixL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InfixR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InfixN" 'PrefixI 'False) (U1 :: Type -> Type)))

data FixityInfo Source #

Fixity information about an infix operator that takes the uncertainty that can arise from conflicting definitions into account.

Constructors

FixityInfo 

Fields

Instances

Instances details
Semigroup FixityInfo Source #

Gives the ability to merge two (maybe conflicting) definitions for an operator, keeping the higher level of compatible information from both.

Instance details

Defined in Ormolu.Fixity.Internal

Generic FixityInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Associated Types

type Rep FixityInfo :: Type -> Type #

Show FixityInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Binary FixityInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Eq FixityInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Ord FixityInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

type Rep FixityInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

type Rep FixityInfo = D1 ('MetaData "FixityInfo" "Ormolu.Fixity.Internal" "ormolu-0.5.3.0-AnPnPiffES06d3yqkU3KCH" 'False) (C1 ('MetaCons "FixityInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "fiDirection") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FixityDirection)) :*: (S1 ('MetaSel ('Just "fiMinPrecedence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "fiMaxPrecedence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))

type FixityMap = Map OpName FixityInfo Source #

Map from the operator name to its FixityInfo.

data LazyFixityMap Source #

A variant of FixityMap, represented as a lazy union of several FixityMaps.

Instances

Instances details
Show LazyFixityMap Source # 
Instance details

Defined in Ormolu.Fixity.Internal

lookupFixity :: OpName -> LazyFixityMap -> Maybe FixityInfo Source #

Lookup a FixityInfo of an operator. This might have drastically different performance depending on whether this is an "unusual" operator.

data HackageInfo Source #

The map of operators declared by each package and the popularity of each package, if available.

Constructors

HackageInfo 

Fields

Instances

Instances details
Generic HackageInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

Associated Types

type Rep HackageInfo :: Type -> Type #

Binary HackageInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

type Rep HackageInfo Source # 
Instance details

Defined in Ormolu.Fixity.Internal

type Rep HackageInfo = D1 ('MetaData "HackageInfo" "Ormolu.Fixity.Internal" "ormolu-0.5.3.0-AnPnPiffES06d3yqkU3KCH" 'False) (C1 ('MetaCons "HackageInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PackageName FixityMap)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PackageName Int))))

defaultStrategyThreshold :: Float Source #

The default value for the popularity ratio threshold, after which a very popular definition from packageToOps will completely rule out conflicting definitions instead of being merged with them.

defaultFixityInfo :: FixityInfo Source #

The lowest level of information we can have about an operator.

buildFixityMap Source #

Arguments

:: Float

Popularity ratio threshold, after which a very popular package will completely rule out conflicting definitions coming from other packages instead of being merged with them

-> Set PackageName

Explicitly known dependencies

-> LazyFixityMap

Resulting map

Build a fixity map using the given popularity threshold and a list of cabal dependencies. Dependencies from the list have higher priority than other packages.

buildFixityMap' Source #

Arguments

:: Map PackageName FixityMap

Map from package to fixity map for operators defined in this package

-> Map PackageName Int

Map from package to popularity

-> Set PackageName

Higher priority packages

-> Float

Popularity ratio threshold, after which a very popular package will completely rule out conflicting definitions coming from other packages instead of being merged with them

-> Set PackageName

Explicitly known dependencies

-> LazyFixityMap

Resulting map

Build a fixity map using the given popularity threshold and a list of cabal dependencies. Dependencies from the list have higher priority than other packages. This specific version of the function allows the user to specify the package databases used to build the final fixity map.

bootPackages :: Set PackageName Source #

List of packages shipped with GHC, for which the download count from Hackage does not reflect their high popularity. See https://github.com/tweag/ormolu/pull/830#issuecomment-986609572. "base" is not is this list, because it is already whitelisted by buildFixityMap'.