module Boilerplate.Types where import Data.Map.Strict (Map) import Data.Text (Text) -- `BOILERPLATE ... BOILERPLATE END` data Marker = Marker Text Int (Maybe Int) -- ^^ config (start position) (end position) deriving (Eq, Show) data Config = Config Text [Text] [(Text, Custom)] -- ^^ type [rule] [custom key, value] | ConfigStart | ConfigEnd deriving (Eq, Show) -- TODO (Text, Custom) could have a namespace data Custom = Global Text -- ^^ available anywhere | Indexed [Text] -- ^^ applies to ordered product fields | Named (Map Text Text) -- ^^ applies to record fields and data constructors | NamedIndexed (Map Text [Text]) -- ^^ applies to ordered fields inside a sum type deriving (Eq, Show) type Tree = [Atom] newtype Rule = Rule Tree deriving (Eq, Show) -- TODO a lot of Text locations could be Tree: convert on demand data Atom = Raw Text | Type | TParams Tree Tree Tree Text Text -- ^^ empty prefix elem sep suffix | TParam | Product Tree -- ^^ elem | Sum Text Tree Text Text -- ^^ prefix elem sep suffix | Uncons Int -- ^^ id | Cons | Field Tree Tree Tree Text Text -- ^^ empty prefix elem sep suffix | TyCase Tree Tree Tree -- ^^ (type param) (higher kinded) (neither) | Param Int -- ^^ id | FieldName | FieldType | Custom Text (Maybe Tree) -- ^^ name fallback | Sugar Sugar deriving (Eq, Show) data Sugar = Instance Text | Data Tree deriving (Eq, Show) -- TODO {RecordCase {RECORD}{DATA}} e.g. to support different Show for data vs records -- TODO syntax sugar for a strict subset with semantics of Divisible, Decidable, -- Applicative, Alt