Module Dim

module Dim: sig .. end

type t = int 
type change = {
   dim : int array;
   intdim : int;
   realdim : int;
}
type change2 = {
   add : change option;
   remove : change option;
}
type perm = int array 
type dimension = {
   intd : int;
   reald : int;
}

APRON Dimensions and related types

val change_add_invert : change -> unit

Assuming a transformation for add_dimensions, invert it in-place to obtain the inverse transformation using remove_dimensions

val perm_compose : perm -> perm -> perm

perm_compose perm1 perm2 composes the 2 permutations perm1 and perm2 (in this order). The sizes of permutations are supposed to be equal.

val perm_invert : perm -> perm

Invert a permutation