ideas-1.3.1: 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.

Minimal complete definition: arr and first, satisfying the 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.

class Arrow a => ArrowChoice a where

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

Minimal complete definition: left, satisfying the 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.

class Arrow a => ArrowZero a where

Methods

zeroArrow :: a b c

class ArrowZero a => ArrowPlus a where

A monoid on arrows.

Methods

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

An associative operation with identity zeroArrow.

(>>>) :: 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

Minimal complete definition

Nothing

Methods

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

matcher :: f 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

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.

Minimal complete definition

Nothing

Methods

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

toView :: f 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

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

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

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 

Instances

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