183 lines
4.4 KiB
Plaintext
183 lines
4.4 KiB
Plaintext
-- -*- haskell -*- File generated by the BNF Converter (bnfc 2.9.6.1).
|
|
|
|
-- Parser definition for use with Happy
|
|
{
|
|
{-# OPTIONS_GHC -Wno-incomplete-patterns -Wno-overlapping-patterns #-}
|
|
{-# LANGUAGE PatternSynonyms #-}
|
|
|
|
module Alisaie.Par
|
|
( happyError
|
|
, myLexer
|
|
, pProgram
|
|
, pDefinition
|
|
, pKind
|
|
, pKind1
|
|
, pType1
|
|
, pType
|
|
, pListDefinition
|
|
, pListIdent
|
|
, pExp4
|
|
, pExp2
|
|
, pExp1
|
|
, pExp
|
|
, pExp3
|
|
) where
|
|
|
|
import Prelude
|
|
|
|
import qualified Alisaie.Abs
|
|
import Alisaie.Lex
|
|
import qualified Data.Text
|
|
|
|
}
|
|
|
|
%name pProgram Program
|
|
%name pDefinition Definition
|
|
%name pKind Kind
|
|
%name pKind1 Kind1
|
|
%name pType1 Type1
|
|
%name pType Type
|
|
%name pListDefinition ListDefinition
|
|
%name pListIdent ListIdent
|
|
%name pExp4 Exp4
|
|
%name pExp2 Exp2
|
|
%name pExp1 Exp1
|
|
%name pExp Exp
|
|
%name pExp3 Exp3
|
|
-- no lexer declaration
|
|
%monad { Err } { (>>=) } { return }
|
|
%tokentype {Token}
|
|
%token
|
|
'(' { PT _ (TS _ 1) }
|
|
')' { PT _ (TS _ 2) }
|
|
'*' { PT _ (TS _ 3) }
|
|
'+' { PT _ (TS _ 4) }
|
|
'-' { PT _ (TS _ 5) }
|
|
'.' { PT _ (TS _ 6) }
|
|
':' { PT _ (TS _ 7) }
|
|
'<' { PT _ (TS _ 8) }
|
|
'=' { PT _ (TS _ 9) }
|
|
'Char' { PT _ (TS _ 10) }
|
|
'Double' { PT _ (TS _ 11) }
|
|
'Int' { PT _ (TS _ 12) }
|
|
'String' { PT _ (TS _ 13) }
|
|
'else' { PT _ (TS _ 14) }
|
|
'if' { PT _ (TS _ 15) }
|
|
'then' { PT _ (TS _ 16) }
|
|
'Λ' { PT _ (TS _ 17) }
|
|
'λ' { PT _ (TS _ 18) }
|
|
'→' { PT _ (TS _ 19) }
|
|
'∀' { PT _ (TS _ 20) }
|
|
L_Ident { PT _ (TV $$) }
|
|
L_charac { PT _ (TC $$) }
|
|
L_doubl { PT _ (TD $$) }
|
|
L_integ { PT _ (TI $$) }
|
|
L_quoted { PT _ (TL $$) }
|
|
L_UIdent { PT _ (T_UIdent $$) }
|
|
|
|
%%
|
|
|
|
Ident :: { Alisaie.Abs.Ident }
|
|
Ident : L_Ident { Alisaie.Abs.Ident $1 }
|
|
|
|
Char :: { Char }
|
|
Char : L_charac { (read (Data.Text.unpack $1)) :: Char }
|
|
|
|
Double :: { Double }
|
|
Double : L_doubl { (read (Data.Text.unpack $1)) :: Double }
|
|
|
|
Integer :: { Integer }
|
|
Integer : L_integ { (read (Data.Text.unpack $1)) :: Integer }
|
|
|
|
String :: { String }
|
|
String : L_quoted { (Data.Text.unpack $1) }
|
|
|
|
UIdent :: { Alisaie.Abs.UIdent }
|
|
UIdent : L_UIdent { Alisaie.Abs.UIdent $1 }
|
|
|
|
Program :: { Alisaie.Abs.Program }
|
|
Program : ListDefinition { Alisaie.Abs.Prog $1 }
|
|
|
|
Definition :: { Alisaie.Abs.Definition }
|
|
Definition
|
|
: Ident ':' Type Ident ListIdent '=' Exp { Alisaie.Abs.Def $1 $3 $4 $5 $7 }
|
|
|
|
Kind :: { Alisaie.Abs.Kind }
|
|
Kind : '*' { Alisaie.Abs.KStar }
|
|
|
|
Kind1 :: { Alisaie.Abs.Kind }
|
|
Kind1 : Kind '→' Kind { Alisaie.Abs.KArr $1 $3 } | Kind { $1 }
|
|
|
|
Type1 :: { Alisaie.Abs.Type }
|
|
Type1
|
|
: 'String' { Alisaie.Abs.TString }
|
|
| 'Int' { Alisaie.Abs.TInt }
|
|
| 'Double' { Alisaie.Abs.TDouble }
|
|
| 'Char' { Alisaie.Abs.TChar }
|
|
| UIdent { Alisaie.Abs.TCustom $1 }
|
|
| '(' Type ')' { $2 }
|
|
|
|
Type :: { Alisaie.Abs.Type }
|
|
Type
|
|
: Type1 '→' Type { Alisaie.Abs.TArr $1 $3 }
|
|
| '∀' Ident ':' Kind '.' Type { Alisaie.Abs.TForall $2 $4 $6 }
|
|
| 'λ' Ident ':' Kind '.' Type { Alisaie.Abs.TLambda $2 $4 $6 }
|
|
| Type1 { $1 }
|
|
|
|
ListDefinition :: { [Alisaie.Abs.Definition] }
|
|
ListDefinition
|
|
: {- empty -} { [] } | Definition ListDefinition { (:) $1 $2 }
|
|
|
|
ListIdent :: { [Alisaie.Abs.Ident] }
|
|
ListIdent : {- empty -} { [] } | Ident ListIdent { (:) $1 $2 }
|
|
|
|
Exp4 :: { Alisaie.Abs.Exp }
|
|
Exp4
|
|
: Ident { Alisaie.Abs.EVar $1 }
|
|
| Integer { Alisaie.Abs.EInt $1 }
|
|
| Double { Alisaie.Abs.EDouble $1 }
|
|
| Char { Alisaie.Abs.EChar $1 }
|
|
| String { Alisaie.Abs.EText $1 }
|
|
| '(' Exp ')' { $2 }
|
|
|
|
Exp2 :: { Alisaie.Abs.Exp }
|
|
Exp2
|
|
: Exp2 Exp3 { Alisaie.Abs.EApp $1 $2 }
|
|
| Exp2 Type { Alisaie.Abs.ETApp $1 $2 }
|
|
| Exp3 { $1 }
|
|
|
|
Exp1 :: { Alisaie.Abs.Exp }
|
|
Exp1
|
|
: Exp1 '+' Exp2 { Alisaie.Abs.EAdd $1 $3 }
|
|
| Exp1 '-' Exp2 { Alisaie.Abs.ESub $1 $3 }
|
|
| Exp1 '<' Exp2 { Alisaie.Abs.ELt $1 $3 }
|
|
| Exp2 { $1 }
|
|
|
|
Exp :: { Alisaie.Abs.Exp }
|
|
Exp
|
|
: 'if' Exp 'then' Exp 'else' Exp { Alisaie.Abs.EIf $2 $4 $6 }
|
|
| 'Λ' Ident ':' Kind '.' Exp { Alisaie.Abs.ETAbs $2 $4 $6 }
|
|
| 'λ' Ident ':' Type '.' Exp { Alisaie.Abs.EAbs $2 $4 $6 }
|
|
| Exp1 { $1 }
|
|
|
|
Exp3 :: { Alisaie.Abs.Exp }
|
|
Exp3 : Exp4 { $1 }
|
|
|
|
{
|
|
|
|
type Err = Either String
|
|
|
|
happyError :: [Token] -> Err a
|
|
happyError ts = Left $
|
|
"syntax error at " ++ tokenPos ts ++
|
|
case ts of
|
|
[] -> []
|
|
[Err _] -> " due to lexer error"
|
|
t:_ -> " before `" ++ (prToken t) ++ "'"
|
|
|
|
myLexer :: Data.Text.Text -> [Token]
|
|
myLexer = tokens
|
|
|
|
}
|
|
|