Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Name
- data CaptureRep codecRep
- = MatchRep String
- | CaptureRep codecRep
- data ParamRep codecRep
- = FlagRep
- | OptionalRep codecRep
- | ListRep codecRep
- data QueryRep codecRep = QueryRep {
- queryRepKey :: String
- queryRepParam :: ParamRep codecRep
- data RouteRep codecRep = RouteRep {
- routeRepName :: String
- routeRepMethod :: String
- routeRepCaptures :: [CaptureRep codecRep]
- routeRepQueries :: [QueryRep codecRep]
- routeReqRequest :: [codecRep]
- routeReqResponse :: NonEmpty codecRep
- data RoutesRep codecRep = RoutesRep {
- routesRepName :: String
- routesRepRoutes :: [RouteRep codecRep]
- routeDataType :: RoutesRep Name -> Q Dec
- enumRoutesInstance :: RoutesRep Name -> Q Dec
- metaInstance :: RoutesRep Name -> Q Dec
- trasa :: RoutesRep Name -> Q [Dec]
- parseTrasa :: QuasiQuoter
Documentation
An abstract type representing names in the syntax tree.
Name
s can be constructed in several ways, which come with different
name-capture guarantees (see Language.Haskell.TH.Syntax for
an explanation of name capture):
- the built-in syntax
'f
and''T
can be used to construct names, The expression'f
gives aName
which refers to the valuef
currently in scope, and''T
gives aName
which refers to the typeT
currently in scope. These names can never be captured. lookupValueName
andlookupTypeName
are similar to'f
and''T
respectively, but theName
s are looked up at the point where the current splice is being run. These names can never be captured.newName
monadically generates a new name, which can never be captured.mkName
generates a capturable name.
Names constructed using newName
and mkName
may be used in bindings
(such as let x = ...
or x -> ...
), but names constructed using
lookupValueName
, lookupTypeName
, 'f
, ''T
may not.
Instances
Eq Name | |
Data Name | |
Defined in Language.Haskell.TH.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Ord Name | |
Show Name | |
Generic Name | |
Ppr Name | |
type Rep Name | |
Defined in Language.Haskell.TH.Syntax type Rep Name = D1 (MetaData "Name" "Language.Haskell.TH.Syntax" "template-haskell" False) (C1 (MetaCons "Name" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OccName) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NameFlavour))) |
data CaptureRep codecRep Source #
MatchRep String | |
CaptureRep codecRep |
Instances
data ParamRep codecRep Source #
FlagRep | |
OptionalRep codecRep | |
ListRep codecRep |
Instances
Functor ParamRep Source # | |
Foldable ParamRep Source # | |
Defined in Trasa.TH.Types fold :: Monoid m => ParamRep m -> m # foldMap :: Monoid m => (a -> m) -> ParamRep a -> m # foldr :: (a -> b -> b) -> b -> ParamRep a -> b # foldr' :: (a -> b -> b) -> b -> ParamRep a -> b # foldl :: (b -> a -> b) -> b -> ParamRep a -> b # foldl' :: (b -> a -> b) -> b -> ParamRep a -> b # foldr1 :: (a -> a -> a) -> ParamRep a -> a # foldl1 :: (a -> a -> a) -> ParamRep a -> a # elem :: Eq a => a -> ParamRep a -> Bool # maximum :: Ord a => ParamRep a -> a # minimum :: Ord a => ParamRep a -> a # | |
Traversable ParamRep Source # | |
Show codecRep => Show (ParamRep codecRep) Source # | |
data QueryRep codecRep Source #
QueryRep | |
|
Instances
Functor QueryRep Source # | |
Foldable QueryRep Source # | |
Defined in Trasa.TH.Types fold :: Monoid m => QueryRep m -> m # foldMap :: Monoid m => (a -> m) -> QueryRep a -> m # foldr :: (a -> b -> b) -> b -> QueryRep a -> b # foldr' :: (a -> b -> b) -> b -> QueryRep a -> b # foldl :: (b -> a -> b) -> b -> QueryRep a -> b # foldl' :: (b -> a -> b) -> b -> QueryRep a -> b # foldr1 :: (a -> a -> a) -> QueryRep a -> a # foldl1 :: (a -> a -> a) -> QueryRep a -> a # elem :: Eq a => a -> QueryRep a -> Bool # maximum :: Ord a => QueryRep a -> a # minimum :: Ord a => QueryRep a -> a # | |
Traversable QueryRep Source # | |
Show codecRep => Show (QueryRep codecRep) Source # | |
data RouteRep codecRep Source #
RouteRep | |
|
Instances
Functor RouteRep Source # | |
Foldable RouteRep Source # | |
Defined in Trasa.TH.Types fold :: Monoid m => RouteRep m -> m # foldMap :: Monoid m => (a -> m) -> RouteRep a -> m # foldr :: (a -> b -> b) -> b -> RouteRep a -> b # foldr' :: (a -> b -> b) -> b -> RouteRep a -> b # foldl :: (b -> a -> b) -> b -> RouteRep a -> b # foldl' :: (b -> a -> b) -> b -> RouteRep a -> b # foldr1 :: (a -> a -> a) -> RouteRep a -> a # foldl1 :: (a -> a -> a) -> RouteRep a -> a # elem :: Eq a => a -> RouteRep a -> Bool # maximum :: Ord a => RouteRep a -> a # minimum :: Ord a => RouteRep a -> a # | |
Traversable RouteRep Source # | |
Show codecRep => Show (RouteRep codecRep) Source # | |
data RoutesRep codecRep Source #
RoutesRep | |
|
Instances
Functor RoutesRep Source # | |
Foldable RoutesRep Source # | |
Defined in Trasa.TH.Types fold :: Monoid m => RoutesRep m -> m # foldMap :: Monoid m => (a -> m) -> RoutesRep a -> m # foldr :: (a -> b -> b) -> b -> RoutesRep a -> b # foldr' :: (a -> b -> b) -> b -> RoutesRep a -> b # foldl :: (b -> a -> b) -> b -> RoutesRep a -> b # foldl' :: (b -> a -> b) -> b -> RoutesRep a -> b # foldr1 :: (a -> a -> a) -> RoutesRep a -> a # foldl1 :: (a -> a -> a) -> RoutesRep a -> a # toList :: RoutesRep a -> [a] # length :: RoutesRep a -> Int # elem :: Eq a => a -> RoutesRep a -> Bool # maximum :: Ord a => RoutesRep a -> a # minimum :: Ord a => RoutesRep a -> a # | |
Traversable RoutesRep Source # | |
Show codecRep => Show (RoutesRep codecRep) Source # | |