New module system

This commit is contained in:
Iavor Diatchki 2022-06-13 15:56:15 -07:00
parent 7ac76ece76
commit 6ab14706af
226 changed files with 24028 additions and 21929 deletions

View File

@ -26,7 +26,6 @@ import qualified Cryptol.ModuleSystem.Base as M
import qualified Cryptol.ModuleSystem.Env as M
import qualified Cryptol.ModuleSystem.Monad as M
import qualified Cryptol.ModuleSystem.NamingEnv as M
import Cryptol.ModuleSystem.Interface (noIfaceParams)
import qualified Cryptol.Parser as P
import qualified Cryptol.Parser.AST as P
@ -130,7 +129,7 @@ tc cd name path =
, M.tcLinter = M.moduleLinter (P.thing (P.mName scm))
, M.tcPrims = prims
}
M.typecheck act scm noIfaceParams tcEnv
M.typecheck act scm mempty tcEnv
ceval :: String -> String -> FilePath -> T.Text -> Benchmark
ceval cd name path expr =

View File

@ -47,7 +47,7 @@ import qualified Cryptol.ModuleSystem.Base as Base
import qualified Cryptol.ModuleSystem.Renamer as R
import Cryptol.ModuleSystem.Name
(Name, mkDeclared, NameSource( UserName ), liftSupply, nameIdent)
import Cryptol.ModuleSystem.NamingEnv (singletonE, shadowing, namespaceMap)
import Cryptol.ModuleSystem.NamingEnv (singletonNS, shadowing, namespaceMap)
import qualified Cryptol.Parser as CP
import qualified Cryptol.Parser.AST as CP
@ -649,7 +649,7 @@ bindValToFreshName nameBase ty val = do
liftModuleCmd (evalDecls [TC.NonRecursive decl])
modifyModuleEnv $ \me ->
let denv = meDynEnv me
in me {meDynEnv = denv { deNames = singletonE (CP.UnQual (mkIdent txt)) name `shadowing` deNames denv }}
in me {meDynEnv = denv { deNames = singletonNS NSValue (CP.UnQual (mkIdent txt)) name `shadowing` deNames denv }}
return $ Just txt
where
genFresh :: CryptolCommand (Text, Name)
@ -660,7 +660,7 @@ bindValToFreshName nameBase ty val = do
mpath = TopModule interactiveName
name <- liftSupply (mkDeclared NSValue mpath UserName ident Nothing emptyRange)
pure (txt, name)
where nextNewName :: Map CP.PName [Name] -> Int -> Text
where nextNewName :: Map CP.PName a -> Int -> Text
nextNewName ns n =
let txt = "CryptolServer'" <> nameBase <> (T.pack $ show n)
pname = CP.UnQual (mkIdent txt)

View File

@ -15,6 +15,7 @@ import Data.Aeson ((.=))
import qualified Data.Map as Map
import Data.Map (Map)
import Data.Text (unpack)
import Data.Maybe(maybeToList)
import Data.Typeable (Proxy(..), typeRep)
import Cryptol.Parser.Name (PName(..))
@ -22,7 +23,8 @@ import Cryptol.ModuleSystem.Env (ModContext(..), ModuleEnv(..), DynamicEnv(..),
import Cryptol.ModuleSystem.Interface (IfaceDecl(..), IfaceDecls(..))
import Cryptol.ModuleSystem.Name (Name)
import Cryptol.ModuleSystem.NamingEnv
(NamingEnv, namespaceMap, lookupValNames, shadowing)
(NamingEnv, namespaceMap, lookupNS, shadowing)
import Cryptol.ModuleSystem.Names(namesToList)
import Cryptol.TypeCheck.Type (Schema(..))
import Cryptol.Utils.PP (pp)
import Cryptol.Utils.Ident(Namespace(..))
@ -71,7 +73,7 @@ getInfo rnEnv info n' =
let ty = ifDeclSig i
nameDocs = ifDeclDoc i
in NameInfo (show (pp n')) (show (pp ty)) ty (unpack <$> nameDocs)
| n <- lookupValNames n' rnEnv
| ns <- maybeToList (lookupNS NSValue n' rnEnv), n <- namesToList ns
]
data NameInfo =

View File

@ -63,6 +63,7 @@ library
monadLib >= 3.7.2,
parameterized-utils >= 2.0.2,
prettyprinter >= 1.7.0,
pretty-show,
process >= 1.2,
sbv >= 8.10 && < 9.1,
simple-smt >= 0.9.7,
@ -116,10 +117,13 @@ library
Cryptol.ModuleSystem.Interface,
Cryptol.ModuleSystem.Monad,
Cryptol.ModuleSystem.Name,
Cryptol.ModuleSystem.Names,
Cryptol.ModuleSystem.NamingEnv,
Cryptol.ModuleSystem.Binds
Cryptol.ModuleSystem.Exports,
Cryptol.ModuleSystem.InstantiateModule,
Cryptol.ModuleSystem.Renamer,
Cryptol.ModuleSystem.Renamer.Imports,
Cryptol.ModuleSystem.Renamer.ImplicitImports,
Cryptol.ModuleSystem.Renamer.Monad,
Cryptol.ModuleSystem.Renamer.Error,
@ -132,7 +136,6 @@ library
Cryptol.TypeCheck.Parseable,
Cryptol.TypeCheck.Monad,
Cryptol.TypeCheck.Infer,
Cryptol.TypeCheck.CheckModuleInstance,
Cryptol.TypeCheck.InferTypes,
Cryptol.TypeCheck.Interface,
Cryptol.TypeCheck.Error,
@ -147,6 +150,8 @@ library
Cryptol.TypeCheck.TypeMap,
Cryptol.TypeCheck.TypeOf,
Cryptol.TypeCheck.Sanity,
Cryptol.TypeCheck.Module,
Cryptol.TypeCheck.ModuleInstance,
Cryptol.TypeCheck.Solver.Types,
Cryptol.TypeCheck.Solver.SMT,
@ -162,9 +167,9 @@ library
Cryptol.Transform.MonoValues,
Cryptol.Transform.Specialize,
Cryptol.Transform.AddModParams,
Cryptol.IR.FreeVars,
Cryptol.IR.TraverseNames,
Cryptol.Backend,
Cryptol.Backend.Arch,
@ -199,6 +204,7 @@ library
Cryptol.Symbolic.What4,
Cryptol.REPL.Command,
Cryptol.REPL.Help,
Cryptol.REPL.Browse,
Cryptol.REPL.Monad,
Cryptol.REPL.Trie

283
docs/RefMan/BasicSyntax.rst Normal file
View File

@ -0,0 +1,283 @@
Basic Syntax
============
Declarations
------------
.. code-block:: cryptol
f x = x + y + z
Type Signatures
---------------
.. code-block:: cryptol
f,g : {a,b} (fin a) => [a] b
Layout
------
Groups of declarations are organized based on indentation.
Declarations with the same indentation belong to the same group.
Lines of text that are indented more than the beginning of a
declaration belong to that declaration, while lines of text that are
indented less terminate a group of declarations. Consider, for example,
the following Cryptol declarations:
.. code-block:: cryptol
f x = x + y + z
where
y = x * x
z = x + y
g y = y
This group has two declarations, one for `f` and one for `g`. All the
lines between `f` and `g` that are indented more than `f` belong to
`f`. The same principle applies to the declarations in the ``where`` block
of `f`, which defines two more local names, `y` and `z`.
Comments
--------
Cryptol supports block comments, which start with ``/*`` and end with
``*/``, and line comments, which start with ``//`` and terminate at the
end of the line. Block comments may be nested arbitrarily.
.. code-block:: cryptol
/* This is a block comment */
// This is a line comment
/* This is a /* Nested */ block comment */
.. todo::
Document ``/** */``
Identifiers
-----------
Cryptol identifiers consist of one or more characters. The first
character must be either an English letter or underscore (``_``). The
following characters may be an English letter, a decimal digit,
underscore (``_``), or a prime (``'``). Some identifiers have special
meaning in the language, so they may not be used in programmer-defined
names (see `Keywords and Built-in Operators`_).
.. code-block:: cryptol
:caption: Examples of identifiers
name name1 name' longer_name
Name Name2 Name'' longerName
Keywords and Built-in Operators
-------------------------------
The following identifiers have special meanings in Cryptol, and may
not be used for programmer defined names:
.. The table below can be generated by running `chop.hs` on this list:
else
extern
if
private
include
module
submodule
interface
newtype
pragma
property
then
type
where
let
import
as
hiding
infixl
infixr
infix
primitive
parameter
constraint
down
by
.. _Keywords:
.. code-block:: none
:caption: Keywords
as extern include interface parameter property where
by hiding infix let pragma submodule else
constraint if infixl module primitive then
down import infixr newtype private type
The following table contains Cryptol's operators and their
associativity with lowest precedence operators first, and highest
precedence last.
.. table:: Operator precedences
+-----------------------------------------+-----------------+
| Operator | Associativity |
+=========================================+=================+
| ``==>`` | right |
+-----------------------------------------+-----------------+
| ``\/`` | right |
+-----------------------------------------+-----------------+
| ``/\`` | right |
+-----------------------------------------+-----------------+
| ``==`` ``!=`` ``===`` ``!==`` | not associative |
+-----------------------------------------+-----------------+
| ``>`` ``<`` ``<=`` ``>=`` | not associative |
| ``<$`` ``>$`` ``<=$`` ``>=$`` | |
+-----------------------------------------+-----------------+
| ``||`` | right |
+-----------------------------------------+-----------------+
| ``^`` | left |
+-----------------------------------------+-----------------+
| ``&&`` | right |
+-----------------------------------------+-----------------+
| ``#`` | right |
+-----------------------------------------+-----------------+
| ``>>`` ``<<`` ``>>>`` ``<<<`` ``>>$`` | left |
+-----------------------------------------+-----------------+
| ``+`` ``-`` | left |
+-----------------------------------------+-----------------+
| ``*`` ``/`` ``%`` ``/$`` ``%$`` | left |
+-----------------------------------------+-----------------+
| ``^^`` | right |
+-----------------------------------------+-----------------+
| ``@`` ``@@`` ``!`` ``!!`` | left |
+-----------------------------------------+-----------------+
| (unary) ``-`` ``~`` | right |
+-----------------------------------------+-----------------+
Built-in Type-level Operators
-----------------------------
Cryptol includes a variety of operators that allow computations on
the numeric types used to specify the sizes of sequences.
.. table:: Type-level operators
+------------+----------------------------------------+
| Operator | Meaning |
+============+========================================+
| ``+`` | Addition |
+------------+----------------------------------------+
| ``-`` | Subtraction |
+------------+----------------------------------------+
| ``*`` | Multiplication |
+------------+----------------------------------------+
| ``/`` | Division |
+------------+----------------------------------------+
| ``/^`` | Ceiling division (``/`` rounded up) |
+------------+----------------------------------------+
| ``%`` | Modulus |
+------------+----------------------------------------+
| ``%^`` | Ceiling modulus (compute padding) |
+------------+----------------------------------------+
| ``^^`` | Exponentiation |
+------------+----------------------------------------+
| ``lg2`` | Ceiling logarithm (base 2) |
+------------+----------------------------------------+
| ``width`` | Bit width (equal to ``lg2(n+1)``) |
+------------+----------------------------------------+
| ``max`` | Maximum |
+------------+----------------------------------------+
| ``min`` | Minimum |
+------------+----------------------------------------+
Numeric Literals
----------------
Numeric literals may be written in binary, octal, decimal, or
hexadecimal notation. The base of a literal is determined by its prefix:
``0b`` for binary, ``0o`` for octal, no special prefix for
decimal, and ``0x`` for hexadecimal.
.. code-block:: cryptol
:caption: Examples of literals
254 // Decimal literal
0254 // Decimal literal
0b11111110 // Binary literal
0o376 // Octal literal
0xFE // Hexadecimal literal
0xfe // Hexadecimal literal
Numeric literals in binary, octal, or hexadecimal notation result in
bit sequences of a fixed length (i.e., they have type ``[n]`` for
some `n`). The length is determined by the base and the number
of digits in the literal. Decimal literals are overloaded, and so the
type is inferred from context in which the literal is used. Examples:
.. code-block:: cryptol
:caption: Literals and their types
0b1010 // : [4], 1 * number of digits
0o1234 // : [12], 3 * number of digits
0x1234 // : [16], 4 * number of digits
10 // : {a}. (Literal 10 a) => a
// a = Integer or [n] where n >= width 10
Numeric literals may also be written as polynomials by writing a polynomial
expression in terms of `x` between an opening ``<|`` and a closing ``|>``.
Numeric literals in polynomial notation result in bit sequences of length
one more than the degree of the polynomial. Examples:
.. code-block:: cryptol
:caption: Polynomial literals
<| x^^6 + x^^4 + x^^2 + x^^1 + 1 |> // : [7], equal to 0b1010111
<| x^^4 + x^^3 + x |> // : [5], equal to 0b11010
Cryptol also supports fractional literals using binary (prefix ``0b``),
octal (prefix ``0o``), decimal (no prefix), and hexadecimal (prefix ``ox``)
digits. A fractional literal must contain a ``.`` and may optionally
have an exponent. The base of the exponent for binary, octal,
and hexadecimal literals is 2 and the exponent is marked using the symbol ``p``.
Decimal fractional literals use exponent base 10, and the symbol ``e``.
Examples:
.. code-block:: cryptol
:caption: Fractional literals
10.2
10.2e3 // 10.2 * 10^3
0x30.1 // 3 * 64 + 1/16
0x30.1p4 // (3 * 64 + 1/16) * 2^4
All fractional literals are overloaded and may be used with types that support
fractional numbers (e.g., ``Rational``, and the ``Float`` family of types).
Some types (e.g. the ``Float`` family) cannot represent all fractional literals
precisely. Such literals are rejected statically when using binary, octal,
or hexadecimal notation. When using decimal notation, the literal is rounded
to the closest representable even number.
All numeric literals may also include ``_``, which has no effect on the
literal value but may be used to improve readability. Here are some examples:
.. code-block:: cryptol
:caption: Using _
0b_0000_0010
0x_FFFF_FFEA

211
docs/RefMan/BasicTypes.rst Normal file
View File

@ -0,0 +1,211 @@
Basic Types
===========
Tuples and Records
------------------
Tuples and records are used for packaging multiple values together.
Tuples are enclosed in parentheses, while records are enclosed in
curly braces. The components of both tuples and records are separated by
commas. The components of tuples are expressions, while the
components of records are a label and a value separated by an equal
sign. Examples:
.. code-block:: cryptol
(1,2,3) // A tuple with 3 component
() // A tuple with no components
{ x = 1, y = 2 } // A record with two fields, `x` and `y`
{} // A record with no fields
The components of tuples are identified by position, while the
components of records are identified by their label, and so the
ordering of record components is not important for most purposes.
Examples:
.. code-block:: cryptol
(1,2) == (1,2) // True
(1,2) == (2,1) // False
{ x = 1, y = 2 } == { x = 1, y = 2 } // True
{ x = 1, y = 2 } == { y = 2, x = 1 } // True
Ordering on tuples and records is defined lexicographically. Tuple
components are compared in the order they appear, whereas record
fields are compared in alphabetical order of field names.
Accessing Fields
~~~~~~~~~~~~~~~~
The components of a record or a tuple may be accessed in two ways: via
pattern matching or by using explicit component selectors. Explicit
component selectors are written as follows:
.. code-block:: cryptol
(15, 20).0 == 15
(15, 20).1 == 20
{ x = 15, y = 20 }.x == 15
Explicit record selectors may be used only if the program contains
sufficient type information to determine the shape of the tuple or
record. For example:
.. code-block:: cryptol
type T = { sign : Bit, number : [15] }
// Valid definition:
// the type of the record is known.
isPositive : T -> Bit
isPositive x = x.sign
// Invalid definition:
// insufficient type information.
badDef x = x.f
The components of a tuple or a record may also be accessed using
pattern matching. Patterns for tuples and records mirror the syntax
for constructing values: tuple patterns use parentheses, while record
patterns use braces. Examples:
.. code-block:: cryptol
getFst (x,_) = x
distance2 { x = xPos, y = yPos } = xPos ^^ 2 + yPos ^^ 2
f p = x + y where
(x, y) = p
Selectors are also lifted through sequence and function types, point-wise,
so that the following equations should hold:
.. code-block:: cryptol
xs.l == [ x.l | x <- xs ] // sequences
f.l == \x -> (f x).l // functions
Thus, if we have a sequence of tuples, ``xs``, then we can quickly obtain a
sequence with only the tuples' first components by writing ``xs.0``.
Similarly, if we have a function, ``f``, that computes a tuple of results,
then we can write ``f.0`` to get a function that computes only the first
entry in the tuple.
This behavior is quite handy when examining complex data at the REPL.
Updating Fields
~~~~~~~~~~~~~~~
The components of a record or a tuple may be updated using the following
notation:
.. code-block:: cryptol
// Example values
r = { x = 15, y = 20 } // a record
t = (True,True) // a tuple
n = { pt = r, size = 100 } // nested record
// Setting fields
{ r | x = 30 } == { x = 30, y = 20 }
{ t | 0 = False } == (False,True)
// Update relative to the old value
{ r | x -> x + 5 } == { x = 20, y = 20 }
// Update a nested field
{ n | pt.x = 10 } == { pt = { x = 10, y = 20 }, size = 100 }
{ n | pt.x -> x + 10 } == { pt = { x = 25, y = 20 }, size = 100 }
Sequences
---------
A sequence is a fixed-length collection of elements of the same type.
The type of a finite sequence of length `n`, with elements of type `a`
is ``[n] a``. Often, a finite sequence of bits, ``[n] Bit``, is called a
*word*. We may abbreviate the type ``[n] Bit`` as ``[n]``. An infinite
sequence with elements of type `a` has type ``[inf] a``, and ``[inf]`` is
an infinite stream of bits.
.. code-block:: cryptol
[e1,e2,e3] // A sequence with three elements
[t1 .. t2] // Enumeration
[t1 .. <t2] // Enumeration (exclusive bound)
[t1 .. t2 by n] // Enumeration (stride)
[t1 .. <t2 by n] // Enumeration (stride, ex. bound)
[t1 .. t2 down by n] // Enumeration (downward stride)
[t1 .. >t2 down by n] // Enumeration (downward stride, ex. bound)
[t1, t2 .. t3] // Enumeration (step by t2 - t1)
[e1 ...] // Infinite sequence starting at e1
[e1, e2 ...] // Infinite sequence stepping by e2-e1
[ e | p11 <- e11, p12 <- e12 // Sequence comprehensions
| p21 <- e21, p22 <- e22 ]
x = generate (\i -> e) // Sequence from generating function
x @ i = e // Sequence with index binding
arr @ i @ j = e // Two-dimensional sequence
Note: the bounds in finite sequences (those with `..`) are type
expressions, while the bounds in infinite sequences are value
expressions.
.. table:: Sequence operations.
+------------------------------+---------------------------------------------+
| Operator | Description |
+==============================+=============================================+
| ``#`` | Sequence concatenation |
+------------------------------+---------------------------------------------+
| ``>>`` ``<<`` | Shift (right, left) |
+------------------------------+---------------------------------------------+
| ``>>>`` ``<<<`` | Rotate (right, left) |
+------------------------------+---------------------------------------------+
| ``>>$`` | Arithmetic right shift (on bitvectors only) |
+------------------------------+---------------------------------------------+
| ``@`` ``!`` | Access elements (front, back) |
+------------------------------+---------------------------------------------+
| ``@@`` ``!!`` | Access sub-sequence (front, back) |
+------------------------------+---------------------------------------------+
| ``update`` ``updateEnd`` | Update the value of a sequence at |
| | a location |
| | (front, back) |
+------------------------------+---------------------------------------------+
| ``updates`` ``updatesEnd`` | Update multiple values of a sequence |
| | (front, back) |
+------------------------------+---------------------------------------------+
There are also lifted pointwise operations.
.. code-block:: cryptol
[p1, p2, p3, p4] // Sequence pattern
p1 # p2 // Split sequence pattern
Functions
---------
.. code-block:: cryptol
\p1 p2 -> e // Lambda expression
f p1 p2 = e // Function definition

162
docs/RefMan/Expressions.rst Normal file
View File

@ -0,0 +1,162 @@
Expressions
===========
This section provides an overview of the Cryptol's expression syntax.
Calling Functions
-----------------
.. code-block:: cryptol
f 2 // call `f` with parameter `2`
g x y // call `g` with two parameters: `x` and `y`
h (x,y) // call `h` with one parameter, the pair `(x,y)`
Prefix Operators
-----------------
.. code-block:: cryptol
-2 // call unary `-` with parameter `2`
- 2 // call unary `-` with parameter `2`
f (-2) // call `f` with one argument: `-2`, parens are important
-f 2 // call unary `-` with parameter `f 2`
- f 2 // call unary `-` with parameter `f 2`
Infix Functions
-----------------
.. code-block:: cryptol
2 + 3 // call `+` with two parameters: `2` and `3`
2 + 3 * 5 // call `+` with two parameters: `2` and `3 * 5`
(+) 2 3 // call `+` with two parameters: `2` and `3`
f 2 + g 3 // call `+` with two parameters: `f 2` and `g 3`
- 2 + - 3 // call `+` with two parameters: `-2` and `-3`
- f 2 + - g 3
Type Annotations
-----------------
Explicit type annotations may be added on expressions, patterns, and
in argument definitions.
.. code-block:: cryptol
x : Bit // specify that `x` has type `Bit`
f x : Bit // specify that `f x` has type `Bit`
- f x : [8] // specify that `- f x` has type `[8]`
2 + 3 : [8] // specify that `2 + 3` has type `[8]`
\x -> x : [8] // type annotation is on `x`, not the function
if x
then y
else z : Bit // the type annotation is on `z`, not the whole `if`
[1..9 : [8]] // specify that elements in `[1..9]` have type `[8]`
f (x : [8]) = x + 1 // type annotation on patterns
.. todo::
Patterns with type variables
Explicit Type Instantiation
----------------------------
If ``f`` is a polymorphic value with type:
.. code-block:: cryptol
f : { tyParam } tyParam
f = zero
you can evaluate ``f``, passing it a type parameter:
.. code-block:: cryptol
f `{ tyParam = 13 }
Local Declarations
------------------
Local declarations have the weakest precedence of all expressions.
.. code-block:: cryptol
2 + x : [T]
where
type T = 8
x = 2 // `T` and `x` are in scope of `2 + x : `[T]`
if x then 1 else 2
where x = 2 // `x` is in scope in the whole `if`
\y -> x + y
where x = 2 // `y` is not in scope in the defintion of `x`
Block Arguments
---------------
When used as the last argument to a function call,
``if`` and lambda expressions do not need parens:
.. code-block:: cryptol
f \x -> x // call `f` with one argument `x -> x`
2 + if x
then y
else z // call `+` with two arguments: `2` and `if ...`
Conditionals
------------
The ``if ... then ... else`` construct can be used with
multiple branches. For example:
.. code-block:: cryptol
x = if y % 2 == 0 then 22 else 33
x = if y % 2 == 0 then 1
| y % 3 == 0 then 2
| y % 5 == 0 then 3
else 7
Demoting Numeric Types to Values
--------------------------------
The value corresponding to a numeric type may be accessed using the
following notation:
.. code-block:: cryptol
`t
Here `t` should be a finite type expression with numeric kind. The resulting
expression will be of a numeric base type, which is sufficiently large
to accommodate the value of the type:
.. code-block:: cryptol
`t : {a} (Literal t a) => a
This backtick notation is syntax sugar for an application of the
`number` primtive, so the above may be written as:
.. code-block:: cryptol
number`{t} : {a} (Literal t a) => a
If a type cannot be inferred from context, a suitable type will be
automatically chosen if possible, usually `Integer`.

610
docs/RefMan/Modules.rst Normal file
View File

@ -0,0 +1,610 @@
Modules
=======
A *module* is used to group some related definitions. Each file may
contain at most one top-level module.
.. code-block:: cryptol
module M where
type T = [8]
f : [8]
f = 10
Hierarchical Module Names
-------------------------
Module may have either simple or *hierarchical* names.
Hierarchical names are constructed by gluing together ordinary
identifiers using the symbol ``::``.
.. code-block:: cryptol
module Hash::SHA256 where
sha256 = ...
The structure in the name may be used to group together related
modules. Also, the Cryptol implementation uses the structure of the
name to locate the file containing the definition of the module.
For example, when searching for module ``Hash::SHA256``, Cryptol
will look for a file named ``SHA256.cry`` in a directory called
``Hash``, contained in one of the directories specified by ``CRYPTOLPATH``.
Module Imports
--------------
To use the definitions from one module in another module, we use
``import`` declarations:
.. code-block:: cryptol
:caption: module M
// Provide some definitions
module M where
f : [8]
f = 2
.. code-block:: cryptol
:caption: module N
// Uses definitions from `M`
module N where
import M // import all definitions from `M`
g = f // `f` was imported from `M`
Import Lists
~~~~~~~~~~~~
Sometimes, we may want to import only some of the definitions
from a module. To do so, we use an import declaration with
an *import list*.
.. code-block:: cryptol
module M where
f = 0x02
g = 0x03
h = 0x04
.. code-block:: cryptol
module N where
import M(f,g) // Imports only `f` and `g`, but not `h`
x = f + g
Using explicit import lists helps reduce name collisions.
It also tends to make code easier to understand, because
it makes it easy to see the source of definitions.
Hiding Imports
~~~~~~~~~~~~~~
Sometimes a module may provide many definitions, and we want to use
most of them but with a few exceptions (e.g., because those would
result to a name clash). In such situations it is convenient
to use a *hiding* import:
.. code-block:: cryptol
:caption: module M
module M where
f = 0x02
g = 0x03
h = 0x04
.. code-block:: cryptol
:caption: module N
module N where
import M hiding (h) // Import everything but `h`
x = f + g
Qualified Module Imports
~~~~~~~~~~~~~~~~~~~~~~~~
Another way to avoid name collisions is by using a
*qualified* import.
.. code-block:: cryptol
:caption: module M
module M where
f : [8]
f = 2
.. code-block:: cryptol
:caption: module N
module N where
import M as P
g = P::f
// `f` was imported from `M`
// but when used it needs to be prefixed by the qualifier `P`
Qualified imports make it possible to work with definitions
that happen to have the same name but are defined in different modules.
Qualified imports may be combined with import lists or hiding clauses:
.. code-block:: cryptol
:caption: Example
import A as B (f) // introduces B::f
import X as Y hiding (f) // introduces everything but `f` from X
// using the prefix `X`
It is also possible to use the same qualifier prefix for imports
from different modules. For example:
.. code-block:: cryptol
:caption: Example
import A as B
import X as B
Such declarations will introduces all definitions from ``A`` and ``X``
but to use them, you would have to qualify using the prefix ``B::``.
Private Blocks
--------------
In some cases, definitions in a module might use helper
functions that are not intended to be used outside the module.
It is good practice to place such declarations in *private blocks*:
.. code-block:: cryptol
:caption: Private blocks
module M where
f : [8]
f = 0x01 + helper1 + helper2
private
helper1 : [8]
helper1 = 2
helper2 : [8]
helper2 = 3
The private block only needs to be indented if it might be followed by
additional public declarations. If all remaining declarations are to be
private then no additional indentation is needed as the ``private`` block will
extend to the end of the module.
.. code-block:: cryptol
:caption: Private blocks
module M where
f : [8]
f = 0x01 + helper1 + helper2
private
helper1 : [8]
helper1 = 2
helper2 : [8]
helper2 = 3
The keyword ``private`` introduces a new layout scope, and all declarations
in the block are considered to be private to the module. A single module
may contain multiple private blocks. For example, the following module
is equivalent to the previous one:
.. code-block:: cryptol
:caption: Private blocks
module M where
f : [8]
f = 0x01 + helper1 + helper2
private
helper1 : [8]
helper1 = 2
private
helper2 : [8]
helper2 = 3
Nested Modules
--------------
Module may be declared withing other modules, using the ``submodule`` keword.
.. code-block:: cryptol
:caption: Declaring a nested module called N
module M where
x = 0x02
submodule N where
y = x + 2
Submodules may refer to names in their enclosing scope.
Declarations in a sub-module will shadow names in the outer scope.
Declarations in a submdule may be imported with ``import submodule``,
which works just like an ordinary import except that ``X`` refers
to the name of a submodule.
.. code-block:: cryptol
:caption: Using declarations from a submodule.
module M where
x = 0x02
submodule N where
y = x + 2
import submodule N as P
z = 2 * P::y
Note that recursive definitions across modules are not allowed.
So, in the previous example, it would be an error if ``y`` was
to try to use ``z`` in its definition.
Implicit Imports
~~~~~~~~~~~~~~~~
For convenience, we add an implicit qualified submodule import for
each locally defined submodules.
.. code-block:: cryptol
:caption: Making use of the implicit import for a submodule.
module M where
x = 0x02
submodule N where
y = x + 2
z = 2 * N::y
``N::y`` works in the previous example because Cryptol added
an implicit import ``import submoulde N as N``.
Managing Module Names
~~~~~~~~~~~~~~~~~~~~~
The names of nested modules are managed by the module system just
like the name of any other declaration in Cryptol. Thus, nested
modules may declared in the public or private sections of their
containing module, and need to be imported before they can be used.
Thus, to use a submodule defined in top-level module ``A`` into
another top-level module ``B`` requires two steps:
1. First we need to import ``A`` to bring the name of the submodule in scope
2. Then we need to import the submodule to bring the names defined in it in scope.
.. code-block:: cryptol
:caption: Using a nested module from a different top-level module.
module A where
x = 0x02
submodule N where
y = x + 2
module B where
import A // Brings `N` in scope
import submodule N // Brings `y` in scope
z = 2 * y
Parameterized Modules
---------------------
Interface Modules
~~~~~~~~~~~~~~~~~
An *interface module* describes the content of a module
without providing a concrete implementation.
.. code-block:: cryptol
:caption: An interface module.
interface module I where
type n : # // `n` is a numeric type
type constraint (fin n, n >= 1)
// Assumptions about the declared numeric type
x : [n] // A declarations of a constant
Like other modules, interfaces modules may be nested in
other modules:
.. code-block:: cryptol
:caption: A nested interface module
module M where
interface submodule I where
type n : # // `n` is a numeric type
type constraint (fin n, n >= 1)
// Assumptions about the declared numeric type
x : [n] // A declarations of a constant
Importing an Interface Module
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A module may be parameterized by importing an interface,
instead of a concrete module
.. code-block:: cryptol
:caption: A parameterized module
// The interface desribes the parmaeters
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
// This module is parameterized
module F where
import interface I
y : [n]
y = x + 1
To import a nested interface use ``import interface sumbodule I``
and make sure that ``I`` is in scope.
It is also possible to import multiple interface modules,
or the same interface module more than once. Each import
of an interface module maybe be linked to a different concrete
module, as described in :ref:`instantiating_modules`.
.. code-block:: cryptol
:caption: Multiple interface parameters
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
module F where
import interface I as I
import interface I as J
y : [I::n]
y = I::x + 1
z : [J::n]
z = J::x + 1
Interface Constraints
~~~~~~~~~~~~~~~~~~~~~
When working with multiple interfaces, it is to useful
to be able to impose additional constraints on the
types imported from the interface.
.. code-block:: cryptol
:caption: Adding constraints to interface parameters
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
module F where
import interface I as I
import interface I as J
interface constraint (I::n == J::n)
y : [I::n]
y = I::x + J::x
In this example we impose the constraint that ``n``
(the width of ``x``) in both interfaces must be the
same. Note that, of course, the two instantiations
may provide different values for ``x``.
.. _instantiating_modules:
Instantiating a Parameterized Module
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
To use a parameterized module we need to provide concrete
implementations for the interfaces that it uses, and provide
a name for the resulting module. This is done as follows:
.. code-block:: cryptol
:caption: Instantiating a parameterized module using a single interface.
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
module F where
import interface I
y : [n]
y = x + 1
module Impl where
type n = 8
x = 26
module MyF = F { Impl }
Here we defined a new module called ``MyF`` which is
obtained by filling in module ``Impl`` for the interface
used by ``F``.
If a module is parameterized my multiple interfaces
we need to provide an implementation module for each
interface, using a slight variation on the previous notation.
.. code-block:: cryptol
:caption: Instantiating a parameterized module by name.
// I is defined as above
module F where
import interface I as I
import interface I as J
interface constraint (I::n == J::n)
y : [I::n]
y = I::x + J::x
module Impl1 where
type n = 8
x = 26
module Impl2 where
type n = 8
x = 30
module MyF = F { I = Impl1, J = Impl 2 }
Each interface import is identified by its name,
which is derived from the ``as`` clause on the
interface import. If there is no ``as`` clause,
then the name of the parameter is derived from
the name of the interface itself.
Since interfaces are identified by name, the
order in which they are provided is not important.
Modules defined by instantiation may be nested,
just like any other module:
.. code-block:: cryptol
:caption: Nested module instantiation.
module M where
import Somewhere // defines G
submodule F = submodule G { I }
In this example, ``submodule F`` is defined
by instantiating some other parameterized
module ``G``, presumably imported from ``Somewhere``.
Note that in this case the argument to the instantiation
``I`` is a top-level module, because it is not
preceded by the ``submodule`` keyword.
Anonymous Interface Modules
~~~~~~~~~~~~~~~~~~~~~~~~~~~
If we need to just parameterize a module by a couple of types/values,
it is quite cumbersome to have to define a whole separate interface module.
To make this more convenient we provide the following notation for defining
an anonymous interface and using it straight away:
.. code-block:: cryptol
:caption: Simple parameterized module.
module M where
parameter
type n : #
type constraint (fin n, n >= 1)
x : [n]
f : [n]
f = 1 + x
The ``parameter`` block defines an interface module and uses it.
Note that the parameters may not use things defined in ``M`` as
the interface is declared outside of ``M``.
Anonymous Instantiation Arguments
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Sometimes it is also a bit cumbersome to have to define a whole
separate module just to pass it as an argument to some parameterized
module. To make this more convenient we support the following notion
for instantiation a module:
.. code-block:: cryptol
// A parameterized module
module M where
parameter
type n : #
x : [n]
y : [n]
f : [n]
f = x + y
// A module instantiation
module N = M
where
type n = 32
x = 11
y = helper
helper = 12
The declarations in the ``where`` block are treated as the
definition of an anonymous module which is passed as the argument
to parameterized module ``M``.

View File

@ -0,0 +1,107 @@
Overloaded Operations
=====================
Equality
--------
.. code-block:: cryptol
Eq
(==) : {a} (Eq a) => a -> a -> Bit
(!=) : {a} (Eq a) => a -> a -> Bit
(===) : {a, b} (Eq b) => (a -> b) -> (a -> b) -> (a -> Bit)
(!==) : {a, b} (Eq b) => (a -> b) -> (a -> b) -> (a -> Bit)
Comparisons
-----------
.. code-block:: cryptol
Cmp
(<) : {a} (Cmp a) => a -> a -> Bit
(>) : {a} (Cmp a) => a -> a -> Bit
(<=) : {a} (Cmp a) => a -> a -> Bit
(>=) : {a} (Cmp a) => a -> a -> Bit
min : {a} (Cmp a) => a -> a -> a
max : {a} (Cmp a) => a -> a -> a
abs : {a} (Cmp a, Ring a) => a -> a
Signed Comparisons
------------------
.. code-block:: cryptol
SignedCmp
(<$) : {a} (SignedCmp a) => a -> a -> Bit
(>$) : {a} (SignedCmp a) => a -> a -> Bit
(<=$) : {a} (SignedCmp a) => a -> a -> Bit
(>=$) : {a} (SignedCmp a) => a -> a -> Bit
Zero
----
.. code-block:: cryptol
Zero
zero : {a} (Zero a) => a
Logical Operations
------------------
.. code-block:: cryptol
Logic
(&&) : {a} (Logic a) => a -> a -> a
(||) : {a} (Logic a) => a -> a -> a
(^) : {a} (Logic a) => a -> a -> a
complement : {a} (Logic a) => a -> a
Basic Arithmetic
----------------
.. code-block:: cryptol
Ring
fromInteger : {a} (Ring a) => Integer -> a
(+) : {a} (Ring a) => a -> a -> a
(-) : {a} (Ring a) => a -> a -> a
(*) : {a} (Ring a) => a -> a -> a
negate : {a} (Ring a) => a -> a
(^^) : {a, e} (Ring a, Integral e) => a -> e -> a
Integral Operations
-------------------
.. code-block:: cryptol
Integral
(/) : {a} (Integral a) => a -> a -> a
(%) : {a} (Integral a) => a -> a -> a
(^^) : {a, e} (Ring a, Integral e) => a -> e -> a
toInteger : {a} (Integral a) => a -> Integer
infFrom : {a} (Integral a) => a -> [inf]a
infFromThen : {a} (Integral a) => a -> a -> [inf]a
Division
--------
.. code-block:: cryptol
Field
recip : {a} (Field a) => a -> a
(/.) : {a} (Field a) => a -> a -> a
Rounding
--------
.. code-block:: cryptol
Round
ceiling : {a} (Round a) => a -> Integer
floor : {a} (Round a) => a -> Integer
trunc : {a} (Round a) => a -> Integer
roundAway : {a} (Round a) => a -> Integer
roundToEven : {a} (Round a) => a -> Integer

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,53 @@
Type Declarations
=================
Type Synonyms
-------------
.. code-block:: cryptol
type T a b = [a] b
A ``type`` declaration creates a synonym for a
pre-existing type expression, which may optionally have
arguments. A type synonym is transparently unfolded at
use sites and is treated as though the user had instead
written the body of the type synonym in line.
Type synonyms may mention other synonyms, but it is not
allowed to create a recursive collection of type synonyms.
Newtypes
--------
.. code-block:: cryptol
newtype NewT a b = { seq : [a]b }
A ``newtype`` declaration declares a new named type which is defined by
a record body. Unlike type synonyms, each named ``newtype`` is treated
as a distinct type by the type checker, even if they have the same
bodies. Moreover, types created by a ``newtype`` declaration will not be
members of any typeclasses, even if the record defining their body
would be. For the purposes of typechecking, two newtypes are
considered equal only if all their arguments are equal, even if the
arguments do not appear in the body of the newtype, or are otherwise
irrelevant. Just like type synonyms, newtypes are not allowed to form
recursive groups.
Every ``newtype`` declaration brings into scope a new function with the
same name as the type which can be used to create values of the
newtype.
.. code-block:: cryptol
x : NewT 3 Integer
x = NewT { seq = [1,2,3] }
Just as with records, field projections can be used directly on values
of newtypes to extract the values in the body of the type.
.. code-block:: none
> sum x.seq
6

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

@ -1,4 +1,4 @@
# Sphinx build info version 1
# This file hashes the configuration used when building these files. When it is not found, a full rebuild will be done.
config: 3f9a4daf23c759ed9c684b18b96cc6ff
config: a4ccf7f1b3589b784c5cab7c48946aab
tags: 645f666f9bcd5a90fca523b33c5a78b7

View File

@ -0,0 +1,390 @@
<!DOCTYPE html>
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Basic Syntax &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="search.html" />
<link rel="next" title="Expressions" href="Expressions.html" />
<link rel="prev" title="Cryptol Reference Manual" href="RefMan.html" />
</head>
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
<input type="hidden" name="check_keywords" value="yes" />
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul class="current">
<li class="toctree-l1 current"><a class="current reference internal" href="#">Basic Syntax</a><ul>
<li class="toctree-l2"><a class="reference internal" href="#declarations">Declarations</a></li>
<li class="toctree-l2"><a class="reference internal" href="#type-signatures">Type Signatures</a></li>
<li class="toctree-l2"><a class="reference internal" href="#layout">Layout</a></li>
<li class="toctree-l2"><a class="reference internal" href="#comments">Comments</a></li>
<li class="toctree-l2"><a class="reference internal" href="#identifiers">Identifiers</a></li>
<li class="toctree-l2"><a class="reference internal" href="#keywords-and-built-in-operators">Keywords and Built-in Operators</a></li>
<li class="toctree-l2"><a class="reference internal" href="#built-in-type-level-operators">Built-in Type-level Operators</a></li>
<li class="toctree-l2"><a class="reference internal" href="#numeric-literals">Numeric Literals</a></li>
</ul>
</li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Basic Syntax</li>
<li class="wy-breadcrumbs-aside">
<a href="_sources/BasicSyntax.rst.txt" rel="nofollow"> View page source</a>
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<div class="section" id="basic-syntax">
<h1>Basic Syntax<a class="headerlink" href="#basic-syntax" title="Permalink to this headline"></a></h1>
<div class="section" id="declarations">
<h2>Declarations<a class="headerlink" href="#declarations" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span> <span class="n">x</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="n">y</span> <span class="o">+</span> <span class="n">z</span>
</pre></div>
</div>
</div>
<div class="section" id="type-signatures">
<h2>Type Signatures<a class="headerlink" href="#type-signatures" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span><span class="p">,</span><span class="n">g</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">,</span><span class="n">b</span><span class="p">}</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="p">[</span><span class="n">a</span><span class="p">]</span> <span class="n">b</span>
</pre></div>
</div>
</div>
<div class="section" id="layout">
<h2>Layout<a class="headerlink" href="#layout" title="Permalink to this headline"></a></h2>
<p>Groups of declarations are organized based on indentation.
Declarations with the same indentation belong to the same group.
Lines of text that are indented more than the beginning of a
declaration belong to that declaration, while lines of text that are
indented less terminate a group of declarations. Consider, for example,
the following Cryptol declarations:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span> <span class="n">x</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="n">y</span> <span class="o">+</span> <span class="n">z</span>
<span class="kr">where</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">*</span> <span class="n">x</span>
<span class="n">z</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="n">y</span>
<span class="nf">g</span> <span class="n">y</span> <span class="ow">=</span> <span class="n">y</span>
</pre></div>
</div>
<p>This group has two declarations, one for <cite>f</cite> and one for <cite>g</cite>. All the
lines between <cite>f</cite> and <cite>g</cite> that are indented more than <cite>f</cite> belong to
<cite>f</cite>. The same principle applies to the declarations in the <code class="docutils literal notranslate"><span class="pre">where</span></code> block
of <cite>f</cite>, which defines two more local names, <cite>y</cite> and <cite>z</cite>.</p>
</div>
<div class="section" id="comments">
<h2>Comments<a class="headerlink" href="#comments" title="Permalink to this headline"></a></h2>
<p>Cryptol supports block comments, which start with <code class="docutils literal notranslate"><span class="pre">/*</span></code> and end with
<code class="docutils literal notranslate"><span class="pre">*/</span></code>, and line comments, which start with <code class="docutils literal notranslate"><span class="pre">//</span></code> and terminate at the
end of the line. Block comments may be nested arbitrarily.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="cm">/* This is a block comment */</span>
<span class="c1">// This is a line comment</span>
<span class="cm">/* This is a /* Nested */ block comment */</span>
</pre></div>
</div>
<div class="admonition-todo admonition" id="id1">
<p class="admonition-title">Todo</p>
<p>Document <code class="docutils literal notranslate"><span class="pre">/**</span> <span class="pre">*/</span></code></p>
</div>
</div>
<div class="section" id="identifiers">
<h2>Identifiers<a class="headerlink" href="#identifiers" title="Permalink to this headline"></a></h2>
<p>Cryptol identifiers consist of one or more characters. The first
character must be either an English letter or underscore (<code class="docutils literal notranslate"><span class="pre">_</span></code>). The
following characters may be an English letter, a decimal digit,
underscore (<code class="docutils literal notranslate"><span class="pre">_</span></code>), or a prime (<code class="docutils literal notranslate"><span class="pre">'</span></code>). Some identifiers have special
meaning in the language, so they may not be used in programmer-defined
names (see <a class="reference internal" href="#keywords-and-built-in-operators">Keywords and Built-in Operators</a>).</p>
<div class="literal-block-wrapper docutils container" id="id2">
<div class="code-block-caption"><span class="caption-text">Examples of identifiers</span><a class="headerlink" href="#id2" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">name</span> <span class="n">name1</span> <span class="n">name&#39;</span> <span class="n">longer_name</span>
<span class="kt">Name</span> <span class="kt">Name2</span> <span class="kt">Name&#39;&#39;</span> <span class="n">longerName</span>
</pre></div>
</div>
</div>
</div>
<div class="section" id="keywords-and-built-in-operators">
<h2>Keywords and Built-in Operators<a class="headerlink" href="#keywords-and-built-in-operators" title="Permalink to this headline"></a></h2>
<p>The following identifiers have special meanings in Cryptol, and may
not be used for programmer defined names:</p>
<div class="literal-block-wrapper docutils container" id="id3">
<span id="keywords"></span><div class="code-block-caption"><span class="caption-text">Keywords</span><a class="headerlink" href="#id3" title="Permalink to this code"></a></div>
<div class="highlight-none notranslate"><div class="highlight"><pre><span></span>as extern include interface parameter property where
by hiding infix let pragma submodule else
constraint if infixl module primitive then
down import infixr newtype private type
</pre></div>
</div>
</div>
<p>The following table contains Cryptols operators and their
associativity with lowest precedence operators first, and highest
precedence last.</p>
<table class="docutils align-default" id="id4">
<caption><span class="caption-text">Operator precedences</span><a class="headerlink" href="#id4" title="Permalink to this table"></a></caption>
<colgroup>
<col style="width: 71%" />
<col style="width: 29%" />
</colgroup>
<thead>
<tr class="row-odd"><th class="head"><p>Operator</p></th>
<th class="head"><p>Associativity</p></th>
</tr>
</thead>
<tbody>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">==&gt;</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">\/</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">/\</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">==</span></code> <code class="docutils literal notranslate"><span class="pre">!=</span></code> <code class="docutils literal notranslate"><span class="pre">===</span></code> <code class="docutils literal notranslate"><span class="pre">!==</span></code></p></td>
<td><p>not associative</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">&gt;</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;=</span></code> <code class="docutils literal notranslate"><span class="pre">&gt;=</span></code>
<code class="docutils literal notranslate"><span class="pre">&lt;$</span></code> <code class="docutils literal notranslate"><span class="pre">&gt;$</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;=$</span></code> <code class="docutils literal notranslate"><span class="pre">&gt;=$</span></code></p></td>
<td><p>not associative</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">||</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">^</span></code></p></td>
<td><p>left</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">&amp;&amp;</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">#</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">&gt;&gt;</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;&lt;</span></code> <code class="docutils literal notranslate"><span class="pre">&gt;&gt;&gt;</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;&lt;&lt;</span></code> <code class="docutils literal notranslate"><span class="pre">&gt;&gt;$</span></code></p></td>
<td><p>left</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">+</span></code> <code class="docutils literal notranslate"><span class="pre">-</span></code></p></td>
<td><p>left</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">*</span></code> <code class="docutils literal notranslate"><span class="pre">/</span></code> <code class="docutils literal notranslate"><span class="pre">%</span></code> <code class="docutils literal notranslate"><span class="pre">/$</span></code> <code class="docutils literal notranslate"><span class="pre">%$</span></code></p></td>
<td><p>left</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">^^</span></code></p></td>
<td><p>right</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">&#64;</span></code> <code class="docutils literal notranslate"><span class="pre">&#64;&#64;</span></code> <code class="docutils literal notranslate"><span class="pre">!</span></code> <code class="docutils literal notranslate"><span class="pre">!!</span></code></p></td>
<td><p>left</p></td>
</tr>
<tr class="row-even"><td><p>(unary) <code class="docutils literal notranslate"><span class="pre">-</span></code> <code class="docutils literal notranslate"><span class="pre">~</span></code></p></td>
<td><p>right</p></td>
</tr>
</tbody>
</table>
</div>
<div class="section" id="built-in-type-level-operators">
<h2>Built-in Type-level Operators<a class="headerlink" href="#built-in-type-level-operators" title="Permalink to this headline"></a></h2>
<p>Cryptol includes a variety of operators that allow computations on
the numeric types used to specify the sizes of sequences.</p>
<table class="docutils align-default" id="id5">
<caption><span class="caption-text">Type-level operators</span><a class="headerlink" href="#id5" title="Permalink to this table"></a></caption>
<colgroup>
<col style="width: 23%" />
<col style="width: 77%" />
</colgroup>
<thead>
<tr class="row-odd"><th class="head"><p>Operator</p></th>
<th class="head"><p>Meaning</p></th>
</tr>
</thead>
<tbody>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">+</span></code></p></td>
<td><p>Addition</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">-</span></code></p></td>
<td><p>Subtraction</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">*</span></code></p></td>
<td><p>Multiplication</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">/</span></code></p></td>
<td><p>Division</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">/^</span></code></p></td>
<td><p>Ceiling division (<code class="docutils literal notranslate"><span class="pre">/</span></code> rounded up)</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">%</span></code></p></td>
<td><p>Modulus</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">%^</span></code></p></td>
<td><p>Ceiling modulus (compute padding)</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">^^</span></code></p></td>
<td><p>Exponentiation</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">lg2</span></code></p></td>
<td><p>Ceiling logarithm (base 2)</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">width</span></code></p></td>
<td><p>Bit width (equal to <code class="docutils literal notranslate"><span class="pre">lg2(n+1)</span></code>)</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">max</span></code></p></td>
<td><p>Maximum</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">min</span></code></p></td>
<td><p>Minimum</p></td>
</tr>
</tbody>
</table>
</div>
<div class="section" id="numeric-literals">
<h2>Numeric Literals<a class="headerlink" href="#numeric-literals" title="Permalink to this headline"></a></h2>
<p>Numeric literals may be written in binary, octal, decimal, or
hexadecimal notation. The base of a literal is determined by its prefix:
<code class="docutils literal notranslate"><span class="pre">0b</span></code> for binary, <code class="docutils literal notranslate"><span class="pre">0o</span></code> for octal, no special prefix for
decimal, and <code class="docutils literal notranslate"><span class="pre">0x</span></code> for hexadecimal.</p>
<div class="literal-block-wrapper docutils container" id="id6">
<div class="code-block-caption"><span class="caption-text">Examples of literals</span><a class="headerlink" href="#id6" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="mi">254</span> <span class="c1">// Decimal literal</span>
<span class="mi">0254</span> <span class="c1">// Decimal literal</span>
<span class="mi">0</span><span class="n">b11111110</span> <span class="c1">// Binary literal</span>
<span class="mo">0o376</span> <span class="c1">// Octal literal</span>
<span class="mh">0xFE</span> <span class="c1">// Hexadecimal literal</span>
<span class="mh">0xfe</span> <span class="c1">// Hexadecimal literal</span>
</pre></div>
</div>
</div>
<p>Numeric literals in binary, octal, or hexadecimal notation result in
bit sequences of a fixed length (i.e., they have type <code class="docutils literal notranslate"><span class="pre">[n]</span></code> for
some <cite>n</cite>). The length is determined by the base and the number
of digits in the literal. Decimal literals are overloaded, and so the
type is inferred from context in which the literal is used. Examples:</p>
<div class="literal-block-wrapper docutils container" id="id7">
<div class="code-block-caption"><span class="caption-text">Literals and their types</span><a class="headerlink" href="#id7" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="mi">0</span><span class="n">b1010</span> <span class="c1">// : [4], 1 * number of digits</span>
<span class="mo">0o1234</span> <span class="c1">// : [12], 3 * number of digits</span>
<span class="mh">0x1234</span> <span class="c1">// : [16], 4 * number of digits</span>
<span class="mi">10</span> <span class="c1">// : {a}. (Literal 10 a) =&gt; a</span>
<span class="c1">// a = Integer or [n] where n &gt;= width 10</span>
</pre></div>
</div>
</div>
<p>Numeric literals may also be written as polynomials by writing a polynomial
expression in terms of <cite>x</cite> between an opening <code class="docutils literal notranslate"><span class="pre">&lt;|</span></code> and a closing <code class="docutils literal notranslate"><span class="pre">|&gt;</span></code>.
Numeric literals in polynomial notation result in bit sequences of length
one more than the degree of the polynomial. Examples:</p>
<div class="literal-block-wrapper docutils container" id="id8">
<div class="code-block-caption"><span class="caption-text">Polynomial literals</span><a class="headerlink" href="#id8" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="o">&lt;|</span> <span class="n">x</span><span class="o">^^</span><span class="mi">6</span> <span class="o">+</span> <span class="n">x</span><span class="o">^^</span><span class="mi">4</span> <span class="o">+</span> <span class="n">x</span><span class="o">^^</span><span class="mi">2</span> <span class="o">+</span> <span class="n">x</span><span class="o">^^</span><span class="mi">1</span> <span class="o">+</span> <span class="mi">1</span> <span class="o">|&gt;</span> <span class="c1">// : [7], equal to 0b1010111</span>
<span class="o">&lt;|</span> <span class="n">x</span><span class="o">^^</span><span class="mi">4</span> <span class="o">+</span> <span class="n">x</span><span class="o">^^</span><span class="mi">3</span> <span class="o">+</span> <span class="n">x</span> <span class="o">|&gt;</span> <span class="c1">// : [5], equal to 0b11010</span>
</pre></div>
</div>
</div>
<p>Cryptol also supports fractional literals using binary (prefix <code class="docutils literal notranslate"><span class="pre">0b</span></code>),
octal (prefix <code class="docutils literal notranslate"><span class="pre">0o</span></code>), decimal (no prefix), and hexadecimal (prefix <code class="docutils literal notranslate"><span class="pre">ox</span></code>)
digits. A fractional literal must contain a <code class="docutils literal notranslate"><span class="pre">.</span></code> and may optionally
have an exponent. The base of the exponent for binary, octal,
and hexadecimal literals is 2 and the exponent is marked using the symbol <code class="docutils literal notranslate"><span class="pre">p</span></code>.
Decimal fractional literals use exponent base 10, and the symbol <code class="docutils literal notranslate"><span class="pre">e</span></code>.
Examples:</p>
<div class="literal-block-wrapper docutils container" id="id9">
<div class="code-block-caption"><span class="caption-text">Fractional literals</span><a class="headerlink" href="#id9" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="mf">10.2</span>
<span class="mf">10.2e3</span> <span class="c1">// 10.2 * 10^3</span>
<span class="mh">0x30</span><span class="o">.</span><span class="mi">1</span> <span class="c1">// 3 * 64 + 1/16</span>
<span class="mh">0x30</span><span class="o">.</span><span class="mi">1</span><span class="n">p4</span> <span class="c1">// (3 * 64 + 1/16) * 2^4</span>
</pre></div>
</div>
</div>
<p>All fractional literals are overloaded and may be used with types that support
fractional numbers (e.g., <code class="docutils literal notranslate"><span class="pre">Rational</span></code>, and the <code class="docutils literal notranslate"><span class="pre">Float</span></code> family of types).</p>
<p>Some types (e.g. the <code class="docutils literal notranslate"><span class="pre">Float</span></code> family) cannot represent all fractional literals
precisely. Such literals are rejected statically when using binary, octal,
or hexadecimal notation. When using decimal notation, the literal is rounded
to the closest representable even number.</p>
<p>All numeric literals may also include <code class="docutils literal notranslate"><span class="pre">_</span></code>, which has no effect on the
literal value but may be used to improve readability. Here are some examples:</p>
<div class="literal-block-wrapper docutils container" id="id10">
<div class="code-block-caption"><span class="caption-text">Using _</span><a class="headerlink" href="#id10" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="mi">0</span><span class="n">b_0000_0010</span>
<span class="mi">0</span><span class="n">x_FFFF_FFEA</span>
</pre></div>
</div>
</div>
</div>
</div>
</div>
</div>
<footer><div class="rst-footer-buttons" role="navigation" aria-label="Footer">
<a href="RefMan.html" class="btn btn-neutral float-left" title="Cryptol Reference Manual" accesskey="p" rel="prev"><span class="fa fa-arrow-circle-left" aria-hidden="true"></span> Previous</a>
<a href="Expressions.html" class="btn btn-neutral float-right" title="Expressions" accesskey="n" rel="next">Next <span class="fa fa-arrow-circle-right" aria-hidden="true"></span></a>
</div>
<hr/>
<div role="contentinfo">
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</body>
</html>

View File

@ -0,0 +1,306 @@
<!DOCTYPE html>
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Basic Types &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="search.html" />
<link rel="next" title="Overloaded Operations" href="OverloadedOperations.html" />
<link rel="prev" title="Expressions" href="Expressions.html" />
</head>
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
<input type="hidden" name="check_keywords" value="yes" />
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul class="current">
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1 current"><a class="current reference internal" href="#">Basic Types</a><ul>
<li class="toctree-l2"><a class="reference internal" href="#tuples-and-records">Tuples and Records</a><ul>
<li class="toctree-l3"><a class="reference internal" href="#accessing-fields">Accessing Fields</a></li>
<li class="toctree-l3"><a class="reference internal" href="#updating-fields">Updating Fields</a></li>
</ul>
</li>
<li class="toctree-l2"><a class="reference internal" href="#sequences">Sequences</a></li>
<li class="toctree-l2"><a class="reference internal" href="#functions">Functions</a></li>
</ul>
</li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Basic Types</li>
<li class="wy-breadcrumbs-aside">
<a href="_sources/BasicTypes.rst.txt" rel="nofollow"> View page source</a>
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<div class="section" id="basic-types">
<h1>Basic Types<a class="headerlink" href="#basic-types" title="Permalink to this headline"></a></h1>
<div class="section" id="tuples-and-records">
<h2>Tuples and Records<a class="headerlink" href="#tuples-and-records" title="Permalink to this headline"></a></h2>
<p>Tuples and records are used for packaging multiple values together.
Tuples are enclosed in parentheses, while records are enclosed in
curly braces. The components of both tuples and records are separated by
commas. The components of tuples are expressions, while the
components of records are a label and a value separated by an equal
sign. Examples:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="p">(</span><span class="mi">1</span><span class="p">,</span><span class="mi">2</span><span class="p">,</span><span class="mi">3</span><span class="p">)</span> <span class="c1">// A tuple with 3 component</span>
<span class="nb">()</span> <span class="c1">// A tuple with no components</span>
<span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">1</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">2</span> <span class="p">}</span> <span class="c1">// A record with two fields, `x` and `y`</span>
<span class="p">{}</span> <span class="c1">// A record with no fields</span>
</pre></div>
</div>
<p>The components of tuples are identified by position, while the
components of records are identified by their label, and so the
ordering of record components is not important for most purposes.
Examples:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span> <span class="p">(</span><span class="mi">1</span><span class="p">,</span><span class="mi">2</span><span class="p">)</span> <span class="o">==</span> <span class="p">(</span><span class="mi">1</span><span class="p">,</span><span class="mi">2</span><span class="p">)</span> <span class="c1">// True</span>
<span class="p">(</span><span class="mi">1</span><span class="p">,</span><span class="mi">2</span><span class="p">)</span> <span class="o">==</span> <span class="p">(</span><span class="mi">2</span><span class="p">,</span><span class="mi">1</span><span class="p">)</span> <span class="c1">// False</span>
<span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">1</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">2</span> <span class="p">}</span> <span class="o">==</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">1</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">2</span> <span class="p">}</span> <span class="c1">// True</span>
<span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">1</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">2</span> <span class="p">}</span> <span class="o">==</span> <span class="p">{</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">2</span><span class="p">,</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">1</span> <span class="p">}</span> <span class="c1">// True</span>
</pre></div>
</div>
<p>Ordering on tuples and records is defined lexicographically. Tuple
components are compared in the order they appear, whereas record
fields are compared in alphabetical order of field names.</p>
<div class="section" id="accessing-fields">
<h3>Accessing Fields<a class="headerlink" href="#accessing-fields" title="Permalink to this headline"></a></h3>
<p>The components of a record or a tuple may be accessed in two ways: via
pattern matching or by using explicit component selectors. Explicit
component selectors are written as follows:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="p">(</span><span class="mi">15</span><span class="p">,</span> <span class="mi">20</span><span class="p">)</span><span class="o">.</span><span class="mi">0</span> <span class="o">==</span> <span class="mi">15</span>
<span class="p">(</span><span class="mi">15</span><span class="p">,</span> <span class="mi">20</span><span class="p">)</span><span class="o">.</span><span class="mi">1</span> <span class="o">==</span> <span class="mi">20</span>
<span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">15</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">20</span> <span class="p">}</span><span class="o">.</span><span class="n">x</span> <span class="o">==</span> <span class="mi">15</span>
</pre></div>
</div>
<p>Explicit record selectors may be used only if the program contains
sufficient type information to determine the shape of the tuple or
record. For example:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">type</span> <span class="kt">T</span> <span class="ow">=</span> <span class="p">{</span> <span class="n">sign</span> <span class="kt">:</span> <span class="kr">Bit</span><span class="p">,</span> <span class="n">number</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">15</span><span class="p">]</span> <span class="p">}</span>
<span class="c1">// Valid definition:</span>
<span class="c1">// the type of the record is known.</span>
<span class="nf">isPositive</span> <span class="kt">:</span> <span class="kt">T</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="nf">isPositive</span> <span class="n">x</span> <span class="ow">=</span> <span class="n">x</span><span class="o">.</span><span class="n">sign</span>
<span class="c1">// Invalid definition:</span>
<span class="c1">// insufficient type information.</span>
<span class="nf">badDef</span> <span class="n">x</span> <span class="ow">=</span> <span class="n">x</span><span class="o">.</span><span class="n">f</span>
</pre></div>
</div>
<p>The components of a tuple or a record may also be accessed using
pattern matching. Patterns for tuples and records mirror the syntax
for constructing values: tuple patterns use parentheses, while record
patterns use braces. Examples:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">getFst</span> <span class="p">(</span><span class="n">x</span><span class="p">,</span><span class="n">_</span><span class="p">)</span> <span class="ow">=</span> <span class="n">x</span>
<span class="nf">distance2</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="n">xPos</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="n">yPos</span> <span class="p">}</span> <span class="ow">=</span> <span class="n">xPos</span> <span class="o">^^</span> <span class="mi">2</span> <span class="o">+</span> <span class="n">yPos</span> <span class="o">^^</span> <span class="mi">2</span>
<span class="nf">f</span> <span class="n">p</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="n">y</span> <span class="kr">where</span>
<span class="p">(</span><span class="n">x</span><span class="p">,</span> <span class="n">y</span><span class="p">)</span> <span class="ow">=</span> <span class="n">p</span>
</pre></div>
</div>
<p>Selectors are also lifted through sequence and function types, point-wise,
so that the following equations should hold:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">xs</span><span class="o">.</span><span class="n">l</span> <span class="o">==</span> <span class="p">[</span> <span class="n">x</span><span class="o">.</span><span class="n">l</span> <span class="o">|</span> <span class="n">x</span> <span class="ow">&lt;-</span> <span class="n">xs</span> <span class="p">]</span> <span class="c1">// sequences</span>
<span class="nf">f</span><span class="o">.</span><span class="n">l</span> <span class="o">==</span> <span class="nf">\</span><span class="n">x</span> <span class="ow">-&gt;</span> <span class="p">(</span><span class="n">f</span> <span class="n">x</span><span class="p">)</span><span class="o">.</span><span class="n">l</span> <span class="c1">// functions</span>
</pre></div>
</div>
<p>Thus, if we have a sequence of tuples, <code class="docutils literal notranslate"><span class="pre">xs</span></code>, then we can quickly obtain a
sequence with only the tuples first components by writing <code class="docutils literal notranslate"><span class="pre">xs.0</span></code>.</p>
<p>Similarly, if we have a function, <code class="docutils literal notranslate"><span class="pre">f</span></code>, that computes a tuple of results,
then we can write <code class="docutils literal notranslate"><span class="pre">f.0</span></code> to get a function that computes only the first
entry in the tuple.</p>
<p>This behavior is quite handy when examining complex data at the REPL.</p>
</div>
<div class="section" id="updating-fields">
<h3>Updating Fields<a class="headerlink" href="#updating-fields" title="Permalink to this headline"></a></h3>
<p>The components of a record or a tuple may be updated using the following
notation:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="c1">// Example values</span>
<span class="nf">r</span> <span class="ow">=</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">15</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">20</span> <span class="p">}</span> <span class="c1">// a record</span>
<span class="nf">t</span> <span class="ow">=</span> <span class="p">(</span><span class="kr">True</span><span class="p">,</span><span class="kr">True</span><span class="p">)</span> <span class="c1">// a tuple</span>
<span class="nf">n</span> <span class="ow">=</span> <span class="p">{</span> <span class="n">pt</span> <span class="ow">=</span> <span class="n">r</span><span class="p">,</span> <span class="n">size</span> <span class="ow">=</span> <span class="mi">100</span> <span class="p">}</span> <span class="c1">// nested record</span>
<span class="c1">// Setting fields</span>
<span class="p">{</span> <span class="n">r</span> <span class="o">|</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">30</span> <span class="p">}</span> <span class="o">==</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">30</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">20</span> <span class="p">}</span>
<span class="p">{</span> <span class="n">t</span> <span class="o">|</span> <span class="mi">0</span> <span class="ow">=</span> <span class="kr">False</span> <span class="p">}</span> <span class="o">==</span> <span class="p">(</span><span class="kr">False</span><span class="p">,</span><span class="kr">True</span><span class="p">)</span>
<span class="c1">// Update relative to the old value</span>
<span class="p">{</span> <span class="n">r</span> <span class="o">|</span> <span class="n">x</span> <span class="ow">-&gt;</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">5</span> <span class="p">}</span> <span class="o">==</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">20</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">20</span> <span class="p">}</span>
<span class="c1">// Update a nested field</span>
<span class="p">{</span> <span class="n">n</span> <span class="o">|</span> <span class="n">pt</span><span class="o">.</span><span class="n">x</span> <span class="ow">=</span> <span class="mi">10</span> <span class="p">}</span> <span class="o">==</span> <span class="p">{</span> <span class="n">pt</span> <span class="ow">=</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">10</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">20</span> <span class="p">},</span> <span class="n">size</span> <span class="ow">=</span> <span class="mi">100</span> <span class="p">}</span>
<span class="p">{</span> <span class="n">n</span> <span class="o">|</span> <span class="n">pt</span><span class="o">.</span><span class="n">x</span> <span class="ow">-&gt;</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">10</span> <span class="p">}</span> <span class="o">==</span> <span class="p">{</span> <span class="n">pt</span> <span class="ow">=</span> <span class="p">{</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">25</span><span class="p">,</span> <span class="n">y</span> <span class="ow">=</span> <span class="mi">20</span> <span class="p">},</span> <span class="n">size</span> <span class="ow">=</span> <span class="mi">100</span> <span class="p">}</span>
</pre></div>
</div>
</div>
</div>
<div class="section" id="sequences">
<h2>Sequences<a class="headerlink" href="#sequences" title="Permalink to this headline"></a></h2>
<p>A sequence is a fixed-length collection of elements of the same type.
The type of a finite sequence of length <cite>n</cite>, with elements of type <cite>a</cite>
is <code class="docutils literal notranslate"><span class="pre">[n]</span> <span class="pre">a</span></code>. Often, a finite sequence of bits, <code class="docutils literal notranslate"><span class="pre">[n]</span> <span class="pre">Bit</span></code>, is called a
<em>word</em>. We may abbreviate the type <code class="docutils literal notranslate"><span class="pre">[n]</span> <span class="pre">Bit</span></code> as <code class="docutils literal notranslate"><span class="pre">[n]</span></code>. An infinite
sequence with elements of type <cite>a</cite> has type <code class="docutils literal notranslate"><span class="pre">[inf]</span> <span class="pre">a</span></code>, and <code class="docutils literal notranslate"><span class="pre">[inf]</span></code> is
an infinite stream of bits.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="p">[</span><span class="n">e1</span><span class="p">,</span><span class="n">e2</span><span class="p">,</span><span class="n">e3</span><span class="p">]</span> <span class="c1">// A sequence with three elements</span>
<span class="p">[</span><span class="n">t1</span> <span class="o">..</span> <span class="n">t2</span><span class="p">]</span> <span class="c1">// Enumeration</span>
<span class="p">[</span><span class="n">t1</span> <span class="o">..</span> <span class="o">&lt;</span><span class="n">t2</span><span class="p">]</span> <span class="c1">// Enumeration (exclusive bound)</span>
<span class="p">[</span><span class="n">t1</span> <span class="o">..</span> <span class="n">t2</span> <span class="n">by</span> <span class="n">n</span><span class="p">]</span> <span class="c1">// Enumeration (stride)</span>
<span class="p">[</span><span class="n">t1</span> <span class="o">..</span> <span class="o">&lt;</span><span class="n">t2</span> <span class="n">by</span> <span class="n">n</span><span class="p">]</span> <span class="c1">// Enumeration (stride, ex. bound)</span>
<span class="p">[</span><span class="n">t1</span> <span class="o">..</span> <span class="n">t2</span> <span class="n">down</span> <span class="n">by</span> <span class="n">n</span><span class="p">]</span> <span class="c1">// Enumeration (downward stride)</span>
<span class="p">[</span><span class="n">t1</span> <span class="o">..</span> <span class="o">&gt;</span><span class="n">t2</span> <span class="n">down</span> <span class="n">by</span> <span class="n">n</span><span class="p">]</span> <span class="c1">// Enumeration (downward stride, ex. bound)</span>
<span class="p">[</span><span class="n">t1</span><span class="p">,</span> <span class="n">t2</span> <span class="o">..</span> <span class="n">t3</span><span class="p">]</span> <span class="c1">// Enumeration (step by t2 - t1)</span>
<span class="p">[</span><span class="n">e1</span> <span class="o">...</span><span class="p">]</span> <span class="c1">// Infinite sequence starting at e1</span>
<span class="p">[</span><span class="n">e1</span><span class="p">,</span> <span class="n">e2</span> <span class="o">...</span><span class="p">]</span> <span class="c1">// Infinite sequence stepping by e2-e1</span>
<span class="p">[</span> <span class="n">e</span> <span class="o">|</span> <span class="n">p11</span> <span class="ow">&lt;-</span> <span class="n">e11</span><span class="p">,</span> <span class="n">p12</span> <span class="ow">&lt;-</span> <span class="n">e12</span> <span class="c1">// Sequence comprehensions</span>
<span class="o">|</span> <span class="n">p21</span> <span class="ow">&lt;-</span> <span class="n">e21</span><span class="p">,</span> <span class="n">p22</span> <span class="ow">&lt;-</span> <span class="n">e22</span> <span class="p">]</span>
<span class="nf">x</span> <span class="ow">=</span> <span class="n">generate</span> <span class="p">(</span><span class="nf">\</span><span class="n">i</span> <span class="ow">-&gt;</span> <span class="n">e</span><span class="p">)</span> <span class="c1">// Sequence from generating function</span>
<span class="nf">x</span> <span class="o">@</span> <span class="n">i</span> <span class="ow">=</span> <span class="n">e</span> <span class="c1">// Sequence with index binding</span>
<span class="nf">arr</span> <span class="o">@</span> <span class="n">i</span> <span class="o">@</span> <span class="n">j</span> <span class="ow">=</span> <span class="n">e</span> <span class="c1">// Two-dimensional sequence</span>
</pre></div>
</div>
<p>Note: the bounds in finite sequences (those with <cite>..</cite>) are type
expressions, while the bounds in infinite sequences are value
expressions.</p>
<table class="docutils align-default" id="id1">
<caption><span class="caption-text">Sequence operations.</span><a class="headerlink" href="#id1" title="Permalink to this table"></a></caption>
<colgroup>
<col style="width: 40%" />
<col style="width: 60%" />
</colgroup>
<thead>
<tr class="row-odd"><th class="head"><p>Operator</p></th>
<th class="head"><p>Description</p></th>
</tr>
</thead>
<tbody>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">#</span></code></p></td>
<td><p>Sequence concatenation</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">&gt;&gt;</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;&lt;</span></code></p></td>
<td><p>Shift (right, left)</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">&gt;&gt;&gt;</span></code> <code class="docutils literal notranslate"><span class="pre">&lt;&lt;&lt;</span></code></p></td>
<td><p>Rotate (right, left)</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">&gt;&gt;$</span></code></p></td>
<td><p>Arithmetic right shift (on bitvectors only)</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">&#64;</span></code> <code class="docutils literal notranslate"><span class="pre">!</span></code></p></td>
<td><p>Access elements (front, back)</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">&#64;&#64;</span></code> <code class="docutils literal notranslate"><span class="pre">!!</span></code></p></td>
<td><p>Access sub-sequence (front, back)</p></td>
</tr>
<tr class="row-even"><td><p><code class="docutils literal notranslate"><span class="pre">update</span></code> <code class="docutils literal notranslate"><span class="pre">updateEnd</span></code></p></td>
<td><p>Update the value of a sequence at
a location
(front, back)</p></td>
</tr>
<tr class="row-odd"><td><p><code class="docutils literal notranslate"><span class="pre">updates</span></code> <code class="docutils literal notranslate"><span class="pre">updatesEnd</span></code></p></td>
<td><p>Update multiple values of a sequence
(front, back)</p></td>
</tr>
</tbody>
</table>
<p>There are also lifted pointwise operations.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="p">[</span><span class="n">p1</span><span class="p">,</span> <span class="n">p2</span><span class="p">,</span> <span class="n">p3</span><span class="p">,</span> <span class="n">p4</span><span class="p">]</span> <span class="c1">// Sequence pattern</span>
<span class="nf">p1</span> <span class="o">#</span> <span class="n">p2</span> <span class="c1">// Split sequence pattern</span>
</pre></div>
</div>
</div>
<div class="section" id="functions">
<h2>Functions<a class="headerlink" href="#functions" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">\</span><span class="n">p1</span> <span class="n">p2</span> <span class="ow">-&gt;</span> <span class="n">e</span> <span class="c1">// Lambda expression</span>
<span class="nf">f</span> <span class="n">p1</span> <span class="n">p2</span> <span class="ow">=</span> <span class="n">e</span> <span class="c1">// Function definition</span>
</pre></div>
</div>
</div>
</div>
</div>
</div>
<footer><div class="rst-footer-buttons" role="navigation" aria-label="Footer">
<a href="Expressions.html" class="btn btn-neutral float-left" title="Expressions" accesskey="p" rel="prev"><span class="fa fa-arrow-circle-left" aria-hidden="true"></span> Previous</a>
<a href="OverloadedOperations.html" class="btn btn-neutral float-right" title="Overloaded Operations" accesskey="n" rel="next">Next <span class="fa fa-arrow-circle-right" aria-hidden="true"></span></a>
</div>
<hr/>
<div role="contentinfo">
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</body>
</html>

View File

@ -0,0 +1,244 @@
<!DOCTYPE html>
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Expressions &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="search.html" />
<link rel="next" title="Basic Types" href="BasicTypes.html" />
<link rel="prev" title="Basic Syntax" href="BasicSyntax.html" />
</head>
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
<input type="hidden" name="check_keywords" value="yes" />
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul class="current">
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1 current"><a class="current reference internal" href="#">Expressions</a><ul>
<li class="toctree-l2"><a class="reference internal" href="#calling-functions">Calling Functions</a></li>
<li class="toctree-l2"><a class="reference internal" href="#prefix-operators">Prefix Operators</a></li>
<li class="toctree-l2"><a class="reference internal" href="#infix-functions">Infix Functions</a></li>
<li class="toctree-l2"><a class="reference internal" href="#type-annotations">Type Annotations</a></li>
<li class="toctree-l2"><a class="reference internal" href="#explicit-type-instantiation">Explicit Type Instantiation</a></li>
<li class="toctree-l2"><a class="reference internal" href="#local-declarations">Local Declarations</a></li>
<li class="toctree-l2"><a class="reference internal" href="#block-arguments">Block Arguments</a></li>
<li class="toctree-l2"><a class="reference internal" href="#conditionals">Conditionals</a></li>
<li class="toctree-l2"><a class="reference internal" href="#demoting-numeric-types-to-values">Demoting Numeric Types to Values</a></li>
</ul>
</li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Expressions</li>
<li class="wy-breadcrumbs-aside">
<a href="_sources/Expressions.rst.txt" rel="nofollow"> View page source</a>
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<div class="section" id="expressions">
<h1>Expressions<a class="headerlink" href="#expressions" title="Permalink to this headline"></a></h1>
<p>This section provides an overview of the Cryptols expression syntax.</p>
<div class="section" id="calling-functions">
<h2>Calling Functions<a class="headerlink" href="#calling-functions" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span> <span class="mi">2</span> <span class="c1">// call `f` with parameter `2`</span>
<span class="nf">g</span> <span class="n">x</span> <span class="n">y</span> <span class="c1">// call `g` with two parameters: `x` and `y`</span>
<span class="nf">h</span> <span class="p">(</span><span class="n">x</span><span class="p">,</span><span class="n">y</span><span class="p">)</span> <span class="c1">// call `h` with one parameter, the pair `(x,y)`</span>
</pre></div>
</div>
</div>
<div class="section" id="prefix-operators">
<h2>Prefix Operators<a class="headerlink" href="#prefix-operators" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="o">-</span><span class="mi">2</span> <span class="c1">// call unary `-` with parameter `2`</span>
<span class="o">-</span> <span class="mi">2</span> <span class="c1">// call unary `-` with parameter `2`</span>
<span class="nf">f</span> <span class="p">(</span><span class="o">-</span><span class="mi">2</span><span class="p">)</span> <span class="c1">// call `f` with one argument: `-2`, parens are important</span>
<span class="o">-</span><span class="n">f</span> <span class="mi">2</span> <span class="c1">// call unary `-` with parameter `f 2`</span>
<span class="o">-</span> <span class="n">f</span> <span class="mi">2</span> <span class="c1">// call unary `-` with parameter `f 2`</span>
</pre></div>
</div>
</div>
<div class="section" id="infix-functions">
<h2>Infix Functions<a class="headerlink" href="#infix-functions" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="mi">2</span> <span class="o">+</span> <span class="mi">3</span> <span class="c1">// call `+` with two parameters: `2` and `3`</span>
<span class="mi">2</span> <span class="o">+</span> <span class="mi">3</span> <span class="o">*</span> <span class="mi">5</span> <span class="c1">// call `+` with two parameters: `2` and `3 * 5`</span>
<span class="p">(</span><span class="o">+</span><span class="p">)</span> <span class="mi">2</span> <span class="mi">3</span> <span class="c1">// call `+` with two parameters: `2` and `3`</span>
<span class="nf">f</span> <span class="mi">2</span> <span class="o">+</span> <span class="n">g</span> <span class="mi">3</span> <span class="c1">// call `+` with two parameters: `f 2` and `g 3`</span>
<span class="o">-</span> <span class="mi">2</span> <span class="o">+</span> <span class="o">-</span> <span class="mi">3</span> <span class="c1">// call `+` with two parameters: `-2` and `-3`</span>
<span class="o">-</span> <span class="n">f</span> <span class="mi">2</span> <span class="o">+</span> <span class="o">-</span> <span class="n">g</span> <span class="mi">3</span>
</pre></div>
</div>
</div>
<div class="section" id="type-annotations">
<h2>Type Annotations<a class="headerlink" href="#type-annotations" title="Permalink to this headline"></a></h2>
<p>Explicit type annotations may be added on expressions, patterns, and
in argument definitions.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">x</span> <span class="kt">:</span> <span class="kr">Bit</span> <span class="c1">// specify that `x` has type `Bit`</span>
<span class="nf">f</span> <span class="n">x</span> <span class="kt">:</span> <span class="kr">Bit</span> <span class="c1">// specify that `f x` has type `Bit`</span>
<span class="o">-</span> <span class="n">f</span> <span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span> <span class="c1">// specify that `- f x` has type `[8]`</span>
<span class="mi">2</span> <span class="o">+</span> <span class="mi">3</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span> <span class="c1">// specify that `2 + 3` has type `[8]`</span>
<span class="nf">\</span><span class="n">x</span> <span class="ow">-&gt;</span> <span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span> <span class="c1">// type annotation is on `x`, not the function</span>
<span class="kr">if</span> <span class="n">x</span>
<span class="kr">then</span> <span class="n">y</span>
<span class="kr">else</span> <span class="n">z</span> <span class="kt">:</span> <span class="kr">Bit</span> <span class="c1">// the type annotation is on `z`, not the whole `if`</span>
<span class="p">[</span><span class="mi">1</span><span class="o">..</span><span class="mi">9</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]]</span> <span class="c1">// specify that elements in `[1..9]` have type `[8]`</span>
<span class="nf">f</span> <span class="p">(</span><span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">])</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">1</span> <span class="c1">// type annotation on patterns</span>
</pre></div>
</div>
<div class="admonition-todo admonition" id="id1">
<p class="admonition-title">Todo</p>
<p>Patterns with type variables</p>
</div>
</div>
<div class="section" id="explicit-type-instantiation">
<h2>Explicit Type Instantiation<a class="headerlink" href="#explicit-type-instantiation" title="Permalink to this headline"></a></h2>
<p>If <code class="docutils literal notranslate"><span class="pre">f</span></code> is a polymorphic value with type:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span> <span class="kt">:</span> <span class="p">{</span> <span class="n">tyParam</span> <span class="p">}</span> <span class="n">tyParam</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="n">zero</span>
</pre></div>
</div>
<p>you can evaluate <code class="docutils literal notranslate"><span class="pre">f</span></code>, passing it a type parameter:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span> <span class="p">`{</span> <span class="n">tyParam</span> <span class="ow">=</span> <span class="mi">13</span> <span class="p">}</span>
</pre></div>
</div>
</div>
<div class="section" id="local-declarations">
<h2>Local Declarations<a class="headerlink" href="#local-declarations" title="Permalink to this headline"></a></h2>
<p>Local declarations have the weakest precedence of all expressions.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="mi">2</span> <span class="o">+</span> <span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="kt">T</span><span class="p">]</span>
<span class="kr">where</span>
<span class="kr">type</span> <span class="kt">T</span> <span class="ow">=</span> <span class="mi">8</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mi">2</span> <span class="c1">// `T` and `x` are in scope of `2 + x : `[T]`</span>
<span class="kr">if</span> <span class="n">x</span> <span class="kr">then</span> <span class="mi">1</span> <span class="kr">else</span> <span class="mi">2</span>
<span class="kr">where</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">2</span> <span class="c1">// `x` is in scope in the whole `if`</span>
<span class="nf">\</span><span class="n">y</span> <span class="ow">-&gt;</span> <span class="n">x</span> <span class="o">+</span> <span class="n">y</span>
<span class="kr">where</span> <span class="n">x</span> <span class="ow">=</span> <span class="mi">2</span> <span class="c1">// `y` is not in scope in the defintion of `x`</span>
</pre></div>
</div>
</div>
<div class="section" id="block-arguments">
<h2>Block Arguments<a class="headerlink" href="#block-arguments" title="Permalink to this headline"></a></h2>
<p>When used as the last argument to a function call,
<code class="docutils literal notranslate"><span class="pre">if</span></code> and lambda expressions do not need parens:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">f</span> <span class="nf">\</span><span class="n">x</span> <span class="ow">-&gt;</span> <span class="n">x</span> <span class="c1">// call `f` with one argument `x -&gt; x`</span>
<span class="mi">2</span> <span class="o">+</span> <span class="kr">if</span> <span class="n">x</span>
<span class="kr">then</span> <span class="n">y</span>
<span class="kr">else</span> <span class="n">z</span> <span class="c1">// call `+` with two arguments: `2` and `if ...`</span>
</pre></div>
</div>
</div>
<div class="section" id="conditionals">
<h2>Conditionals<a class="headerlink" href="#conditionals" title="Permalink to this headline"></a></h2>
<p>The <code class="docutils literal notranslate"><span class="pre">if</span> <span class="pre">...</span> <span class="pre">then</span> <span class="pre">...</span> <span class="pre">else</span></code> construct can be used with
multiple branches. For example:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">x</span> <span class="ow">=</span> <span class="kr">if</span> <span class="n">y</span> <span class="o">%</span> <span class="mi">2</span> <span class="o">==</span> <span class="mi">0</span> <span class="kr">then</span> <span class="mi">22</span> <span class="kr">else</span> <span class="mi">33</span>
<span class="nf">x</span> <span class="ow">=</span> <span class="kr">if</span> <span class="n">y</span> <span class="o">%</span> <span class="mi">2</span> <span class="o">==</span> <span class="mi">0</span> <span class="kr">then</span> <span class="mi">1</span>
<span class="o">|</span> <span class="n">y</span> <span class="o">%</span> <span class="mi">3</span> <span class="o">==</span> <span class="mi">0</span> <span class="kr">then</span> <span class="mi">2</span>
<span class="o">|</span> <span class="n">y</span> <span class="o">%</span> <span class="mi">5</span> <span class="o">==</span> <span class="mi">0</span> <span class="kr">then</span> <span class="mi">3</span>
<span class="kr">else</span> <span class="mi">7</span>
</pre></div>
</div>
</div>
<div class="section" id="demoting-numeric-types-to-values">
<h2>Demoting Numeric Types to Values<a class="headerlink" href="#demoting-numeric-types-to-values" title="Permalink to this headline"></a></h2>
<p>The value corresponding to a numeric type may be accessed using the
following notation:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="p">`</span><span class="n">t</span>
</pre></div>
</div>
<p>Here <cite>t</cite> should be a finite type expression with numeric kind. The resulting
expression will be of a numeric base type, which is sufficiently large
to accommodate the value of the type:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="p">`</span><span class="n">t</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Literal</span> <span class="n">t</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span>
</pre></div>
</div>
<p>This backtick notation is syntax sugar for an application of the
<cite>number</cite> primtive, so the above may be written as:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">number</span><span class="p">`{</span><span class="n">t</span><span class="p">}</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Literal</span> <span class="n">t</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span>
</pre></div>
</div>
<p>If a type cannot be inferred from context, a suitable type will be
automatically chosen if possible, usually <cite>Integer</cite>.</p>
</div>
</div>
</div>
</div>
<footer><div class="rst-footer-buttons" role="navigation" aria-label="Footer">
<a href="BasicSyntax.html" class="btn btn-neutral float-left" title="Basic Syntax" accesskey="p" rel="prev"><span class="fa fa-arrow-circle-left" aria-hidden="true"></span> Previous</a>
<a href="BasicTypes.html" class="btn btn-neutral float-right" title="Basic Types" accesskey="n" rel="next">Next <span class="fa fa-arrow-circle-right" aria-hidden="true"></span></a>
</div>
<hr/>
<div role="contentinfo">
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</body>
</html>

View File

@ -0,0 +1,690 @@
<!DOCTYPE html>
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Modules &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="search.html" />
<link rel="prev" title="Type Declarations" href="TypeDeclarations.html" />
</head>
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
<input type="hidden" name="check_keywords" value="yes" />
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul class="current">
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1 current"><a class="current reference internal" href="#">Modules</a><ul>
<li class="toctree-l2"><a class="reference internal" href="#hierarchical-module-names">Hierarchical Module Names</a></li>
<li class="toctree-l2"><a class="reference internal" href="#module-imports">Module Imports</a><ul>
<li class="toctree-l3"><a class="reference internal" href="#import-lists">Import Lists</a></li>
<li class="toctree-l3"><a class="reference internal" href="#hiding-imports">Hiding Imports</a></li>
<li class="toctree-l3"><a class="reference internal" href="#qualified-module-imports">Qualified Module Imports</a></li>
</ul>
</li>
<li class="toctree-l2"><a class="reference internal" href="#private-blocks">Private Blocks</a></li>
<li class="toctree-l2"><a class="reference internal" href="#nested-modules">Nested Modules</a><ul>
<li class="toctree-l3"><a class="reference internal" href="#implicit-imports">Implicit Imports</a></li>
<li class="toctree-l3"><a class="reference internal" href="#managing-module-names">Managing Module Names</a></li>
</ul>
</li>
<li class="toctree-l2"><a class="reference internal" href="#parameterized-modules">Parameterized Modules</a><ul>
<li class="toctree-l3"><a class="reference internal" href="#interface-modules">Interface Modules</a></li>
<li class="toctree-l3"><a class="reference internal" href="#importing-an-interface-module">Importing an Interface Module</a></li>
<li class="toctree-l3"><a class="reference internal" href="#interface-constraints">Interface Constraints</a></li>
<li class="toctree-l3"><a class="reference internal" href="#instantiating-a-parameterized-module">Instantiating a Parameterized Module</a></li>
<li class="toctree-l3"><a class="reference internal" href="#anonymous-interface-modules">Anonymous Interface Modules</a></li>
<li class="toctree-l3"><a class="reference internal" href="#anonymous-instantiation-arguments">Anonymous Instantiation Arguments</a></li>
</ul>
</li>
</ul>
</li>
</ul>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Modules</li>
<li class="wy-breadcrumbs-aside">
<a href="_sources/Modules.rst.txt" rel="nofollow"> View page source</a>
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<div class="section" id="modules">
<h1>Modules<a class="headerlink" href="#modules" title="Permalink to this headline"></a></h1>
<p>A <em>module</em> is used to group some related definitions. Each file may
contain at most one top-level module.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="kt">T</span> <span class="ow">=</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mi">10</span>
</pre></div>
</div>
<div class="section" id="hierarchical-module-names">
<h2>Hierarchical Module Names<a class="headerlink" href="#hierarchical-module-names" title="Permalink to this headline"></a></h2>
<p>Module may have either simple or <em>hierarchical</em> names.
Hierarchical names are constructed by gluing together ordinary
identifiers using the symbol <code class="docutils literal notranslate"><span class="pre">::</span></code>.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">Hash</span><span class="ow">::</span><span class="kt">SHA256</span> <span class="kr">where</span>
<span class="nf">sha256</span> <span class="ow">=</span> <span class="o">...</span>
</pre></div>
</div>
<p>The structure in the name may be used to group together related
modules. Also, the Cryptol implementation uses the structure of the
name to locate the file containing the definition of the module.
For example, when searching for module <code class="docutils literal notranslate"><span class="pre">Hash::SHA256</span></code>, Cryptol
will look for a file named <code class="docutils literal notranslate"><span class="pre">SHA256.cry</span></code> in a directory called
<code class="docutils literal notranslate"><span class="pre">Hash</span></code>, contained in one of the directories specified by <code class="docutils literal notranslate"><span class="pre">CRYPTOLPATH</span></code>.</p>
</div>
<div class="section" id="module-imports">
<h2>Module Imports<a class="headerlink" href="#module-imports" title="Permalink to this headline"></a></h2>
<p>To use the definitions from one module in another module, we use
<code class="docutils literal notranslate"><span class="pre">import</span></code> declarations:</p>
<div class="literal-block-wrapper docutils container" id="id1">
<div class="code-block-caption"><span class="caption-text">module M</span><a class="headerlink" href="#id1" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="c1">// Provide some definitions</span>
<span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mi">2</span>
</pre></div>
</div>
</div>
<div class="literal-block-wrapper docutils container" id="id2">
<div class="code-block-caption"><span class="caption-text">module N</span><a class="headerlink" href="#id2" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="c1">// Uses definitions from `M`</span>
<span class="kr">module</span> <span class="nn">N</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">M</span> <span class="c1">// import all definitions from `M`</span>
<span class="nf">g</span> <span class="ow">=</span> <span class="n">f</span> <span class="c1">// `f` was imported from `M`</span>
</pre></div>
</div>
</div>
<div class="section" id="import-lists">
<h3>Import Lists<a class="headerlink" href="#import-lists" title="Permalink to this headline"></a></h3>
<p>Sometimes, we may want to import only some of the definitions
from a module. To do so, we use an import declaration with
an <em>import list</em>.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mh">0x02</span>
<span class="nf">g</span> <span class="ow">=</span> <span class="mh">0x03</span>
<span class="nf">h</span> <span class="ow">=</span> <span class="mh">0x04</span>
</pre></div>
</div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">N</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">M</span><span class="p">(</span><span class="n">f</span><span class="p">,</span><span class="n">g</span><span class="p">)</span> <span class="c1">// Imports only `f` and `g`, but not `h`</span>
<span class="nf">x</span> <span class="ow">=</span> <span class="n">f</span> <span class="o">+</span> <span class="n">g</span>
</pre></div>
</div>
<p>Using explicit import lists helps reduce name collisions.
It also tends to make code easier to understand, because
it makes it easy to see the source of definitions.</p>
</div>
<div class="section" id="hiding-imports">
<h3>Hiding Imports<a class="headerlink" href="#hiding-imports" title="Permalink to this headline"></a></h3>
<p>Sometimes a module may provide many definitions, and we want to use
most of them but with a few exceptions (e.g., because those would
result to a name clash). In such situations it is convenient
to use a <em>hiding</em> import:</p>
<div class="literal-block-wrapper docutils container" id="id3">
<div class="code-block-caption"><span class="caption-text">module M</span><a class="headerlink" href="#id3" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mh">0x02</span>
<span class="nf">g</span> <span class="ow">=</span> <span class="mh">0x03</span>
<span class="nf">h</span> <span class="ow">=</span> <span class="mh">0x04</span>
</pre></div>
</div>
</div>
<div class="literal-block-wrapper docutils container" id="id4">
<div class="code-block-caption"><span class="caption-text">module N</span><a class="headerlink" href="#id4" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">N</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">M</span> <span class="k">hiding</span> <span class="p">(</span><span class="nf">h</span><span class="p">)</span> <span class="c1">// Import everything but `h`</span>
<span class="nf">x</span> <span class="ow">=</span> <span class="n">f</span> <span class="o">+</span> <span class="n">g</span>
</pre></div>
</div>
</div>
</div>
<div class="section" id="qualified-module-imports">
<h3>Qualified Module Imports<a class="headerlink" href="#qualified-module-imports" title="Permalink to this headline"></a></h3>
<p>Another way to avoid name collisions is by using a
<em>qualified</em> import.</p>
<div class="literal-block-wrapper docutils container" id="id5">
<div class="code-block-caption"><span class="caption-text">module M</span><a class="headerlink" href="#id5" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mi">2</span>
</pre></div>
</div>
</div>
<div class="literal-block-wrapper docutils container" id="id6">
<div class="code-block-caption"><span class="caption-text">module N</span><a class="headerlink" href="#id6" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">N</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">M</span> <span class="k">as</span> <span class="n">P</span>
<span class="nf">g</span> <span class="ow">=</span> <span class="kt">P</span><span class="ow">::</span><span class="n">f</span>
<span class="c1">// `f` was imported from `M`</span>
<span class="c1">// but when used it needs to be prefixed by the qualifier `P`</span>
</pre></div>
</div>
</div>
<p>Qualified imports make it possible to work with definitions
that happen to have the same name but are defined in different modules.</p>
<p>Qualified imports may be combined with import lists or hiding clauses:</p>
<div class="literal-block-wrapper docutils container" id="id7">
<div class="code-block-caption"><span class="caption-text">Example</span><a class="headerlink" href="#id7" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">import</span> <span class="nn">A</span> <span class="k">as</span> <span class="n">B</span> <span class="p">(</span><span class="n">f</span><span class="p">)</span> <span class="c1">// introduces B::f</span>
<span class="kr">import</span> <span class="nn">X</span> <span class="k">as</span> <span class="n">Y</span> <span class="n">hiding</span> <span class="p">(</span><span class="n">f</span><span class="p">)</span> <span class="c1">// introduces everything but `f` from X</span>
<span class="c1">// using the prefix `X`</span>
</pre></div>
</div>
</div>
<p>It is also possible to use the same qualifier prefix for imports
from different modules. For example:</p>
<div class="literal-block-wrapper docutils container" id="id8">
<div class="code-block-caption"><span class="caption-text">Example</span><a class="headerlink" href="#id8" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">import</span> <span class="nn">A</span> <span class="k">as</span> <span class="n">B</span>
<span class="kr">import</span> <span class="nn">X</span> <span class="k">as</span> <span class="n">B</span>
</pre></div>
</div>
</div>
<p>Such declarations will introduces all definitions from <code class="docutils literal notranslate"><span class="pre">A</span></code> and <code class="docutils literal notranslate"><span class="pre">X</span></code>
but to use them, you would have to qualify using the prefix <code class="docutils literal notranslate"><span class="pre">B::</span></code>.</p>
</div>
</div>
<div class="section" id="private-blocks">
<h2>Private Blocks<a class="headerlink" href="#private-blocks" title="Permalink to this headline"></a></h2>
<p>In some cases, definitions in a module might use helper
functions that are not intended to be used outside the module.
It is good practice to place such declarations in <em>private blocks</em>:</p>
<div class="literal-block-wrapper docutils container" id="id9">
<div class="code-block-caption"><span class="caption-text">Private blocks</span><a class="headerlink" href="#id9" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mh">0x01</span> <span class="o">+</span> <span class="n">helper1</span> <span class="o">+</span> <span class="n">helper2</span>
<span class="nf">private</span>
<span class="n">helper1</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="n">helper1</span> <span class="ow">=</span> <span class="mi">2</span>
<span class="n">helper2</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="n">helper2</span> <span class="ow">=</span> <span class="mi">3</span>
</pre></div>
</div>
</div>
<p>The private block only needs to be indented if it might be followed by
additional public declarations. If all remaining declarations are to be
private then no additional indentation is needed as the <code class="docutils literal notranslate"><span class="pre">private</span></code> block will
extend to the end of the module.</p>
<div class="literal-block-wrapper docutils container" id="id10">
<div class="code-block-caption"><span class="caption-text">Private blocks</span><a class="headerlink" href="#id10" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mh">0x01</span> <span class="o">+</span> <span class="n">helper1</span> <span class="o">+</span> <span class="n">helper2</span>
<span class="nf">private</span>
<span class="nf">helper1</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">helper1</span> <span class="ow">=</span> <span class="mi">2</span>
<span class="nf">helper2</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">helper2</span> <span class="ow">=</span> <span class="mi">3</span>
</pre></div>
</div>
</div>
<p>The keyword <code class="docutils literal notranslate"><span class="pre">private</span></code> introduces a new layout scope, and all declarations
in the block are considered to be private to the module. A single module
may contain multiple private blocks. For example, the following module
is equivalent to the previous one:</p>
<div class="literal-block-wrapper docutils container" id="id11">
<div class="code-block-caption"><span class="caption-text">Private blocks</span><a class="headerlink" href="#id11" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="nf">f</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="nf">f</span> <span class="ow">=</span> <span class="mh">0x01</span> <span class="o">+</span> <span class="n">helper1</span> <span class="o">+</span> <span class="n">helper2</span>
<span class="nf">private</span>
<span class="n">helper1</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="n">helper1</span> <span class="ow">=</span> <span class="mi">2</span>
<span class="nf">private</span>
<span class="n">helper2</span> <span class="kt">:</span> <span class="p">[</span><span class="mi">8</span><span class="p">]</span>
<span class="n">helper2</span> <span class="ow">=</span> <span class="mi">3</span>
</pre></div>
</div>
</div>
</div>
<div class="section" id="nested-modules">
<h2>Nested Modules<a class="headerlink" href="#nested-modules" title="Permalink to this headline"></a></h2>
<p>Module may be declared withing other modules, using the <code class="docutils literal notranslate"><span class="pre">submodule</span></code> keword.</p>
<div class="literal-block-wrapper docutils container" id="id12">
<div class="code-block-caption"><span class="caption-text">Declaring a nested module called N</span><a class="headerlink" href="#id12" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mh">0x02</span>
<span class="n">submodule</span> <span class="kt">N</span> <span class="kr">where</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">2</span>
</pre></div>
</div>
</div>
<p>Submodules may refer to names in their enclosing scope.
Declarations in a sub-module will shadow names in the outer scope.</p>
<p>Declarations in a submdule may be imported with <code class="docutils literal notranslate"><span class="pre">import</span> <span class="pre">submodule</span></code>,
which works just like an ordinary import except that <code class="docutils literal notranslate"><span class="pre">X</span></code> refers
to the name of a submodule.</p>
<div class="literal-block-wrapper docutils container" id="id13">
<div class="code-block-caption"><span class="caption-text">Using declarations from a submodule.</span><a class="headerlink" href="#id13" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mh">0x02</span>
<span class="n">submodule</span> <span class="kt">N</span> <span class="kr">where</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">2</span>
<span class="kr">import</span> <span class="nn">submodule</span> <span class="kt">N</span> <span class="n">as</span> <span class="kt">P</span>
<span class="n">z</span> <span class="ow">=</span> <span class="mi">2</span> <span class="o">*</span> <span class="kt">P</span><span class="ow">::</span><span class="n">y</span>
</pre></div>
</div>
</div>
<p>Note that recursive definitions across modules are not allowed.
So, in the previous example, it would be an error if <code class="docutils literal notranslate"><span class="pre">y</span></code> was
to try to use <code class="docutils literal notranslate"><span class="pre">z</span></code> in its definition.</p>
<div class="section" id="implicit-imports">
<h3>Implicit Imports<a class="headerlink" href="#implicit-imports" title="Permalink to this headline"></a></h3>
<p>For convenience, we add an implicit qualified submodule import for
each locally defined submodules.</p>
<div class="literal-block-wrapper docutils container" id="id14">
<div class="code-block-caption"><span class="caption-text">Making use of the implicit import for a submodule.</span><a class="headerlink" href="#id14" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mh">0x02</span>
<span class="n">submodule</span> <span class="kt">N</span> <span class="kr">where</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">2</span>
<span class="n">z</span> <span class="ow">=</span> <span class="mi">2</span> <span class="o">*</span> <span class="kt">N</span><span class="ow">::</span><span class="n">y</span>
</pre></div>
</div>
</div>
<p><code class="docutils literal notranslate"><span class="pre">N::y</span></code> works in the previous example because Cryptol added
an implicit import <code class="docutils literal notranslate"><span class="pre">import</span> <span class="pre">submoulde</span> <span class="pre">N</span> <span class="pre">as</span> <span class="pre">N</span></code>.</p>
</div>
<div class="section" id="managing-module-names">
<h3>Managing Module Names<a class="headerlink" href="#managing-module-names" title="Permalink to this headline"></a></h3>
<p>The names of nested modules are managed by the module system just
like the name of any other declaration in Cryptol. Thus, nested
modules may declared in the public or private sections of their
containing module, and need to be imported before they can be used.
Thus, to use a submodule defined in top-level module <code class="docutils literal notranslate"><span class="pre">A</span></code> into
another top-level module <code class="docutils literal notranslate"><span class="pre">B</span></code> requires two steps:</p>
<blockquote>
<div><ol class="arabic simple">
<li><p>First we need to import <code class="docutils literal notranslate"><span class="pre">A</span></code> to bring the name of the submodule in scope</p></li>
<li><p>Then we need to import the submodule to bring the names defined in it in scope.</p></li>
</ol>
</div></blockquote>
<div class="literal-block-wrapper docutils container" id="id15">
<div class="code-block-caption"><span class="caption-text">Using a nested module from a different top-level module.</span><a class="headerlink" href="#id15" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">A</span> <span class="kr">where</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mh">0x02</span>
<span class="n">submodule</span> <span class="kt">N</span> <span class="kr">where</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">2</span>
<span class="kr">module</span> <span class="nn">B</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">A</span> <span class="c1">// Brings `N` in scope</span>
<span class="kr">import</span> <span class="nn">submodule</span> <span class="kt">N</span> <span class="c1">// Brings `y` in scope</span>
<span class="n">z</span> <span class="ow">=</span> <span class="mi">2</span> <span class="o">*</span> <span class="n">y</span>
</pre></div>
</div>
</div>
</div>
</div>
<div class="section" id="parameterized-modules">
<h2>Parameterized Modules<a class="headerlink" href="#parameterized-modules" title="Permalink to this headline"></a></h2>
<div class="section" id="interface-modules">
<h3>Interface Modules<a class="headerlink" href="#interface-modules" title="Permalink to this headline"></a></h3>
<p>An <em>interface module</em> describes the content of a module
without providing a concrete implementation.</p>
<div class="literal-block-wrapper docutils container" id="id16">
<div class="code-block-caption"><span class="caption-text">An interface module.</span><a class="headerlink" href="#id16" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">interface</span> <span class="kr">module</span> <span class="nn">I</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span> <span class="c1">// `n` is a numeric type</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="c1">// Assumptions about the declared numeric type</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span> <span class="c1">// A declarations of a constant</span>
</pre></div>
</div>
</div>
<p>Like other modules, interfaces modules may be nested in
other modules:</p>
<div class="literal-block-wrapper docutils container" id="id17">
<div class="code-block-caption"><span class="caption-text">A nested interface module</span><a class="headerlink" href="#id17" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="n">interface</span> <span class="n">submodule</span> <span class="kt">I</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span> <span class="c1">// `n` is a numeric type</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="c1">// Assumptions about the declared numeric type</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span> <span class="c1">// A declarations of a constant</span>
</pre></div>
</div>
</div>
</div>
<div class="section" id="importing-an-interface-module">
<h3>Importing an Interface Module<a class="headerlink" href="#importing-an-interface-module" title="Permalink to this headline"></a></h3>
<p>A module may be parameterized by importing an interface,
instead of a concrete module</p>
<div class="literal-block-wrapper docutils container" id="id18">
<div class="code-block-caption"><span class="caption-text">A parameterized module</span><a class="headerlink" href="#id18" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="c1">// The interface desribes the parmaeters</span>
<span class="nf">interface</span> <span class="kr">module</span> <span class="nn">I</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="c1">// This module is parameterized</span>
<span class="kr">module</span> <span class="nn">F</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span>
<span class="n">y</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">1</span>
</pre></div>
</div>
</div>
<p>To import a nested interface use <code class="docutils literal notranslate"><span class="pre">import</span> <span class="pre">interface</span> <span class="pre">sumbodule</span> <span class="pre">I</span></code>
and make sure that <code class="docutils literal notranslate"><span class="pre">I</span></code> is in scope.</p>
<p>It is also possible to import multiple interface modules,
or the same interface module more than once. Each import
of an interface module maybe be linked to a different concrete
module, as described in <a class="reference internal" href="#instantiating-modules"><span class="std std-ref">Instantiating a Parameterized Module</span></a>.</p>
<div class="literal-block-wrapper docutils container" id="id19">
<div class="code-block-caption"><span class="caption-text">Multiple interface parameters</span><a class="headerlink" href="#id19" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">interface</span> <span class="kr">module</span> <span class="nn">I</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="kr">module</span> <span class="nn">F</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span> <span class="n">as</span> <span class="kt">I</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span> <span class="n">as</span> <span class="kt">J</span>
<span class="n">y</span> <span class="kt">:</span> <span class="p">[</span><span class="kt">I</span><span class="ow">::</span><span class="n">n</span><span class="p">]</span>
<span class="n">y</span> <span class="ow">=</span> <span class="kt">I</span><span class="ow">::</span><span class="n">x</span> <span class="o">+</span> <span class="mi">1</span>
<span class="n">z</span> <span class="kt">:</span> <span class="p">[</span><span class="kt">J</span><span class="ow">::</span><span class="n">n</span><span class="p">]</span>
<span class="n">z</span> <span class="ow">=</span> <span class="kt">J</span><span class="ow">::</span><span class="n">x</span> <span class="o">+</span> <span class="mi">1</span>
</pre></div>
</div>
</div>
</div>
<div class="section" id="interface-constraints">
<h3>Interface Constraints<a class="headerlink" href="#interface-constraints" title="Permalink to this headline"></a></h3>
<p>When working with multiple interfaces, it is to useful
to be able to impose additional constraints on the
types imported from the interface.</p>
<div class="literal-block-wrapper docutils container" id="id20">
<div class="code-block-caption"><span class="caption-text">Adding constraints to interface parameters</span><a class="headerlink" href="#id20" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">interface</span> <span class="kr">module</span> <span class="nn">I</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="kr">module</span> <span class="nn">F</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span> <span class="n">as</span> <span class="kt">I</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span> <span class="n">as</span> <span class="kt">J</span>
<span class="n">interface</span> <span class="n">constraint</span> <span class="p">(</span><span class="kt">I</span><span class="ow">::</span><span class="n">n</span> <span class="o">==</span> <span class="kt">J</span><span class="ow">::</span><span class="n">n</span><span class="p">)</span>
<span class="n">y</span> <span class="kt">:</span> <span class="p">[</span><span class="kt">I</span><span class="ow">::</span><span class="n">n</span><span class="p">]</span>
<span class="n">y</span> <span class="ow">=</span> <span class="kt">I</span><span class="ow">::</span><span class="n">x</span> <span class="o">+</span> <span class="kt">J</span><span class="ow">::</span><span class="n">x</span>
</pre></div>
</div>
</div>
<p>In this example we impose the constraint that <code class="docutils literal notranslate"><span class="pre">n</span></code>
(the width of <code class="docutils literal notranslate"><span class="pre">x</span></code>) in both interfaces must be the
same. Note that, of course, the two instantiations
may provide different values for <code class="docutils literal notranslate"><span class="pre">x</span></code>.</p>
</div>
<div class="section" id="instantiating-a-parameterized-module">
<span id="instantiating-modules"></span><h3>Instantiating a Parameterized Module<a class="headerlink" href="#instantiating-a-parameterized-module" title="Permalink to this headline"></a></h3>
<p>To use a parameterized module we need to provide concrete
implementations for the interfaces that it uses, and provide
a name for the resulting module. This is done as follows:</p>
<div class="literal-block-wrapper docutils container" id="id21">
<div class="code-block-caption"><span class="caption-text">Instantiating a parameterized module using a single interface.</span><a class="headerlink" href="#id21" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">interface</span> <span class="kr">module</span> <span class="nn">I</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="kr">module</span> <span class="nn">F</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span>
<span class="n">y</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="mi">1</span>
<span class="kr">module</span> <span class="nn">Impl</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="ow">=</span> <span class="mi">8</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mi">26</span>
<span class="kr">module</span> <span class="nn">MyF</span> <span class="ow">=</span> <span class="kt">F</span> <span class="p">{</span> <span class="kt">Impl</span> <span class="p">}</span>
</pre></div>
</div>
</div>
<p>Here we defined a new module called <code class="docutils literal notranslate"><span class="pre">MyF</span></code> which is
obtained by filling in module <code class="docutils literal notranslate"><span class="pre">Impl</span></code> for the interface
used by <code class="docutils literal notranslate"><span class="pre">F</span></code>.</p>
<p>If a module is parameterized my multiple interfaces
we need to provide an implementation module for each
interface, using a slight variation on the previous notation.</p>
<div class="literal-block-wrapper docutils container" id="id22">
<div class="code-block-caption"><span class="caption-text">Instantiating a parameterized module by name.</span><a class="headerlink" href="#id22" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="c1">// I is defined as above</span>
<span class="kr">module</span> <span class="nn">F</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span> <span class="n">as</span> <span class="kt">I</span>
<span class="kr">import</span> <span class="nn">interface</span> <span class="kt">I</span> <span class="n">as</span> <span class="kt">J</span>
<span class="n">interface</span> <span class="n">constraint</span> <span class="p">(</span><span class="kt">I</span><span class="ow">::</span><span class="n">n</span> <span class="o">==</span> <span class="kt">J</span><span class="ow">::</span><span class="n">n</span><span class="p">)</span>
<span class="n">y</span> <span class="kt">:</span> <span class="p">[</span><span class="kt">I</span><span class="ow">::</span><span class="n">n</span><span class="p">]</span>
<span class="n">y</span> <span class="ow">=</span> <span class="kt">I</span><span class="ow">::</span><span class="n">x</span> <span class="o">+</span> <span class="kt">J</span><span class="ow">::</span><span class="n">x</span>
<span class="kr">module</span> <span class="nn">Impl1</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="ow">=</span> <span class="mi">8</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mi">26</span>
<span class="kr">module</span> <span class="nn">Impl2</span> <span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="ow">=</span> <span class="mi">8</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mi">30</span>
<span class="kr">module</span> <span class="nn">MyF</span> <span class="ow">=</span> <span class="kt">F</span> <span class="p">{</span> <span class="kt">I</span> <span class="ow">=</span> <span class="kt">Impl1</span><span class="p">,</span> <span class="kt">J</span> <span class="ow">=</span> <span class="kt">Impl</span> <span class="mi">2</span> <span class="p">}</span>
</pre></div>
</div>
</div>
<p>Each interface import is identified by its name,
which is derived from the <code class="docutils literal notranslate"><span class="pre">as</span></code> clause on the
interface import. If there is no <code class="docutils literal notranslate"><span class="pre">as</span></code> clause,
then the name of the parameter is derived from
the name of the interface itself.</p>
<p>Since interfaces are identified by name, the
order in which they are provided is not important.</p>
<p>Modules defined by instantiation may be nested,
just like any other module:</p>
<div class="literal-block-wrapper docutils container" id="id23">
<div class="code-block-caption"><span class="caption-text">Nested module instantiation.</span><a class="headerlink" href="#id23" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="kr">import</span> <span class="nn">Somewhere</span> <span class="c1">// defines G</span>
<span class="n">submodule</span> <span class="kt">F</span> <span class="ow">=</span> <span class="n">submodule</span> <span class="kt">G</span> <span class="p">{</span> <span class="kt">I</span> <span class="p">}</span>
</pre></div>
</div>
</div>
<p>In this example, <code class="docutils literal notranslate"><span class="pre">submodule</span> <span class="pre">F</span></code> is defined
by instantiating some other parameterized
module <code class="docutils literal notranslate"><span class="pre">G</span></code>, presumably imported from <code class="docutils literal notranslate"><span class="pre">Somewhere</span></code>.
Note that in this case the argument to the instantiation
<code class="docutils literal notranslate"><span class="pre">I</span></code> is a top-level module, because it is not
preceded by the <code class="docutils literal notranslate"><span class="pre">submodule</span></code> keyword.</p>
</div>
<div class="section" id="anonymous-interface-modules">
<h3>Anonymous Interface Modules<a class="headerlink" href="#anonymous-interface-modules" title="Permalink to this headline"></a></h3>
<p>If we need to just parameterize a module by a couple of types/values,
it is quite cumbersome to have to define a whole separate interface module.
To make this more convenient we provide the following notation for defining
an anonymous interface and using it straight away:</p>
<div class="literal-block-wrapper docutils container" id="id24">
<div class="code-block-caption"><span class="caption-text">Simple parameterized module.</span><a class="headerlink" href="#id24" title="Permalink to this code"></a></div>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="n">parameter</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span>
<span class="kr">type</span> <span class="n">constraint</span> <span class="p">(</span><span class="kr">fin</span> <span class="n">n</span><span class="p">,</span> <span class="n">n</span> <span class="o">&gt;=</span> <span class="mi">1</span><span class="p">)</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">f</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">f</span> <span class="ow">=</span> <span class="mi">1</span> <span class="o">+</span> <span class="n">x</span>
</pre></div>
</div>
</div>
<p>The <code class="docutils literal notranslate"><span class="pre">parameter</span></code> block defines an interface module and uses it.
Note that the parameters may not use things defined in <code class="docutils literal notranslate"><span class="pre">M</span></code> as
the interface is declared outside of <code class="docutils literal notranslate"><span class="pre">M</span></code>.</p>
</div>
<div class="section" id="anonymous-instantiation-arguments">
<h3>Anonymous Instantiation Arguments<a class="headerlink" href="#anonymous-instantiation-arguments" title="Permalink to this headline"></a></h3>
<p>Sometimes it is also a bit cumbersome to have to define a whole
separate module just to pass it as an argument to some parameterized
module. To make this more convenient we support the following notion
for instantiation a module:</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="c1">// A parameterized module</span>
<span class="kr">module</span> <span class="nn">M</span> <span class="kr">where</span>
<span class="n">parameter</span>
<span class="kr">type</span> <span class="n">n</span> <span class="kt">:</span> <span class="o">#</span>
<span class="n">x</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">y</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">f</span> <span class="kt">:</span> <span class="p">[</span><span class="n">n</span><span class="p">]</span>
<span class="n">f</span> <span class="ow">=</span> <span class="n">x</span> <span class="o">+</span> <span class="n">y</span>
<span class="c1">// A module instantiation</span>
<span class="kr">module</span> <span class="nn">N</span> <span class="ow">=</span> <span class="kt">M</span>
<span class="kr">where</span>
<span class="kr">type</span> <span class="n">n</span> <span class="ow">=</span> <span class="mi">32</span>
<span class="n">x</span> <span class="ow">=</span> <span class="mi">11</span>
<span class="n">y</span> <span class="ow">=</span> <span class="n">helper</span>
<span class="n">helper</span> <span class="ow">=</span> <span class="mi">12</span>
</pre></div>
</div>
<p>The declarations in the <code class="docutils literal notranslate"><span class="pre">where</span></code> block are treated as the
definition of an anonymous module which is passed as the argument
to parameterized module <code class="docutils literal notranslate"><span class="pre">M</span></code>.</p>
</div>
</div>
</div>
</div>
</div>
<footer><div class="rst-footer-buttons" role="navigation" aria-label="Footer">
<a href="TypeDeclarations.html" class="btn btn-neutral float-left" title="Type Declarations" accesskey="p" rel="prev"><span class="fa fa-arrow-circle-left" aria-hidden="true"></span> Previous</a>
</div>
<hr/>
<div role="contentinfo">
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</body>
</html>

View File

@ -0,0 +1,212 @@
<!DOCTYPE html>
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Overloaded Operations &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="search.html" />
<link rel="next" title="Type Declarations" href="TypeDeclarations.html" />
<link rel="prev" title="Basic Types" href="BasicTypes.html" />
</head>
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
<input type="hidden" name="check_keywords" value="yes" />
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul class="current">
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1 current"><a class="current reference internal" href="#">Overloaded Operations</a><ul>
<li class="toctree-l2"><a class="reference internal" href="#equality">Equality</a></li>
<li class="toctree-l2"><a class="reference internal" href="#comparisons">Comparisons</a></li>
<li class="toctree-l2"><a class="reference internal" href="#signed-comparisons">Signed Comparisons</a></li>
<li class="toctree-l2"><a class="reference internal" href="#zero">Zero</a></li>
<li class="toctree-l2"><a class="reference internal" href="#logical-operations">Logical Operations</a></li>
<li class="toctree-l2"><a class="reference internal" href="#basic-arithmetic">Basic Arithmetic</a></li>
<li class="toctree-l2"><a class="reference internal" href="#integral-operations">Integral Operations</a></li>
<li class="toctree-l2"><a class="reference internal" href="#division">Division</a></li>
<li class="toctree-l2"><a class="reference internal" href="#rounding">Rounding</a></li>
</ul>
</li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Overloaded Operations</li>
<li class="wy-breadcrumbs-aside">
<a href="_sources/OverloadedOperations.rst.txt" rel="nofollow"> View page source</a>
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<div class="section" id="overloaded-operations">
<h1>Overloaded Operations<a class="headerlink" href="#overloaded-operations" title="Permalink to this headline"></a></h1>
<div class="section" id="equality">
<h2>Equality<a class="headerlink" href="#equality" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Eq</span>
<span class="p">(</span><span class="o">==</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Eq</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">!=</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Eq</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">===</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">,</span> <span class="n">b</span><span class="p">}</span> <span class="p">(</span><span class="kt">Eq</span> <span class="n">b</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="p">(</span><span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">b</span><span class="p">)</span> <span class="ow">-&gt;</span> <span class="p">(</span><span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">b</span><span class="p">)</span> <span class="ow">-&gt;</span> <span class="p">(</span><span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span><span class="p">)</span>
<span class="p">(</span><span class="o">!==</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">,</span> <span class="n">b</span><span class="p">}</span> <span class="p">(</span><span class="kt">Eq</span> <span class="n">b</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="p">(</span><span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">b</span><span class="p">)</span> <span class="ow">-&gt;</span> <span class="p">(</span><span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">b</span><span class="p">)</span> <span class="ow">-&gt;</span> <span class="p">(</span><span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span><span class="p">)</span>
</pre></div>
</div>
</div>
<div class="section" id="comparisons">
<h2>Comparisons<a class="headerlink" href="#comparisons" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">Cmp</span>
<span class="p">(</span><span class="o">&lt;</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">&gt;</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">&lt;=</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">&gt;=</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="kr">min</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="kr">max</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="n">abs</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kr">Cmp</span> <span class="n">a</span><span class="p">,</span> <span class="kt">Ring</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
</pre></div>
</div>
</div>
<div class="section" id="signed-comparisons">
<h2>Signed Comparisons<a class="headerlink" href="#signed-comparisons" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">SignedCmp</span>
<span class="p">(</span><span class="o">&lt;$</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">SignedCmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">&gt;$</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">SignedCmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">&lt;=$</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">SignedCmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
<span class="p">(</span><span class="o">&gt;=$</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">SignedCmp</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kr">Bit</span>
</pre></div>
</div>
</div>
<div class="section" id="zero">
<h2>Zero<a class="headerlink" href="#zero" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Zero</span>
<span class="n">zero</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Zero</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span>
</pre></div>
</div>
</div>
<div class="section" id="logical-operations">
<h2>Logical Operations<a class="headerlink" href="#logical-operations" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Logic</span>
<span class="p">(</span><span class="o">&amp;&amp;</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Logic</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">||</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Logic</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">^</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Logic</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="n">complement</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Logic</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
</pre></div>
</div>
</div>
<div class="section" id="basic-arithmetic">
<h2>Basic Arithmetic<a class="headerlink" href="#basic-arithmetic" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Ring</span>
<span class="n">fromInteger</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="kt">Integer</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">+</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">-</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">*</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="n">negate</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">^^</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">,</span> <span class="n">e</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">,</span> <span class="kt">Integral</span> <span class="n">e</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">e</span> <span class="ow">-&gt;</span> <span class="n">a</span>
</pre></div>
</div>
</div>
<div class="section" id="integral-operations">
<h2>Integral Operations<a class="headerlink" href="#integral-operations" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Integral</span>
<span class="p">(</span><span class="o">/</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Integral</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">%</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Integral</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">^^</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">,</span> <span class="n">e</span><span class="p">}</span> <span class="p">(</span><span class="kt">Ring</span> <span class="n">a</span><span class="p">,</span> <span class="kt">Integral</span> <span class="n">e</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">e</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="n">toInteger</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Integral</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kt">Integer</span>
<span class="n">infFrom</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Integral</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="p">[</span><span class="kr">inf</span><span class="p">]</span><span class="n">a</span>
<span class="n">infFromThen</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Integral</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="p">[</span><span class="kr">inf</span><span class="p">]</span><span class="n">a</span>
</pre></div>
</div>
</div>
<div class="section" id="division">
<h2>Division<a class="headerlink" href="#division" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Field</span>
<span class="n">recip</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Field</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
<span class="p">(</span><span class="o">/.</span><span class="p">)</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Field</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="n">a</span>
</pre></div>
</div>
</div>
<div class="section" id="rounding">
<h2>Rounding<a class="headerlink" href="#rounding" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kt">Round</span>
<span class="n">ceiling</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Round</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kt">Integer</span>
<span class="n">floor</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Round</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kt">Integer</span>
<span class="n">trunc</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Round</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kt">Integer</span>
<span class="n">roundAway</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Round</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kt">Integer</span>
<span class="n">roundToEven</span> <span class="kt">:</span> <span class="p">{</span><span class="n">a</span><span class="p">}</span> <span class="p">(</span><span class="kt">Round</span> <span class="n">a</span><span class="p">)</span> <span class="ow">=&gt;</span> <span class="n">a</span> <span class="ow">-&gt;</span> <span class="kt">Integer</span>
</pre></div>
</div>
</div>
</div>
</div>
</div>
<footer><div class="rst-footer-buttons" role="navigation" aria-label="Footer">
<a href="BasicTypes.html" class="btn btn-neutral float-left" title="Basic Types" accesskey="p" rel="prev"><span class="fa fa-arrow-circle-left" aria-hidden="true"></span> Previous</a>
<a href="TypeDeclarations.html" class="btn btn-neutral float-right" title="Type Declarations" accesskey="n" rel="next">Next <span class="fa fa-arrow-circle-right" aria-hidden="true"></span></a>
</div>
<hr/>
<div role="contentinfo">
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</body>
</html>

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,154 @@
<!DOCTYPE html>
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Type Declarations &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="search.html" />
<link rel="next" title="Modules" href="Modules.html" />
<link rel="prev" title="Overloaded Operations" href="OverloadedOperations.html" />
</head>
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
<input type="hidden" name="check_keywords" value="yes" />
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul class="current">
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1 current"><a class="current reference internal" href="#">Type Declarations</a><ul>
<li class="toctree-l2"><a class="reference internal" href="#type-synonyms">Type Synonyms</a></li>
<li class="toctree-l2"><a class="reference internal" href="#newtypes">Newtypes</a></li>
</ul>
</li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Type Declarations</li>
<li class="wy-breadcrumbs-aside">
<a href="_sources/TypeDeclarations.rst.txt" rel="nofollow"> View page source</a>
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<div class="section" id="type-declarations">
<h1>Type Declarations<a class="headerlink" href="#type-declarations" title="Permalink to this headline"></a></h1>
<div class="section" id="type-synonyms">
<h2>Type Synonyms<a class="headerlink" href="#type-synonyms" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">type</span> <span class="kt">T</span> <span class="n">a</span> <span class="n">b</span> <span class="ow">=</span> <span class="p">[</span><span class="n">a</span><span class="p">]</span> <span class="n">b</span>
</pre></div>
</div>
<p>A <code class="docutils literal notranslate"><span class="pre">type</span></code> declaration creates a synonym for a
pre-existing type expression, which may optionally have
arguments. A type synonym is transparently unfolded at
use sites and is treated as though the user had instead
written the body of the type synonym in line.
Type synonyms may mention other synonyms, but it is not
allowed to create a recursive collection of type synonyms.</p>
</div>
<div class="section" id="newtypes">
<h2>Newtypes<a class="headerlink" href="#newtypes" title="Permalink to this headline"></a></h2>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="kr">newtype</span> <span class="kt">NewT</span> <span class="n">a</span> <span class="n">b</span> <span class="ow">=</span> <span class="p">{</span> <span class="nb">seq</span> <span class="kt">:</span> <span class="p">[</span><span class="n">a</span><span class="p">]</span><span class="n">b</span> <span class="p">}</span>
</pre></div>
</div>
<p>A <code class="docutils literal notranslate"><span class="pre">newtype</span></code> declaration declares a new named type which is defined by
a record body. Unlike type synonyms, each named <code class="docutils literal notranslate"><span class="pre">newtype</span></code> is treated
as a distinct type by the type checker, even if they have the same
bodies. Moreover, types created by a <code class="docutils literal notranslate"><span class="pre">newtype</span></code> declaration will not be
members of any typeclasses, even if the record defining their body
would be. For the purposes of typechecking, two newtypes are
considered equal only if all their arguments are equal, even if the
arguments do not appear in the body of the newtype, or are otherwise
irrelevant. Just like type synonyms, newtypes are not allowed to form
recursive groups.</p>
<p>Every <code class="docutils literal notranslate"><span class="pre">newtype</span></code> declaration brings into scope a new function with the
same name as the type which can be used to create values of the
newtype.</p>
<div class="highlight-cryptol notranslate"><div class="highlight"><pre><span></span><span class="nf">x</span> <span class="kt">:</span> <span class="kt">NewT</span> <span class="mi">3</span> <span class="kt">Integer</span>
<span class="nf">x</span> <span class="ow">=</span> <span class="kt">NewT</span> <span class="p">{</span> <span class="nb">seq</span> <span class="ow">=</span> <span class="p">[</span><span class="mi">1</span><span class="p">,</span><span class="mi">2</span><span class="p">,</span><span class="mi">3</span><span class="p">]</span> <span class="p">}</span>
</pre></div>
</div>
<p>Just as with records, field projections can be used directly on values
of newtypes to extract the values in the body of the type.</p>
<div class="highlight-none notranslate"><div class="highlight"><pre><span></span>&gt; sum x.seq
6
</pre></div>
</div>
</div>
</div>
</div>
</div>
<footer><div class="rst-footer-buttons" role="navigation" aria-label="Footer">
<a href="OverloadedOperations.html" class="btn btn-neutral float-left" title="Overloaded Operations" accesskey="p" rel="prev"><span class="fa fa-arrow-circle-left" aria-hidden="true"></span> Previous</a>
<a href="Modules.html" class="btn btn-neutral float-right" title="Modules" accesskey="n" rel="next">Next <span class="fa fa-arrow-circle-right" aria-hidden="true"></span></a>
</div>
<hr/>
<div role="contentinfo">
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</body>
</html>

View File

@ -0,0 +1,283 @@
Basic Syntax
============
Declarations
------------
.. code-block:: cryptol
f x = x + y + z
Type Signatures
---------------
.. code-block:: cryptol
f,g : {a,b} (fin a) => [a] b
Layout
------
Groups of declarations are organized based on indentation.
Declarations with the same indentation belong to the same group.
Lines of text that are indented more than the beginning of a
declaration belong to that declaration, while lines of text that are
indented less terminate a group of declarations. Consider, for example,
the following Cryptol declarations:
.. code-block:: cryptol
f x = x + y + z
where
y = x * x
z = x + y
g y = y
This group has two declarations, one for `f` and one for `g`. All the
lines between `f` and `g` that are indented more than `f` belong to
`f`. The same principle applies to the declarations in the ``where`` block
of `f`, which defines two more local names, `y` and `z`.
Comments
--------
Cryptol supports block comments, which start with ``/*`` and end with
``*/``, and line comments, which start with ``//`` and terminate at the
end of the line. Block comments may be nested arbitrarily.
.. code-block:: cryptol
/* This is a block comment */
// This is a line comment
/* This is a /* Nested */ block comment */
.. todo::
Document ``/** */``
Identifiers
-----------
Cryptol identifiers consist of one or more characters. The first
character must be either an English letter or underscore (``_``). The
following characters may be an English letter, a decimal digit,
underscore (``_``), or a prime (``'``). Some identifiers have special
meaning in the language, so they may not be used in programmer-defined
names (see `Keywords and Built-in Operators`_).
.. code-block:: cryptol
:caption: Examples of identifiers
name name1 name' longer_name
Name Name2 Name'' longerName
Keywords and Built-in Operators
-------------------------------
The following identifiers have special meanings in Cryptol, and may
not be used for programmer defined names:
.. The table below can be generated by running `chop.hs` on this list:
else
extern
if
private
include
module
submodule
interface
newtype
pragma
property
then
type
where
let
import
as
hiding
infixl
infixr
infix
primitive
parameter
constraint
down
by
.. _Keywords:
.. code-block:: none
:caption: Keywords
as extern include interface parameter property where
by hiding infix let pragma submodule else
constraint if infixl module primitive then
down import infixr newtype private type
The following table contains Cryptol's operators and their
associativity with lowest precedence operators first, and highest
precedence last.
.. table:: Operator precedences
+-----------------------------------------+-----------------+
| Operator | Associativity |
+=========================================+=================+
| ``==>`` | right |
+-----------------------------------------+-----------------+
| ``\/`` | right |
+-----------------------------------------+-----------------+
| ``/\`` | right |
+-----------------------------------------+-----------------+
| ``==`` ``!=`` ``===`` ``!==`` | not associative |
+-----------------------------------------+-----------------+
| ``>`` ``<`` ``<=`` ``>=`` | not associative |
| ``<$`` ``>$`` ``<=$`` ``>=$`` | |
+-----------------------------------------+-----------------+
| ``||`` | right |
+-----------------------------------------+-----------------+
| ``^`` | left |
+-----------------------------------------+-----------------+
| ``&&`` | right |
+-----------------------------------------+-----------------+
| ``#`` | right |
+-----------------------------------------+-----------------+
| ``>>`` ``<<`` ``>>>`` ``<<<`` ``>>$`` | left |
+-----------------------------------------+-----------------+
| ``+`` ``-`` | left |
+-----------------------------------------+-----------------+
| ``*`` ``/`` ``%`` ``/$`` ``%$`` | left |
+-----------------------------------------+-----------------+
| ``^^`` | right |
+-----------------------------------------+-----------------+
| ``@`` ``@@`` ``!`` ``!!`` | left |
+-----------------------------------------+-----------------+
| (unary) ``-`` ``~`` | right |
+-----------------------------------------+-----------------+
Built-in Type-level Operators
-----------------------------
Cryptol includes a variety of operators that allow computations on
the numeric types used to specify the sizes of sequences.
.. table:: Type-level operators
+------------+----------------------------------------+
| Operator | Meaning |
+============+========================================+
| ``+`` | Addition |
+------------+----------------------------------------+
| ``-`` | Subtraction |
+------------+----------------------------------------+
| ``*`` | Multiplication |
+------------+----------------------------------------+
| ``/`` | Division |
+------------+----------------------------------------+
| ``/^`` | Ceiling division (``/`` rounded up) |
+------------+----------------------------------------+
| ``%`` | Modulus |
+------------+----------------------------------------+
| ``%^`` | Ceiling modulus (compute padding) |
+------------+----------------------------------------+
| ``^^`` | Exponentiation |
+------------+----------------------------------------+
| ``lg2`` | Ceiling logarithm (base 2) |
+------------+----------------------------------------+
| ``width`` | Bit width (equal to ``lg2(n+1)``) |
+------------+----------------------------------------+
| ``max`` | Maximum |
+------------+----------------------------------------+
| ``min`` | Minimum |
+------------+----------------------------------------+
Numeric Literals
----------------
Numeric literals may be written in binary, octal, decimal, or
hexadecimal notation. The base of a literal is determined by its prefix:
``0b`` for binary, ``0o`` for octal, no special prefix for
decimal, and ``0x`` for hexadecimal.
.. code-block:: cryptol
:caption: Examples of literals
254 // Decimal literal
0254 // Decimal literal
0b11111110 // Binary literal
0o376 // Octal literal
0xFE // Hexadecimal literal
0xfe // Hexadecimal literal
Numeric literals in binary, octal, or hexadecimal notation result in
bit sequences of a fixed length (i.e., they have type ``[n]`` for
some `n`). The length is determined by the base and the number
of digits in the literal. Decimal literals are overloaded, and so the
type is inferred from context in which the literal is used. Examples:
.. code-block:: cryptol
:caption: Literals and their types
0b1010 // : [4], 1 * number of digits
0o1234 // : [12], 3 * number of digits
0x1234 // : [16], 4 * number of digits
10 // : {a}. (Literal 10 a) => a
// a = Integer or [n] where n >= width 10
Numeric literals may also be written as polynomials by writing a polynomial
expression in terms of `x` between an opening ``<|`` and a closing ``|>``.
Numeric literals in polynomial notation result in bit sequences of length
one more than the degree of the polynomial. Examples:
.. code-block:: cryptol
:caption: Polynomial literals
<| x^^6 + x^^4 + x^^2 + x^^1 + 1 |> // : [7], equal to 0b1010111
<| x^^4 + x^^3 + x |> // : [5], equal to 0b11010
Cryptol also supports fractional literals using binary (prefix ``0b``),
octal (prefix ``0o``), decimal (no prefix), and hexadecimal (prefix ``ox``)
digits. A fractional literal must contain a ``.`` and may optionally
have an exponent. The base of the exponent for binary, octal,
and hexadecimal literals is 2 and the exponent is marked using the symbol ``p``.
Decimal fractional literals use exponent base 10, and the symbol ``e``.
Examples:
.. code-block:: cryptol
:caption: Fractional literals
10.2
10.2e3 // 10.2 * 10^3
0x30.1 // 3 * 64 + 1/16
0x30.1p4 // (3 * 64 + 1/16) * 2^4
All fractional literals are overloaded and may be used with types that support
fractional numbers (e.g., ``Rational``, and the ``Float`` family of types).
Some types (e.g. the ``Float`` family) cannot represent all fractional literals
precisely. Such literals are rejected statically when using binary, octal,
or hexadecimal notation. When using decimal notation, the literal is rounded
to the closest representable even number.
All numeric literals may also include ``_``, which has no effect on the
literal value but may be used to improve readability. Here are some examples:
.. code-block:: cryptol
:caption: Using _
0b_0000_0010
0x_FFFF_FFEA

View File

@ -0,0 +1,211 @@
Basic Types
===========
Tuples and Records
------------------
Tuples and records are used for packaging multiple values together.
Tuples are enclosed in parentheses, while records are enclosed in
curly braces. The components of both tuples and records are separated by
commas. The components of tuples are expressions, while the
components of records are a label and a value separated by an equal
sign. Examples:
.. code-block:: cryptol
(1,2,3) // A tuple with 3 component
() // A tuple with no components
{ x = 1, y = 2 } // A record with two fields, `x` and `y`
{} // A record with no fields
The components of tuples are identified by position, while the
components of records are identified by their label, and so the
ordering of record components is not important for most purposes.
Examples:
.. code-block:: cryptol
(1,2) == (1,2) // True
(1,2) == (2,1) // False
{ x = 1, y = 2 } == { x = 1, y = 2 } // True
{ x = 1, y = 2 } == { y = 2, x = 1 } // True
Ordering on tuples and records is defined lexicographically. Tuple
components are compared in the order they appear, whereas record
fields are compared in alphabetical order of field names.
Accessing Fields
~~~~~~~~~~~~~~~~
The components of a record or a tuple may be accessed in two ways: via
pattern matching or by using explicit component selectors. Explicit
component selectors are written as follows:
.. code-block:: cryptol
(15, 20).0 == 15
(15, 20).1 == 20
{ x = 15, y = 20 }.x == 15
Explicit record selectors may be used only if the program contains
sufficient type information to determine the shape of the tuple or
record. For example:
.. code-block:: cryptol
type T = { sign : Bit, number : [15] }
// Valid definition:
// the type of the record is known.
isPositive : T -> Bit
isPositive x = x.sign
// Invalid definition:
// insufficient type information.
badDef x = x.f
The components of a tuple or a record may also be accessed using
pattern matching. Patterns for tuples and records mirror the syntax
for constructing values: tuple patterns use parentheses, while record
patterns use braces. Examples:
.. code-block:: cryptol
getFst (x,_) = x
distance2 { x = xPos, y = yPos } = xPos ^^ 2 + yPos ^^ 2
f p = x + y where
(x, y) = p
Selectors are also lifted through sequence and function types, point-wise,
so that the following equations should hold:
.. code-block:: cryptol
xs.l == [ x.l | x <- xs ] // sequences
f.l == \x -> (f x).l // functions
Thus, if we have a sequence of tuples, ``xs``, then we can quickly obtain a
sequence with only the tuples' first components by writing ``xs.0``.
Similarly, if we have a function, ``f``, that computes a tuple of results,
then we can write ``f.0`` to get a function that computes only the first
entry in the tuple.
This behavior is quite handy when examining complex data at the REPL.
Updating Fields
~~~~~~~~~~~~~~~
The components of a record or a tuple may be updated using the following
notation:
.. code-block:: cryptol
// Example values
r = { x = 15, y = 20 } // a record
t = (True,True) // a tuple
n = { pt = r, size = 100 } // nested record
// Setting fields
{ r | x = 30 } == { x = 30, y = 20 }
{ t | 0 = False } == (False,True)
// Update relative to the old value
{ r | x -> x + 5 } == { x = 20, y = 20 }
// Update a nested field
{ n | pt.x = 10 } == { pt = { x = 10, y = 20 }, size = 100 }
{ n | pt.x -> x + 10 } == { pt = { x = 25, y = 20 }, size = 100 }
Sequences
---------
A sequence is a fixed-length collection of elements of the same type.
The type of a finite sequence of length `n`, with elements of type `a`
is ``[n] a``. Often, a finite sequence of bits, ``[n] Bit``, is called a
*word*. We may abbreviate the type ``[n] Bit`` as ``[n]``. An infinite
sequence with elements of type `a` has type ``[inf] a``, and ``[inf]`` is
an infinite stream of bits.
.. code-block:: cryptol
[e1,e2,e3] // A sequence with three elements
[t1 .. t2] // Enumeration
[t1 .. <t2] // Enumeration (exclusive bound)
[t1 .. t2 by n] // Enumeration (stride)
[t1 .. <t2 by n] // Enumeration (stride, ex. bound)
[t1 .. t2 down by n] // Enumeration (downward stride)
[t1 .. >t2 down by n] // Enumeration (downward stride, ex. bound)
[t1, t2 .. t3] // Enumeration (step by t2 - t1)
[e1 ...] // Infinite sequence starting at e1
[e1, e2 ...] // Infinite sequence stepping by e2-e1
[ e | p11 <- e11, p12 <- e12 // Sequence comprehensions
| p21 <- e21, p22 <- e22 ]
x = generate (\i -> e) // Sequence from generating function
x @ i = e // Sequence with index binding
arr @ i @ j = e // Two-dimensional sequence
Note: the bounds in finite sequences (those with `..`) are type
expressions, while the bounds in infinite sequences are value
expressions.
.. table:: Sequence operations.
+------------------------------+---------------------------------------------+
| Operator | Description |
+==============================+=============================================+
| ``#`` | Sequence concatenation |
+------------------------------+---------------------------------------------+
| ``>>`` ``<<`` | Shift (right, left) |
+------------------------------+---------------------------------------------+
| ``>>>`` ``<<<`` | Rotate (right, left) |
+------------------------------+---------------------------------------------+
| ``>>$`` | Arithmetic right shift (on bitvectors only) |
+------------------------------+---------------------------------------------+
| ``@`` ``!`` | Access elements (front, back) |
+------------------------------+---------------------------------------------+
| ``@@`` ``!!`` | Access sub-sequence (front, back) |
+------------------------------+---------------------------------------------+
| ``update`` ``updateEnd`` | Update the value of a sequence at |
| | a location |
| | (front, back) |
+------------------------------+---------------------------------------------+
| ``updates`` ``updatesEnd`` | Update multiple values of a sequence |
| | (front, back) |
+------------------------------+---------------------------------------------+
There are also lifted pointwise operations.
.. code-block:: cryptol
[p1, p2, p3, p4] // Sequence pattern
p1 # p2 // Split sequence pattern
Functions
---------
.. code-block:: cryptol
\p1 p2 -> e // Lambda expression
f p1 p2 = e // Function definition

View File

@ -0,0 +1,162 @@
Expressions
===========
This section provides an overview of the Cryptol's expression syntax.
Calling Functions
-----------------
.. code-block:: cryptol
f 2 // call `f` with parameter `2`
g x y // call `g` with two parameters: `x` and `y`
h (x,y) // call `h` with one parameter, the pair `(x,y)`
Prefix Operators
-----------------
.. code-block:: cryptol
-2 // call unary `-` with parameter `2`
- 2 // call unary `-` with parameter `2`
f (-2) // call `f` with one argument: `-2`, parens are important
-f 2 // call unary `-` with parameter `f 2`
- f 2 // call unary `-` with parameter `f 2`
Infix Functions
-----------------
.. code-block:: cryptol
2 + 3 // call `+` with two parameters: `2` and `3`
2 + 3 * 5 // call `+` with two parameters: `2` and `3 * 5`
(+) 2 3 // call `+` with two parameters: `2` and `3`
f 2 + g 3 // call `+` with two parameters: `f 2` and `g 3`
- 2 + - 3 // call `+` with two parameters: `-2` and `-3`
- f 2 + - g 3
Type Annotations
-----------------
Explicit type annotations may be added on expressions, patterns, and
in argument definitions.
.. code-block:: cryptol
x : Bit // specify that `x` has type `Bit`
f x : Bit // specify that `f x` has type `Bit`
- f x : [8] // specify that `- f x` has type `[8]`
2 + 3 : [8] // specify that `2 + 3` has type `[8]`
\x -> x : [8] // type annotation is on `x`, not the function
if x
then y
else z : Bit // the type annotation is on `z`, not the whole `if`
[1..9 : [8]] // specify that elements in `[1..9]` have type `[8]`
f (x : [8]) = x + 1 // type annotation on patterns
.. todo::
Patterns with type variables
Explicit Type Instantiation
----------------------------
If ``f`` is a polymorphic value with type:
.. code-block:: cryptol
f : { tyParam } tyParam
f = zero
you can evaluate ``f``, passing it a type parameter:
.. code-block:: cryptol
f `{ tyParam = 13 }
Local Declarations
------------------
Local declarations have the weakest precedence of all expressions.
.. code-block:: cryptol
2 + x : [T]
where
type T = 8
x = 2 // `T` and `x` are in scope of `2 + x : `[T]`
if x then 1 else 2
where x = 2 // `x` is in scope in the whole `if`
\y -> x + y
where x = 2 // `y` is not in scope in the defintion of `x`
Block Arguments
---------------
When used as the last argument to a function call,
``if`` and lambda expressions do not need parens:
.. code-block:: cryptol
f \x -> x // call `f` with one argument `x -> x`
2 + if x
then y
else z // call `+` with two arguments: `2` and `if ...`
Conditionals
------------
The ``if ... then ... else`` construct can be used with
multiple branches. For example:
.. code-block:: cryptol
x = if y % 2 == 0 then 22 else 33
x = if y % 2 == 0 then 1
| y % 3 == 0 then 2
| y % 5 == 0 then 3
else 7
Demoting Numeric Types to Values
--------------------------------
The value corresponding to a numeric type may be accessed using the
following notation:
.. code-block:: cryptol
`t
Here `t` should be a finite type expression with numeric kind. The resulting
expression will be of a numeric base type, which is sufficiently large
to accommodate the value of the type:
.. code-block:: cryptol
`t : {a} (Literal t a) => a
This backtick notation is syntax sugar for an application of the
`number` primtive, so the above may be written as:
.. code-block:: cryptol
number`{t} : {a} (Literal t a) => a
If a type cannot be inferred from context, a suitable type will be
automatically chosen if possible, usually `Integer`.

View File

@ -0,0 +1,610 @@
Modules
=======
A *module* is used to group some related definitions. Each file may
contain at most one top-level module.
.. code-block:: cryptol
module M where
type T = [8]
f : [8]
f = 10
Hierarchical Module Names
-------------------------
Module may have either simple or *hierarchical* names.
Hierarchical names are constructed by gluing together ordinary
identifiers using the symbol ``::``.
.. code-block:: cryptol
module Hash::SHA256 where
sha256 = ...
The structure in the name may be used to group together related
modules. Also, the Cryptol implementation uses the structure of the
name to locate the file containing the definition of the module.
For example, when searching for module ``Hash::SHA256``, Cryptol
will look for a file named ``SHA256.cry`` in a directory called
``Hash``, contained in one of the directories specified by ``CRYPTOLPATH``.
Module Imports
--------------
To use the definitions from one module in another module, we use
``import`` declarations:
.. code-block:: cryptol
:caption: module M
// Provide some definitions
module M where
f : [8]
f = 2
.. code-block:: cryptol
:caption: module N
// Uses definitions from `M`
module N where
import M // import all definitions from `M`
g = f // `f` was imported from `M`
Import Lists
~~~~~~~~~~~~
Sometimes, we may want to import only some of the definitions
from a module. To do so, we use an import declaration with
an *import list*.
.. code-block:: cryptol
module M where
f = 0x02
g = 0x03
h = 0x04
.. code-block:: cryptol
module N where
import M(f,g) // Imports only `f` and `g`, but not `h`
x = f + g
Using explicit import lists helps reduce name collisions.
It also tends to make code easier to understand, because
it makes it easy to see the source of definitions.
Hiding Imports
~~~~~~~~~~~~~~
Sometimes a module may provide many definitions, and we want to use
most of them but with a few exceptions (e.g., because those would
result to a name clash). In such situations it is convenient
to use a *hiding* import:
.. code-block:: cryptol
:caption: module M
module M where
f = 0x02
g = 0x03
h = 0x04
.. code-block:: cryptol
:caption: module N
module N where
import M hiding (h) // Import everything but `h`
x = f + g
Qualified Module Imports
~~~~~~~~~~~~~~~~~~~~~~~~
Another way to avoid name collisions is by using a
*qualified* import.
.. code-block:: cryptol
:caption: module M
module M where
f : [8]
f = 2
.. code-block:: cryptol
:caption: module N
module N where
import M as P
g = P::f
// `f` was imported from `M`
// but when used it needs to be prefixed by the qualifier `P`
Qualified imports make it possible to work with definitions
that happen to have the same name but are defined in different modules.
Qualified imports may be combined with import lists or hiding clauses:
.. code-block:: cryptol
:caption: Example
import A as B (f) // introduces B::f
import X as Y hiding (f) // introduces everything but `f` from X
// using the prefix `X`
It is also possible to use the same qualifier prefix for imports
from different modules. For example:
.. code-block:: cryptol
:caption: Example
import A as B
import X as B
Such declarations will introduces all definitions from ``A`` and ``X``
but to use them, you would have to qualify using the prefix ``B::``.
Private Blocks
--------------
In some cases, definitions in a module might use helper
functions that are not intended to be used outside the module.
It is good practice to place such declarations in *private blocks*:
.. code-block:: cryptol
:caption: Private blocks
module M where
f : [8]
f = 0x01 + helper1 + helper2
private
helper1 : [8]
helper1 = 2
helper2 : [8]
helper2 = 3
The private block only needs to be indented if it might be followed by
additional public declarations. If all remaining declarations are to be
private then no additional indentation is needed as the ``private`` block will
extend to the end of the module.
.. code-block:: cryptol
:caption: Private blocks
module M where
f : [8]
f = 0x01 + helper1 + helper2
private
helper1 : [8]
helper1 = 2
helper2 : [8]
helper2 = 3
The keyword ``private`` introduces a new layout scope, and all declarations
in the block are considered to be private to the module. A single module
may contain multiple private blocks. For example, the following module
is equivalent to the previous one:
.. code-block:: cryptol
:caption: Private blocks
module M where
f : [8]
f = 0x01 + helper1 + helper2
private
helper1 : [8]
helper1 = 2
private
helper2 : [8]
helper2 = 3
Nested Modules
--------------
Module may be declared withing other modules, using the ``submodule`` keword.
.. code-block:: cryptol
:caption: Declaring a nested module called N
module M where
x = 0x02
submodule N where
y = x + 2
Submodules may refer to names in their enclosing scope.
Declarations in a sub-module will shadow names in the outer scope.
Declarations in a submdule may be imported with ``import submodule``,
which works just like an ordinary import except that ``X`` refers
to the name of a submodule.
.. code-block:: cryptol
:caption: Using declarations from a submodule.
module M where
x = 0x02
submodule N where
y = x + 2
import submodule N as P
z = 2 * P::y
Note that recursive definitions across modules are not allowed.
So, in the previous example, it would be an error if ``y`` was
to try to use ``z`` in its definition.
Implicit Imports
~~~~~~~~~~~~~~~~
For convenience, we add an implicit qualified submodule import for
each locally defined submodules.
.. code-block:: cryptol
:caption: Making use of the implicit import for a submodule.
module M where
x = 0x02
submodule N where
y = x + 2
z = 2 * N::y
``N::y`` works in the previous example because Cryptol added
an implicit import ``import submoulde N as N``.
Managing Module Names
~~~~~~~~~~~~~~~~~~~~~
The names of nested modules are managed by the module system just
like the name of any other declaration in Cryptol. Thus, nested
modules may declared in the public or private sections of their
containing module, and need to be imported before they can be used.
Thus, to use a submodule defined in top-level module ``A`` into
another top-level module ``B`` requires two steps:
1. First we need to import ``A`` to bring the name of the submodule in scope
2. Then we need to import the submodule to bring the names defined in it in scope.
.. code-block:: cryptol
:caption: Using a nested module from a different top-level module.
module A where
x = 0x02
submodule N where
y = x + 2
module B where
import A // Brings `N` in scope
import submodule N // Brings `y` in scope
z = 2 * y
Parameterized Modules
---------------------
Interface Modules
~~~~~~~~~~~~~~~~~
An *interface module* describes the content of a module
without providing a concrete implementation.
.. code-block:: cryptol
:caption: An interface module.
interface module I where
type n : # // `n` is a numeric type
type constraint (fin n, n >= 1)
// Assumptions about the declared numeric type
x : [n] // A declarations of a constant
Like other modules, interfaces modules may be nested in
other modules:
.. code-block:: cryptol
:caption: A nested interface module
module M where
interface submodule I where
type n : # // `n` is a numeric type
type constraint (fin n, n >= 1)
// Assumptions about the declared numeric type
x : [n] // A declarations of a constant
Importing an Interface Module
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
A module may be parameterized by importing an interface,
instead of a concrete module
.. code-block:: cryptol
:caption: A parameterized module
// The interface desribes the parmaeters
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
// This module is parameterized
module F where
import interface I
y : [n]
y = x + 1
To import a nested interface use ``import interface sumbodule I``
and make sure that ``I`` is in scope.
It is also possible to import multiple interface modules,
or the same interface module more than once. Each import
of an interface module maybe be linked to a different concrete
module, as described in :ref:`instantiating_modules`.
.. code-block:: cryptol
:caption: Multiple interface parameters
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
module F where
import interface I as I
import interface I as J
y : [I::n]
y = I::x + 1
z : [J::n]
z = J::x + 1
Interface Constraints
~~~~~~~~~~~~~~~~~~~~~
When working with multiple interfaces, it is to useful
to be able to impose additional constraints on the
types imported from the interface.
.. code-block:: cryptol
:caption: Adding constraints to interface parameters
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
module F where
import interface I as I
import interface I as J
interface constraint (I::n == J::n)
y : [I::n]
y = I::x + J::x
In this example we impose the constraint that ``n``
(the width of ``x``) in both interfaces must be the
same. Note that, of course, the two instantiations
may provide different values for ``x``.
.. _instantiating_modules:
Instantiating a Parameterized Module
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
To use a parameterized module we need to provide concrete
implementations for the interfaces that it uses, and provide
a name for the resulting module. This is done as follows:
.. code-block:: cryptol
:caption: Instantiating a parameterized module using a single interface.
interface module I where
type n : #
type constraint (fin n, n >= 1)
x : [n]
module F where
import interface I
y : [n]
y = x + 1
module Impl where
type n = 8
x = 26
module MyF = F { Impl }
Here we defined a new module called ``MyF`` which is
obtained by filling in module ``Impl`` for the interface
used by ``F``.
If a module is parameterized my multiple interfaces
we need to provide an implementation module for each
interface, using a slight variation on the previous notation.
.. code-block:: cryptol
:caption: Instantiating a parameterized module by name.
// I is defined as above
module F where
import interface I as I
import interface I as J
interface constraint (I::n == J::n)
y : [I::n]
y = I::x + J::x
module Impl1 where
type n = 8
x = 26
module Impl2 where
type n = 8
x = 30
module MyF = F { I = Impl1, J = Impl 2 }
Each interface import is identified by its name,
which is derived from the ``as`` clause on the
interface import. If there is no ``as`` clause,
then the name of the parameter is derived from
the name of the interface itself.
Since interfaces are identified by name, the
order in which they are provided is not important.
Modules defined by instantiation may be nested,
just like any other module:
.. code-block:: cryptol
:caption: Nested module instantiation.
module M where
import Somewhere // defines G
submodule F = submodule G { I }
In this example, ``submodule F`` is defined
by instantiating some other parameterized
module ``G``, presumably imported from ``Somewhere``.
Note that in this case the argument to the instantiation
``I`` is a top-level module, because it is not
preceded by the ``submodule`` keyword.
Anonymous Interface Modules
~~~~~~~~~~~~~~~~~~~~~~~~~~~
If we need to just parameterize a module by a couple of types/values,
it is quite cumbersome to have to define a whole separate interface module.
To make this more convenient we provide the following notation for defining
an anonymous interface and using it straight away:
.. code-block:: cryptol
:caption: Simple parameterized module.
module M where
parameter
type n : #
type constraint (fin n, n >= 1)
x : [n]
f : [n]
f = 1 + x
The ``parameter`` block defines an interface module and uses it.
Note that the parameters may not use things defined in ``M`` as
the interface is declared outside of ``M``.
Anonymous Instantiation Arguments
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Sometimes it is also a bit cumbersome to have to define a whole
separate module just to pass it as an argument to some parameterized
module. To make this more convenient we support the following notion
for instantiation a module:
.. code-block:: cryptol
// A parameterized module
module M where
parameter
type n : #
x : [n]
y : [n]
f : [n]
f = x + y
// A module instantiation
module N = M
where
type n = 32
x = 11
y = helper
helper = 12
The declarations in the ``where`` block are treated as the
definition of an anonymous module which is passed as the argument
to parameterized module ``M``.

View File

@ -0,0 +1,107 @@
Overloaded Operations
=====================
Equality
--------
.. code-block:: cryptol
Eq
(==) : {a} (Eq a) => a -> a -> Bit
(!=) : {a} (Eq a) => a -> a -> Bit
(===) : {a, b} (Eq b) => (a -> b) -> (a -> b) -> (a -> Bit)
(!==) : {a, b} (Eq b) => (a -> b) -> (a -> b) -> (a -> Bit)
Comparisons
-----------
.. code-block:: cryptol
Cmp
(<) : {a} (Cmp a) => a -> a -> Bit
(>) : {a} (Cmp a) => a -> a -> Bit
(<=) : {a} (Cmp a) => a -> a -> Bit
(>=) : {a} (Cmp a) => a -> a -> Bit
min : {a} (Cmp a) => a -> a -> a
max : {a} (Cmp a) => a -> a -> a
abs : {a} (Cmp a, Ring a) => a -> a
Signed Comparisons
------------------
.. code-block:: cryptol
SignedCmp
(<$) : {a} (SignedCmp a) => a -> a -> Bit
(>$) : {a} (SignedCmp a) => a -> a -> Bit
(<=$) : {a} (SignedCmp a) => a -> a -> Bit
(>=$) : {a} (SignedCmp a) => a -> a -> Bit
Zero
----
.. code-block:: cryptol
Zero
zero : {a} (Zero a) => a
Logical Operations
------------------
.. code-block:: cryptol
Logic
(&&) : {a} (Logic a) => a -> a -> a
(||) : {a} (Logic a) => a -> a -> a
(^) : {a} (Logic a) => a -> a -> a
complement : {a} (Logic a) => a -> a
Basic Arithmetic
----------------
.. code-block:: cryptol
Ring
fromInteger : {a} (Ring a) => Integer -> a
(+) : {a} (Ring a) => a -> a -> a
(-) : {a} (Ring a) => a -> a -> a
(*) : {a} (Ring a) => a -> a -> a
negate : {a} (Ring a) => a -> a
(^^) : {a, e} (Ring a, Integral e) => a -> e -> a
Integral Operations
-------------------
.. code-block:: cryptol
Integral
(/) : {a} (Integral a) => a -> a -> a
(%) : {a} (Integral a) => a -> a -> a
(^^) : {a, e} (Ring a, Integral e) => a -> e -> a
toInteger : {a} (Integral a) => a -> Integer
infFrom : {a} (Integral a) => a -> [inf]a
infFromThen : {a} (Integral a) => a -> a -> [inf]a
Division
--------
.. code-block:: cryptol
Field
recip : {a} (Field a) => a -> a
(/.) : {a} (Field a) => a -> a -> a
Rounding
--------
.. code-block:: cryptol
Round
ceiling : {a} (Round a) => a -> Integer
floor : {a} (Round a) => a -> Integer
trunc : {a} (Round a) => a -> Integer
roundAway : {a} (Round a) => a -> Integer
roundToEven : {a} (Round a) => a -> Integer

File diff suppressed because it is too large Load Diff

View File

@ -0,0 +1,53 @@
Type Declarations
=================
Type Synonyms
-------------
.. code-block:: cryptol
type T a b = [a] b
A ``type`` declaration creates a synonym for a
pre-existing type expression, which may optionally have
arguments. A type synonym is transparently unfolded at
use sites and is treated as though the user had instead
written the body of the type synonym in line.
Type synonyms may mention other synonyms, but it is not
allowed to create a recursive collection of type synonyms.
Newtypes
--------
.. code-block:: cryptol
newtype NewT a b = { seq : [a]b }
A ``newtype`` declaration declares a new named type which is defined by
a record body. Unlike type synonyms, each named ``newtype`` is treated
as a distinct type by the type checker, even if they have the same
bodies. Moreover, types created by a ``newtype`` declaration will not be
members of any typeclasses, even if the record defining their body
would be. For the purposes of typechecking, two newtypes are
considered equal only if all their arguments are equal, even if the
arguments do not appear in the body of the newtype, or are otherwise
irrelevant. Just like type synonyms, newtypes are not allowed to form
recursive groups.
Every ``newtype`` declaration brings into scope a new function with the
same name as the type which can be used to create values of the
newtype.
.. code-block:: cryptol
x : NewT 3 Integer
x = NewT { seq = [1,2,3] }
Just as with records, field projections can be used directly on values
of newtypes to extract the values in the body of the type.
.. code-block:: none
> sum x.seq
6

View File

@ -4,7 +4,7 @@
*
* Sphinx stylesheet -- basic theme.
*
* :copyright: Copyright 2007-2019 by the Sphinx team, see AUTHORS.
* :copyright: Copyright 2007-2021 by the Sphinx team, see AUTHORS.
* :license: BSD, see LICENSE for details.
*
*/
@ -15,6 +15,12 @@ div.clearer {
clear: both;
}
div.section::after {
display: block;
content: '';
clear: left;
}
/* -- relbar ---------------------------------------------------------------- */
div.related {
@ -124,7 +130,7 @@ ul.search li a {
font-weight: bold;
}
ul.search li div.context {
ul.search li p.context {
color: #888;
margin: 2px 0 0 30px;
text-align: left;
@ -231,6 +237,16 @@ a.headerlink {
visibility: hidden;
}
a.brackets:before,
span.brackets > a:before{
content: "[";
}
a.brackets:after,
span.brackets > a:after {
content: "]";
}
h1:hover > a.headerlink,
h2:hover > a.headerlink,
h3:hover > a.headerlink,
@ -261,19 +277,25 @@ p.rubric {
font-weight: bold;
}
img.align-left, .figure.align-left, object.align-left {
img.align-left, figure.align-left, .figure.align-left, object.align-left {
clear: left;
float: left;
margin-right: 1em;
}
img.align-right, .figure.align-right, object.align-right {
img.align-right, figure.align-right, .figure.align-right, object.align-right {
clear: right;
float: right;
margin-left: 1em;
}
img.align-center, .figure.align-center, object.align-center {
img.align-center, figure.align-center, .figure.align-center, object.align-center {
display: block;
margin-left: auto;
margin-right: auto;
}
img.align-default, figure.align-default, .figure.align-default {
display: block;
margin-left: auto;
margin-right: auto;
@ -287,30 +309,41 @@ img.align-center, .figure.align-center, object.align-center {
text-align: center;
}
.align-default {
text-align: center;
}
.align-right {
text-align: right;
}
/* -- sidebars -------------------------------------------------------------- */
div.sidebar {
div.sidebar,
aside.sidebar {
margin: 0 0 0.5em 1em;
border: 1px solid #ddb;
padding: 7px 7px 0 7px;
padding: 7px;
background-color: #ffe;
width: 40%;
float: right;
clear: right;
overflow-x: auto;
}
p.sidebar-title {
font-weight: bold;
}
div.admonition, div.topic, blockquote {
clear: left;
}
/* -- topics ---------------------------------------------------------------- */
div.topic {
border: 1px solid #ccc;
padding: 7px 7px 0 7px;
padding: 7px;
margin: 10px 0 10px 0;
}
@ -332,10 +365,6 @@ div.admonition dt {
font-weight: bold;
}
div.admonition dl {
margin-bottom: 0;
}
p.admonition-title {
margin: 0px 10px 5px 0px;
font-weight: bold;
@ -346,9 +375,30 @@ div.body p.centered {
margin-top: 25px;
}
/* -- content of sidebars/topics/admonitions -------------------------------- */
div.sidebar > :last-child,
aside.sidebar > :last-child,
div.topic > :last-child,
div.admonition > :last-child {
margin-bottom: 0;
}
div.sidebar::after,
aside.sidebar::after,
div.topic::after,
div.admonition::after,
blockquote::after {
display: block;
content: '';
clear: both;
}
/* -- tables ---------------------------------------------------------------- */
table.docutils {
margin-top: 10px;
margin-bottom: 10px;
border: 0;
border-collapse: collapse;
}
@ -358,6 +408,11 @@ table.align-center {
margin-right: auto;
}
table.align-default {
margin-left: auto;
margin-right: auto;
}
table caption span.caption-number {
font-style: italic;
}
@ -391,22 +446,34 @@ table.citation td {
border-bottom: none;
}
th > :first-child,
td > :first-child {
margin-top: 0px;
}
th > :last-child,
td > :last-child {
margin-bottom: 0px;
}
/* -- figures --------------------------------------------------------------- */
div.figure {
div.figure, figure {
margin: 0.5em;
padding: 0.5em;
}
div.figure p.caption {
div.figure p.caption, figcaption {
padding: 0.3em;
}
div.figure p.caption span.caption-number {
div.figure p.caption span.caption-number,
figcaption span.caption-number {
font-style: italic;
}
div.figure p.caption span.caption-text {
div.figure p.caption span.caption-text,
figcaption span.caption-text {
}
/* -- field list styles ----------------------------------------------------- */
@ -433,10 +500,71 @@ table.field-list td, table.field-list th {
/* -- hlist styles ---------------------------------------------------------- */
table.hlist {
margin: 1em 0;
}
table.hlist td {
vertical-align: top;
}
/* -- object description styles --------------------------------------------- */
.sig {
font-family: 'Consolas', 'Menlo', 'DejaVu Sans Mono', 'Bitstream Vera Sans Mono', monospace;
}
.sig-name, code.descname {
background-color: transparent;
font-weight: bold;
}
.sig-name {
font-size: 1.1em;
}
code.descname {
font-size: 1.2em;
}
.sig-prename, code.descclassname {
background-color: transparent;
}
.optional {
font-size: 1.3em;
}
.sig-paren {
font-size: larger;
}
.sig-param.n {
font-style: italic;
}
/* C++ specific styling */
.sig-inline.c-texpr,
.sig-inline.cpp-texpr {
font-family: unset;
}
.sig.c .k, .sig.c .kt,
.sig.cpp .k, .sig.cpp .kt {
color: #0033B3;
}
.sig.c .m,
.sig.cpp .m {
color: #1750EB;
}
.sig.c .s, .sig.c .sc,
.sig.cpp .s, .sig.cpp .sc {
color: #067D17;
}
/* -- other body styles ----------------------------------------------------- */
@ -460,11 +588,78 @@ ol.upperroman {
list-style: upper-roman;
}
:not(li) > ol > li:first-child > :first-child,
:not(li) > ul > li:first-child > :first-child {
margin-top: 0px;
}
:not(li) > ol > li:last-child > :last-child,
:not(li) > ul > li:last-child > :last-child {
margin-bottom: 0px;
}
ol.simple ol p,
ol.simple ul p,
ul.simple ol p,
ul.simple ul p {
margin-top: 0;
}
ol.simple > li:not(:first-child) > p,
ul.simple > li:not(:first-child) > p {
margin-top: 0;
}
ol.simple p,
ul.simple p {
margin-bottom: 0;
}
dl.footnote > dt,
dl.citation > dt {
float: left;
margin-right: 0.5em;
}
dl.footnote > dd,
dl.citation > dd {
margin-bottom: 0em;
}
dl.footnote > dd:after,
dl.citation > dd:after {
content: "";
clear: both;
}
dl.field-list {
display: grid;
grid-template-columns: fit-content(30%) auto;
}
dl.field-list > dt {
font-weight: bold;
word-break: break-word;
padding-left: 0.5em;
padding-right: 5px;
}
dl.field-list > dt:after {
content: ":";
}
dl.field-list > dd {
padding-left: 0.5em;
margin-top: 0em;
margin-left: 0em;
margin-bottom: 0em;
}
dl {
margin-bottom: 15px;
}
dd p {
dd > :first-child {
margin-top: 0px;
}
@ -478,6 +673,11 @@ dd {
margin-left: 30px;
}
dl > dd:last-child,
dl > dd:last-child > :last-child {
margin-bottom: 0;
}
dt:target, span.highlighted {
background-color: #fbe54e;
}
@ -491,14 +691,6 @@ dl.glossary dt {
font-size: 1.1em;
}
.optional {
font-size: 1.3em;
}
.sig-paren {
font-size: larger;
}
.versionmodified {
font-style: italic;
}
@ -537,6 +729,12 @@ dl.glossary dt {
font-style: oblique;
}
.classifier:before {
font-style: normal;
margin: 0.5em;
content: ":";
}
abbr, acronym {
border-bottom: dotted 1px;
cursor: help;
@ -549,6 +747,10 @@ pre {
overflow-y: hidden; /* fixes display issues on Chrome browsers */
}
pre, div[class*="highlight-"] {
clear: both;
}
span.pre {
-moz-hyphens: none;
-ms-hyphens: none;
@ -556,22 +758,57 @@ span.pre {
hyphens: none;
}
div[class*="highlight-"] {
margin: 1em 0;
}
td.linenos pre {
padding: 5px 0px;
border: 0;
background-color: transparent;
color: #aaa;
}
table.highlighttable {
margin-left: 0.5em;
display: block;
}
table.highlighttable tbody {
display: block;
}
table.highlighttable tr {
display: flex;
}
table.highlighttable td {
padding: 0 0.5em 0 0.5em;
margin: 0;
padding: 0;
}
table.highlighttable td.linenos {
padding-right: 0.5em;
}
table.highlighttable td.code {
flex: 1;
overflow: hidden;
}
.highlight .hll {
display: block;
}
div.highlight pre,
table.highlighttable pre {
margin: 0;
}
div.code-block-caption + div {
margin-top: 0;
}
div.code-block-caption {
margin-top: 1em;
padding: 2px 5px;
font-size: small;
}
@ -580,8 +817,14 @@ div.code-block-caption code {
background-color: transparent;
}
div.code-block-caption + div > div.highlight > pre {
margin-top: 0;
table.highlighttable td.linenos,
span.linenos,
div.highlight span.gp { /* gp: Generic.Prompt */
user-select: none;
-webkit-user-select: text; /* Safari fallback only */
-webkit-user-select: none; /* Chrome/Safari */
-moz-user-select: none; /* Firefox */
-ms-user-select: none; /* IE10+ */
}
div.code-block-caption span.caption-number {
@ -593,21 +836,7 @@ div.code-block-caption span.caption-text {
}
div.literal-block-wrapper {
padding: 1em 1em 0;
}
div.literal-block-wrapper div.highlight {
margin: 0;
}
code.descname {
background-color: transparent;
font-weight: bold;
font-size: 1.2em;
}
code.descclassname {
background-color: transparent;
margin: 1em 0;
}
code.xref, a code {
@ -648,8 +877,7 @@ span.eqno {
}
span.eqno a.headerlink {
position: relative;
left: 0px;
position: absolute;
z-index: 1;
}

View File

@ -1,261 +0,0 @@
/*
* classic.css_t
* ~~~~~~~~~~~~~
*
* Sphinx stylesheet -- classic theme.
*
* :copyright: Copyright 2007-2019 by the Sphinx team, see AUTHORS.
* :license: BSD, see LICENSE for details.
*
*/
@import url("basic.css");
/* -- page layout ----------------------------------------------------------- */
body {
font-family: sans-serif;
font-size: 100%;
background-color: #11303d;
color: #000;
margin: 0;
padding: 0;
}
div.document {
background-color: #1c4e63;
}
div.documentwrapper {
float: left;
width: 100%;
}
div.bodywrapper {
margin: 0 0 0 230px;
}
div.body {
background-color: #ffffff;
color: #000000;
padding: 0 20px 30px 20px;
}
div.footer {
color: #ffffff;
width: 100%;
padding: 9px 0 9px 0;
text-align: center;
font-size: 75%;
}
div.footer a {
color: #ffffff;
text-decoration: underline;
}
div.related {
background-color: #133f52;
line-height: 30px;
color: #ffffff;
}
div.related a {
color: #ffffff;
}
div.sphinxsidebar {
}
div.sphinxsidebar h3 {
font-family: 'Trebuchet MS', sans-serif;
color: #ffffff;
font-size: 1.4em;
font-weight: normal;
margin: 0;
padding: 0;
}
div.sphinxsidebar h3 a {
color: #ffffff;
}
div.sphinxsidebar h4 {
font-family: 'Trebuchet MS', sans-serif;
color: #ffffff;
font-size: 1.3em;
font-weight: normal;
margin: 5px 0 0 0;
padding: 0;
}
div.sphinxsidebar p {
color: #ffffff;
}
div.sphinxsidebar p.topless {
margin: 5px 10px 10px 10px;
}
div.sphinxsidebar ul {
margin: 10px;
padding: 0;
color: #ffffff;
}
div.sphinxsidebar a {
color: #98dbcc;
}
div.sphinxsidebar input {
border: 1px solid #98dbcc;
font-family: sans-serif;
font-size: 1em;
}
/* -- hyperlink styles ------------------------------------------------------ */
a {
color: #355f7c;
text-decoration: none;
}
a:visited {
color: #355f7c;
text-decoration: none;
}
a:hover {
text-decoration: underline;
}
/* -- body styles ----------------------------------------------------------- */
div.body h1,
div.body h2,
div.body h3,
div.body h4,
div.body h5,
div.body h6 {
font-family: 'Trebuchet MS', sans-serif;
background-color: #f2f2f2;
font-weight: normal;
color: #20435c;
border-bottom: 1px solid #ccc;
margin: 20px -20px 10px -20px;
padding: 3px 0 3px 10px;
}
div.body h1 { margin-top: 0; font-size: 200%; }
div.body h2 { font-size: 160%; }
div.body h3 { font-size: 140%; }
div.body h4 { font-size: 120%; }
div.body h5 { font-size: 110%; }
div.body h6 { font-size: 100%; }
a.headerlink {
color: #c60f0f;
font-size: 0.8em;
padding: 0 4px 0 4px;
text-decoration: none;
}
a.headerlink:hover {
background-color: #c60f0f;
color: white;
}
div.body p, div.body dd, div.body li, div.body blockquote {
text-align: justify;
line-height: 130%;
}
div.admonition p.admonition-title + p {
display: inline;
}
div.admonition p {
margin-bottom: 5px;
}
div.admonition pre {
margin-bottom: 5px;
}
div.admonition ul, div.admonition ol {
margin-bottom: 5px;
}
div.note {
background-color: #eee;
border: 1px solid #ccc;
}
div.seealso {
background-color: #ffc;
border: 1px solid #ff6;
}
div.topic {
background-color: #eee;
}
div.warning {
background-color: #ffe4e4;
border: 1px solid #f66;
}
p.admonition-title {
display: inline;
}
p.admonition-title:after {
content: ":";
}
pre {
padding: 5px;
background-color: #eeffcc;
color: #333333;
line-height: 120%;
border: 1px solid #ac9;
border-left: none;
border-right: none;
}
code {
background-color: #ecf0f3;
padding: 0 1px 0 1px;
font-size: 0.95em;
}
th {
background-color: #ede;
}
.warning code {
background: #efc2c2;
}
.note code {
background: #d6d6d6;
}
.viewcode-back {
font-family: sans-serif;
}
div.viewcode-block:target {
background-color: #f4debf;
border-top: 1px solid #ac9;
border-bottom: 1px solid #ac9;
}
div.code-block-caption {
color: #efefef;
background-color: #1c4e63;
}

File diff suppressed because one or more lines are too long

View File

@ -4,7 +4,7 @@
*
* Sphinx JavaScript utilities for all documentation.
*
* :copyright: Copyright 2007-2019 by the Sphinx team, see AUTHORS.
* :copyright: Copyright 2007-2021 by the Sphinx team, see AUTHORS.
* :license: BSD, see LICENSE for details.
*
*/
@ -29,9 +29,14 @@ if (!window.console || !console.firebug) {
/**
* small helper function to urldecode strings
*
* See https://developer.mozilla.org/en-US/docs/Web/JavaScript/Reference/Global_Objects/decodeURIComponent#Decoding_query_parameters_from_a_URL
*/
jQuery.urldecode = function(x) {
return decodeURIComponent(x).replace(/\+/g, ' ');
if (!x) {
return x
}
return decodeURIComponent(x.replace(/\+/g, ' '));
};
/**
@ -87,14 +92,13 @@ jQuery.fn.highlightText = function(text, className) {
node.nextSibling));
node.nodeValue = val.substr(0, pos);
if (isInSVG) {
var bbox = span.getBBox();
var rect = document.createElementNS("http://www.w3.org/2000/svg", "rect");
rect.x.baseVal.value = bbox.x;
var bbox = node.parentElement.getBBox();
rect.x.baseVal.value = bbox.x;
rect.y.baseVal.value = bbox.y;
rect.width.baseVal.value = bbox.width;
rect.height.baseVal.value = bbox.height;
rect.setAttribute('class', className);
var parentOfText = node.parentNode.parentNode;
addItems.push({
"parent": node.parentNode,
"target": rect});
@ -284,10 +288,12 @@ var Documentation = {
},
initOnKeyListeners: function() {
$(document).keyup(function(event) {
$(document).keydown(function(event) {
var activeElementType = document.activeElement.tagName;
// don't navigate when in search box or textarea
if (activeElementType !== 'TEXTAREA' && activeElementType !== 'INPUT' && activeElementType !== 'SELECT') {
// don't navigate when in search box, textarea, dropdown or button
if (activeElementType !== 'TEXTAREA' && activeElementType !== 'INPUT' && activeElementType !== 'SELECT'
&& activeElementType !== 'BUTTON' && !event.altKey && !event.ctrlKey && !event.metaKey
&& !event.shiftKey) {
switch (event.keyCode) {
case 37: // left
var prevHref = $('link[rel="prev"]').prop('href');
@ -295,12 +301,14 @@ var Documentation = {
window.location.href = prevHref;
return false;
}
break;
case 39: // right
var nextHref = $('link[rel="next"]').prop('href');
if (nextHref) {
window.location.href = nextHref;
return false;
}
break;
}
}
});

View File

@ -3,8 +3,10 @@ var DOCUMENTATION_OPTIONS = {
VERSION: '2.11.0',
LANGUAGE: 'None',
COLLAPSE_INDEX: false,
BUILDER: 'html',
FILE_SUFFIX: '.html',
LINK_SUFFIX: '.html',
HAS_SOURCE: true,
SOURCELINK_SUFFIX: '.txt',
NAVIGATION_WITH_KEYS: false,
NAVIGATION_WITH_KEYS: false
};

File diff suppressed because it is too large Load Diff

Before

Width:  |  Height:  |  Size: 434 KiB

File diff suppressed because it is too large Load Diff

File diff suppressed because one or more lines are too long

File diff suppressed because one or more lines are too long

File diff suppressed because one or more lines are too long

View File

@ -5,7 +5,7 @@
* This script contains the language-specific data used by searchtools.js,
* namely the list of stopwords, stemmer, scorer and splitter.
*
* :copyright: Copyright 2007-2019 by the Sphinx team, see AUTHORS.
* :copyright: Copyright 2007-2021 by the Sphinx team, see AUTHORS.
* :license: BSD, see LICENSE for details.
*
*/
@ -13,7 +13,8 @@
var stopwords = ["a","and","are","as","at","be","but","by","for","if","in","into","is","it","near","no","not","of","on","or","such","that","the","their","then","there","these","they","this","to","was","will","with"];
/* Non-minified version JS is _stemmer.js if file is provided */
/* Non-minified version is copied as a separate JS file, is available */
/**
* Porter Stemmer
*/
@ -199,7 +200,6 @@ var Stemmer = function() {
var splitChars = (function() {
var result = {};
var singles = [96, 180, 187, 191, 215, 247, 749, 885, 903, 907, 909, 930, 1014, 1648,

View File

@ -4,7 +4,7 @@
*
* Sphinx JavaScript utilities for the full-text search.
*
* :copyright: Copyright 2007-2019 by the Sphinx team, see AUTHORS.
* :copyright: Copyright 2007-2021 by the Sphinx team, see AUTHORS.
* :license: BSD, see LICENSE for details.
*
*/
@ -36,8 +36,10 @@ if (!Scorer) {
// query found in title
title: 15,
partialTitle: 7,
// query found in terms
term: 5
term: 5,
partialTerm: 2
};
}
@ -56,6 +58,19 @@ var Search = {
_queued_query : null,
_pulse_status : -1,
htmlToText : function(htmlString) {
var virtualDocument = document.implementation.createHTMLDocument('virtual');
var htmlElement = $(htmlString, virtualDocument);
htmlElement.find('.headerlink').remove();
docContent = htmlElement.find('[role=main]')[0];
if(docContent === undefined) {
console.warn("Content block not found. Sphinx search tries to obtain it " +
"via '[role=main]'. Could you check your theme or template.");
return "";
}
return docContent.textContent || docContent.innerText;
},
init : function() {
var params = $.getQueryParameters();
if (params.q) {
@ -120,7 +135,7 @@ var Search = {
this.out = $('#search-results');
this.title = $('<h2>' + _('Searching') + '</h2>').appendTo(this.out);
this.dots = $('<span></span>').appendTo(this.title);
this.status = $('<p style="display: none"></p>').appendTo(this.out);
this.status = $('<p class="search-summary">&nbsp;</p>').appendTo(this.out);
this.output = $('<ul class="search"/>').appendTo(this.out);
$('#search-progress').text(_('Preparing search...'));
@ -151,8 +166,7 @@ var Search = {
objectterms.push(tmp[i].toLowerCase());
}
if ($u.indexOf(stopwords, tmp[i].toLowerCase()) != -1 || tmp[i].match(/^\d+$/) ||
tmp[i] === "") {
if ($u.indexOf(stopwords, tmp[i].toLowerCase()) != -1 || tmp[i] === "") {
// skip this "word"
continue;
}
@ -234,8 +248,10 @@ var Search = {
// results left, load the summary and display it
if (results.length) {
var item = results.pop();
var listItem = $('<li style="display:none"></li>');
if (DOCUMENTATION_OPTIONS.FILE_SUFFIX === '') {
var listItem = $('<li></li>');
var requestUrl = "";
var linkUrl = "";
if (DOCUMENTATION_OPTIONS.BUILDER === 'dirhtml') {
// dirhtml builder
var dirname = item[0] + '/';
if (dirname.match(/\/index\/$/)) {
@ -243,44 +259,45 @@ var Search = {
} else if (dirname == 'index/') {
dirname = '';
}
listItem.append($('<a/>').attr('href',
DOCUMENTATION_OPTIONS.URL_ROOT + dirname +
highlightstring + item[2]).html(item[1]));
requestUrl = DOCUMENTATION_OPTIONS.URL_ROOT + dirname;
linkUrl = requestUrl;
} else {
// normal html builders
listItem.append($('<a/>').attr('href',
item[0] + DOCUMENTATION_OPTIONS.FILE_SUFFIX +
highlightstring + item[2]).html(item[1]));
requestUrl = DOCUMENTATION_OPTIONS.URL_ROOT + item[0] + DOCUMENTATION_OPTIONS.FILE_SUFFIX;
linkUrl = item[0] + DOCUMENTATION_OPTIONS.LINK_SUFFIX;
}
listItem.append($('<a/>').attr('href',
linkUrl +
highlightstring + item[2]).html(item[1]));
if (item[3]) {
listItem.append($('<span> (' + item[3] + ')</span>'));
Search.output.append(listItem);
listItem.slideDown(5, function() {
setTimeout(function() {
displayNextItem();
});
}, 5);
} else if (DOCUMENTATION_OPTIONS.HAS_SOURCE) {
var suffix = DOCUMENTATION_OPTIONS.SOURCELINK_SUFFIX;
if (suffix === undefined) {
suffix = '.txt';
}
$.ajax({url: DOCUMENTATION_OPTIONS.URL_ROOT + '_sources/' + item[5] + (item[5].slice(-suffix.length) === suffix ? '' : suffix),
$.ajax({url: requestUrl,
dataType: "text",
complete: function(jqxhr, textstatus) {
var data = jqxhr.responseText;
if (data !== '' && data !== undefined) {
listItem.append(Search.makeSearchSummary(data, searchterms, hlterms));
var summary = Search.makeSearchSummary(data, searchterms, hlterms);
if (summary) {
listItem.append(summary);
}
}
Search.output.append(listItem);
listItem.slideDown(5, function() {
setTimeout(function() {
displayNextItem();
});
}, 5);
}});
} else {
// no source available, just display title
Search.output.append(listItem);
listItem.slideDown(5, function() {
setTimeout(function() {
displayNextItem();
});
}, 5);
}
}
// search finished, update title and status message
@ -313,12 +330,13 @@ var Search = {
for (var prefix in objects) {
for (var name in objects[prefix]) {
var fullname = (prefix ? prefix + '.' : '') + name;
if (fullname.toLowerCase().indexOf(object) > -1) {
var fullnameLower = fullname.toLowerCase()
if (fullnameLower.indexOf(object) > -1) {
var score = 0;
var parts = fullname.split('.');
var parts = fullnameLower.split('.');
// check for different match types: exact matches of full name or
// "last name" (i.e. last dotted part)
if (fullname == object || parts[parts.length - 1] == object) {
if (fullnameLower == object || parts[parts.length - 1] == object) {
score += Scorer.objNameMatch;
// matches in last name
} else if (parts[parts.length - 1].indexOf(object) > -1) {
@ -364,6 +382,13 @@ var Search = {
return results;
},
/**
* See https://developer.mozilla.org/en-US/docs/Web/JavaScript/Guide/Regular_Expressions
*/
escapeRegExp : function(string) {
return string.replace(/[.*+\-?^${}()|[\]\\]/g, '\\$&'); // $& means the whole matched string
},
/**
* search for full-text terms in the index
*/
@ -385,6 +410,20 @@ var Search = {
{files: terms[word], score: Scorer.term},
{files: titleterms[word], score: Scorer.title}
];
// add support for partial matches
if (word.length > 2) {
var word_regex = this.escapeRegExp(word);
for (var w in terms) {
if (w.match(word_regex) && !terms[word]) {
_o.push({files: terms[w], score: Scorer.partialTerm})
}
}
for (var w in titleterms) {
if (w.match(word_regex) && !titleterms[word]) {
_o.push({files: titleterms[w], score: Scorer.partialTitle})
}
}
}
// no match but word was a required one
if ($u.every(_o, function(o){return o.files === undefined;})) {
@ -404,7 +443,7 @@ var Search = {
for (j = 0; j < _files.length; j++) {
file = _files[j];
if (!(file in scoreMap))
scoreMap[file] = {}
scoreMap[file] = {};
scoreMap[file][word] = o.score;
}
});
@ -412,7 +451,7 @@ var Search = {
// create the mapping
for (j = 0; j < files.length; j++) {
file = files[j];
if (file in fileMap)
if (file in fileMap && fileMap[file].indexOf(word) === -1)
fileMap[file].push(word);
else
fileMap[file] = [word];
@ -424,8 +463,12 @@ var Search = {
var valid = true;
// check if all requirements are matched
if (fileMap[file].length != searchterms.length)
continue;
var filteredTermCount = // as search terms with length < 3 are discarded: ignore
searchterms.filter(function(term){return term.length > 2}).length
if (
fileMap[file].length != searchterms.length &&
fileMap[file].length != filteredTermCount
) continue;
// ensure that none of the excluded terms is in the search result
for (i = 0; i < excluded.length; i++) {
@ -456,7 +499,11 @@ var Search = {
* words. the first one is used to find the occurrence, the
* latter for highlighting it.
*/
makeSearchSummary : function(text, keywords, hlwords) {
makeSearchSummary : function(htmlText, keywords, hlwords) {
var text = Search.htmlToText(htmlText);
if (text == "") {
return null;
}
var textLower = text.toLowerCase();
var start = 0;
$.each(keywords, function() {
@ -468,7 +515,7 @@ var Search = {
var excerpt = ((start > 0) ? '...' : '') +
$.trim(text.substr(start, 240)) +
((start + 240 - text.length) ? '...' : '');
var rv = $('<div class="context"></div>').text(excerpt);
var rv = $('<p class="context"></p>').text(excerpt);
$.each(hlwords, function() {
rv = rv.highlightText(this, 'highlighted');
});

View File

@ -1,159 +0,0 @@
/*
* sidebar.js
* ~~~~~~~~~~
*
* This script makes the Sphinx sidebar collapsible.
*
* .sphinxsidebar contains .sphinxsidebarwrapper. This script adds
* in .sphixsidebar, after .sphinxsidebarwrapper, the #sidebarbutton
* used to collapse and expand the sidebar.
*
* When the sidebar is collapsed the .sphinxsidebarwrapper is hidden
* and the width of the sidebar and the margin-left of the document
* are decreased. When the sidebar is expanded the opposite happens.
* This script saves a per-browser/per-session cookie used to
* remember the position of the sidebar among the pages.
* Once the browser is closed the cookie is deleted and the position
* reset to the default (expanded).
*
* :copyright: Copyright 2007-2019 by the Sphinx team, see AUTHORS.
* :license: BSD, see LICENSE for details.
*
*/
$(function() {
// global elements used by the functions.
// the 'sidebarbutton' element is defined as global after its
// creation, in the add_sidebar_button function
var bodywrapper = $('.bodywrapper');
var sidebar = $('.sphinxsidebar');
var sidebarwrapper = $('.sphinxsidebarwrapper');
// for some reason, the document has no sidebar; do not run into errors
if (!sidebar.length) return;
// original margin-left of the bodywrapper and width of the sidebar
// with the sidebar expanded
var bw_margin_expanded = bodywrapper.css('margin-left');
var ssb_width_expanded = sidebar.width();
// margin-left of the bodywrapper and width of the sidebar
// with the sidebar collapsed
var bw_margin_collapsed = '.8em';
var ssb_width_collapsed = '.8em';
// colors used by the current theme
var dark_color = $('.related').css('background-color');
var light_color = $('.document').css('background-color');
function sidebar_is_collapsed() {
return sidebarwrapper.is(':not(:visible)');
}
function toggle_sidebar() {
if (sidebar_is_collapsed())
expand_sidebar();
else
collapse_sidebar();
}
function collapse_sidebar() {
sidebarwrapper.hide();
sidebar.css('width', ssb_width_collapsed);
bodywrapper.css('margin-left', bw_margin_collapsed);
sidebarbutton.css({
'margin-left': '0',
'height': bodywrapper.height()
});
sidebarbutton.find('span').text('»');
sidebarbutton.attr('title', _('Expand sidebar'));
document.cookie = 'sidebar=collapsed';
}
function expand_sidebar() {
bodywrapper.css('margin-left', bw_margin_expanded);
sidebar.css('width', ssb_width_expanded);
sidebarwrapper.show();
sidebarbutton.css({
'margin-left': ssb_width_expanded-12,
'height': bodywrapper.height()
});
sidebarbutton.find('span').text('«');
sidebarbutton.attr('title', _('Collapse sidebar'));
document.cookie = 'sidebar=expanded';
}
function add_sidebar_button() {
sidebarwrapper.css({
'float': 'left',
'margin-right': '0',
'width': ssb_width_expanded - 28
});
// create the button
sidebar.append(
'<div id="sidebarbutton"><span>&laquo;</span></div>'
);
var sidebarbutton = $('#sidebarbutton');
light_color = sidebarbutton.css('background-color');
// find the height of the viewport to center the '<<' in the page
var viewport_height;
if (window.innerHeight)
viewport_height = window.innerHeight;
else
viewport_height = $(window).height();
sidebarbutton.find('span').css({
'display': 'block',
'margin-top': (viewport_height - sidebar.position().top - 20) / 2
});
sidebarbutton.click(toggle_sidebar);
sidebarbutton.attr('title', _('Collapse sidebar'));
sidebarbutton.css({
'color': '#FFFFFF',
'border-left': '1px solid ' + dark_color,
'font-size': '1.2em',
'cursor': 'pointer',
'height': bodywrapper.height(),
'padding-top': '1px',
'margin-left': ssb_width_expanded - 12
});
sidebarbutton.hover(
function () {
$(this).css('background-color', dark_color);
},
function () {
$(this).css('background-color', light_color);
}
);
}
function set_position_from_cookie() {
if (!document.cookie)
return;
var items = document.cookie.split(';');
for(var k=0; k<items.length; k++) {
var key_val = items[k].split('=');
var key = key_val[0].replace(/ /, ""); // strip leading spaces
if (key == 'sidebar') {
var value = key_val[1];
if ((value == 'collapsed') && (!sidebar_is_collapsed()))
collapse_sidebar();
else if ((value == 'expanded') && (sidebar_is_collapsed()))
expand_sidebar();
}
}
}
add_sidebar_button();
var sidebarbutton = $('#sidebarbutton');
set_position_from_cookie();
});

File diff suppressed because it is too large Load Diff

File diff suppressed because one or more lines are too long

View File

@ -1,70 +1,31 @@
<!DOCTYPE html>
<html class="writer-html4" lang="en" >
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Index &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script type="text/javascript" id="documentation_options" data-url_root="./" src="_static/documentation_options.js"></script>
<script type="text/javascript" src="_static/jquery.js"></script>
<script type="text/javascript" src="_static/underscore.js"></script>
<script type="text/javascript" src="_static/doctools.js"></script>
<script type="text/javascript" src="_static/language_data.js"></script>
<script type="text/javascript" src="_static/js/theme.js"></script>
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<link rel="index" title="Index" href="#" />
<link rel="search" title="Search" href="search.html" />
</head>
<body class="wy-body-for-nav">
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="search.html" method="get">
<input type="text" name="q" placeholder="Search docs" />
@ -72,83 +33,40 @@
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul>
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
<div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="main navigation">
<!-- Local TOC -->
<div class="local-toc"></div>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap">
<nav class="wy-nav-top" aria-label="top navigation">
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="breadcrumbs navigation">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Index</li>
<li class="wy-breadcrumbs-aside">
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<h1 id="index">Index</h1>
@ -158,46 +76,30 @@
</div>
</div>
<footer>
<hr/>
<div role="contentinfo">
<p>
&#169; Copyright 2021, The Cryptol Team.
</p>
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script type="text/javascript">
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
</script>
</body>
</html>

Binary file not shown.

View File

@ -1,72 +1,34 @@
<!DOCTYPE html>
<html class="writer-html4" lang="en" >
<html class="writer-html5" lang="en" >
<head>
<meta charset="utf-8" />
<meta name="viewport" content="width=device-width, initial-scale=1.0" />
<title>Search &mdash; Cryptol 2.11.0 documentation</title>
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/pygments.css" type="text/css" />
<link rel="stylesheet" href="_static/css/theme.css" type="text/css" />
<!--[if lt IE 9]>
<script src="_static/js/html5shiv.min.js"></script>
<![endif]-->
<script type="text/javascript" id="documentation_options" data-url_root="./" src="_static/documentation_options.js"></script>
<script type="text/javascript" src="_static/jquery.js"></script>
<script type="text/javascript" src="_static/underscore.js"></script>
<script type="text/javascript" src="_static/doctools.js"></script>
<script type="text/javascript" src="_static/language_data.js"></script>
<script type="text/javascript" src="_static/js/theme.js"></script>
<script type="text/javascript" src="_static/searchtools.js"></script>
<script type="text/javascript" src="_static/language_data.js"></script>
<script data-url_root="./" id="documentation_options" src="_static/documentation_options.js"></script>
<script src="_static/jquery.js"></script>
<script src="_static/underscore.js"></script>
<script src="_static/doctools.js"></script>
<script src="_static/js/theme.js"></script>
<script src="_static/searchtools.js"></script>
<script src="_static/language_data.js"></script>
<link rel="index" title="Index" href="genindex.html" />
<link rel="search" title="Search" href="#" />
</head>
<body class="wy-body-for-nav">
<body class="wy-body-for-nav">
<div class="wy-grid-for-nav">
<nav data-toggle="wy-nav-shift" class="wy-nav-side">
<div class="wy-side-scroll">
<div class="wy-side-nav-search" >
<a href="RefMan.html" class="icon icon-home"> Cryptol
</a>
<div role="search">
<form id="rtd-search-form" class="wy-form" action="#" method="get">
<input type="text" name="q" placeholder="Search docs" />
@ -74,81 +36,40 @@
<input type="hidden" name="area" value="default" />
</form>
</div>
</div><div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="Navigation menu">
<p class="caption" role="heading"><span class="caption-text">Cryptol Reference Manual</span></p>
<ul>
<li class="toctree-l1"><a class="reference internal" href="BasicSyntax.html">Basic Syntax</a></li>
<li class="toctree-l1"><a class="reference internal" href="Expressions.html">Expressions</a></li>
<li class="toctree-l1"><a class="reference internal" href="BasicTypes.html">Basic Types</a></li>
<li class="toctree-l1"><a class="reference internal" href="OverloadedOperations.html">Overloaded Operations</a></li>
<li class="toctree-l1"><a class="reference internal" href="TypeDeclarations.html">Type Declarations</a></li>
<li class="toctree-l1"><a class="reference internal" href="Modules.html">Modules</a></li>
</ul>
</div>
<div class="wy-menu wy-menu-vertical" data-spy="affix" role="navigation" aria-label="main navigation">
<!-- Local TOC -->
<div class="local-toc"></div>
</div>
</div>
</nav>
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap">
<nav class="wy-nav-top" aria-label="top navigation">
<section data-toggle="wy-nav-shift" class="wy-nav-content-wrap"><nav class="wy-nav-top" aria-label="Mobile navigation menu" >
<i data-toggle="wy-nav-top" class="fa fa-bars"></i>
<a href="RefMan.html">Cryptol</a>
</nav>
<div class="wy-nav-content">
<div class="rst-content">
<div role="navigation" aria-label="breadcrumbs navigation">
<div role="navigation" aria-label="Page navigation">
<ul class="wy-breadcrumbs">
<li><a href="RefMan.html" class="icon icon-home"></a> &raquo;</li>
<li>Search</li>
<li class="wy-breadcrumbs-aside">
</li>
</ul>
<hr/>
</div>
<div role="main" class="document" itemscope="itemscope" itemtype="http://schema.org/Article">
<div itemprop="articleBody">
<noscript>
<div id="fallback" class="admonition warning">
<p class="last">
@ -163,51 +84,35 @@
</div>
</div>
</div>
<footer>
<hr/>
<div role="contentinfo">
<p>
&#169; Copyright 2021, The Cryptol Team.
</p>
<p>&#169; Copyright 2021, The Cryptol Team.</p>
</div>
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
Built with <a href="https://www.sphinx-doc.org/">Sphinx</a> using a
<a href="https://github.com/readthedocs/sphinx_rtd_theme">theme</a>
provided by <a href="https://readthedocs.org">Read the Docs</a>.
provided by <a href="https://readthedocs.org">Read the Docs</a>.
</footer>
</div>
</div>
</section>
</div>
<script type="text/javascript">
<script>
jQuery(function () {
SphinxRtdTheme.Navigation.enable(true);
});
</script>
<script type="text/javascript">
<script>
jQuery(function() { Search.loadIndex("searchindex.js"); });
</script>
<script type="text/javascript" id="searchindexloader"></script>
<script id="searchindexloader"></script>

File diff suppressed because one or more lines are too long

View File

@ -11,10 +11,10 @@
# If extensions (or modules to document with autodoc) are in another directory,
# add these directories to sys.path here. If the directory is relative to the
# documentation root, use os.path.abspath to make it absolute, like shown here.
#
# import os
# import sys
# sys.path.insert(0, os.path.abspath('.'))
import os
import sys
sys.path.insert(0, os.path.abspath('.'))
import sphinx_rtd_theme

View File

@ -9,12 +9,12 @@
-- Portability : portable
{- A utility for spliting a long column of stuff into multiple columns. -}
import Data.List(transpose)
import Data.List(transpose,sort)
rs = 4 -- number of rows per column
spacing = 4 -- blanks between columns
main = interact (unlines . map concat . transpose . map toCol . chop rs . lines)
main = interact (unlines . map concat . transpose . map toCol . chop rs . sort . lines)
colWidth xs = spacing + maximum (0 : map length xs)

52
module_system_example.txt Normal file
View File

@ -0,0 +1,52 @@
signature S where -- u1
type n : # -- u5
module M where -- u2
parameter X : S -- X, u1
-- introduces: u6
-- to do this, we need to resolve `S` first
f : [X.n] -- u7, u6
f = ... -- u7
module N where -- u2
type n = 16 -- u9
module I = -- u4
M with X = N -- u2, X, u3
import I -- u4
-- introduces: u10
g = f -- u8, u10
--------------------------------------------------------------------------------
Defines (naming env)
toplevel:
NS Names Uniq
module S u1
module M u2
module N u3
module I u4
value g u8
u1:
type n u5
u2:
type X.n u6
value f u7
u3:
type n u9
u4:
value f u10

View File

@ -171,8 +171,9 @@ evalExpr sym env expr = case expr of
Just (Right val)
| ?callStacks ->
case nameInfo n of
Declared{} -> sPushFrame sym n ?range (cacheCallStack sym =<< val)
Parameter -> cacheCallStack sym =<< val
GlobalName {} ->
sPushFrame sym n ?range (cacheCallStack sym =<< val)
LocalName {} -> cacheCallStack sym =<< val
| otherwise -> val
Nothing -> do
envdoc <- ppEnv sym defaultPPOpts env

View File

@ -0,0 +1,227 @@
{-# Language ImplicitParams #-}
module Cryptol.IR.TraverseNames where
import Data.Set(Set)
import qualified Data.Set as Set
import Data.Functor.Identity
import Cryptol.ModuleSystem.Name(nameUnique)
import Cryptol.Utils.RecordMap(traverseRecordMap)
import Cryptol.Parser.Position(Located(..))
import Cryptol.TypeCheck.AST
traverseNames ::
(TraverseNames t, Applicative f) => (Name -> f Name) -> (t -> f t)
traverseNames f = let ?name = f in traverseNamesIP
mapNames :: (TraverseNames t) => (Name -> Name) -> t -> t
mapNames f x = result
where
Identity result = let ?name = pure . f
in traverseNamesIP x
class TraverseNames t where
traverseNamesIP :: (Applicative f, ?name :: Name -> f Name) => t -> f t
instance TraverseNames a => TraverseNames [a] where
traverseNamesIP = traverse traverseNamesIP
instance TraverseNames a => TraverseNames (Maybe a) where
traverseNamesIP = traverse traverseNamesIP
instance (Ord a, TraverseNames a) => TraverseNames (Set a) where
traverseNamesIP = fmap Set.fromList . traverseNamesIP . Set.toList
instance TraverseNames a => TraverseNames (Located a) where
traverseNamesIP (Located r a) = Located r <$> traverseNamesIP a
instance TraverseNames Name where
traverseNamesIP = ?name
instance (Ord a, TraverseNames a) => TraverseNames (ExportSpec a) where
traverseNamesIP (ExportSpec mp) = ExportSpec <$> traverse traverseNamesIP mp
instance TraverseNames Expr where
traverseNamesIP expr =
case expr of
EList es t -> EList <$> traverseNamesIP es <*> traverseNamesIP t
ETuple es -> ETuple <$> traverseNamesIP es
ERec mp -> ERec <$> traverseRecordMap (\_ -> traverseNamesIP) mp
ESel e l -> (`ESel` l) <$> traverseNamesIP e
ESet t e1 l e2 -> ESet <$> traverseNamesIP t
<*> traverseNamesIP e1
<*> pure l
<*> traverseNamesIP e2
EIf e1 e2 e3 -> EIf <$> traverseNamesIP e1
<*> traverseNamesIP e2
<*> traverseNamesIP e3
EComp t1 t2 e mss -> EComp <$> traverseNamesIP t1
<*> traverseNamesIP t2
<*> traverseNamesIP e
<*> traverseNamesIP mss
EVar x -> EVar <$> traverseNamesIP x
ETAbs tp e -> ETAbs <$> traverseNamesIP tp <*> traverseNamesIP e
ETApp e t -> ETApp <$> traverseNamesIP e <*> traverseNamesIP t
EApp e1 e2 -> EApp <$> traverseNamesIP e1 <*> traverseNamesIP e2
EAbs x t e -> EAbs <$> traverseNamesIP x
<*> traverseNamesIP t
<*> traverseNamesIP e
ELocated r e -> ELocated r <$> traverseNamesIP e
EProofAbs p e -> EProofAbs <$> traverseNamesIP p <*> traverseNamesIP e
EProofApp e -> EProofApp <$> traverseNamesIP e
EWhere e ds -> EWhere <$> traverseNamesIP e <*> traverseNamesIP ds
instance TraverseNames Match where
traverseNamesIP mat =
case mat of
From x t1 t2 e -> From <$> traverseNamesIP x
<*> traverseNamesIP t1
<*> traverseNamesIP t2
<*> traverseNamesIP e
Let d -> Let <$> traverseNamesIP d
instance TraverseNames DeclGroup where
traverseNamesIP dg =
case dg of
NonRecursive d -> NonRecursive <$> traverseNamesIP d
Recursive ds -> Recursive <$> traverseNamesIP ds
instance TraverseNames Decl where
traverseNamesIP decl = mk <$> traverseNamesIP (dName decl)
<*> traverseNamesIP (dSignature decl)
<*> traverseNamesIP (dDefinition decl)
where mk nm sig def = decl { dName = nm
, dSignature = sig
, dDefinition = def
}
instance TraverseNames DeclDef where
traverseNamesIP d =
case d of
DPrim -> pure d
DExpr e -> DExpr <$> traverseNamesIP e
instance TraverseNames Schema where
traverseNamesIP (Forall as ps t) =
Forall <$> traverseNamesIP as
<*> traverseNamesIP ps
<*> traverseNamesIP t
instance TraverseNames TParam where
traverseNamesIP tp = mk <$> traverseNamesIP (tpFlav tp)
<*> traverseNamesIP (tpInfo tp)
-- XXX: module parameters should probably be represented directly
-- as (abstract) user-defined types, rather than type variables.
where mk f i = case f of
TPModParam x ->
tp { tpUnique = nameUnique x, tpFlav = f, tpInfo = i }
_ -> tp { tpFlav = f, tpInfo = i }
instance TraverseNames TPFlavor where
traverseNamesIP tpf =
case tpf of
TPModParam x -> TPModParam <$> traverseNamesIP x
TPUnifyVar -> pure tpf
TPSchemaParam x -> TPSchemaParam <$> traverseNamesIP x
TPTySynParam x -> TPTySynParam <$> traverseNamesIP x
TPPropSynParam x -> TPPropSynParam <$> traverseNamesIP x
TPNewtypeParam x -> TPNewtypeParam <$> traverseNamesIP x
TPPrimParam x -> TPPrimParam <$> traverseNamesIP x
instance TraverseNames TVarInfo where
traverseNamesIP (TVarInfo r s) = TVarInfo r <$> traverseNamesIP s
instance TraverseNames TypeSource where
traverseNamesIP src =
case src of
TVFromModParam x -> TVFromModParam <$> traverseNamesIP x
TVFromSignature x -> TVFromSignature <$> traverseNamesIP x
TypeWildCard -> pure src
TypeOfRecordField {} -> pure src
TypeOfTupleField {} -> pure src
TypeOfSeqElement -> pure src
LenOfSeq -> pure src
TypeParamInstNamed x i -> TypeParamInstNamed <$> traverseNamesIP x
<*> pure i
TypeParamInstPos x i -> TypeParamInstPos <$> traverseNamesIP x
<*> pure i
DefinitionOf x -> DefinitionOf <$> traverseNamesIP x
LenOfCompGen -> pure src
TypeOfArg arg -> TypeOfArg <$> traverseNamesIP arg
TypeOfRes -> pure src
FunApp -> pure src
TypeOfIfCondExpr -> pure src
TypeFromUserAnnotation -> pure src
GeneratorOfListComp -> pure src
TypeErrorPlaceHolder -> pure src
instance TraverseNames ArgDescr where
traverseNamesIP arg = mk <$> traverseNamesIP (argDescrFun arg)
where mk n = arg { argDescrFun = n }
instance TraverseNames Type where
traverseNamesIP ty =
case ty of
TCon tc ts -> TCon <$> traverseNamesIP tc <*> traverseNamesIP ts
TVar x -> TVar <$> traverseNamesIP x
TUser x ts t -> TUser <$> traverseNamesIP x
<*> traverseNamesIP ts
<*> traverseNamesIP t
TRec rm -> TRec <$> traverseRecordMap (\_ -> traverseNamesIP) rm
TNewtype nt ts -> TNewtype <$> traverseNamesIP nt <*> traverseNamesIP ts
instance TraverseNames TCon where
traverseNamesIP tcon =
case tcon of
TC tc -> TC <$> traverseNamesIP tc
_ -> pure tcon
instance TraverseNames TC where
traverseNamesIP tc =
case tc of
TCAbstract ut -> TCAbstract <$> traverseNamesIP ut
_ -> pure tc
instance TraverseNames UserTC where
traverseNamesIP (UserTC x k) = UserTC <$> traverseNamesIP x <*> pure k
instance TraverseNames TVar where
traverseNamesIP tvar =
case tvar of
TVFree x k ys i -> TVFree x k <$> traverseNamesIP ys <*> traverseNamesIP i
TVBound x -> TVBound <$> traverseNamesIP x
instance TraverseNames Newtype where
traverseNamesIP nt = mk <$> traverseNamesIP (ntName nt)
<*> traverseNamesIP (ntParams nt)
<*> traverseNamesIP (ntConstraints nt)
<*> traverseRecordMap (\_ -> traverseNamesIP)
(ntFields nt)
where
mk a b c d = nt { ntName = a
, ntParams = b
, ntConstraints = c
, ntFields = d
}
instance TraverseNames ModTParam where
traverseNamesIP nt = mk <$> traverseNamesIP (mtpName nt)
where
mk x = nt { mtpName = x }
instance TraverseNames ModVParam where
traverseNamesIP nt = mk <$> traverseNamesIP (mvpName nt)
<*> traverseNamesIP (mvpType nt)
where
mk x t = nt { mvpName = x, mvpType = t }

View File

@ -29,8 +29,7 @@ module Cryptol.ModuleSystem (
, renameType
-- * Interfaces
, Iface, IfaceG(..), IfaceParams(..), IfaceDecls(..), T.genIface
, IfaceTySyn, IfaceDecl(..)
, Iface, IfaceG(..), IfaceDecls(..), T.genIface, IfaceDecl(..)
) where
import Data.Map (Map)
@ -63,21 +62,21 @@ findModule :: P.ModName -> ModuleCmd ModulePath
findModule n env = runModuleM env (Base.findModule n)
-- | Load the module contained in the given file.
loadModuleByPath :: FilePath -> ModuleCmd (ModulePath,T.Module)
loadModuleByPath :: FilePath -> ModuleCmd (ModulePath,T.TCTopEntity)
loadModuleByPath path minp =
runModuleM minp{ minpModuleEnv = resetModuleEnv (minpModuleEnv minp) } $ do
unloadModule ((InFile path ==) . lmFilePath)
m <- Base.loadModuleByPath path
setFocusedModule (T.mName m)
setFocusedModule (T.tcTopEntitytName m)
return (InFile path,m)
-- | Load the given parsed module.
loadModuleByName :: P.ModName -> ModuleCmd (ModulePath,T.Module)
loadModuleByName :: P.ModName -> ModuleCmd (ModulePath,T.TCTopEntity)
loadModuleByName n minp =
runModuleM minp{ minpModuleEnv = resetModuleEnv (minpModuleEnv minp) } $ do
unloadModule ((n ==) . lmName)
(path,m') <- Base.loadModuleFrom False (FromModule n)
setFocusedModule (T.mName m')
setFocusedModule (T.tcTopEntitytName m')
return (path,m')
-- Extended Environments -------------------------------------------------------

View File

@ -13,15 +13,15 @@
{-# LANGUAGE ImplicitParams #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE BlockArguments #-}
module Cryptol.ModuleSystem.Base where
import qualified Control.Exception as X
import Control.Monad (unless,when)
import Control.Monad (unless,forM)
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import Data.Text.Encoding (decodeUtf8')
import Data.IORef(newIORef,readIORef)
import System.Directory (doesFileExist, canonicalizePath)
import System.FilePath ( addExtension
, isAbsolute
@ -44,8 +44,9 @@ import Cryptol.ModuleSystem.Fingerprint
import Cryptol.ModuleSystem.Interface
import Cryptol.ModuleSystem.Monad
import Cryptol.ModuleSystem.Name (Name,liftSupply,PrimMap,ModPath(..))
import Cryptol.ModuleSystem.Env (lookupModule
, LoadedModule(..)
import Cryptol.ModuleSystem.Env ( lookupModule
, lookupTCEntity
, LoadedModuleG(..), lmInterface
, meCoreLint, CoreLint(..)
, ModContext(..)
, ModulePath(..), modulePathLabel)
@ -65,10 +66,9 @@ import qualified Cryptol.TypeCheck.AST as T
import qualified Cryptol.TypeCheck.PP as T
import qualified Cryptol.TypeCheck.Sanity as TcSanity
import Cryptol.Transform.AddModParams (addModParams)
import Cryptol.Utils.Ident ( preludeName, floatName, arrayName, suiteBName, primeECName
, preludeReferenceName, interactiveName, modNameChunks
, notParamInstModName, isParamInstModName )
, modNameToNormalModName )
import Cryptol.Utils.PP (pretty)
import Cryptol.Utils.Panic (panic)
import Cryptol.Utils.Logger(logPutStrLn, logPrint)
@ -118,7 +118,7 @@ noPat a = do
-- Parsing ---------------------------------------------------------------------
-- | Parse a module and expand includes
parseModule :: ModulePath -> ModuleM (Fingerprint, P.Module PName)
parseModule :: ModulePath -> ModuleM (Fingerprint, [P.Module PName])
parseModule path = do
getBytes <- getByteReader
@ -150,15 +150,16 @@ parseModule path = do
}
case P.parseModule cfg txt of
Right pm ->
Right pms ->
do let fp = fingerprint bytes
pm1 <- case path of
InFile p ->
do r <- getByteReader
mb <- io (removeIncludesModule r p pm)
case mb of
Right ok -> pure ok
Left err -> noIncludeErrors err
forM pms \pm ->
do mb <- io (removeIncludesModule r p pm)
case mb of
Right ok -> pure ok
Left err -> noIncludeErrors err
{- We don't do "include" resolution for in-memory files
because at the moment the include resolution pass requires
@ -166,51 +167,55 @@ parseModule path = do
looking for other inlcude files. This could be
generalized, but we can do it once we have a concrete use
case as it would help guide the design. -}
InMem {} -> pure pm
InMem {} -> pure pms
fp `seq` return (fp, pm1)
Left err -> moduleParseError path err
-- Modules ---------------------------------------------------------------------
-- Top Level Modules and Signatures ----------------------------------------------
-- | Load a module by its path.
loadModuleByPath :: FilePath -> ModuleM T.Module
loadModuleByPath :: FilePath -> ModuleM T.TCTopEntity
loadModuleByPath path = withPrependedSearchPath [ takeDirectory path ] $ do
let fileName = takeFileName path
foundPath <- findFile fileName
(fp, pm) <- parseModule (InFile foundPath)
let n = thing (P.mName pm)
(fp, pms) <- parseModule (InFile foundPath)
last <$>
forM pms \pm ->
do let n = thing (P.mName pm)
-- Check whether this module name has already been loaded from a different file
env <- getModuleEnv
-- path' is the resolved, absolute path, used only for checking
-- whether it's already been loaded
path' <- io (canonicalizePath foundPath)
-- Check whether this module name has already been loaded from a
-- different file
env <- getModuleEnv
-- path' is the resolved, absolute path, used only for checking
-- whether it's already been loaded
path' <- io (canonicalizePath foundPath)
case lookupModule n env of
-- loadModule will calculate the canonical path again
Nothing -> doLoadModule False (FromModule n) (InFile foundPath) fp pm
Just lm
| path' == loaded -> return (lmModule lm)
| otherwise -> duplicateModuleName n path' loaded
where loaded = lmModuleId lm
case lookupTCEntity n env of
-- loadModule will calculate the canonical path again
Nothing -> doLoadModule False (FromModule n) (InFile foundPath) fp pm
Just lm
| path' == loaded -> return (lmData lm)
| otherwise -> duplicateModuleName n path' loaded
where loaded = lmModuleId lm
-- | Load a module, unless it was previously loaded.
loadModuleFrom :: Bool {- ^ quiet mode -} -> ImportSource -> ModuleM (ModulePath,T.Module)
loadModuleFrom ::
Bool {- ^ quiet mode -} -> ImportSource -> ModuleM (ModulePath,T.TCTopEntity)
loadModuleFrom quiet isrc =
do let n = importedModule isrc
mb <- getLoadedMaybe n
case mb of
Just m -> return (lmFilePath m, lmModule m)
Just m -> return (lmFilePath m, lmData m)
Nothing ->
do path <- findModule n
errorInFile path $
do (fp, pm) <- parseModule path
m <- doLoadModule quiet isrc path fp pm
return (path,m)
do (fp, pms) <- parseModule path
ms <- mapM (doLoadModule quiet isrc path fp) pms
return (path,last ms)
-- | Load dependencies, typecheck, and add to the eval environment.
doLoadModule ::
@ -219,37 +224,34 @@ doLoadModule ::
ModulePath ->
Fingerprint ->
P.Module PName ->
ModuleM T.Module
ModuleM T.TCTopEntity
doLoadModule quiet isrc path fp pm0 =
loading isrc $
do let pm = addPrelude pm0
loadDeps pm
let what = case P.mDef pm of
P.InterfaceModule {} -> "interface module"
_ -> "module"
unless quiet $ withLogger logPutStrLn
("Loading module " ++ pretty (P.thing (P.mName pm)))
("Loading " ++ what ++ " " ++ pretty (P.thing (P.mName pm)))
(nameEnv,tcmod) <- checkModule isrc pm
tcm <- optionalInstantiate tcmod
(nameEnv,tcm) <- checkModule isrc pm
-- extend the eval env, unless a functor.
tbl <- Concrete.primTable <$> getEvalOptsAction
let ?evalPrim = \i -> Right <$> Map.lookup i tbl
callStacks <- getCallStacks
let ?callStacks = callStacks
unless (T.isParametrizedModule tcm) $ modifyEvalEnv (E.moduleEnv Concrete tcm)
loadedModule path fp nameEnv tcm
case tcm of
T.TCTopModule m | not (T.isParametrizedModule m) ->
modifyEvalEnv (E.moduleEnv Concrete m)
_ -> pure ()
loadedModule path fp nameEnv tcm
return tcm
where
optionalInstantiate tcm
| isParamInstModName (importedModule isrc) =
if T.isParametrizedModule tcm then
case addModParams tcm of
Right tcm1 -> return tcm1
Left xs -> failedToParameterizeModDefs (T.mName tcm) xs
else notAParameterizedModule (T.mName tcm)
| otherwise = return tcm
@ -298,30 +300,37 @@ findModule n = do
-- | Discover a file. This is distinct from 'findModule' in that we
-- assume we've already been given a particular file name.
findFile :: FilePath -> ModuleM FilePath
findFile path | isAbsolute path = do
-- No search path checking for absolute paths
b <- io (doesFileExist path)
if b then return path else cantFindFile path
findFile path = do
paths <- getSearchPath
loop (possibleFiles paths)
where
loop paths = case paths of
path':rest -> do
b <- io (doesFileExist path')
if b then return (normalise path') else loop rest
[] -> cantFindFile path
possibleFiles paths = map (</> path) paths
findFile path
| isAbsolute path =
do -- No search path checking for absolute paths
b <- io (doesFileExist path)
if b then return path else cantFindFile path
| otherwise =
do paths <- getSearchPath
loop (possibleFiles paths)
where
loop paths = case paths of
path' : rest ->
do b <- io (doesFileExist path')
if b then return (normalise path') else loop rest
[] -> cantFindFile path
possibleFiles paths = map (</> path) paths
-- | Add the prelude to the import list if it's not already mentioned.
addPrelude :: P.Module PName -> P.Module PName
addPrelude m
| preludeName == P.thing (P.mName m) = m
| preludeName `elem` importedMods = m
| otherwise = m { mDecls = importPrelude : mDecls m }
| otherwise = m { mDef = newDef }
where
newDef =
case mDef m of
NormalModule ds -> NormalModule (P.DImport prel : ds)
FunctorInstance f as ins -> FunctorInstance f as ins
InterfaceModule s -> InterfaceModule s { sigImports = prel : sigImports s }
importedMods = map (P.iModule . P.thing) (P.mImports m)
importPrelude = P.DImport P.Located
prel = P.Located
{ P.srcRange = emptyRange
, P.thing = P.Import
{ iModule = P.ImpTop preludeName
@ -331,15 +340,43 @@ addPrelude m
}
-- | Load the dependencies of a module into the environment.
loadDeps :: P.Module name -> ModuleM ()
loadDeps :: P.ModuleG mname name -> ModuleM ()
loadDeps m =
do mapM_ loadI (P.mImports m)
mapM_ loadF (P.mInstance m)
case mDef m of
NormalModule ds -> mapM_ depsOfDecl ds
FunctorInstance f as _ ->
do loadImpName FromModuleInstance f
case as of
DefaultInstArg a -> loadImpName FromModuleInstance a
DefaultInstAnonArg ds -> mapM_ depsOfDecl ds
NamedInstArgs args -> mapM_ loadInstArg args
InterfaceModule s -> mapM_ loadImpD (sigImports s)
where
loadI i = do (_,m1) <- loadModuleFrom False (FromImport i)
when (T.isParametrizedModule m1) $ importParamModule $ T.mName m1
loadF f = do _ <- loadModuleFrom False (FromModuleInstance f)
return ()
loadI i = do _ <- loadModuleFrom False i
pure ()
loadImpName src l =
case thing l of
ImpTop f -> loadI (src l { thing = f })
_ -> pure ()
loadImpD li = loadImpName (FromImport . new) (iModule <$> li)
where new i = i { thing = (thing li) { iModule = thing i } }
loadInstArg (ModuleInstanceArg _ f) = loadImpName FromModuleInstance f
depsOfDecl d =
case d of
DImport li -> loadImpD li
DModule TopLevel { tlValue = NestedModule nm } -> loadDeps nm
DModParam mo -> loadImpName FromSigImport s
where s = mpSignature mo
_ -> pure ()
@ -405,38 +442,17 @@ getPrimMap =
Nothing -> panic "Cryptol.ModuleSystem.Base.getPrimMap"
[ "Unable to find the prelude" ]
-- | Load a module, be it a normal module or a functor instantiation.
checkModule :: ImportSource -> P.Module PName -> ModuleM (R.NamingEnv, T.Module)
checkModule isrc m =
case P.mInstance m of
Nothing -> checkSingleModule T.tcModule isrc m
Just fmName ->
do mbtf <- getLoadedMaybe (thing fmName)
case mbtf of
Just tf ->
do renThis <- io $ newIORef (lmNamingEnv tf)
let how = T.tcModuleInst renThis (lmModule tf)
(_,m') <- checkSingleModule how isrc m
newEnv <- io $ readIORef renThis
pure (newEnv,m')
Nothing -> panic "checkModule"
[ "Functor of module instantiation not loaded" ]
-- | Typecheck a single module. If the module is an instantiation
-- of a functor, then this just type-checks the instantiating parameters.
-- See 'checkModule'
-- | Typecheck a single module.
-- Note: we assume that @include@s have already been processed
checkSingleModule ::
Act (P.Module Name) T.Module {- ^ how to check -} ->
ImportSource {- ^ why are we loading this -} ->
P.Module PName {- ^ module to check -} ->
ModuleM (R.NamingEnv,T.Module)
checkSingleModule how isrc m = do
checkModule ::
ImportSource {- ^ why are we loading this -} ->
P.Module PName {- ^ module to check -} ->
ModuleM (R.NamingEnv,T.TCTopEntity)
checkModule isrc m = do
-- check that the name of the module matches expectations
let nm = importedModule isrc
unless (notParamInstModName nm == thing (P.mName m))
unless (modNameToNormalModName nm == modNameToNormalModName (thing (P.mName m)))
(moduleNameMismatch nm (mName m))
-- remove pattern bindings
@ -445,6 +461,13 @@ checkSingleModule how isrc m = do
-- rename everything
renMod <- renameModule npm
{-
-- dump renamed
unless (thing (mName (R.rmModule renMod)) == preludeName)
do (io $ print (T.pp renMod))
-- io $ exitSuccess
--}
-- when generating the prim map for the typechecker, if we're checking the
-- prelude, we have to generate the map from the renaming environment, as we
-- don't have the interface yet.
@ -453,21 +476,22 @@ checkSingleModule how isrc m = do
else getPrimMap
-- typecheck
let act = TCAction { tcAction = how
, tcLinter = moduleLinter (P.thing (P.mName m))
let act = TCAction { tcAction = T.tcModule
, tcLinter = tcTopEntitytLinter (P.thing (P.mName m))
, tcPrims = prims }
tcm0 <- typecheck act (R.rmModule renMod) noIfaceParams (R.rmImported renMod)
tcm <- typecheck act (R.rmModule renMod) mempty (R.rmImported renMod)
let tcm = tcm0 -- fromMaybe tcm0 (addModParams tcm0)
rewMod <- liftSupply (`rewModule` tcm)
rewMod <- case tcm of
T.TCTopModule mo -> T.TCTopModule <$> liftSupply (`rewModule` mo)
T.TCTopSignature {} -> pure tcm
pure (R.rmInScope renMod,rewMod)
data TCLinter o = TCLinter
{ lintCheck ::
o -> T.InferInput -> Either (Range, TcSanity.Error) [TcSanity.ProofObligation]
o -> T.InferInput ->
Either (Range, TcSanity.Error) [TcSanity.ProofObligation]
, lintModule :: Maybe P.ModName
}
@ -502,6 +526,17 @@ moduleLinter m = TCLinter
, lintModule = Just m
}
tcTopEntitytLinter :: P.ModName -> TCLinter T.TCTopEntity
tcTopEntitytLinter m = TCLinter
{ lintCheck = \m' i -> case m' of
T.TCTopModule mo ->
lintCheck (moduleLinter m) mo i
T.TCTopSignature {} -> Right []
-- XXX: what can we lint about module interfaces
, lintModule = Just m
}
type Act i o = i -> T.InferInput -> IO (T.InferOutput o)
data TCAction i o = TCAction
@ -511,8 +546,8 @@ data TCAction i o = TCAction
}
typecheck ::
(Show i, Show o, HasLoc i) => TCAction i o -> i ->
IfaceParams -> IfaceDecls -> ModuleM o
(Show i, Show o, HasLoc i) =>
TCAction i o -> i -> T.FunctorParams -> IfaceDecls -> ModuleM o
typecheck act i params env = do
let range = fromMaybe emptyRange (getLoc i)
@ -540,8 +575,9 @@ typecheck act i params env = do
typeCheckingFailed nameMap errs
-- | Generate input for the typechecker.
genInferInput :: Range -> PrimMap -> IfaceParams -> IfaceDecls -> ModuleM T.InferInput
genInferInput r prims params env' = do
genInferInput :: Range -> PrimMap -> T.FunctorParams -> IfaceDecls ->
ModuleM T.InferInput
genInferInput r prims params env = do
seeds <- getNameSeeds
monoBinds <- getMonoBinds
solver <- getTCSolver
@ -549,25 +585,26 @@ genInferInput r prims params env' = do
searchPath <- getSearchPath
callStacks <- getCallStacks
-- TODO: include the environment needed by the module
let env = flatPublicDecls env'
-- XXX: we should really just pass this directly
topMods <- getAllLoaded
topSigs <- getAllLoadedSignatures
return T.InferInput
{ T.inpRange = r
, T.inpVars = Map.map ifDeclSig (ifDecls env)
, T.inpTSyns = ifTySyns env
, T.inpNewtypes = ifNewtypes env
, T.inpAbstractTypes = ifAbstractTypes env
, T.inpNameSeeds = seeds
, T.inpMonoBinds = monoBinds
, T.inpCallStacks = callStacks
, T.inpSearchPath = searchPath
, T.inpSupply = supply
, T.inpPrimNames = prims
, T.inpParamTypes = ifParamTypes params
, T.inpParamConstraints = ifParamConstraints params
, T.inpParamFuns = ifParamFuns params
{ T.inpRange = r
, T.inpVars = Map.map ifDeclSig (ifDecls env)
, T.inpTSyns = ifTySyns env
, T.inpNewtypes = ifNewtypes env
, T.inpAbstractTypes = ifAbstractTypes env
, T.inpSignatures = ifSignatures env
, T.inpNameSeeds = seeds
, T.inpMonoBinds = monoBinds
, T.inpCallStacks = callStacks
, T.inpSearchPath = searchPath
, T.inpSupply = supply
, T.inpParams = params
, T.inpPrimNames = prims
, T.inpSolver = solver
, T.inpTopModules = topMods
, T.inpTopSignatures = topSigs
}

View File

@ -0,0 +1,428 @@
{-# Language BlockArguments #-}
{-# Language RecordWildCards #-}
{-# Language FlexibleInstances #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveTraversable #-}
module Cryptol.ModuleSystem.Binds
( BindsNames
, TopDef(..)
, Mod(..)
, ModKind(..)
, modNested
, modBuilder
, topModuleDefs
, topDeclsDefs
, newModParam
, InModule(..)
, ifaceToMod
, ifaceSigToMod
, modToMap
, defsOf
) where
import Data.Map(Map)
import qualified Data.Map as Map
import Data.Set(Set)
import qualified Data.Set as Set
import Data.Maybe(fromMaybe)
import Control.Monad(foldM)
import qualified MonadLib as M
import Cryptol.Utils.Panic (panic)
import Cryptol.Utils.Ident(allNamespaces)
import Cryptol.Parser.Position
import Cryptol.Parser.Name(isGeneratedName)
import Cryptol.Parser.AST
import Cryptol.ModuleSystem.Exports(exportedDecls,exported)
import Cryptol.ModuleSystem.Renamer.Error
import Cryptol.ModuleSystem.Name
import Cryptol.ModuleSystem.Names
import Cryptol.ModuleSystem.NamingEnv
import Cryptol.ModuleSystem.Interface
import Cryptol.TypeCheck.Type(ModParamNames(..))
data TopDef = TopMod ModName (Mod ())
| TopInst ModName (ImpName PName) (ModuleInstanceArgs PName)
-- | Things defined by a module
data Mod a = Mod
{ modImports :: [ ImportG (ImpName PName) ]
, modKind :: ModKind
, modInstances :: Map Name (ImpName PName, ModuleInstanceArgs PName)
, modMods :: Map Name (Mod a) -- ^ this includes signatures
, modDefines :: NamingEnv
{- ^ Things defined by this module. Note the for normal modules we
really just need the public names, however for things within
functors we need all defined names, so that we can generate fresh
names in instantiations -}
, modPublic :: !(Set Name)
-- ^ These are the exported names
, modState :: a
{- ^ Used in the import loop to track the current state of processing.
The reason this is here, rather than just having a pair in the
other algorithm is because this type is recursive (for nested modules)
and it is conveninet to keep track for all modules at once -}
}
modNested :: Mod a -> Set Name
modNested m = Set.unions [ Map.keysSet (modInstances m)
, Map.keysSet (modMods m)
]
instance Functor Mod where
fmap f m = m { modState = f (modState m)
, modMods = fmap f <$> modMods m
}
-- | Generate a map from this module and all modules nested in it.
modToMap ::
ImpName Name -> Mod () ->
Map (ImpName Name) (Mod ()) -> Map (ImpName Name) (Mod ())
modToMap x m mp = Map.insert x m (Map.foldrWithKey add mp (modMods m))
where
add n = modToMap (ImpNested n)
-- | Make a `Mod` from the public declarations in an interface.
-- This is used to handle imports.
ifaceToMod :: IfaceG name -> Mod ()
ifaceToMod iface = ifaceNamesToMod iface (ifaceIsFunctor iface) (ifNames iface)
ifaceNamesToMod :: IfaceG topname -> Bool -> IfaceNames name -> Mod ()
ifaceNamesToMod iface params names =
Mod
{ modKind = if params then AFunctor else AModule
, modMods = (ifaceNamesToMod iface False <$> ifModules decls)
`Map.union`
(ifaceToMod <$> ifFunctors decls)
`Map.union`
(ifaceSigToMod <$> ifSignatures decls)
, modDefines = namingEnvFromNames defs
, modPublic = ifsPublic names
, modImports = []
, modInstances = mempty
, modState = ()
}
where
defs = ifsDefines names
isLocal x = x `Set.member` defs
decls = filterIfaceDecls isLocal (ifDefines iface)
ifaceSigToMod :: ModParamNames -> Mod ()
ifaceSigToMod ps = Mod
{ modImports = []
, modKind = ASignature
, modInstances = mempty
, modMods = mempty
, modDefines = env
, modPublic = namingEnvNames env
, modState = ()
}
where
env = modParamsNamingEnv ps
type ModBuilder = SupplyT (M.StateT [RenamerError] M.Id)
modBuilder :: ModBuilder a -> Supply -> ((a, [RenamerError]),Supply)
modBuilder m s = ((a,errs),s1)
where ((a,s1),errs) = M.runId (M.runStateT [] (runSupplyT s m))
defErr :: RenamerError -> ModBuilder ()
defErr a = M.lift (M.sets_ (a:))
defNames :: BuildNamingEnv -> ModBuilder NamingEnv
defNames b = liftSupply \s -> M.runId (runSupplyT s (runBuild b))
topModuleDefs :: Module PName -> ModBuilder TopDef
topModuleDefs m =
case mDef m of
NormalModule ds -> TopMod mname <$> declsToMod (Just (TopModule mname)) ds
FunctorInstance f as _ -> pure (TopInst mname (thing f) as)
InterfaceModule s -> TopMod mname <$> sigToMod (TopModule mname) s
where
mname = thing (mName m)
topDeclsDefs :: [TopDecl PName] -> ModBuilder (Mod ())
topDeclsDefs = declsToMod Nothing
sigToMod :: ModPath -> Signature PName -> ModBuilder (Mod ())
sigToMod mp sig =
do env <- defNames (signatureDefs mp sig)
pure Mod { modImports = map thing (sigImports sig)
, modKind = ASignature
, modInstances = mempty
, modMods = mempty
, modDefines = env
, modPublic = mempty -- unused
, modState = ()
}
declsToMod :: Maybe ModPath -> [TopDecl PName] -> ModBuilder (Mod ())
declsToMod mbPath ds =
do defs <- defNames (foldMap (namingEnv . InModule mbPath) ds)
let expSpec = exportedDecls ds
let pub = Set.fromList
[ name
| ns <- allNamespaces
, pname <- Set.toList (exported ns expSpec)
, name <- lookupListNS ns pname defs
]
case findAmbig defs of
bad@(_ : _) : _ ->
-- defErr (MultipleDefinitions mbPath (nameIdent f) (map nameLoc bad))
defErr (OverlappingSyms bad)
_ -> pure ()
let mo = Mod { modImports = [ thing i | DImport i <- ds ]
, modKind = if any isParamDecl ds
then AFunctor else AModule
, modInstances = mempty
, modMods = mempty
, modDefines = defs
, modPublic = pub
, modState = ()
}
foldM (checkNest defs) mo ds
where
checkNest defs mo d =
case d of
DModule tl ->
do let NestedModule nmod = tlValue tl
pname = thing (mName nmod)
name = case lookupNS NSModule pname defs of
Just xs -> anyOne xs
_ -> panic "declsToMod" ["undefined name", show pname]
case mbPath of
Nothing ->
do defErr (UnexpectedNest (srcRange (mName nmod)) pname)
pure mo
Just path ->
case mDef nmod of
NormalModule xs ->
do m <- declsToMod (Just (Nested path (nameIdent name))) xs
pure mo { modMods = Map.insert name m (modMods mo) }
FunctorInstance f args _ ->
pure mo { modInstances = Map.insert name (thing f, args)
(modInstances mo) }
InterfaceModule sig ->
do m <- sigToMod (Nested path (nameIdent name)) sig
pure mo { modMods = Map.insert name m (modMods mo) }
_ -> pure mo
-- | These are the names "owned" by the signature. These names are
-- used when resolving the signature. They are also used to figure out what
-- names to instantuate when the signature is used.
signatureDefs :: ModPath -> Signature PName -> BuildNamingEnv
signatureDefs m sig =
mconcat [ namingEnv (InModule loc p) | p <- sigTypeParams sig ]
<> mconcat [ namingEnv (InModule loc p) | p <- sigFunParams sig ]
where
loc = Just m
--------------------------------------------------------------------------------
--------------------------------------------------------------------------------
-- Computes the names introduced by various declarations.
-- | Things that define exported names.
class BindsNames a where
namingEnv :: a -> BuildNamingEnv
newtype BuildNamingEnv = BuildNamingEnv { runBuild :: SupplyT M.Id NamingEnv }
buildNamingEnv :: BuildNamingEnv -> Supply -> (NamingEnv,Supply)
buildNamingEnv b supply = M.runId $ runSupplyT supply $ runBuild b
-- | Generate a 'NamingEnv' using an explicit supply.
defsOf :: BindsNames a => a -> Supply -> (NamingEnv,Supply)
defsOf = buildNamingEnv . namingEnv
instance Semigroup BuildNamingEnv where
BuildNamingEnv a <> BuildNamingEnv b = BuildNamingEnv $
do x <- a
y <- b
return (mappend x y)
instance Monoid BuildNamingEnv where
mempty = BuildNamingEnv (pure mempty)
mappend = (<>)
mconcat bs = BuildNamingEnv $
do ns <- sequence (map runBuild bs)
return (mconcat ns)
instance BindsNames NamingEnv where
namingEnv env = BuildNamingEnv (return env)
{-# INLINE namingEnv #-}
instance BindsNames a => BindsNames (Maybe a) where
namingEnv = foldMap namingEnv
{-# INLINE namingEnv #-}
instance BindsNames a => BindsNames [a] where
namingEnv = foldMap namingEnv
{-# INLINE namingEnv #-}
-- | Generate a type renaming environment from the parameters that are bound by
-- this schema.
instance BindsNames (Schema PName) where
namingEnv (Forall ps _ _ _) = foldMap namingEnv ps
{-# INLINE namingEnv #-}
-- | Introduce the name
instance BindsNames (InModule (Bind PName)) where
namingEnv (InModule mb b) = BuildNamingEnv $
do let Located { .. } = bName b
n <- case mb of
Just m -> newTop NSValue m thing (bFixity b) srcRange
Nothing -> newLocal NSValue thing srcRange -- local fixitiies?
return (singletonNS NSValue thing n)
-- | Generate the naming environment for a type parameter.
instance BindsNames (TParam PName) where
namingEnv TParam { .. } = BuildNamingEnv $
do let range = fromMaybe emptyRange tpRange
n <- newLocal NSType tpName range
return (singletonNS NSType tpName n)
instance BindsNames (InModule (TopDecl PName)) where
namingEnv (InModule ns td) =
case td of
Decl d -> namingEnv (InModule ns (tlValue d))
DPrimType d -> namingEnv (InModule ns (tlValue d))
TDNewtype d -> namingEnv (InModule ns (tlValue d))
DParamDecl {} -> mempty
Include _ -> mempty
DImport {} -> mempty -- see 'openLoop' in the renamer
DModule m -> namingEnv (InModule ns (tlValue m))
DModParam {} -> mempty -- shouldn't happen
DInterfaceConstraint {} -> mempty
-- handled in the renamer as we need to resolve
-- the signature name first (similar to import)
instance BindsNames (InModule (NestedModule PName)) where
namingEnv (InModule ~(Just m) (NestedModule mdef)) = BuildNamingEnv $
do let pnmame = mName mdef
nm <- newTop NSModule m (thing pnmame) Nothing (srcRange pnmame)
pure (singletonNS NSModule (thing pnmame) nm)
instance BindsNames (InModule (PrimType PName)) where
namingEnv (InModule ~(Just m) PrimType { .. }) =
BuildNamingEnv $
do let Located { .. } = primTName
nm <- newTop NSType m thing primTFixity srcRange
pure (singletonNS NSType thing nm)
instance BindsNames (InModule (ParameterFun PName)) where
namingEnv (InModule ~(Just ns) ParameterFun { .. }) = BuildNamingEnv $
do let Located { .. } = pfName
ntName <- newTop NSValue ns thing pfFixity srcRange
return (singletonNS NSValue thing ntName)
instance BindsNames (InModule (ParameterType PName)) where
namingEnv (InModule ~(Just ns) ParameterType { .. }) = BuildNamingEnv $
-- XXX: we don't seem to have a fixity environment at the type level
do let Located { .. } = ptName
ntName <- newTop NSType ns thing Nothing srcRange
return (singletonNS NSType thing ntName)
-- NOTE: we use the same name at the type and expression level, as there's only
-- ever one name introduced in the declaration. The names are only ever used in
-- different namespaces, so there's no ambiguity.
instance BindsNames (InModule (Newtype PName)) where
namingEnv (InModule ~(Just ns) Newtype { .. }) = BuildNamingEnv $
do let Located { .. } = nName
ntName <- newTop NSType ns thing Nothing srcRange
-- XXX: the name reuse here is sketchy
return (singletonNS NSType thing ntName `mappend` singletonNS NSValue thing ntName)
-- | The naming environment for a single declaration.
instance BindsNames (InModule (Decl PName)) where
namingEnv (InModule pfx d) = case d of
DBind b -> namingEnv (InModule pfx b)
DSignature ns _sig -> foldMap qualBind ns
DPragma ns _p -> foldMap qualBind ns
DType syn -> qualType (tsName syn) (tsFixity syn)
DProp syn -> qualType (psName syn) (psFixity syn)
DLocated d' _ -> namingEnv (InModule pfx d')
DRec {} -> panic "namingEnv" [ "DRec" ]
DPatBind _pat _e -> panic "namingEnv" ["Unexpected pattern binding"]
DFixity{} -> panic "namingEnv" ["Unexpected fixity declaration"]
where
mkName ns ln fx = case pfx of
Just m -> newTop ns m (thing ln) fx (srcRange ln)
Nothing -> newLocal ns (thing ln) (srcRange ln)
qualBind ln = BuildNamingEnv $
do n <- mkName NSValue ln Nothing
return (singletonNS NSValue (thing ln) n)
qualType ln f = BuildNamingEnv $
do n <- mkName NSType ln f
return (singletonNS NSType (thing ln) n)
--------------------------------------------------------------------------------
-- Helpers
newTop ::
FreshM m => Namespace -> ModPath -> PName -> Maybe Fixity -> Range -> m Name
newTop ns m thing fx rng =
liftSupply (mkDeclared ns m src (getIdent thing) fx rng)
where src = if isGeneratedName thing then SystemName else UserName
newLocal :: FreshM m => Namespace -> PName -> Range -> m Name
newLocal ns thing rng = liftSupply (mkLocal ns (getIdent thing) rng)
-- | Given a name in a signature, make a name for the parameter corresponding
-- to the signature.
newModParam :: FreshM m => ModPath -> Ident -> Range -> Name -> m Name
newModParam m i rng n = liftSupply (mkModParam m i rng n)
{- | Do something in the context of a module.
If `Nothing` than we are working with a local declaration.
Otherwise we are at the top-level of the given module.
By wrapping types with this, we can pass the module path
to methdods that need the extra information. -}
data InModule a = InModule (Maybe ModPath) a
deriving (Functor,Traversable,Foldable,Show)

View File

@ -12,6 +12,7 @@
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Cryptol.ModuleSystem.Env where
#ifndef RELOCATABLE
@ -34,6 +35,7 @@ import Control.Monad (guard,mplus)
import qualified Control.Exception as X
import Data.Function (on)
import Data.Set(Set)
import qualified Data.Set as Set
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Semigroup
@ -171,9 +173,9 @@ loadedModules = map lmModule . getLoadedModules . meLoadedModules
loadedNonParamModules :: ModuleEnv -> [T.Module]
loadedNonParamModules = map lmModule . lmLoadedModules . meLoadedModules
loadedNewtypes :: ModuleEnv -> Map Name IfaceNewtype
loadedNewtypes :: ModuleEnv -> Map Name T.Newtype
loadedNewtypes menv = Map.unions
[ ifNewtypes (ifPublic i) <> ifNewtypes (ifPrivate i)
[ ifNewtypes (ifDefines i) <> ifNewtypes (ifDefines i)
| i <- map lmInterface (getLoadedModules (meLoadedModules menv))
]
@ -187,7 +189,7 @@ allDeclGroups = concatMap T.mDecls . loadedNonParamModules
-- | Contains enough information to browse what's in scope,
-- or type check new expressions.
data ModContext = ModContext
{ mctxParams :: IfaceParams
{ mctxParams :: T.FunctorParams
, mctxExported :: Set Name
, mctxDecls :: IfaceDecls
-- ^ Should contain at least names in NamingEnv, but may have more
@ -199,7 +201,7 @@ data ModContext = ModContext
-- This instance is a bit bogus. It is mostly used to add the dynamic
-- environemnt to an existing module, and it makes sense for that use case.
instance Semigroup ModContext where
x <> y = ModContext { mctxParams = jnParams (mctxParams x) (mctxParams y)
x <> y = ModContext { mctxParams = mctxParams x <> mctxParams y
, mctxExported = mctxExported x <> mctxExported y
, mctxDecls = mctxDecls x <> mctxDecls y
, mctxNames = names
@ -208,14 +210,9 @@ instance Semigroup ModContext where
where
names = mctxNames x `R.shadowing` mctxNames y
jnParams a b
| isEmptyIfaceParams a = b
| isEmptyIfaceParams b = a
| otherwise =
panic "ModContext" [ "Cannot combined 2 parameterized contexts" ]
instance Monoid ModContext where
mempty = ModContext { mctxParams = noIfaceParams
mempty = ModContext { mctxParams = mempty
, mctxDecls = mempty
, mctxExported = mempty
, mctxNames = mempty
@ -229,12 +226,14 @@ modContextOf mname me =
do lm <- lookupModule mname me
let localIface = lmInterface lm
localNames = lmNamingEnv lm
loadedDecls = map (ifPublic . lmInterface)
-- XXX: do we want only public ones here?
loadedDecls = map (ifDefines . lmInterface)
$ getLoadedModules (meLoadedModules me)
pure ModContext
{ mctxParams = ifParams localIface
, mctxExported = ifaceDeclsNames (ifPublic localIface)
, mctxDecls = mconcat (ifPrivate localIface : loadedDecls)
, mctxExported = ifsPublic (ifNames localIface)
, mctxDecls = mconcat (ifDefines localIface : loadedDecls)
, mctxNames = localNames
, mctxNameDisp = R.toNameDisp localNames
}
@ -303,24 +302,44 @@ data LoadedModules = LoadedModules
, lmLoadedParamModules :: [LoadedModule]
-- ^ Loaded parameterized modules.
, lmLoadedSignatures :: ![LoadedSignature]
} deriving (Show, Generic, NFData)
getLoadedEntities ::
LoadedModules -> Map ModName (Either LoadedSignature LoadedModule)
getLoadedEntities lm =
Map.fromList $ [ (lmName x, Right x) | x <- lmLoadedModules lm ] ++
[ (lmName x, Right x) | x <- lmLoadedParamModules lm ] ++
[ (lmName x, Left x) | x <- lmLoadedSignatures lm ]
getLoadedModules :: LoadedModules -> [LoadedModule]
getLoadedModules x = lmLoadedParamModules x ++ lmLoadedModules x
getLoadedNames :: LoadedModules -> Set ModName
getLoadedNames lm = Set.fromList
$ map lmName (lmLoadedModules lm)
++ map lmName (lmLoadedParamModules lm)
++ map lmName (lmLoadedSignatures lm)
instance Semigroup LoadedModules where
l <> r = LoadedModules
{ lmLoadedModules = List.unionBy ((==) `on` lmName)
(lmLoadedModules l) (lmLoadedModules r)
, lmLoadedParamModules = lmLoadedParamModules l ++ lmLoadedParamModules r }
, lmLoadedParamModules = lmLoadedParamModules l ++ lmLoadedParamModules r
, lmLoadedSignatures = lmLoadedSignatures l ++ lmLoadedSignatures r
}
instance Monoid LoadedModules where
mempty = LoadedModules { lmLoadedModules = []
, lmLoadedParamModules = []
, lmLoadedSignatures = []
}
mappend = (<>)
data LoadedModule = LoadedModule
-- | A generic type for loaded things.
-- The things can be either modules or signatures.
data LoadedModuleG a = LoadedModule
{ lmName :: ModName
-- ^ The name of this module. Should match what's in 'lmModule'
@ -335,29 +354,75 @@ data LoadedModule = LoadedModule
, lmNamingEnv :: !R.NamingEnv
-- ^ What's in scope in this module
, lmInterface :: Iface
, lmFingerprint :: Fingerprint
, lmData :: a
} deriving (Show, Generic, NFData)
type LoadedModule = LoadedModuleG LoadedModuleData
lmModule :: LoadedModule -> T.Module
lmModule = lmdModule . lmData
lmInterface :: LoadedModule -> Iface
lmInterface = lmdInterface . lmData
data LoadedModuleData = LoadedModuleData
{ lmdInterface :: Iface
-- ^ The module's interface.
, lmModule :: T.Module
, lmdModule :: T.Module
-- ^ The actual type-checked module
, lmFingerprint :: Fingerprint
} deriving (Show, Generic, NFData)
type LoadedSignature = LoadedModuleG T.ModParamNames
-- | Has this module been loaded already.
isLoaded :: ModName -> LoadedModules -> Bool
isLoaded mn lm = any ((mn ==) . lmName) (getLoadedModules lm)
isLoaded mn lm = mn `Set.member` getLoadedNames lm
-- | Is this a loaded parameterized module.
isLoadedParamMod :: ModName -> LoadedModules -> Bool
isLoadedParamMod mn ln = any ((mn ==) . lmName) (lmLoadedParamModules ln)
lookupTCEntity :: ModName -> ModuleEnv -> Maybe (LoadedModuleG T.TCTopEntity)
lookupTCEntity m env =
case lookupModule m env of
Just lm -> pure lm { lmData = T.TCTopModule (lmModule lm) }
Nothing ->
do lm <- lookupSignature m env
pure lm { lmData = T.TCTopSignature m (lmData lm) }
-- | Try to find a previously loaded module
lookupModule :: ModName -> ModuleEnv -> Maybe LoadedModule
lookupModule mn me = search lmLoadedModules `mplus` search lmLoadedParamModules
where
search how = List.find ((mn ==) . lmName) (how (meLoadedModules me))
lookupSignature :: ModName -> ModuleEnv -> Maybe LoadedSignature
lookupSignature mn me =
List.find ((mn ==) . lmName) (lmLoadedSignatures (meLoadedModules me))
addLoadedSignature ::
ModulePath -> String -> Fingerprint -> R.NamingEnv ->
ModName -> T.ModParamNames ->
LoadedModules -> LoadedModules
addLoadedSignature path ident fp nameEnv nm si lm
| isLoaded nm lm = lm
| otherwise = lm { lmLoadedSignatures = loaded : lmLoadedSignatures lm }
where
loaded = LoadedModule
{ lmName = nm
, lmFilePath = path
, lmModuleId = ident
, lmNamingEnv = nameEnv
, lmData = si
, lmFingerprint = fp
}
-- | Add a freshly loaded module. If it was previously loaded, then
-- the new version is ignored.
@ -376,19 +441,23 @@ addLoadedModule path ident fp nameEnv tm lm
, lmFilePath = path
, lmModuleId = ident
, lmNamingEnv = nameEnv
, lmInterface = T.genIface tm
, lmModule = tm
, lmData = LoadedModuleData
{ lmdInterface = T.genIface tm
, lmdModule = tm
}
, lmFingerprint = fp
}
-- | Remove a previously loaded module.
-- Note that this removes exactly the modules specified by the predicate.
-- One should be carfule to preserve the invariant on 'LoadedModules'.
removeLoadedModule :: (LoadedModule -> Bool) -> LoadedModules -> LoadedModules
removeLoadedModule ::
(forall a. LoadedModuleG a -> Bool) -> LoadedModules -> LoadedModules
removeLoadedModule rm lm =
LoadedModules
{ lmLoadedModules = filter (not . rm) (lmLoadedModules lm)
, lmLoadedParamModules = filter (not . rm) (lmLoadedParamModules lm)
{ lmLoadedModules = filter (not . rm) (lmLoadedModules lm)
, lmLoadedParamModules = filter (not . rm) (lmLoadedParamModules lm)
, lmLoadedSignatures = filter (not . rm) (lmLoadedSignatures lm)
}
-- Dynamic Environments --------------------------------------------------------
@ -433,6 +502,8 @@ deIfaceDecls DEnv { deDecls = dgs, deTySyns = tySyns } =
, ifAbstractTypes = Map.empty
, ifDecls = decls
, ifModules = Map.empty
, ifFunctors = Map.empty
, ifSignatures = Map.empty
}
where
decls = mconcat

View File

@ -13,27 +13,28 @@ import Cryptol.Parser.AST
import Cryptol.Parser.Names(namesD,tnamesD,tnamesNT)
import Cryptol.ModuleSystem.Name
modExports :: Ord name => ModuleG mname name -> ExportSpec name
modExports m = fold (concat [ exportedNames d | d <- mDecls m ])
exportedDecls :: Ord name => [TopDecl name] -> ExportSpec name
exportedDecls ds = fold (concat [ exportedNames d | d <- ds ])
exportedNames :: Ord name => TopDecl name -> [ExportSpec name]
exportedNames (Decl td) = map exportBind (names namesD td)
++ map exportType (names tnamesD td)
exportedNames (DPrimType t) = [ exportType (thing . primTName <$> t) ]
exportedNames (TDNewtype nt) = map exportType (names tnamesNT nt)
exportedNames (Include {}) = []
exportedNames (DImport {}) = []
exportedNames (DParameterFun {}) = []
exportedNames (DParameterType {}) = []
exportedNames (DParameterConstraint {}) = []
exportedNames (DModule nested) =
case tlValue nested of
NestedModule x ->
[exportName NSModule nested { tlValue = thing (mName x) }]
exportedNames decl =
case decl of
Decl td -> map exportBind (names namesD td)
++ map exportType (names tnamesD td)
DPrimType t -> [ exportType (thing . primTName <$> t) ]
TDNewtype nt -> map exportType (names tnamesNT nt)
Include {} -> []
DImport {} -> []
DParamDecl {} -> []
DInterfaceConstraint {} -> []
DModule nested ->
case tlValue nested of
NestedModule x ->
[exportName NSModule nested { tlValue = thing (mName x) }]
DModParam {} -> []
where
names by td = [ td { tlValue = thing n } | n <- fst (by (tlValue td)) ]
names :: (a -> ([Located a'], b)) -> TopLevel a -> [TopLevel a']
names by td = [ td { tlValue = thing n } | n <- fst (by (tlValue td)) ]
newtype ExportSpec name = ExportSpec (Map Namespace (Set name))
@ -54,6 +55,9 @@ exportName ns n
$ Set.singleton (tlValue n)
| otherwise = mempty
allExported :: Ord name => ExportSpec name -> Set name
allExported (ExportSpec mp) = Set.unions (Map.elems mp)
exported :: Namespace -> ExportSpec name -> Set name
exported ns (ExportSpec mp) = Map.findWithDefault Set.empty ns mp

View File

@ -1,325 +0,0 @@
{-# Language FlexibleInstances, PatternGuards #-}
{-# Language BlockArguments #-}
-- | Assumes that local names do not shadow top level names.
module Cryptol.ModuleSystem.InstantiateModule
( instantiateModule
) where
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Map (Map)
import qualified Data.Map as Map
import MonadLib(ReaderT,runReaderT,ask)
import Cryptol.Utils.Panic(panic)
import Cryptol.Utils.Ident(ModName,modParamIdent)
import Cryptol.Parser.Position(Located(..))
import Cryptol.ModuleSystem.Name
import Cryptol.TypeCheck.AST
import Cryptol.TypeCheck.Subst(listParamSubst, apSubst)
import Cryptol.TypeCheck.SimpType(tRebuild)
{-
XXX: Should we simplify constraints in the instantiated modules?
If so, we also need to adjust the constraint parameters on terms appropriately,
especially when working with dictionaries.
-}
-- | Convert a module instantiation into a partial module.
-- The resulting module is incomplete because it is missing the definitions
-- from the instantiation.
instantiateModule :: FreshM m =>
Module {- ^ Parametrized module -} ->
ModName {- ^ Name of the new module -} ->
Map TParam Type {- ^ Type params -} ->
Map Name Expr {- ^ Value parameters -} ->
m (Name -> Name, [Located Prop], Module)
-- ^ Renaming, instantiated constraints, fresh module, new supply
instantiateModule func newName tpMap vpMap
| not (null (mSubModules func)) =
panic "instantiateModule"
[ "XXX: we don't support functors with nested moduels yet." ]
| otherwise =
runReaderT (TopModule newName) $
do let oldVpNames = Map.keys vpMap
newVpNames <- mapM freshParamName (Map.keys vpMap)
let vpNames = Map.fromList (zip oldVpNames newVpNames)
env <- computeEnv func tpMap vpNames
let ren x = case nameNamespace x of
NSValue -> Map.findWithDefault x x (funNameMap env)
NSType -> Map.findWithDefault x x (tyNameMap env)
NSModule -> x
let rnMp :: Inst a => (a -> Name) -> Map Name a -> Map Name a
rnMp f m = Map.fromList [ (f x, x) | a <- Map.elems m
, let x = inst env a ]
renamedExports = inst env (mExports func)
renamedTySyns = rnMp tsName (mTySyns func)
renamedNewtypes = rnMp ntName (mNewtypes func)
renamedPrimTys = rnMp atName (mPrimTypes func)
su = listParamSubst (Map.toList (tyParamMap env))
goals = map (fmap (apSubst su)) (mParamConstraints func)
-- Constraints to discharge about the type instances
let renamedDecls = inst env (mDecls func)
paramDecls = map (mkParamDecl su vpNames) (Map.toList vpMap)
return ( ren
, goals
, Module
{ mName = newName
, mExports = renamedExports
, mImports = mImports func
, mTySyns = renamedTySyns
, mNewtypes = renamedNewtypes
, mPrimTypes = renamedPrimTys
, mParamTypes = Map.empty
, mParamConstraints = []
, mParamFuns = Map.empty
, mDecls = paramDecls ++ renamedDecls
, mSubModules = mempty
, mFunctors = mempty
} )
where
mkParamDecl su vpNames (x,e) =
NonRecursive Decl
{ dName = Map.findWithDefault (error "OOPS") x vpNames
, dSignature = apSubst su
$ mvpType
$ Map.findWithDefault (error "UUPS") x (mParamFuns func)
, dDefinition = DExpr e
, dPragmas = [] -- XXX: which if any pragmas?
, dInfix = False -- XXX: get from parameter?
, dFixity = Nothing -- XXX: get from parameter
, dDoc = Nothing -- XXX: get from parametr(or instance?)
}
--------------------------------------------------------------------------------
-- Things that need to be renamed
class Defines t where
defines :: t -> Set Name
instance Defines t => Defines [t] where
defines = Set.unions . map defines
instance Defines Decl where
defines = Set.singleton . dName
instance Defines DeclGroup where
defines d =
case d of
NonRecursive x -> defines x
Recursive x -> defines x
--------------------------------------------------------------------------------
type InstM = ReaderT ModPath
-- | Generate a new instance of a declared name.
freshenName :: FreshM m => Name -> InstM m Name
freshenName x =
do m <- ask
let sys = case nameInfo x of
Declared _ s -> s
_ -> UserName
liftSupply (mkDeclared (nameNamespace x)
m sys (nameIdent x) (nameFixity x) (nameLoc x))
freshParamName :: FreshM m => Name -> InstM m Name
freshParamName x =
do m <- ask
let newName = modParamIdent (nameIdent x)
liftSupply (mkDeclared (nameNamespace x)
m UserName newName (nameFixity x) (nameLoc x))
-- | Compute renaming environment from a module instantiation.
-- computeEnv :: ModInst -> InstM Env
computeEnv :: FreshM m =>
Module {- ^ Functor being instantiated -} ->
Map TParam Type {- replace type params by type -} ->
Map Name Name {- replace value parameters by other names -} ->
InstM m Env
computeEnv m tpMap vpMap =
do tss <- mapM freshTy (Map.toList (mTySyns m))
nts <- mapM freshTy (Map.toList (mNewtypes m))
let tnMap = Map.fromList (tss ++ nts)
defHere <- mapM mkVParam (Set.toList (defines (mDecls m)))
let fnMap = Map.union vpMap (Map.fromList defHere)
return Env { funNameMap = fnMap
, tyNameMap = tnMap
, tyParamMap = tpMap
}
where
freshTy (x,_) = do y <- freshenName x
return (x,y)
mkVParam x = do y <- freshenName x
return (x,y)
--------------------------------------------------------------------------------
-- Do the renaming
data Env = Env
{ funNameMap :: Map Name Name
, tyNameMap :: Map Name Name
, tyParamMap :: Map TParam Type
} deriving Show
class Inst t where
inst :: Env -> t -> t
instance Inst a => Inst [a] where
inst env = map (inst env)
instance Inst Expr where
inst env = go
where
go expr =
case expr of
EVar x -> case Map.lookup x (funNameMap env) of
Just y -> EVar y
_ -> expr
ELocated r e -> ELocated r (inst env e)
EList xs t -> EList (inst env xs) (inst env t)
ETuple es -> ETuple (inst env es)
ERec xs -> ERec (fmap go xs)
ESel e s -> ESel (go e) s
ESet ty e x v -> ESet (inst env ty) (go e) x (go v)
EIf e1 e2 e3 -> EIf (go e1) (go e2) (go e3)
EComp t1 t2 e mss -> EComp (inst env t1) (inst env t2)
(go e)
(inst env mss)
ETAbs t e -> ETAbs t (go e)
ETApp e t -> ETApp (go e) (inst env t)
EApp e1 e2 -> EApp (go e1) (go e2)
EAbs x t e -> EAbs x (inst env t) (go e)
EProofAbs p e -> EProofAbs (inst env p) (go e)
EProofApp e -> EProofApp (go e)
EWhere e ds -> EWhere (go e) (inst env ds)
instance Inst DeclGroup where
inst env dg =
case dg of
NonRecursive d -> NonRecursive (inst env d)
Recursive ds -> Recursive (inst env ds)
instance Inst DeclDef where
inst env d =
case d of
DPrim -> DPrim
DExpr e -> DExpr (inst env e)
instance Inst Decl where
inst env d = d { dSignature = inst env (dSignature d)
, dDefinition = inst env (dDefinition d)
, dName = Map.findWithDefault (dName d) (dName d)
(funNameMap env)
}
instance Inst Match where
inst env m =
case m of
From x t1 t2 e -> From x (inst env t1) (inst env t2) (inst env e)
Let d -> Let (inst env d)
instance Inst Schema where
inst env s = s { sProps = inst env (sProps s)
, sType = inst env (sType s)
}
instance Inst Type where
inst env ty =
tRebuild $
case ty of
TCon tc ts -> TCon (inst env tc) (inst env ts)
TVar tv ->
case tv of
TVBound tp | Just t <- Map.lookup tp (tyParamMap env) -> t
_ -> ty
TUser x ts t -> TUser y (inst env ts) (inst env t)
where y = Map.findWithDefault x x (tyNameMap env)
TRec fs -> TRec (fmap (inst env) fs)
TNewtype nt ts -> TNewtype (inst env nt) (inst env ts)
instance Inst TCon where
inst env tc =
case tc of
TC x -> TC (inst env x)
_ -> tc
instance Inst TC where
inst env tc =
case tc of
TCAbstract x -> TCAbstract (inst env x)
_ -> tc
instance Inst UserTC where
inst env (UserTC x t) = UserTC y t
where y = Map.findWithDefault x x (tyNameMap env)
instance Inst (ExportSpec Name) where
inst env (ExportSpec spec) = ExportSpec (Map.mapWithKey doNS spec)
where
doNS ns =
case ns of
NSType -> Set.map \x -> Map.findWithDefault x x (tyNameMap env)
NSValue -> Set.map \x -> Map.findWithDefault x x (funNameMap env)
NSModule -> id
instance Inst TySyn where
inst env ts = TySyn { tsName = instTyName env x
, tsParams = tsParams ts
, tsConstraints = inst env (tsConstraints ts)
, tsDef = inst env (tsDef ts)
, tsDoc = tsDoc ts
}
where x = tsName ts
instance Inst Newtype where
inst env nt = Newtype { ntName = instTyName env x
, ntParams = ntParams nt
, ntConstraints = inst env (ntConstraints nt)
, ntFields = fmap (inst env) (ntFields nt)
, ntDoc = ntDoc nt
}
where x = ntName nt
instance Inst AbstractType where
inst env a = AbstractType { atName = instTyName env (atName a)
, atKind = atKind a
, atCtrs = case atCtrs a of
(xs,ps) -> (xs, inst env ps)
, atFixitiy = atFixitiy a
, atDoc = atDoc a
}
instTyName :: Env -> Name -> Name
instTyName env x = Map.findWithDefault x x (tyNameMap env)

View File

@ -15,18 +15,14 @@ module Cryptol.ModuleSystem.Interface (
Iface
, IfaceG(..)
, IfaceDecls(..)
, IfaceTySyn, ifTySynName
, IfaceNewtype
, IfaceDecl(..)
, IfaceParams(..)
, IfaceNames(..)
, ifModName
, emptyIface
, ifacePrimMap
, noIfaceParams
, isEmptyIfaceParams
, ifaceForgetName
, ifaceIsFunctor
, flatPublicIface
, flatPublicDecls
, filterIfaceDecls
, ifaceDeclsNames
) where
@ -48,70 +44,67 @@ import Cryptol.Utils.Ident (ModName)
import Cryptol.Utils.Panic(panic)
import Cryptol.Utils.Fixity(Fixity)
import Cryptol.Parser.AST(Pragma)
import Cryptol.Parser.Position(Located)
import Cryptol.TypeCheck.Type
-- | The resulting interface generated by a module that has been typechecked.
data IfaceG mname = Iface
{ ifModName :: !mname -- ^ Module name
, ifPublic :: IfaceDecls -- ^ Exported definitions
, ifPrivate :: IfaceDecls -- ^ Private defintiions
, ifParams :: IfaceParams -- ^ Uninterpreted constants (aka module params)
} deriving (Show, Generic, NFData)
ifaceIsFunctor :: IfaceG mname -> Bool
ifaceIsFunctor = not . isEmptyIfaceParams . ifParams
-- | The public declarations in all modules, including nested
-- The modules field contains public functors
-- Assumes that we are not a functor.
flatPublicIface :: IfaceG mname -> IfaceDecls
flatPublicIface iface = flatPublicDecls (ifPublic iface)
flatPublicDecls :: IfaceDecls -> IfaceDecls
flatPublicDecls ifs = mconcat ( ifs { ifModules = fun }
: map flatPublicIface (Map.elems nofun)
)
where
(fun,nofun) = Map.partition ifaceIsFunctor (ifModules ifs)
type Iface = IfaceG ModName
emptyIface :: mname -> IfaceG mname
emptyIface nm = Iface
{ ifModName = nm
, ifPublic = mempty
, ifPrivate = mempty
, ifParams = noIfaceParams
}
data IfaceParams = IfaceParams
{ ifParamTypes :: Map.Map Name ModTParam
, ifParamConstraints :: [Located Prop] -- ^ Constraints on param. types
, ifParamFuns :: Map.Map Name ModVParam
-- | The interface repersenting a typecheck top-level module.
data IfaceG name = Iface
{ ifNames :: IfaceNames name -- ^ Info about names in this module
, ifParams :: FunctorParams -- ^ Module parameters, if any
, ifDefines :: IfaceDecls -- ^ All things defines in the module
-- (includes nested definitions)
} deriving (Show, Generic, NFData)
noIfaceParams :: IfaceParams
noIfaceParams = IfaceParams
{ ifParamTypes = Map.empty
, ifParamConstraints = []
, ifParamFuns = Map.empty
ifaceForgetName :: IfaceG name -> IfaceG ()
ifaceForgetName i = i { ifNames = newNames }
where newNames = (ifNames i) { ifsName = () }
ifModName :: Iface -> ModName
ifModName = ifsName . ifNames
-- | Information about the names in a module.
data IfaceNames name = IfaceNames
{ ifsName :: name -- ^ Name of this submodule
, ifsNested :: Set Name -- ^ Things nested in this module
, ifsDefines :: Set Name -- ^ Things defined in this module
, ifsPublic :: Set Name -- ^ Subset of `ifsDefines` that is public
} deriving (Show, Generic, NFData)
-- | Is this interface for a functor.
ifaceIsFunctor :: IfaceG name -> Bool
ifaceIsFunctor = not . Map.null . ifParams
emptyIface :: ModName -> Iface
emptyIface nm = Iface
{ ifNames = IfaceNames { ifsName = nm
, ifsDefines = mempty
, ifsPublic = mempty
, ifsNested = mempty
}
, ifParams = mempty
, ifDefines = mempty
}
isEmptyIfaceParams :: IfaceParams -> Bool
isEmptyIfaceParams IfaceParams { .. } =
Map.null ifParamTypes && null ifParamConstraints && Map.null ifParamFuns
-- | Declarations in a module. Note that this includes things from nested
-- modules, but not things from nested functors, which are in `ifFunctors`.
data IfaceDecls = IfaceDecls
{ ifTySyns :: Map.Map Name IfaceTySyn
, ifNewtypes :: Map.Map Name IfaceNewtype
, ifAbstractTypes :: Map.Map Name IfaceAbstractType
{ ifTySyns :: Map.Map Name TySyn
, ifNewtypes :: Map.Map Name Newtype
, ifAbstractTypes :: Map.Map Name AbstractType
, ifDecls :: Map.Map Name IfaceDecl
, ifModules :: !(Map.Map Name (IfaceG Name))
, ifModules :: !(Map.Map Name (IfaceNames Name))
, ifSignatures :: !(Map.Map Name ModParamNames)
, ifFunctors :: !(Map.Map Name (IfaceG Name))
{- ^ XXX: Maybe arg info?
Also, with the current implementation we aim to complete remove functors
by essentially inlining them. To achieve this with just interfaces
we'd have to store here the entire module, not just its interface.
At the moment we work around this by passing all loaded modules to the
type checker, so it looks up functors there, instead of in the interfaces,
but we'd need to change this if we want better support for separate
compilation. -}
} deriving (Show, Generic, NFData)
filterIfaceDecls :: (Name -> Bool) -> IfaceDecls -> IfaceDecls
@ -121,6 +114,8 @@ filterIfaceDecls p ifs = IfaceDecls
, ifAbstractTypes = filterMap (ifAbstractTypes ifs)
, ifDecls = filterMap (ifDecls ifs)
, ifModules = filterMap (ifModules ifs)
, ifFunctors = filterMap (ifFunctors ifs)
, ifSignatures = filterMap (ifSignatures ifs)
}
where
filterMap :: Map.Map Name a -> Map.Map Name a
@ -132,6 +127,8 @@ ifaceDeclsNames i = Set.unions [ Map.keysSet (ifTySyns i)
, Map.keysSet (ifAbstractTypes i)
, Map.keysSet (ifDecls i)
, Map.keysSet (ifModules i)
, Map.keysSet (ifFunctors i)
, Map.keysSet (ifSignatures i)
]
@ -142,27 +139,31 @@ instance Semigroup IfaceDecls where
, ifAbstractTypes = Map.union (ifAbstractTypes l) (ifAbstractTypes r)
, ifDecls = Map.union (ifDecls l) (ifDecls r)
, ifModules = Map.union (ifModules l) (ifModules r)
, ifFunctors = Map.union (ifFunctors l) (ifFunctors r)
, ifSignatures = ifSignatures l <> ifSignatures r
}
instance Monoid IfaceDecls where
mempty = IfaceDecls Map.empty Map.empty Map.empty Map.empty Map.empty
mappend = (<>)
mempty = IfaceDecls
{ ifTySyns = mempty
, ifNewtypes = mempty
, ifAbstractTypes = mempty
, ifDecls = mempty
, ifModules = mempty
, ifFunctors = mempty
, ifSignatures = mempty
}
mappend l r = l <> r
mconcat ds = IfaceDecls
{ ifTySyns = Map.unions (map ifTySyns ds)
, ifNewtypes = Map.unions (map ifNewtypes ds)
, ifAbstractTypes = Map.unions (map ifAbstractTypes ds)
, ifDecls = Map.unions (map ifDecls ds)
, ifModules = Map.unions (map ifModules ds)
, ifFunctors = Map.unions (map ifFunctors ds)
, ifSignatures = Map.unions (map ifSignatures ds)
}
type IfaceTySyn = TySyn
ifTySynName :: TySyn -> Name
ifTySynName = tsName
type IfaceNewtype = Newtype
type IfaceAbstractType = AbstractType
data IfaceDecl = IfaceDecl
{ ifDeclName :: !Name -- ^ Name of thing
, ifDeclSig :: Schema -- ^ Type
@ -177,14 +178,7 @@ data IfaceDecl = IfaceDecl
--
-- NOTE: the map will expose /both/ public and private names.
ifacePrimMap :: Iface -> PrimMap
ifacePrimMap Iface { .. } =
PrimMap { primDecls = merge primDecls
, primTypes = merge primTypes }
where
merge f = Map.union (f public) (f private)
public = ifaceDeclsPrimMap ifPublic
private = ifaceDeclsPrimMap ifPrivate
ifacePrimMap = ifaceDeclsPrimMap . ifDefines
ifaceDeclsPrimMap :: IfaceDecls -> PrimMap
ifaceDeclsPrimMap IfaceDecls { .. } =

Some files were not shown because too many files have changed in this diff Show More