proto-lens-protoc-0.4.0.1: Protocol buffer compiler for the proto-lens library.

Safe HaskellSafe
LanguageHaskell2010

Data.ProtoLens.Compiler.Combinators

Contents

Description

Some utility functions, classes and instances for nicer code generation.

Re-exports simpler versions of the types and constructors from haskell-src-exts.

We define orphan instances of IsString for various syntax datatypes, with some intelligence about Haskell names. For example, "foo" :: Exp is treated as a variable and Foo :: Exp is treated as a constructor.

Synopsis

Documentation

class App a where Source #

Application of a Haskell type or expression to an argument. For example, to represent f x y, you can write

"f" @@ "x" @@ "y"

Minimal complete definition

(@@)

Methods

(@@) :: a -> a -> a infixl 2 Source #

Instances
App Type Source # 
Instance details

Defined in Data.ProtoLens.Compiler.Combinators

Methods

(@@) :: Type -> Type -> Type Source #

App Exp Source # 
Instance details

Defined in Data.ProtoLens.Compiler.Combinators

Methods

(@@) :: Exp -> Exp -> Exp Source #

type Type = Type () Source #

type QName = QName () Source #

type Pat = Pat () Source #

type Name = Name () Source #

data CommentedDecl Source #

A declaration, along with an optional comment.

Constructors

CommentedDecl (Maybe String) Decl 

data Module Source #

A hand-rolled type for modules, which allows comments on top-level declarations.

type Match = Match () Source #

type Alt = Alt () Source #

type Exp = Exp () Source #

type Decl = Decl () Source #

type Asst = Asst () Source #

instDecl :: [Asst] -> InstHead -> [[Match]] -> Decl Source #

let' :: [Decl] -> Exp -> Exp Source #

case' :: Exp -> [Alt] -> Exp Source #

alt :: Pat -> Exp -> Alt Source #

tuple :: [Exp] -> Exp Source #

lambda :: [Pat] -> Exp -> Exp Source #

(@::@) :: Exp -> Type -> Exp infixl 2 Source #

list :: [Exp] -> Exp Source #

match :: Name -> [Pat] -> Exp -> Match Source #

A simple clause of a function binding.

guardedMatch :: Name -> [Pat] -> [(Exp, Exp)] -> Match Source #

pApp :: QName -> [Pat] -> Pat Source #

isIdentChar :: Char -> Bool Source #

Whether this character belongs to an Ident (e.g., "foo") or a symbol (e.g., "$").

data ImportDecl l #

An import declaration.

Constructors

ImportDecl 

Fields

Instances
Functor ImportDecl 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fmap :: (a -> b) -> ImportDecl a -> ImportDecl b #

(<$) :: a -> ImportDecl b -> ImportDecl a #

Foldable ImportDecl 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

fold :: Monoid m => ImportDecl m -> m #

foldMap :: Monoid m => (a -> m) -> ImportDecl a -> m #

foldr :: (a -> b -> b) -> b -> ImportDecl a -> b #

foldr' :: (a -> b -> b) -> b -> ImportDecl a -> b #

foldl :: (b -> a -> b) -> b -> ImportDecl a -> b #

foldl' :: (b -> a -> b) -> b -> ImportDecl a -> b #

foldr1 :: (a -> a -> a) -> ImportDecl a -> a #

foldl1 :: (a -> a -> a) -> ImportDecl a -> a #

toList :: ImportDecl a -> [a] #

null :: ImportDecl a -> Bool #

length :: ImportDecl a -> Int #

elem :: Eq a => a -> ImportDecl a -> Bool #

maximum :: Ord a => ImportDecl a -> a #

minimum :: Ord a => ImportDecl a -> a #

sum :: Num a => ImportDecl a -> a #

product :: Num a => ImportDecl a -> a #

Traversable ImportDecl 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

traverse :: Applicative f => (a -> f b) -> ImportDecl a -> f (ImportDecl b) #

sequenceA :: Applicative f => ImportDecl (f a) -> f (ImportDecl a) #

mapM :: Monad m => (a -> m b) -> ImportDecl a -> m (ImportDecl b) #

sequence :: Monad m => ImportDecl (m a) -> m (ImportDecl a) #

Annotated ImportDecl 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

ann :: ImportDecl l -> l #

amap :: (l -> l) -> ImportDecl l -> ImportDecl l #

Eq l => Eq (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

(==) :: ImportDecl l -> ImportDecl l -> Bool #

(/=) :: ImportDecl l -> ImportDecl l -> Bool #

Data l => Data (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Methods

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

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

toConstr :: ImportDecl l -> Constr #

dataTypeOf :: ImportDecl l -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord l => Ord (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Show l => Show (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Generic (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Associated Types

type Rep (ImportDecl l) :: * -> * #

Methods

from :: ImportDecl l -> Rep (ImportDecl l) x #

to :: Rep (ImportDecl l) x -> ImportDecl l #

Pretty (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: ImportDecl l -> Doc

prettyPrec :: Int -> ImportDecl l -> Doc

type Rep (ImportDecl l) 
Instance details

Defined in Language.Haskell.Exts.Syntax

Orphan instances

IsString Promoted Source # 
Instance details

IsString Type Source # 
Instance details

Methods

fromString :: String -> Type #

IsString TyVarBind Source # 
Instance details

IsString QName Source # 
Instance details

Methods

fromString :: String -> QName #

IsString Pat Source # 
Instance details

Methods

fromString :: String -> Pat #

IsString Name Source # 
Instance details

Methods

fromString :: String -> Name #

IsString ModuleName Source # 
Instance details

IsString InstHead Source # 
Instance details

IsString Exp Source # 
Instance details

Methods

fromString :: String -> Exp #