initial commit

This commit is contained in:
Yannick Gottschalk
2017-04-24 00:15:00 +02:00
commit 9ba103928d
30 changed files with 1162 additions and 0 deletions

48
src/Aufgabe1.hs Normal file
View File

@ -0,0 +1,48 @@
{-
Aufgabe 1
=========
-}
module Aufgabe1 where
{- Gegeben ist der Datentyp Pred a, der eine Prüffunktion (Prädikat) repräsentiert,
die einen Wert vom Typ a zu einem Wert vom Typ Bool auswertet.
Beachten Sie, dass mit dem Wertekonstruktor Pred bereits eine Funktion
Pred :: (a -> Bool) -> Pred a
gegeben ist, mit der Sie ein Prädikat "einpacken" können.
-}
newtype Pred a = Pred (a -> Bool)
{- Schreiben Sie eine Funktion unPred, die das Prädikat "auspackt".
-}
unPred :: Pred a -> (a -> Bool)
unPred = undefined
{- Da Haskell-Funktionen grundsätzlich “gecurried” sind, bzw. der (->)-Operator
rechtsassoziativ ist, können Sie die Klammern hinten in der Signatur auch weglassen
und erhalten unPred :: Pred a -> a -> Bool, was man zugleich als “wende Pred a an,
wenn du ein a bekommst” lesen kann.
-}
{- Definieren Sie nun eine Funktion isVowel, die prüft, ob ein Buchstabe ein Vokal ist.
-}
isVowel :: Pred Char
isVowel = undefined
{-
Schreiben Sie eine Funktion filterVowels, die alle Vorkommen von Vokalen aus
einem String entfernt. Verwenden Sie hierfür das Prädikat isVowel.
-}
filterVowels :: String -> String
filterVowels = undefined
result :: String
result = filterVowels "Hello World!"

47
src/Aufgabe1.lhs Normal file
View File

@ -0,0 +1,47 @@
Aufgabe 1
=========
> module Aufgabe1 where
Gegeben ist der Datentyp Pred a, der eine Prüffunktion (Prädikat) repräsentiert,
die einen Wert vom Typ a zu einem Wert vom Typ Bool auswertet.
Beachten Sie, dass mit dem Wertekonstruktor Pred bereits eine Funktion
Pred :: (a -> Bool) -> Pred a
gegeben ist, mit der Sie ein Prädikat "einpacken" können.
> newtype Pred a = Pred (a -> Bool)
Schreiben Sie eine Funktion unPred, die das Prädikat "auspackt".
> unPred :: Pred a -> (a -> Bool)
>
> unPred = undefined
Da Haskell-Funktionen grundsätzlich “gecurried” sind, bzw. der (->)-Operator
rechtsassoziativ ist, können Sie die Klammern hinten in der Signatur auch weglassen
und erhalten unPred :: Pred a -> a -> Bool, was man zugleich als “wende Pred a an,
wenn du ein a bekommst” lesen kann.
Definieren Sie nun eine Funktion isVowel, die prüft, ob ein Buchstabe ein Vokal ist.
> isVowel :: Pred Char
>
> isVowel = undefined
Schreiben Sie eine Funktion filterVowels, die alle Vorkommen von Vokalen aus
einem String entfernt. Verwenden Sie hierfür das Prädikat isVowel.
> filterVowels :: String -> String
>
> filterVowels = undefined
> result :: String
>
> result = filterVowels "Hello World!"

47
src/Aufgabe1.md Normal file
View File

@ -0,0 +1,47 @@
Aufgabe 1
=========
> module Aufgabe1 where
Gegeben ist der Datentyp Pred a, der eine Prüffunktion (Prädikat) repräsentiert,
die einen Wert vom Typ a zu einem Wert vom Typ Bool auswertet.
Beachten Sie, dass mit dem Wertekonstruktor Pred bereits eine Funktion
Pred :: (a -> Bool) -> Pred a
gegeben ist, mit der Sie ein Prädikat "einpacken" können.
> newtype Pred a = Pred (a -> Bool)
Schreiben Sie eine Funktion unPred, die das Prädikat "auspackt".
> unPred :: Pred a -> (a -> Bool)
>
> unPred = undefined
Da Haskell-Funktionen grundsätzlich “gecurried” sind, bzw. der (->)-Operator
rechtsassoziativ ist, können Sie die Klammern hinten in der Signatur auch weglassen
und erhalten unPred :: Pred a -> a -> Bool, was man zugleich als “wende Pred a an,
wenn du ein a bekommst” lesen kann.
Definieren Sie nun eine Funktion isVowel, die prüft, ob ein Buchstabe ein Vokal ist.
> isVowel :: Pred Char
>
> isVowel = undefined
Schreiben Sie eine Funktion filterVowels, die alle Vorkommen von Vokalen aus
einem String entfernt. Verwenden Sie hierfür das Prädikat isVowel.
> filterVowels :: String -> String
>
> filterVowels = undefined
> result :: String
>
> result = filterVowels "Hello World!"

41
src/Aufgabe2.hs Normal file
View File

@ -0,0 +1,41 @@
-- Aufgabe 2
-- =========
module Aufgabe2 where
-- Machen Sie sich mit den Modulen
import List
import ERPSys
-- vertraut. Einige der Aufgaben diese Woche basieren auf diesen.
-- Hypothetisches Real-World Problem
-- ---------------------------------
-- Gegeben ein bereits existierendes Warenwirtschaftssystem (Modul ERPSys), welches
-- auf einer eigenen Datenstruktur (Modul List) basiert.
-- Die Firma, in der Sie arbeiten wird beauftragt, ein neues Kassensystem zu
-- entwickeln. Sie werden beauftragt, den Scanalogorithmus der Kasse zu
-- programmieren.
-- Dazu ist zuerst die Funktion `findArticle` zu entwickeln, die gegeben einen
-- Barcode und eine Produktliste einen Artikel findet.
findArticle :: (Eq a) => a -> ProductList a b c -> Maybe (Article a b c)
findArticle = undefined
productCatalog :: ProductList Int String Float
productCatalog = insert (Article 1 "Apfel" 1)
$ insert (Article 2 "Birne" 0.5)
$ insert (Article 3 "Banane" 1.5)
$ insert (Article 4 "Tomate" 0.75)
ListEnd
result = show $ findArticle 2 productCatalog

41
src/Aufgabe2.lhs Normal file
View File

@ -0,0 +1,41 @@
Aufgabe 2
=========
> module Aufgabe2 where
Machen Sie sich mit den Modulen
> import List
>
> import ERPSys
vertraut. Einige der Aufgaben diese Woche basieren auf diesen.
Hypothetisches Real-World Problem
---------------------------------
Gegeben ein bereits existierendes Warenwirtschaftssystem (Modul `ERPSys`), welches
auf einer eigenen Datenstruktur (Modul `List`) basiert.
Die Firma, in der Sie arbeiten wird beauftragt, ein neues Kassensystem zu
entwickeln. Sie werden beauftragt, eine Teil des Scanalogorithmuses der Kasse zu
programmieren.
Dazu ist zuerst die Funktion `findArticle` zu entwickeln, die gegeben einen
Barcode und eine Produktliste einen Artikel findet.
> findArticle :: (Eq a) => a -> ProductList a b c -> Maybe (Article a b c)
>
> findArticle = undefined
> productCatalog :: ProductList Int String Float
> productCatalog = insert (Article 1 "Apfel" 1)
> $ insert (Article 2 "Birne" 0.5)
> $ insert (Article 3 "Banane" 1.5)
> $ insert (Article 4 "Tomate" 0.75)
> ListEnd
> result = show $ findArticle 2 productCatalog

41
src/Aufgabe2.md Normal file
View File

@ -0,0 +1,41 @@
Aufgabe 2
=========
> module Aufgabe2 where
Machen Sie sich mit den Modulen
> import List
>
> import ERPSys
vertraut. Einige der Aufgaben diese Woche basieren auf diesen.
Hypothetisches Real-World Problem
---------------------------------
Gegeben ein bereits existierendes Warenwirtschaftssystem (Modul `ERPSys`), welches
auf einer eigenen Datenstruktur (Modul `List`) basiert.
Die Firma, in der Sie arbeiten wird beauftragt, ein neues Kassensystem zu
entwickeln. Sie werden beauftragt, eine Teil des Scanalogorithmuses der Kasse zu
programmieren.
Dazu ist zuerst die Funktion `findArticle` zu entwickeln, die gegeben einen
Barcode und eine Produktliste einen Artikel findet.
> findArticle :: (Eq a) => a -> ProductList a b c -> Maybe (Article a b c)
>
> findArticle = undefined
> productCatalog :: ProductList Int String Float
> productCatalog = insert (Article 1 "Apfel" 1)
> $ insert (Article 2 "Birne" 0.5)
> $ insert (Article 3 "Banane" 1.5)
> $ insert (Article 4 "Tomate" 0.75)
> ListEnd
> result = show $ findArticle 2 productCatalog

31
src/Aufgabe3.hs Normal file
View File

@ -0,0 +1,31 @@
-- Aufgabe 3
-- =========
module Aufgabe3 where
import Data.Maybe (fromMaybe)
import List
import ERPSys
import Aufgabe2
-- Die Funktion scan soll, aus einer `ProductList` (2. Argument) anhand eines
-- Barcodes (1. Argument) einen Artikel finden und diesen dann in eine
-- Scannerliste einfügen. Wurde kein Artiekl gefunden gibt `scan` `Nothing` zurück.
-- Um die eigentliche Funktion `scan` zu implementieren, empfiehlt es sich, zuerst
-- eine Instanz `Eq` für `Article` zu definieren.
-- Diese sollte anhand des Barcodes die Gleichheit eines Artikels bestimmen.
scan :: (Eq a) => a -> ProductList a b c -> ScannerList a b c -> Maybe (ScannerList a b c)
scan = undefined
instance (Eq a) => Eq (Article a b c) where
(==) = undefined
result = show $ scan 1 productCatalog
$ fromMaybe AmountListEnd $ scan 2 productCatalog
$ fromMaybe AmountListEnd $ scan 1 productCatalog AmountListEnd

31
src/Aufgabe3.lhs Normal file
View File

@ -0,0 +1,31 @@
Aufgabe 3
=========
> module Aufgabe3 where
>
> import Data.Maybe (fromMaybe)
>
> import List
>
> import ERPSys
>
> import Aufgabe2
Die Funktion scan soll, aus einer `ProductList` (2. Argument) anhand eines
Barcodes (1. Argument) einen Artikel finden und diesen dann in eine
Scannerliste einfügen. Wurde kein Artiekl gefunden gibt `scan` `Nothing` zurück.
Um die eigentliche Funktion `scan` zu implementieren, empfiehlt es sich, zuerst
eine Instanz `Eq` für `Article` zu definieren.
Diese sollte anhand des Barcodes die Gleichheit eines Artikels bestimmen.
> scan :: (Eq a) => a -> ProductList a b c -> ScannerList a b c -> Maybe (ScannerList a b c)
>
> scan = undefined
> instance (Eq a) => Eq (Article a b c) where
>
> (==) = undefined
> result = show $ scan 1 productCatalog
> $ fromMaybe AmountListEnd $ scan 2 productCatalog
> $ fromMaybe AmountListEnd $ scan 1 productCatalog AmountListEnd

31
src/Aufgabe3.md Normal file
View File

@ -0,0 +1,31 @@
Aufgabe 3
=========
> module Aufgabe3 where
>
> import Data.Maybe (fromMaybe)
>
> import List
>
> import ERPSys
>
> import Aufgabe2
Die Funktion scan soll, aus einer `ProductList` (2. Argument) anhand eines
Barcodes (1. Argument) einen Artikel finden und diesen dann in eine
Scannerliste einfügen. Wurde kein Artiekl gefunden gibt `scan` `Nothing` zurück.
Um die eigentliche Funktion `scan` zu implementieren, empfiehlt es sich, zuerst
eine Instanz `Eq` für `Article` zu definieren.
Diese sollte anhand des Barcodes die Gleichheit eines Artikels bestimmen.
> scan :: (Eq a) => a -> ProductList a b c -> ScannerList a b c -> Maybe (ScannerList a b c)
>
> scan = undefined
> instance (Eq a) => Eq (Article a b c) where
>
> (==) = undefined
> result = show $ scan 1 productCatalog
> $ fromMaybe AmountListEnd $ scan 2 productCatalog
> $ fromMaybe AmountListEnd $ scan 1 productCatalog AmountListEnd

40
src/Aufgabe4.hs Normal file
View File

@ -0,0 +1,40 @@
-- Aufgabe 4
-- =========
module Aufgabe4 where
import Lib
import Aufgabe2
import Aufgabe3
import Data.Maybe (fromMaybe)
-- Nun da eine `ScannerList` erstellt werden kann, wird eine Funktion, die einen Kassenbon erstellen kann, benötigt.
-- Dieser sollte angemessen formatiert sein.
-- Die Funktion `generateBill` soll diese Aufgabe übernehmen.
type Bill = String
generateBill :: (Show a, Show b, Show c) => ScannerList a b c -> Bill
generateBill = undefined
result = generateBill scannerList
-- Ein paar Hilfsfunktionen zum generieren einer `ScannerList` asu einer Liste
-- von Barcodes. /Glücklicherweise/ hat diese bereits ein Kollege von Ihnen entwickelt!
-- (Mit anderen Worten: Sie brauchen die unten stehenden Funktionen weder
-- anpassen, noch verstehen und auch nicht benutzen, nochmal Glück gehabt ;D )
scannerList :: ScannerList Int String Float
scannerList = fromMaybe AmountListEnd $ scanList [1,3,1,2,1,3]
scanList :: [Int] -> Maybe (ScannerList Int String Float)
scanList l = let help :: [Int] -> Maybe (ScannerList Int String Float) -> Maybe (ScannerList Int String Float)
help = flip $ foldl (\sl a -> sl >>= preparedScan a)
in help l $ Just AmountListEnd
preparedScan :: Int -> ScannerList Int String Float -> Maybe (ScannerList Int String Float)
preparedScan = flip scan productCatalog

40
src/Aufgabe4.lhs Normal file
View File

@ -0,0 +1,40 @@
Aufgabe 4
=========
> module Aufgabe4 where
>
> import Lib
> import Aufgabe2
> import Aufgabe3
> import Data.Maybe (fromMaybe)
Nun da eine `ScannerList` erstellt werden kann, wird eine Funktion, die einen Kassenbon erstellen kann, benötigt.
Dieser sollte /angemessen/ formatiert sein.
Die Funktion `generateBill` soll diese Aufgabe übernehmen.
> type Bill = String
>
> generateBill :: (Show a, Show b, Show c) => ScannerList a b c -> Bill
>
> generateBill = undefined
> result = generateBill scannerList
Ein paar Hilfsfunktionen zum generieren einer `ScannerList` asu einer Liste
von Barcodes. /Glücklicherweise/ hat diese bereits ein Kollege von Ihnen entwickelt!
(Mit anderen Worten: Sie brauchen die unten stehenden Funktionen weder
anpassen, noch verstehen und auch nicht benutzen, nochmal Glück gehabt ;D )
> scannerList :: ScannerList Int String Float
> scannerList = fromMaybe AmountListEnd $ scanList [1,3,1,2,1,3]
> scanList :: [Int] -> Maybe (ScannerList Int String Float)
> scanList l = let help :: [Int] -> Maybe (ScannerList Int String Float) -> Maybe (ScannerList Int String Float)
> help = flip $ foldl (\sl a -> sl >>= preparedScan a)
> in help l $ Just AmountListEnd
> preparedScan :: Int -> ScannerList Int String Float -> Maybe (ScannerList Int String Float)
>
> preparedScan = flip scan productCatalog

40
src/Aufgabe4.md Normal file
View File

@ -0,0 +1,40 @@
Aufgabe 4
=========
> module Aufgabe4 where
>
> import Lib
> import Aufgabe2
> import Aufgabe3
> import Data.Maybe (fromMaybe)
Nun da eine `ScannerList` erstellt werden kann, wird eine Funktion, die einen Kassenbon erstellen kann, benötigt.
Dieser sollte /angemessen/ formatiert sein.
Die Funktion `generateBill` soll diese Aufgabe übernehmen.
> type Bill = String
>
> generateBill :: (Show a, Show b, Show c) => ScannerList a b c -> Bill
>
> generateBill = undefined
> result = generateBill scannerList
Ein paar Hilfsfunktionen zum generieren einer `ScannerList` asu einer Liste
von Barcodes. /Glücklicherweise/ hat diese bereits ein Kollege von Ihnen entwickelt!
(Mit anderen Worten: Sie brauchen die unten stehenden Funktionen weder
anpassen, noch verstehen und auch nicht benutzen, nochmal Glück gehabt ;D )
> scannerList :: ScannerList Int String Float
> scannerList = fromMaybe AmountListEnd $ scanList [1,3,1,2,1,3]
> scanList :: [Int] -> Maybe (ScannerList Int String Float)
> scanList l = let help :: [Int] -> Maybe (ScannerList Int String Float) -> Maybe (ScannerList Int String Float)
> help = flip $ foldl (\sl a -> sl >>= preparedScan a)
> in help l $ Just AmountListEnd
> preparedScan :: Int -> ScannerList Int String Float -> Maybe (ScannerList Int String Float)
>
> preparedScan = flip scan productCatalog

18
src/ERPSys.hs Normal file
View File

@ -0,0 +1,18 @@
module ERPSys
( ProductList
, ScannerList
, Article(Article)
) where
import List
type ProductList a b c = List (Article a b c) -- ^ List with Articles
type ScannerList a b c = AmountList Int (Article a b c) -- ^ AmountList with Articles
-- | generic Article isomorph to (,,)
data Article a b c = Article
{ _barcode :: a
, _name :: b
, _price :: c
} deriving (Show)

14
src/Lib.hs Normal file
View File

@ -0,0 +1,14 @@
module Lib
( ProductList
, ScannerList
, Article(Article)
, List(ListEnd, Element)
, AmountList(AmountAndElement, AmountListEnd)
, Filter
, Searchable(..)
, Consumable(..)
, Insertable(..)
) where
import List
import ERPSys

123
src/List.hs Normal file
View File

@ -0,0 +1,123 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE TemplateHaskell #-}
module List
( List(ListEnd, Element)
, AmountList(AmountAndElement, AmountListEnd)
, Filter
, Searchable(..)
, Consumable(..)
, Insertable(..)
-- , amountOf
) where
import Control.Lens
import Data.Maybe (fromMaybe)
-- | isomorph to []
data List a = ListEnd | Element
{ _el :: a
, _remaining :: (List a)
} deriving (Show)
makeLenses (''List)
-- | counting list
data AmountList a b = AmountListEnd | AmountAndElement
{ _amount :: a
, _el' :: b
, _remaining' :: (AmountList a b)
} deriving (Show)
makeLenses (''AmountList)
type Filter a = a -> Bool
instance Monoid (List a) where
mempty = ListEnd
mappend ListEnd = id
mappend a = mappend $ a ^. remaining
instance Monoid (AmountList a b) where
mempty = AmountListEnd
mappend AmountListEnd = id
mappend a = mappend $ a ^. remaining'
instance Eq a => Eq (List a) where
ListEnd == ListEnd = True
a == b = a^?el == b^?el
&& a^?remaining == b^?remaining
instance (Eq a, Eq b) => Eq (AmountList a b) where
AmountListEnd == AmountListEnd = True
a == b = a^?amount == b^?amount
&& a^?el' == b^?el'
&& a^?remaining' == b^?remaining'
-- | find with return type determined by the structure b a
class Searchable a b c | b a -> c where
findFirst :: Filter a -> b a -> Maybe c
-- | find first a in list matching the filter
instance Searchable a List a where
findFirst :: Filter a -> List a -> Maybe a
findFirst filter list = list^?el>>=(\el_-> if filter el_
then Just el_
else findFirst filter $ list^.remaining)
-- | find first a in list matching the filter returning (amount, element)
instance Searchable a (AmountList b) (b, a) where
findFirst :: Filter a -> AmountList b a -> Maybe (b, a)
findFirst filter list = list^?el' >>= \el_ -> if filter el_
then Just (list^?!amount, el_)
else list^?remaining' >>= findFirst filter
class Consumable b a c | b a -> c where
consume :: (c -> d -> d) -> d -> b a -> d
-- ^ special form of a fold determined by structure b a
-- | isomorph to a foldr
instance Consumable List a a where
consume :: (a -> d -> d) -> d -> List a -> d
consume _ a ListEnd = a
consume f s (Element a as) = f a $ consume f s as
-- | foldr over (element, amount)
instance Consumable (AmountList b) a (a, b) where
consume :: ((a, b) -> e -> e) -> e -> AmountList b a -> e
consume _ a AmountListEnd = a
consume f s (AmountAndElement b a as) = f (a,b) $ consume f s as
{--instance {-# OVERLAPPABLE #-} Consumable (AmountList b) a a where
consume :: (a -> e -> e) -> e -> AmountList b a -> e
consume _ a AmountListEnd = a
consume f s (AmountAndElement b a as) = f a $ consume f s as --}
class Insertable a b where
insert :: a -> b a -> b a
-- ^ insert a to structure b
-- | RTFC!
instance Insertable a List where
insert :: a -> List a -> List a
insert = Element
-- | insert with amount count += 1
instance (Eq a, Num b) => Insertable a (AmountList b) where
insert :: a -> AmountList b a -> AmountList b a
insert a AmountListEnd = AmountAndElement 1 a AmountListEnd
insert a b = case b^?el' & _Just %~ (==a) of
Just True -> b & amount +~ 1
_ -> b & remaining' %~ (insert a)
-- | get amount of a in list. returning mempty if not found
amountOf :: (Eq a, Monoid b) => a -> AmountList b a -> b
amountOf a b = fromMaybe mempty $ b ^. to (findFirst (==a)) & _Just %~ fst
--b ^. to findFirst (==a) %~ _1 ^. to fromMaybe mempty
-- (Just (c,_)) -> c
-- Nothing -> mempty