-- This Happy file was machine-generated by the BNF converter { {-# OPTIONS_GHC -fno-warn-incomplete-patterns -fno-warn-overlapping-patterns #-} module Language.Par where import Language.Abs import Language.Lex import Language.ErrM } %name pSpecification Specification %name pName Name %name pVersion Version %name pModules Modules %name pEnumType EnumType %name pStructType StructType %name pResource Resource %name pMode Mode %name pField Field %name pFType FType %name pAnnotation Annotation %name pEnumVal EnumVal %name pListEnumType ListEnumType %name pListField ListField %name pListStructType ListStructType %name pListResource ListResource %name pListEnumVal ListEnumVal %name pListAnnotation ListAnnotation %name pListIdent ListIdent -- no lexer declaration %monad { Err } { thenM } { returnM } %tokentype { Token } %token '\"' { PT _ (TS _ 1) } '(' { PT _ (TS _ 2) } ')' { PT _ (TS _ 3) } ',' { PT _ (TS _ 4) } ':' { PT _ (TS _ 5) } '@' { PT _ (TS _ 6) } 'Double' { PT _ (TS _ 7) } 'Int' { PT _ (TS _ 8) } 'Long' { PT _ (TS _ 9) } 'String' { PT _ (TS _ 10) } '[' { PT _ (TS _ 11) } ']' { PT _ (TS _ 12) } 'enum' { PT _ (TS _ 13) } 'modules' { PT _ (TS _ 14) } 'read_only' { PT _ (TS _ 15) } 'require' { PT _ (TS _ 16) } 'resource' { PT _ (TS _ 17) } 'service_name' { PT _ (TS _ 18) } 'service_version' { PT _ (TS _ 19) } 'struct' { PT _ (TS _ 20) } '{' { PT _ (TS _ 21) } '}' { PT _ (TS _ 22) } L_ident { PT _ (TV $$) } L_VerIdent { PT _ (T_VerIdent $$) } L_RouteIdent { PT _ (T_RouteIdent $$) } %% Ident :: { Ident } : L_ident { Ident $1 } VerIdent :: { VerIdent} : L_VerIdent { VerIdent ($1)} RouteIdent :: { RouteIdent} : L_RouteIdent { RouteIdent ($1)} Specification :: { Specification } Specification : Name Version Modules ListEnumType ListStructType ListResource { Spec $1 $2 $3 (reverse $4) $5 $6 } Name :: { Name } Name : 'service_name' ':' Ident { Nm $3 } Version :: { Version } Version : 'service_version' ':' VerIdent { Ver $3 } Modules :: { Modules } Modules : {- empty -} { EmptyMods } | 'require' 'modules' '[' ListIdent ']' { Mods $4 } EnumType :: { EnumType } EnumType : 'enum' Ident '{' ListEnumVal '}' { DefEnum $2 $4 } StructType :: { StructType } StructType : 'struct' Ident '{' ListField '}' { DefStr $2 $4 } Resource :: { Resource } Resource : 'resource' Ident '(' '\"' RouteIdent '\"' ')' Mode { Res $2 $5 $8 } Mode :: { Mode } Mode : 'read_only' { ReadOnly } | {- empty -} { Write } Field :: { Field } Field : ListAnnotation Ident ':' FType { FDef (reverse $1) $2 $4 } FType :: { FType } FType : 'String' { FString } | 'Int' { FInt } | 'Long' { FLong } | 'Double' { FDouble } | Ident { FDefined $1 } | '[' FType ']' { FList $2 } Annotation :: { Annotation } Annotation : '@' Ident { Ann $2 } EnumVal :: { EnumVal } EnumVal : Ident { EnVal $1 } ListEnumType :: { [EnumType] } ListEnumType : {- empty -} { [] } | ListEnumType EnumType { flip (:) $1 $2 } ListField :: { [Field] } ListField : Field { (:[]) $1 } | Field ',' ListField { (:) $1 $3 } ListStructType :: { [StructType] } ListStructType : StructType { (:[]) $1 } | StructType ListStructType { (:) $1 $2 } ListResource :: { [Resource] } ListResource : Resource { (:[]) $1 } | Resource ListResource { (:) $1 $2 } ListEnumVal :: { [EnumVal] } ListEnumVal : EnumVal { (:[]) $1 } | EnumVal ',' ListEnumVal { (:) $1 $3 } ListAnnotation :: { [Annotation] } ListAnnotation : {- empty -} { [] } | ListAnnotation Annotation { flip (:) $1 $2 } ListIdent :: { [Ident] } ListIdent : Ident { (:[]) $1 } | Ident ListIdent { (:) $1 $2 } { returnM :: a -> Err a returnM = return thenM :: Err a -> (a -> Err b) -> Err b thenM = (>>=) happyError :: [Token] -> Err a happyError ts = Bad $ "syntax error at " ++ tokenPos ts ++ case ts of [] -> [] [Err _] -> " due to lexer error" _ -> " before " ++ unwords (map (id . prToken) (take 4 ts)) myLexer = tokens }