{- # LANGUAGE FreeSections #-} -- with GHC's -F you cannot... -- Might as well test interaction with the pre-existing -- tuple section generalisation. {-# LANGUAGE TupleSections #-} module S24 where -- Tests of each of the Exp contexts. -- Here, all free section contexts are given explicitly with _[ ... ]_. -- S25.hs is an analogous file, but default contexts are attempted. -- -- This module won't compile, but you can examine the preprocessed code. -- InfixApp Exp QOp Exp -- infix application v= _[ __ + 2 ]_ -- App Exp Exp -- ordinary application v= _[ f __ ]_ v= _[ __ x ]_ -- NegApp Exp v= _[ - __ ]_ -- Lambda SrcLoc [Pat] Exp -- lambda expression v= _[ \ x -> __ x ]_ -- Let Binds Exp -- local declarations with let ... in ... v= _[ let x=2 in __ x ]_ -- If Exp Exp Exp -- conditional expression v= _[ if __ then __ else __ ]_ -- Case Exp [Alt] -- case expression v= _[ case __ of _ -> 2 ]_ -- Tuple [Exp] -- tuple expression v= _[ (__,2,__,4,5,__,7) ]_ -- TupleSection [Maybe Exp] -- tuple section expression, e.g. (,,3) v= _[ (,,__) ]_ v= _[ (,__,,__) ]_ -- List [Exp] -- list expression v= _[ [__,2,__,4,5,__,7] ]_ -- FSContext Exp -- free section context v= a _[ __ c __ ]_ e -- Paren Exp -- parenthesised expression v= _[ (__) ]_ v= _[ ( __ b __ ) ]_ -- LeftSection Exp QOp -- left section ( /exp/ /qop/ ) v= _[ (__ +) ]_ -- RightSection QOp Exp -- right section ( /qop/ /exp/ ) v= _[ (+ __) ]_ -- RecUpdate Exp [FieldUpdate] -- record update expression v= _[ __ { f3 = 2 } ]_ Ctor v= _[ Ctor { f3 = __ } ]_ 2 -- EnumFrom Exp -- unbounded arithmetic sequence v= _[ [__..] ]_ v= _[ [__..] ]_ $ 3 -- EnumFromTo Exp Exp -- bounded arithmetic sequence v= _[ [__..__] ]_ $ 3 5 -- EnumFromThen Exp Exp -- unbounded arithmetic sequence with stride v= _[ [__,__..] ]_ $ 3 5 -- EnumFromThenTo Exp Exp Exp -- bounded arithmetic sequence with stride v= _[ [__,__..__] ]_ $ 3 5 8 -- ListComp Exp [QualStmt] -- ordinary list comprehension v= _[ [f __ x|x<-[1..3]] $ 2 ]_ {- still not working v= _[ [f 2 x|x<- __ ] $ [1..3] ]_ v= _[ [f __ x|x<- __ ] $ 2 [1..3] ]_ -} -- ParComp Exp [[QualStmt]] -- parallel list comprehension --v= ?? -- ExpTypeSig SrcLoc Exp Type -- expression with explicit type signature --v= __ :: Int->Int $ 2 v= _[ __ :: Int->Int ]_ 2 -- Arrows -- Proc SrcLoc Pat Exp -- arrows proc: proc /pat/ -> /exp/ -- LeftArrApp Exp Exp -- arrow application (from left): /exp/ -< /exp/ -- RightArrApp Exp Exp -- arrow application (from right): /exp/ >- /exp/ -- LeftArrHighApp Exp Exp -- higher-order arrow application (from left): /exp/ -<< /exp/ -- RightArrHighApp Exp Exp -- higher-order arrow application (from right): /exp/ >>- /exp/ {- -- Haskell expressions. -- Those which contain Exp in their productions are tested here. -- This doesn't mean that there is an immediate Exp child in every -- case (some are wrapped in List or Maybe); and it doesn't mean -- that FreeSect won't perform rewriting in the branches of any -- of the non-*'d alternates either -- a Stmt, for instance, may -- contain Exp's. data Exp = Var QName -- ^ variable | FreeSectSlot -- ^ FreeSect placeholder: @__@ | IPVar IPName -- ^ implicit parameter variable | Con QName -- ^ data constructor | Lit Literal -- ^ literal constant * | InfixApp Exp QOp Exp -- ^ infix application * | App Exp Exp -- ^ ordinary application * | NegApp Exp -- ^ negation expression @-/exp/@ (unary minus) * | Lambda SrcLoc [Pat] Exp -- ^ lambda expression * | Let Binds Exp -- ^ local declarations with @let@ ... @in@ ... * | If Exp Exp Exp -- ^ @if@ /exp/ @then@ /exp/ @else@ /exp/ * | Case Exp [Alt] -- ^ @case@ /exp/ @of@ /alts/ | Do [Stmt] -- ^ @do@-expression: -- the last statement in the list -- should be an expression. | MDo [Stmt] -- ^ @mdo@-expression * | Tuple [Exp] -- ^ tuple expression * | TupleSection [Maybe Exp] -- ^ tuple section expression, e.g. @(,,3)@ * | List [Exp] -- ^ list expression * | FSContext Exp -- ^ FreeSect context * | Paren Exp -- ^ parenthesised expression * | LeftSection Exp QOp -- ^ left section @(@/exp/ /qop/@)@ * | RightSection QOp Exp -- ^ right section @(@/qop/ /exp/@)@ | RecConstr QName [FieldUpdate] -- ^ record construction expression * | RecUpdate Exp [FieldUpdate] -- ^ record update expression * | EnumFrom Exp -- ^ unbounded arithmetic sequence, -- incrementing by 1: @[from ..]@ * | EnumFromTo Exp Exp -- ^ bounded arithmetic sequence, -- incrementing by 1 @[from .. to]@ * | EnumFromThen Exp Exp -- ^ unbounded arithmetic sequence, -- with first two elements given @[from, then ..]@ * | EnumFromThenTo Exp Exp Exp -- ^ bounded arithmetic sequence, -- with first two elements given @[from, then .. to]@ * | ListComp Exp [QualStmt] -- ^ ordinary list comprehension * | ParComp Exp [[QualStmt]] -- ^ parallel list comprehension * | ExpTypeSig SrcLoc Exp Type -- ^ expression with explicit type signature | VarQuote QName -- ^ @'x@ for template haskell reifying of expressions | TypQuote QName -- ^ @''T@ for template haskell reifying of types | BracketExp Bracket -- ^ template haskell bracket expression | SpliceExp Splice -- ^ template haskell splice expression | QuasiQuote String String -- ^ quasi-quotaion: @[$/name/| /string/ |]@ -- Hsx * | XTag SrcLoc XName [XAttr] (Maybe Exp) [Exp] -- ^ xml element, with attributes and children * | XETag SrcLoc XName [XAttr] (Maybe Exp) -- ^ empty xml element, with attributes | XPcdata String -- ^ PCDATA child element * | XExpTag Exp -- ^ escaped haskell expression inside xml * | XChildTag SrcLoc [Exp] -- ^ children of an xml element -- Pragmas * | CorePragma String Exp -- ^ CORE pragma * | SCCPragma String Exp -- ^ SCC pragma * | GenPragma String (Int, Int) (Int, Int) Exp -- ^ GENERATED pragma -- Arrows * | Proc SrcLoc Pat Exp -- ^ arrows proc: @proc@ /pat/ @->@ /exp/ * | LeftArrApp Exp Exp -- ^ arrow application (from left): /exp/ @-<@ /exp/ * | RightArrApp Exp Exp -- ^ arrow application (from right): /exp/ @>-@ /exp/ * | LeftArrHighApp Exp Exp -- ^ higher-order arrow application (from left): /exp/ @-<<@ /exp/ * | RightArrHighApp Exp Exp -- ^ higher-order arrow application (from right): /exp/ @>>-@ /exp/ -}