{-# LANGUAGE StandaloneDeriving #-}
module GLL.Types.Grammar where
import Data.Text
type Nt = Text
data Prod t = Prod (Nt) (Symbols t)
type Prods t = [Prod t]
type Grammar t = (Nt, Prods t)
data Slot t = Slot (Nt) (([Symbol t])) (([Symbol t]))
data Symbol t = Nt Nt
| Term t
type Symbols t = [Symbol t]
data Token = Char Char
| Keyword String
| EOS
| Epsilon
| IntLit (Maybe Int)
| FloatLit (Maybe Double)
| BoolLit (Maybe Bool)
| StringLit (Maybe String)
| CharLit (Maybe Char)
| IDLit (Maybe String)
| AltIDLit (Maybe String)
| Token String (Maybe String)
type Tokens = [Token]
class (Ord a, Eq a, Show a) => Parseable a where
eos :: a
eps :: a
matches :: a -> a -> Bool
unlex :: a -> String
unlex = show
class SubsumesToken a where
upcast :: Token -> a
downcast :: a -> Maybe Token
instance SubsumesToken Token where
upcast = id
downcast = Just
deriving instance Ord Token
deriving instance Eq Token
instance Show Token where
show (Char c) = "keychar('" ++ [c] ++ "')"
show (Keyword s) = "keyword(\"" ++ s ++ "\")"
show (EOS) = "<end-of-string>"
show (Epsilon) = "<epsilon>"
show (IntLit (Just i)) = "int(" ++ show i ++ ")"
show (IntLit _) = "<int>"
show (FloatLit (Just i)) = "float(" ++ show i ++ ")"
show (FloatLit _) = "<float>"
show (BoolLit (Just b)) = "bool(" ++ show b ++ ")"
show (BoolLit _) = "<bool>"
show (StringLit (Just s)) = "string(\"" ++ s ++ "\")"
show (StringLit _) = "<string>"
show (CharLit (Just c)) = "char('" ++ [c] ++ "')"
show (CharLit Nothing) = "<char>"
show (AltIDLit (Just id)) = "altid(\"" ++ id ++ "\")"
show (AltIDLit Nothing) = "<altid>"
show (IDLit (Just id)) = "id(\"" ++ id ++ "\")"
show (IDLit Nothing) = "<id>"
show (Token nm (Just s)) = nm ++ "(\"" ++ s ++ "\")"
show (Token nm _) = "<" ++ nm ++ ">"
instance Parseable Token where
eos = EOS
eps = Epsilon
unlex = unlexToken
Token k _ `matches` Token k' _ = k' == k
Char c `matches` Char c' = c' == c
Keyword k `matches` Keyword k' = k' == k
EOS `matches` EOS = True
Epsilon `matches` Epsilon = True
StringLit _ `matches` StringLit _ = True
CharLit _ `matches` CharLit _ = True
IntLit _ `matches` IntLit _ = True
FloatLit _ `matches` FloatLit _ = True
BoolLit _ `matches` BoolLit _ = True
AltIDLit _ `matches` AltIDLit _ = True
IDLit _ `matches` IDLit _ = True
_ `matches` _ = False
unlexTokens :: [Token] -> String
unlexTokens = Prelude.concatMap unlexToken
unlexToken :: Token -> String
unlexToken t = case t of
Char c -> [c]
Keyword s -> s
IntLit (Just i) -> show i
BoolLit (Just b) -> show b
StringLit (Just s) -> s
CharLit (Just c) -> [c]
AltIDLit (Just s) -> s
IDLit (Just s) -> s
Token _ (Just s) -> s
_ -> ""
isNt (Nt _) = True
isNt _ = False
isTerm (Term _) = True
isTerm _ = False
instance (Show t) => Show (Slot t) where
show (Slot x alpha beta) = show x ++ " ::= " ++ showRhs alpha ++ "." ++ showRhs beta
where showRhs [] = ""
showRhs ((Term t):rhs) = show t ++ showRhs rhs
showRhs ((Nt x):rhs) = show x ++ showRhs rhs
instance (Show t) => Show (Symbol t) where
show (Nt s) = unpack s
show (Term t) = show t
deriving instance (Ord t) => Ord (Slot t)
deriving instance (Eq t) => Eq (Slot t)
deriving instance (Show t) => Show (Prod t)
deriving instance (Ord t) => Ord (Prod t)
deriving instance (Eq t) => Eq (Prod t)
deriving instance (Eq t) => Eq (Symbol t)
deriving instance (Ord t) => Ord (Symbol t)