summaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
-rw-r--r--cobol.html.markdown317
-rw-r--r--fsharp.html.markdown4
-rw-r--r--lbstanza.html.markdown282
3 files changed, 447 insertions, 156 deletions
diff --git a/cobol.html.markdown b/cobol.html.markdown
index 4452bd95..7d94d8c9 100644
--- a/cobol.html.markdown
+++ b/cobol.html.markdown
@@ -8,178 +8,187 @@ COBOL is a business-oriented language revised multiple times since its original
organizations.
```cobol
- *COBOL. Coding like it's 1985.
+ *COBOL. Coding like it's 1985.
*Compiles with GnuCOBOL in OpenCobolIDE 4.7.6.
*COBOL has significant differences between legacy (COBOL-85)
*and modern (COBOL-2002 and COBOL-2014) versions.
*Legacy versions require columns 1-6 to be blank (they are used
*to store the index number of the punched card..)
- *A * in column 7 means a comment.
+ *A '*' in column 7 means a comment.
*In legacy COBOL, a comment can only be a full line.
*Modern COBOL doesn't require fixed columns and uses *> for
*a comment, which can appear in the middle of a line.
*Legacy COBOL also imposes a limit on maximum line length.
*Keywords have to be in capitals in legacy COBOL,
*but are case insensitive in modern.
-
- *First, we must give our program ID.
+ *Although modern COBOL allows you to use mixed-case characters
+ *it is still common to use all caps when writing COBOL code.
+ *This is what most professional COBOL developers do.
+ *COBOL statements end with a period.
+
+ *COBOL code is broken up into 4 divisions.
+ *Those divisions, in order, are:
+ *IDENTIFICATION DIVSION.
+ *ENVIRONMENT DIVISION.
+ *DATA DIVISION.
+ *PROCEDURE DIVISION.
+
+ *First, we must give our program an ID.
*Identification division can include other values too,
- *but they are comments only. Program-id is mandatory.
- identification division.
- program-id. learn.
+ *but they are comments only. Program-id is the only one that is mandatory.
+ IDENTIFICATION DIVISION.
+ PROGRAM-ID. LEARN.
+ AUTHOR. JOHN DOE.
+ DATE-WRITTEN. 05/02/2020.
*Let's declare some variables.
- data division.
- working-storage section.
-
- *Variables are specified by a "picture" - how they should be
- *displayed, and variable type is inferred from this.
- *The "01" value is the level number which is used for building
- *data structures.
- 01 myname picture xxxxxxxxxx. *> A 10 character string.
- 01 age picture 999. *> A number up to 3 digits.
- 01 valx picture 999. *> Another number up to 3 digits.
- 01 inyear picture s9(7). *> S makes number signed.
+ *We do this in the WORKING-STORAGE section within the DATA DIVISION.
+ *Each data item (aka variable) with start with a level number,
+ *then the name of the item, followed by a picture clause
+ *describing the type of data that the variable will contain.
+ *Almost every COBOL programmer will abbreviate PICTURE as PIC.
+ *A is for alphabetic, X is for alphanumeric, and 9 is for numeric.
+
+ *example:
+ 01 MYNAME PIC xxxxxxxxxx. *> A 10 character string.
+
+ *But counting all those x's can lead to errors,
+ *so the above code can, and should
+ *be re-written as:
+ 01 MYNAME PIC X(10).
+
+ *Here are some more examples:
+ 01 AGE PIC 9(3). *> A number up to 3 digits.
+ 01 LAST_NAME PIC X(10). *> A string up to 10 characters.
+
+ *In COBOL, multiple spaces are the same as a single space, so it is common
+ *to use multiple spaces to line up your code so that it is easier for other
+ *coders to read.
+ 01 inyear picture s9(7). *> S makes number signed.
*> Brackets indicate 7 repeats of 9,
*> ie a 6 digit number (not an array).
- *Now let's write some code.
- procedure division.
-
- main-procedure.
- *> COBOL is the language that uses DISPLAY instead of PRINT.
- *> Note: no full stops after commands. Only after the LAST
- *> command.
- display "Hello. What's your name?"
-
- *> Let's input a string.
- *> If input too long, later characters are trimmed.
- accept myname
- display "Hello " myname *> We can display several things.
- display "How old are you?"
-
- *> Let's input a number.
- *> If input too long, EARLIER characters are trimmed.
- accept age
-
- display age *> Left-padded to three chracaters with zeroes,
- *> because of the defined PICTURE for age.
-
- *> We have two ways of doing a FOR loop.
- *> Old style way: doesn't give an index.
- perform age times
- display "*" with no advancing *> Ie, no newline at end
- end-perform
- display "." *> Output buffer isn't flushed until newline.
-
- *> New style way: with an index.
- perform varying valx from 1 by 1 until valx > age
- display valx "-" with no advancing
- end-perform
- display "."
-
- *> If tests are still good old if tests.
- if myname = "Bob" then
- display "I don't like Bob."
- else
- display "I don't know you."
- end-if
-
- *> There are two ways of doing subprograms and calling
- *> them.
- *> The simplest way: a paragraph.
- perform subparagraph
-
- *> The complex way, with parameters and stuff.
- call "eratosthenes" using age returning valx
-
- display "There were " valx " primes."
-
- stop run.
-
- subparagraph. *> Marks the top of an internal subprogram.
- *> Shares variable score with its caller.
-
- *> Read year from system timer.
- *> Remember the whole "year 2000 crisis"? The yyyyddd
- *> option was added in response to that.
- accept inyear from day yyyyddd.
-
- *> We can do math step-by-step like this...
- divide 1000 into inyear.
- subtract age from inyear.
-
- display "You were born in " inyear "."
-
- *> Or we can just use expressions.
- compute inyear = 1970 - inyear.
-
- if inyear >= 0 then
- display "When you were " inyear ", " with no advancing
- else
- display inyear " years before you were born, " with no
- advancing
- end-if
-
- display "COBOL was the most popular language in the world."
- . *> You can put the final . on a new line if it's clearer.
-
-
- *If we want to use a subprogram, we use literally a subprogram.
- *This is the entire program layout, repeated for the
- *eratosthenes subroutine.
- identification division.
- program-id. eratosthenes.
-
- data division.
- working-storage section.
- *Declare an array.
- *We can declare a variable to use as an index for it at the
- *same time.
- 01 sieve pic 9 occurs 999 times indexed by sa, sb.
- *> Standard cobol doesn't have a boolean type.
- 01 pstart pic 999.
- 01 counter pic 999.
-
- *Our parameters have to be declared in the linkage section.
- *Their pictures must match the values they're called with.
- linkage section.
- 01 maxvalue picture 999.
-
- *"using" declares our actual parameter variables.
- *"returning" declares the variable value returned at end.
- procedure division using maxvalue returning counter.
- main-procedure.
-
- display "Here are all the primes up to " maxvalue "."
-
- perform varying sa from 1 by 1 until sa > maxvalue
- move 1 to sieve (sa)
- end-perform
-
- perform varying sa from 2 by 1 until sa > maxvalue
- if sieve(sa) = 1 then
- compute pstart = sa + sa
- perform varying sb from pstart by sa until sb >
- maxvalue
- move 0 to sieve(sb)
- end-perform
- end-if
- end-perform
-
- initialise counter *> To zero by default for a number.
-
- perform varying sa from 2 by 1 until sa > maxvalue
- if sieve(sa) = 1 THEN
- display sa
- add 1 to counter
- end-if
- end-perform.
-
- end program eratosthenes.
-
- end program learn.
+ *Now let's write some code. Here is a simple, Hello World program.
+ IDENTIFICATION DIVISION.
+ PROGRAM-ID. HELLO.
+ DATA DIVISION.
+ WORKING-STORAGE SECTION.
+ 01 THE-MESSAGE PIC X(20).
+ PROCEDURE DIVSION.
+ DISPLAY "STARTING PROGRAM".
+ MOVE "HELLO WORLD" TO THE-MESSAGE.
+ DISPLAY THE-MESSAGE.
+ STOP RUN.
+
+ *The above code will output:
+ *STARTING PROGRAM
+ *HELLO WORLD
+
+
+
+ ********COBOL can perform math***************
+ ADD 1 TO AGE GIVING NEW-AGE.
+ SUBTRACT 1 FROM COUNT.
+ DIVIDE VAR-1 INTO VAR-2 GIVING VAR-3.
+ COMPUTE TOTAL-COUNT = COUNT1 PLUS COUNT2.
+
+
+ *********PERFORM********************
+ *The PERFORM keyword allows you to jump to another specified section of the code,
+ *and then to return to the next executable
+ *statement once the specified section of code is completed.
+ *You must write the full word, PERFORM, you cannot abbreviate it.
+
+ IDENTIFICATION DIVISION.
+ PROGRAM-ID. HELLOCOBOL.
+
+ PROCEDURE DIVISION.
+ FIRST-PARA.
+ DISPLAY 'THIS IS IN FIRST-PARA'.
+ PERFORM THIRD-PARA THRU FOURTH-PARA. *>skip second-para and perfrom 3rd & 4th
+ *> then after performing third and fourth,
+ *> return here and continue the program until STOP RUN.
+
+ SECOND-PARA.
+ DISPLAY 'THIS IS IN SECOND-PARA'.
+ STOP RUN.
+
+ THIRD-PARA.
+ DISPLAY 'THIS IS IN THIRD-PARA'.
+
+ FOURTH-PARA.
+ DISPLAY 'THIS IS IN FOURTH-PARA'.
+
+
+ *When you compile and execute the above program, it produces the following result:
+ THIS IS IN FIRST-PARA
+ THIS IS IN THIRD-PARA
+ THIS IS IN FOURTH-PARA
+ THIS IS IN SECOND-PARA
+
+
+ **********Combining variables together using STRING ***********
+
+ *Now it is time to learn about two related COBOL verbs: string and unstring.
+
+ *The string verb is used to concatenate, or put together, two or more stings.
+ *Unstring is used, not surprisingly, to separate a
+ *string into two or more smaller strings.
+ *It is important that you remember to use ‘delimited by’ when you
+ *are using string or unstring in your program.
+
+ IDENTIFICATION DIVISION.
+ PROGRAM-ID. LEARNING.
+ ENVIRONMENT DIVISION.
+ DATA DIVISION.
+ WORKING-STORAGE SECTION.
+ 01 FULL-NAME PIC X(20).
+ 01 FIRST-NAME PIC X(13) VALUE "BOB GIBBERISH".
+ 01 LAST-NAME PIC X(5) VALUE "COBB".
+ PROCEDURE DIVISION.
+ STRING FIRST-NAME DELIMITED BY SPACE
+ " "
+ LAST-NAME DELIMITED BY SIZE
+ INTO FULL-NAME
+ END-STRING.
+ DISPLAY "THE FULL NAME IS: "FULL-NAME.
+ STOP RUN.
+
+
+ *The above code will output:
+ THE FULL NAME IS: BOB COBB
+
+
+ *Let’s examine it to see why.
+
+ *First, we declared all of our variables, including the one that we are creating
+ *by the string command, in the DATA DIVISION.
+
+ *The action takes place down in the PROCEDURE DIVISION.
+ *We start with the STRING keyword and end with END-STRING. In between we
+ *list what we want to combine together into the larger, master variable.
+ *Here, we are combining FIRST-NAME, a space, and LAST-NAME.
+
+ *The DELIMITED BY phrase that follows FIRST-NAME and
+ *LAST-NAME tells the program how much of each variable we want to capture.
+ *DELIMITED BY SPACE tells the program to start at the beginning,
+ *and capture the variable until it runs into a space.
+ *DELIMITED BY SIZE tells the program to capture the full size of the variable.
+ *Since we have DELIMITED BY SPACE after FIRST-NAME, the GIBBERISH part is ignored.
+
+ *To make this clearer, change line 10 in the above code to:
+
+ STRING FIRST-NAME DELIMITED BY SIZE
+
+ *and then re-run the program. This time the output is:
+
+ THE FULL NAME IS: BOB GIBBERISH COBB
+
+
+
+
+
```
diff --git a/fsharp.html.markdown b/fsharp.html.markdown
index 064a9fdd..c140d6b1 100644
--- a/fsharp.html.markdown
+++ b/fsharp.html.markdown
@@ -633,6 +633,6 @@ module NetCompatibilityExamples =
## More Information
-For more demonstrations of F#, go to the [Try F#](http://www.tryfsharp.org/Learn) site, or my [why use F#](http://fsharpforfunandprofit.com/why-use-fsharp/) series.
+For more demonstrations of F#, go to my [why use F#](http://fsharpforfunandprofit.com/why-use-fsharp/) series.
-Read more about F# at [fsharp.org](http://fsharp.org/).
+Read more about F# at [fsharp.org](http://fsharp.org/) and [dotnet's F# page](https://dotnet.microsoft.com/languages/fsharp).
diff --git a/lbstanza.html.markdown b/lbstanza.html.markdown
new file mode 100644
index 00000000..19dc7db7
--- /dev/null
+++ b/lbstanza.html.markdown
@@ -0,0 +1,282 @@
+---
+language: LB Stanza
+filename: learn-stanza.stanza
+contributors:
+ - ["Mike Hilgendorf", "https://github.com/m-hilgendorf"]
+---
+
+LB Stanza (or Stanza for short) is a new optionally-typed general purpose programming language from the University of California, Berkeley. Stanza was designed to help programmers tackle the complexity of architecting large programs and significantly increase the productivity of application programmers across the entire software development life cycle.
+
+
+```stanza
+; this is a comment
+;<A>
+This is a block comment
+ ;<B>
+ block comments can be nested with optional tags.
+ ;<B>
+;<A>
+defpackage learn-stanza-in-y:
+ import core
+ import collections
+
+;==============================================================================
+; The basics, things you'd find in most programming languages
+;==============================================================================
+
+
+; Variables can be mutable (var) or immutable (val)
+val immutable = "this string can't be changed"
+var mutable = "this one can be"
+mutable = "like this"
+
+; The basic data types (annotations are optional)
+val an-int: Int = 12345
+val a-long: Long = 12345L
+val a-float: Float = 1.2345f
+val a-double: Double = 3.14159
+val a-string: String = "this is a string"
+val a-multiline-string = \<tag>
+ this is a "raw" string literal
+\<tag>
+
+; Print a formatted string with println and "..." % [...]
+println("this is a formatted string %_ %_" % [mutable, immutable])
+
+; Stanza is optionally typed, and has a ? (any) type.
+var anything:? = 0
+anything = 3.14159
+anything = "a string"
+
+; Stanza has basic collections like Tuples, Arrays, Vectors and HashTables
+val tuple: Tuple<?> = [mutable, immutable]
+
+val array = Array<?>(3)
+array[0] = "string"
+array[1] = 1
+array[2] = 1.23455
+; array[3] = "out-of-bounds" ; arrays are bounds-checked
+
+val vector = Vector<?>()
+vector[0] = "string"
+vector[1] = 1
+vector[2] = 3.14159
+
+val hash-table = HashTable<String, ?>()
+hash-table["0"] = 0
+hash-table["1"] = 1
+hash-table["2"] = 1
+
+
+;==============================================================================
+; Functions
+;==============================================================================
+; Functions are declared with the `defn` keyword
+defn my-function (arg:?) : ; note the space between identifier and arg list
+ println("called my-function with %_" % [arg])
+
+my-function("arg") ; note the lack of a space to call the function
+
+; Functions can be declared inside another function and capture variables from
+; the surrounding environment.
+defn outer (arg):
+ defn inner ():
+ println("outer had arg: %_" % [arg])
+ inner()
+
+outer("something")
+
+; functions are "first-class" in stanza, meaning you can assign variables
+; to functions and pass functions as arguments to other functions.
+val a-function = outer
+defn do-n-times (arg, func, n:Int):
+ for i in 0 to n do :
+ func(arg)
+do-n-times("argument", a-function, 3)
+
+; sometimes you want to define a function inline, or use an anonymous function.
+; for this you can use the syntax:
+; fn (args):
+; ...
+do-n-times("hello", fn (arg): println(arg), 2)
+
+; there is a shorthand for writing anonymous functions
+do-n-times("hello", { println(_) }, 2)
+
+; the short hand works for multiple arguments as well.
+val multi-lambda = { println(_ + 2 * _) }
+multi-lambda(1, 2)
+
+;==============================================================================
+; User defined types
+;==============================================================================
+; Structs are declared with the `defstruct` keyword
+defstruct MyStruct:
+ field
+
+; constructors are derived automatically
+val my-struct = MyStruct("field:value")
+
+; fields are accessed using function-call syntax
+println(field(my-struct))
+
+; Stanza supports subtyping with a "multimethod" system based on method
+; overloading.
+deftype MyType
+defmulti a-method (m:MyType)
+
+defstruct Foo <: MyType
+defstruct Bar <: MyType
+defmethod a-method (a-foo: Foo):
+ println("called a-method on a Foo")
+
+defmethod a-method (a-foo: Bar):
+ println("called a-method on a Bar")
+
+;==============================================================================
+; The Type System
+;==============================================================================
+; True and Falseare types with a single value.
+val a-true: True = true
+val a-false: False = false
+
+; You can declare a union type, or a value that is one of a set of types
+val a-boolean: True|False = true
+val another-boolean: True|False = false
+
+; You can pattern match on types
+match(a-boolean):
+ (t:True): println("is true")
+ (f:False): println("is false")
+
+; You can match against a single possible type
+match(a-boolean:True):
+ println("is still true")
+else:
+ println("is not true")
+
+; You can compose program logic around the type of a variable
+if anything is Float :
+ println("anything is a float")
+else if anything is-not String :
+ println("anything is not an int")
+else :
+ println("I don't know what anything is")
+
+;==============================================================================
+; Control Flow
+;==============================================================================
+; stanza has the standard basic control flow
+val condition = [false, false]
+if condition[0] :
+ ; do something
+ false
+else if condition[1] :
+ ; do another thing
+ false
+else :
+ ; whatever else
+ false
+
+; there is also a switch statement, which can be used to pattern match
+; on values (as opposed to types)
+switch(anything):
+ "this": false
+ "that": false
+ "the-other-thing": false
+ else: false
+
+; for and while loops are supported
+while condition[0]:
+ println("do stuff")
+
+for i in 0 to 10 do:
+ vector[i] = i
+
+; stanza also supports named labels which can functin as break or return
+; statements
+defn another-fn ():
+ label<False> return:
+ label<False> break:
+ while true:
+ if condition[0] is False:
+ break(false)
+ return(false)
+
+; For a comprehensive guide on Stanza's advanced control flow, check out
+; this page: http://lbstanza.org/chapter9.html from Stanza-by-Example
+
+;==============================================================================
+; Sequences
+;==============================================================================
+; for "loops" are sugar for a more powerful syntax.
+val xs = [1, 2, 3]
+val ys = ['a', 'b', 'c']
+val zs = ["foo", "bar", "baz"]
+
+for (x in xs, y in ys, z in zs) do :
+ println("x:%_, y:%_, z:%_" % [x, y, z])
+
+
+;xs, ys, and zs are all "Seqable" meaing they are Seq types (sequences).
+; the `do` identifier is a special function that just applies the body of
+; the for loop to each element of the sequence.
+;
+; A common sequence task is concatenating sequences. This is accomplished
+; using the `seq-cat` function. This is analogous to "flattening" iterateors
+val concat = to-tuple $
+ for sequence in [xs, ys, zs] seq-cat:
+ sequence
+
+; we can also use a variation to interleave the elements of multiple sequences
+val interleaved = to-tuple $
+ for (x in xs, y in ys, z in zs) seq-cat :
+ [x, y, z]
+
+println("[%,] [%,]" % [concat, interleaved])
+
+; Another common task is mapping a sequence to another, for example multiplying
+; all the elements of a list of numbers by a constant. To do this we use `seq`.
+var numbers = [1.0, 2.0, 3.0, 4.0]
+numbers = to-tuple $
+ for n in numbers seq :
+ 2.0 * n
+println("%," % [numbers])
+
+if find({_ == 2.0}, numbers) is-not False :
+ println("found it!")
+
+; or maybe we just want to know if there's something in a sequence
+var is-there =
+ for n in numbers any? :
+ n == 2.0
+
+; since this is "syntactic sugar" we can write it explicitly using an
+; anonymous function
+is-there = any?({_ == 2.0}, numbers)
+
+; a detailed reference of the sequence library and various adaptors can
+; be found here: http://lbstanza.org/reference.html#anchor439
+
+
+=========================================================================
+; Documentation
+;=========================================================================
+;
+; Top level statements can be prefixed with the "doc" field which takes
+; a string value and is used to autogenerate documentation for the package.
+doc: \<doc>
+ # Document Strings
+
+ ```stanza
+ val you-can = "include code snippets, too"
+ ```
+
+ To render documentation as markdown (compatible with mdbook)
+
+ ```bash
+ stanza doc source.stanza -o docs
+ ```
+\<doc>
+defn docfn () : false
+``` \ No newline at end of file