Search code examples
recursionocamlfunctor

Extend mutually recursive functors


I am writing a compiler and need to represent several structures that are co recursive and depend on the data-structure representing expressions. At the beginning of compilation my expressions are not typed but I do type them at a later stage.

I wrote the following functors to be able to reuse code during the process:

module type Exp = sig                                                                                                                  
  type t                                                                                                                               
end  

module type IR = sig                                                                                                                    
  type exp                                                                                                                              
  type ty =                                                                                                                             
    | Unknown                                                                                                                           
    | Typed of exp                                                                                                                      
  type exp_descr =                                                                                                                      
    | Leaf                                                                                                                              
    | Node of exp                                                                                                                       
end                                                                                                                                     

module MyIR (E: Exp) = struct                                                                                                           
  type ty =                                                                                                                             
    | Unknown                                                                                                                           
    | Typed of E.t                                                                                                                      

  type exp_descr =
    | Leaf 
    | Node of E.t

  type exp = E.t  
end       

module UntypedExp (TD: IR) : (Exp with type t = TD.exp_descr) = struct
  type t = TD.exp_descr
end                          

module TypedExp (TD: IR) : Exp = struct
  type t =        
    {
      ty : TD.ty; 
      descr : TD.exp_descr;
    }            
end

module rec UTExp : Exp = UntypedExp(UTIR)
and UTIR : IR = MyIR(UTExp)

module rec TExp : Exp = TypedExp(TIR)
and TIR : IR = MyIR(TExp)

I now have 2 intermediate representations one that uses untyped expressions and the other that uses typed expressions.

I now want to write a printing module and I want to factorize code in the same manner as I did earlier. Below is my unsuccessful attempt, I don't understand how properly extend TExp and UTexp. More specifically, I don't know how to share the field constructor defined in TypedExp.

module type ExpPrint = sig             
  type t  
  val string_of_t: t -> string
end              

module type IRPrint = sig
  include IR
  val string_of_ty: ty -> string
  val string_of_exp_descr: exp_descr -> string
  val string_of_exp: exp -> string
end

module MyExpPrint (R: IR) (E: ExpPrint with type t = R.exp) : (IRPrint with type exp := R.exp and type exp_descr := R.exp_descr and type ty := R.ty) = struct
  open R
  let string_of_exp = E.string_of_t
  let string_of_ty = function
    | R.Unknown -> "Unknown"
    |   Typed e -> "Typed: " ^ string_of_exp e

  let string_of_exp_descr = function
    | R.Leaf   -> "Leaf"
    |   Node e -> "Node: " ^ string_of_exp e

end

module UTExpPrint (E : module type of UTExp) (R: IRPrint with type exp = E.t) : (ExpPrint with type t := R.exp_descr) = struct
  open E
  let string_of_t = R.string_of_exp_descr
end

module TExpPrint (E : module type of TExp) (R: IRPrint with type exp = E.t) : (ExpPrint with type t := R.exp) = struct
  open E
  let string_of_t e = R.string_of_exp_descr e.TExp.descr ^ " " ^ R.string_of_ty e.ty
end

EDIT: fixes the problems with MyExpPrint


Solution

  • Since the module type Exp is defined as

     module type Exp = sig type t end
    

    any signature constraint of the form M: Exp makes M unusable since it hides all information about M, except the existence of an abstract type M.t. This abstract type is unusable since there are no functions between this type and the outside world.

    For instance, this module definition defines a type and immediately hides it to the outside world:

    module TypedExp (TD: IR) : Exp = struct
      type t =        
        {
        ty : TD.ty; 
        descr : TD.exp_descr;
       }            
    end
    

    What you wanted was simply

    module TypedExp (TD: IR) = struct
      type t =        
        {
        ty : TD.ty; 
        descr : TD.exp_descr;
       }            
    end
    

    If you really want to add a signature constraint, the right one would be

    module TypedExp (TD: IR): sig
      type t =        
        {
        ty : TD.ty; 
        descr : TD.exp_descr;
       }            
    end
    = struct
      type t =        
        {
        ty : TD.ty; 
        descr : TD.exp_descr;
       }            
    end
    

    Note that that I did not use Exp with type t = ... for two reasons: First, the with constraint cannot define new types. Second, Exp with type t = ... is just a complicated way to write sig type t = ... end.

    This is the core issue with your code: it is hiding all information that would make possible to manipulate meaningfully the type that you defines.

    For instance, after removing the signature constraint on functor result, fixing the signature in the recursive module constraints, simplifying the signature of IRprint to

    module type IRPrint = sig
      type ty
      type exp_descr
      type exp
      val string_of_ty: ty -> string
      val string_of_exp_descr: exp_descr -> string
      val string_of_exp: exp -> string
    end
    

    then the functor TExpPrint can be fixed with

    module TExpPrint
        (E : module type of TExp)
        (R: IRPrint with type exp_descr = TIR.exp_descr
                     and type exp = E.t
                     and type ty = TIR.ty)
    =
    struct
      open E
      let string_of_t e =
        R.string_of_exp_descr e.E.descr ^ " " ^ R.string_of_ty e.ty
    end
    

    and I expect the rest of the errors to follow since it becomes possible to share the right type equalities.