1/* Part of LogicMOO Base An Implementation a MUD server in SWI-Prolog
    2% ===================================================================
    3% File 'multimodal_dcg.pl'
    4% Purpose: An Implementation in SWI-Prolog of certain debugging tools
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: 'logicmoo_util_bugger.pl' 1.0.0
    8% Revision:  $Revision: 1.1 $
    9% Revised At:   $Date: 2002/07/11 21:57:28 $
   10% ===================================================================
   11*/
   12:- module(multimodal_dcg,[
   13         do_dcg_util_tests/0,
   14         isVar/1,
   15         isQVar/1,
   16         isVarOrVAR/1,
   17
   18
   19         dcgOneOrMore//1,
   20         dcgOptional//1,
   21         dcgZeroOrMore//1,
   22         dcgOptionalGreedy//1,
   23         dcgAnd//2,
   24         dcgAnd//3,
   25         dcgAnd//4,
   26         dcgMust//1,
   27         % dumpList/1,
   28         dcgSeqLen//1,
   29         dcgOr//2,
   30         dcgNot//1,
   31         theString//1,
   32         theString//2,
   33         theText//1,
   34         theCode//1,         
   35         dcgLenBetween/4,
   36
   37         % unit test functions
   38         do_dcgTest/3,
   39         do_dcgTest_startsWith/3,
   40         decl_dcgTest_startsWith/2,
   41         decl_dcgTest_startsWith/3,
   42         decl_dcgTest/2,
   43         decl_dcgTest/3,
   44         dcgReorder/4
   45	 ]).   46
   47:- set_module(class(library)).   48
   49:- use_module(library(logicmoo_common)).   50:- reexport(library(logicmoo/dcg_meta)).