ideas-1.8: Feedback services for intelligent tutoring systems

Maintainerbastiaan.heeren@ou.nl
Stabilityprovisional
Portabilityportable (depends on ghc)
Safe HaskellSafe
LanguageHaskell98

Ideas.Common.Classes

Contents

Description

Type classes and instances.

Synopsis

Type class Apply

class Apply t where Source #

A type class for functors that can be applied to a value. Transformation, Rule, and Strategy are all instances of this type class.

Minimal complete definition

applyAll

Methods

applyAll Source #

Arguments

:: t a 
-> a 
-> [a]

Returns zero or more results

Instances
Apply RewriteRule Source # 
Instance details

Defined in Ideas.Common.Rewriting.RewriteRule

Methods

applyAll :: RewriteRule a -> a -> [a] Source #

Apply Rule Source # 
Instance details

Defined in Ideas.Common.Rule.Abstract

Methods

applyAll :: Rule a -> a -> [a] Source #

Apply Dynamic Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

applyAll :: Dynamic a -> a -> [a] Source #

Apply Leaf Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

applyAll :: Leaf a -> a -> [a] Source #

Apply LabeledStrategy Source # 
Instance details

Defined in Ideas.Common.Strategy.Abstract

Methods

applyAll :: LabeledStrategy a -> a -> [a] Source #

Apply Strategy Source # 
Instance details

Defined in Ideas.Common.Strategy.Abstract

Methods

applyAll :: Strategy a -> a -> [a] Source #

Apply Exercise Source # 
Instance details

Defined in Ideas.Common.Exercise

Methods

applyAll :: Exercise a -> a -> [a] Source #

apply :: Apply t => t a -> a -> Maybe a Source #

Returns zero or one results

applicable :: Apply t => t a -> a -> Bool Source #

Checks whether the functor is applicable (at least one result)

applyD :: Apply t => t a -> a -> a Source #

If not applicable, return the current value (as default)

applyM :: (Apply t, Monad m) => t a -> a -> m a Source #

Same as apply, except that the result (at most one) is returned in some monad

applyList :: Apply t => [t a] -> a -> Maybe a Source #

Type class Container

class Container f where Source #

Instances should satisfy the following law: getSingleton . singleton == Just

Minimal complete definition

singleton, getSingleton

Methods

singleton :: a -> f a Source #

getSingleton :: f a -> Maybe a Source #

Instances
Container [] Source # 
Instance details

Defined in Ideas.Common.Classes

Methods

singleton :: a -> [a] Source #

getSingleton :: [a] -> Maybe a Source #

Container Set Source # 
Instance details

Defined in Ideas.Common.Classes

Methods

singleton :: a -> Set a Source #

getSingleton :: Set a -> Maybe a Source #

Type class BiArrow

class Arrow arr => BiArrow arr where Source #

Type class for bi-directional arrows. - should be used instead of arr from the arrow interface. Minimal complete definition: -.

Minimal complete definition

(<->)

Methods

(<->) :: (a -> b) -> (b -> a) -> arr a b infix 1 Source #

(!->) :: (a -> b) -> arr a b Source #

(<-!) :: (b -> a) -> arr a b Source #

Instances
BiArrow Isomorphism Source # 
Instance details

Defined in Ideas.Common.View

Methods

(<->) :: (a -> b) -> (b -> a) -> Isomorphism a b Source #

(!->) :: (a -> b) -> Isomorphism a b Source #

(<-!) :: (b -> a) -> Isomorphism a b Source #

BiArrow View Source # 
Instance details

Defined in Ideas.Common.View

Methods

(<->) :: (a -> b) -> (b -> a) -> View a b Source #

(!->) :: (a -> b) -> View a b Source #

(<-!) :: (b -> a) -> View a b Source #

Type class BiFunctor

class BiFunctor f where Source #

Minimal complete definition

biMap

Methods

biMap :: (a -> c) -> (b -> d) -> f a b -> f c d Source #

mapFirst :: (a -> b) -> f a c -> f b c Source #

mapSecond :: (b -> c) -> f a b -> f a c Source #

Instances
BiFunctor Either Source # 
Instance details

Defined in Ideas.Common.Classes

Methods

biMap :: (a -> c) -> (b -> d) -> Either a b -> Either c d Source #

mapFirst :: (a -> b) -> Either a c -> Either b c Source #

mapSecond :: (b -> c) -> Either a b -> Either a c Source #

BiFunctor (,) Source # 
Instance details

Defined in Ideas.Common.Classes

Methods

biMap :: (a -> c) -> (b -> d) -> (a, b) -> (c, d) Source #

mapFirst :: (a -> b) -> (a, c) -> (b, c) Source #

mapSecond :: (b -> c) -> (a, b) -> (a, c) Source #

BiFunctor CyclicTree Source # 
Instance details

Defined in Ideas.Common.Strategy.CyclicTree

Methods

biMap :: (a -> c) -> (b -> d) -> CyclicTree a b -> CyclicTree c d Source #

mapFirst :: (a -> b) -> CyclicTree a c -> CyclicTree b c Source #

mapSecond :: (b -> c) -> CyclicTree a b -> CyclicTree a c Source #

BiFunctor Derivation Source # 
Instance details

Defined in Ideas.Common.Derivation

Methods

biMap :: (a -> c) -> (b -> d) -> Derivation a b -> Derivation c d Source #

mapFirst :: (a -> b) -> Derivation a c -> Derivation b c Source #

mapSecond :: (b -> c) -> Derivation a b -> Derivation a c Source #

BiFunctor DerivationTree Source # 
Instance details

Defined in Ideas.Common.DerivationTree

Methods

biMap :: (a -> c) -> (b -> d) -> DerivationTree a b -> DerivationTree c d Source #

mapFirst :: (a -> b) -> DerivationTree a c -> DerivationTree b c Source #

mapSecond :: (b -> c) -> DerivationTree a b -> DerivationTree a c Source #

mapBoth :: BiFunctor f => (a -> b) -> f a a -> f b b Source #

Type class Fix

class Fix a where Source #

Methods

fix :: (a -> a) -> a Source #

Instances
Fix (Process a) Source # 
Instance details

Defined in Ideas.Common.Strategy.Process

Methods

fix :: (Process a -> Process a) -> Process a Source #

Fix (Strategy a) Source # 
Instance details

Defined in Ideas.Common.Strategy.Abstract

Methods

fix :: (Strategy a -> Strategy a) -> Strategy a Source #

Fix (CyclicTree a b) Source # 
Instance details

Defined in Ideas.Common.Strategy.CyclicTree

Methods

fix :: (CyclicTree a b -> CyclicTree a b) -> CyclicTree a b Source #

Boolean Algebra

class BoolValue a where Source #

Minimal complete definition

isTrue, isFalse

Methods

true :: a Source #

false :: a Source #

fromBool :: Bool -> a Source #

isTrue :: a -> Bool Source #

isFalse :: a -> Bool Source #

Instances
BoolValue Bool Source # 
Instance details

Defined in Ideas.Common.Classes

BoolValue (Predicate a) Source # 
Instance details

Defined in Ideas.Common.Predicate

BoolValue b => BoolValue (a -> b) Source # 
Instance details

Defined in Ideas.Common.Classes

Methods

true :: a -> b Source #

false :: a -> b Source #

fromBool :: Bool -> a -> b Source #

isTrue :: (a -> b) -> Bool Source #

isFalse :: (a -> b) -> Bool Source #

class BoolValue a => Boolean a where Source #

Minimal complete definition

(<&&>), (<||>), complement

Methods

(<&&>) :: a -> a -> a Source #

(<||>) :: a -> a -> a Source #

complement :: a -> a Source #

Instances
Boolean Bool Source # 
Instance details

Defined in Ideas.Common.Classes

Boolean (Predicate a) Source # 
Instance details

Defined in Ideas.Common.Predicate

Boolean b => Boolean (a -> b) Source # 
Instance details

Defined in Ideas.Common.Classes

Methods

(<&&>) :: (a -> b) -> (a -> b) -> a -> b Source #

(<||>) :: (a -> b) -> (a -> b) -> a -> b Source #

complement :: (a -> b) -> a -> b Source #

ands :: Boolean a => [a] -> a Source #

ors :: Boolean a => [a] -> a Source #

implies :: Boolean a => a -> a -> a Source #

equivalent :: Boolean a => a -> a -> a Source #

Buggy and Minor properties

class Buggy a where Source #

Minimal complete definition

setBuggy, isBuggy

Methods

buggy :: a -> a Source #

setBuggy :: Bool -> a -> a Source #

isBuggy :: a -> Bool Source #

Instances
Buggy (Rule a) Source # 
Instance details

Defined in Ideas.Common.Rule.Abstract

Methods

buggy :: Rule a -> Rule a Source #

setBuggy :: Bool -> Rule a -> Rule a Source #

isBuggy :: Rule a -> Bool Source #

class Minor a where Source #

Minimal complete definition

setMinor, isMinor

Methods

minor :: a -> a Source #

setMinor :: Bool -> a -> a Source #

isMinor :: a -> Bool Source #

isMajor :: a -> Bool Source #

Instances
Minor (Rule a) Source # 
Instance details

Defined in Ideas.Common.Rule.Abstract

Methods

minor :: Rule a -> Rule a Source #

setMinor :: Bool -> Rule a -> Rule a Source #

isMinor :: Rule a -> Bool Source #

isMajor :: Rule a -> Bool Source #

Minor (Leaf a) Source # 
Instance details

Defined in Ideas.Common.Strategy.StrategyTree

Methods

minor :: Leaf a -> Leaf a Source #

setMinor :: Bool -> Leaf a -> Leaf a Source #

isMinor :: Leaf a -> Bool Source #

isMajor :: Leaf a -> Bool Source #