Added solutions for Blatt 3 & Blatt 5

To compile and run Blatt5 just do a "stack build" and either

stack exec Blatt5-static

or

stack exec Blatt5-animated
This commit is contained in:
Stefan Dresselhaus
2016-07-25 04:05:30 +02:00
parent 003c995794
commit ff4826cc23
12 changed files with 10492 additions and 0 deletions

View File

@ -0,0 +1,46 @@
module GUI where
import Data.Array
import Graphics.Gloss
import Data.Word
type Height = Int
type Width = Int
drawBar :: Width -> Height -> Array Int Int -> Picture
drawBar w h a = Pictures $ draw <$> [0..num]
where
num = u - l
(l, u) = bounds a
w' :: Float
w' = fromIntegral w / fromIntegral num
h' :: Float
h' = fromIntegral h / fromIntegral (maximum $ elems a)
draw :: Int -> Picture
draw i = Translate (w'*i') 0 $ -- translate the whole bar
Pictures [ Color blue $ Polygon [(0,0), (0, h''), (w', h''), (w', 0)] -- draw bar
, Translate 0 (-10) $ Scale 0.05 0.05 $ Text (show i) -- draw caption
]
where
i' = fromIntegral i
h'' = fromIntegral (a!i) * h'
animateGrid :: Width -> Height -> Array (Word8, Word8, Int) Int -> Float -> Picture
animateGrid w h d f = Pictures $ draw <$> [0..l1] <*> [0..l2]
where
(_, (l1, l2, t)) = bounds d
maxVal :: Float
maxVal = fromIntegral . maximum . elems $ d
draw :: Word8 -> Word8 -> Picture
draw x y = Translate (w'*fromIntegral x) (h'*fromIntegral y) $
Pictures [ Color (mixColors val (maxVal-val) red green) $ rectangleSolid w' h'
, Scale 0.05 0.05 . Text . show . round $ val
]
where
val = fromIntegral $ d!(x,y,f')
w' :: Float
w' = fromIntegral w / fromIntegral l1
h' :: Float
h' = fromIntegral h / fromIntegral l2
f' = floor f `mod` t

View File

@ -0,0 +1,69 @@
module Parser
(parseData)
where
import qualified Data.ByteString as BS
import Data.Attoparsec.ByteString
import Data.Attoparsec.ByteString.Char8 (isHorizontalSpace, char, endOfLine, decimal, digit)
import Data.Time (Day(..), TimeOfDay(..), makeTimeOfDayValid, fromGregorianValid)
import Types
parseData :: BS.ByteString -> Either String [Data]
parseData = parseOnly parserData
parserData :: Parser [Data]
parserData = many' parseDatapoint
parseDatapoint :: Parser Data
parseDatapoint = do
skipWhile isHorizontalSpace
d <- parseDay
char 'T'
t <- parseTime
char 'Z'
skipWhile isHorizontalSpace
char ','
skipWhile isHorizontalSpace
ip <- parseIP
skipWhile isHorizontalSpace
endOfLine
return $ Data d t ip
parseDay :: Parser Day
parseDay = do
y <- count 4 digit
char '-'
m <- count 2 digit
char '-'
d <- count 2 digit
case fromGregorianValid (read y) (read m) (read d) of
(Just d) -> return d
Nothing -> fail "Incorrect Date"
parseTime :: Parser TimeOfDay
parseTime = do
h <- count 2 digit
char ':'
m <- count 2 digit
char ':'
s <- count 2 digit
case makeTimeOfDayValid (read h) (read m) (read s) of
(Just t) -> return t
Nothing -> fail "Incorrect Time"
parseIP :: Parser IPv4
parseIP = do
a <- decimal
char '.'
b <- decimal
char '.'
c <- decimal
char '.'
d <- decimal
return $ IPv4 a b c d

View File

@ -0,0 +1,14 @@
module Types where
import Data.Word
import Data.Time
data Data = Data
{ date :: Day
, time :: TimeOfDay
, ip :: IPv4
}
deriving (Show, Eq)
data IPv4 = IPv4 Word8 Word8 Word8 Word8
deriving (Show, Eq)