doc-src/IsarRef/generic.tex
author krauss
Mon, 03 Sep 2007 16:50:53 +0200
changeset 24524 6892fdc7e9f8
parent 24429 76372c3847a2
child 24859 9b9b1599fb89
permissions -rw-r--r--
Documented function package in IsarRef-manual.
     1 \chapter{Generic tools and packages}\label{ch:gen-tools}
     2 
     3 \section{Specification commands}
     4 
     5 \subsection{Derived specifications}
     6 
     7 \indexisarcmd{axiomatization}
     8 \indexisarcmd{definition}\indexisaratt{defn}
     9 \indexisarcmd{abbreviation}\indexisarcmd{print-abbrevs}
    10 \indexisarcmd{notation}
    11 \begin{matharray}{rcll}
    12   \isarcmd{axiomatization} & : & \isarkeep{local{\dsh}theory} & (axiomatic!)\\
    13   \isarcmd{definition} & : & \isarkeep{local{\dsh}theory} \\
    14   defn & : & \isaratt \\
    15   \isarcmd{abbreviation} & : & \isarkeep{local{\dsh}theory} \\
    16   \isarcmd{print_abbrevs}^* & : & \isarkeep{theory~|~proof} \\
    17   \isarcmd{notation} & : & \isarkeep{local{\dsh}theory} \\
    18 \end{matharray}
    19 
    20 These specification mechanisms provide a slightly more abstract view
    21 than the underlying primitives of $\CONSTS$, $\DEFS$ (see
    22 \S\ref{sec:consts}), and $\isarkeyword{axioms}$ (see
    23 \S\ref{sec:axms-thms}).  In particular, type-inference is commonly
    24 available, and result names need not be given.
    25 
    26 \begin{rail}
    27   'axiomatization' target? fixes? ('where' specs)?
    28   ;
    29   'definition' target? (decl 'where')? thmdecl? prop
    30   ;
    31   'abbreviation' target? mode? (decl 'where')? prop
    32   ;
    33   'notation' target? mode? (nameref mixfix + 'and')
    34   ;
    35 
    36   fixes: ((name ('::' type)? mixfix? | vars) + 'and')
    37   ;
    38   specs: (thmdecl? props + 'and')
    39   ;
    40   decl: name ('::' type)? mixfix?
    41   ;
    42 \end{rail}
    43 
    44 \begin{descr}
    45   
    46 \item $\isarkeyword{axiomatization} ~ c@1 \dots c@n ~
    47   \isarkeyword{where} ~ A@1 \dots A@m$ introduces several constants
    48   simultaneously and states axiomatic properties for these.  The
    49   constants are marked as being specified once and for all, which
    50   prevents additional specifications being issued later on.
    51   
    52   Note that axiomatic specifications are only appropriate when
    53   declaring a new logical system.  Normal applications should only use
    54   definitional mechanisms!
    55 
    56 \item $\isarkeyword{definition}~c~\isarkeyword{where}~eq$ produces an
    57   internal definition $c \equiv t$ according to the specification
    58   given as $eq$, which is then turned into a proven fact.  The given
    59   proposition may deviate from internal meta-level equality according
    60   to the rewrite rules declared as $defn$ by the object-logic.  This
    61   typically covers object-level equality $x = t$ and equivalence $A
    62   \leftrightarrow B$.  Users normally need not change the $defn$
    63   setup.
    64   
    65   Definitions may be presented with explicit arguments on the LHS, as
    66   well as additional conditions, e.g.\ $f\;x\;y = t$ instead of $f
    67   \equiv \lambda x\;y. t$ and $y \not= 0 \Imp g\;x\;y = u$ instead of
    68   an unguarded $g \equiv \lambda x\;y. u$.
    69   
    70 \item $\isarkeyword{abbreviation}~c~\isarkeyword{where}~eq$ introduces
    71   a syntactic constant which is associated with a certain term
    72   according to the meta-level equality $eq$.
    73   
    74   Abbreviations participate in the usual type-inference process, but
    75   are expanded before the logic ever sees them.  Pretty printing of
    76   terms involves higher-order rewriting with rules stemming from
    77   reverted abbreviations.  This needs some care to avoid overlapping
    78   or looping syntactic replacements!
    79   
    80   The optional $mode$ specification restricts output to a particular
    81   print mode; using ``$input$'' here achieves the effect of one-way
    82   abbreviations.  The mode may also include an ``$output$'' qualifier
    83   that affects the concrete syntax declared for abbreviations, cf.\ 
    84   $\isarkeyword{syntax}$ in \S\ref{sec:syn-trans}.
    85   
    86 \item $\isarkeyword{print_abbrevs}$ prints all constant abbreviations
    87   of the current context.
    88   
    89 \item $\isarkeyword{notation}~c~mx$ associates mixfix syntax with an
    90   existing constant or fixed variable.  This is a robust interface to
    91   the underlying $\isarkeyword{syntax}$ primitive
    92   (\S\ref{sec:syn-trans}).  Type declaration and internal syntactic
    93   representation of the given entity is retrieved from the context.
    94   
    95 \end{descr}
    96 
    97 All of these specifications support local theory targets (cf.\ 
    98 \S\ref{sec:target}).
    99 
   100 
   101 \subsection{Generic declarations}
   102 
   103 Arbitrary operations on the background context may be wrapped-up as
   104 generic declaration elements.  Since the underlying concept of local
   105 theories may be subject to later re-interpretation, there is an
   106 additional dependency on a morphism that tells the difference of the
   107 original declaration context wrt.\ the application context encountered
   108 later on.  A fact declaration is an important special case: it
   109 consists of a theorem which is applied to the context by means of an
   110 attribute.
   111 
   112 \indexisarcmd{declaration}\indexisarcmd{declare}
   113 \begin{matharray}{rcl}
   114   \isarcmd{declaration} & : & \isarkeep{local{\dsh}theory} \\
   115   \isarcmd{declare} & : & \isarkeep{local{\dsh}theory} \\
   116 \end{matharray}
   117 
   118 \begin{rail}
   119   'declaration' target? text
   120   ;
   121   'declare' target? (thmrefs + 'and')
   122   ;
   123 \end{rail}
   124 
   125 \begin{descr}
   126 
   127 \item [$\isarkeyword{declaration}~d$] adds the declaration function
   128   $d$ of ML type \verb,declaration, to the current local theory under
   129   construction.  In later application contexts, the function is
   130   transformed according to the morphisms being involved in the
   131   interpretation hierarchy.
   132 
   133 \item [$\isarkeyword{declare}~thms$] declares theorems to the current
   134   local theory context.  No theorem binding is involved here, unlike
   135   $\isarkeyword{theorems}$ or $\isarkeyword{lemmas}$ (cf.\
   136   \S\ref{sec:axms-thms}), so $\isarkeyword{declare}$ only has the
   137   effect of applying attributes as included in the theorem
   138   specification.
   139 
   140 \end{descr}
   141 
   142 
   143 \subsection{Local theory targets}\label{sec:target}
   144 
   145 A local theory target is a context managed separately within the
   146 enclosing theory.  Contexts may introduce parameters (fixed variables)
   147 and assumptions (hypotheses).  Definitions and theorems depending on
   148 the context may be added incrementally later on.  Named contexts refer
   149 to locales (cf.\ \S\ref{sec:locale}) or type classes (cf.\ 
   150 \S\ref{sec:class}); the name ``$-$'' signifies the global theory
   151 context.
   152 
   153 \indexisarcmd{context}\indexisarcmd{end}
   154 \begin{matharray}{rcll}
   155   \isarcmd{context} & : & \isartrans{theory}{local{\dsh}theory} \\
   156   \isarcmd{end} & : & \isartrans{local{\dsh}theory}{theory} \\
   157 \end{matharray}
   158 
   159 \indexouternonterm{target}
   160 \begin{rail}
   161   'context' name 'begin'
   162   ;
   163 
   164   target: '(' 'in' name ')'
   165   ;
   166 \end{rail}
   167 
   168 \begin{descr}
   169   
   170 \item $\isarkeyword{context}~c~\isarkeyword{begin}$ recommences an
   171   existing locale or class context $c$.  Note that locale and class
   172   definitions allow to include the $\isarkeyword{begin}$ keyword as
   173   well, in order to continue the local theory immediately after the
   174   initial specification.
   175   
   176 \item $\END$ concludes the current local theory and continues the
   177   enclosing global theory.  Note that a non-local $\END$ has a
   178   different meaning: it concludes the theory itself
   179   (\S\ref{sec:begin-thy}).
   180   
   181 \item $(\IN~loc)$ given after any local theory command specifies an
   182   immediate target, e.g.\ 
   183   ``$\isarkeyword{definition}~(\IN~loc)~\dots$'' or
   184   ``$\THEOREMNAME~(\IN~loc)~\dots$''.  This works both in a local or
   185   global theory context; the current target context will be suspended
   186   for this command only.  Note that $(\IN~-)$ will always produce a
   187   global result independently of the current target context.
   188 
   189 \end{descr}
   190 
   191 The exact meaning of results produced within a local theory context
   192 depends on the underlying target infrastructure (locale, type class
   193 etc.).  The general idea is as follows, considering a context named
   194 $c$ with parameter $x$ and assumption $A[x]$.
   195 
   196 Definitions are exported by introducing a global version with
   197 additional arguments; a syntactic abbreviation links the long form
   198 with the abstract version of the target context.  For example, $a
   199 \equiv t[x]$ becomes $c\dtt a \; ?x \equiv t[?x]$ at the theory level
   200 (for arbitrary $?x$), together with a local abbreviation $c \equiv
   201 c\dtt a\; x$ in the target context (for fixed $x$).
   202 
   203 Theorems are exported by discharging the assumptions and generalizing
   204 the parameters of the context.  For example, $a: B[x]$ becomes $c\dtt
   205 a: A[?x] \Imp B[?x]$ (for arbitrary $?x$).
   206 
   207 
   208 \subsection{Locales}\label{sec:locale}
   209 
   210 Locales are named local contexts, consisting of a list of declaration elements
   211 that are modeled after the Isar proof context commands (cf.\
   212 \S\ref{sec:proof-context}).
   213 
   214 
   215 \subsubsection{Locale specifications}
   216 
   217 \indexisarcmd{locale}\indexisarcmd{print-locale}\indexisarcmd{print-locales}
   218 \begin{matharray}{rcl}
   219   \isarcmd{locale} & : & \isartrans{theory}{local{\dsh}theory} \\
   220   \isarcmd{print_locale}^* & : & \isarkeep{theory~|~proof} \\
   221   \isarcmd{print_locales}^* & : & \isarkeep{theory~|~proof} \\
   222   intro_locales & : & \isarmeth \\
   223   unfold_locales & : & \isarmeth \\
   224 \end{matharray}
   225 
   226 \indexouternonterm{contextexpr}\indexouternonterm{contextelem}
   227 \indexisarelem{fixes}\indexisarelem{constrains}\indexisarelem{assumes}
   228 \indexisarelem{defines}\indexisarelem{notes}\indexisarelem{includes}
   229 
   230 \begin{rail}
   231   'locale' ('(open)')? name ('=' localeexpr)? 'begin'?
   232   ;
   233   'print\_locale' '!'? localeexpr
   234   ;
   235   localeexpr: ((contextexpr '+' (contextelem+)) | contextexpr | (contextelem+))
   236   ;
   237 
   238   contextexpr: nameref | '(' contextexpr ')' |
   239   (contextexpr (name mixfix? +)) | (contextexpr + '+')
   240   ;
   241   contextelem: fixes | constrains | assumes | defines | notes | includes
   242   ;
   243   fixes: 'fixes' ((name ('::' type)? structmixfix? | vars) + 'and')
   244   ;
   245   constrains: 'constrains' (name '::' type + 'and')
   246   ;
   247   assumes: 'assumes' (thmdecl? props + 'and')
   248   ;
   249   defines: 'defines' (thmdecl? prop proppat? + 'and')
   250   ;
   251   notes: 'notes' (thmdef? thmrefs + 'and')
   252   ;
   253   includes: 'includes' contextexpr
   254   ;
   255 \end{rail}
   256 
   257 \begin{descr}
   258   
   259 \item [$\LOCALE~loc~=~import~+~body$] defines a new locale $loc$ as a context
   260   consisting of a certain view of existing locales ($import$) plus some
   261   additional elements ($body$).  Both $import$ and $body$ are optional; the
   262   degenerate form $\LOCALE~loc$ defines an empty locale, which may still be
   263   useful to collect declarations of facts later on.  Type-inference on locale
   264   expressions automatically takes care of the most general typing that the
   265   combined context elements may acquire.
   266 
   267   The $import$ consists of a structured context expression, consisting of
   268   references to existing locales, renamed contexts, or merged contexts.
   269   Renaming uses positional notation: $c~\vec x$ means that (a prefix of) the
   270   fixed parameters of context $c$ are named according to $\vec x$; a
   271   ``\texttt{_}'' (underscore) \indexisarthm{_@\texttt{_}} means to skip that
   272   position.  Renaming by default deletes existing syntax.  Optionally,
   273   new syntax may by specified with a mixfix annotation.  Note that the
   274   special syntax declared with ``$(structure)$'' (see below) is
   275   neither deleted nor can it be changed.
   276   Merging proceeds from left-to-right, suppressing any duplicates stemming
   277   from different paths through the import hierarchy.
   278 
   279   The $body$ consists of basic context elements, further context expressions
   280   may be included as well.
   281 
   282   \begin{descr}
   283 
   284   \item [$\FIXES{~x::\tau~(mx)}$] declares a local parameter of type $\tau$
   285     and mixfix annotation $mx$ (both are optional).  The special syntax
   286     declaration ``$(structure)$'' means that $x$ may be referenced
   287     implicitly in this context.
   288 
   289   \item [$\CONSTRAINS{~x::\tau}$] introduces a type constraint $\tau$
   290     on the local parameter $x$.
   291 
   292   \item [$\ASSUMES{a}{\vec\phi}$] introduces local premises, similar to
   293     $\ASSUMENAME$ within a proof (cf.\ \S\ref{sec:proof-context}).
   294 
   295   \item [$\DEFINES{a}{x \equiv t}$] defines a previously declared parameter.
   296     This is close to $\DEFNAME$ within a proof (cf.\
   297     \S\ref{sec:proof-context}), but $\DEFINESNAME$ takes an equational
   298     proposition instead of variable-term pair.  The left-hand side of the
   299     equation may have additional arguments, e.g.\ ``$\DEFINES{}{f~\vec x
   300       \equiv t}$''.
   301 
   302   \item [$\NOTES{a}{\vec b}$] reconsiders facts within a local context.  Most
   303     notably, this may include arbitrary declarations in any attribute
   304     specifications included here, e.g.\ a local $simp$ rule.
   305 
   306   \item [$\INCLUDES{c}$] copies the specified context in a statically scoped
   307     manner.  Only available in the long goal format of \S\ref{sec:goals}.
   308 
   309     In contrast, the initial $import$ specification of a locale expression
   310     maintains a dynamic relation to the locales being referenced (benefiting
   311     from any later fact declarations in the obvious manner).
   312   \end{descr}
   313   
   314   Note that ``$\IS{p}$'' patterns given in the syntax of $\ASSUMESNAME$ and
   315   $\DEFINESNAME$ above are illegal in locale definitions.  In the long goal
   316   format of \S\ref{sec:goals}, term bindings may be included as expected,
   317   though.
   318   
   319   \medskip By default, locale specifications are ``closed up'' by turning the
   320   given text into a predicate definition $loc_axioms$ and deriving the
   321   original assumptions as local lemmas (modulo local definitions).  The
   322   predicate statement covers only the newly specified assumptions, omitting
   323   the content of included locale expressions.  The full cumulative view is
   324   only provided on export, involving another predicate $loc$ that refers to
   325   the complete specification text.
   326   
   327   In any case, the predicate arguments are those locale parameters that
   328   actually occur in the respective piece of text.  Also note that these
   329   predicates operate at the meta-level in theory, but the locale packages
   330   attempts to internalize statements according to the object-logic setup
   331   (e.g.\ replacing $\Forall$ by $\forall$, and $\Imp$ by $\imp$ in HOL; see
   332   also \S\ref{sec:object-logic}).  Separate introduction rules
   333   $loc_axioms.intro$ and $loc.intro$ are declared as well.
   334   
   335   The $(open)$ option of a locale specification prevents both the current
   336   $loc_axioms$ and cumulative $loc$ predicate constructions.  Predicates are
   337   also omitted for empty specification texts.
   338 
   339 \item [$\isarkeyword{print_locale}~import~+~body$] prints the specified locale
   340   expression in a flattened form.  The notable special case
   341   $\isarkeyword{print_locale}~loc$ just prints the contents of the named
   342   locale, but keep in mind that type-inference will normalize type variables
   343   according to the usual alphabetical order.  The command omits
   344   $\isarkeyword{notes}$ elements by default.  Use
   345   $\isarkeyword{print_locale}!$ to get them included.
   346 
   347 \item [$\isarkeyword{print_locales}$] prints the names of all locales of the
   348   current theory.
   349 
   350 \item [$intro_locales$ and $unfold_locales$] repeatedly expand
   351   all introduction rules of locale predicates of the theory.  While
   352   $intro_locales$ only applies the $loc.intro$ introduction rules and
   353   therefore does not decend to assumptions, $unfold_locales$ is more
   354   aggressive and applies $loc_axioms.intro$ as well.  Both methods are
   355   aware of locale specifications entailed by the context, both from
   356   target and $\isarkeyword{includes}$ statements, and from
   357   interpretations (see below).  New goals that are entailed by the
   358   current context are discharged automatically.
   359 
   360 \end{descr}
   361 
   362 
   363 \subsubsection{Interpretation of locales}
   364 
   365 Locale expressions (more precisely, \emph{context expressions}) may be
   366 instantiated, and the instantiated facts added to the current context.
   367 This requires a proof of the instantiated specification and is called
   368 \emph{locale interpretation}.  Interpretation is possible in theories
   369 and locales (command $\isarcmd{interpretation}$) and also in proof
   370 contexts ($\isarcmd{interpret}$).
   371 
   372 \indexisarcmd{interpretation}\indexisarcmd{interpret}
   373 \indexisarcmd{print-interps}
   374 \begin{matharray}{rcl}
   375   \isarcmd{interpretation} & : & \isartrans{theory}{proof(prove)} \\
   376   \isarcmd{interpret} & : & \isartrans{proof(state) ~|~ proof(chain)}{proof(prove)} \\
   377   \isarcmd{print_interps}^* & : &  \isarkeep{theory~|~proof} \\
   378 \end{matharray}
   379 
   380 \indexouternonterm{interp}
   381 
   382 \railalias{printinterps}{print\_interps}
   383 \railterm{printinterps}
   384 
   385 \begin{rail}
   386   'interpretation' (interp | name ('<' | subseteq) contextexpr)
   387   ;
   388   'interpret' interp
   389   ;
   390   printinterps '!'? name
   391   ;
   392   interp: thmdecl? \\ (contextexpr ('[' (inst+) ']')? |
   393     name ('[' (inst+) ']')? 'where' (prop + 'and'))
   394   ;
   395 \end{rail}
   396 
   397 
   398 \begin{descr}
   399 
   400 \item [$\isarcmd{interpretation}~expr~insts~\isarkeyword{where}~eqns$]
   401 
   402   The first form of $\isarcmd{interpretation}$ interprets $expr$ in
   403   the theory.  The instantiation is given as a list of terms $insts$
   404   and is positional.  All parameters must receive an instantiation
   405   term --- with the exception of defined parameters.  These are, if
   406   omitted, derived from the defining equation and other
   407   instantiations.  Use ``\_'' to omit an instantiation term.  Free
   408   variables are automatically generalized.
   409 
   410   The command generates proof obligations for the instantiated
   411   specifications (assumes and defines elements).  Once these are
   412   discharged by the user, instantiated facts are added to the theory in
   413   a post-processing phase.
   414 
   415   Additional equations, which are unfolded in facts during
   416   post-processing, may be given after the keyword
   417   $\isarkeyword{where}$.  This is useful for interpreting concepts
   418   introduced through definition specification elements.  The equations
   419   must be proved.  Note that if equations are present, the context
   420   expression is restricted to a locale name.
   421 
   422   The command is aware of interpretations already active in the
   423   theory.  No proof obligations are generated for those, neither is
   424   post-processing applied to their facts.  This avoids duplication of
   425   interpreted facts, in particular.  Note that, in the case of a
   426   locale with import, parts of the interpretation may already be
   427   active.  The command will only generate proof obligations and process
   428   facts for new parts.
   429 
   430   The context expression may be preceded by a name and/or attributes.
   431   These take effect in the post-processing of facts.  The name is used
   432   to prefix fact names, for example to avoid accidental hiding of
   433   other facts.  Attributes are applied after attributes of the
   434   interpreted facts.
   435 
   436   Adding facts to locales has the
   437   effect of adding interpreted facts to the theory for all active
   438   interpretations also.  That is, interpretations dynamically
   439   participate in any facts added to locales.
   440 
   441 \item [$\isarcmd{interpretation}~name~\subseteq~expr$]
   442 
   443   This form of the command interprets $expr$ in the locale $name$.  It
   444   requires a proof that the specification of $name$ implies the
   445   specification of $expr$.  As in the localized version of the theorem
   446   command, the proof is in the context of $name$.  After the proof
   447   obligation has been dischared, the facts of $expr$
   448   become part of locale $name$ as \emph{derived} context elements and
   449   are available when the context $name$ is subsequently entered.
   450   Note that, like import, this is dynamic: facts added to a locale
   451   part of $expr$ after interpretation become also available in
   452   $name$.  Like facts
   453   of renamed context elements, facts obtained by interpretation may be
   454   accessed by prefixing with the parameter renaming (where the parameters
   455   are separated by `\_').
   456 
   457   Unlike interpretation in theories, instantiation is confined to the
   458   renaming of parameters, which may be specified as part of the context
   459   expression $expr$.  Using defined parameters in $name$ one may
   460   achieve an effect similar to instantiation, though.
   461 
   462   Only specification fragments of $expr$ that are not already part of
   463   $name$ (be it imported, derived or a derived fragment of the import)
   464   are considered by interpretation.  This enables circular
   465   interpretations.
   466 
   467   If interpretations of $name$ exist in the current theory, the
   468   command adds interpretations for $expr$ as well, with the same
   469   prefix and attributes, although only for fragments of $expr$ that
   470   are not interpreted in the theory already.
   471 
   472 \item [$\isarcmd{interpret}~expr~insts~\isarkeyword{where}~eqns$]
   473   interprets $expr$ in the proof context and is otherwise similar to
   474   interpretation in theories.  Free variables in instantiations are not
   475   generalized, however.
   476 
   477 \item [$\isarcmd{print_interps}~loc$]
   478   prints the interpretations of a particular locale $loc$ that are
   479   active in the current context, either theory or proof context.  The
   480   exclamation point argument triggers printing of
   481   \emph{witness} theorems justifying interpretations.  These are
   482   normally omitted from the output.
   483 
   484   
   485 \end{descr}
   486 
   487 \begin{warn}
   488   Since attributes are applied to interpreted theorems, interpretation
   489   may modify the context of common proof tools, e.g.\ the Simplifier
   490   or Classical Reasoner.  Since the behavior of such automated
   491   reasoning tools is \emph{not} stable under interpretation morphisms,
   492   manual declarations might have to be issued.
   493 \end{warn}
   494 
   495 \begin{warn}
   496   An interpretation in a theory may subsume previous interpretations.
   497   This happens if the same specification fragment is interpreted twice
   498   and the instantiation of the second interpretation is more general
   499   than the interpretation of the first.  A warning is issued, since it
   500   is likely that these could have been generalized in the first place.
   501   The locale package does not attempt to remove subsumed
   502   interpretations.
   503 \end{warn}
   504 
   505 
   506 \subsection{Type classes}\label{sec:class}
   507 
   508 A type class is a special case of a locale, with some additional
   509 infrastructure (notably a link to type-inference).  Type classes
   510 consist of a locale with \emph{exactly one} type variable and an
   511 corresponding axclass.  \cite{isabelle-classes} gives a substantial
   512 introduction on type classes.
   513 
   514 \indexisarcmd{instance}\indexisarcmd{class}\indexisarcmd{print-classes}
   515 \begin{matharray}{rcl}
   516   \isarcmd{class} & : & \isartrans{theory}{local{\dsh}theory} \\
   517   \isarcmd{instance} & : & \isartrans{theory}{proof(prove)} \\
   518   \isarcmd{print_classes}^* & : & \isarkeep{theory~|~proof} \\
   519 \end{matharray}
   520 
   521 \begin{rail}
   522   'class' name '=' classexpr 'begin'?
   523   ;
   524   'instance' (instarity | instsubsort)
   525   ;
   526   'print\_classes'
   527   ;
   528 
   529   classexpr: ((superclassexpr '+' (contextelem+)) | superclassexpr | (contextelem+))
   530   ;
   531   instarity: (nameref '::' arity + 'and') (axmdecl prop +)?
   532   ;
   533   instsubsort: nameref ('<' | subseteq) sort
   534   ;
   535   superclassexpr: nameref | (nameref '+' superclassexpr)
   536   ;
   537 \end{rail}
   538 
   539 \begin{descr}
   540 
   541 \item [$\CLASS~c = superclasses~+~body$] defines a new class $c$,
   542   inheriting from $superclasses$. Simultaneously, a locale
   543   named $c$ is introduced, inheriting from the locales
   544   corresponding to $superclasses$; also, an axclass
   545   named $c$, inheriting from the axclasses corresponding to
   546   $superclasses$. $\FIXESNAME$ in $body$ are lifted
   547   to the theory toplevel, constraining
   548   the free type variable to sort $c$ and stripping local syntax.
   549   $\ASSUMESNAME$ in $body$ are also lifted, 
   550   constraining
   551   the free type variable to sort $c$.
   552 
   553 \item [$\INSTANCE~a: \vec{arity}~\vec{defs}$]
   554   sets up a goal stating type arities.  The proof would usually
   555   proceed by $intro_classes$, and then establish the characteristic theorems
   556   of the type classes involved.
   557   The $defs$, if given, must correspond to the class parameters
   558   involved in the $arities$ and are introduces in the theory
   559   before proof.
   560   After finishing the proof, the theory will be
   561   augmented by a type signature declaration corresponding to the
   562   resulting theorems.
   563   This $\isarcmd{instance}$ command is actually an extension
   564   of primitive axclass $\isarcmd{instance}$ (see \ref{sec:axclass}).
   565   
   566 \item [$\INSTANCE~c \subseteq \vec{c}$] sets up a
   567   goal stating 
   568   the interpretation of the locale corresponding to $c$
   569   in the merge of all locales corresponding to $\vec{c}$.
   570   After finishing the proof, it is automatically lifted to
   571   prove the additional class relation $c \subseteq \vec{c}$.
   572 
   573 \item [$\isarkeyword{print_classes}$] prints all classes
   574   in the current theory.
   575 
   576 \end{descr}
   577 
   578 
   579 \subsection{Axiomatic type classes}\label{sec:axclass}
   580 
   581 \indexisarcmd{axclass}\indexisarmeth{intro-classes}
   582 \begin{matharray}{rcl}
   583   \isarcmd{axclass} & : & \isartrans{theory}{theory} \\
   584   \isarcmd{instance} & : & \isartrans{theory}{proof(prove)} \\
   585   intro_classes & : & \isarmeth \\
   586 \end{matharray}
   587 
   588 Axiomatic type classes are provided by Isabelle/Pure as a \emph{definitional}
   589 interface to type classes (cf.~\S\ref{sec:classes}).  Thus any object logic
   590 may make use of this light-weight mechanism of abstract theories
   591 \cite{Wenzel:1997:TPHOL}.  There is also a tutorial on using axiomatic type
   592 classes in Isabelle \cite{isabelle-axclass} that is part of the standard
   593 Isabelle documentation.
   594 
   595 \begin{rail}
   596   'axclass' classdecl (axmdecl prop +)
   597   ;
   598   'instance' (nameref ('<' | subseteq) nameref | nameref '::' arity)
   599   ;
   600 \end{rail}
   601 
   602 \begin{descr}
   603   
   604 \item [$\AXCLASS~c \subseteq \vec c~~axms$] defines an axiomatic type class as
   605   the intersection of existing classes, with additional axioms holding.  Class
   606   axioms may not contain more than one type variable.  The class axioms (with
   607   implicit sort constraints added) are bound to the given names.  Furthermore
   608   a class introduction rule is generated (being bound as
   609   $c_class{\dtt}intro$); this rule is employed by method $intro_classes$ to
   610   support instantiation proofs of this class.
   611   
   612   The ``axioms'' are stored as theorems according to the given name
   613   specifications, adding the class name $c$ as name space prefix; the same
   614   facts are also stored collectively as $c_class{\dtt}axioms$.
   615   
   616 \item [$\INSTANCE~c@1 \subseteq c@2$ and $\INSTANCE~t :: (\vec s)s$] setup a
   617   goal stating a class relation or type arity.  The proof would usually
   618   proceed by $intro_classes$, and then establish the characteristic theorems
   619   of the type classes involved.  After finishing the proof, the theory will be
   620   augmented by a type signature declaration corresponding to the resulting
   621   theorem.
   622 
   623 \item [$intro_classes$] repeatedly expands all class introduction rules of
   624   this theory.  Note that this method usually needs not be named explicitly,
   625   as it is already included in the default proof step (of $\PROOFNAME$ etc.).
   626   In particular, instantiation of trivial (syntactic) classes may be performed
   627   by a single ``$\DDOT$'' proof step.
   628 
   629 \end{descr}
   630 
   631 
   632 \subsection{Configuration options}
   633 
   634 Isabelle/Pure maintains a record of named configuration options within the
   635 theory or proof context, with values of type $bool$, $int$, or $string$.
   636 Tools may declare options in ML, and then refer to these values (relative to
   637 the context).  Thus global reference variables are easily avoided.  The user
   638 may change the value of a configuration option by means of an associated
   639 attribute of the same name.  This form of context declaration works
   640 particularly well with commands such as $\isarkeyword{declare}$ or
   641 $\isarkeyword{using}$.
   642 
   643 For historical reasons, some tools cannot take the full proof context
   644 into account and merely refer to the background theory.  This is
   645 accommodated by configuration options being declared as ``global'',
   646 which may not be changed within a local context.
   647 
   648 \indexisarcmd{print-configs}
   649 \begin{matharray}{rcll}
   650   \isarcmd{print_configs} & : & \isarkeep{theory~|~proof} \\
   651 \end{matharray}
   652 
   653 \begin{rail}
   654   name ('=' ('true' | 'false' | int | name))?
   655 \end{rail}
   656 
   657 \begin{descr}
   658   
   659 \item [$\isarkeyword{print_configs}$] prints the available configuration
   660   options, with names, types, and current values.
   661   
   662 \item [$name = value$] as an attribute expression modifies the named option,
   663   with the syntax of the value depending on the option's type.  For $bool$ the
   664   default value is $true$.  Any attempt to change a global option in a local
   665   context is ignored.
   666 
   667 \end{descr}
   668 
   669 
   670 \section{Derived proof schemes}
   671 
   672 \subsection{Generalized elimination}\label{sec:obtain}
   673 
   674 \indexisarcmd{obtain}\indexisarcmd{guess}
   675 \begin{matharray}{rcl}
   676   \isarcmd{obtain} & : & \isartrans{proof(state)}{proof(prove)} \\
   677   \isarcmd{guess}^* & : & \isartrans{proof(state)}{proof(prove)} \\
   678 \end{matharray}
   679 
   680 Generalized elimination means that additional elements with certain properties
   681 may be introduced in the current context, by virtue of a locally proven
   682 ``soundness statement''.  Technically speaking, the $\OBTAINNAME$ language
   683 element is like a declaration of $\FIXNAME$ and $\ASSUMENAME$ (see also see
   684 \S\ref{sec:proof-context}), together with a soundness proof of its additional
   685 claim.  According to the nature of existential reasoning, assumptions get
   686 eliminated from any result exported from the context later, provided that the
   687 corresponding parameters do \emph{not} occur in the conclusion.
   688 
   689 \begin{rail}
   690   'obtain' parname? (vars + 'and') 'where' (props + 'and')
   691   ;
   692   'guess' (vars + 'and')
   693   ;
   694 \end{rail}
   695 
   696 $\OBTAINNAME$ is defined as a derived Isar command as follows, where $\vec b$
   697 shall refer to (optional) facts indicated for forward chaining.
   698 \begin{matharray}{l}
   699   \langle facts~\vec b\rangle \\
   700   \OBTAIN{\vec x}{a}{\vec \phi}~~\langle proof\rangle \equiv {} \\[1ex]
   701   \quad \HAVE{}{\All{thesis} (\All{\vec x} \vec\phi \Imp thesis) \Imp thesis} \\
   702   \quad \PROOF{succeed} \\
   703   \qquad \FIX{thesis} \\
   704   \qquad \ASSUME{that~[intro?]}{\All{\vec x} \vec\phi \Imp thesis} \\
   705   \qquad \THUS{}{thesis} \\
   706   \quad\qquad \APPLY{-} \\
   707   \quad\qquad \USING{\vec b}~~\langle proof\rangle \\
   708   \quad \QED{} \\
   709   \quad \FIX{\vec x}~\ASSUMENAME^\ast~a\colon~\vec\phi \\
   710 \end{matharray}
   711 
   712 Typically, the soundness proof is relatively straight-forward, often just by
   713 canonical automated tools such as ``$\BY{simp}$'' or ``$\BY{blast}$''.
   714 Accordingly, the ``$that$'' reduction above is declared as simplification and
   715 introduction rule.
   716 
   717 In a sense, $\OBTAINNAME$ represents at the level of Isar proofs what would be
   718 meta-logical existential quantifiers and conjunctions.  This concept has a
   719 broad range of useful applications, ranging from plain elimination (or
   720 introduction) of object-level existential and conjunctions, to elimination
   721 over results of symbolic evaluation of recursive definitions, for example.
   722 Also note that $\OBTAINNAME$ without parameters acts much like $\HAVENAME$,
   723 where the result is treated as a genuine assumption.
   724 
   725 An alternative name to be used instead of ``$that$'' above may be
   726 given in parentheses.
   727 
   728 \medskip
   729 
   730 The improper variant $\isarkeyword{guess}$ is similar to $\OBTAINNAME$, but
   731 derives the obtained statement from the course of reasoning!  The proof starts
   732 with a fixed goal $thesis$.  The subsequent proof may refine this to anything
   733 of the form like $\All{\vec x} \vec\phi \Imp thesis$, but must not introduce
   734 new subgoals.  The final goal state is then used as reduction rule for the
   735 obtain scheme described above.  Obtained parameters $\vec x$ are marked as
   736 internal by default, which prevents the proof context from being polluted by
   737 ad-hoc variables.  The variable names and type constraints given as arguments
   738 for $\isarkeyword{guess}$ specify a prefix of obtained parameters explicitly
   739 in the text.
   740 
   741 It is important to note that the facts introduced by $\OBTAINNAME$ and
   742 $\isarkeyword{guess}$ may not be polymorphic: any type-variables occurring
   743 here are fixed in the present context!
   744 
   745 
   746 \subsection{Calculational reasoning}\label{sec:calculation}
   747 
   748 \indexisarcmd{also}\indexisarcmd{finally}
   749 \indexisarcmd{moreover}\indexisarcmd{ultimately}
   750 \indexisarcmd{print-trans-rules}
   751 \indexisaratt{trans}\indexisaratt{sym}\indexisaratt{symmetric}
   752 \begin{matharray}{rcl}
   753   \isarcmd{also} & : & \isartrans{proof(state)}{proof(state)} \\
   754   \isarcmd{finally} & : & \isartrans{proof(state)}{proof(chain)} \\
   755   \isarcmd{moreover} & : & \isartrans{proof(state)}{proof(state)} \\
   756   \isarcmd{ultimately} & : & \isartrans{proof(state)}{proof(chain)} \\
   757   \isarcmd{print_trans_rules}^* & : & \isarkeep{theory~|~proof} \\
   758   trans & : & \isaratt \\
   759   sym & : & \isaratt \\
   760   symmetric & : & \isaratt \\
   761 \end{matharray}
   762 
   763 Calculational proof is forward reasoning with implicit application of
   764 transitivity rules (such those of $=$, $\leq$, $<$).  Isabelle/Isar maintains
   765 an auxiliary register $calculation$\indexisarthm{calculation} for accumulating
   766 results obtained by transitivity composed with the current result.  Command
   767 $\ALSO$ updates $calculation$ involving $this$, while $\FINALLY$ exhibits the
   768 final $calculation$ by forward chaining towards the next goal statement.  Both
   769 commands require valid current facts, i.e.\ may occur only after commands that
   770 produce theorems such as $\ASSUMENAME$, $\NOTENAME$, or some finished proof of
   771 $\HAVENAME$, $\SHOWNAME$ etc.  The $\MOREOVER$ and $\ULTIMATELY$ commands are
   772 similar to $\ALSO$ and $\FINALLY$, but only collect further results in
   773 $calculation$ without applying any rules yet.
   774 
   775 Also note that the implicit term abbreviation ``$\dots$'' has its canonical
   776 application with calculational proofs.  It refers to the argument of the
   777 preceding statement. (The argument of a curried infix expression happens to be
   778 its right-hand side.)
   779 
   780 Isabelle/Isar calculations are implicitly subject to block structure in the
   781 sense that new threads of calculational reasoning are commenced for any new
   782 block (as opened by a local goal, for example).  This means that, apart from
   783 being able to nest calculations, there is no separate \emph{begin-calculation}
   784 command required.
   785 
   786 \medskip
   787 
   788 The Isar calculation proof commands may be defined as follows:\footnote{We
   789   suppress internal bookkeeping such as proper handling of block-structure.}
   790 \begin{matharray}{rcl}
   791   \ALSO@0 & \equiv & \NOTE{calculation}{this} \\
   792   \ALSO@{n+1} & \equiv & \NOTE{calculation}{trans~[OF~calculation~this]} \\[0.5ex]
   793   \FINALLY & \equiv & \ALSO~\FROM{calculation} \\
   794   \MOREOVER & \equiv & \NOTE{calculation}{calculation~this} \\
   795   \ULTIMATELY & \equiv & \MOREOVER~\FROM{calculation} \\
   796 \end{matharray}
   797 
   798 \begin{rail}
   799   ('also' | 'finally') ('(' thmrefs ')')?
   800   ;
   801   'trans' (() | 'add' | 'del')
   802   ;
   803 \end{rail}
   804 
   805 \begin{descr}
   806 
   807 \item [$\ALSO~(\vec a)$] maintains the auxiliary $calculation$ register as
   808   follows.  The first occurrence of $\ALSO$ in some calculational thread
   809   initializes $calculation$ by $this$. Any subsequent $\ALSO$ on the same
   810   level of block-structure updates $calculation$ by some transitivity rule
   811   applied to $calculation$ and $this$ (in that order).  Transitivity rules are
   812   picked from the current context, unless alternative rules are given as
   813   explicit arguments.
   814 
   815 \item [$\FINALLY~(\vec a)$] maintaining $calculation$ in the same way as
   816   $\ALSO$, and concludes the current calculational thread.  The final result
   817   is exhibited as fact for forward chaining towards the next goal. Basically,
   818   $\FINALLY$ just abbreviates $\ALSO~\FROM{calculation}$.  Note that
   819   ``$\FINALLY~\SHOW{}{\Var{thesis}}~\DOT$'' and
   820   ``$\FINALLY~\HAVE{}{\phi}~\DOT$'' are typical idioms for concluding
   821   calculational proofs.
   822 
   823 \item [$\MOREOVER$ and $\ULTIMATELY$] are analogous to $\ALSO$ and $\FINALLY$,
   824   but collect results only, without applying rules.
   825 
   826 \item [$\isarkeyword{print_trans_rules}$] prints the list of transitivity
   827   rules (for calculational commands $\ALSO$ and $\FINALLY$) and symmetry rules
   828   (for the $symmetric$ operation and single step elimination patters) of the
   829   current context.
   830 
   831 \item [$trans$] declares theorems as transitivity rules.
   832 
   833 \item [$sym$] declares symmetry rules.
   834 
   835 \item [$symmetric$] resolves a theorem with some rule declared as $sym$ in the
   836   current context.  For example, ``$\ASSUME{[symmetric]}{x = y}$'' produces a
   837   swapped fact derived from that assumption.
   838 
   839   In structured proof texts it is often more appropriate to use an explicit
   840   single-step elimination proof, such as ``$\ASSUME{}{x = y}~\HENCE{}{y =
   841     x}~\DDOT$''.  The very same rules known to $symmetric$ are declared as
   842   $elim?$ as well.
   843 
   844 \end{descr}
   845 
   846 
   847 \section{Proof tools}
   848 
   849 \subsection{Miscellaneous methods and attributes}\label{sec:misc-meth-att}
   850 
   851 \indexisarmeth{unfold}\indexisarmeth{fold}\indexisarmeth{insert}
   852 \indexisarmeth{erule}\indexisarmeth{drule}\indexisarmeth{frule}
   853 \indexisarmeth{fail}\indexisarmeth{succeed}
   854 \begin{matharray}{rcl}
   855   unfold & : & \isarmeth \\
   856   fold & : & \isarmeth \\
   857   insert & : & \isarmeth \\[0.5ex]
   858   erule^* & : & \isarmeth \\
   859   drule^* & : & \isarmeth \\
   860   frule^* & : & \isarmeth \\
   861   succeed & : & \isarmeth \\
   862   fail & : & \isarmeth \\
   863 \end{matharray}
   864 
   865 \begin{rail}
   866   ('fold' | 'unfold' | 'insert') thmrefs
   867   ;
   868   ('erule' | 'drule' | 'frule') ('('nat')')? thmrefs
   869   ;
   870 \end{rail}
   871 
   872 \begin{descr}
   873   
   874 \item [$unfold~\vec a$ and $fold~\vec a$] expand (or fold back again)
   875   the given definitions throughout all goals; any chained facts
   876   provided are inserted into the goal and subject to rewriting as
   877   well.
   878 
   879 \item [$insert~\vec a$] inserts theorems as facts into all goals of the proof
   880   state.  Note that current facts indicated for forward chaining are ignored.
   881 
   882 \item [$erule~\vec a$, $drule~\vec a$, and $frule~\vec a$] are similar to the
   883   basic $rule$ method (see \S\ref{sec:pure-meth-att}), but apply rules by
   884   elim-resolution, destruct-resolution, and forward-resolution, respectively
   885   \cite{isabelle-ref}.  The optional natural number argument (default $0$)
   886   specifies additional assumption steps to be performed here.
   887 
   888   Note that these methods are improper ones, mainly serving for
   889   experimentation and tactic script emulation.  Different modes of basic rule
   890   application are usually expressed in Isar at the proof language level,
   891   rather than via implicit proof state manipulations.  For example, a proper
   892   single-step elimination would be done using the plain $rule$ method, with
   893   forward chaining of current facts.
   894 
   895 \item [$succeed$] yields a single (unchanged) result; it is the identity of
   896   the ``\texttt{,}'' method combinator (cf.\ \S\ref{sec:syn-meth}).
   897 
   898 \item [$fail$] yields an empty result sequence; it is the identity of the
   899   ``\texttt{|}'' method combinator (cf.\ \S\ref{sec:syn-meth}).
   900 
   901 \end{descr}
   902 
   903 \indexisaratt{tagged}\indexisaratt{untagged}
   904 \indexisaratt{THEN}\indexisaratt{COMP}
   905 \indexisaratt{unfolded}\indexisaratt{folded}
   906 \indexisaratt{standard}\indexisarattof{Pure}{elim-format}
   907 \indexisaratt{no-vars}
   908 \begin{matharray}{rcl}
   909   tagged & : & \isaratt \\
   910   untagged & : & \isaratt \\[0.5ex]
   911   THEN & : & \isaratt \\
   912   COMP & : & \isaratt \\[0.5ex]
   913   unfolded & : & \isaratt \\
   914   folded & : & \isaratt \\[0.5ex]
   915   rotated & : & \isaratt \\
   916   elim_format & : & \isaratt \\
   917   standard^* & : & \isaratt \\
   918   no_vars^* & : & \isaratt \\
   919 \end{matharray}
   920 
   921 \begin{rail}
   922   'tagged' nameref
   923   ;
   924   'untagged' name
   925   ;
   926   ('THEN' | 'COMP') ('[' nat ']')? thmref
   927   ;
   928   ('unfolded' | 'folded') thmrefs
   929   ;
   930   'rotated' ( int )?
   931 \end{rail}
   932 
   933 \begin{descr}
   934 
   935 \item [$tagged~name~arg$ and $untagged~name$] add and remove $tags$ of some
   936   theorem.  Tags may be any list of strings that serve as comment for some
   937   tools (e.g.\ $\LEMMANAME$ causes the tag ``$lemma$'' to be added to the
   938   result).  The first string is considered the tag name, the second its
   939   argument.  Note that $untagged$ removes any tags of the same name.
   940 
   941 \item [$THEN~a$ and $COMP~a$] compose rules by resolution.  $THEN$ resolves
   942   with the first premise of $a$ (an alternative position may be also
   943   specified); the $COMP$ version skips the automatic lifting process that is
   944   normally intended (cf.\ \texttt{RS} and \texttt{COMP} in
   945   \cite[\S5]{isabelle-ref}).
   946   
   947 \item [$unfolded~\vec a$ and $folded~\vec a$] expand and fold back
   948   again the given definitions throughout a rule.
   949 
   950 \item [$rotated~n$] rotate the premises of a theorem by $n$ (default 1).
   951 
   952 \item [$elim_format$] turns a destruction rule into elimination rule format,
   953   by resolving with the rule $\PROP A \Imp (\PROP A \Imp \PROP B) \Imp \PROP
   954   B$.
   955   
   956   Note that the Classical Reasoner (\S\ref{sec:classical}) provides its own
   957   version of this operation.
   958 
   959 \item [$standard$] puts a theorem into the standard form of object-rules at
   960   the outermost theory level.  Note that this operation violates the local
   961   proof context (including active locales).
   962 
   963 \item [$no_vars$] replaces schematic variables by free ones; this is mainly
   964   for tuning output of pretty printed theorems.
   965 
   966 \end{descr}
   967 
   968 
   969 \subsection{Further tactic emulations}\label{sec:tactics}
   970 
   971 The following improper proof methods emulate traditional tactics.  These admit
   972 direct access to the goal state, which is normally considered harmful!  In
   973 particular, this may involve both numbered goal addressing (default 1), and
   974 dynamic instantiation within the scope of some subgoal.
   975 
   976 \begin{warn}
   977   Dynamic instantiations refer to universally quantified parameters of
   978   a subgoal (the dynamic context) rather than fixed variables and term
   979   abbreviations of a (static) Isar context.
   980 \end{warn}
   981 
   982 Tactic emulation methods, unlike their ML counterparts, admit
   983 simultaneous instantiation from both dynamic and static contexts.  If
   984 names occur in both contexts goal parameters hide locally fixed
   985 variables.  Likewise, schematic variables refer to term abbreviations,
   986 if present in the static context.  Otherwise the schematic variable is
   987 interpreted as a schematic variable and left to be solved by unification
   988 with certain parts of the subgoal.
   989 
   990 Note that the tactic emulation proof methods in Isabelle/Isar are consistently
   991 named $foo_tac$.  Note also that variable names occurring on left hand sides
   992 of instantiations must be preceded by a question mark if they coincide with
   993 a keyword or contain dots.
   994 This is consistent with the attribute $where$ (see \S\ref{sec:pure-meth-att}).
   995 
   996 \indexisarmeth{rule-tac}\indexisarmeth{erule-tac}
   997 \indexisarmeth{drule-tac}\indexisarmeth{frule-tac}
   998 \indexisarmeth{cut-tac}\indexisarmeth{thin-tac}
   999 \indexisarmeth{subgoal-tac}\indexisarmeth{rename-tac}
  1000 \indexisarmeth{rotate-tac}\indexisarmeth{tactic}
  1001 \begin{matharray}{rcl}
  1002   rule_tac^* & : & \isarmeth \\
  1003   erule_tac^* & : & \isarmeth \\
  1004   drule_tac^* & : & \isarmeth \\
  1005   frule_tac^* & : & \isarmeth \\
  1006   cut_tac^* & : & \isarmeth \\
  1007   thin_tac^* & : & \isarmeth \\
  1008   subgoal_tac^* & : & \isarmeth \\
  1009   rename_tac^* & : & \isarmeth \\
  1010   rotate_tac^* & : & \isarmeth \\
  1011   tactic^* & : & \isarmeth \\
  1012 \end{matharray}
  1013 
  1014 \railalias{ruletac}{rule\_tac}
  1015 \railterm{ruletac}
  1016 
  1017 \railalias{eruletac}{erule\_tac}
  1018 \railterm{eruletac}
  1019 
  1020 \railalias{druletac}{drule\_tac}
  1021 \railterm{druletac}
  1022 
  1023 \railalias{fruletac}{frule\_tac}
  1024 \railterm{fruletac}
  1025 
  1026 \railalias{cuttac}{cut\_tac}
  1027 \railterm{cuttac}
  1028 
  1029 \railalias{thintac}{thin\_tac}
  1030 \railterm{thintac}
  1031 
  1032 \railalias{subgoaltac}{subgoal\_tac}
  1033 \railterm{subgoaltac}
  1034 
  1035 \railalias{renametac}{rename\_tac}
  1036 \railterm{renametac}
  1037 
  1038 \railalias{rotatetac}{rotate\_tac}
  1039 \railterm{rotatetac}
  1040 
  1041 \begin{rail}
  1042   ( ruletac | eruletac | druletac | fruletac | cuttac | thintac ) goalspec?
  1043   ( insts thmref | thmrefs )
  1044   ;
  1045   subgoaltac goalspec? (prop +)
  1046   ;
  1047   renametac goalspec? (name +)
  1048   ;
  1049   rotatetac goalspec? int?
  1050   ;
  1051   'tactic' text
  1052   ;
  1053 
  1054   insts: ((name '=' term) + 'and') 'in'
  1055   ;
  1056 \end{rail}
  1057 
  1058 \begin{descr}
  1059 
  1060 \item [$rule_tac$ etc.] do resolution of rules with explicit instantiation.
  1061   This works the same way as the ML tactics \texttt{res_inst_tac} etc. (see
  1062   \cite[\S3]{isabelle-ref}).
  1063 
  1064   Multiple rules may be only given if there is no instantiation; then
  1065   $rule_tac$ is the same as \texttt{resolve_tac} in ML (see
  1066   \cite[\S3]{isabelle-ref}).
  1067 
  1068 \item [$cut_tac$] inserts facts into the proof state as assumption of a
  1069   subgoal, see also \texttt{cut_facts_tac} in \cite[\S3]{isabelle-ref}.  Note
  1070   that the scope of schematic variables is spread over the main goal
  1071   statement.  Instantiations may be given as well, see also ML tactic
  1072   \texttt{cut_inst_tac} in \cite[\S3]{isabelle-ref}.
  1073 
  1074 \item [$thin_tac~\phi$] deletes the specified assumption from a subgoal; note
  1075   that $\phi$ may contain schematic variables.  See also \texttt{thin_tac} in
  1076   \cite[\S3]{isabelle-ref}.
  1077 
  1078 \item [$subgoal_tac~\phi$] adds $\phi$ as an assumption to a subgoal.  See
  1079   also \texttt{subgoal_tac} and \texttt{subgoals_tac} in
  1080   \cite[\S3]{isabelle-ref}.
  1081 
  1082 \item [$rename_tac~\vec x$] renames parameters of a goal according to the list
  1083   $\vec x$, which refers to the \emph{suffix} of variables.
  1084 
  1085 \item [$rotate_tac~n$] rotates the assumptions of a goal by $n$ positions:
  1086   from right to left if $n$ is positive, and from left to right if $n$ is
  1087   negative; the default value is $1$.  See also \texttt{rotate_tac} in
  1088   \cite[\S3]{isabelle-ref}.
  1089 
  1090 \item [$tactic~text$] produces a proof method from any ML text of type
  1091   \texttt{tactic}.  Apart from the usual ML environment and the current
  1092   implicit theory context, the ML code may refer to the following locally
  1093   bound values:
  1094 
  1095 {\footnotesize\begin{verbatim}
  1096 val ctxt  : Proof.context
  1097 val facts : thm list
  1098 val thm   : string -> thm
  1099 val thms  : string -> thm list
  1100 \end{verbatim}}
  1101   Here \texttt{ctxt} refers to the current proof context, \texttt{facts}
  1102   indicates any current facts for forward-chaining, and
  1103   \texttt{thm}~/~\texttt{thms} retrieve named facts (including global
  1104   theorems) from the context.
  1105 \end{descr}
  1106 
  1107 
  1108 \subsection{The Simplifier}\label{sec:simplifier}
  1109 
  1110 \subsubsection{Simplification methods}
  1111 
  1112 \indexisarmeth{simp}\indexisarmeth{simp-all}
  1113 \begin{matharray}{rcl}
  1114   simp & : & \isarmeth \\
  1115   simp_all & : & \isarmeth \\
  1116 \end{matharray}
  1117 
  1118 \indexouternonterm{simpmod}
  1119 \begin{rail}
  1120   ('simp' | 'simp\_all') ('!' ?) opt? (simpmod *)
  1121   ;
  1122 
  1123   opt: '(' ('no\_asm' | 'no\_asm\_simp' | 'no\_asm\_use' | 'asm\_lr' | 'depth\_limit' ':' nat) ')'
  1124   ;
  1125   simpmod: ('add' | 'del' | 'only' | 'cong' (() | 'add' | 'del') |
  1126     'split' (() | 'add' | 'del')) ':' thmrefs
  1127   ;
  1128 \end{rail}
  1129 
  1130 \begin{descr}
  1131 
  1132 \item [$simp$] invokes Isabelle's simplifier, after declaring additional rules
  1133   according to the arguments given.  Note that the \railtterm{only} modifier
  1134   first removes all other rewrite rules, congruences, and looper tactics
  1135   (including splits), and then behaves like \railtterm{add}.
  1136 
  1137   \medskip The \railtterm{cong} modifiers add or delete Simplifier congruence
  1138   rules (see also \cite{isabelle-ref}), the default is to add.
  1139 
  1140   \medskip The \railtterm{split} modifiers add or delete rules for the
  1141   Splitter (see also \cite{isabelle-ref}), the default is to add.  This works
  1142   only if the Simplifier method has been properly setup to include the
  1143   Splitter (all major object logics such HOL, HOLCF, FOL, ZF do this already).
  1144 
  1145 \item [$simp_all$] is similar to $simp$, but acts on all goals (backwards from
  1146   the last to the first one).
  1147 
  1148 \end{descr}
  1149 
  1150 By default the Simplifier methods take local assumptions fully into account,
  1151 using equational assumptions in the subsequent normalization process, or
  1152 simplifying assumptions themselves (cf.\ \texttt{asm_full_simp_tac} in
  1153 \cite[\S10]{isabelle-ref}).  In structured proofs this is usually quite well
  1154 behaved in practice: just the local premises of the actual goal are involved,
  1155 additional facts may be inserted via explicit forward-chaining (using $\THEN$,
  1156 $\FROMNAME$ etc.).  The full context of assumptions is only included if the
  1157 ``$!$'' (bang) argument is given, which should be used with some care, though.
  1158 
  1159 Additional Simplifier options may be specified to tune the behavior further
  1160 (mostly for unstructured scripts with many accidental local facts):
  1161 ``$(no_asm)$'' means assumptions are ignored completely (cf.\ 
  1162 \texttt{simp_tac}), ``$(no_asm_simp)$'' means assumptions are used in the
  1163 simplification of the conclusion but are not themselves simplified (cf.\ 
  1164 \texttt{asm_simp_tac}), and ``$(no_asm_use)$'' means assumptions are
  1165 simplified but are not used in the simplification of each other or the
  1166 conclusion (cf.\ \texttt{full_simp_tac}).  For compatibility reasons, there is
  1167 also an option ``$(asm_lr)$'', which means that an assumption is only used for
  1168 simplifying assumptions which are to the right of it (cf.\ 
  1169 \texttt{asm_lr_simp_tac}).  Giving an option ``$(depth_limit: n)$'' limits the
  1170 number of recursive invocations of the simplifier during conditional
  1171 rewriting.
  1172 
  1173 \medskip
  1174 
  1175 The Splitter package is usually configured to work as part of the Simplifier.
  1176 The effect of repeatedly applying \texttt{split_tac} can be simulated by
  1177 ``$(simp~only\colon~split\colon~\vec a)$''.  There is also a separate $split$
  1178 method available for single-step case splitting.
  1179 
  1180 
  1181 \subsubsection{Declaring rules}
  1182 
  1183 \indexisarcmd{print-simpset}
  1184 \indexisaratt{simp}\indexisaratt{split}\indexisaratt{cong}
  1185 \begin{matharray}{rcl}
  1186   \isarcmd{print_simpset}^* & : & \isarkeep{theory~|~proof} \\
  1187   simp & : & \isaratt \\
  1188   cong & : & \isaratt \\
  1189   split & : & \isaratt \\
  1190 \end{matharray}
  1191 
  1192 \begin{rail}
  1193   ('simp' | 'cong' | 'split') (() | 'add' | 'del')
  1194   ;
  1195 \end{rail}
  1196 
  1197 \begin{descr}
  1198 
  1199 \item [$\isarcmd{print_simpset}$] prints the collection of rules declared to
  1200   the Simplifier, which is also known as ``simpset'' internally
  1201   \cite{isabelle-ref}.  This is a diagnostic command; $undo$ does not apply.
  1202 
  1203 \item [$simp$] declares simplification rules.
  1204 
  1205 \item [$cong$] declares congruence rules.
  1206 
  1207 \item [$split$] declares case split rules.
  1208 
  1209 \end{descr}
  1210 
  1211 
  1212 \subsubsection{Simplification procedures}
  1213 
  1214 \indexisarcmd{simproc-setup}
  1215 \indexisaratt{simproc}
  1216 \begin{matharray}{rcl}
  1217   \isarcmd{simproc_setup} & : & \isarkeep{local{\dsh}theory} \\
  1218   simproc & : & \isaratt \\
  1219 \end{matharray}
  1220 
  1221 \begin{rail}
  1222   'simproc\_setup' name '(' (term + '|') ')' '=' text \\ ('identifier' (nameref+))?
  1223   ;
  1224 
  1225   'simproc' (('add' ':')? | 'del' ':') (name+)
  1226   ;
  1227 \end{rail}
  1228 
  1229 \begin{descr}
  1230 
  1231 \item [$\isarcmd{simproc_setup}$] defines a named simplification
  1232   procedure that is invoked by the Simplifier whenever any of the
  1233   given term patterns match the current redex.  The implementation,
  1234   which is provided as ML source text, needs to be of type
  1235   \verb,morphism -> simpset -> cterm -> thm option,, where the
  1236   \verb,cterm, represents the current redex $r$ and the result is
  1237   supposed to be some proven rewrite rule $r \equiv r'$ (or a
  1238   generalized version), or \verb,NONE, to indicate failure.  The
  1239   \verb,simpset, argument holds the full context of the current
  1240   Simplifier invocation, including the actual Isar proof context.  The
  1241   \verb,morphism, informs about the difference of the original
  1242   compilation context wrt.\ the one of the actual application later
  1243   on.  The optional $\isarkeyword{identifier}$ specifies theorems that
  1244   represent the logical content of the abstract theory of this
  1245   simproc.
  1246 
  1247   Morphisms and identifiers are only relevant for simprocs that are
  1248   defined within a local target context, e.g.\ in a locale.
  1249 
  1250 \item [$simproc\;add\colon\;name$ and $simproc\;del\colon\;name$] add
  1251   or delete named simprocs to the current Simplifier context.  The
  1252   default is to add a simproc.  Note that $\isarcmd{simproc_setup}$
  1253   already adds the new simproc to the subsequent context.
  1254 
  1255 \end{descr}
  1256 
  1257 \subsubsection{Forward simplification}
  1258 
  1259 \indexisaratt{simplified}
  1260 \begin{matharray}{rcl}
  1261   simplified & : & \isaratt \\
  1262 \end{matharray}
  1263 
  1264 \begin{rail}
  1265   'simplified' opt? thmrefs?
  1266   ;
  1267 
  1268   opt: '(' (noasm | noasmsimp | noasmuse) ')'
  1269   ;
  1270 \end{rail}
  1271 
  1272 \begin{descr}
  1273   
  1274 \item [$simplified~\vec a$] causes a theorem to be simplified, either by
  1275   exactly the specified rules $\vec a$, or the implicit Simplifier context if
  1276   no arguments are given.  The result is fully simplified by default,
  1277   including assumptions and conclusion; the options $no_asm$ etc.\ tune the
  1278   Simplifier in the same way as the for the $simp$ method.
  1279 
  1280   Note that forward simplification restricts the simplifier to its most basic
  1281   operation of term rewriting; solver and looper tactics \cite{isabelle-ref}
  1282   are \emph{not} involved here.  The $simplified$ attribute should be only
  1283   rarely required under normal circumstances.
  1284 
  1285 \end{descr}
  1286 
  1287 
  1288 \subsubsection{Low-level equational reasoning}
  1289 
  1290 \indexisarmeth{subst}\indexisarmeth{hypsubst}\indexisarmeth{split}
  1291 \begin{matharray}{rcl}
  1292   subst^* & : & \isarmeth \\
  1293   hypsubst^* & : & \isarmeth \\
  1294   split^* & : & \isarmeth \\
  1295 \end{matharray}
  1296 
  1297 \begin{rail}
  1298   'subst' ('(' 'asm' ')')? ('(' (nat+) ')')? thmref
  1299   ;
  1300   'split' ('(' 'asm' ')')? thmrefs
  1301   ;
  1302 \end{rail}
  1303 
  1304 These methods provide low-level facilities for equational reasoning that are
  1305 intended for specialized applications only.  Normally, single step
  1306 calculations would be performed in a structured text (see also
  1307 \S\ref{sec:calculation}), while the Simplifier methods provide the canonical
  1308 way for automated normalization (see \S\ref{sec:simplifier}).
  1309 
  1310 \begin{descr}
  1311 
  1312 \item [$subst~eq$] performs a single substitution step using rule $eq$, which
  1313   may be either a meta or object equality.
  1314 
  1315 \item [$subst~(asm)~eq$] substitutes in an assumption.
  1316 
  1317 \item [$subst~(i \dots j)~eq$] performs several substitutions in the
  1318 conclusion. The numbers $i$ to $j$ indicate the positions to substitute at.
  1319 Positions are ordered from the top of the term tree moving down from left to
  1320 right. For example, in $(a+b)+(c+d)$ there are three positions where
  1321 commutativity of $+$ is applicable: 1 refers to the whole term, 2 to $a+b$
  1322 and 3 to $c+d$. If the positions in the list $(i \dots j)$ are
  1323 non-overlapping (e.g. $(2~3)$ in $(a+b)+(c+d)$) you may assume all
  1324 substitutions are performed simultaneously. Otherwise the behaviour of
  1325 $subst$ is not specified.
  1326 
  1327 \item [$subst~(asm)~(i \dots j)~eq$] performs the substitutions in the
  1328 assumptions. Positions $1 \dots i@1$ refer
  1329 to assumption 1, positions $i@1+1 \dots i@2$ to assumption 2, and so on.
  1330 
  1331 \item [$hypsubst$] performs substitution using some assumption; this only
  1332   works for equations of the form $x = t$ where $x$ is a free or bound
  1333   variable.
  1334 
  1335 \item [$split~\vec a$] performs single-step case splitting using rules $thms$.
  1336   By default, splitting is performed in the conclusion of a goal; the $asm$
  1337   option indicates to operate on assumptions instead.
  1338   
  1339   Note that the $simp$ method already involves repeated application of split
  1340   rules as declared in the current context.
  1341 \end{descr}
  1342 
  1343 
  1344 \subsection{The Classical Reasoner}\label{sec:classical}
  1345 
  1346 \subsubsection{Basic methods}
  1347 
  1348 \indexisarmeth{rule}\indexisarmeth{default}\indexisarmeth{contradiction}
  1349 \indexisarmeth{intro}\indexisarmeth{elim}
  1350 \begin{matharray}{rcl}
  1351   rule & : & \isarmeth \\
  1352   contradiction & : & \isarmeth \\
  1353   intro & : & \isarmeth \\
  1354   elim & : & \isarmeth \\
  1355 \end{matharray}
  1356 
  1357 \begin{rail}
  1358   ('rule' | 'intro' | 'elim') thmrefs?
  1359   ;
  1360 \end{rail}
  1361 
  1362 \begin{descr}
  1363 
  1364 \item [$rule$] as offered by the classical reasoner is a refinement over the
  1365   primitive one (see \S\ref{sec:pure-meth-att}).  Both versions essentially
  1366   work the same, but the classical version observes the classical rule context
  1367   in addition to that of Isabelle/Pure.
  1368 
  1369   Common object logics (HOL, ZF, etc.) declare a rich collection of classical
  1370   rules (even if these would qualify as intuitionistic ones), but only few
  1371   declarations to the rule context of Isabelle/Pure
  1372   (\S\ref{sec:pure-meth-att}).
  1373 
  1374 \item [$contradiction$] solves some goal by contradiction, deriving any result
  1375   from both $\lnot A$ and $A$.  Chained facts, which are guaranteed to
  1376   participate, may appear in either order.
  1377 
  1378 \item [$intro$ and $elim$] repeatedly refine some goal by intro- or
  1379   elim-resolution, after having inserted any chained facts.  Exactly the rules
  1380   given as arguments are taken into account; this allows fine-tuned
  1381   decomposition of a proof problem, in contrast to common automated tools.
  1382 
  1383 \end{descr}
  1384 
  1385 
  1386 \subsubsection{Automated methods}
  1387 
  1388 \indexisarmeth{blast}\indexisarmeth{fast}\indexisarmeth{slow}
  1389 \indexisarmeth{best}\indexisarmeth{safe}\indexisarmeth{clarify}
  1390 \begin{matharray}{rcl}
  1391   blast & : & \isarmeth \\
  1392   fast & : & \isarmeth \\
  1393   slow & : & \isarmeth \\
  1394   best & : & \isarmeth \\
  1395   safe & : & \isarmeth \\
  1396   clarify & : & \isarmeth \\
  1397 \end{matharray}
  1398 
  1399 \indexouternonterm{clamod}
  1400 \begin{rail}
  1401   'blast' ('!' ?) nat? (clamod *)
  1402   ;
  1403   ('fast' | 'slow' | 'best' | 'safe' | 'clarify') ('!' ?) (clamod *)
  1404   ;
  1405 
  1406   clamod: (('intro' | 'elim' | 'dest') ('!' | () | '?') | 'del') ':' thmrefs
  1407   ;
  1408 \end{rail}
  1409 
  1410 \begin{descr}
  1411 \item [$blast$] refers to the classical tableau prover (see \texttt{blast_tac}
  1412   in \cite[\S11]{isabelle-ref}).  The optional argument specifies a
  1413   user-supplied search bound (default 20).
  1414 \item [$fast$, $slow$, $best$, $safe$, and $clarify$] refer to the generic
  1415   classical reasoner.  See \texttt{fast_tac}, \texttt{slow_tac},
  1416   \texttt{best_tac}, \texttt{safe_tac}, and \texttt{clarify_tac} in
  1417   \cite[\S11]{isabelle-ref} for more information.
  1418 \end{descr}
  1419 
  1420 Any of the above methods support additional modifiers of the context of
  1421 classical rules.  Their semantics is analogous to the attributes given before.
  1422 Facts provided by forward chaining are inserted into the goal before
  1423 commencing proof search.  The ``!''~argument causes the full context of
  1424 assumptions to be included as well.
  1425 
  1426 
  1427 \subsubsection{Combined automated methods}\label{sec:clasimp}
  1428 
  1429 \indexisarmeth{auto}\indexisarmeth{force}\indexisarmeth{clarsimp}
  1430 \indexisarmeth{fastsimp}\indexisarmeth{slowsimp}\indexisarmeth{bestsimp}
  1431 \begin{matharray}{rcl}
  1432   auto & : & \isarmeth \\
  1433   force & : & \isarmeth \\
  1434   clarsimp & : & \isarmeth \\
  1435   fastsimp & : & \isarmeth \\
  1436   slowsimp & : & \isarmeth \\
  1437   bestsimp & : & \isarmeth \\
  1438 \end{matharray}
  1439 
  1440 \indexouternonterm{clasimpmod}
  1441 \begin{rail}
  1442   'auto' '!'? (nat nat)? (clasimpmod *)
  1443   ;
  1444   ('force' | 'clarsimp' | 'fastsimp' | 'slowsimp' | 'bestsimp') '!'? (clasimpmod *)
  1445   ;
  1446 
  1447   clasimpmod: ('simp' (() | 'add' | 'del' | 'only') |
  1448     ('cong' | 'split') (() | 'add' | 'del') |
  1449     'iff' (((() | 'add') '?'?) | 'del') |
  1450     (('intro' | 'elim' | 'dest') ('!' | () | '?') | 'del')) ':' thmrefs
  1451 \end{rail}
  1452 
  1453 \begin{descr}
  1454 \item [$auto$, $force$, $clarsimp$, $fastsimp$, $slowsimp$, and $bestsimp$]
  1455   provide access to Isabelle's combined simplification and classical reasoning
  1456   tactics.  These correspond to \texttt{auto_tac}, \texttt{force_tac},
  1457   \texttt{clarsimp_tac}, and Classical Reasoner tactics with the Simplifier
  1458   added as wrapper, see \cite[\S11]{isabelle-ref} for more information.  The
  1459   modifier arguments correspond to those given in \S\ref{sec:simplifier} and
  1460   \S\ref{sec:classical}.  Just note that the ones related to the Simplifier
  1461   are prefixed by \railtterm{simp} here.
  1462 
  1463   Facts provided by forward chaining are inserted into the goal before doing
  1464   the search.  The ``!''~argument causes the full context of assumptions to be
  1465   included as well.
  1466 \end{descr}
  1467 
  1468 
  1469 \subsubsection{Declaring rules}
  1470 
  1471 \indexisarcmd{print-claset}
  1472 \indexisaratt{intro}\indexisaratt{elim}\indexisaratt{dest}
  1473 \indexisaratt{iff}\indexisaratt{rule}
  1474 \begin{matharray}{rcl}
  1475   \isarcmd{print_claset}^* & : & \isarkeep{theory~|~proof} \\
  1476   intro & : & \isaratt \\
  1477   elim & : & \isaratt \\
  1478   dest & : & \isaratt \\
  1479   rule & : & \isaratt \\
  1480   iff & : & \isaratt \\
  1481 \end{matharray}
  1482 
  1483 \begin{rail}
  1484   ('intro' | 'elim' | 'dest') ('!' | () | '?') nat?
  1485   ;
  1486   'rule' 'del'
  1487   ;
  1488   'iff' (((() | 'add') '?'?) | 'del')
  1489   ;
  1490 \end{rail}
  1491 
  1492 \begin{descr}
  1493 
  1494 \item [$\isarcmd{print_claset}$] prints the collection of rules declared to
  1495   the Classical Reasoner, which is also known as ``claset'' internally
  1496   \cite{isabelle-ref}.  This is a diagnostic command; $undo$ does not apply.
  1497   
  1498 \item [$intro$, $elim$, and $dest$] declare introduction, elimination, and
  1499   destruction rules, respectively.  By default, rules are considered as
  1500   \emph{unsafe} (i.e.\ not applied blindly without backtracking), while a
  1501   single ``!'' classifies as \emph{safe}.  Rule declarations marked by ``?''
  1502   coincide with those of Isabelle/Pure, cf.\ \S\ref{sec:pure-meth-att} (i.e.\ 
  1503   are only applied in single steps of the $rule$ method).  The optional
  1504   natural number specifies an explicit weight argument, which is ignored by
  1505   automated tools, but determines the search order of single rule steps.
  1506 
  1507 \item [$rule~del$] deletes introduction, elimination, or destruction rules from
  1508   the context.
  1509 
  1510 \item [$iff$] declares logical equivalences to the Simplifier and the
  1511   Classical reasoner at the same time.  Non-conditional rules result in a
  1512   ``safe'' introduction and elimination pair; conditional ones are considered
  1513   ``unsafe''.  Rules with negative conclusion are automatically inverted
  1514   (using $\lnot$ elimination internally).
  1515 
  1516   The ``?'' version of $iff$ declares rules to the Isabelle/Pure context only,
  1517   and omits the Simplifier declaration.
  1518 
  1519 \end{descr}
  1520 
  1521 
  1522 \subsubsection{Classical operations}
  1523 
  1524 \indexisaratt{swapped}
  1525 
  1526 \begin{matharray}{rcl}
  1527   swapped & : & \isaratt \\
  1528 \end{matharray}
  1529 
  1530 \begin{descr}
  1531 
  1532 \item [$swapped$] turns an introduction rule into an elimination, by resolving
  1533   with the classical swap principle $(\lnot B \Imp A) \Imp (\lnot A \Imp B)$.
  1534 
  1535 \end{descr}
  1536 
  1537 
  1538 \subsection{Proof by cases and induction}\label{sec:cases-induct}
  1539 
  1540 \subsubsection{Rule contexts}
  1541 
  1542 \indexisarcmd{case}\indexisarcmd{print-cases}
  1543 \indexisaratt{case-names}\indexisaratt{case-conclusion}
  1544 \indexisaratt{params}\indexisaratt{consumes}
  1545 \begin{matharray}{rcl}
  1546   \isarcmd{case} & : & \isartrans{proof(state)}{proof(state)} \\
  1547   \isarcmd{print_cases}^* & : & \isarkeep{proof} \\
  1548   case_names & : & \isaratt \\
  1549   case_conclusion & : & \isaratt \\
  1550   params & : & \isaratt \\
  1551   consumes & : & \isaratt \\
  1552 \end{matharray}
  1553 
  1554 The puristic way to build up Isar proof contexts is by explicit language
  1555 elements like $\FIXNAME$, $\ASSUMENAME$, $\LET$ (see
  1556 \S\ref{sec:proof-context}).  This is adequate for plain natural deduction, but
  1557 easily becomes unwieldy in concrete verification tasks, which typically
  1558 involve big induction rules with several cases.
  1559 
  1560 The $\CASENAME$ command provides a shorthand to refer to a local context
  1561 symbolically: certain proof methods provide an environment of named ``cases''
  1562 of the form $c\colon \vec x, \vec \phi$; the effect of ``$\CASE{c}$'' is then
  1563 equivalent to ``$\FIX{\vec x}~\ASSUME{c}{\vec\phi}$''.  Term bindings may be
  1564 covered as well, notably $\Var{case}$ for the main conclusion.
  1565 
  1566 By default, the ``terminology'' $\vec x$ of a case value is marked as hidden,
  1567 i.e.\ there is no way to refer to such parameters in the subsequent proof
  1568 text.  After all, original rule parameters stem from somewhere outside of the
  1569 current proof text.  By using the explicit form ``$\CASE{(c~\vec y)}$''
  1570 instead, the proof author is able to chose local names that fit nicely into
  1571 the current context.
  1572 
  1573 \medskip
  1574 
  1575 It is important to note that proper use of $\CASENAME$ does not provide means
  1576 to peek at the current goal state, which is not directly observable in Isar!
  1577 Nonetheless, goal refinement commands do provide named cases $goal@i$ for each
  1578 subgoal $i = 1, \dots, n$ of the resulting goal state.  Using this feature
  1579 requires great care, because some bits of the internal tactical machinery
  1580 intrude the proof text.  In particular, parameter names stemming from the
  1581 left-over of automated reasoning tools are usually quite unpredictable.
  1582 
  1583 Under normal circumstances, the text of cases emerge from standard elimination
  1584 or induction rules, which in turn are derived from previous theory
  1585 specifications in a canonical way (say from $\isarkeyword{inductive}$
  1586 definitions).
  1587 
  1588 \medskip Proper cases are only available if both the proof method and the
  1589 rules involved support this.  By using appropriate attributes, case names,
  1590 conclusions, and parameters may be also declared by hand.  Thus variant
  1591 versions of rules that have been derived manually become ready to use in
  1592 advanced case analysis later.
  1593 
  1594 \begin{rail}
  1595   'case' (caseref | '(' caseref ((name | underscore) +) ')')
  1596   ;
  1597   caseref: nameref attributes?
  1598   ;
  1599 
  1600   'case\_names' (name +)
  1601   ;
  1602   'case\_conclusion' name (name *)
  1603   ;
  1604   'params' ((name *) + 'and')
  1605   ;
  1606   'consumes' nat?
  1607   ;
  1608 \end{rail}
  1609 
  1610 \begin{descr}
  1611   
  1612 \item [$\CASE{(c~\vec x)}$] invokes a named local context $c\colon \vec x,
  1613   \vec \phi$, as provided by an appropriate proof method (such as $cases$ and
  1614   $induct$).  The command ``$\CASE{(c~\vec x)}$'' abbreviates ``$\FIX{\vec
  1615     x}~\ASSUME{c}{\vec\phi}$''.
  1616 
  1617 \item [$\isarkeyword{print_cases}$] prints all local contexts of the current
  1618   state, using Isar proof language notation.  This is a diagnostic command;
  1619   $undo$ does not apply.
  1620   
  1621 \item [$case_names~\vec c$] declares names for the local contexts of premises
  1622   of a theorem; $\vec c$ refers to the \emph{suffix} of the list of premises.
  1623   
  1624 \item [$case_conclusion~c~\vec d$] declares names for the conclusions of a
  1625   named premise $c$; here $\vec d$ refers to the prefix of arguments of a
  1626   logical formula built by nesting a binary connective (e.g.\ $\lor$).
  1627   
  1628   Note that proof methods such as $induct$ and $coinduct$ already provide a
  1629   default name for the conclusion as a whole.  The need to name subformulas
  1630   only arises with cases that split into several sub-cases, as in common
  1631   co-induction rules.
  1632 
  1633 \item [$params~\vec p@1 \dots \vec p@n$] renames the innermost parameters of
  1634   premises $1, \dots, n$ of some theorem.  An empty list of names may be given
  1635   to skip positions, leaving the present parameters unchanged.
  1636   
  1637   Note that the default usage of case rules does \emph{not} directly expose
  1638   parameters to the proof context.
  1639   
  1640 \item [$consumes~n$] declares the number of ``major premises'' of a rule,
  1641   i.e.\ the number of facts to be consumed when it is applied by an
  1642   appropriate proof method.  The default value of $consumes$ is $n = 1$, which
  1643   is appropriate for the usual kind of cases and induction rules for inductive
  1644   sets (cf.\ \S\ref{sec:hol-inductive}).  Rules without any $consumes$
  1645   declaration given are treated as if $consumes~0$ had been specified.
  1646   
  1647   Note that explicit $consumes$ declarations are only rarely needed; this is
  1648   already taken care of automatically by the higher-level $cases$, $induct$,
  1649   and $coinduct$ declarations.
  1650 
  1651 \end{descr}
  1652 
  1653 
  1654 \subsubsection{Proof methods}
  1655 
  1656 \indexisarmeth{cases}\indexisarmeth{induct}\indexisarmeth{coinduct}
  1657 \begin{matharray}{rcl}
  1658   cases & : & \isarmeth \\
  1659   induct & : & \isarmeth \\
  1660   coinduct & : & \isarmeth \\
  1661 \end{matharray}
  1662 
  1663 The $cases$, $induct$, and $coinduct$ methods provide a uniform interface to
  1664 common proof techniques over datatypes, inductive sets, recursive functions
  1665 etc.  The corresponding rules may be specified and instantiated in a casual
  1666 manner.  Furthermore, these methods provide named local contexts that may be
  1667 invoked via the $\CASENAME$ proof command within the subsequent proof text.
  1668 This accommodates compact proof texts even when reasoning about large
  1669 specifications.
  1670 
  1671 The $induct$ method also provides some additional infrastructure in order to
  1672 be applicable to structure statements (either using explicit meta-level
  1673 connectives, or including facts and parameters separately).  This avoids
  1674 cumbersome encoding of ``strengthened'' inductive statements within the
  1675 object-logic.
  1676 
  1677 \begin{rail}
  1678   'cases' open? (insts * 'and') rule?
  1679   ;
  1680   'induct' open? (definsts * 'and') \\ arbitrary? taking? rule?
  1681   ;
  1682   'coinduct' open? insts taking rule?
  1683   ;
  1684 
  1685   open: '(' 'open' ')'
  1686   ;
  1687   rule: ('type' | 'set') ':' (nameref +) | 'rule' ':' (thmref +)
  1688   ;
  1689   definst: name ('==' | equiv) term | inst
  1690   ;
  1691   definsts: ( definst *)
  1692   ;
  1693   arbitrary: 'arbitrary' ':' ((term *) 'and' +)
  1694   ;
  1695   taking: 'taking' ':' insts
  1696   ;
  1697 \end{rail}
  1698 
  1699 \begin{descr}
  1700 
  1701 \item [$cases~insts~R$] applies method $rule$ with an appropriate case
  1702   distinction theorem, instantiated to the subjects $insts$.  Symbolic case
  1703   names are bound according to the rule's local contexts.
  1704 
  1705   The rule is determined as follows, according to the facts and arguments
  1706   passed to the $cases$ method:
  1707   \begin{matharray}{llll}
  1708     \Text{facts}    &       & \Text{arguments} & \Text{rule} \\\hline
  1709                     & cases &           & \Text{classical case split} \\
  1710                     & cases & t         & \Text{datatype exhaustion (type of $t$)} \\
  1711     \edrv a \in A   & cases & \dots     & \Text{inductive set elimination (of $A$)} \\
  1712     \dots           & cases & \dots ~ R & \Text{explicit rule $R$} \\
  1713   \end{matharray}
  1714 
  1715   Several instantiations may be given, referring to the \emph{suffix} of
  1716   premises of the case rule; within each premise, the \emph{prefix} of
  1717   variables is instantiated.  In most situations, only a single term needs to
  1718   be specified; this refers to the first variable of the last premise (it is
  1719   usually the same for all cases).
  1720 
  1721   The ``$(open)$'' option causes the parameters of the new local contexts to
  1722   be exposed to the current proof context.  Thus local variables stemming from
  1723   distant parts of the theory development may be introduced in an implicit
  1724   manner, which can be quite confusing to the reader.  Furthermore, this
  1725   option may cause unwanted hiding of existing local variables, resulting in
  1726   less robust proof texts.
  1727 
  1728 \item [$induct~insts~R$] is analogous to the $cases$ method, but refers to
  1729   induction rules, which are determined as follows:
  1730   \begin{matharray}{llll}
  1731     \Text{facts}    &        & \Text{arguments} & \Text{rule} \\\hline
  1732                     & induct & P ~ x ~ \dots & \Text{datatype induction (type of $x$)} \\
  1733     \edrv x \in A   & induct & \dots         & \Text{set induction (of $A$)} \\
  1734     \dots           & induct & \dots ~ R     & \Text{explicit rule $R$} \\
  1735   \end{matharray}
  1736   
  1737   Several instantiations may be given, each referring to some part of
  1738   a mutual inductive definition or datatype --- only related partial
  1739   induction rules may be used together, though.  Any of the lists of
  1740   terms $P, x, \dots$ refers to the \emph{suffix} of variables present
  1741   in the induction rule.  This enables the writer to specify only
  1742   induction variables, or both predicates and variables, for example.
  1743   
  1744   Instantiations may be definitional: equations $x \equiv t$ introduce local
  1745   definitions, which are inserted into the claim and discharged after applying
  1746   the induction rule.  Equalities reappear in the inductive cases, but have
  1747   been transformed according to the induction principle being involved here.
  1748   In order to achieve practically useful induction hypotheses, some variables
  1749   occurring in $t$ need to be fixed (see below).
  1750   
  1751   The optional ``$arbitrary\colon \vec x$'' specification generalizes
  1752   variables $\vec x$ of the original goal before applying induction.  Thus
  1753   induction hypotheses may become sufficiently general to get the proof
  1754   through.  Together with definitional instantiations, one may effectively
  1755   perform induction over expressions of a certain structure.
  1756   
  1757   The optional ``$taking\colon \vec t$'' specification provides additional
  1758   instantiations of a prefix of pending variables in the rule.  Such schematic
  1759   induction rules rarely occur in practice, though.
  1760 
  1761   The ``$(open)$'' option works the same way as for $cases$.
  1762 
  1763 \item [$coinduct~inst~R$] is analogous to the $induct$ method, but refers to
  1764   coinduction rules, which are determined as follows:
  1765   \begin{matharray}{llll}
  1766     \Text{goal}     &          & \Text{arguments} & \Text{rule} \\\hline
  1767                     & coinduct & x ~ \dots        & \Text{type coinduction (type of $x$)} \\
  1768     x \in A         & coinduct & \dots            & \Text{set coinduction (of $A$)} \\
  1769     \dots           & coinduct & \dots ~ R        & \Text{explicit rule $R$} \\
  1770   \end{matharray}
  1771   
  1772   Coinduction is the dual of induction.  Induction essentially eliminates $x
  1773   \in A$ towards a generic result $P ~ x$, while coinduction introduces $x \in
  1774   A$ starting with $x \in B$, for a suitable ``bisimulation'' $B$.  The cases
  1775   of a coinduct rule are typically named after the sets being covered, while
  1776   the conclusions consist of several alternatives being named after the
  1777   individual destructor patterns.
  1778   
  1779   The given instantiation refers to the \emph{prefix} of variables occurring
  1780   in the rule's conclusion.  An additional ``$taking: \vec t$'' specification
  1781   may be required in order to specify the bisimulation to be used in the
  1782   coinduction step.
  1783 
  1784   The ``$(open)$'' option works the same way as for $cases$.
  1785 
  1786 \end{descr}
  1787 
  1788 Above methods produce named local contexts, as determined by the instantiated
  1789 rule as given in the text.  Beyond that, the $induct$ and $coinduct$ methods
  1790 guess further instantiations from the goal specification itself.  Any
  1791 persisting unresolved schematic variables of the resulting rule will render
  1792 the the corresponding case invalid.  The term binding
  1793 $\Var{case}$\indexisarvar{case} for the conclusion will be provided with each
  1794 case, provided that term is fully specified.
  1795 
  1796 The $\isarkeyword{print_cases}$ command prints all named cases present in the
  1797 current proof state.
  1798 
  1799 \medskip
  1800 
  1801 Despite the additional infrastructure, both $cases$ and $coinduct$ merely
  1802 apply a certain rule, after instantiation, while conforming due to the usual
  1803 way of monotonic natural deduction: the context of a structured statement
  1804 $\All{\vec x} \vec\phi \Imp \dots$ reappears unchanged after the case split.
  1805 
  1806 The $induct$ method is significantly different in this respect: the meta-level
  1807 structure is passed through the ``recursive'' course involved in the
  1808 induction.  Thus the original statement is basically replaced by separate
  1809 copies, corresponding to the induction hypotheses and conclusion; the original
  1810 goal context is no longer available.  Thus local assumptions, fixed parameters
  1811 and definitions effectively participate in the inductive rephrasing of the
  1812 original statement.
  1813 
  1814 In induction proofs, local assumptions introduced by cases are split into two
  1815 different kinds: $hyps$ stemming from the rule and $prems$ from the goal
  1816 statement.  This is reflected in the extracted cases accordingly, so invoking
  1817 ``$\isarcmd{case}~c$'' will provide separate facts $c\mathord.hyps$ and
  1818 $c\mathord.prems$, as well as fact $c$ to hold the all-inclusive list.
  1819 
  1820 \medskip
  1821 
  1822 Facts presented to either method are consumed according to the number of
  1823 ``major premises'' of the rule involved, which is usually $0$ for plain cases
  1824 and induction rules of datatypes etc.\ and $1$ for rules of inductive sets and
  1825 the like.  The remaining facts are inserted into the goal verbatim before the
  1826 actual $cases$, $induct$, or $coinduct$ rule is applied.
  1827 
  1828 
  1829 \subsubsection{Declaring rules}
  1830 
  1831 \indexisarcmd{print-induct-rules}\indexisaratt{cases}\indexisaratt{induct}\indexisaratt{coinduct}
  1832 \begin{matharray}{rcl}
  1833   \isarcmd{print_induct_rules}^* & : & \isarkeep{theory~|~proof} \\
  1834   cases & : & \isaratt \\
  1835   induct & : & \isaratt \\
  1836   coinduct & : & \isaratt \\
  1837 \end{matharray}
  1838 
  1839 \begin{rail}
  1840   'cases' spec
  1841   ;
  1842   'induct' spec
  1843   ;
  1844   'coinduct' spec
  1845   ;
  1846 
  1847   spec: ('type' | 'set') ':' nameref
  1848   ;
  1849 \end{rail}
  1850 
  1851 \begin{descr}
  1852 
  1853 \item [$\isarkeyword{print_induct_rules}$] prints cases and induct rules for
  1854   sets and types of the current context.
  1855   
  1856 \item [$cases$, $induct$, and $coinduct$] (as attributes) augment the
  1857   corresponding context of rules for reasoning about (co)inductive sets and
  1858   types, using the corresponding methods of the same name.  Certain
  1859   definitional packages of object-logics usually declare emerging cases and
  1860   induction rules as expected, so users rarely need to intervene.
  1861   
  1862   Manual rule declarations usually refer to the $case_names$ and $params$
  1863   attributes to adjust names of cases and parameters of a rule; the $consumes$
  1864   declaration is taken care of automatically: $consumes~0$ is specified for
  1865   ``type'' rules and $consumes~1$ for ``set'' rules.
  1866 
  1867 \end{descr}
  1868 
  1869 %%% Local Variables:
  1870 %%% mode: latex
  1871 %%% TeX-master: "isar-ref"
  1872 %%% End: