-------------------------------------------------------------------------------

  {-  LANGUAGE CPP #-}

-------------------------------------------------------------------------------

-- |
-- Module      :  Control.DeepSeq.Bounded.Pattern
-- Copyright   :  Andrew G. Seniuk 2014-2015
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Andrew Seniuk <rasfar@gmail.com>
-- Stability   :  provisional
-- Portability :  portable
--

-------------------------------------------------------------------------------

#if ! NEW_IMPROVED_PATTERN_GRAMMAR
#warning You are using the old pattern grammar (NEW_IMPROVED_PATTERN_GRAMMAR flag is False). This will be deprecated in version 0.7.
#endif

  module Control.DeepSeq.Bounded.Pattern
  (

#if NEW_IMPROVED_PATTERN_GRAMMAR

     -- * Pattern datatype

       Pattern

     , PatNode(..)

     , PatNodeAttrs(..)

     -- * Pattern DSL

-- XXX You cannot use CPP here to tack on a note at the head of
-- this doc comment, probably because CPP (all of 'em) tend
-- to (not very smartly IMO) inject blank lines, which throws
-- Haddock off as document comments are ended by (among other
-- things) a blank line.
--
-- So if I want this touch, I need to duplicate the whole large
-- comment block, which I am willing to do as this is very
-- short-term (perhaps one month).

#if HASKELL98_FRAGMENT
{- XXX PLEASE DON'T EDIT BELOW (i.e. this) BRANCH BY ACCIDENT!!! -}
     -- | /NOTE: You are using the HASKELL98_FRAGMENT (defaults False; set True).  This means, for a short time, the DSL is unavailable, and you will need to resort to using the PatNode constructors directly.  (The Blah98_new_grammar test suite is also unavailable.)  The reason is that the new grammar parser is written in attoparsec, which is far from being Haskell 98 (depends directly or indirectly on many language extensions).  This situation should be remedied by 0.7 (release expected early March 2015), maybe perhaps sooner, when I write an H98 parser for the new grammar.  In any case, these comments have been allowed to stand as they contain other useful information and examples./
     --
{- XXX Copy from the below, once it's stabilised! -}
{- XXX PLEASE DON'T EDIT ABOVE (i.e. this) BRANCH BY ACCIDENT!!! -}
#else
     -- | __Grammar__
     --
     -- @
     -- /pat/          /->/  /[/ /modifiers/ /]/ /pat'/
     -- /pat'/         /->/     __.__  /|/  __!__  /|/  __*__ /[/ /decimalint/ /]/  /|/  __(__ /{/ /pat/ /}/ __)__
     -- /modifiers/    /->/  zero or one of each of the eight /modifier/, in any order
     -- /modifier/     /->/     __=__  /|/  __+__  /|/  __^__  /|/  __\/__  /|/  __%__
     --                  /|/  __:__ /typename/ /{/ __;__ /typename/ /}/ __:__
     --                  /|/  __@__ /decimalint/
     --                  /|/  __>__ /permutation/
     -- /typename/     /->/  string containing neither __:__ (unless /escaped/) nor __;__
     -- /escaped/      /->/  __\\\\:__ 
     -- /decimalint/   /->/  digit string not beginning with zero
     -- /permutation/  /->/  of an initial part of the lowercase alphabet, /e.g./ __cdba__
     -- @
     --
     -- Here is the grammar in a more <http://fremissant.net/deepseq-bounded/grammar.html#new-grammar vivid rendering>.
     -- (Haddock makes it tricky to distinguish between metasyntax and concrete syntax.)
     --
     -- Optional whitespace can go between any two tokens (basically,
     -- anyplace there is space shown in the grammar above).
     --
     -- Semicolons never need escaping, because they're already illegal
     -- as part of any Haskell type name.
     --
     -- The semantics are given formally in the 'PatNode' and 'PatNodeAttrs'
     -- documentation, as well as informally in the examples below and from
     -- the project <http://www.fremissant.net/deepseq-bounded homepage>.
     --
     -- __Examples__
     --
     -- @\"__(...)__\"@ will match any ternary constructor.
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(!!!)__\" expr@ will force evaluation of @expr@ to a depth of two,
     -- provided the head of @expr@ is a ternary constructor; otherwise it behaves
     -- as @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__.__\" expr@ (/i.e./ do nothing).
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(...)__\" expr@ will force it to only a depth of one. That is,
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(...)__\" expr =
     -- <http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp>
     -- \"__!__\" expr@ when the head of @expr@
     -- is a ternary constructor; otherwise it won't perform any evaluation.
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__*__\" expr = <http://hackage.haskell.org/package/deepseq/docs/Control-DeepSeq.html#t:NFData rnf> expr@.
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(***)__\" expr@ will <http://hackage.haskell.org/package/deepseq/docs/Control-DeepSeq.html#t:NFData rnf> (deep) any ternary constructor, but
     -- will not touch any constructor of other arity.
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(.(*.).)__\" expr@ will match any ternary constructor, then
     -- match the second subexpression constructor if it is binary, and
     -- if matching got this far, then the left sub-subexpression
     -- will be forced (<http://hackage.haskell.org/package/deepseq/docs/Control-DeepSeq.html#t:NFData rnf>), but not the right.
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(!:T:*.)__\" expr@ will unwrap (shallow 'seq') the first
     -- subexpression of @expr@, and the third subexpression won't be touched.
     -- As for the second subexpression, if its type is @T@ it will be
     -- completely evaluated (<http://hackage.haskell.org/package/deepseq/docs/Control-DeepSeq.html#t:NFData rnf>), but otherwise it won't be touched.
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(=**)__\" expr@ will spark the /parallel/ complete evaluation of
     -- the two components of any pair. (Whether the computations actually
     -- run in parallel depends on resource availability, and the discretion
     -- of the RTS, as usual).
     --
     -- @<http://hackage.haskell.org/package/deepseq-bounded-0.6.0.0/docs/Control-DeepSeq-Bounded-NFDataP.html#t:NFDataP rnfp> \"__(>ba(+*+*)=*)__\" expr@ matches a binary constructor, whose first parameter is also a binary constructor. This identifies three main AST branches -- serendipitously symbolised by asterisks -- making up the expression: which branches we'll call __A__, __B__ and __C__. So this example will perform <http://hackage.haskell.org/package/deepseq/docs/Control-DeepSeq.html#t:NFData rnf>, but in a controlled manner: __A__ and __B__ are forced in parallel with __C__, and furthermore, __B__ is forced before __A__. A traceline will be printed at the beginning of the forcing of __B__ and then another traceline will be printed at the beginning of the forcing of __A__. Note that \"__(=>ba(+*+*)*)__\" would be a legal equivalent.
     --
     -- I make no claims as to the usefulness of the examples, they are here just to explain the semantics of the DSL.
     --
     -- __Details__
     --
     -- The present pattern parser ignores any subpatterns of all
     -- pattern nodes except 'WR' and 'TR', optionally emitting a warning.
     -- /(XXX In 0.6.0.0, I'm not sure the warning is still possible.)/
     -- Hence, only 'WR' and 'TR' patterns are potentially recursive.
     --
     -- When specifying the list of subpatterns with 'WR' and 'TR',
     -- in order for the match to succeed, the number of subpatterns must
     -- be equal to the arity of the constructor the pattern node is
     -- matching against. (No other pattern node types accept subpatterns.)
     --
     -- Additionally, in the case of 'TR', matching (and consequent recursion) will only
     -- succeed if the term node has constructor name which is listed in the constraints.
     --
     -- It would be possible to have 'TR' nodes interpret the constraint
     -- as type name rather than constructor name, but this would require /sum patterns/
     -- (maybe for version 0.7).  The problem is, no single 'WR' node
     -- can match multiple constructors of differing arity.  This has the
     -- feel of an excellent application for SOP generics!...
     --
     -- (As contrasted with 'TR' nodes,) 'TI', 'TN' and 'TW' nodes interpret
     -- type constraint strings as type names (not constructor names).
     -- A moment's reflection will show you why it must be so.
     --
     -- Finally, if you're trying to name a constructor with __:__ in its name,
     -- you must escape the colon with a backslash thus __\\\\:__ because
     -- the unescaped colon is used as (opening and) closing character for
     -- lists of type and constructor names.
{--}
     -- Old interjection:
     -- I regret that Haddock cannot offer better markup for distinguishing
     -- the metasyntax.  The bold is not bold enough.  The alternation symbol,
     -- although \/|\/ in the document comment, does not show as slanted for me.
     -- Had no luck using color, also Unicode support seems pretty sketchy.
     -- Embedding an image is possible via data URL, but this has been known
     -- to crash Haddock except for very small images.
{--}
-- I'm still not sure if I try accepting a double-colon close here?
-- (Checking...)
     --              /|/   /(/ __.__  /|/  __*__ /[/ /decimalint/ /]/ /)/ __::__ /typename/ /{/ __;__ /typename/ /}/ __:__ /[/ __:__ /]/
#endif

#if 0
-- These are now in Compile (but may move them back once sort out some stuff)
     , compilePat
     , showPat
#endif

     , isWI , isWR , isWS , isWN , isWW , isTI , isTR , isTN , isTW

     , emptyPatNodeAttrs
--   , emptySparkPatNodeAttrs
     , getPatNodeAttrs
     , setPatNodeAttrs
     , setPatNodePingParentTID
     , showPerm
     , showPatRaw
     , showPatNodeRaw

     , setPatternPatNodeUniqueIDs

--   , patternShapeOK  -- useful for defining instances of NFDataP

     -- * Why depend on whole containers package, when we only want a rose tree

     , Rose(..)

     -- * Preferred to have this in Seqable, but had cyclical dependency issues

     , SeqNode(..)

#else

     -- * Pattern datatype

       Pattern
     , PatNode(..)

--   , patternShapeOK  -- useful for defining instances of NFDataP

     -- * Pattern DSL

     -- | __Grammar__
     --
     -- @
     -- /pat/ /->/ /[/ __=__ /]/ __.__ /[/ __{__ /{/ /pat/ /}/ __}__ /]/
     --     /|/  /(/ /[/ __=__ /]/ __*__ /[/ /decimalint/ /]/ /|/ __#__ /)/
     --     /|/  __.:__ /ctorname/ /{/ /space/ /ctorname/ /}/ __{__ /[/ /{/ /pat/ /}/ /]/ __}__
     --     /|/  /(/ __*__ /[/ /decimalint/ /]/ /|/ __#__ /)/ __:__ /typename/ /{/ /space/ /typename/ /}/ __{}__
     -- /typename/ -> /string/
     -- /ctorname/ -> /string/
     -- /decimalint/ -> /digit string not beginning with zero/
     -- /space/ -> /space character ASCII 0x32/
     -- @
     --
     -- Here is the grammar in a more <http://fremissant.net/deepseq-bounded/grammar.html vivid rendering>.
     -- (The Haddock markup makes it almost tricky to distinguish between metasyntax and concrete syntax.)
     --
     -- __Examples__
     --
     -- @\".{...}\"@ will match any ternary constructor.
     --
     -- @'rnfp' \".{...}\" expr@ will force evaluation of @expr@ to a depth of two,
     -- provided the head of @expr@ is a ternary constructor; otherwise it behaves
     -- as @'rnfp' \"#\" expr@ (/i.e./ do nothing).
     --
     -- @'rnfp' \".{###}\" expr@ will force it to only a depth of one. That is,
     -- @'rnfp' \".{###}\" expr = 'rnfp' \".\" expr@ when the head of @expr@
     -- is a ternary constructor; otherwise it won't perform any evaluation.
     --
     -- @'rnfp' \"*\" expr = 'rnf' expr@.
     --
     -- @'rnfp' \".{***}\" expr@ will 'rnf' (deep) any ternary constructor, but
     -- will not touch any constructor of other arity.
     --
     -- @'rnfp' \".{..{*.}.}\" expr@ will match any ternary constructor, then
     -- match the second subexpression constructor if it is binary, and
     -- if matching got this far, then the left sub-subexpression
     -- will be forced ('rnf'), but not the right.
     --
     -- @'rnfp' \".{.*:T{}#}\" expr@ will unwrap (shallow 'seq') the first
     -- subexpression of @expr@, and the third subexpression won't be touched.
     -- As for the second subexpression, if its type is @T@ it will be
     -- completely evaluated ('rnf'), but otherwise it won't be touched.
     --
     -- @'rnfp' \".{=**}\" expr@ will spark the /parallel/ complete evaluation of
     -- the two components of any pair. (Whether the computations actually
     -- run in parallel depends on resource availability, and the discretion
     -- of the RTS, as usual).
     --
     -- __Details__
     --
     -- The present pattern parser ignores any subpatterns of all
     -- pattern nodes except 'WR', 'TR' and 'PR', optionally emitting a warning.
     -- Hence, only 'WR', 'TR' and 'PR' patterns are potentially recursive.
     --
     -- When specifying a list of subpatterns with 'WR' or 'PR',
     -- in order for the match to succeed, the number of subpatterns must
     -- be equal to the arity of the named constructor.
     --
     -- Type constraints must always be followed by __{__ (opening brace) as delimiter.
     -- In the case of 'TR', if no recursion is desired, provide __{}__.
     -- In order for the match to succeed, the number of subpatterns must either
     -- be zero (__{}__), or be equal to the arity of the named constructor.
     --
{--}
     -- Old interjection:
     -- I regret that Haddock cannot offer better markup for distinguishing
     -- the metasyntax.  The bold is not bold enough.  The alternation symbol,
     -- although \/|\/ in the document comment, does not show as slanted for me.
     -- Had no luck using color, also Unicode support seems pretty sketchy.
     -- Embedding an image is possible via data URL, but this has been known
     -- to crash Haddock except for very small images.

#if 0
-- These are now in Compile (but may move them back once sort out some stuff)
     , compilePat
     , showPat
#endif

     -- * Why depend on whole containers package, when we only want a rose tree

     , Rose(..)

     -- * Preferred to have this in Seqable, but had cyclical dependency issues

     , SeqNode(..)

#endif

--- #if NEW_IMPROVED_PATTERN_GRAMMAR
---      module Control.DeepSeq.Bounded.Pattern_new_grammar  ,
--- #else
---      module Control.DeepSeq.Bounded.Pattern_old_grammar  ,
--- #endif

  )
  where

-------------------------------------------------------------------------------

#if NEW_IMPROVED_PATTERN_GRAMMAR
  import Control.DeepSeq.Bounded.Pattern_new_grammar
#else
  import Control.DeepSeq.Bounded.Pattern_old_grammar
#endif

-------------------------------------------------------------------------------