Safe Haskell | None |
---|
- type PropLiteral = (Bool, String)
- negate :: PropLiteral -> PropLiteral
- newtype Argument = Arg ([PropLiteral], [PropLiteral], PropLiteral)
- showProp :: PropLiteral -> String
- type ArgSet = Gr (PropLiteral, [Argument]) ()
- newtype CAES = CAES (ArgSet, Audience, PropStandard)
- type Audience = (Assumptions, ArgWeight)
- type Assumptions = [PropLiteral]
- type ArgWeight = Argument -> Weight
- type Weight = Double
- type PropStandard = PropLiteral -> PSName
- data PSName
- type ProofStandard = PropLiteral -> CAES -> Bool
- newtype ProofStandardNamed = P (String, PropLiteral -> CAES -> Bool)
- applicable :: Argument -> CAES -> Bool
- acceptable :: PropLiteral -> CAES -> Bool
- scintilla :: ProofStandard
- maxWeightApplicable :: [Argument] -> CAES -> Weight
- maxWeightPro :: PropLiteral -> CAES -> Weight
- maxWeightCon :: PropLiteral -> CAES -> Weight
- preponderance :: ProofStandard
- clear_and_convincing :: ProofStandard
- beyond_reasonable_doubt :: ProofStandard
- dialectical_validity :: ProofStandard
- psMap :: PSName -> ProofStandard
- getAllArgs :: ArgSet -> [Argument]
- getProps :: ArgSet -> [PropLiteral]
- applicableArgs :: CAES -> [Argument]
- nonApplicableArgs :: CAES -> [Argument]
- acceptableProps :: CAES -> [PropLiteral]
- nonAcceptableProps :: CAES -> [PropLiteral]
- contextP :: PropLiteral -> AGraph -> [Context (PropLiteral, [Argument]) ()]
- getArgs :: PropLiteral -> AGraph -> [Argument]
- type AGraph = ArgSet
- type PropNode = LNode (PropLiteral, [Argument])
- type AssociatedGraph = (AGraph, Map PropLiteral Node)
- mkArgSet :: [Argument] -> ArgSet
- mkArgGraph :: [Argument] -> AGraph
- addArgument :: Argument -> AssociatedGraph -> AssociatedGraph
- addToContext :: Argument -> (Context (PropLiteral, [Argument]) (), AGraph) -> AGraph
- unsafeMatch :: Graph gr => Node -> gr a b -> (Context a b, gr a b)
- addArgument' :: Argument -> AssociatedGraph -> (AssociatedGraph, Node)
- addNode :: PropLiteral -> AssociatedGraph -> (AssociatedGraph, Node)
- addEdges :: Node -> [PropLiteral] -> AssociatedGraph -> AssociatedGraph
- addEdges' :: Node -> [Node] -> AssociatedGraph -> AssociatedGraph
- propsToNodes :: [PropLiteral] -> Node -> [PropNode]
- checkCycle :: AGraph -> Bool
- mkProp :: String -> PropLiteral
- mkAssumptions :: [String] -> [PropLiteral]
- mkArg :: [String] -> [String] -> String -> Argument
- alpha :: Double
- gamma :: Double
- beta :: Double
Documentation
type PropLiteral = (Bool, String)Source
Arg ([PropLiteral], [PropLiteral], PropLiteral) |
showProp :: PropLiteral -> StringSource
type ArgSet = Gr (PropLiteral, [Argument]) ()Source
subset mathcal{L}$ is a propositionally consistent set of literals (i.e., not containing both a literal and its negation) assumed to be acceptable by the audience and emph{weight} is a function mapping arguments to a real-valued weight in the range $[0,1]$. end{definition} This definition is captured by the following Haskell definitions:
type Audience = (Assumptions, ArgWeight)Source
type Assumptions = [PropLiteral]Source
type PropStandard = PropLiteral -> PSNameSource
type ProofStandard = PropLiteral -> CAES -> BoolSource
then an argument $a = langle P, E, c rangle$ is emph{applicable} iff begin{itemize} item $p in P$ implies $p$ is an assumption or [,$overline{p}$ is not an assumption and $p$ is acceptable in $C$,] and item $e in E$ implies $e$ is not an assumption and [,$overline{e}$ is an assumption or $e$ is not acceptable in $C$,]. end{itemize} end{definition} begin{definition}[Acceptability of propositions] Given a CAES $C$, a proposition $p$ is emph{acceptable} in $C$ iff $(s ; p ; C)$ is $true$, where $s$ is the proof standard for $p$. end{definition}
Note that these two definitions in general are mutually dependent
because acceptability depends on proof standards, and most sensible
proof standards depend on the applicability of arguments. This is the
reason that Carneades restricts the set of arguments to be acyclic.
(Specific proof standards are considered in the next section.)
The realisation of applicability and acceptability in Haskell is
straightforward:
-- begin{code}
-- applicable :: Argument -> CAES -> Bool
-- applicable (Arg (prems, excns, _)) caes(CAES (_, (assumptions, _), _))
-- = and $ [(p
(CAES (_, _, standard))
-- = c elem
assumptions) || (p acceptable
caes) | p <- prems ]
-- ++
-- [(e elem
assumptions) nor
(e acceptable
caes) | e <- excns ]
-- where
-- x nor
y = not (x || y)
-- acceptable :: PropLiteral -> CAES -> Bool
-- acceptable c caess
caes
-- where P (_, s) = standard c
-- end{code}
applicable :: Argument -> CAES -> BoolSource
acceptable :: PropLiteral -> CAES -> BoolSource
$gamma$; these are assumed to be defined once and globally. This time, we proceed to give the definitions directly in Haskell, as they really only are translitarations of the original definitions.
For a proposition $p$ to satisfy the weakest proof standard, scintilla of evidence, there should be at least one applicable argument pro $p$ in the CAES:
maxWeightApplicable :: [Argument] -> CAES -> WeightSource
maxWeightPro :: PropLiteral -> CAES -> WeightSource
maxWeightCon :: PropLiteral -> CAES -> WeightSource
psMap :: PSName -> ProofStandardSource
getAllArgs :: ArgSet -> [Argument]Source
getProps :: ArgSet -> [PropLiteral]Source
applicableArgs :: CAES -> [Argument]Source
nonApplicableArgs :: CAES -> [Argument]Source
acceptableProps :: CAES -> [PropLiteral]Source
nonAcceptableProps :: CAES -> [PropLiteral]Source
contextP :: PropLiteral -> AGraph -> [Context (PropLiteral, [Argument]) ()]Source
getArgs :: PropLiteral -> AGraph -> [Argument]Source
type PropNode = LNode (PropLiteral, [Argument])Source
type AssociatedGraph = (AGraph, Map PropLiteral Node)Source
mkArgGraph :: [Argument] -> AGraphSource
addToContext :: Argument -> (Context (PropLiteral, [Argument]) (), AGraph) -> AGraphSource
unsafeMatch :: Graph gr => Node -> gr a b -> (Context a b, gr a b)Source
addArgument' :: Argument -> AssociatedGraph -> (AssociatedGraph, Node)Source
addNode :: PropLiteral -> AssociatedGraph -> (AssociatedGraph, Node)Source
addEdges :: Node -> [PropLiteral] -> AssociatedGraph -> AssociatedGraphSource
addEdges' :: Node -> [Node] -> AssociatedGraph -> AssociatedGraphSource
propsToNodes :: [PropLiteral] -> Node -> [PropNode]Source
checkCycle :: AGraph -> BoolSource
mkProp :: String -> PropLiteralSource
mkAssumptions :: [String] -> [PropLiteral]Source