shithub: mc

ref: 21ead16ccde2a943abe68ef279c89dbff030cb87
dir: /doc/lang.txt/

View raw version
                    The Myrddin Programming Language
                              Jul 2012
                          Updated Dec 2015
                            Ori Bernstein

TABLE OF CONTENTS:

    1. ABOUT
    2. NOTATION AND SEMANTICS
        2.1. Grammar
        2.2. As-If Rule
    3. LEXICAL CONVENTIONS
        3.1. Summary
    4. SYNTAX
        4.1. Declarations
        4.2. Data Types
        4.3. Literal Values
        4.4. Blocks
        4.5. Control Constructs
        4.6. Expressions
        4.7. Type Inference
        4.8. Generics
        4.9. Traits
        4.10. Packages and Uses
    5. GRAMMAR

1. ABOUT:

        Myrddin is designed to be a simple, low-level programming
        language.  It is designed to provide the programmer with
        predictable behavior and a transparent compilation model,
        while at the same time providing the benefits of strong type
        checking, generics, type inference, and similar.  Myrddin is
        not a language designed to explore the forefront of type
        theory or compiler technology. It is not a language that is
        focused on guaranteeing perfect safety. Its focus is on being
        a practical, small, fairly well defined, and easy to
        understand language for work that needs to be close to the
        hardware.

        Myrddin is a computer language influenced strongly by C and
        ML, with ideas from too many other places to name. 


2. NOTATION AND SEMANTICS:

    2.1. Grammar:

        Syntax is defined using an informal variant of EBNF.

            token:      /regex/ | "quoted" | <english description>
            prod:       prodname ":" expr*
            expr:       alt ( "|" alt )*
            alt:        term term*
            term:       prod | token | group | opt | rep
            group:      "(" expr ")" .
            opt:        "[" expr "]" .
            rep:        zerorep | onerep
            zerorep:    term "*"
            onerep:     term "+"

        Whitespace and comments are ommitted in this description.

        To put it in words, /regex/ defines a regular expression that would
        match a single token in the input. "quoted" would match a single
        string. <english description> contains an informal description of what
        characters would match.

        Productions are defined by any number of expressions, in which
        expressions are '|' separated sequences of terms.

        Terms can are productions or tokens, and may come with a repeat
        specifier. wrapping a term in "[]" denotes that the term is repeated
        0 or 1 times. suffixing it with a '*' denotes 0 or more repetitions,
        and '+' denotes 1 or more repetitions.

    2.2. As-If Rule:

        Anything specified here may be treated however the compiler wishes,
        as long as the result is observed as if the semantics specified were
        followed strictly.

3. LEXICAL CONVENTIONS:

    3.1. Summary:

        The language is composed of several classes of tokens. There are
        comments, identifiers, keywords, punctuation, and whitespace.

        Comments begin with "/*" and end with "*/". They may nest.

            /* this is a comment /* with another inside */ */

        Identifiers begin with any alphabetic character or underscore, and
        continue with alphanumeric characters or underscores. Currently the
        compiler places a limit of 1024 bytes on the length of the identifier.

            some_id_234__

        Keywords are a special class of identifier that is reserved by the
        language and given a special meaning. The full set of keywords are
        listed below. Their meanings will be covered later in this reference
        manual.

            $noret          _               break
            castto          const           continue
            elif            else            extern
            false           for             generic
            goto            if              impl
            in              match           pkg
            pkglocal        sizeof          struct
            trait           true            type
            union           use             var
            void            while

        Literals are a direct representation of a data object within the
        source of the program. There are several literals implemented within
        the language.  These are fully described in section 4.2 of this
        manual. 

        Single semicolons (';') and newline (\n) characters are synonymous and
        interchangable. They both are used to mark the end of logical lines,
        and will be uniformly referred to as line terminators.

4. SYNTAX OVERVIEW:

    4.1. Declarations:

            decl:       attrs ("var" | "const" | "generic")  decllist
            attrs:      ("exern" | "pkglocal" | "$noret")+
            decllist:   declbody ("," declbody)*
            declbody:   declcore ["=" expr]
            declcore:   name [":" type

        A declaration consists of a declaration class (i.e., one
        of 'const', 'var', or 'generic'), followed by a declaration
        name, optionally followed by a type and assignment. One thing
        you may note is that unlike most other languages, there is no
        special function declaration syntax. Instead, a function is
        declared like any other value: by assigning its name to a
        constant or variable.

            const:      Declares a constant value, which may not be
                        modified at run time. Constants must have
                        initializers defined.

            var:        Declares a variable value. This value may be
                        assigned to, copied from, and modified.

            generic:    Declares a specializable value. This value
                        has the same restrictions as a const, but
                        taking its address is not defined. The type
                        parameters for a generic must be explicitly
                        named in the declaration in order for their
                        substitution to be allowed.

        In addition, declarations may accept a number of modifiers which
        change the attributes of the declarations:

            extern:     Declares a variable as having external linkage.
                        Assigning a definition to this variable within the
                        file that contains the extern definition is an error.

            pkglocal:   Declares a variable which is local to the package.
                        This variable may be used from other files that
                        declare the same `pkg` namespace, but referring to
                        it from outside the namespace is an error.

            $noret:     Declares the function to which this is applied as
                        a non-returning function.

        Examples:

            Declare a constant with a value 123. The type is not defined,
            and will be inferred:

                const x = 123

            Declare a variable with no value and no type defined. The
            value can be assigned later (and must be assigned before use),
            and the type will be inferred.

                var y

            Declare a generic with type '@a', and assigns it the value
            'blah'. Every place that 'z' is used, it will be specialized,
            and the type parameter '@a' will be substituted.

                generic z : @a = blah

            Declare a function f with and without type inference. Both
            forms are equivalent. 'f' takes two parameters, both of type
            int, and returns their sum as an int

                const f = {a, b
                    var c : int = 42
                    -> a + b + c
                }

                const f : (a : int, b : int -> int) = {a : int, b : int -> int
                    var c : int  = 42
                    -> a + b + c
                }



    4.2. Data Types:

        The language defines a number of built in primitive types. These
        are not keywords, and in fact live in a separate namespace from
        the variable names. Yes, this does mean that you could, if you want,
        define a variable named 'int'.

        There are no implicit conversions within the language. All types
        must be explicitly cast if you want to convert, and the casts must
        be of compatible types, as will be described later.

            4.2.1. Primitive types:

                    void
                    bool            char
                    int8            uint8
                    int16           uint16
                    int32           uint32
                    int64           uint64
                    int             uint
                    long            ulong
                    float32         float64

                These types are as you would expect. 'void' represents a
                lack of type, although for the sake of genericity, you can
                assign between void types, return values of void, and so on.
                This allows generics to not have to somehow work around void
                being a toxic type. The void value is named `void`.

                It is interesting to note that these types are not keywords,
                but are instead merely predefined identifiers in the type
                namespace.

                bool is a type that can only hold true and false. It can be
                assigned, tested for equality, and used in the various boolean
                operators.

                char is a 32 bit integer type, and is guaranteed to be able
                to hold exactly one codepoint. It can be assigned integer
                literals, tested against, compared, and all the other usual
                numeric types.

                The various [u]intXX types hold, as expected, signed and
                unsigned integers of the named sizes respectively.
                Similarly, floats hold floating point types with the
                indicated precision.

                    var x : int         declare x as an int
                    var y : float32     declare y as a 32 bit float


            4.2.2. Composite types:

                    pointer
                    slice           array

                Pointers are, as expected, values that hold the address of
                the pointed to value. They are declared by appending a '#'
                to the type. Pointer arithmetic is not allowed. They are
                declared by appending a '#' to the base type

                Arrays are a group of N values, where N is part of the type.
                Arrays of different sizes are incompatible. Arrays in
                Myrddin, unlike many other languages, are passed by value.
                They are declared by appending a '[SIZE]' to the base type.

                Slices are similar to arrays in many contemporary languages.
                They are reference types that store the length of their
                contents. They are declared by appending a '[,]' to the base
                type.

                    foo#        type: pointer to foo
                    foo[123]    type: array of 123 foo
                    foo[,]      type: slice of foo

            4.2.3. Aggregate types:

                    tuple           struct
                    union

                Tuples are the traditional product type. They are declared
                by putting the comma separated list of types within square
                brackets.

                Structs are aggregations of types with named members. They
                are declared by putting the word 'struct' before a block of
                declaration cores (ie, declarations without the storage type
                specifier).

                Unions are the traditional sum type. They consist of a tag
                (a keyword prefixed with a '`' (backtick)) indicating their
                current contents, and a type to hold. They are declared by
                placing the keyword 'union' before a list of tag-type pairs.
                They may also omit the type, in which case, the tag is
                sufficient to determine which option was selected.

                    [int, int, char]            a tuple of 2 ints and a char

                    struct                      a struct containing an int named
                        a : int                 'a', and a char named 'b'.
                        b : char
                    ;;

                    union                       a union containing one of
                        `Thing int              int or char. The values are not
                        `Other float32          named, but they are tagged.
                    ;;


            4.2.4. Magic types:

                    tyvar           typaram
                    tyname

                A tyname is a named type, similar to a typedef in C, however
                it genuinely creates a new type, and not an alias. There are
                no implicit conversions, but a tyname will inherit all
                constraints of its underlying type.

                A typaram is a parametric type. It is used in generics as
                a placeholder for a type that will be substituted in later.
                It is an identifier prefixed with '@'. These are only valid
                within generic contexts, and may not appear elsewhere.

                A tyvar is an internal implementation detail that currently
                leaks in error messages out during type inference, and is a
                major cause of confusing error messages. It should not be in
                this manual, except that the current incarnation of the
                compiler will make you aware of it. It looks like '@$type',
                and is a variable that holds an incompletely inferred type.

                    type mine = int             creates a tyname named
                                                'mine', equivalent to int.


                    @foo                        creates a type parameter
                                                named '@foo'.

    4.3. Literal Values

        4.3.1. Atomic Literals:

                literal:    strlit | chrlit | floatlit |
                            boollit | voidlit | intlit |
                            funclit | seqlit | tuplit

                strlit:     \"(byte|escape)*\"
                chrlit:     \'(utf8seq|escape)\'
                char:       <any byte value>
                escape:     <any escape sequence>
                intlit:     "0x" digits | "0o" digits | "0b" digits | digits
                floatlit:   digit+"."digit+["e" digit+]
                boollit:    "true"|"false"
                voidlit:    "void"

            Integers literals are a sequence of digits, beginning with a digit and
            possibly separated by underscores. They are of a generic type, and can
            be used where any numeric type is expected. They may be prefixed with
            "0x" to indicate that the following number is a hexadecimal value, 0o
            to indicate an octal value, or 0b to indicate a binary value. Decimal
            values are not prefixed.

                eg: 0x123_fff, 0b1111, 0o777, 1234

            Floating-point literals are also a sequence of digits beginning with a
            digit and possibly separated by underscores. They are also of a
            generic type, and may be used whenever a floating-point type is
            expected. Floating point literals are always in decimal, but may
            have an exponent attached to them.

                eg: 123.456, 10.0e7, 1_000.

            String literals represent a compact method of representing a byte
            array. Any byte values are allowed in a string literal, and will be
            spit out again by the compiler unmodified, with the exception of
            escape sequences.

            There are a number of escape sequences supported for both character
            and string literals:
                \n          newline
                \r          carriage return
                \t          tab
                \b          backspace
                \"          double quote
                \'          single quote
                \v          vertical tab
                \\          single slash
                \0          nul character
                \xDD        single byte value, where DD are two hex digits.
                \u{xxx}     unicode escape, emitted as utf8.

            String literals begin with a ", and continue to the next
            unescaped ".

                eg: "foo\"bar"

            Multiple consecutive string literals are implicitly merged to create
            a single combined string literal. To allow a string literal to span
            across multiple lines, the new line characters must be escaped.
            
                eg: "foo" \
                    "bar"

            Character literals represent a single codepoint in the character
            set. A character starts with a single quote, contains a single
            codepoint worth of text, encoded either as an escape sequence
            or in the input character set for the compiler (generally UTF8).
            They share the same set of escape sequences as string literals.

                eg: 'א', '\n', '\u{1234}'

            Boolean literals are either the keyword "true" or the keyword
            "false".

                eg: true, false

        4.3.2. Sequence and Tuple Literals:
            
                seqlit:     "[" structelts | arrayelts "]"
                tuplit:     "(" tuplelts ")"

                structelts: ("." ident "=" expr)+
                arrayelts:  (expr ":" expr | expr)*
                tupelts:    expr ("," expr)* [","]

            Sequence literals are used to initialize either a structure
            or an array. They are '['-bracketed expressions, and are evaluated
            Tuple literals are similarly used to initialize a tuple.

            Struct literals describe a fully initialized struct value.
            A struct must have at least one member specified, in
            order to distinguish them from the empty array literal. All
            members which are designated with a `.name` expression are
            initialized to the expression passed. If an initializer is
            omitted, then the value is initialized to the zero value for
            that type.

            Sequence literals describe either an array or a structure
            literal. They begin with a '[', followed by an initializer
            sequence and closing ']'. For array literals, the initializer
            sequence is either an indexed initializer sequence[4], or an
            unindexed initializer sequence. For struct literals, the
            initializer sequence is always a named initializer sequence.

            An unindexed initializer sequence is simply a comma separated
            list of values. An indexed initializer sequence contains a
            '#number=value' comma separated sequence, which indicates the
            index of the array into which the value is inserted. A named
            initializer sequence contains a comma separated list of
            '.name=value' pairs.


            A tuple literal is a parentheses separated list of values.
            A single element tuple contains a trailing comma.

            Example: Struct literal.
                [.a = 42, .b="str"]

            Example: Array literal:
                [1,2,3], [2:3, 1:2, 0:1], 

            Example: Tuple literals:
                (1,), (1,'b',"three")


        4.3.3. Function Literals:

                funclit:        "{" arglist "\n" blockbody "}"
                arglist:        (ident [":" type])*

            Function literals describe a function. They begin with a '{',
            followed by a newline-terminated argument list, followed by a
            body and closing '}'. These may be specified at any place that
            an expression is specified, assigned to any variable, and are
            not distinguished from expressions in any significant way.

            Function literals may refer to variables outside of their scope.
            These are treated differently in a number of ways. Variables with
            global scope are used directly, by value.
            
            If a function is defined where stack variables are in scope,
            and it refers to them, then the stack variables shall be copied
            to an environment on thes stack. That environment is scoped to
            the lifetime of the stack frame in which it was defined. If it
            does not refer to any of its enclosing stack variables, then
            this environment will not be created or accessed by the function.

            This environment must be transferrable to the heap in an
            implementation specific manner.

            Example: Empty function literal:
                {;}

            Example: Function literal

                {a : int, b
                    -> a + b
                }

            Example: Nested function with environment:

                const fn = {a
                    var b = {; a + 1}
                }


        4.3.4: Labels:

                label:  ":" ident
                goto:   "goto" ident

            Finally, while strictly not a literal, it's not a control
            flow construct either. Labels are identifiers preceded by
            colons.

                eg: :my_label

            They can be used as targets for gotos, as follows:

                goto my_label

            the ':' is not part of the label name.

    4.4. Blocks:

            block:      blockbody ";;"
            blockbody:  (decl | stmt | tydef | "\n")*
            stmt:       goto | break | continue | retexpr | label |
                        ifstmt | forstmt | whilestmt | matchstmt

        Blocks are the basic building block of functionality in Myrddin.  They
        are simply sequences of statements that are completed one after the
        other. They are generally terminated by a double semicolon (";;"),
        although they may be terminated by keywords if they are part of a more
        complex control flow construct.

        Any declarations within the block are scoped to within the block,
        and are not accessible outside of it. Their storage duration is
        limited to within the block, and any attempts to access the associated
        storage (via pointer, for example) is not valid.

    4.5. Control Constructs:

            ifstmt:     "if" cond "\n" blockbody
                        ("elif" blockbody)*
                        ["else" blockbody] ";;"

            forstmt:    foriter | foreach
            foreach:    "for" pattern "in" expr "\n" block
            foriter:    "for" init "\n" cond "\n" step "\n" block

            whilestmt:  "while" cond "\n" block

            matchstmt:  "match" expr "\n" matchpat* ";;"
            matchpat:   "|" pat ":" blockbody

            
            goto

        The control statements in Myrddin are similar to those in many other
        popular languages, and with the exception of 'match', there should
        be no surprises to a user of any of the Algol derived languages.

        Blocks are the "carriers of code" in Myrddin programs. They consist
        of series of expressions, typically ending with a ';;', although the
        function-level block ends at the function's '}', and in if
        statements, an 'elif' may terminate a block. They can contain any
        number of declarations, expressions, control constructs, and empty
        lines. Every control statement example below will (and, in fact,
        must) have a block attached to the control statement.

        If statements branch one way or the other depending on the truth
        value of their argument. The truth statement is separated from the
        block body

            if true
                std.put("The program always get here")
            elif elephant != mouse
                std.put("...eh.")
            else
                std.put("The program never gets here")
            ;;

        For statements come in two forms. There are the C style for loops
        which begin with an initializer, followed by a test condition,
        followed by an increment action. For statements run the initializer
        once before the loop is run, the test each on each iteration through
        the loop before the body, and the increment on each iteration after
        the body. If the loop is broken out of early (for example, by a goto),
        the final increment will not be run. The syntax is as follows:

            for init; test; increment
                blockbody()
            ;;

        The second form is the collection iteration form. This form allows
        for iterating over a collection of values contained within something
        which is iterable. Currently, only the built in sequences -- arrays
        and slices -- can be iterated, however, there is work going towards
        allowing user defined iterables.

            for pat in expr
                blockbody()
            ;;

        The pattern applied in the for loop is a full match statement style
        pattern match, and will filter any elements in the iteration
        expression which do not match the value.

        While loops are equivalent to for loops with empty initializers
        and increments. They run the test on every iteration of the loop,
        and exit only if it returns false.

        Match statements do pattern matching on values. They take as an
        argument a value of type 't', and match it against a list of other
        values of the same type. The patterns matched against can also contain
        free names, which will be bound to the sub-value matched against. The
        patterns are checked in order, and the first matching pattern has its
        body executed, after which no other patterns will be matched. This
        implies that if you have specific patterns mixed with by more general
        ones, the specific patterns must come first.

        Match patterns can be one of the following:

            - Union patterns

                These look like union constructors, only they define
                a value to match against.

            - Literal patterns

                Any literal value can be matched against.

            - Constant patterns

                Any constant value can be matched against.

        More types of pattern to match will be added over time.

        Match statements consist of the keyword 'match', followed by
        the expression to match against the patterns, followed by a
        newline. The body of the match statement consists of a list
        of pattern clauses. A patterned clause is a '|', followed by
        a pattern, followed by a ':', followed by a block body.

        An example of the syntax follows:

            const Val234 = `Val 234     /* set up a constant value */
            var v = `Val 123            /* set up variable to match */
            match v
            /* pattern clauses */
            | `Val 123:
                std.put("Matched literal union pat\n")
            | Val234:
                std.put("Matched const value pat\n")
            | `Val a:
                std.put("Matched pattern with capture\n")
                std.put("Captured value: a = {}\n", a)
            | a
                std.put("A top level bind matches anything.")
            | `Val 111
                std.put("Unreachable block.")
            ;;


    4.6. Expressions:

        Myrddin expressions are relatively similar to expressions in C.  The
        operators are listed below in order of precedence, and a short
        summary of what they do is listed given. For the sake of clarity,
        'x' will stand in for any expression composed entirely of
        subexpressions with higher precedence than the current current
        operator. 'e' will stand in for any expression. Unless marked
        otherwise, expressions are left associative.

        BUG: There are too many precedence levels.


            Precedence 14: (*ok, not really operators)
                (,,,)           Tuple Construction
                (e)             Grouping
                name            Bare names
                literal         Values

            Precedence 13:
                x.name          Member lookup
                x++             Postincrement
                x--             Postdecrement
                x#              Dereference
                x[e]            Index
                x[from,to]      Slice

            Precedence 12:
                ++x             Preincrement
                --x             Predecrement
                &x              Address
                !x              Logical negation
                ~x              Bitwise negation
                +x              Positive (no operation)
                -x              Negate x

            Precedence 11:
                x << x          Shift left
                x >> x          Shift right

            Precedence 10:
                x * x           Multiply
                x / x           Divide
                x % x           Modulo

            Precedence 9:
                x + x           Add
                x - x           Subtract

            Precedence 8:
                x & y           Bitwise and

            Precedence 7:
                x | y           Bitwise or
                x ^ y           Bitwise xor

            Precedence 6:
                `Name x         Union construction

            Precedence 5:
                x castto(type)  Cast expression

            Precedence 4:
                x == x          Equality
                x != x          Inequality
                x > x           Greater than
                x >= x          Greater than or equal to
                x < x           Less than
                x <= x          Less than or equal to

            Precedence 3:
                x && x          Logical and

            Precedence 2:
                x || x          Logical or

            Precedence 1:
                x = x           Assign                  Right assoc
                x += x          Fused add/assign        Right assoc
                x -= x          Fused sub/assign        Right assoc
                x *= x          Fused mul/assign        Right assoc
                x /= x          Fused div/assign        Right assoc
                x %= x          Fused mod/assign        Right assoc
                x |= x          Fused or/assign         Right assoc
                x ^= x          Fused xor/assign        Right assoc
                x &= x          Fused and/assign        Right assoc
                x <<= x         Fused shl/assign        Right assoc
                x >>= x         Fused shr/assign        Right assoc

            Precedence 0:
                -> x            Return expression

        All expressions on integers act on two's complement values which wrap
        on overflow. Right shift expressions fill with the sign bit on
        signed types, and fill with zeros on unsigned types.


    4.7. Type Inference:

        The myrddin type system is a system similar to the Hindley Milner
        system, however, types are not implicitly generalized. Instead, type
        schemes (type parameters, in Myrddin lingo) must be explicitly provided
        in the declarations. For purposes of brevity, instead of specifying type
        rules for every operator, we group operators which behave identically
        from the type system perspective into a small set of classes. and define
        the constraints that they require.

        Type inference in Myrddin operates as a bottom up tree walk,
        applying the type equations for the operator to its arguments.
        It begins by initializing all leaf nodes with the most specific
        known type for them as follows:

        4.6.1 Types for leaf nodes:

            Variable        Type
            ----------------------
            var foo         $t

                A type variable is the most specific type for a declaration
                or function without any specified type

            var foo : t     t

                If a type is specified, that type is taken for the
                declaration.

            "asdf"          byte[:]

                String literals are byte arrays.


            'a'             char

                Char literals are of type 'char'

            void            void

                void is a literal value of type void.

            true            bool
            false           bool

                true/false are boolean literals

            123             $t::(integral,numeric)

                Integer literals get a fresh type variable of type with
                the constraints for int-like types.

            123.1           $t::(floating,numeric)

                Float literals get a fresh type variable of type with
                the constraints for float-like types.

            {a,b:t; }       ($a,t -> $b)

                Function literals get the most specific type that can
                be determined by their signature.


        num-binop:

                +           -               *               /               %
                +=          -=              *=              /=              %

            Number binops require the constraint 'numeric' for both the

        num-unary:
            -           +
            Number binops require the constraint 'numeric'.

        int-binop:
            |           &               ^               <<              >>
            |=          &=              ^=              <<=             >>
        int-unary:
            ~           ++              --

        bool-binop:
            ||          &&              ==              !=
            <           <=              >               >=


    4.8. Packages and Uses:

            pkg     use

        There are two keywords for module system. 'use' is the simpler
        of the two, and has two cases:

            use syspkg
            use "localfile"

        The unquoted form searches all system include paths for 'syspkg'
        and imports it into the namespace. By convention, the namespace
        defined by 'syspkg' is 'syspkg', and is unique and unmerged. This
        is not enforced, however. Typical usage of unquoted names is to
        import a library that already exists.

        The quoted form searches the local directory for "localpkg".  By
        convention, the package it imports does not match the name
        "localpkg", but instead is used as partial of the definition of the
        importers package. This is a confusing description.

        A typical use of a quoted import is to allow splitting one package
        into multiple files. In order to support this behavior, if a package
        is defined in the current file, and a use statements imports a
        package with the same namespace, the two namespaces are merged.

        The 'pkg' keyword allows you to define a (partial) package by
        listing the symbols and types for export. For example,

            pkg mypkg =
                type mytype

                const Myconst   : int = 42
                const myfunc    : (v : int -> bool)
            ;;

        declares a package "mypkg", which defines three exports, "mytype",
        "Myconst", and "myfunc". The definitions of the values may be
        defined in the 'pkg' specification, but it is preferred to implement
        them in the body of the code for readability. Scanning the export
        list is desirable from a readability perspective.

9. GRAMMAR:

10. FUTURE DIRECTIONS:

BUGS: