;; ;; NEMO ;; ;; Copyright 2008-2011 Ivan Raikov and the Okinawa Institute of ;; Science and Technology. ;; ;; This program is free software: you can redistribute it and/or ;; modify it under the terms of the GNU General Public License as ;; published by the Free Software Foundation, either version 3 of the ;; License, or (at your option) any later version. ;; ;; This program is distributed in the hope that it will be useful, but ;; WITHOUT ANY WARRANTY; without even the implied warranty of ;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU ;; General Public License for more details. ;; ;; A full copy of the GPL license can be found at ;; . ;; (import scheme chicken srfi-1) (require-extension nemo-core nemo-macros nemo-hh nemo-vclamp) (require-extension matchable ssax sxml-transforms sxpath sxpath-lolevel environments getopt-long) (define nemo-nmodl? (extension-information 'nemo-nmodl)) (define nemo-matlab? (extension-information 'nemo-matlab)) (if nemo-nmodl? (use nemo-nmodl)) (if nemo-matlab? (use nemo-matlab)) (define (lookup-def k lst . rest) (let-optionals rest ((default #f)) (let ((kv (assoc k lst))) (if (not kv) default (match kv ((k v) v) (else (cdr kv))))))) (define ($ x) (and x (string->symbol (->string x)))) ;;; Procedures for string concatenation and pretty-printing (define (s+ . lst) (string-concatenate (map ->string lst))) (define (sw+ lst) (string-intersperse (filter-map (lambda (x) (and x (->string x))) lst) " ")) (define (s\ p . lst) (string-intersperse (map ->string lst) p)) (define (sl\ p lst) (string-intersperse (map ->string lst) p)) (define nl "\n") (define (warn port message . specialising-msgs) (print-error-message message (current-output-port) "Warning") (print (string-concatenate (map ->string specialising-msgs)))) ;;; Error procedure for the XML parser (define (parser-error port message . specialising-msgs) (error (string-append message (string-concatenate (map ->string specialising-msgs))))) (define ssax:warn warn) (define opt-defaults `( (nmodl-kinetic . all) )) (define (defopt x) (lookup-def x opt-defaults)) (define opt-grammar `( (input-format "specify input format (nemo, xml, sxml, s-exp)" (single-char #\i) (value (required FORMAT) (transformer ,string->symbol))) (xml "write XML output to file (default: .xml)" (value (optional FILENAME) )) (sxml "write SXML output to file (default: .sxml)" (value (optional FILENAME) )) ,@(if nemo-matlab? `((matlab "write MATLAB output") (octave "write Octave output to given file (default: .m)" (value (optional FILENAME))) (octave-method "specify Octave integration method (lsode or odepkg)" (value (required METHOD) (transformer ,string->symbol))) ) `()) ,@(if nemo-nmodl? `( (nmodl "write NMODL output to file (default: .mod)" (value (optional FILENAME))) (nmodl-kinetic ,(s+ "use NMODL kinetic equations for the given reactions " "(or for all reactions)") (value (optional STATES) (default ,(defopt 'nmodl-kinetic)) (transformer ,(lambda (x) (if (string=? x "all") 'all (map string->symbol (string-split x ","))))))) (nmodl-method "specify NMODL integration method" (value (required METHOD) (transformer ,string->symbol))) (nmodl-depend "specify DEPEND variables for NMODL interpolation tables" (value (required VARS) (transformer ,(lambda (x) (map string->symbol (string-split x ",")))))) ) `()) (vclamp-hoc "write voltage clamp scripts to HOC file (default: .(ses|hoc))" (value (optional FILENAME) )) (vclamp-octave "write voltage clamp script to Octave file (default: _vclamp.m)" (value (optional FILENAME) )) (t "use interpolation tables in generated code, if possible") (help (single-char #\h)) )) ;; Use args:usage to generate a formatted list of options (from OPTS), ;; suitable for embedding into help text. (define (nemo:usage) (print "Usage: " (car (argv)) " [options...] ") (newline) (print "The following options are recognized: ") (newline) (print (parameterize ((indent 5) (width 30)) (usage opt-grammar))) (exit 1)) ;; Process arguments and collate options and arguments into OPTIONS ;; alist, and operands (filenames) into OPERANDS. You can handle ;; options as they are processed, or afterwards. (define opts (getopt-long (command-line-arguments) opt-grammar)) (define opt (make-option-dispatch opts opt-grammar)) (define (ncml:sxpath query doc) ((sxpath query '((ncml . "ncml"))) doc)) (define (ncml:car-sxpath query doc) (let ((lst ((sxpath query '((ncml . "ncml") )) doc))) (car lst))) (define (ncml:if-car-sxpath query doc) (let ((lst ((sxpath query '((ncml . "ncml") )) doc))) (and (not (null? lst)) (car lst)))) (define (ncml:if-sxpath query doc) (let ((lst ((sxpath query '((ncml . "ncml") )) doc))) (and (not (null? lst)) lst))) (define (ncml-binding->binding node) (match node (('ncml:bnd ('@ ('id id)) ('ncml:expr expr)) `(,($ id) ,(ncml-expr->expr expr))) (else (error 'ncml-binding->binding "invalid binding " node)))) (define (ncml-expr->expr node) (match node ((? number?) node) ((? string?) (sxml:number node)) (('ncml:id id) ($ id)) (('ncml:apply ('@ ('id id)) . args) (cons ($ id) (map ncml-expr->expr args))) (('ncml:let ('ncml:bnds . bnds) ('ncml:expr body)) `(let ,(map ncml-binding->binding bnds) ,(ncml-expr->expr body))) (((and op (? symbol?)) . args) (cons (ncml-op->op op) (map ncml-expr->expr args))) (else (error 'ncml-expr->expr "unknown expression " node)))) (define (ncml-op->op op) (case op ((ncml:sum) '+) ((ncml:sub) '-) ((ncml:mul) '*) ((ncml:div) '/) ((ncml:gt) '>) ((ncml:lt) '<) ((ncml:lte) '<=) ((ncml:gte) '>=) ((ncml:eq) '=) (else (match (string-split (->string op) ":") ((pre op) (string->symbol op)) (else (error 'ncml-op->op "invalid operator" op)))))) (define (nemo-constructor name declarations parse-expr) (let* ((nemo (make-nemo-core)) (sys ((nemo 'system) name)) (qs (eval-nemo-system-decls nemo name sys declarations parse-expr))) (list sys nemo qs))) (define (sexp->model options doc parse-expr) (match doc (('nemo-model model-name model-decls) (let* ((model+nemo (nemo-constructor model-name model-decls parse-expr)) (model (first model+nemo)) (nemo (second model+nemo))) (let ((model-1 (nemo:hh-transformer model parse-expr))) (if (assoc 'depgraph options) (print "dependency graph: " ((nemo 'depgraph*) model-1))) (if (assoc 'exports options) (print "exports: " ((nemo 'exports) model-1))) (if (assoc 'imports options) (print "imports: " ((nemo 'imports) model-1))) (if (assoc 'components options) (for-each (lambda (x) (print "component " x ": " ((nemo 'component-exports) model-1 (second x))) (print "component " x " subcomponents: " ((nemo 'component-subcomps) model-1 (second x)))) ((nemo 'components) model-1))) model-1))) (else (error 'sexp->model "unknown model format")))) (define model->nmodl (if nemo-nmodl? (lambda (options model) (nemo:nmodl-translator model (lookup-def 'method options) (lookup-def 'table options) -150 150 1 (lookup-def 'depend options) (lookup-def 'kinetic options) )) (lambda (options model) (void)))) (define model->matlab (if nemo-matlab? (lambda (options model) (nemo:matlab-translator model)) (lambda (options model) (void)))) (define model->vclamp-hoc (lambda (options model) (nemo:vclamp-translator model 'hoc (lookup-def 'filename options)))) (define model->vclamp-octave (lambda (options model) (nemo:vclamp-translator model 'matlab (lookup-def 'filename options)))) (define model->octave (if nemo-matlab? (lambda (options model) (nemo:octave-translator model (lookup-def 'method options) (lookup-def 'filename options))) (lambda (options model) (void)))) (define (transition->ncml-transition x) (match x (('-> src dst rate) `((ncml:transition (@ (src ,src) (dst ,dst)) (ncml:rate ,(expr->ncml-expr rate))))) ((src '-> dst rate) `((ncml:transition (@ (src ,src) (dst ,dst)) (ncml:rate ,(expr->ncml-expr rate))))) (('<-> src dst rate1 rate2) `((ncml:transition (@ (src ,src) (dst ,dst)) (ncml:rate ,(expr->ncml-expr rate1))) (ncml:transition (@ (src ,dst) (dst ,src)) (ncml:rate ,(expr->ncml-expr rate2))))) ((src '<-> dst rate1 rate2) `((ncml:transition (@ (src ,src) (dst ,dst)) (ncml:rate ,(expr->ncml-expr rate1))) (ncml:transition (@ (src ,dst) (dst ,src)) (ncml:rate ,(expr->ncml-expr rate2))))) (else (error 'transition->ncml-transition "invalid transition " x)))) (define (conseq->ncml-conseq parse-expr) (lambda (x) (match x (((and i (? integer?)) '= rhs) `(ncml:conseq (@ (val ,(->string i))) (ncml:expr ,(expr->ncml-expr (parse-expr rhs))))) (else (error 'conseq->ncml-conseq "invalid linear equation " x))))) (define builtin-fns `(+ - * / pow neg abs atan asin acos sin cos exp ln sqrt tan cosh sinh tanh hypot gamma lgamma log10 log2 log1p ldexp cube > < <= >= = and or round ceiling floor max min)) (define (binding->ncml-binding bnd) (match bnd ((id expr) `(ncml:bnd (@ (id ,id)) (ncml:expr ,(expr->ncml-expr expr)))) (else (error 'binding->ncml-binding "invalid binding " bnd)))) (define (expr->ncml-expr x) (match x ((? number?) x) ((? symbol?) `(ncml:id ,x)) (('let bnds expr) `(ncml:let (ncml:bnds . ,(map binding->ncml-binding bnds)) (ncml:expr ,(expr->ncml-expr expr)))) (((and op (? symbol?)) . args) (let ((ncml-expr (if (member op builtin-fns) (cons (op->ncml-op op) (map expr->ncml-expr args)) `(ncml:apply (@ (id ,op)) ,@(map expr->ncml-expr args))))) ncml-expr)) (else (error 'expr->ncml-expr "unknown expression " x)))) (define (op->ncml-op op) (case op ((+) 'ncml:sum) ((-) 'ncml:sub) ((*) 'ncml:mul) ((/) 'ncml:div) ((>) 'ncml:gt) ((<) 'ncml:lt) ((<=) 'ncml:lte) ((>=) 'ncml:gte) ((=) 'ncml:eq) (else (string->symbol (string-append "ncml:" (->string op)))))) (define (declaration->ncml parse-expr) (lambda (x) (match x (((or 'input 'INPUT) . lst) (map (lambda (x) (match x ((? symbol?) `(ncml:input (@ id ,(->string x)))) ((id1 (or 'as 'AS) x1) `(ncml:input (@ (id ,(->string id1)) (as ,(->string x1))))) ((id1 (or 'from 'FROM) n1) `(ncml:input (@ (id ,(->string id1)) (from ,(->string n1))))) ((id1 (or 'as 'AS) x1 (or 'from 'FROM) n1) `(ncml:input (@ (id ,(->string id1)) (as ,(->string x1)) (from ,(->string n1))))))) lst)) (((or 'output 'OUTPUT) . (and lst (? (lambda (x) (every symbol? x))))) (map (lambda (x) `(ncml:output (@ (id ,(->string x))))) lst)) (((or 'const 'CONST) (and id (? symbol?)) '= expr) `(ncml:const (@ (id ,(->string id))) (ncml:expr ,(expr->ncml-expr (parse-expr expr))))) (((or 'reaction 'REACTION) ((and id (? symbol?)) . alst) ) (let ((trs (lookup-def 'transitions alst)) (initial (lookup-def 'initial alst)) (open (lookup-def 'open alst)) (cons (lookup-def 'conserve alst)) (p (lookup-def 'power alst))) (let ((sxml-trs (append-map transition->ncml-transition trs))) `(ncml:reaction (@ (id ,(->string id))) (ncml:open ,open) ,(and initial `(ncml:initial ,(expr->ncml-expr (parse-expr initial))) ) ,(and cons `(ncml:conserve ,((conseq->ncml-conseq parse-expr) cons)) ) (ncml:transitions ,@sxml-trs) (ncml:power ,(expr->ncml-expr (parse-expr p))))))) (((or 'd 'D) ((and id (? symbol?))) '= expr . rest) (let ((initial (lookup-def 'initial rest))) `(ncml:rate (@ (id ,(->string id)) ) ,(and initial `(ncml:initial ,(expr->ncml-expr (parse-expr initial)))) (ncml:expr ,(expr->ncml-expr (parse-expr expr)))))) (((and id (? symbol?)) '= expr) `(ncml:asgn (@ (id ,id)) (ncml:expr ,(expr->ncml-expr (parse-expr expr))))) (((or 'defun 'DEFUN) (and id (? symbol?)) (and idlist (? (lambda (x) (every symbol? x)))) expr) `(ncml:defun (@ (id ,x)) ,@(map (lambda (v) `(ncml:arg ,(->string v))) idlist) (ncml:body ,(expr->ncml-expr (parse-expr expr))))) (((or 'component 'COMPONENT) ((or 'type 'TYPE) typ) ((or 'name 'NAME) name) . lst) `(ncml:component (@ (name ,(->string name)) (type ,(->string typ))) ,@(map (declaration->ncml parse-expr) lst))) (((or 'component 'COMPONENT) ((or 'type 'TYPE) typ) . lst) `(ncml:component (@ (type ,(->string typ))) ,@(map (declaration->ncml parse-expr) lst))) (((or 'component 'COMPONENT) ((or 'name 'NAME) name) '= (and functor-name (? symbol?)) (and args (? list?))) `(ncml:component (@ (name ,(->string name)) (functor-name ,(->string functor-name))) ,@(map (declaration->ncml parse-expr) lst))) ))) (define (make-component->ncml dis model parse-expr) (lambda (x) (let ((en (environment-ref model x))) (cond ((procedure? en) (let ((fd (procedure-data en))) `(ncml:defun (@ (id ,x)) ,@(map (lambda (v) `(ncml:arg ,v)) (lookup-def 'vars fd)) (ncml:body ,(expr->ncml-expr (lookup-def 'body fd)))))) (else (match en (($ nemo:quantity 'EXTERNAL local-name name namespace) (if namespace `(ncml:input (@ (id ,name)) (as ,local-name) (from ,namespace)) `(ncml:input (@ (id ,name)) (as ,local-name)))) (($ nemo:quantity 'CONST name value) `(ncml:const (@ (id ,name)) (ncml:expr ,value))) (($ nemo:quantity 'ASGN name value rhs) (let ((expr (expr->ncml-expr rhs))) `(ncml:asgn (@ (id ,name)) (ncml:expr ,expr)))) (($ nemo:quantity 'RATE name initial rhs) (let ((expr (expr->ncml-expr rhs)) (initial (and initial (expr->ncml-expr initial)))) `(ncml:rate (@ (id ,name)) ,(and initial `(ncml:initial ,initial)) (ncml:expr ,expr)))) (($ nemo:quantity 'REACTION name initial open trs cons p) (let ((sxml-trs (append-map transition->ncml-transition trs))) `(ncml:reaction (@ (id ,name)) (ncml:open ,open) ,(and initial `(ncml:initial ,(expr->ncml-expr initial))) ,(and cons `(ncml:conserve ,(map (conseq->ncml-conseq identity) cons)) ) (ncml:transitions ,@sxml-trs) (ncml:power ,(expr->ncml-expr p))))) (($ nemo:quantity 'COMPONENT name type lst) (let ((component->ncml (make-component->ncml dis model parse-expr)) (component-exports ((dis 'component-exports) model x))) (case type ((toplevel) `(,@(map component->ncml lst) ,@(map (lambda (x) `(ncml:output (@ (id ,x)))) component-exports))) (else `(ncml:component (@ (name ,name) (type ,type)) ,@(filter-map component->ncml lst) ,@(map (lambda (x) `(ncml:output (@ (id ,x)))) component-exports) ))))) (($ nemo:quantity 'FUNCTOR name args type lst) (let ((component->ncml (make-component->ncml dis model parse-expr))) `(ncml:functor (@ (name ,name) (type ,type) (parameters ,(string-intersperse (map ->string args) ","))) ,@(filter-map (declaration->ncml parse-expr) lst) ))) (else #f))))))) (define (model->ncml model parse-expr) (match-let ((($ nemo:quantity 'DISPATCH dis) (environment-ref model (nemo-intern 'dispatch)))) (let ((sysname ((dis 'sysname) model)) (component->ncml (make-component->ncml dis model parse-expr))) `(ncml:model (@ (name ,sysname)) ,@(component->ncml (nemo-intern 'toplevel)))))) (include "expr-parser.scm") (include "SXML.scm") (include "SXML-to-XML.scm") (include "stx-engine.scm") (define null-template `(*default* ,(lambda (node bindings root env) (begin (warn "Unrecognized input element:" node) '())))) (define-syntax sxml:make-null-ss (syntax-rules () ((stx rule ...) (list ; default handler null-template ; handler for textual nodes (list '*text* (lambda (text) text)) rule ...)))) (define (ensure-xmlns doc) (let ((doc1 (sxml:add-attr doc '(xmlns:ncml "ncml")))) (sxml:add-attr doc1 '(xmlns ncml)))) ;; based on SRV:send-reply by Oleg Kiselyov (define (print-fragments b) (let loop ((fragments b) (result #f)) (cond ((null? fragments) result) ((not (car fragments)) (loop (cdr fragments) result)) ((null? (car fragments)) (loop (cdr fragments) result)) ((eq? #t (car fragments)) (loop (cdr fragments) #t)) ((pair? (car fragments)) (loop (cdr fragments) (loop (car fragments) result))) ((procedure? (car fragments)) ((car fragments)) (loop (cdr fragments) #t)) (else (display (car fragments)) (loop (cdr fragments) #t))))) (define (ncml->declarations ncml:model) (letrec ((input-template (sxml:match 'ncml:input (lambda (node bindings root env) (let ((id (sxml:attr node 'id)) (from (sxml:kidn* 'ncml:from node)) (as (sxml:kidn* 'ncml:as node))) (if (not id) (error 'input-template "input declaration requires id attribute")) (cond ((and from as) `(input (,($ id) as ,($ (second as) ) from ,($ (second from)) ))) (from `(input (,($ id) from ,($ (second from))))) (as `(input (,($ id) as ,($ (second as))))) (else `(input ,($ id)))))))) (output-template (sxml:match 'ncml:output (lambda (node bindings root env) (let ((id (sxml:attr node 'id))) (if (not id) (error 'output-template "output declaration requires id attribute")) `(output ,($ id)))))) (const-template (sxml:match 'ncml:const (lambda (node bindings root env) (let* ((id (sxml:attr node 'id)) (expr ((lambda (x) (if (not x) (error 'const-template "const declaration " id " requires expr element") (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:expr node)))) (if (not id) (error 'const-template "const declaration requires id attribute")) `(const ,($ id) = ,expr))))) (reaction-transition-template (sxml:match 'ncml:transition (lambda (node bindings root env) (let ((src (sxml:attr node 'src)) (dst (sxml:attr node 'dst)) (rate ((lambda (x) (if (not x) (error 'reaction-transition-template "reaction transition requires rate element") (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:rate node)))) (if (not src) (error 'reaction-transition-template "reaction transition requires src attribute")) (if (not dst) (error 'reaction-transition-template "reaction transition requires dst attribute")) `(-> ,($ src) ,($ dst) ,rate))))) (asgn-template (sxml:match 'ncml:asgn (lambda (node bindings root env) (let ((id (sxml:attr node 'id)) (expr ((lambda (x) (if (not x) (error 'asgn-template "algebraic assignment requires expr element") (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:expr node)))) (if (not id) (error 'asgn-template "algebraic assignment requires id attribute")) `(,($ id) = ,expr))))) (rate-template (sxml:match 'ncml:rate (lambda (node bindings root env) (let ((id (sxml:attr node 'id)) (rhs ((lambda (x) (if (not x) (error 'rate-template "rate equation requires expr element") (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:expr node))) (initial ((lambda (x) (and x (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:initial node)))) (if (not id) (error 'rate-template "rate equation requires id attribute")) `(d (,($ id)) = ,rhs ,(and initial `(initial ,initial) )))))) (conseq-template (sxml:match 'ncml:conseq (lambda (node bindings root env) (let ((val (string->number (->string (sxml:attr node 'val)))) (rhs ((lambda (x) (if (not x) (error 'conseq-template "conseq definition requires expr element") (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:expr node)))) `(,val = ,rhs))))) (reaction-template (sxml:match 'ncml:reaction (lambda (node bindings root env) (let* ((id ($ (sxml:attr node 'id))) (initial ((lambda (x) (and x (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:initial node))) (open ((lambda (x) (if (not x) (error 'reaction-template "reaction declaration requires open element") ($ (second x)))) (sxml:kidn* 'ncml:open node))) (conserve ((lambda (x) (and x (let ((tmpl (sxml:make-null-ss conseq-template))) (stx:apply-templates (second x) tmpl root env)))) (sxml:kidn* 'ncml:conserve node))) (power ((lambda (x) (if (not x) (error 'reaction-template "reaction declaration requires open element") (sxml:number (second x)))) (sxml:kidn* 'ncml:power node))) (transitions ((lambda (x) (if (not x) (error 'reaction-template "reaction declaration requires transitions element") (let ((tmpl (sxml:make-null-ss reaction-transition-template))) (stx:apply-templates (cdr x) tmpl root env)))) (sxml:kidn* 'ncml:transitions node))) ) (if (not id) (error 'reaction-template "reaction transition requires id attribute")) `(reaction (,id (initial ,initial) (open ,open) (power ,power) ,(and conserve `(conserve ,conserve) ) (transitions ,@transitions))))))) (defun-template (sxml:match 'ncml:defun (lambda (node bindings root env) (let ((id (sxml:attr node 'id)) (args ((lambda (x) (if (null? x) (error 'defun-template "function definition requires at least one arg element") (map (compose $ second) x))) (sxml:kidsn 'ncml:arg node))) (body ((lambda (x) (if (not x) (error 'defun-template "function definition requires body element") (ncml-expr->expr (second x)))) (sxml:kidn* 'ncml:body node)))) (if (not id) (error 'defun-template "function definition requires id attribute")) `(defun ,($ id) ,args ,body))))) (component-template (sxml:match 'ncml:component (lambda (node bindings root env) (let ((name (sxml:attr node 'name)) (functor-name (sxml:attr node 'functor-name)) (type (sxml:attr node 'type))) (if (not type) (error 'component-template "component definition requires type attribute")) (if name `(component (type ,($ type)) (name ,($ name)) ,@(ncml->declarations (sxml:kids node))) (if functor-name `(component (name ,($ name)) = ,functor-name ,(ncml->declarations (sxml:kids node))) `(component (type ,($ type)) ,@(ncml->declarations (sxml:kids node))))))))) (functor-template (sxml:match 'ncml:functor (lambda (node bindings root env) (let ((parameters (sxml:attr node 'parameters)) (name (sxml:attr node 'name)) (type (sxml:attr node 'type))) (if (not type) (error 'functor-template "functor definition requires type attribute")) (if (not name) (error 'functor-template "functor definition requires name attribute")) (if (not parameters) (error 'functor-template "functor definition requires parameters attribute")) `(functor (type ,($ type)) (name ,($ name)) (args ,(map string->symbol (string-split parameters ","))) ,@(ncml->declarations (sxml:kids node))))))) (hh-template (sxml:match 'ncml:hh_ionic_conductance (lambda (node bindings root env) (let* ((or-expr (lambda (x) (and x (ncml-expr->expr (second x))))) (id (sxml:attr node 'id)) (initial_m (or-expr (sxml:kidn* 'ncml:initial_m node))) (initial_h (or-expr (sxml:kidn* 'ncml:initial_h node))) (m_power (or-expr (sxml:kidn* 'ncml:m_power node))) (h_power (or-expr (sxml:kidn* 'ncml:h_power node))) (m_alpha (or-expr (sxml:kidn* 'ncml:m_alpha node))) (m_beta (or-expr (sxml:kidn* 'ncml:m_beta node))) (h_alpha (or-expr (sxml:kidn* 'ncml:h_alpha node))) (h_beta (or-expr (sxml:kidn* 'ncml:h_beta node))) (m_tau (or-expr (sxml:kidn* 'ncml:m_tau node))) (m_inf (or-expr (sxml:kidn* 'ncml:m_inf node))) (h_tau (or-expr (sxml:kidn* 'ncml:h_tau node))) (h_inf (or-expr (sxml:kidn* 'ncml:h_inf node)))) (if (not id) (error 'hh-template "hh ionic conductance definition requires id attribute")) `(hh-ionic-gate (,($ id) ,@(if initial_m `((initial-m ,initial_m)) `()) ,@(if initial_h `((initial-h ,initial_h)) `()) ,@(if m_power `((m-power ,m_power)) '()) ,@(if h_power `((h-power ,h_power)) '()) ,@(if m_alpha `((m-alpha ,m_alpha)) '()) ,@(if h_alpha `((h-alpha ,h_alpha)) '()) ,@(if m_beta `((m-beta ,m_beta)) '()) ,@(if h_beta `((h-beta ,h_beta)) '()) ,@(if m_inf `((m-inf ,m_inf)) '()) ,@(if h_inf `((h-inf ,h_inf)) '()) ,@(if m_tau `((m-tau ,m_tau)) '()) ,@(if h_tau `((h-tau ,h_tau)) '()) )))))) (decaying-pool-template (sxml:match 'ncml:decaying_pool (lambda (node bindings root env) (let* ((or-expr (lambda (x) (and x (ncml-expr->expr (second x))))) (id (sxml:attr node 'id)) (initial (or-expr (sxml:kidn* 'ncml:initial node))) (beta (or-expr (sxml:kidn* 'ncml:beta node))) (depth (or-expr (sxml:kidn* 'ncml:depth node))) (temp-adj (or-expr (sxml:kidn* 'ncml:temp_adj node)))) (if (not id) (error 'decaying-pool-template "decaying pool definition requires id attribute")) (if (not initial) (error 'decaying-pool-template "decaying pool definition requires initial value")) (if (not beta) (error 'decaying-pool-template "decaying pool definition requires beta parameter")) (if (not depth) (error 'decaying-pool-template "decaying pool definition requires depth parameter")) `(decaying-pool (,($ id) ,@(if temp_adj `((temp_adj ,temp_adj)) `()) (beta ,beta) (depth ,depth) (initial ,initial))))))) ) (stx:apply-templates ncml:model (sxml:make-null-ss input-template output-template const-template asgn-template rate-template reaction-template defun-template component-template functor-template hh-template decaying-pool-template) ncml:model (list)))) (define (ncml->model options doc) (let* ((ncml:model ((lambda (x) (if (null? x) (error 'ncml->model "ncml:model element not found in input document") (car x))) (ncml:sxpath '(// ncml:model) `(*TOP* . ,doc)))) (model-name (sxml:attr ncml:model 'name)) (model-decls (ncml->declarations (sxml:kids ncml:model)))) (let* ((model+nemo (nemo-constructor model-name model-decls (lambda (x . rest) (identity x)))) (model (first model+nemo)) (nemo (second model+nemo))) (let ((model-1 (nemo:hh-transformer model identity))) (if (assoc 'depgraph options) (print "dependency graph: " ((nemo 'depgraph*) model-1))) (if (assoc 'exports options) (print "exports: " ((nemo 'exports) model-1))) (if (assoc 'imports options) (print "imports: " ((nemo 'imports) model-1))) (if (assoc 'components options) (for-each (lambda (x) (print "component " x ": " ((nemo 'component-exports) model-1 (second x))) (print "component " x " subcomponents: " ((nemo 'component-subcomps) model-1 (second x)))) ((nemo 'components) model-1))) model-1)))) (define (main opt operands) (if (null? operands) (nemo:usage) (for-each (lambda (operand) (let* ((read-xml (lambda (name) (call-with-input-file name (lambda (port) (ssax:xml->sxml port '((ncml . "ncml")))) ))) (read-sexp (lambda (name) (call-with-input-file name read))) (in-format (cond ((opt 'input-format) => (lambda (x) (case x ((nemo) 'nemo) ((s-exp sexp) 'sexp) ((sxml) 'sxml) ((xml) 'xml) (else (error 'nemo "unknown input format" x))))) (else (case ((lambda (x) (or (not x) ($ x))) (pathname-extension operand)) ((s-exp sexp) 'sexp) ((sxml) 'sxml) ((xml) 'xml) (else 'nemo))))) (doc (case in-format ((nemo sxml s-exp sexp) (read-sexp operand)) ((xml) (read-xml operand)) (else (error 'nemo "unknown input format" in-format)))) (parse-expr (case in-format ((sxml xml) identity) ((s-exp sexp) identity) ((nemo) nemo:parse-sym-expr) (else (error 'nemo "unknown input format" in-format)))) (model (case in-format ((sxml xml) (ncml->model '() doc)) ((s-exp sexp) (sexp->model '() doc parse-expr)) ((nemo) (sexp->model '() doc parse-expr)) (else (error 'nemo "unknown input format" in-format)))) (make-fname (lambda (operand x suffix) (and x (let ((fname (pathname-strip-extension operand))) (if (string? x) x (s+ fname suffix)))))) (sxml-fname (make-fname operand (opt 'sxml) ".sxml")) (xml-fname (make-fname operand (opt 'xml) ".xml")) (mod-fname (make-fname operand (opt 'nmodl) ".mod")) (octave-fname (and (string? (opt 'octave)) (make-fname operand (opt 'octave) ".m") )) (vclamp-ses-fname (make-fname operand (opt 'vclamp-hoc) ".ses")) (vclamp-octave-fname (make-fname operand (opt 'vclamp-octave) "_vclamp.m")) (matlab (opt 'matlab)) (octave (opt 'octave)) (vclamp-hoc (opt 'vclamp-hoc)) (vclamp-octave (opt 'vclamp-octave)) (nmodl-depend (opt 'nmodl-depend)) (nmodl-method (let ((method ($ (opt 'nmodl-method) ))) (case method ((adams runge euler adeuler heun adrunge gear newton simplex simeq seidel sparse derivimplicit cnexp clsoda after_cvode cvode_t cvode_t_v expeuler #f) method) (else (error "unknown nmodl-method " method))))) (octave-method (let ((method ($ (opt 'octave-method) ))) (case method ((lsode odepkg #f) method) (else (error "unknown octave method " method))))) ) (if sxml-fname (with-output-to-file sxml-fname (lambda () (pretty-print (model->ncml model parse-expr))))) (if xml-fname (let* ((doc (model->ncml model parse-expr)) (doc1 (ensure-xmlns (cond ((eq? (car doc) '*TOP*) (assoc 'ncml:model (cdr doc))) (else doc))))) (with-output-to-file xml-fname (lambda () (print-fragments (generate-XML `(begin ,doc1))))))) (if mod-fname (with-output-to-file mod-fname (lambda () (model->nmodl `((depend . ,nmodl-depend) (method . ,nmodl-method) (table . ,(opt 't)) (kinetic . ,(opt 'nmodl-kinetic))) model)))) (if octave (model->octave `((filename . ,octave-fname) (method . ,octave-method)) model)) (if matlab (model->matlab `() model)) (if vclamp-hoc (model->vclamp-hoc `((filename . ,vclamp-ses-fname) ) model)) (if vclamp-octave (model->vclamp-octave `((filename . ,vclamp-octave-fname) ) model)) )) operands))) (main opt (opt '@))