-- Haskell data types for the abstract syntax. -- Generated by the BNF converter. {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternSynonyms #-} -- | The abstract syntax of language BNFC. module BNFC.Abs where import Prelude (Char, Double, Integer, String) import qualified Prelude as C ( Eq, Ord, Show, Read , Functor, Foldable, Traversable , Int, Maybe(..) ) type Grammar = Grammar' BNFC'Position data Grammar' a = Grammar a [Def' a] deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Def = Def' BNFC'Position data Def' a = Rule a (Label' a) (Cat' a) (RHS' a) | Comment a String | Comments a String String | Internal a (Label' a) (Cat' a) (RHS' a) | Token a Identifier (Reg' a) | PosToken a Identifier (Reg' a) | Entryp a [Cat' a] | Separator a (MinimumSize' a) (Cat' a) String | Terminator a (MinimumSize' a) (Cat' a) String | Delimiters a (Cat' a) String String (Separation' a) (MinimumSize' a) | Coercions a Identifier Integer | Rules a Identifier [RHS' a] | Function a Identifier [Arg' a] (Exp' a) | Layout a [String] | LayoutStop a [String] | LayoutTop a deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Item = Item' BNFC'Position data Item' a = Terminal a String | NTerminal a (Cat' a) deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Cat = Cat' BNFC'Position data Cat' a = ListCat a (Cat' a) | IdCat a Identifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Label = Label' BNFC'Position data Label' a = Id a Identifier | Wild a | ListEmpty a | ListCons a | ListOne a deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Arg = Arg' BNFC'Position data Arg' a = Arg a Identifier deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Separation = Separation' BNFC'Position data Separation' a = SepNone a | SepTerm a String | SepSepar a String deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Exp = Exp' BNFC'Position data Exp' a = Cons a (Exp' a) (Exp' a) | App a Identifier [Exp' a] | Var a Identifier | LitInteger a Integer | LitChar a Char | LitString a String | LitDouble a Double | List a [Exp' a] deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type RHS = RHS' BNFC'Position data RHS' a = RHS a [Item' a] deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type MinimumSize = MinimumSize' BNFC'Position data MinimumSize' a = MNonEmpty a | MEmpty a deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) type Reg = Reg' BNFC'Position data Reg' a = RAlt a (Reg' a) (Reg' a) | RMinus a (Reg' a) (Reg' a) | RSeq a (Reg' a) (Reg' a) | RStar a (Reg' a) | RPlus a (Reg' a) | ROpt a (Reg' a) | REps a | RChar a Char | RAlts a String | RSeqs a String | RDigit a | RLetter a | RUpper a | RLower a | RAny a deriving (C.Eq, C.Ord, C.Show, C.Read, C.Functor, C.Foldable, C.Traversable) newtype Identifier = Identifier ((C.Int, C.Int), String) deriving (C.Eq, C.Ord, C.Show, C.Read) -- | Start position (line, column) of something. type BNFC'Position = C.Maybe (C.Int, C.Int) pattern BNFC'NoPosition :: BNFC'Position pattern BNFC'NoPosition = C.Nothing pattern BNFC'Position :: C.Int -> C.Int -> BNFC'Position pattern BNFC'Position line col = C.Just (line, col) -- | Get the start position of something. class HasPosition a where hasPosition :: a -> BNFC'Position instance HasPosition Grammar where hasPosition = \case Grammar p _ -> p instance HasPosition Def where hasPosition = \case Rule p _ _ _ -> p Comment p _ -> p Comments p _ _ -> p Internal p _ _ _ -> p Token p _ _ -> p PosToken p _ _ -> p Entryp p _ -> p Separator p _ _ _ -> p Terminator p _ _ _ -> p Delimiters p _ _ _ _ _ -> p Coercions p _ _ -> p Rules p _ _ -> p Function p _ _ _ -> p Layout p _ -> p LayoutStop p _ -> p LayoutTop p -> p instance HasPosition Item where hasPosition = \case Terminal p _ -> p NTerminal p _ -> p instance HasPosition Cat where hasPosition = \case ListCat p _ -> p IdCat p _ -> p instance HasPosition Label where hasPosition = \case Id p _ -> p Wild p -> p ListEmpty p -> p ListCons p -> p ListOne p -> p instance HasPosition Arg where hasPosition = \case Arg p _ -> p instance HasPosition Separation where hasPosition = \case SepNone p -> p SepTerm p _ -> p SepSepar p _ -> p instance HasPosition Exp where hasPosition = \case Cons p _ _ -> p App p _ _ -> p Var p _ -> p LitInteger p _ -> p LitChar p _ -> p LitString p _ -> p LitDouble p _ -> p List p _ -> p instance HasPosition RHS where hasPosition = \case RHS p _ -> p instance HasPosition MinimumSize where hasPosition = \case MNonEmpty p -> p MEmpty p -> p instance HasPosition Reg where hasPosition = \case RAlt p _ _ -> p RMinus p _ _ -> p RSeq p _ _ -> p RStar p _ -> p RPlus p _ -> p ROpt p _ -> p REps p -> p RChar p _ -> p RAlts p _ -> p RSeqs p _ -> p RDigit p -> p RLetter p -> p RUpper p -> p RLower p -> p RAny p -> p instance HasPosition Identifier where hasPosition (Identifier (p, _)) = C.Just p