Joshua Moerman
12 years ago
3 changed files with 67 additions and 10 deletions
@ -0,0 +1,56 @@ |
|||||
|
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, TypeOperators, ScopedTypeVariables, OverlappingInstances #-} |
||||
|
|
||||
|
import Control.Monad.Instances |
||||
|
import Control.Compose |
||||
|
import Coalgebra |
||||
|
|
||||
|
-- F X = 2 x X^A, for some fixed alphabet A |
||||
|
type F a = (,) Bool `O` ((->) a) |
||||
|
|
||||
|
-- Fixpoint, ie languages |
||||
|
type Language a = Mu (F a) |
||||
|
|
||||
|
-- basic constructor |
||||
|
ctor :: Bool -> (a -> Language a) -> Language a |
||||
|
ctor b t = phi (O (b, t)) |
||||
|
|
||||
|
-- For every (F a)-coalgebra x, there is a arrow x -> Language a |
||||
|
-- and it is unique, so `Language a` is the final (F a)-coalgebra! |
||||
|
sem :: (Coalgebra (F a) x) => x -> Language a |
||||
|
sem s = ctor b (\w -> sem $ trans w) where O (b, trans) = psi s |
||||
|
|
||||
|
-- auciliry function |
||||
|
is_member :: [a] -> Language a -> Bool |
||||
|
is_member [] l = b where O (b, _) = psi l |
||||
|
is_member (a:r) l = is_member r (trans a) where O (_, trans) = psi l |
||||
|
|
||||
|
|
||||
|
|
||||
|
-- Our alphabet |
||||
|
data A = A | B |
||||
|
deriving Show |
||||
|
|
||||
|
-- Our example automaton, we will look at its language given by sem |
||||
|
data X = One | Two | Three |
||||
|
trans :: X -> A -> X |
||||
|
trans One A = Two |
||||
|
trans One B = Three |
||||
|
trans Two A = Three |
||||
|
trans Two B = One |
||||
|
trans Three _ = Three |
||||
|
|
||||
|
fin :: X -> Bool |
||||
|
fin One = True; |
||||
|
fin Two = True; |
||||
|
fin _ = False; |
||||
|
|
||||
|
instance Coalgebra (F A) X where |
||||
|
psi x = O (fin x, trans x) |
||||
|
|
||||
|
|
||||
|
-- Test a word against it |
||||
|
show_member word = putStrLn $ show (word, is_member word (sem One :: Language A)) |
||||
|
|
||||
|
main = do |
||||
|
let words = [[A], [A,B], [A,B,B], [A,B,B,A], [A,B,A,B,A]] |
||||
|
sequence $ map show_member words |
Reference in new issue