egison-pattern-src-0.1.0.0: Manipulating Egison patterns: abstract syntax, parser, and pretty-printer

Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Language.Egison.Pretty.Pattern

Contents

Description

A pretty printer for Egison patterns.

Synopsis

Documentation

prettyExpr :: (MonadError (Error n) m, Ord n) => PrintMode n v e -> Expr n v e -> m Text Source #

Pretty print Expr.

Re-exports

newtype Error n Source #

A pretty printer error.

Constructors

UnknownInfixOperator n 
Instances
Eq n => Eq (Error n) Source # 
Instance details

Defined in Language.Egison.Pretty.Pattern.Error

Methods

(==) :: Error n -> Error n -> Bool #

(/=) :: Error n -> Error n -> Bool #

Show n => Show (Error n) Source # 
Instance details

Defined in Language.Egison.Pretty.Pattern.Error

Methods

showsPrec :: Int -> Error n -> ShowS #

show :: Error n -> String #

showList :: [Error n] -> ShowS #

data Associativity Source #

Associativity of infix operators.

Instances
Eq Associativity Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Associativity

Data Associativity Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Associativity

Methods

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

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

toConstr :: Associativity -> Constr #

dataTypeOf :: Associativity -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Associativity Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Associativity

Generic Associativity Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Associativity

Associated Types

type Rep Associativity :: Type -> Type #

type Rep Associativity Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Associativity

type Rep Associativity = D1 (MetaData "Associativity" "Language.Egison.Syntax.Pattern.Fixity.Associativity" "egison-pattern-src-0.1.0.0-inplace" False) (C1 (MetaCons "AssocLeft" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "AssocRight" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "AssocNone" PrefixI False) (U1 :: Type -> Type)))

newtype Precedence Source #

A precedence of infix operators.

Constructors

Precedence Int 
Instances
Eq Precedence Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Precedence

Data Precedence Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Precedence

Methods

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

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

toConstr :: Precedence -> Constr #

dataTypeOf :: Precedence -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Precedence Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Precedence

Show Precedence Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Precedence

Generic Precedence Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Precedence

Associated Types

type Rep Precedence :: Type -> Type #

type Rep Precedence Source # 
Instance details

Defined in Language.Egison.Syntax.Pattern.Fixity.Precedence

type Rep Precedence = D1 (MetaData "Precedence" "Language.Egison.Syntax.Pattern.Fixity.Precedence" "egison-pattern-src-0.1.0.0-inplace" True) (C1 (MetaCons "Precedence" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

data Fixity n Source #

Fixity of infix operators.

Constructors

Fixity 

data PrintMode n v e Source #

Printer configuration.

data PageMode Source #

Rendering style configuration.

Constructors

PageMode 

data PrintFixity n Source #

Fixity of infix operators.

Constructors

PrintFixity 

Fields

type ExtPrinter a = a -> Text Source #

ExtPrinter a is a type for externally provided printer of a.