Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.TI85.Var
Description
Specifics of the TI-85 variables themselves (i.e. not their representation in the file).
Synopsis
- data Variable
- = TIScalar TINumber
- | TIVector [TINumber]
- | TIList [TINumber]
- | TIMatrix [[TINumber]]
- | TIConstant TINumber
- | TIEquation Text
- | TIString Text
- | TIProgram Program
- | TIPicture TIBitmap
- | TIFuncSettings FuncSettings
- | TIPolarSettings PolarSettings
- | TIParamSettings ParamSettings
- | TIDiffEqSettings DiffEqSettings
- | TIZRCL SavedWinSettings
- | TIFuncGDB (GDB 'Func)
- | TIPolarGDB (GDB 'Polar)
- | TIParamGDB (GDB 'Param)
- | TIDiffEqGDB (GDB 'DiffEq)
- data TINumber
- data Program
- data Token = Token TokenDef Text
- data FuncSettings = FuncSettings {}
- data PolarSettings = PolarSettings {}
- data ParamSettings = ParamSettings {}
- data SavedWinSettings = SavedWinSettings {}
- data DiffEqSettings = DiffEqSettings {}
- data DiffEqAxis
- data AxisInd
- data ModeSettings = ModeSettings {
- modeDrawDot :: Bool
- modeSimulG :: Bool
- modeGridOn :: Bool
- modePolarGC :: Bool
- modeCoordOff :: Bool
- modeAxesOff :: Bool
- modeLabelOn :: Bool
- data GraphMode
- type FuncEqn = Text
- data ParamEqn = ParamEqn {}
- data DiffEqEqn = DiffEqEqn {}
- data GDBLibEntry (a :: GraphMode) = GDBLibEntry {}
- type family GDBEqn (a :: GraphMode)
- type family GDBSettings (a :: GraphMode)
- data GDB (a :: GraphMode) = GDB {
- gdbMode :: ModeSettings
- gdbSettings :: GDBSettings a
- gdbLib :: [GDBLibEntry a]
- class HasGDB (a :: GraphMode)
- showVariable :: Variable -> Text
- showNumber :: TINumber -> Text
- showProgram :: Program -> Text
- showFuncSettings :: FuncSettings -> Text
- showPolarSettings :: PolarSettings -> Text
- showParamSettings :: ParamSettings -> Text
- showDiffEqSettings :: DiffEqSettings -> Text
- showWinSettings :: SavedWinSettings -> Text
- showGDB :: forall (a :: GraphMode). HasGDB a => GDB a -> Text
- showGDBMode :: ModeSettings -> Text
- printVariable :: Variable -> IO ()
Types
Variables have a type and type-specific data.
See also VarType
.
Constructors
Numerical variables are either Real or Complex.
Program
A program is either stored as plaintext
(in the TI-86 codepage; see tiDecode
)
or a list of tokens. The two are represented here to
maintain that information.
An instance of a token from the TokenDef
table. This will include actual text that goes
along with a token, when it is not a fixed-text
token.
Window Settings
data FuncSettings Source #
Function window settings
Constructors
FuncSettings | |
Instances
Show FuncSettings Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> FuncSettings -> ShowS # show :: FuncSettings -> String # showList :: [FuncSettings] -> ShowS # |
data PolarSettings Source #
Polar window settings
Constructors
PolarSettings | |
Instances
Show PolarSettings Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> PolarSettings -> ShowS # show :: PolarSettings -> String # showList :: [PolarSettings] -> ShowS # |
data ParamSettings Source #
Parametric window settings
Constructors
ParamSettings | |
Instances
Show ParamSettings Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> ParamSettings -> ShowS # show :: ParamSettings -> String # showList :: [ParamSettings] -> ShowS # |
data SavedWinSettings Source #
Saved window settings, used for ZRCL.
Constructors
SavedWinSettings | |
Instances
Show SavedWinSettings Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> SavedWinSettings -> ShowS # show :: SavedWinSettings -> String # showList :: [SavedWinSettings] -> ShowS # |
Differential Equations
data DiffEqSettings Source #
Differential equation window settings
Constructors
DiffEqSettings | |
Instances
Show DiffEqSettings Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> DiffEqSettings -> ShowS # show :: DiffEqSettings -> String # showList :: [DiffEqSettings] -> ShowS # |
data DiffEqAxis Source #
Differential equation axis type
Instances
Show DiffEqAxis Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> DiffEqAxis -> ShowS # show :: DiffEqAxis -> String # showList :: [DiffEqAxis] -> ShowS # |
Differential equation axes can come with an index (e.g. Q1-Q9).
Graph Database
data ModeSettings Source #
Constructors
ModeSettings | |
Fields
|
Instances
Show ModeSettings Source # | |
Defined in Data.TI85.Var Methods showsPrec :: Int -> ModeSettings -> ShowS # show :: ModeSettings -> String # showList :: [ModeSettings] -> ShowS # |
There are four graph modes, each with its own set of window ranges and equation types.
Parametric functions use a pair of equations
Differential equations have a single equation paired with an initial condition.
data GDBLibEntry (a :: GraphMode) Source #
A graph database entry, containing a function ID, whether or not it is currently selected, and the equations that define the function.
Constructors
GDBLibEntry | |
type family GDBEqn (a :: GraphMode) Source #
Instances
type GDBEqn 'DiffEq Source # | |
Defined in Data.TI85.Var | |
type GDBEqn 'Func Source # | |
Defined in Data.TI85.Var | |
type GDBEqn 'Param Source # | |
Defined in Data.TI85.Var | |
type GDBEqn 'Polar Source # | |
Defined in Data.TI85.Var |
type family GDBSettings (a :: GraphMode) Source #
Instances
type GDBSettings 'DiffEq Source # | |
Defined in Data.TI85.Var | |
type GDBSettings 'Func Source # | |
Defined in Data.TI85.Var | |
type GDBSettings 'Param Source # | |
Defined in Data.TI85.Var | |
type GDBSettings 'Polar Source # | |
Defined in Data.TI85.Var |
data GDB (a :: GraphMode) Source #
A graph database contains mode settings, window settings, and a library of functions. The latter two depend on the graphcs mode.
Constructors
GDB | |
Fields
|
class HasGDB (a :: GraphMode) Source #
Minimal complete definition
showGDBSettings, showGDBHeader, showGDBEntry
Instances
Text Conversion
showVariable :: Variable -> Text Source #
Convert a Variable to Text
Variable-specific
showNumber :: TINumber -> Text Source #
Convert a TINumber to Text.
showProgram :: Program -> Text Source #
Convert a Program to Text.
showFuncSettings :: FuncSettings -> Text Source #
Function window settings.
showPolarSettings :: PolarSettings -> Text Source #
Polar window settings.
showParamSettings :: ParamSettings -> Text Source #
Parametric window settings.
showDiffEqSettings :: DiffEqSettings -> Text Source #
DiffEq window settings.
showWinSettings :: SavedWinSettings -> Text Source #
Saved window settings.
showGDBMode :: ModeSettings -> Text Source #
IO
printVariable :: Variable -> IO () Source #
Print a textual representation of a Variable.