CVode and at_time problem

Anything that doesn't fit elsewhere.
Post Reply
crepatas
Posts: 6
Joined: Wed Mar 15, 2006 10:26 am

CVode and at_time problem

Post by crepatas »

I am using the Kampa release.mod file. It seems I am introducing some bugs so that the variable time step will not work correctly. If I use any delay other than zero NEURON will miss the release completely.

I added the code which work correctly with fixed time steps, but does not with variable step.

Thanks for nay help.
Crepatas

release.mod

Code: Select all

TITLE transmitter release

COMMENT
-----------------------------------------------------------------------------

 
   References:

   Destexhe, A., Mainen, Z.F. and Sejnowski, T.J. Synthesis of models for
   excitable membranes, synaptic transmission and neuromodulation using a 
   common kinetic formalism, Journal of Computational Neuroscience 1: 
   195-230, 1994.

   Destexhe, A., Mainen, Z.F. and Sejnowski, T.J.  Kinetic models of 
   synaptic transmission.  In: Methods in Neuronal Modeling (2nd edition; 
   edited by Koch, C. and Segev, I.), MIT press, Cambridge, 1996.

  Written by Bjoern Kampa, 2004

-----------------------------------------------------------------------------
ENDCOMMENT


INDEPENDENT {t FROM 0 TO 1 WITH 1 (ms)}

NEURON {
	SUFFIX rel
	RANGE T, del, dur, amp
}

UNITS {
	(mM) = (milli/liter)
}

PARAMETER {
	del (ms)
	dur (ms)	<0,1e9>
	amp (mM)
}

ASSIGNED { T (mM)
}


INITIAL {
	T = 0
}

BREAKPOINT {
	at_time(del)
	at_time(del+dur)

	
	if (t < del + dur && t > del) {
		:T = amp*exp(-3.14*(t-del))
		T=amp
		
	}else{
		T = 0
	}
}


nmda5.mod

Code: Select all

TITLE detailed model of glutamate NMDA receptors

COMMENT
-----------------------------------------------------------------------------

	Kinetic model of NMDA receptors
	===============================

	5-state gating model:
	Clements & Westbrook 1991. Neuron 7: 605.
	Lester & Jahr 1992. J Neurosci 12: 635.
	Edmonds & Colquhoun 1992. Proc. R. Soc. Lond. B 250: 279.
	Hessler, Shirke & Malinow. 1993. Nature 366: 569.
	Clements et al. 1992. Science 258: 1498.
  
	C -- C1 -- C2 -- O
	           |
      	           D

	Voltage dependence of Mg2+ block:
	Jahr & Stevens 1990. J Neurosci 10: 1830.
	Jahr & Stevens 1990. J Neurosci 10: 3178.

-----------------------------------------------------------------------------

  Based on voltage-clamp recordings of NMDA receptor-mediated currents in rat
  hippocampal slices (Hessler et al., Nature 366: 569-572, 1993), this model 
  was fit directly to experimental recordings in order to obtain the optimal
  values for the parameters (see Destexhe, Mainen and Sejnowski, 1996).

-----------------------------------------------------------------------------

  This mod file does not include mechanisms for the release and time course
  of transmitter; it is to be used in conjunction with a sepearate mechanism
  to describe the release of transmitter and that provides the concentration
  of transmitter in the synaptic cleft (to be connected to pointer C here).

-----------------------------------------------------------------------------

  See details in:

  Destexhe, A., Mainen, Z.F. and Sejnowski, T.J.  Kinetic models of 
  synaptic transmission.  In: Methods in Neuronal Modeling (2nd edition; 
  edited by Koch, C. and Segev, I.), MIT press, Cambridge, 1998, pp 1-25.

  (electronic copy available at http://cns.iaf.cnrs-gif.fr)


  Written by Alain Destexhe and Zach Mainen, 1995

-----------------------------------------------------------------------------
ENDCOMMENT

INDEPENDENT {t FROM 0 TO 1 WITH 1 (ms)}

NEURON {
	POINT_PROCESS NMDA5
	POINTER C
	RANGE C0, C1, C2, D, O, B
	RANGE g, gmax, rb
	GLOBAL Erev, mg, Rb, Ru, Rd, Rr, Ro, Rc
	GLOBAL vmin, vmax
	NONSPECIFIC_CURRENT i
}

UNITS {
	(nA) = (nanoamp)
	(mV) = (millivolt)
	(pS) = (picosiemens)
	(umho) = (micromho)
	(mM) = (milli/liter)
	(uM) = (micro/liter)
}

PARAMETER {

	Erev	= 0    (mV)	: reversal potential
	gmax	= 500  (pS)	: maximal conductance
	mg	= 0    (mM)	: external magnesium concentration
	vmin = -120	(mV)
	vmax = 100	(mV)
	
: Rates

	: Destexhe, Mainen & Sejnowski, 1996
	Rb	= 5e-3    (/uM /ms)	: binding 		
	Ru	= 12.9e-3  (/ms)	: unbinding		
	Rd	= 8.4e-3   (/ms)	: desensitization
	Rr	= 6.8e-3   (/ms)	: resensitization 
	Ro	= 46.5e-3   (/ms)	: opening
	Rc	= 73.8e-3   (/ms)	: closing
}

ASSIGNED {
	v		(mV)		: postsynaptic voltage
	i 		(nA)		: current = g*(v - Erev)
	g 		(pS)		: conductance
	C 		(mM)		: pointer to glutamate concentration

	rb		(/ms)    : binding
}

STATE {
	: Channel states (all fractions)
	C0		: unbound
	C1		: single bound
	C2		: double bound
	D		: desensitized
	O		: open
	B		: fraction free of Mg2+ block
}

INITIAL {
	rates(v)
	C0 = 1
}

BREAKPOINT {
	rates(v)
	SOLVE kstates METHOD sparse

	g = gmax * O * B
	i = (1e-6) * g * (v - Erev)
}

KINETIC kstates {
	
	rb = Rb * (1e3) * C 

	~ C0 <-> C1	(rb,Ru)
	~ C1 <-> C2	(rb,Ru)
	~ C2 <-> D	(Rd,Rr)
	~ C2 <-> O	(Ro,Rc)

	CONSERVE C0+C1+C2+D+O = 1
}

PROCEDURE rates(v(mV)) {
	TABLE B
	DEPEND mg
	FROM vmin TO vmax WITH 200

	: from Jahr & Stevens

	B = 1 / (1 + exp(0.062 (/mV) * -v) * (mg / 3.57 (mM)))
}
nmda5.hoc

Code: Select all

/*----------------------------------------------------------------------------

	Detailed kinetic synapse mechanism
	----------------------------------

	Demo file to show the behavior of a synaptic currents mediated by
	glutamate NMDA receptors, using a detailed kinetic model of these
	receptors and a kinetic model for the release of transmitter.

	Kinetic model from Clements & Westbrook, Neuron 7: 605, 1991.


  See details in:

  Destexhe, A., Mainen, Z.F. and Sejnowski, T.J.  Kinetic models of 
  synaptic transmission.  In: Methods in Neuronal Modeling (2nd edition; 
  edited by Koch, C. and Segev, I.), MIT press, Cambridge, 1998, pp. 1-25.

  (electronic copy available at http://cns.iaf.cnrs-gif.fr)


  Written by Alain Destexhe, Laval University, 1995

----------------------------------------------------------------------------*/



//----------------------------------------------------------------------------
//  load and define general graphical procedures
//----------------------------------------------------------------------------

xopen("$(NEURONHOME)/lib/hoc/stdrun.hoc")

objectvar g[20]			// max 20 graphs
ngraph = 0

proc addgraph() { local ii	// define subroutine to add a new graph
				// addgraph("variable", minvalue, maxvalue)
	ngraph = ngraph+1
	ii = ngraph-1
	g[ii] = new Graph()
	g[ii].size(0,tstop,$2,$3)
	g[ii].xaxis()
	g[ii].yaxis()
	g[ii].addvar($s1,1,0)
	g[ii].save_name("graphList[0].")
	graphList[0].append(g[ii])
}

if(ismenu==0) {
  nrnmainmenu()			// create main menu
  nrncontrolmenu()		// crate control menu
  ismenu=1
}



//----------------------------------------------------------------------------
//  general parameters
//----------------------------------------------------------------------------

dt=0.025
tstop = 500
runStopAt = tstop
steps_per_ms = 1/dt
celsius = 36
v_init = -70



//----------------------------------------------------------------------------
//  create compartments and insert passive properties
//----------------------------------------------------------------------------

create PRE,POST
forall {
  diam=10
  L=10
  insert pas
  g_pas=1/5000
  e_pas=v_init
}



//----------------------------------------------------------------------------
//  insert presynaptic mechanisms
//----------------------------------------------------------------------------

access PRE		// insert Hodgk-Hux. Na+ and K+ currents for spikes

insert rel		// glutamate release
del_rel = 10
dur_rel = 1		
amp_rel = 1






//----------------------------------------------------------------------------
//  insert postsynaptic mechansisms
//----------------------------------------------------------------------------

objectvar c
c = new NMDA5()			// create synapse
POST c.loc(0.5)				// assign postsynaptic compartment
setpointer c.C, PRE.T_rel(0.5)		// assign presynaptic compartment

Erev_NMDA5	= 0	//	(mV)	reversal potential (E_K)
mg_NMDA5	= 0	//	put in zero magnesium for the demo

// parameters from Hessler Shirke & Malinow 1993
Rb_NMDA5	= 5e-3    //	(/uM /ms)	: binding 		
Ru_NMDA5	= 12.9e-3  //	(/ms)	: unbinding		
Rd_NMDA5	= 8.4e-3   //	(/ms)	: desensitization
Rr_NMDA5	= 6.8e-3   //	(/ms)	: resensitization 
Ro_NMDA5	= 46.5e-3   //	(/ms)	: opening
Rc_NMDA5	= 73.8e-3   //	(/ms)	: closing
c.gmax 		= 50	//	(pS)	maximum conductance


//insert SEClamp
objectvar vc
vc =new SEClamp(.5)
{vc.dur1=10000 vc.rs=1 vc.amp1=-75}

POST vc.loc(0.5)


//----------------------------------------------------------------------------
//  add graphs
//----------------------------------------------------------------------------


//addgraph("PRE.v(0.5)",-90,40)
//addgraph("PRE.T_rel(0.5)",0,1.5)

addgraph("c.i",-0.001,0.0001)
//addgraph("POST.v(0.5)",v_init-2,v_init+4)
ted
Site Admin
Posts: 6300
Joined: Wed May 18, 2005 4:50 pm
Location: Yale University School of Medicine
Contact:

Post by ted »

In release.mod change the

Code: Select all

if (t < del + dur && t > del)
to

Code: Select all

if (t < del + dur && t >= del)
(i.e. the same way it is in stim.mod, the source for the built-in IClamp)
and it will work with cvode.

Comment:
c.i will be too small unless you tighten absolute tolerance to <= 1e-4
Post Reply