\ No newline at end of file
diff --git a/_includes/note.html b/_includes/note.html
new file mode 100644
index 000000000..00d3501c7
--- /dev/null
+++ b/_includes/note.html
@@ -0,0 +1,4 @@
+
\ No newline at end of file
diff --git a/_includes/tip.html b/_includes/tip.html
new file mode 100644
index 000000000..19ec2b786
--- /dev/null
+++ b/_includes/tip.html
@@ -0,0 +1,4 @@
+
\ No newline at end of file
diff --git a/_layouts/default.html b/_layouts/default.html
index b96a9d778..149518296 100644
--- a/_layouts/default.html
+++ b/_layouts/default.html
@@ -10,6 +10,7 @@
+
+
+
+
+
+## Controlling program flow
+
+### Conditional construct (`if`)
+
+__Example:__ single branch `if`
+
+```fortran
+ if (angle < 90.0) then
+ print *, 'Angle is acute'
+ end if
+```
+
+__Example:__ two-branch `if-else`
+
+```fortran
+ if (angle < 90.0) then
+ print *, 'Angle is acute'
+ else
+ print *, 'Angle is obtuse'
+ end if
+```
+
+__Example:__ multi-branch `if-elseif-else`
+```fortran
+ if (age < 90.0) then
+ print *, 'Angle is acute'
+ else if (angle < 180.0) then
+ print *, 'Angle is obtuse'
+ else
+ print *, 'Angle is reflex'
+ end if
+```
+
+
+### Loop constructs (`do`)
+
+__Example:__ `do` loop
+
+```fortran
+ integer :: i
+ do i=1,10
+ print *, i
+ end do
+```
+
+__Example:__ `do` loop with skip
+
+```fortran
+ integer :: i
+ do i=1,10,2
+ print *, i ! Print odd numbers
+ end do
+```
+
+
+__Example:__ `do while` loop
+
+```fortran
+ integer :: i
+ i = 1
+ do while (i<11)
+ print *, i
+ i = i + 1
+ end do
+```
+
+
+## Procedures
+
+Fortran has two forms of procedure:
+
+- __Subroutine:__ invoked by a `call` statement
+- __Function:__ invoked within an expression or assignment to which it returns a value
+
+Both subroutines and functions have access to variables in the parent scope by _argument association_;
+unless the `VALUE` attribute is specified, this is similar to call by reference.
+
+### Subroutines
+
+
+The subroutine input arguments, known as _dummy arguments_ are specified in parentheses after the subroutine name;
+the dummy argument types and attributes are declared within the body of the subroutine just like local variables.
+
+__Example:__
+
+```fortran
+! Print matrix A to screen
+subroutine print_matrix(n,m,A)
+ implicit none
+ integer, intent(in) :: n
+ integer, intent(in) :: m
+ real, intent(in) :: A(n,m)
+
+ integer :: i
+ do i=1,n
+ print *,A(i,1:m)
+ end do
+
+end subroutine print_matrix
+```
+
+
+Note the additional `intent` attribute when declaring the dummy arguments; this optional attribute signifies to the compiler whether the argument
+is 'read-only' (`intent(in)`) 'write-only' (`intent(out)`) or 'read-write' (`intent(inout)`) within the procedure.
+In this example, the subroutine does not modify its arguments, hence all arguments are `intent(in)`.
+
+{% include tip.html content="It is good practice to always specify the `intent` attribute for
+dummy arguments; this allows the compiler to check for unintentional errors and provides self-documentation." %}
+
+
+We can call this subroutine from a program using a `call` statement:
+```fortran
+program call_sub
+ implicit none
+
+ real :: mat(10,20)
+
+ mat(:,:) = 0.0
+
+ call print_matrix(10,20,mat)
+
+end program call_sub
+```
+
+{% include note.html content="This example uses a so-called _explicit-shape_ array argument since we have passed additional variables to describe
+the dimensions of the array `A`; this will not be necessary if we place our subroutine in a module as described later." %}
+
+
+### Functions
+
+```fortran
+! L2 Norm of a vector
+function vector_norm(n,vec) result(norm)
+ implicit none
+ integer, intent(in) :: n
+ real, intent(in) :: vec(n)
+ real :: norm
+
+ norm = sqrt(sum(vec**2))
+
+end function vector_norm
+```
+
+To execute this function:
+
+```fortran
+program run_fcn
+ implicit none
+
+ real :: v(9)
+ real :: vector_norm
+
+ v(:) = 9
+
+ print *, 'Vector norm = ',vector_norm(9,v)
+
+end program run_fcn
+```
+
+{% include tip.html content="It is good programming practice for functions not to modify their arguments - _i.e._ all function arguments should be `intent(in)` - such
+functions are known as `pure` functions. Use subroutines if your procedure needs to modify its arguments." %}
+
+
+## Modules
+
+Fortran modules contain definitions that are made accessible to programs, procedures and other modules through the `use` statement.
+They can contain data objects, type definitions, procedures and interfaces.
+
+- Modules allow controlled scoping extension whereby entity access is made explicit
+- Modules automatically generate explicit interfaces required for modern procedures
+
+{% include tip.html content="It is recommended to always place functions and subroutines
+within modules." %}
+
+__Example:__
+
+```fortran
+module my_mod
+ implicit none
+
+ private ! All entities are module-private by default
+ public public_var, print_matrix ! Explicitly export public entities
+
+ real, parameter :: public_var = 2
+ integer :: private_var
+
+ contains
+
+ ! Print matrix A to screen
+ subroutine print_matrix(A)
+ real, intent(in) :: A(:,:) ! An assumed-shape dummy argument
+
+ integer :: i
+ do i=1,size(A,1)
+ print *,A(i,:)
+ end do
+
+ end subroutine print_matrix
+
+end module my_mod
+```
+
+{% include note.html content="Compare this `print_matrix` subroutine with [that written outside of a module](#subroutines);
+we no longer have to explicitly pass the matrix dimensions and can instead take
+advantage of _assumed-shape_ arguments since the module will generate the required
+explicit interface for us. This results in a much simpler subroutine interface." %}
+
+To `use` the module within a program:
+```fortran
+program use_mod
+ use my_mod
+ implicit none
+
+ real :: mat(10,10)
+
+ mat(:,:) = public_var
+
+ call print_matrix(mat)
+
+end program use_mod
+```
+
+__Example:__ explicit import list
+
+```fortran
+ use my_mod, only: public_var
+```
+
+__Example:__ aliased import
+
+```fortran
+ use my_mod, only: printMat=>print_matrix
+```
+
+{% include note.html content="Each module should be written in a separate .f90 source file. Modules need to be compiled prior to any program units that `use` them." %}
+
+
+
diff --git a/tutorial.md b/tutorial.md
deleted file mode 100644
index a560b0894..000000000
--- a/tutorial.md
+++ /dev/null
@@ -1,69 +0,0 @@
----
-layout: page
-title: Fortran tutorial
-permalink: /tutorial/
----
-
-This page will include a Fortran tutorial.
-It should be a no-nonsense practical step-by-step guide,
-written in plain language.
-It will include just enough information for a newcomer to Fortran to write
-basic and correct Fortran programs and libraries, without external resources.
-At a later time, we may decide to include more advanced topics like
-parallelism, Fortran OO, or C-interop.
-
-Syntax highlighting doesn't work yet, it's a TODO.
-
-## Get a Fortran compiler
-
-In this tutorial, we'll work with the free and open source
-[GNU Fortran compiler (gfortran)](https://gcc.gnu.org/fortran/),
-which is part of the
-[GNU Compiler Colection (GCC)](https://gcc.gnu.org/).
-
-To install gfortran on Linux, use your system package manager.
-Otherwise, for macOS or Windows, refer to gfortran binaries from
-[this page](https://gcc.gnu.org/install/binaries.html).
-
-## Your first Fortran program
-
-Here's your first Fortran program that prints some text to the terminal:
-
-```fortran
-program hello
- print *, 'Hello, World!'
-end program hello
-```
-
-## Data types
-
-Fortran comes with 5 built-in data types:
-
-* `integer`--for data that represent whole numbers, positive or negative
-* `real`--for floatin-point data
-* `complex`--tuples of real numbers
-* `character`--for text data
-* `logical`--for data that represent boolean (true or false) values
-
-### Declaration
-
-## Arrays
-
-## Procedures
-
-### Functions
-
-Here's a function that returns a cube-root of a real number:
-
-```fortran
-real function cbrt(x)
- real, intent(in) :: x
- cbrt = x**(1. / 3)
-end function cbrt
-```
-
-### Subroutines
-
-## Modules
-
-etc.