Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Fixity
Synopsis
- data Fixity = Fixity SourceText Int FixityDirection
- data FixityDirection
- data LexicalFixity
- maxPrecedence :: Int
- minPrecedence :: Int
- defaultFixity :: Fixity
- negateFixity :: Fixity
- funTyFixity :: Fixity
- compareFixity :: Fixity -> Fixity -> (Bool, Bool)
Documentation
Instances
Data Fixity Source # | |
Defined in GHC.Types.Fixity gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Fixity -> c Fixity Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Fixity Source # toConstr :: Fixity -> Constr Source # dataTypeOf :: Fixity -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Fixity) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Fixity) Source # gmapT :: (forall b. Data b => b -> b) -> Fixity -> Fixity Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Fixity -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Fixity -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Fixity -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Fixity -> m Fixity Source # | |
Binary Fixity Source # | |
Outputable Fixity Source # | |
Eq Fixity Source # | |
data FixityDirection Source #
Instances
data LexicalFixity Source #
Captures the fixity of declarations as they are parsed. This is not necessarily the same as the fixity declaration, as the normal fixity may be overridden using parens or backticks.
Instances
maxPrecedence :: Int Source #
minPrecedence :: Int Source #
funTyFixity :: Fixity Source #