Skip to content

Instantly share code, notes, and snippets.

@ichistmeinname
Created June 4, 2014 13:44
Show Gist options
  • Save ichistmeinname/0bb22c8345dffb2ce3c6 to your computer and use it in GitHub Desktop.
Save ichistmeinname/0bb22c8345dffb2ce3c6 to your computer and use it in GitHub Desktop.
Seventh group session
module Automaton where
import Prelude hiding ( repeat )
import Data.List ( find )
data State = State
[(Char, State)] -- transitions
Bool -- final state?
-- prueft, ob ein Automat ein gegebenes Wort akzeptiert
accepts :: State -> String -> Bool
-- Sonderfall bei Beispiel aus Praesenzaufgabe
-- accepts (State _ True) cs = True
-- accepts (State _ False) "" = False
accepts (State _ finalFlag) "" = finalFlag
accepts (State ts _ ) (c:cs) =
-- lookup :: Eq a => a -> [(a,b)] -> Maybe b
case lookup c ts of
Nothing -> False
Just newState -> newState `accepts` cs
-- alternative Variante mit `find`
accepts2 :: State -> String -> Bool
accepts2 (State _ finalFlag) "" = finalFlag
accepts2 (State ts _ ) (c:cs) =
case find searchFunc ts of
Nothing -> False
Just (_,newState) -> accepts2 newState cs
where
searchFunc (c',_) = c == c'
-- find :: (a -> Bool) -> [a] -> Maybe a
abb :: State
abb = q0
where
q0 = State [('a',q0),('b',q1)] False
q1 = State [('a',q2),('b',q1)] False
q2 = State [('a',q3),('b',q1)] False
q3 = State [('a',q3),('b',q3)] True
aaabbb :: State
aaabbb = q0
where
q0 = nonFinal [('a',q1),('b',qFalsch)]
q1 = nonFinal [('a',q2),('b',qFalsch)]
q2 = nonFinal [('a',q3),('b',qFalsch)]
q3 = nonFinal [('b',q4),('a',qFalsch)]
q4 = nonFinal [('b',q5),('a',qFalsch)]
q5 = nonFinal [('b',qRichtig),('a',qFalsch)]
qRichtig = final [('a',qFalsch),('b',qFalsch)]
qFalsch = nonFinal [('a',qFalsch),('b',qFalsch)]
-- tatsaechlich "smarte" Smartkonstruktoren
nonFinal :: [(Char,State)] -> State
nonFinal ts = State ts False
final :: [(Char,State)] -> State
final ts = State ts True
-----
-- Nochmal zurueck zu den Bauemen
data Tree a = Node (Tree a) a (Tree a)
| Empty
-- Smartkonstruktor
leaf :: a -> Tree a
leaf v = Node Empty v Empty
tree1,tree2 :: Tree Int
tree1 = Node (leaf 5) 1 (leaf 3)
tree2 = Node (Node tree1 7 Empty) 42 (Node Empty 1 tree1)
tree3 :: Tree String
tree3 = Node (Node (leaf "durch") "Anhalter" Empty)
"Per"
(Node Empty "die" (leaf "Galaxis"))
-- Wie sollen meine Baeume aussehen?
{-
1
5
_
_
3
_
_
-}
instance Show a => Show (Tree a) where
show tree = showLayout tree 0
where
-- Hilfsfunktion, um ein Einrueckungen zu erzeugen
showLayout :: Show a => Tree a -> Int -> String
-- n*" " ++ "_"
showLayout Empty n =
repeat n ' ' ++ "_"
showLayout (Node t1 elem t2) n =
repeat n ' ' ++ show elem
++ "\n" ++ showLayout t1 (n+1)
++ "\n" ++ showLayout t2 (n+1)
-- Hilfsfunktion, um eine n-lange Liste von einem Wert zu erzeugen
repeat :: Int -> a -> [a]
repeat n v | n <= 0 = []
| otherwise = v : repeat (n-1) v
-----
{- Exkurs zu XML-Dokumenten
<beispiele>
<list name="Serien" inhaber="Sandra">
<titel>House of Cards<\titel>
<titel>Friends<\titel>
<\list>
<einkaufsliste>
Milch
Kaffee
<\einkaufsliste>
<\beispiele>
-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment