ideas-1.6: Feedback services for intelligent tutoring systems

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

Ideas.Common.View

Contents

Description

This module defines views on data-types, as described in "Canonical Forms in Interactive Exercise Assistants"

Synopsis

Documentation

class Category * a => Arrow a where #

The basic arrow class.

Instances should satisfy the following laws:

where

assoc ((a,b),c) = (a,(b,c))

The other combinators have sensible default definitions, which may be overridden for efficiency.

Minimal complete definition

arr, (first | (***))

Methods

arr :: (b -> c) -> a b c #

Lift a function to an arrow.

first :: a b c -> a (b, d) (c, d) #

Send the first component of the input through the argument arrow, and copy the rest unchanged to the output.

second :: a b c -> a (d, b) (d, c) #

A mirror image of first.

The default definition may be overridden with a more efficient version if desired.

(***) :: a b c -> a b' c' -> a (b, b') (c, c') infixr 3 #

Split the input between the two argument arrows and combine their output. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

(&&&) :: a b c -> a b c' -> a b (c, c') infixr 3 #

Fanout: send the input to both argument arrows and combine their output.

The default definition may be overridden with a more efficient version if desired.

Instances

Arrow (->) 

Methods

arr :: (b -> c) -> b -> c #

first :: (b -> c) -> (b, d) -> (c, d) #

second :: (b -> c) -> (d, b) -> (d, c) #

(***) :: (b -> c) -> (b' -> c') -> (b, b') -> (c, c') #

(&&&) :: (b -> c) -> (b -> c') -> b -> (c, c') #

Arrow Isomorphism # 

Methods

arr :: (b -> c) -> Isomorphism b c #

first :: Isomorphism b c -> Isomorphism (b, d) (c, d) #

second :: Isomorphism b c -> Isomorphism (d, b) (d, c) #

(***) :: Isomorphism b c -> Isomorphism b' c' -> Isomorphism (b, b') (c, c') #

(&&&) :: Isomorphism b c -> Isomorphism b c' -> Isomorphism b (c, c') #

Arrow View # 

Methods

arr :: (b -> c) -> View b c #

first :: View b c -> View (b, d) (c, d) #

second :: View b c -> View (d, b) (d, c) #

(***) :: View b c -> View b' c' -> View (b, b') (c, c') #

(&&&) :: View b c -> View b c' -> View b (c, c') #

Arrow Matcher # 

Methods

arr :: (b -> c) -> Matcher b c #

first :: Matcher b c -> Matcher (b, d) (c, d) #

second :: Matcher b c -> Matcher (d, b) (d, c) #

(***) :: Matcher b c -> Matcher b' c' -> Matcher (b, b') (c, c') #

(&&&) :: Matcher b c -> Matcher b c' -> Matcher b (c, c') #

Arrow Trans # 

Methods

arr :: (b -> c) -> Trans b c #

first :: Trans b c -> Trans (b, d) (c, d) #

second :: Trans b c -> Trans (d, b) (d, c) #

(***) :: Trans b c -> Trans b' c' -> Trans (b, b') (c, c') #

(&&&) :: Trans b c -> Trans b c' -> Trans b (c, c') #

Monad m => Arrow (Kleisli m) 

Methods

arr :: (b -> c) -> Kleisli m b c #

first :: Kleisli m b c -> Kleisli m (b, d) (c, d) #

second :: Kleisli m b c -> Kleisli m (d, b) (d, c) #

(***) :: Kleisli m b c -> Kleisli m b' c' -> Kleisli m (b, b') (c, c') #

(&&&) :: Kleisli m b c -> Kleisli m b c' -> Kleisli m b (c, c') #

Arrow (Encoder a) # 

Methods

arr :: (b -> c) -> Encoder a b c #

first :: Encoder a b c -> Encoder a (b, d) (c, d) #

second :: Encoder a b c -> Encoder a (d, b) (d, c) #

(***) :: Encoder a b c -> Encoder a b' c' -> Encoder a (b, b') (c, c') #

(&&&) :: Encoder a b c -> Encoder a b c' -> Encoder a b (c, c') #

class Arrow a => ArrowChoice a where #

Choice, for arrows that support it. This class underlies the if and case constructs in arrow notation.

Instances should satisfy the following laws:

where

assocsum (Left (Left x)) = Left x
assocsum (Left (Right y)) = Right (Left y)
assocsum (Right z) = Right (Right z)

The other combinators have sensible default definitions, which may be overridden for efficiency.

Minimal complete definition

left | (+++)

Methods

left :: a b c -> a (Either b d) (Either c d) #

Feed marked inputs through the argument arrow, passing the rest through unchanged to the output.

right :: a b c -> a (Either d b) (Either d c) #

A mirror image of left.

The default definition may be overridden with a more efficient version if desired.

(+++) :: a b c -> a b' c' -> a (Either b b') (Either c c') infixr 2 #

Split the input between the two argument arrows, retagging and merging their outputs. Note that this is in general not a functor.

The default definition may be overridden with a more efficient version if desired.

(|||) :: a b d -> a c d -> a (Either b c) d infixr 2 #

Fanin: Split the input between the two argument arrows and merge their outputs.

The default definition may be overridden with a more efficient version if desired.

Instances

ArrowChoice (->) 

Methods

left :: (b -> c) -> Either b d -> Either c d #

right :: (b -> c) -> Either d b -> Either d c #

(+++) :: (b -> c) -> (b' -> c') -> Either b b' -> Either c c' #

(|||) :: (b -> d) -> (c -> d) -> Either b c -> d #

ArrowChoice Isomorphism # 

Methods

left :: Isomorphism b c -> Isomorphism (Either b d) (Either c d) #

right :: Isomorphism b c -> Isomorphism (Either d b) (Either d c) #

(+++) :: Isomorphism b c -> Isomorphism b' c' -> Isomorphism (Either b b') (Either c c') #

(|||) :: Isomorphism b d -> Isomorphism c d -> Isomorphism (Either b c) d #

ArrowChoice View # 

Methods

left :: View b c -> View (Either b d) (Either c d) #

right :: View b c -> View (Either d b) (Either d c) #

(+++) :: View b c -> View b' c' -> View (Either b b') (Either c c') #

(|||) :: View b d -> View c d -> View (Either b c) d #

ArrowChoice Matcher # 

Methods

left :: Matcher b c -> Matcher (Either b d) (Either c d) #

right :: Matcher b c -> Matcher (Either d b) (Either d c) #

(+++) :: Matcher b c -> Matcher b' c' -> Matcher (Either b b') (Either c c') #

(|||) :: Matcher b d -> Matcher c d -> Matcher (Either b c) d #

ArrowChoice Trans # 

Methods

left :: Trans b c -> Trans (Either b d) (Either c d) #

right :: Trans b c -> Trans (Either d b) (Either d c) #

(+++) :: Trans b c -> Trans b' c' -> Trans (Either b b') (Either c c') #

(|||) :: Trans b d -> Trans c d -> Trans (Either b c) d #

Monad m => ArrowChoice (Kleisli m) 

Methods

left :: Kleisli m b c -> Kleisli m (Either b d) (Either c d) #

right :: Kleisli m b c -> Kleisli m (Either d b) (Either d c) #

(+++) :: Kleisli m b c -> Kleisli m b' c' -> Kleisli m (Either b b') (Either c c') #

(|||) :: Kleisli m b d -> Kleisli m c d -> Kleisli m (Either b c) d #

class Arrow a => ArrowZero a where #

Minimal complete definition

zeroArrow

Methods

zeroArrow :: a b c #

Instances

ArrowZero Matcher # 

Methods

zeroArrow :: Matcher b c #

ArrowZero Trans # 

Methods

zeroArrow :: Trans b c #

MonadPlus m => ArrowZero (Kleisli m) 

Methods

zeroArrow :: Kleisli m b c #

class ArrowZero a => ArrowPlus a where #

A monoid on arrows.

Minimal complete definition

(<+>)

Methods

(<+>) :: a b c -> a b c -> a b c infixr 5 #

An associative operation with identity zeroArrow.

Instances

ArrowPlus Matcher # 

Methods

(<+>) :: Matcher b c -> Matcher b c -> Matcher b c #

ArrowPlus Trans # 

Methods

(<+>) :: Trans b c -> Trans b c -> Trans b c #

MonadPlus m => ArrowPlus (Kleisli m) 

Methods

(<+>) :: Kleisli m b c -> Kleisli m b c -> Kleisli m b c #

(>>>) :: Category k cat => cat a b -> cat b c -> cat a c infixr 1 #

Left-to-right composition

(<<<) :: Category k cat => cat b c -> cat a b -> cat a c infixr 1 #

Right-to-left composition

IsMatch type class

class IsMatcher f where Source #

Methods

match :: f a b -> a -> Maybe b Source #

matcher :: f a b -> Matcher a b Source #

Instances

IsMatcher Isomorphism Source # 

Methods

match :: Isomorphism a b -> a -> Maybe b Source #

matcher :: Isomorphism a b -> Matcher a b Source #

IsMatcher View Source # 

Methods

match :: View a b -> a -> Maybe b Source #

matcher :: View a b -> Matcher a b Source #

IsMatcher Matcher Source # 

Methods

match :: Matcher a b -> a -> Maybe b Source #

matcher :: Matcher a b -> Matcher a b Source #

matchM :: (Monad m, IsMatcher f) => f a b -> a -> m b Source #

generalized monadic variant of match

belongsTo :: IsMatcher f => a -> f a b -> Bool Source #

viewEquivalent :: (IsMatcher f, Eq b) => f a b -> a -> a -> Bool Source #

viewEquivalentWith :: IsMatcher f => (b -> b -> Bool) -> f a b -> a -> a -> Bool Source #

data Matcher a b Source #

Instances

Arrow Matcher Source # 

Methods

arr :: (b -> c) -> Matcher b c #

first :: Matcher b c -> Matcher (b, d) (c, d) #

second :: Matcher b c -> Matcher (d, b) (d, c) #

(***) :: Matcher b c -> Matcher b' c' -> Matcher (b, b') (c, c') #

(&&&) :: Matcher b c -> Matcher b c' -> Matcher b (c, c') #

ArrowZero Matcher Source # 

Methods

zeroArrow :: Matcher b c #

ArrowPlus Matcher Source # 

Methods

(<+>) :: Matcher b c -> Matcher b c -> Matcher b c #

ArrowChoice Matcher Source # 

Methods

left :: Matcher b c -> Matcher (Either b d) (Either c d) #

right :: Matcher b c -> Matcher (Either d b) (Either d c) #

(+++) :: Matcher b c -> Matcher b' c' -> Matcher (Either b b') (Either c c') #

(|||) :: Matcher b d -> Matcher c d -> Matcher (Either b c) d #

IsMatcher Matcher Source # 

Methods

match :: Matcher a b -> a -> Maybe b Source #

matcher :: Matcher a b -> Matcher a b Source #

Category * Matcher Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

makeMatcher :: (a -> Maybe b) -> Matcher a b Source #

IsView type class

class IsMatcher f => IsView f where Source #

Minimal complete definition: toView or both match and build.

Methods

build :: f a b -> b -> a Source #

toView :: f a b -> View a b Source #

Instances

IsView Isomorphism Source # 

Methods

build :: Isomorphism a b -> b -> a Source #

toView :: Isomorphism a b -> View a b Source #

IsView View Source # 

Methods

build :: View a b -> b -> a Source #

toView :: View a b -> View a b Source #

simplify :: IsView f => f a b -> a -> a Source #

simplifyWith :: IsView f => (b -> b) -> f a b -> a -> a Source #

simplifyWithM :: IsView f => (b -> Maybe b) -> f a b -> a -> a Source #

canonical :: IsView f => f a b -> a -> Maybe a Source #

canonicalWith :: IsView f => (b -> b) -> f a b -> a -> Maybe a Source #

canonicalWithM :: IsView f => (b -> Maybe b) -> f a b -> a -> Maybe a Source #

isCanonical :: (IsView f, Eq a) => f a b -> a -> Bool Source #

isCanonicalWith :: IsView f => (a -> a -> Bool) -> f a b -> a -> Bool Source #

Views

data View a b Source #

Instances

Arrow View Source # 

Methods

arr :: (b -> c) -> View b c #

first :: View b c -> View (b, d) (c, d) #

second :: View b c -> View (d, b) (d, c) #

(***) :: View b c -> View b' c' -> View (b, b') (c, c') #

(&&&) :: View b c -> View b c' -> View b (c, c') #

ArrowChoice View Source # 

Methods

left :: View b c -> View (Either b d) (Either c d) #

right :: View b c -> View (Either d b) (Either d c) #

(+++) :: View b c -> View b' c' -> View (Either b b') (Either c c') #

(|||) :: View b d -> View c d -> View (Either b c) d #

BiArrow View Source # 

Methods

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

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

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

IsView View Source # 

Methods

build :: View a b -> b -> a Source #

toView :: View a b -> View a b Source #

IsMatcher View Source # 

Methods

match :: View a b -> a -> Maybe b Source #

matcher :: View a b -> Matcher a b Source #

Category * View Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

HasId (View a b) Source # 

Methods

getId :: View a b -> Id Source #

changeId :: (Id -> Id) -> View a b -> View a b Source #

Identify (View a b) Source # 

Methods

(@>) :: IsId n => n -> View a b -> View a b Source #

identity :: Category f => f a a Source #

makeView :: (a -> Maybe b) -> (b -> a) -> View a b Source #

matcherView :: Matcher a b -> (b -> a) -> View a b Source #

Isomorphisms

data Isomorphism a b Source #

Instances

Arrow Isomorphism Source # 

Methods

arr :: (b -> c) -> Isomorphism b c #

first :: Isomorphism b c -> Isomorphism (b, d) (c, d) #

second :: Isomorphism b c -> Isomorphism (d, b) (d, c) #

(***) :: Isomorphism b c -> Isomorphism b' c' -> Isomorphism (b, b') (c, c') #

(&&&) :: Isomorphism b c -> Isomorphism b c' -> Isomorphism b (c, c') #

ArrowChoice Isomorphism Source # 

Methods

left :: Isomorphism b c -> Isomorphism (Either b d) (Either c d) #

right :: Isomorphism b c -> Isomorphism (Either d b) (Either d c) #

(+++) :: Isomorphism b c -> Isomorphism b' c' -> Isomorphism (Either b b') (Either c c') #

(|||) :: Isomorphism b d -> Isomorphism c d -> Isomorphism (Either b c) d #

BiArrow Isomorphism Source # 

Methods

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

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

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

IsView Isomorphism Source # 

Methods

build :: Isomorphism a b -> b -> a Source #

toView :: Isomorphism a b -> View a b Source #

IsMatcher Isomorphism Source # 

Methods

match :: Isomorphism a b -> a -> Maybe b Source #

matcher :: Isomorphism a b -> Matcher a b Source #

Category * Isomorphism Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

HasId (Isomorphism a b) Source # 

Methods

getId :: Isomorphism a b -> Id Source #

changeId :: (Id -> Id) -> Isomorphism a b -> Isomorphism a b Source #

Identify (Isomorphism a b) Source # 

Methods

(@>) :: IsId n => n -> Isomorphism a b -> Isomorphism a b Source #

from :: Isomorphism a b -> a -> b Source #

to :: Isomorphism a b -> b -> a Source #

Lifting with views

class LiftView f where Source #

Minimal complete definition

liftViewIn

Methods

liftView :: View a b -> f b -> f a Source #

liftViewIn :: View a (b, c) -> f b -> f a Source #

Instances

Some combinators

swapView :: Isomorphism (a, b) (b, a) Source #

listView :: View a b -> View [a] [b] Source #

Specialized version of traverseView

traverseView :: Traversable f => View a b -> View (f a) (f b) Source #

($<) :: Traversable f => View a (f b) -> View b c -> View a (f c) Source #

Packaging a view

data ViewPackage where Source #

Constructors

ViewPackage :: (Show a, Show b, Eq a) => (String -> Maybe a) -> View a b -> ViewPackage 

Properties on views

propIdempotence :: (Show a, Eq a) => Gen a -> View a b -> Property Source #

propSoundness :: Show a => (a -> a -> Bool) -> Gen a -> View a c -> Property Source #

propNormalForm :: (Show a, Eq a) => Gen a -> View a b -> Property Source #