-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Changing Haskell's Read Implementation Such That by Mainpulating Abstract Syntax Trees it Reads Expressions Efficiently -- -- Alternative approach of read that composes grammars instead of -- parsers. It reads data in linear time, while the function read -- has an exponential behavior in some cases of data types with infix -- operators. @package ChristmasTree @version 0.1 -- | Representation of Data Type Grammars. module Text.GRead.Grammar -- | Class of data types with typed grammar representation. It has to be -- instantiated in order to use the function Text.GRead.gread. -- -- Instances can be derived automatically using the functions defined in -- the module Text.GRead.Derive. -- -- For example, given the declarations -- --
--   infixl 5 :<:
--   infixr 6 :>:, :*:
--   
--   data T1  =  T1 :<: T1
--            |  T1 :>: T1
--            |  C1
--   
--   data T2 a  =  a :*: T2 a
--              |  C2
--   
-- -- the instances of Gram can be -- --
--   _0 = Zero
--   _1 = Suc _0
--   
--   instance Gram T1 where
--    grammar = DGrammar   _0 envT1
--   
--   envT1 :: Env DGram ((),T1) ((),T1) 
--   envT1 =  consD (nonts _0) Empty 
--        where
--         nonts _T1 = DLNontDefs
--          [  (  DRef (_T1, 5) 
--             ,  DPS  [  dNont (_T1, 5) .#. dTerm ":<:" .#.
--                        dNont (_T1, 6) .#. dEnd infixL ]
--             )
--          ,  (  DRef (_T1, 6) 
--             ,  DPS  [  dNont (_T1, 7) .#. dTerm ":>:" .#.
--                        dNont (_T1, 6) .#. dEnd infixR ] 
--             ) 
--          ,  (  DRef (_T1,10) 
--             ,  DPS  [  dTerm "C1"   .#. dEnd (const C1)
--                     ,  dTerm "(" .#. dNont (_T1,0) .#. 
--                        dTerm ")" .#. dEnd parenT ] 
--             )
--          ]
--         infixL e1 _ e2   = e2 :<: e1
--         infixR e1 _ e2   = e2 :>: e1 
--   
--   instance Gram a => Gram (T2 a) where
--    grammar = DGrammar   _0  envT2 
--   
--   envT2 :: (Gram a) => Env DGram  (((),a),T2 a)
--                                   (((),a),T2 a)
--   envT2 =  consD (nonts  _0 _1) $ 
--            consG grammar Empty
--        where
--         nonts _T2 _A = DLNontDefs
--          [  (  DRef (_T2, 6)
--             ,  DPS  [  dNont (_A,   7)  .#. dTerm ":*:" .#. 
--                        dNont (_T2,  7)  .#. dEnd infixT ] 
--             )
--          ,  (  DRef (_T2,10) 
--             ,  DPS  [  dTerm "C2"   .#. dEnd (const C2)
--                     ,  dTerm "("    .#. dNont (_T2,0) .#. 
--                        dTerm ")"    .#. dEnd parenT ] 
--             )
--          ]
--         infixP   e1 _ e2  = e2 :+: e1
--         infixT   e1 _ e2  = e2 :*: e1 
--   
-- -- In case of mutually recursive datatypes, their definitions have to be -- tupled together into a single environment. class Gram a grammar :: (Gram a) => DGrammar a -- | Data type describing grammatical structures of data types, including -- information about precedences. The type DGrammar a describes -- the grammar of the data type a. data DGrammar a -- | A grammar consists of an environment (Env) with the defined -- non-terminals and a reference (Ref) to the main -- non-terminal in the environment. DGrammar :: Ref a env -> Env DGram env env -> DGrammar a data DGram a env DGD :: DLNontDefs a env -> DGram a env DGG :: DGrammar a -> DGram a env newtype DRef a env DRef :: (Ref a env, Int) -> DRef a env newtype DLNontDefs a env DLNontDefs :: [(DRef a env, DProductions a env)] -> DLNontDefs a env newtype DProductions a env DPS :: [DProd a env] -> DProductions a env unDPS :: DProductions a env -> [DProd a env] data DProd a env DSeq :: DSymbol b env -> DProd (b -> a) env -> DProd a env DEnd :: a -> DProd a env data DSymbol a env DNont :: DRef a env -> DSymbol a env DTerm :: Token -> DSymbol Token env (.#.) :: DSymbol b env -> DProd (b -> a) env -> DProd a env consG :: DGrammar a -> Env DGram use def' -> Env DGram use (def', a) consD :: DLNontDefs a env -> Env DGram env def' -> Env DGram env (def', a) dNont :: (Ref a env, Int) -> DSymbol a env dTerm :: [Char] -> DSymbol Token env dEnd :: a -> DProd a env parenT :: t -> t1 -> t2 -> t1 data Grammar a Grammar :: Ref a env -> Env Productions env env -> Grammar a newtype Productions a env PS :: [Prod a env] -> Productions a env unPS :: Productions a env -> [Prod a env] data Prod a env Seq :: Symbol b env -> Prod (b -> a) env -> Prod a env End :: a -> Prod a env data Symbol a env Nont :: Ref a env -> Symbol a env Term :: Token -> Symbol Token env data Token Keyw :: String -> Token Open :: Token Close :: Token ext :: Env Productions env def' -> [Prod a env] -> Env Productions env (def', a) (.*.) :: Symbol b env -> Prod (b -> a) env -> Prod a env matchSym :: Symbol a env -> Symbol b env -> Maybe (Equal a b) append :: (a -> b -> c) -> Prod a env -> Symbol b env -> Prod c env instance Ord Token instance Eq Token -- | Automatically derive Text.GRead.Gram instances for data types. -- -- Note! This is not a complete implementation and will not work -- for all datatypes. -- -- Unsupported are -- -- -- -- Use with care. module Text.GRead.Derive -- | Derive a Text.GRead.Gram instance. This is a Template Haskell -- function. Usage example: -- --
--   data T1 = C1 | C2 | C3
--   
--   $(deriveGrammar ''T1)
--   
deriveGrammar :: Name -> Q [Dec] -- | Simpler version of deriveGrammar that doesn't do binding group -- calculations. Use this for large types without cyclic references to -- other types. -- -- For example, if you want to derive the HDYRM.Gram for T3 and T4 below, -- you will need the normal deriveGrammar. -- --
--   data T3 = T3 T4 | C3
--   data T4 = T4 T3 | C4
--   
deriveSimpleGrammar :: Name -> Q [Dec] -- | Alternative approach of read that composes grammars instead of -- parsers. Grammars describing the data types are composed dynamically, -- removing possible left-recursion and combining common prefixes of -- alternatives. -- -- The function gread defined here is able to handle the -- associativities defined for infix operators. -- -- The function gread reads data in linear time, while the -- function read has an exponential behavior in some cases of data -- types with infix operators. -- -- Non uniform data types are not supported, because they generate -- infinite grammars. -- -- The library is documented in the paper: Haskell, do you read me?: -- constructing and composing efficient top-down parsers at runtime -- -- Bibtex entry: -- http://www.cs.uu.nl/wiki/bin/viewfile/Center/TTTAS?rev=1;filename=GRead.bib -- -- For more documentation see the TTTAS webpage: -- http://www.cs.uu.nl/wiki/bin/view/Center/TTTAS . module Text.GRead -- | The gread reads input from a string, which must be completely -- consumed by the input process. Returns Ok value on a -- successful parse. Otherwise returns Rep value msgs, where the -- value results of parsing a repaired input. The list -- msgs contains the "corrections" done to the input. -- -- For example, a read-like implementation can be: -- --
--   read :: (Gram a) => String -> a
--   read input = case gread input of
--                    Ok  a       -> a
--                    Rep _ (m:_) -> error $ show m
--   
gread :: (Gram a) => String -> GReadResult a -- | Type of error repair messages. type GReadMsg = Message Token (Maybe Token) -- | Type of gread results. data GReadResult a Ok :: a -> GReadResult a Rep :: a -> [GReadMsg] -> GReadResult a instance (Show a) => Show (GReadResult a) instance Symbol Token instance Show Token module Text.GShow class GShow a gshow :: (GShow a) => a -> String gshowsPrec :: (GShow a) => Int -> a -> ShowS deriveShow :: Name -> Q [Dec]