| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | GHC2021 | 
Ormolu.Fixity.Internal
Synopsis
- data OpName
 - pattern OpName :: Text -> OpName
 - unOpName :: OpName -> Text
 - occOpName :: OccName -> OpName
 - data FixityDirection
 - data FixityInfo = FixityInfo {}
 - colonFixityInfo :: FixityInfo
 - defaultFixityInfo :: FixityInfo
 - data FixityApproximation = FixityApproximation {}
 - defaultFixityApproximation :: FixityApproximation
 - newtype HackageInfo = HackageInfo (Map PackageName (Map ModuleName (Map OpName FixityInfo)))
 - newtype FixityOverrides = FixityOverrides {}
 - defaultFixityOverrides :: FixityOverrides
 - newtype ModuleReexports = ModuleReexports {}
 - defaultModuleReexports :: ModuleReexports
 - newtype PackageFixityMap = PackageFixityMap (Map OpName (NonEmpty (PackageName, ModuleName, FixityInfo)))
 - newtype ModuleFixityMap = ModuleFixityMap (Map OpName FixityProvenance)
 - data FixityProvenance
 - data FixityQualification
 - inferFixity :: Bool -> RdrName -> ModuleFixityMap -> FixityApproximation
 
Documentation
An operator name.
data FixityDirection Source #
Fixity direction.
Instances
data FixityInfo Source #
Fixity information about an infix operator. This type provides precise
 information as opposed to FixityApproximation.
Constructors
| FixityInfo | |
Fields 
  | |
Instances
colonFixityInfo :: FixityInfo Source #
Fixity info of the built-in colon data constructor.
defaultFixityInfo :: FixityInfo Source #
Fixity that is implicitly assumed if no fixity declaration is present.
data FixityApproximation Source #
Approximation of fixity information that takes the uncertainty that can arise from conflicting definitions into account.
Constructors
| FixityApproximation | |
Fields 
  | |
Instances
defaultFixityApproximation :: FixityApproximation Source #
The lowest level of information we can have about an operator.
newtype HackageInfo Source #
The map of operators declared by each package grouped by module name.
Constructors
| HackageInfo (Map PackageName (Map ModuleName (Map OpName FixityInfo))) | 
Instances
| Generic HackageInfo Source # | |
Defined in Ormolu.Fixity.Internal Associated Types type Rep HackageInfo :: Type -> Type #  | |
| Binary HackageInfo Source # | |
Defined in Ormolu.Fixity.Internal  | |
| NFData HackageInfo Source # | |
Defined in Ormolu.Fixity.Internal Methods rnf :: HackageInfo -> () #  | |
| type Rep HackageInfo Source # | |
Defined in Ormolu.Fixity.Internal type Rep HackageInfo = D1 ('MetaData "HackageInfo" "Ormolu.Fixity.Internal" "fourmolu-0.15.0.0-7W1ACELXGTqDZS1JB01T2w" 'True) (C1 ('MetaCons "HackageInfo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map PackageName (Map ModuleName (Map OpName FixityInfo))))))  | |
newtype FixityOverrides Source #
Map from the operator name to its FixityInfo.
Constructors
| FixityOverrides | |
Fields  | |
Instances
| Show FixityOverrides Source # | |
Defined in Ormolu.Fixity.Internal Methods showsPrec :: Int -> FixityOverrides -> ShowS # show :: FixityOverrides -> String # showList :: [FixityOverrides] -> ShowS #  | |
| Eq FixityOverrides Source # | |
Defined in Ormolu.Fixity.Internal Methods (==) :: FixityOverrides -> FixityOverrides -> Bool # (/=) :: FixityOverrides -> FixityOverrides -> Bool #  | |
defaultFixityOverrides :: FixityOverrides Source #
Fixity overrides to use by default.
newtype ModuleReexports Source #
Module re-exports
Constructors
| ModuleReexports | |
Fields  | |
Instances
| Show ModuleReexports Source # | |
Defined in Ormolu.Fixity.Internal Methods showsPrec :: Int -> ModuleReexports -> ShowS # show :: ModuleReexports -> String # showList :: [ModuleReexports] -> ShowS #  | |
| Eq ModuleReexports Source # | |
Defined in Ormolu.Fixity.Internal Methods (==) :: ModuleReexports -> ModuleReexports -> Bool # (/=) :: ModuleReexports -> ModuleReexports -> Bool #  | |
defaultModuleReexports :: ModuleReexports Source #
Module re-exports to apply by default.
newtype PackageFixityMap Source #
Fixity information that is specific to a package being formatted. It requires module-specific imports in order to be usable.
Constructors
| PackageFixityMap (Map OpName (NonEmpty (PackageName, ModuleName, FixityInfo))) | 
Instances
| Show PackageFixityMap Source # | |
Defined in Ormolu.Fixity.Internal Methods showsPrec :: Int -> PackageFixityMap -> ShowS # show :: PackageFixityMap -> String # showList :: [PackageFixityMap] -> ShowS #  | |
| Eq PackageFixityMap Source # | |
Defined in Ormolu.Fixity.Internal Methods (==) :: PackageFixityMap -> PackageFixityMap -> Bool # (/=) :: PackageFixityMap -> PackageFixityMap -> Bool #  | |
newtype ModuleFixityMap Source #
Fixity map that takes into account imports in a particular module.
Constructors
| ModuleFixityMap (Map OpName FixityProvenance) | 
Instances
| Show ModuleFixityMap Source # | |
Defined in Ormolu.Fixity.Internal Methods showsPrec :: Int -> ModuleFixityMap -> ShowS # show :: ModuleFixityMap -> String # showList :: [ModuleFixityMap] -> ShowS #  | |
| Eq ModuleFixityMap Source # | |
Defined in Ormolu.Fixity.Internal Methods (==) :: ModuleFixityMap -> ModuleFixityMap -> Bool # (/=) :: ModuleFixityMap -> ModuleFixityMap -> Bool #  | |
data FixityProvenance Source #
Provenance of fixity info.
Constructors
| Given FixityInfo | 
  | 
| FromModuleImports (NonEmpty (FixityQualification, FixityInfo)) | 
  | 
Instances
| Show FixityProvenance Source # | |
Defined in Ormolu.Fixity.Internal Methods showsPrec :: Int -> FixityProvenance -> ShowS # show :: FixityProvenance -> String # showList :: [FixityProvenance] -> ShowS #  | |
| Eq FixityProvenance Source # | |
Defined in Ormolu.Fixity.Internal Methods (==) :: FixityProvenance -> FixityProvenance -> Bool # (/=) :: FixityProvenance -> FixityProvenance -> Bool #  | |
data FixityQualification Source #
Fixity qualification that determines how FixityInfo matches a
 particular use of an operator, given whether it is qualified or
 unqualified and the module name used.
Constructors
| UnqualifiedAndQualified ModuleName | |
| OnlyQualified ModuleName | 
Instances
| Show FixityQualification Source # | |
Defined in Ormolu.Fixity.Internal Methods showsPrec :: Int -> FixityQualification -> ShowS # show :: FixityQualification -> String # showList :: [FixityQualification] -> ShowS #  | |
| Eq FixityQualification Source # | |
Defined in Ormolu.Fixity.Internal Methods (==) :: FixityQualification -> FixityQualification -> Bool # (/=) :: FixityQualification -> FixityQualification -> Bool #  | |
Arguments
| :: Bool | Whether to print debug info regarding fixity inference  | 
| -> RdrName | Operator name  | 
| -> ModuleFixityMap | Module fixity map  | 
| -> FixityApproximation | The resulting fixity approximation  | 
Get a FixityApproximation of an operator.