split web-dev

This commit is contained in:
Nicole Dresselhaus 2022-08-25 05:26:25 +02:00
parent 5e48571fda
commit da8594c678
36 changed files with 5399 additions and 642 deletions

View File

@ -2,7 +2,7 @@
Stellen wir uns vor, dass wir eine Funktion schreiben, die einen String bekommt (mehrere Lines mit ACSII-Text) und dieses Wort-für-Wort rückwärts ausgeben soll. Das ist ein einfacher Einzeiler:
~~~ { .haskell .numberLines }
~~~ { .haskell }
module Main where
import System.Environment (getArgs)

View File

@ -8,7 +8,7 @@ Syntax nehmen.
### Beispiel
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Person = P { name :: String
, addr :: Address
, salary :: Int }
@ -38,7 +38,7 @@ Probleme mit diesem Code:
### Was wir gern hätten
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Person = P { name :: String
, addr :: Address
, salary :: Int }
@ -57,7 +57,7 @@ composeL :: Lens' s1 s2 -> Lens s2 a -> Lens' s1 a
Mit diesen Dingen (wenn wir sie hätten) könnte man dann
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Person = P { name :: String
, addr :: Address
, salary :: Int }
@ -75,7 +75,7 @@ machen und wäre fertig.
### Getter/Setter als Lens-Methoden
~~~ { .haskell .numberLines }
~~~ { .haskell }
data LensR s a = L { viewR :: s -> a
, setR :: a -> s -> s }
@ -91,14 +91,14 @@ composeL (L v1 u1) (L v2 u2)
Auslesen traversiert die Datenstruktur, dann wird die Funktion angewendet und
zum setzen wird die Datenstruktur erneut traversiert:
~~~ { .haskell .numberLines }
~~~ { .haskell }
over :: LensR s a -> (a -> a) -> s -> s
over ln f s = setR l (f (viewR l s)) s
~~~~~~~~~~~~~~~~~~
- Lösung: modify-funktion hinzufügen
~~~ { .haskell .numberLines }
~~~ { .haskell }
data LensR s a
= L { viewR :: s -> a
, setR :: a -> s -> s
@ -113,7 +113,7 @@ Neues Problem: Für jeden Spezialfall muss die Lens erweitert werden.
Man kann alle Monaden abstrahieren. Functor reicht schon:
~~~ { .haskell .numberLines }
~~~ { .haskell }
data LensR s a
= L { viewR :: s -> a
, setR :: a -> s -> s
@ -144,7 +144,7 @@ anders aussehen.
## Benutzen einer Lens als Setter
~~~ { .haskell .numberLines }
~~~ { .haskell }
set :: Lens' s a -> (a -> s -> s)
set ln a s = --...umm...
--:t ln => (a -> f a) -> s -> f s
@ -154,7 +154,7 @@ set ln a s = --...umm...
Wir können für f einfach die "Identity"-Monade nehmen, die wir nachher wegcasten
können.
~~~ { .haskell .numberLines }
~~~ { .haskell }
newtype Identity a = Identity a
-- Id :: a -> Identity a
@ -167,7 +167,7 @@ instance Functor Identity where
somit ist set einfach nur
~~~ { .haskell .numberLines }
~~~ { .haskell }
set :: Lens' s a -> (a -> s -> s)
set ln x s
= runIdentity (ls set_fld s)
@ -197,7 +197,7 @@ over ln f = runIdentity . ln (Identity . f)
## Benutzen einer Lens als Getter
~~~ { .haskell .numberLines }
~~~ { .haskell }
view :: Lens' s a -> (s -> a)
view ln s = --...umm...
--:t ln => (a -> f a) -> s -> f s
@ -208,7 +208,7 @@ view ln s = --...umm...
Auch hier gibt es einen netten Funktor. Wir packen das "a" einfach in das "f"
und werfen das "s" am Ende weg.
~~~ { .haskell .numberLines }
~~~ { .haskell }
newtype Const v a = Const v
getConst :: Const v a -> v
@ -221,7 +221,7 @@ instance Functor (Const v) where
somit ergibt sich
~~~ { .haskell .numberLines }
~~~ { .haskell }
view :: Lens' s a -> (s -> a)
view ln s
= getConst (ln Const s)
@ -246,7 +246,7 @@ type Lens' s a = forall f. Functor f
Für unser Personen-Beispiel vom Anfang:
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Person = P { _name :: String, _salary :: Int }
name :: Lens' Person String
@ -270,7 +270,7 @@ name elt_fn (P n s)
## Wie funktioniert das intern?
~~~ { .haskell .numberLines }
~~~ { .haskell }
view name (P {_name="Fred", _salary=100})
-- inline view-function
= getConst (name Const (P {_name="Fred", _salary=100})
@ -312,7 +312,7 @@ Somit ist Lens-Composition einfach nur Function-Composition (.).
Der Code um die Lenses zu bauen ist für records immer Identisch:
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Person = P { _name :: String, _salary :: Int }
name :: Lens' Person String
@ -321,7 +321,7 @@ name elt_fn (P n s) = (\n' -> P n' s) <$> (elt_fn n)
Daher kann man einfach
~~~ { .haskell .numberLines }
~~~ { .haskell }
import Control.Lens.TH
data Person = P { _name :: String, _salary :: Int }
@ -336,7 +336,7 @@ Will man das aber haben, muss man selbst in den Control.Lens.TH-Code schauen.
## Lenses für den Beispielcode
~~~ { .haskell .numberLines }
~~~ { .haskell }
import Control.Lens.TH
data Person = P { _name :: String
@ -355,7 +355,7 @@ setPostcode pc p = set (addr . postcode) pc p
## Shortcuts mit "Line-Noise"
~~~ { .haskell .numberLines }
~~~ { .haskell }
-- ...
setPostcode :: String -> Person -> Person
@ -375,7 +375,7 @@ Listenkonvertierungen, -traversierungen, ...)
Man kann mit Lenses sogar Felder emulieren, die gar nicht da sind. Angenommen
folgender Code:
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Temp = T { _fahrenheit :: Float }
$(makeLenses ''Temp)
@ -399,7 +399,7 @@ Minuten oder 37 Stunden ist)
Das ganze kann man auch parametrisieren und auf Non-Record-Strukturen anwenden.
Beispielhaft an einer Map verdeutlicht:
~~~ { .haskell .numberLines }
~~~ { .haskell }
-- from Data.Lens.At
at :: Ord k => k -> Lens' (Map k v) (Maybe v)
@ -425,7 +425,7 @@ at k mb_fn m
- Bitfields auf Strukturen die Bits haben (Ints, ...) in Data.Bits.Lens
- Web-scraper in Package hexpat-lens
~~~ { .haskell .numberLines }
~~~ { .haskell }
p ^.. _HTML' . to allNodes
. traverse . named "a"
. traverse . ix "href"
@ -441,7 +441,7 @@ at k mb_fn m
Bisher hatten wir Lenses nur auf Funktoren F. Die nächstmächtigere Klasse ist
Applicative.
~~~ { .haskell .numberLines }
~~~ { .haskell }
type Traversal' s a = forall f. Applicative f
=> (a -> f a) -> (s -> f s)
~~~~~~~~~~~~~~~~~~
@ -452,7 +452,7 @@ etwas anderes ändern. Statt eines einzelnen Focus erhalten wir viele Foci.
Was ist ein Applicative überhaupt? Eine schwächere Monade (nur 1x Anwendung und
kein Bind - dafür kann man die beliebig oft hintereinanderhängen).
~~~ { .haskell .numberLines }
~~~ { .haskell }
class Functor f => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
@ -464,7 +464,7 @@ mf <*> mx = do { f <- mf; x <- mx; return (f x) }
Recap: Was macht eine Lens:
~~~ { .haskell .numberLines }
~~~ { .haskell }
data Adress = A { _road :: String
, _city :: String
, _postcode :: String }
@ -476,7 +476,7 @@ road elt_fn (A r c p) = (\r' -> A r' c p) <$> (elt_fn r)
Wenn man nun road & city gleichzeitig bearbeiten will:
~~~ { .haskell .numberLines }
~~~ { .haskell }
addr_strs :: Traversal' Address String
addr_strs elt_fn (A r c p)
= ... (\r' c' -> A r' c' p) .. (elt_fn r) .. (elt_fn c) ..
@ -487,7 +487,7 @@ fmap kann nur 1 Loch stopfen, aber nicht mit n Löchern umgehen. Applicative mit
<*> kann das.
Somit gibt sich
~~~ { .haskell .numberLines }
~~~ { .haskell }
addr_strs :: Traversal' Address String
addr_strs elt_fn (A r c p)
= pure (\r' c' -> A r' c' p) <*> (elt_fn r) <*> (elt_fn c)
@ -551,7 +551,7 @@ Die modify-Funktion over ist auch
Lens alleine definiert 39 newtypes, 34 data-types und 194 Typsynonyme...
Ausschnitt
~~~ { .haskell .numberLines }
~~~ { .haskell }
-- traverseOf :: Functor f => Iso s t a b -> (a -> f b) -> s -> f t
-- traverseOf :: Functor f => Lens s t a b -> (a -> f b) -> s -> f t
-- traverseOf :: Applicative f => Traversal s t a b -> (a -> f b) -> s -> f t

View File

@ -0,0 +1,311 @@
# Webapp-Development in Haskell
Step-by-Step-Anleitung, wie man ein neues Projekt mit einer bereits erprobten
Pipeline erstellt.
## Definition der API
Erster Schritt ist immer ein wünsch-dir-was bei der Api-Defenition.
Die meisten Services haben offensichtliche Anforderungen (Schnittstellen nach
draußen, Schnittstellen intern, ...). Diese kann man immer sehr gut in einem
`Request -> Response`-Model erfassen.
Diese Definition läuft über openapi-v3 und kann z.b. mit Echtzeit-Vorschau im
http://editor.swagger.io/ erspielen. Per Default ist der noch auf openapi-v2
(aka swagger), kann aber auch v3.
Nach der Definition, was man am Ende haben möchte, muss man sich entscheiden, in
welcher Sprache man weiter entwickelt. Ich empfehle aus verschiedenen Gründen
primär 2 Sprachen: Python-Microservices (weil die ML-Libraries sehr gut sind,
allerdings Änderungen meist schwer sind und der Code wenig robust - meist nur 1
API-Endpunkt pro service) und Haskell (stabilität, performace, leicht zu ändern,
gut anzupassen).
Im folgenden wird (aus offensichtlichen Gründen) nur auf das Haskell-Projekt eingegangen.
## Startprojekt in Haskell
### Erstellen eines neuen Projektes
Zunächst erstellen wir in normales Haskell-Projekt ohne funktionalität & firlefanz:
```bash
stack new myservice
```
Dies erstellt ein neues Verzeichnis und das generelle scaffolding.
Nach einer kurzen anpassung der stack.yaml (resolver auf unserer setzen;
aktuell: lts-17.4) fügen wir am Ende der Datei
```yaml
allow-newer: true
ghc-options:
"$locals": -fwrite-ide-info
```
ein.
Anschließend organisieren™ wir uns noch eine gute `.gitignore` und initialisieren
das git mittels `git init; git add .; git commit -m "initial scaffold"`
### Generierung der API
Da die API immer wieder neu generiert werden kann (und sollte!) liegt sich in
einem unterverzeichnis des Haputprojektes.
Initial ist es das einfachste ein leeres temporäres Verzeichnis woanders zu
erstellen, die `api-doc.yml` hinein kopieren und folgendes ausführen:
```bash
openapi-generator generate -g haskell -o . -i api-doc.yml
```
Dieses erstellt einem dann eine komplette library inkl. Datentypen.
Wichtig: Der Name in der api-doc sollte vom Namen des Services (oben myservice)
abweichen - entweder in Casing oder im Namen direkt. Suffixe wie API schneidet
der Generator hier leider ab.
(Wieso das ganze? Es entstehen nachher 2 libraries, foo & fooAPI. Da der
generator das API abschneidet endet man mit foo & foo und der compiler meckert,
dass er nicht weiss, welche lib gemeint ist).
danach: wie gewohnt `git init; git add .; git commit -m "initial"`. Auf dem
Server der Wahl (github, gitea, gitlab, ...) nun ein Repository erstellen (am
Besten: myserviceAPI - alles auf API endend ist autogeneriert!) und den
Anweisungen nach ein remote hinzufügen & pushen.
#### Wieder zurück im Haskell-Service
In unserem eigentlichen Service müssen wir nun die API einbinden.
Dazu erstellen wir ein Verzeichnis `libs` (konvention) und machen ein `git
submodule add <repository-url> libs/myserviceAPI`
Git hat nun die API in das submodul gepackt und wir können das oben erstellte
temporäre verzeichnis wieder löschen.
Anschließend müssen wir stack noch erklären, dass wir die API da nun liegen
haben und passen wieder die stack.yaml an, indem wir das Verzeichnis unter
packages hinzufügen.
```yaml
packages:
- .
- libs/myserviceAPI # <<
```
nun können wir in der `package.yaml` (oder `myservice.cabal`, falls kein hpack
verwendet wird) unter den dependencies unsere api hinzufügen (name wie die
cabal-datei in libs/myserviceAPI).
### Einbinden anderer Microservices
Funktioniert komplett analog zu dem vorgehen oben (ohne das generieren natürlich
:grin:).
`stack.yaml` editieren und zu den packages hinzufügen:
```yaml
packages:
- .
- libs/myserviceAPI
- libs/myCoolMLServiceAPI
```
in der `package.yaml` (oder der cabal) die dependencies hinzufügen und schon
haben wir die Features zur Verfügung und können gegen diese Services reden.
### Entfernen von anderen Technologien/Microservices
In git ist das entfernen von Submodules etwas frickelig, daher hier ein
copy&paste der
[GitHub-Antwort](https://gist.github.com/myusuf3/7f645819ded92bda6677):
```bash
## Remove the submodule entry from .git/config
git submodule deinit -f path/to/submodule
## Remove the submodule directory from the superproject's .git/modules directory
rm-rf .git/modules/path/to/submodule
## Remove the entry in .gitmodules and remove the submodule directory located at path/to/submodule
git rm-f path/to/submodule
```
Falls das nicht klappt, gibt es alternative Vorschläge unter dem Link oben.
### Woher weiss ich, was wo liegt? Dokumentation? Halloo??
Keine Panik. Ein `stack haddock --open` hilft da. Das generiert die
Dokumentation für alle in der `package.yaml` (oder cabal-file) eingetragenen
dependencies inkl. aller upstream-dependencies. Man bekommt also eine komplette
lokale Dokumentation von allem. Geöffnet wird dann die Paket-Startseite inkl.
der direkten dependencies:
Es gibt 2 wichtige Pfade im Browser:
- ...../all/index.html - hier sind alle Pakete aufgeführt
- ...../index.html - hier sind nur die direkten dependencies aufgeführt.
Wenn man einen lokalen Webserver startet kann man mittels "s" auch die
interaktive Suche öffnen (Suche nach Typen, Funktionen, Signaturen, etc.). In
Bash mit python3 geht das z.b. einfach über:
```bash
cd $(stack path --local-doc-root)
python3 -m SimpleHTTPServer 8000
firefox "http://localhost:8000"
```
### Implementation des Services und Start
#### Loader/Bootstrapper
Generelles Vorgehen:
- in app/Main.hs:
Hier ist quasi immer nur eine Zeile drin: `main = myServiceMain`
Grund: Applications tauchen nicht im Haddock auf. Also haben wir ein
"src"-Modul, welches hier nur geladen & ausgeführt wird.
- in src/MyService.hs:
`myServiceMain :: IO ()` definieren
Für die Main kann man prinzipiell eine Main andere Services copy/pasten. Im
folgenden eine Annotierte main-Funktion - zu den einzelnen Vorraussetzungen
kommen wir im Anschluss.
![[Main.hs#]]
#### Weitere Instanzen und Definitionen, die der Generator (noch) nicht macht
In der `Myservice.Types` werden ein paar hilfreiche Typen und Typinstanzen
definiert. Im Folgenden geht es dabei um Dinge für:
- Envy
- Laden von \$ENV_VAR in Datentypen
- Definitionen für Default-Settings
- ServerConfig
- Definition der Server-Konfiguration & Benennung der Environment-Variablen
- ExtraTypes
- ggf. Paketweite extra-Typen, die der Generator nicht macht, weil sie nicht
aus der API kommen (z.B. cache)
- Out/BSON-Instanzen
- Der API-Generator generiert nur wenige Instanzen automatisch (z.B. Aeson),
daher werden hier die fehlenden definiert.
- BSON: Kommunakation mit MongoDB
- Out: pretty-printing im Log
![[MyService_Types.hs#]]
#### Was noch zu tun ist
Den Service implementieren. Einfach ein neues Modul aufmachen (z.B.
`MyService.Handler` oder
`MyService.DieserEndpunktbereich`/`MyService.JenerEndpunktbereich`) und dort die
Funktion implementieren, die man in der `Main.hs` benutzt hat.
In dem Handler habt ihr dann keinen Stress mehr mit validierung, networking,
logging, etc. pp. weil alles in der Main abgehandelt wurde und ihr nur noch den
"Happy-Case" implementieren müsst.
Beispiel für unseren Handler oben:
```haskell
myApiEndpointV1Post :: MonadIO m => ServerConfig -> (ClientEnv,ClientEnv) -> TQueue BS.ByteString -> ([LogItem] -> IO ()) -> Request -> m Response
myApiEndpointV1Post sc calls amqPost log req = do
liftIO . log $ [Info $ "recieved "<>pretty req] -- input-logging
liftIO . atomically . writeTQueue . LBS.toStrict $ "{\"hey Kibana, i recieved:\"" <> A.encode (pretty req) <> "}" -- log in activeMQ/Kibana
--- .... gaaaanz viel komplizierter code um die Response zu erhalten ;)
let ret = Response 1337 Nothing -- dummy-response ;)
-- gegeben wir haben eine gültige mongodb-pipe;
-- mehr logik will ich in die Beispiele nicht packen.
-- Man kann die z.b. als weiteren Wert in einer TMVar (damit man sie ändern & updaten kann) an die Funktion übergeben.
liftIO . access pipe master "DatabaseName" $ do
ifM (auth (myServiceMongoUsername sc) (myServiceMongoPassword sc)) (return ()) (liftIO . printLog . pure . Error $ "MongoDB: Login failed.")
save "DatabaseCollection" ["_id" =: 1337, "entry" =: ret] -- selbe id wie oben ;)
return ret
```
Diese dummy-Antwort führt auf, wie gut man die ganzen Sachen mischen kann.
- Logging in die Dateien/stdout nach config
- Logging von Statistiken in Kibana
- Speichern der Antwort in der MongoDB
- Generieren einer Serverantwort und ausliefern dieser über die Schnittstelle
#### Tipps & Tricks
##### Dateien, die statisch ausgeliefert werden sollen
Hierzu erstellt man ein Verzeichnis `static/` (konvention; ist im generator so
generiert, dass das ausgeliefert wird). Packt man hier z.b. eine `index.html`
rein, erscheint die, wenn man den Service ansurft.
##### Wie bekomme ich diese fancy Preview hin?
Der Editor, der ganz am Anfang zum Einsatz gekommen ist, braucht nur die
`api-doc.yml` um diese Ansicht zu erzeugen. Daher empfielt sich hier ein
angepasster Fork davon indem die Pfade in der index.html korrigiert sind. Am
einfachsten (und von den meisten services so benutzt): In meiner Implementation
liegt dann nach dem starten auf http://localhost:PORT/ui/ und kann direkt dort
getestet werden.
##### Wie sorge ich für bessere Warnungen, damit der Compiler meine Bugs fängt?
```bash
stack build --file-watch --ghc-options '-freverse-errors -W -Wall -Wcompat' --interleaved-output
```
Was tut das?
- `--file-watch`: automatisches (minimales) kompilieren bei dateiänderungen
- `--ghc-options`
- `-freverse-errors`: Fehlermeldungen in umgekehrter Reihenfolge (Erster
Fehler ganz unten; wenig scrollen )
- `-W`: Warnungen an
- `-Wall`: Alle sinnvollen Warnungen an (im gegensatz zu `-Weverything`, was
WIRKLICH alles ist )
- `-Wcompat`: Warnungen für Sachen, die in der nächsten Compilerversion kaputt
brechen werden & vermieden werden sollten
- `--interleaved-output`: stack-log direkt ausgeben & nicht in dateien schreiben
und die dann am ende zusammen cat\'en.
Um pro Datei Warnungen auszuschalten (z.B. weil man ganz sicher weiss, was man
tut -.-): `{-# OPTIONS_GHC -Wno-whatsoever #-}` als Pragma in die Datei.
**Idealerweise sollte das Projekt keine Warnungen erzeugen.**
### Deployment
Als Beispiel sei hier ein einfaches Docker-Build mit Jenkins-CI gezeigt, weil
ich das aus Gründen rumliegen hatte. Kann man analog in fast alle anderen CI
übrsetzen.
#### Docker
Die angehängten Scripte gehen von einer Standard-Einrichtung aus (statische
sachen in static, 2-3 händische Anpassungen auf das eigene Projekt nach
auspacken). Nachher liegt dann auch unter static/version die gebaute
Versionsnummer & kann abgerufen werden. In der Dockerfile.release und der
Jenkinsfile müssen noch anpassungen gemacht werden. Konkret:
- in der Dockerfile.release: alle `<<<HIER>>>`-Stellen sinnvoll befüllen
- in der Jenkinsfile die defs für "servicename" und "servicebinary" ausfüllen.
Binary ist das, was bei stack exec aufgerufen wird; name ist der Image-Name
für das docker-repository.
#### Jenkins
Änderungen die dann noch gemacht werden müssen:
- git-repository url anpassen
- Environment-Vars anpasses ($BRANCH = test & live haben keine zusatzdinger im
docker-image-repository; ansonsten hat das image $BRANCH im namen)
Wenn das durchgebaut ist, liegt im test/live-repository ein docker-image namens `servicename:version`.
### OMG! Ich muss meine API ändern. Was mache ich nun?
1. api-doc.yml bearbeiten, wie gewünscht
2. mittels generator die Api & submodule neu generieren
3. ggf. custom Änderungen übernehmen (:Gitdiffsplit hilft)
4. Alle Compilerfehler + Warnungen in der eigentlichen Applikation fixen
5. If it comipilez, ship it! (Besser nicht :grin:)

View File

@ -0,0 +1,188 @@
# Webapp-Example: Main.hs
Wie man das verwendet, siehe #[[Webapp-Example]].
```haskell
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module MyService where
-- generische imports aus den dependencies/base, nicht in der prelude
import Codec.MIME.Type
import Configuration.Dotenv as Dotenv
import Control.Concurrent (forkIO, threadDelay)
import Control.Concurrent.Async
import Control.Concurrent.STM
import Control.Monad
import Control.Monad.Catch
import Control.Monad.Except
import Conversion
import Conversion.Text ()
import Data.Binary.Builder
import Data.String (IsString (..))
import Data.Time
import Data.Time.Clock
import Data.Time.Format
import Data.Default
import Network.HostName
import Network.HTTP.Client as HTTP hiding
(withConnection)
import Network.HTTP.Types (Status, statusCode)
import Network.Mom.Stompl.Client.Queue
import Network.Wai (Middleware)
import Network.Wai.Logger
import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger (OutputFormat (..),
logStdout,
mkRequestLogger,
outputFormat)
import Servant.Client (mkClientEnv,
parseBaseUrl)
import System.Directory
import System.Envy
import System.IO
import System.Log.FastLogger
import Text.PrettyPrint.GenericPretty
-- generische imports, aber qualified, weil es sonst zu name-clashes kommt
import qualified Data.ByteString as BS
-- import qualified Data.ByteString.Char8 as BS8
import qualified Data.ByteString.Lazy as LBS
import qualified Network.HTTP.Client.TLS as UseDefaultHTTPSSettings (tlsManagerSettings)
import qualified Network.Mom.Stompl.Client.Queue as AMQ
import qualified Network.Wai as WAI
-- Handler für den MyServiceBackend-Typen und Imports aus den Libraries
import MyService.Handler as H -- handler der H.myApiEndpointV1Post implementiert
import MyService.Types -- weitere Type (s. nächste box)
import MyServiceGen.API as MS -- aus der generierten library
myServicemain :: IO ()
myServicemain = do
-- .env-Datei ins Prozess-Environment laden, falls noch nicht von außen gesetzt
void $ loadFile $ Dotenv.Config [".env"] [] False
-- Config holen (defaults + overrides aus dem Environment)
sc@ServerConfig{..} <- decodeWithDefaults defConfig
-- Backend-Setup
-- legt sowas wie Proxy-Server fest und wo man wie dran kommt. Benötigt für das Sprechen mit anderen Microservices
let defaultHTTPSSettings = UseDefaultHTTPSSettings.tlsManagerSettings { managerResponseTimeout = responseTimeoutMicro $ 1000 * 1000 * myserviceMaxTimeout }
createBackend url proxy = do
manager <- newManager . managerSetProxy proxy
$ defaultHTTPSSettings
url' <- parseBaseUrl url
return (mkClientEnv manager url')
internalProxy = case myserviceInternalProxyUrl of
"" -> noProxy
url -> useProxy $ HTTP.Proxy (fromString url) myserviceInternalProxyPort
-- externalProxy = case myserviceExternalProxyUrl of
-- "" -> noProxy
-- url -> useProxy $ HTTP.Proxy (fromString url) myserviceExternalProxyPort
-- Definieren & Erzeugen der Funktionen um die anderen Services anzusprechen.
calls <- (,)
<$> createBackend myserviceAUri internalProxy
<*> createBackend myserviceBUri internalProxy
-- Logging-Setup
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
-- Infos holen, brauchen wir später
myName <- getHostName
today <- formatTime defaultTimeLocale "%F" . utctDay <$> getCurrentTime
-- activeMQ-Transaktional-Queue zum schreiben nachher vorbereiten
amqPost <- newTQueueIO
-- bracket a b c == erst a machen, ergebnis an c als variablen übergeben. Schmeisst c ne exception/wird gekillt/..., werden die variablen an b übergeben.
bracket
-- logfiles öffnen
(LogFiles <$> openFile ("/logs/myservice-"<>myName<>"-"<>today<>".info") AppendMode
<*> openFile (if myserviceDebug then "/logs/myservice-"<>myName<>"-"<>today<>".debug" else "/dev/null") AppendMode
<*> openFile ("/logs/myservice-"<>myName<>"-"<>today<>".error") AppendMode
<*> openFile ("/logs/myservice-"<>myName<>"-"<>today<>".timings") AppendMode
)
-- und bei exception/beendigung schlißen.h
(\(LogFiles a b c d) -> mapM_ hClose [a,b,c,d])
$ \logfiles -> do
-- logschreibe-funktionen aliasen; log ist hier abstrakt, iolog spezialisiert auf io.
let log = printLogFiles logfiles :: MonadIO m => [LogItem] -> m ()
iolog = printLogFilesIO logfiles :: [LogItem] -> IO ()
-- H.myApiEndpointV1Post ist ein Handler (alle Handler werden mit alias H importiert) und in einer eigenen Datei
-- Per Default bekommen Handler sowas wie die server-config, die Funktionen um mit anderen Services zu reden, die AMQ-Queue um ins Kibana zu loggen und eine Datei-Logging-Funktion
-- Man kann aber noch viel mehr machen - z.b. gecachte Daten übergeben, eine Talk-Instanz, etc. pp.
server = MyServiceBackend{ myApiEndpointV1Post = H.myApiEndpointV1Post sc calls amqPost log
}
config = MS.Config $ "http://" ++ myserviceHost ++ ":" ++ show myservicePort ++ "/"
iolog . pure . Info $ "Using Server configuration:"
iolog . pure . Info $ pretty sc { myserviceActivemqPassword = "******" -- Do NOT log the password ;)
, myserviceMongoPassword = "******"
}
-- alle Services starten (Hintergrund-Aktionen wie z.b. einen MongoDB-Dumper, einen Talk-Server oder wie hier die ActiveMQ
void $ forkIO $ keepActiveMQConnected sc iolog amqPost
-- logging-Framework erzeugen
loggingMW <- loggingMiddleware
-- server starten
if myserviceDebug
then runMyServiceMiddlewareServer config (cors (\_ -> Just (simpleCorsResourcePolicy {corsRequestHeaders = ["Content-Type"]})) . loggingMW . logStdout) server
else runMyServiceMiddlewareServer config (cors (\_ -> Just (simpleCorsResourcePolicy {corsRequestHeaders = ["Content-Type"]}))) server
-- Sollte bald in die Library hs-stomp ausgelagert werden
-- ist ein Beispiel für einen ActiveMQ-Dumper
keepActiveMQConnected :: ServerConfig -> ([LogItem] -> IO ()) -> TQueue BS.ByteString -> IO ()
keepActiveMQConnected sc@ServerConfig{..} printLog var = do
res <- handle (\(e :: SomeException) -> do
printLog . pure . Error $ "Exception in AMQ-Thread: "<>show e
return $ Right ()
) $ AMQ.try $ do -- catches all AMQ-Exception that we can handle. All others bubble up.
printLog . pure . Info $ "AMQ: connecting..."
withConnection myserviceActivemqHost myserviceActivemqPort [ OAuth myserviceActivemqUsername myserviceActivemqPassword
, OTmo (30*1000) {- 30 sec timeout -}
]
[] $ \c -> do
let oconv = return
printLog . pure . Info $ "AMQ: connected"
withWriter c "Chaos-Logger for Kibana" "chaos.logs" [] [] oconv $ \writer -> do
printLog . pure . Info $ "AMQ: queue created"
let postfun = writeQ writer (Type (Application "json") []) []
void $ race
(forever $ atomically (readTQueue var) >>= postfun)
(threadDelay (600*1000*1000)) -- wait 10 Minutes
-- close writer
-- close connection
-- get outside of all try/handle/...-constructions befor recursing.
case res of
Left ex -> do
printLog . pure . Error $ "AMQ: "<>show ex
keepActiveMQConnected sc printLog var
Right _ -> keepActiveMQConnected sc printLog var
-- Beispiel für eine Custom-Logging-Middleware.
-- Hier werden z.B. alle 4xx-Status-Codes inkl. Payload ins stdout-Log geschrieben.
-- Nützlich, wenn die Kollegen ihre Requests nicht ordentlich schreiben können und der Server das Format zurecht mit einem BadRequest ablehnt ;)
loggingMiddleware :: IO Middleware
loggingMiddleware = liftIO $ mkRequestLogger $ def { outputFormat = CustomOutputFormatWithDetails out }
where
out :: ZonedDate -> WAI.Request -> Status -> Maybe Integer -> NominalDiffTime -> [BS.ByteString] -> Builder -> LogStr
out _ r status _ _ payload _
| statusCode status < 300 = ""
| statusCode status > 399 && statusCode status < 500 = "Error code "<>toLogStr (statusCode status) <>" sent. Request-Payload was: "<> mconcat (toLogStr <$> payload) <> "\n"
| otherwise = toLogStr (show r) <> "\n"
```

View File

@ -0,0 +1,83 @@
# Webapp-Example: MyService/Types.hs
Anleitung siehe #[[Webapp-Example]].
```haskell
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
module MyService.Types where
import Data.Aeson (FromJSON, ToJSON)
import Data.Text
import Data.Time.Clock
import GHC.Generics
import System.Envy
import Text.PrettyPrint (text)
import Text.PrettyPrint.GenericPretty
-- Out hat hierfür keine Instanzen, daher kurz eine einfach Definition.
instance Out Text where
doc = text . unpack
docPrec i a = text $ showsPrec i a ""
instance Out UTCTime where
doc = text . show
docPrec i a = text $ showsPrec i a ""
-- Der ServerConfig-Typ. Wird mit den defaults unten initialisiert, dann mit den Variablen aus der .env-Datei überschrieben und zum Schluss können Serveradmins diese via $MYSERVICE_FOO nochmal überschreiben.
data ServerConfig = ServerConfig
{ myserviceHost :: String -- ^ Environment: $MYSERVICE_HOST
, myservicePort :: Int -- ^ Environment: $MYSERVICE_PORT
, myserviceMaxTimeout :: Int -- ^ Environment: $MYSERVICE_MAX_TIMEOUT
, myserviceInternalProxyUrl :: String -- ^ Environment: $MYSERVICE_INTERNAL_PROXY_URL
, myserviceInternalProxyPort :: Int -- ^ Environment: $MYSERVICE_INTERNAL_PROXY_PORT
, myserviceExternalProxyUrl :: String -- ^ Environment: $MYSERVICE_EXTERNAL_PROXY_URL
, myserviceExternalProxyPort :: Int -- ^ Environment: $MYSERVICE_EXTERNAL_PROXY_PORT
, myserviceActivemqHost :: String -- ^ Environment: $MYSERVICE_ACTIVEMQ_HOST
, myserviceActivemqPort :: Int -- ^ Environment: $MYSERVICE_ACTIVEMQ_PORT
, myserviceActivemqUsername :: String -- ^ Environment: $MYSERVICE_ACTIVEMQ_USERNAME
, myserviceActivemqPassword :: String -- ^ Environment: $MYSERVICE_ACTIVEMQ_PASSWORD
, myserviceMongoUsername :: String -- ^ Environment: $MYSERVICE_MONGO_USERNAME
, myserviceMongoPassword :: String -- ^ Environment: $MYSERVICE_MONGO_PASSWORD
, myserviceDebug :: Bool -- ^ Environment: $MYSERVICE_DEBUG
} deriving (Show, Eq, Generic)
-- Default-Konfigurations-Instanz für diesen Service.
instance DefConfig ServerConfig where
defConfig = ServerConfig "0.0.0.0" 8080 20
""
""
""
0
""
0
""
0
""
""
""
""
False
-- Kann auch aus dem ENV gefüllt werden
instance FromEnv ServerConfig
-- Und hübsch ausgegeben werden.
instance Out ServerConfig
instance Out Response
instance FromBSON Repsonse -- FromBSON-Instanz geht immer davon aus, dass alle keys da sind (ggf. mit null bei Nothing).
```

View File

@ -1,503 +0,0 @@
# Webapp-Development in Haskell
Step-by-Step-Anleitung, wie man ein neues Projekt mit einer bereits erprobten Pipeline erstellt.
## Definition der API
Erster Schritt ist immer ein wünsch-dir-was bei der Api-Defenition.
Die meisten Services haben offensichtliche Anforderungen (Schnittstellen nach draußen, Schnittstellen intern, ...). Diese kann man immer sehr gut in einem `Request -> Response`-Model erfassen.
Diese Definition läuft über openapi-v3 und kann z.b. mit Echtzeit-Vorschau im http://editor.swagger.io/ erspielen. Per Default ist der noch auf openapi-v2 (aka swagger), kann aber auch v3.
Nach der Definition, was man am Ende haben möchte, muss man sich entscheiden, in welcher Sprache man weiter entwickelt. Ich empfehle aus verschiedenen Gründen primär 2 Sprachen: Python-Microservices (weil die ML-Libraries sehr gut sind, allerdings Änderungen meist schwer sind und der Code wenig robust - meist nur 1 API-Endpunkt pro service) und Haskell (stabilität, performace, leicht zu ändern, gut anzupassen).
Im folgenden wird (aus offensichtlichen Gründen) nur auf das Haskell-Projekt eingegangen.
## Startprojekt in Haskell
### Erstellen eines neuen Projektes
zunächst erstellen wir in normales Haskell-Projekt ohne funktionalität & firlefanz:
```bash
stack new myservice
```
Dies erstellt ein neues Verzeichnis und das generelle scaffolding.
Nach einer kurzen anpassung der stack.yaml (resolver auf unserer setzen; aktuell: lts-17.4) fügen wir am Ende der Datei
```yaml
allow-newer: true
ghc-options:
"$locals": -fwrite-ide-info
```
ein.
Anschließend organisieren wir uns noch eine gute `.gitignore` und initialisieren das git mittels `git init; git add .; git commit -m "initial scaffold"`
### Generierung der API
Da die API immer wieder neu generiert werden kann (und sollte!) liegt sich in einem unterverzeichnis des Haputprojektes.
Initial ist es das einfachste ein leeres temporäres Verzeichnis woanders zu erstellen, die `api-doc.yml` hinein kopieren und folgendes ausführen:
```bash
openapi-generator generate -g haskell -o . -i api-doc.yml
```
Dieses erstellt einem dann eine komplette library inkl. Datentypen.
Wichtig: Der Name in der api-doc sollte vom Namen des Services (oben myservice) abweichen - entweder in Casing oder im Namen direkt. Suffixe wie API schneidet der Generator hier leider ab.
(Wieso das ganze? Es entstehen nachher 2 libraries, foo & fooAPI. Da der generator das API abschneidet endet man mit foo & foo und der compiler meckert, dass er nicht weiss, welche lib gemeint ist).
danach: wie gewohnt `git init; git add .; git commit -m "initial"`. Auf dem Server der Wahl (github, gitea, gitlab, ...) nun ein Repository erstellen (am Besten: myserviceAPI - alles auf API endend ist autogeneriert!) und den Anweisungen nach ein remote hinzufügen & pushen.
#### Wieder zurück im Haskell-Service
In unserem eigentlichen Service müssen wir nun die API einbinden.
Dazu erstellen wir ein Verzeichnis `libs` (konvention) und machen ein `git submodule add <repository-url> libs/myserviceAPI`
Git hat nun die API in das submodul gepackt und wir können das oben erstellte temporäre verzeichnis wieder löschen.
Anschließend müssen wir stack noch erklären, dass wir die API da nun liegen haben und passen wieder die stack.yaml an, indem wir das Verzeichnis unter packages hinzufügen.
```yaml
packages:
- .
- libs/myserviceAPI # <<
```
nun können wir in der `package.yaml` (oder `myservice.cabal`, falls kein hpack verwendet wird) unter den dependencies unsere api hinzufügen (name wie die cabal-datei in libs/myserviceAPI).
### Einbinden anderer Microservices
Funktioniert komplett analog zu dem vorgehen oben (ohne das generieren natürlich ;) ).
`stack.yaml` editieren und zu den packages hinzufügen:
```yaml
packages:
- .
- libs/myserviceAPI
- libs/myCoolMLServiceAPI
```
in der `package.yaml` (oder der cabal) die dependencies hinzufügen und schon haben wir die Features zur Verfügung und können gegen diese Services reden.
### Entfernen von anderen Technologien/Microservices
In git ist das entfernen von Submodules etwas frickelig, daher hier ein copy&paste der [GitHub-Antwort](https://gist.github.com/myusuf3/7f645819ded92bda6677):
```bash
## Remove the submodule entry from .git/config
git submodule deinit -f path/to/submodule
## Remove the submodule directory from the superproject's .git/modules directory
rm-rf .git/modules/path/to/submodule
## Remove the entry in .gitmodules and remove the submodule directory located at path/to/submodule
git rm-f path/to/submodule
```
Falls das nicht klappt, gibt es alternative Vorschläge unter dem Link oben.
### Woher weiss ich, was wo liegt? Dokumentation? Halloo??
Keine Panik. Ein `stack haddock --open` hilft da. Das generiert die Dokumentation für alle in der `package.yaml` (oder cabal-file) eingetragenen dependencies inkl. aller upstream-dependencies. Man bekommt also eine komplette lokale Dokumentation von allem. Geöffnet wird dann die Paket-Startseite inkl. der direkten dependencies:
Es gibt 2 wichtige Pfade im Browser:
- ...../all/index.html - hier sind alle Pakete aufgeführt
- ...../index.html - hier sind nur die direkten dependencies aufgeführt.
Wenn man einen lokalen Webserver startet kann man mittels "s" auch die interaktive Suche öffnen (Suche nach Typen, Funktionen, Signaturen, etc.). In Bash mit python3 geht das z.b. einfach über:
```bash
cd $(stack path --local-doc-root)
python3 -m SimpleHTTPServer 8000
firefox "http://localhost:8000"
```
### Implementation des Services und Start
#### Loader/Bootstrapper
Generelles Vorgehen:
- in app/Main.hs:
Hier ist quasi immer nur eine Zeile drin: `main = myServiceMain`
Grund: Applications tauchen nicht im Haddock auf. Also haben wir ein "src"-Modul, welches hier nur geladen & ausgeführt wird.
- in src/MyService.hs:
`myServiceMain :: IO ()` definieren
Für die Main kann man prinzipiell eine Main andere Services copy/pasten. Im folgenden eine Annotierte main-Funktion - zu den einzelnen Vorraussetzungen kommen wir im Anschluss.
```haskell
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
module MyService where
-- generische imports aus den dependencies/base, nicht in der prelude
import Codec.MIME.Type
import Configuration.Dotenv as Dotenv
import Control.Concurrent (forkIO, threadDelay)
import Control.Concurrent.Async
import Control.Concurrent.STM
import Control.Monad
import Control.Monad.Catch
import Control.Monad.Except
import Conversion
import Conversion.Text ()
import Data.Binary.Builder
import Data.String (IsString (..))
import Data.Time
import Data.Time.Clock
import Data.Time.Format
import Data.Default
import Network.HostName
import Network.HTTP.Client as HTTP hiding
(withConnection)
import Network.HTTP.Types (Status, statusCode)
import Network.Mom.Stompl.Client.Queue
import Network.Wai (Middleware)
import Network.Wai.Logger
import Network.Wai.Middleware.Cors
import Network.Wai.Middleware.RequestLogger (OutputFormat (..),
logStdout,
mkRequestLogger,
outputFormat)
import Servant.Client (mkClientEnv,
parseBaseUrl)
import System.Directory
import System.Envy
import System.IO
import System.Log.FastLogger
import Text.PrettyPrint.GenericPretty
-- generische imports, aber qualified, weil es sonst zu name-clashes kommt
import qualified Data.ByteString as BS
-- import qualified Data.ByteString.Char8 as BS8
import qualified Data.ByteString.Lazy as LBS
import qualified Network.HTTP.Client.TLS as UseDefaultHTTPSSettings (tlsManagerSettings)
import qualified Network.Mom.Stompl.Client.Queue as AMQ
import qualified Network.Wai as WAI
-- Handler für den MyServiceBackend-Typen und Imports aus den Libraries
import MyService.Handler as H -- handler der H.myApiEndpointV1Post implementiert
import MyService.Types -- weitere Type (s. nächste box)
import MyServiceGen.API as MS -- aus der generierten library
myServicemain :: IO ()
myServicemain = do
-- .env-Datei ins Prozess-Environment laden, falls noch nicht von außen gesetzt
void $ loadFile $ Dotenv.Config [".env"] [] False
-- Config holen (defaults + overrides aus dem Environment)
sc@ServerConfig{..} <- decodeWithDefaults defConfig
-- Backend-Setup
-- legt sowas wie Proxy-Server fest und wo man wie dran kommt. Benötigt für das Sprechen mit anderen Microservices
let defaultHTTPSSettings = UseDefaultHTTPSSettings.tlsManagerSettings { managerResponseTimeout = responseTimeoutMicro $ 1000 * 1000 * myserviceMaxTimeout }
createBackend url proxy = do
manager <- newManager . managerSetProxy proxy
$ defaultHTTPSSettings
url' <- parseBaseUrl url
return (mkClientEnv manager url')
internalProxy = case myserviceInternalProxyUrl of
"" -> noProxy
url -> useProxy $ HTTP.Proxy (fromString url) myserviceInternalProxyPort
-- externalProxy = case myserviceExternalProxyUrl of
-- "" -> noProxy
-- url -> useProxy $ HTTP.Proxy (fromString url) myserviceExternalProxyPort
-- Definieren & Erzeugen der Funktionen um die anderen Services anzusprechen.
calls <- (,)
<$> createBackend myserviceAUri internalProxy
<*> createBackend myserviceBUri internalProxy
-- Logging-Setup
hSetBuffering stdout LineBuffering
hSetBuffering stderr LineBuffering
-- Infos holen, brauchen wir später
myName <- getHostName
today <- formatTime defaultTimeLocale "%F" . utctDay <$> getCurrentTime
-- activeMQ-Transaktional-Queue zum schreiben nachher vorbereiten
amqPost <- newTQueueIO
-- bracket a b c == erst a machen, ergebnis an c als variablen übergeben. Schmeisst c ne exception/wird gekillt/..., werden die variablen an b übergeben.
bracket
-- logfiles öffnen
(LogFiles <$> openFile ("/logs/myservice-"<>myName<>"-"<>today<>".info") AppendMode
<*> openFile (if myserviceDebug then "/logs/myservice-"<>myName<>"-"<>today<>".debug" else "/dev/null") AppendMode
<*> openFile ("/logs/myservice-"<>myName<>"-"<>today<>".error") AppendMode
<*> openFile ("/logs/myservice-"<>myName<>"-"<>today<>".timings") AppendMode
)
-- und bei exception/beendigung schlißen.h
(\(LogFiles a b c d) -> mapM_ hClose [a,b,c,d])
$ \logfiles -> do
-- logschreibe-funktionen aliasen; log ist hier abstrakt, iolog spezialisiert auf io.
let log = printLogFiles logfiles :: MonadIO m => [LogItem] -> m ()
iolog = printLogFilesIO logfiles :: [LogItem] -> IO ()
-- H.myApiEndpointV1Post ist ein Handler (alle Handler werden mit alias H importiert) und in einer eigenen Datei
-- Per Default bekommen Handler sowas wie die server-config, die Funktionen um mit anderen Services zu reden, die AMQ-Queue um ins Kibana zu loggen und eine Datei-Logging-Funktion
-- Man kann aber noch viel mehr machen - z.b. gecachte Daten übergeben, eine Talk-Instanz, etc. pp.
server = MyServiceBackend{ myApiEndpointV1Post = H.myApiEndpointV1Post sc calls amqPost log
}
config = MS.Config $ "http://" ++ myserviceHost ++ ":" ++ show myservicePort ++ "/"
iolog . pure . Info $ "Using Server configuration:"
iolog . pure . Info $ pretty sc { myserviceActivemqPassword = "******" -- Do NOT log the password ;)
, myserviceMongoPassword = "******"
}
-- alle Services starten (Hintergrund-Aktionen wie z.b. einen MongoDB-Dumper, einen Talk-Server oder wie hier die ActiveMQ
void $ forkIO $ keepActiveMQConnected sc iolog amqPost
-- logging-Framework erzeugen
loggingMW <- loggingMiddleware
-- server starten
if myserviceDebug
then runMyServiceMiddlewareServer config (cors (\_ -> Just (simpleCorsResourcePolicy {corsRequestHeaders = ["Content-Type"]})) . loggingMW . logStdout) server
else runMyServiceMiddlewareServer config (cors (\_ -> Just (simpleCorsResourcePolicy {corsRequestHeaders = ["Content-Type"]}))) server
-- Sollte bald in die Library hs-stomp ausgelagert werden
-- ist ein Beispiel für einen ActiveMQ-Dumper
keepActiveMQConnected :: ServerConfig -> ([LogItem] -> IO ()) -> TQueue BS.ByteString -> IO ()
keepActiveMQConnected sc@ServerConfig{..} printLog var = do
res <- handle (\(e :: SomeException) -> do
printLog . pure . Error $ "Exception in AMQ-Thread: "<>show e
return $ Right ()
) $ AMQ.try $ do -- catches all AMQ-Exception that we can handle. All others bubble up.
printLog . pure . Info $ "AMQ: connecting..."
withConnection myserviceActivemqHost myserviceActivemqPort [ OAuth myserviceActivemqUsername myserviceActivemqPassword
, OTmo (30*1000) {- 30 sec timeout -}
]
[] $ \c -> do
let oconv = return
printLog . pure . Info $ "AMQ: connected"
withWriter c "Chaos-Logger for Kibana" "chaos.logs" [] [] oconv $ \writer -> do
printLog . pure . Info $ "AMQ: queue created"
let postfun = writeQ writer (Type (Application "json") []) []
void $ race
(forever $ atomically (readTQueue var) >>= postfun)
(threadDelay (600*1000*1000)) -- wait 10 Minutes
-- close writer
-- close connection
-- get outside of all try/handle/...-constructions befor recursing.
case res of
Left ex -> do
printLog . pure . Error $ "AMQ: "<>show ex
keepActiveMQConnected sc printLog var
Right _ -> keepActiveMQConnected sc printLog var
-- Beispiel für eine Custom-Logging-Middleware.
-- Hier werden z.B. alle 4xx-Status-Codes inkl. Payload ins stdout-Log geschrieben.
-- Nützlich, wenn die Kollegen ihre Requests nicht ordentlich schreiben können und der Server das Format zurecht mit einem BadRequest ablehnt ;)
loggingMiddleware :: IO Middleware
loggingMiddleware = liftIO $ mkRequestLogger $ def { outputFormat = CustomOutputFormatWithDetails out }
where
out :: ZonedDate -> WAI.Request -> Status -> Maybe Integer -> NominalDiffTime -> [BS.ByteString] -> Builder -> LogStr
out _ r status _ _ payload _
| statusCode status < 300 = ""
| statusCode status > 399 && statusCode status < 500 = "Error code "<>toLogStr (statusCode status) <>" sent. Request-Payload was: "<> mconcat (toLogStr <$> payload) <> "\n"
| otherwise = toLogStr (show r) <> "\n"
```
#### Weitere Instanzen und Definitionen, die der Generator (noch) nicht macht
In der `Myservice.Types` werden ein paar hilfreiche Typen und Typinstanzen definiert. Im Folgenden geht es dabei um Dinge für:
- Envy
- Laden von $ENV_VAR in Datentypen
- Definitionen für Default-Settings
- ServerConfig
- Definition der Server-Konfiguration & Benennung der Environment-Variablen
- ExtraTypes
- ggf. Paketweite extra-Typen, die der Generator nicht macht, weil sie nicht aus der API kommen (z.B. cache)
- Out/BSON-Instanzen
- Der API-Generator generiert nur wenige Instanzen automatisch (z.B. Aeson), daher werden hier die fehlenden definiert.
- BSON: Kommunakation mit MongoDB
- Out: pretty-printing im Log
```haskell
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
module MyService.Types where
import Data.Aeson (FromJSON, ToJSON)
import Data.Text
import Data.Time.Clock
import GHC.Generics
import System.Envy
import Text.PrettyPrint (text)
import Text.PrettyPrint.GenericPretty
-- Out hat hierfür keine Instanzen, daher kurz eine einfach Definition.
instance Out Text where
doc = text . unpack
docPrec i a = text $ showsPrec i a ""
instance Out UTCTime where
doc = text . show
docPrec i a = text $ showsPrec i a ""
-- Der ServerConfig-Typ. Wird mit den defaults unten initialisiert, dann mit den Variablen aus der .env-Datei überschrieben und zum Schluss können Serveradmins diese via $MYSERVICE_FOO nochmal überschreiben.
data ServerConfig = ServerConfig
{ myserviceHost :: String -- ^ Environment: $MYSERVICE_HOST
, myservicePort :: Int -- ^ Environment: $MYSERVICE_PORT
, myserviceMaxTimeout :: Int -- ^ Environment: $MYSERVICE_MAX_TIMEOUT
, myserviceInternalProxyUrl :: String -- ^ Environment: $MYSERVICE_INTERNAL_PROXY_URL
, myserviceInternalProxyPort :: Int -- ^ Environment: $MYSERVICE_INTERNAL_PROXY_PORT
, myserviceExternalProxyUrl :: String -- ^ Environment: $MYSERVICE_EXTERNAL_PROXY_URL
, myserviceExternalProxyPort :: Int -- ^ Environment: $MYSERVICE_EXTERNAL_PROXY_PORT
, myserviceActivemqHost :: String -- ^ Environment: $MYSERVICE_ACTIVEMQ_HOST
, myserviceActivemqPort :: Int -- ^ Environment: $MYSERVICE_ACTIVEMQ_PORT
, myserviceActivemqUsername :: String -- ^ Environment: $MYSERVICE_ACTIVEMQ_USERNAME
, myserviceActivemqPassword :: String -- ^ Environment: $MYSERVICE_ACTIVEMQ_PASSWORD
, myserviceMongoUsername :: String -- ^ Environment: $MYSERVICE_MONGO_USERNAME
, myserviceMongoPassword :: String -- ^ Environment: $MYSERVICE_MONGO_PASSWORD
, myserviceDebug :: Bool -- ^ Environment: $MYSERVICE_DEBUG
} deriving (Show, Eq, Generic)
-- Default-Konfigurations-Instanz für diesen Service.
instance DefConfig ServerConfig where
defConfig = ServerConfig "0.0.0.0" 8080 20
""
""
""
0
""
0
""
0
""
""
""
""
False
-- Kann auch aus dem ENV gefüllt werden
instance FromEnv ServerConfig
-- Und hübsch ausgegeben werden.
instance Out ServerConfig
instance Out Response
instance FromBSON Repsonse -- FromBSON-Instanz geht immer davon aus, dass alle keys da sind (ggf. mit null bei Nothing).
```
#### Was noch zu tun ist
Den Service implementieren. Einfach ein neues Modul aufmachen (z.B. `MyService.Handler` oder `MyService.DieserEndpunktbereich`/`MyService.JenerEndpunktbereich`) und dort die Funktion implementieren, die man in der `Main.hs` benutzt hat.
In dem Handler habt ihr dann keinen Stress mehr mit validierung, networking, logging, etc. pp. weil alles in der Main abgehandelt wurde und ihr nur noch den "Happy-Case" implementieren müsst.
Beispiel für unseren Handler oben:
```haskell
myApiEndpointV1Post :: MonadIO m => ServerConfig -> (ClientEnv,ClientEnv) -> TQueue BS.ByteString -> ([LogItem] -> IO ()) -> Request -> m Response
myApiEndpointV1Post sc calls amqPost log req = do
liftIO . log $ [Info $ "recieved "<>pretty req] -- input-logging
liftIO . atomically . writeTQueue . LBS.toStrict $ "{\"hey Kibana, i recieved:\"" <> A.encode (pretty req) <> "}" -- log in activeMQ/Kibana
--- .... gaaaanz viel komplizierter code um die Response zu erhalten ;)
let ret = Response 1337 Nothing -- dummy-response ;)
-- gegeben wir haben eine gültige mongodb-pipe;
-- mehr logik will ich in die Beispiele nicht packen.
-- Man kann die z.b. als weiteren Wert in einer TMVar (damit man sie ändern & updaten kann) an die Funktion übergeben.
liftIO . access pipe master "DatabaseName" $ do
ifM (auth (myServiceMongoUsername sc) (myServiceMongoPassword sc)) (return ()) (liftIO . printLog . pure . Error $ "MongoDB: Login failed.")
save "DatabaseCollection" ["_id" =: 1337, "entry" =: ret] -- selbe id wie oben ;)
return ret
```
Diese dummy-Antwort führt auf, wie gut man die ganzen Sachen mischen kann.
- Logging in die Dateien/stdout nach config
- Logging von Statistiker in Kibana
- Speichern der Antwort in der MongoDB
- Generieren einer Serverantwort und ausliefern dieser über die Schnittstelle
#### Tipps & Tricks
##### Dateien, die statisch ausgeliefert werden sollen
Hierzu erstellt man ein Verzeichnis `static/` (konvention; ist im generator so generiert, dass das ausgeliefert wird). Packt man hier z.b. eine `index.html` rein, erscheint die, wenn man den Service ansurft.
##### Wie bekomme ich diese fancy Preview hin?
Der Editor, der ganz am Anfang zum Einsatz gekommen ist, braucht nur die `api-doc.yml` um diese Ansicht zu erzeugen.
Daher empfielt sich hier ein angepasster Fork davon indem die Pfade in der index.html korrigiert sind. Am einfachsten (und von den meisten services so benutzt):
In meiner Implementation liegt dann nach dem starten auf http://localhost:PORT/ui/ und kann direkt dort getestet werden.
##### Wie sorge ich für bessere Warnungen, damit der Compiler meine Bugs fängt?
```bash
stack build --file-watch --ghc-options '-freverse-errors -W -Wall -Wcompat' --interleaved-output
```
Was tut das?
- `--file-watch`: automatisches (minimales) kompilieren bei dateiänderungen
- `--ghc-options`
- `-freverse-errors`: Fehlermeldungen in umgekehrter Reihenfolge (Erster Fehler ganz unten; wenig scrollen )
- `-W`: Warnungen an
- `-Wall`: Alle sinnvollen Warnungen an (im gegensatz zu `-Weverything`, was WIRKLICH alles ist )
- `-Wcompat`: Warnungen für Sachen, die in der nächsten Compilerversion kaputt brechen werden & vermieden werden sollten
- `--interleaved-output`: stack-log direkt ausgeben & nicht in dateien schreiben und die dann am ende zusammen cat\'en.
Um pro Datei Warnungen auszuschalten (z.B. weil man ganz sicher weiss, was man tut -.-): `{-# OPTIONS_GHC -Wno-whatsoever #-}` als Pragma in die Datei.
**Idealerweise sollte das Projekt keine Warnungen erzeugen.**
### Deployment
Als Beispiel sei hier ein einfaches Docker-Build mit Jenkins-CI gezeigt, weil ich das aus Gründen rumliegen hatte. Kann man analog in fast alle anderen CI übrsetzen.
#### Docker
Die angehängten Scripte gehen von einer Standard-Einrichtung aus (statische sachen in static, 2-3 händische Anpassungen auf das eigene Projekt nach auspacken). Nachher liegt dann auch unter static/version die gebaute Versionsnummer & kann abgerufen werden.
In der Dockerfile.release und der Jenkinsfile müssen noch anpassungen gemacht werden. Konkret:
- in der Dockerfile.release: alle `<<<HIER>>>`-Stellen sinnvoll befüllen
- in der Jenkinsfile die defs für "servicename" und "servicebinary" ausfüllen. Binary ist das, was bei stack exec aufgerufen wird; name ist der Image-Name für das docker-repository.
#### Jenkins
Änderungen die dann noch gemacht werden müssen:
- git-repository url anpassen
- Environment-Vars anpasses ($BRANCH = test & live haben keine zusatzdinger im docker-image-repository; ansonsten hat das image $BRANCH im namen)
Wenn das durchgebaut ist, liegt im test/live-repository ein docker-image namens `servicename:version`.
### OMG! Ich muss meine API ändern. Was mache ich nun?
1. api-doc.yml bearbeiten, wie gewünscht
2. mittels generator die Api & submodule neu generieren
3. ggf. custom Änderungen übernehmen (:Gitdiffsplit hilft)
4. Alle Compilerfehler + Warnungen in der eigentlichen Applikation fixen
5. If it comipilez, ship it! (Besser nicht ;) )

View File

@ -0,0 +1,14 @@
<section title="Embedded note" class="p-4 mx-2 mb-2 bg-white border-2 rounded-lg shadow-inner">
<details>
<summary class="flex items-center justify-center text-2xl italic bg-${theme}-50 rounded py-1 px-2 mb-3" >
<header style="display:list-item">
<a href="${ema:note:url}">
<ema:note:title />
</a>
</header>
</summary>
<div>
<apply template="/templates/components/pandoc" />
</div>
</details>
</section>

View File

@ -46,7 +46,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -725,6 +725,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -745,8 +781,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -758,6 +794,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

File diff suppressed because one or more lines are too long

Binary file not shown.

View File

@ -46,7 +46,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>

View File

@ -46,7 +46,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -802,6 +802,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -822,8 +858,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -835,6 +871,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -802,6 +802,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -822,8 +858,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -835,6 +871,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -802,6 +802,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -822,8 +858,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -835,6 +871,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>
@ -1125,7 +1203,7 @@
<span class='mr-2 text-right text-gray-600'>
</span>
<a class='flex-1 text-red-600 mavenLinkBold border-l-2 pl-2 hover:underline' href='Haskell/Webapp_Development'>
<a class='flex-1 text-red-600 mavenLinkBold border-l-2 pl-2 hover:underline' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -820,6 +820,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -840,8 +876,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -853,6 +889,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>
@ -1126,7 +1204,7 @@
<p class='mb-3'>
Stellen wir uns vor, dass wir eine Funktion schreiben, die einen String bekommt (mehrere Lines mit ACSII-Text) und dieses Wort-für-Wort rückwärts ausgeben soll. Das ist ein einfacher Einzeiler:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>module Main where
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>module Main where
import System.Environment (getArgs)
import Data.Monoid (mconcat)

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -820,6 +820,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -840,8 +876,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -853,6 +889,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -811,6 +811,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -831,8 +867,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -844,6 +880,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>
@ -1169,7 +1247,7 @@
<p class='mb-3'>
Die Idee dahinter ist, dass man Zugriffsabstraktionen über Daten verknüpfen kann. Als einfachen Datenstruktur kann man einen Record mit der entsprechenden Syntax nehmen.
</p>
<h3 id='beispiel' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Beispiel</h3><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Person = P { name :: String
<h3 id='beispiel' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Beispiel</h3><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Person = P { name :: String
, addr :: Address
, salary :: Int }
data Address = A { road :: String
@ -1207,7 +1285,7 @@ data Address = A { road :: String
</li>
</ul>
<h3 id='was-wir-gern-hätten' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Was wir gern hätten</h3><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Person = P { name :: String
<h3 id='was-wir-gern-hätten' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Was wir gern hätten</h3><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Person = P { name :: String
, addr :: Address
, salary :: Int }
-- a lens for each field
@ -1222,7 +1300,7 @@ composeL :: Lens' s1 s2 -&gt; Lens s2 a -&gt; Lens' s1 a</code></pre></div><h3 i
<p class='mb-3'>
Mit diesen Dingen (wenn wir sie hätten) könnte man dann
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Person = P { name :: String
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Person = P { name :: String
, addr :: Address
, salary :: Int }
data Address = A { road :: String
@ -1234,7 +1312,7 @@ setPostcode pc p
<p class='mb-3'>
machen und wäre fertig.
</p>
<h2 id='trivialer-ansatz' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Trivialer Ansatz</h2><h3 id='gettersetter-als-lens-methoden' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Getter/Setter als Lens-Methoden</h3><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data LensR s a = L { viewR :: s -&gt; a
<h2 id='trivialer-ansatz' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Trivialer Ansatz</h2><h3 id='gettersetter-als-lens-methoden' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Getter/Setter als Lens-Methoden</h3><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data LensR s a = L { viewR :: s -&gt; a
, setR :: a -&gt; s -&gt; s }
composeL (L v1 u1) (L v2 u2)
@ -1251,7 +1329,7 @@ composeL (L v1 u1) (L v2 u2)
<p class='mb-3'>
Auslesen traversiert die Datenstruktur, dann wird die Funktion angewendet und zum setzen wird die Datenstruktur erneut traversiert:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>over :: LensR s a -&gt; (a -&gt; a) -&gt; s -&gt; s
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>over :: LensR s a -&gt; (a -&gt; a) -&gt; s -&gt; s
over ln f s = setR l (f (viewR l s)) s</code></pre></div>
<ul class='my-3 ml-6 space-y-1 list-disc'>
@ -1260,7 +1338,7 @@ over ln f s = setR l (f (viewR l s)) s</code></pre></div>
</li>
</ul>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data LensR s a
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data LensR s a
= L { viewR :: s -&gt; a
, setR :: a -&gt; s -&gt; s
, mod :: (a-&gt;a) -&gt; s -&gt; s
@ -1273,7 +1351,7 @@ over ln f s = setR l (f (viewR l s)) s</code></pre></div>
<p class='mb-3'>
Man kann alle Monaden abstrahieren. Functor reicht schon:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data LensR s a
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data LensR s a
= L { viewR :: s -&gt; a
, setR :: a -&gt; s -&gt; s
, mod :: (a-&gt;a) -&gt; s -&gt; s
@ -1295,14 +1373,14 @@ over ln f s = setR l (f (viewR l s)) s</code></pre></div>
<p class='mb-3'>
Stellt sich raus: Die sind isomorph! Auch wenn die von den Typen her komplett anders aussehen.
</p>
<h2 id='benutzen-einer-lens-als-setter' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Benutzen einer Lens als Setter</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>set :: Lens' s a -&gt; (a -&gt; s -&gt; s)
<h2 id='benutzen-einer-lens-als-setter' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Benutzen einer Lens als Setter</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>set :: Lens' s a -&gt; (a -&gt; s -&gt; s)
set ln a s = --...umm...
--:t ln =&gt; (a -&gt; f a) -&gt; s -&gt; f s
-- =&gt; get s out of f s to return it</code></pre></div>
<p class='mb-3'>
Wir können für f einfach die “Identity”-Monade nehmen, die wir nachher wegcasten können.
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>newtype Identity a = Identity a
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>newtype Identity a = Identity a
-- Id :: a -&gt; Identity a
runIdentity :: Identity s -&gt; s
@ -1313,7 +1391,7 @@ instance Functor Identity where
<p class='mb-3'>
somit ist set einfach nur
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>set :: Lens' s a -&gt; (a -&gt; s -&gt; s)
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>set :: Lens' s a -&gt; (a -&gt; s -&gt; s)
set ln x s
= runIdentity (ls set_fld s)
where
@ -1330,7 +1408,7 @@ set ln x = runIdentity . ln (Identity . const x)</code></pre></div><h2 id='benut
Dasselbe wie Set, nur dass wir den Parameter nicht entsorgen, sondern in die mitgelieferte Funktion stopfen.
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>over :: Lens' s a -&gt; (a -&gt; a) -&gt; s -&gt; s
over ln f = runIdentity . ln (Identity . f)</code></pre></div><h2 id='benutzen-einer-lens-als-getter' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Benutzen einer Lens als Getter</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>view :: Lens' s a -&gt; (s -&gt; a)
over ln f = runIdentity . ln (Identity . f)</code></pre></div><h2 id='benutzen-einer-lens-als-getter' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Benutzen einer Lens als Getter</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>view :: Lens' s a -&gt; (s -&gt; a)
view ln s = --...umm...
--:t ln =&gt; (a -&gt; f a) -&gt; s -&gt; f s
-- =&gt; get a out of the (f s) return-value
@ -1338,7 +1416,7 @@ view ln s = --...umm...
<p class='mb-3'>
Auch hier gibt es einen netten Funktor. Wir packen das “a” einfach in das “f” und werfen das “s” am Ende weg.
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>newtype Const v a = Const v
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>newtype Const v a = Const v
getConst :: Const v a -&gt; v
getConst (Const x) = x
@ -1349,7 +1427,7 @@ instance Functor (Const v) where
<p class='mb-3'>
somit ergibt sich
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>view :: Lens' s a -&gt; (s -&gt; a)
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>view :: Lens' s a -&gt; (s -&gt; a)
view ln s
= getConst (ln Const s)
-- Const :: s -&gt; Const a s</code></pre></div>
@ -1366,7 +1444,7 @@ view ln = getConst . ln Const</code></pre></div><h2 id='lenses-bauen' class='inl
<p class='mb-3'>
Für unser Personen-Beispiel vom Anfang:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Person = P { _name :: String, _salary :: Int }
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Person = P { _name :: String, _salary :: Int }
name :: Lens' Person String
-- name :: Functor f =&gt; (String -&gt; f String)
@ -1382,7 +1460,7 @@ name elt_fn (P n s)
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>name elt_fn (P n s)
= (\n' -&gt; P n' s) &lt;$&gt; (elt_fn n)
-- | Focus | |Function|</code></pre></div><h2 id='wie-funktioniert-das-intern' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Wie funktioniert das intern?</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>view name (P {_name="Fred", _salary=100})
-- | Focus | |Function|</code></pre></div><h2 id='wie-funktioniert-das-intern' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Wie funktioniert das intern?</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>view name (P {_name="Fred", _salary=100})
-- inline view-function
= getConst (name Const (P {_name="Fred", _salary=100})
-- inline name
@ -1446,14 +1524,14 @@ name elt_fn (P n s)
<p class='mb-3'>
Der Code um die Lenses zu bauen ist für records immer Identisch:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Person = P { _name :: String, _salary :: Int }
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Person = P { _name :: String, _salary :: Int }
name :: Lens' Person String
name elt_fn (P n s) = (\n' -&gt; P n' s) &lt;$&gt; (elt_fn n)</code></pre></div>
<p class='mb-3'>
Daher kann man einfach
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>import Control.Lens.TH
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>import Control.Lens.TH
data Person = P { _name :: String, _salary :: Int }
$(makeLenses ''Person)</code></pre></div>
@ -1464,7 +1542,7 @@ $(makeLenses ''Person)</code></pre></div>
<p class='mb-3'>
Will man das aber haben, muss man selbst in den Control.Lens.TH-Code schauen.
</p>
<h2 id='lenses-für-den-beispielcode' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Lenses für den Beispielcode</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>import Control.Lens.TH
<h2 id='lenses-für-den-beispielcode' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Lenses für den Beispielcode</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>import Control.Lens.TH
data Person = P { _name :: String
, _addr :: Address
@ -1477,7 +1555,7 @@ $(makeLenses ''Person)
$(makeLenses ''Address)
setPostcode :: String -&gt; Person -&gt; Person
setPostcode pc p = set (addr . postcode) pc p</code></pre></div><h2 id='shortcuts-mit-line-noise' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Shortcuts mit “Line-Noise”</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>-- ...
setPostcode pc p = set (addr . postcode) pc p</code></pre></div><h2 id='shortcuts-mit-line-noise' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Shortcuts mit “Line-Noise”</h2><div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>-- ...
setPostcode :: String -&gt; Person -&gt; Person
setPostcode pc p = addr . postcode .~ pc $ p
@ -1493,7 +1571,7 @@ getPostcode p = p ^. $ addr . postcode
<p class='mb-3'>
Man kann mit Lenses sogar Felder emulieren, die gar nicht da sind. Angenommen folgender Code:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Temp = T { _fahrenheit :: Float }
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Temp = T { _fahrenheit :: Float }
$(makeLenses ''Temp)
-- liefert Lens: fahrenheit :: Lens Temp Float
@ -1510,7 +1588,7 @@ centigrade centi_fn (T faren)
<p class='mb-3'>
Das ganze kann man auch parametrisieren und auf Non-Record-Strukturen anwenden. Beispielhaft an einer Map verdeutlicht:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>-- from Data.Lens.At
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>-- from Data.Lens.At
at :: Ord k =&gt; k -&gt; Lens' (Map k v) (Maybe v)
-- oder identisch, wenn man die Lens' auflöst:
@ -1543,7 +1621,7 @@ at k mb_fn m
<p class='mb-3'>
Web-scraper in Package hexpat-lens
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>p ^.. _HTML' . to allNodes
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>p ^.. _HTML' . to allNodes
. traverse . named "a"
. traverse . ix "href"
. filtered isLocal
@ -1559,7 +1637,7 @@ at k mb_fn m
<p class='mb-3'>
Bisher hatten wir Lenses nur auf Funktoren F. Die nächstmächtigere Klasse ist Applicative.
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>type Traversal' s a = forall f. Applicative f
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>type Traversal' s a = forall f. Applicative f
=&gt; (a -&gt; f a) -&gt; (s -&gt; f s)</code></pre></div>
<p class='mb-3'>
Da wir den Container identisch lassen (weder s noch a wurde angefasst) muss sich etwas anderes ändern. Statt eines einzelnen Focus erhalten wir viele Foci.
@ -1568,7 +1646,7 @@ at k mb_fn m
<p class='mb-3'>
Was ist ein Applicative überhaupt? Eine schwächere Monade (nur 1x Anwendung und kein Bind - dafür kann man die beliebig oft hintereinanderhängen).
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>class Functor f =&gt; Applicative f where
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>class Functor f =&gt; Applicative f where
pure :: a -&gt; f a
(&lt;*&gt;) :: f (a -&gt; b) -&gt; f a -&gt; f b
@ -1578,7 +1656,7 @@ mf &lt;*&gt; mx = do { f &lt;- mf; x &lt;- mx; return (f x) }</code></pre></div>
<p class='mb-3'>
Recap: Was macht eine Lens:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>data Adress = A { _road :: String
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>data Adress = A { _road :: String
, _city :: String
, _postcode :: String }
@ -1588,14 +1666,14 @@ road elt_fn (A r c p) = (\r' -&gt; A r' c p) &lt;$&gt; (elt_fn r)
<p class='mb-3'>
Wenn man nun road & city gleichzeitig bearbeiten will:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>addr_strs :: Traversal' Address String
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>addr_strs :: Traversal' Address String
addr_strs elt_fn (A r c p)
= ... (\r' c' -&gt; A r' c' p) .. (elt_fn r) .. (elt_fn c) ..
-- | function with 2 "Holes"| first Thing | second Thing</code></pre></div>
<p class='mb-3'>
fmap kann nur 1 Loch stopfen, aber nicht mit n Löchern umgehen. Applicative mit &lt;*&gt; kann das.<br />Somit gibt sich
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>addr_strs :: Traversal' Address String
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>addr_strs :: Traversal' Address String
addr_strs elt_fn (A r c p)
= pure (\r' c' -&gt; A r' c' p) &lt;*&gt; (elt_fn r) &lt;*&gt; (elt_fn c)
-- lift in Appl. | function with 2 "Holes"| first Thing | second Thing
@ -1672,7 +1750,7 @@ type Lens s t a b = forall f. Functor f =&gt; (a -&gt; f b) -&gt; (s -&gt; f t)<
<p class='mb-3'>
Lens alleine definiert 39 newtypes, 34 data-types und 194 Typsynonyme…<br />Ausschnitt
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell numberLines'>-- traverseOf :: Functor f =&gt; Iso s t a b -&gt; (a -&gt; f b) -&gt; s -&gt; f t
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>-- traverseOf :: Functor f =&gt; Iso s t a b -&gt; (a -&gt; f b) -&gt; s -&gt; f t
-- traverseOf :: Functor f =&gt; Lens s t a b -&gt; (a -&gt; f b) -&gt; s -&gt; f t
-- traverseOf :: Applicative f =&gt; Traversal s t a b -&gt; (a -&gt; f b) -&gt; s -&gt; f t

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -817,7 +817,7 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
@ -825,13 +825,13 @@
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M9 12h6m-6 4h6m2 5H7a2 2 0 01-2-2V5a2 2 0 012-2h5.586a1 1 0 01.707.293l5.414 5.414a1 1 0 01.293.707V19a2 2 0 01-2 2z'>
</path>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold text-red-600 hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
<a class='font-bold text-red-600 hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
@ -843,6 +843,84 @@
-->
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>
@ -1124,7 +1202,7 @@
</p>
<h2 id='startprojekt-in-haskell' class='inline-block mt-6 mb-4 text-4xl font-bold text-gray-700 border-b-2'>Startprojekt in Haskell</h2><h3 id='erstellen-eines-neuen-projektes' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Erstellen eines neuen Projektes</h3>
<p class='mb-3'>
zunächst erstellen wir in normales Haskell-Projekt ohne funktionalität & firlefanz:
Zunächst erstellen wir in normales Haskell-Projekt ohne funktionalität & firlefanz:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='bash language-bash'>stack new myservice</code></pre></div>
<p class='mb-3'>
@ -1134,7 +1212,7 @@
ghc-options:
"$locals": -fwrite-ide-info</code></pre></div>
<p class='mb-3'>
ein. Anschließend organisieren wir uns noch eine gute <code class='py-0.5 px-0.5 bg-gray-100'>.gitignore</code> und initialisieren das git mittels <code class='py-0.5 px-0.5 bg-gray-100'>git init; git add .; git commit -m "initial scaffold"</code>
ein. Anschließend organisieren wir uns noch eine gute <code class='py-0.5 px-0.5 bg-gray-100'>.gitignore</code> und initialisieren das git mittels <code class='py-0.5 px-0.5 bg-gray-100'>git init; git add .; git commit -m "initial scaffold"</code>
</p>
<h3 id='generierung-der-api' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Generierung der API</h3>
<p class='mb-3'>
@ -1172,7 +1250,7 @@ ghc-options:
</p>
<h3 id='einbinden-anderer-microservices' class='mt-6 mb-2 text-3xl font-bold text-gray-700'>Einbinden anderer Microservices</h3>
<p class='mb-3'>
Funktioniert komplett analog zu dem vorgehen oben (ohne das generieren natürlich ;) ). <code class='py-0.5 px-0.5 bg-gray-100'>stack.yaml</code> editieren und zu den packages hinzufügen:
Funktioniert komplett analog zu dem vorgehen oben (ohne das generieren natürlich <span class='emoji' data-emoji='grin' style='font-family: emoji'>😁</span>). <code class='py-0.5 px-0.5 bg-gray-100'>stack.yaml</code> editieren und zu den packages hinzufügen:
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='yaml language-yaml'>packages:
- .
@ -1254,6 +1332,20 @@ firefox "http://localhost:8000"</code></pre></div><h3 id='implementation-des-ser
<p class='mb-3'>
Für die Main kann man prinzipiell eine Main andere Services copy/pasten. Im folgenden eine Annotierte main-Funktion - zu den einzelnen Vorraussetzungen kommen wir im Anschluss.
</p>
<section title='Embedded note' class='p-4 mx-2 mb-2 bg-white border-2 rounded-lg shadow-inner'>
<details>
<summary class='flex items-center justify-center text-2xl italic bg-red-50 rounded py-1 px-2 mb-3'>
<header style='display:list-item'>
<a href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
</header>
</summary>
<div>
<p class='mb-3'>
Wie man das verwendet, siehe <a href='Haskell/Webapp-Example' class='text-red-600 mavenLinkBold hover:underline' data-wikilink-type='WikiLinkTag'>Webapp-Development in Haskell</a>.
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
@ -1435,7 +1527,11 @@ loggingMiddleware = liftIO $ mkRequestLogger $ def { outputFormat = CustomOutput
| statusCode status &lt; 300 = ""
| statusCode status &gt; 399 && statusCode status &lt; 500 = "Error code "&lt;&gt;toLogStr (statusCode status) &lt;&gt;" sent. Request-Payload was: "&lt;&gt; mconcat (toLogStr &lt;$&gt; payload) &lt;&gt; "\n"
| otherwise = toLogStr (show r) &lt;&gt; "\n"
</code></pre></div><h4 id='weitere-instanzen-und-definitionen-die-der-generator-noch-nicht-macht' class='mt-6 mb-2 text-2xl font-bold text-gray-700'>Weitere Instanzen und Definitionen, die der Generator (noch) nicht macht</h4>
</code></pre></div>
</div>
</details>
</section>
<h4 id='weitere-instanzen-und-definitionen-die-der-generator-noch-nicht-macht' class='mt-6 mb-2 text-2xl font-bold text-gray-700'>Weitere Instanzen und Definitionen, die der Generator (noch) nicht macht</h4>
<p class='mb-3'>
In der <code class='py-0.5 px-0.5 bg-gray-100'>Myservice.Types</code> werden ein paar hilfreiche Typen und Typinstanzen definiert. Im Folgenden geht es dabei um Dinge für:
</p>
@ -1503,6 +1599,20 @@ loggingMiddleware = liftIO $ mkRequestLogger $ def { outputFormat = CustomOutput
</li>
</ul>
<section title='Embedded note' class='p-4 mx-2 mb-2 bg-white border-2 rounded-lg shadow-inner'>
<details>
<summary class='flex items-center justify-center text-2xl italic bg-red-50 rounded py-1 px-2 mb-3'>
<header style='display:list-item'>
<a href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</header>
</summary>
<div>
<p class='mb-3'>
Anleitung siehe <a href='Haskell/Webapp-Example' class='text-red-600 mavenLinkBold hover:underline' data-wikilink-type='WikiLinkTag'>Webapp-Development in Haskell</a>.
</p>
<div class='py-0.5 mb-3 text-sm'><pre><code class='haskell language-haskell'>{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-name-shadowing #-}
{-# LANGUAGE DeriveAnyClass #-}
@ -1579,7 +1689,11 @@ instance Out ServerConfig
instance Out Response
instance FromBSON Repsonse -- FromBSON-Instanz geht immer davon aus, dass alle keys da sind (ggf. mit null bei Nothing).</code></pre></div><h4 id='was-noch-zu-tun-ist' class='mt-6 mb-2 text-2xl font-bold text-gray-700'>Was noch zu tun ist</h4>
instance FromBSON Repsonse -- FromBSON-Instanz geht immer davon aus, dass alle keys da sind (ggf. mit null bei Nothing).</code></pre></div>
</div>
</details>
</section>
<h4 id='was-noch-zu-tun-ist' class='mt-6 mb-2 text-2xl font-bold text-gray-700'>Was noch zu tun ist</h4>
<p class='mb-3'>
Den Service implementieren. Einfach ein neues Modul aufmachen (z.B. <code class='py-0.5 px-0.5 bg-gray-100'>MyService.Handler</code> oder <code class='py-0.5 px-0.5 bg-gray-100'>MyService.DieserEndpunktbereich</code>/<code class='py-0.5 px-0.5 bg-gray-100'>MyService.JenerEndpunktbereich</code>) und dort die Funktion implementieren, die man in der <code class='py-0.5 px-0.5 bg-gray-100'>Main.hs</code> benutzt hat. In dem Handler habt ihr dann keinen Stress mehr mit validierung, networking, logging, etc. pp. weil alles in der Main abgehandelt wurde und ihr nur noch den “Happy-Case” implementieren müsst. Beispiel für unseren Handler oben:
</p>
@ -1609,7 +1723,7 @@ myApiEndpointV1Post sc calls amqPost log req = do
</li>
<li>
Logging von Statistiker in Kibana
Logging von Statistiken in Kibana
</li>
<li>
@ -1737,7 +1851,7 @@ myApiEndpointV1Post sc calls amqPost log req = do
</li>
<li>
If it comipilez, ship it! (Besser nicht ;) )
If it comipilez, ship it! (Besser nicht <span class='emoji' data-emoji='grin' style='font-family: emoji'>😁</span>)
</li>
</ul>
@ -1759,6 +1873,43 @@ myApiEndpointV1Post sc calls amqPost log req = do
<div class='flex flex-col lg:flex-row lg:space-x-2'>
<div class='flex-1 p-4 mt-8 bg-gray-100 rounded'>
<header class='mb-2 text-xl font-semibold text-gray-500'>Links to this page</header>
<ul class='space-y-1'>
<li>
<a class='text-red-600 mavenLinkBold hover:bg-red-50' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
<div class='mb-4 overflow-auto text-sm text-gray-500'>
<div class='pl-2 mt-2 border-l-2 border-red-200 hover:border-red-500'>
<div><p>Anleitung siehe <a href='Haskell/Webapp-Example' class='text-gray-600 font-bold hover:bg-gray-50' data-wikilink-type='WikiLinkTag'>Webapp-Development in Haskell</a>.</p></div>
</div>
</div>
</li>
<li>
<a class='text-red-600 mavenLinkBold hover:bg-red-50' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
<div class='mb-4 overflow-auto text-sm text-gray-500'>
<div class='pl-2 mt-2 border-l-2 border-red-200 hover:border-red-500'>
<div><p>Wie man das verwendet, siehe <a href='Haskell/Webapp-Example' class='text-gray-600 font-bold hover:bg-gray-50' data-wikilink-type='WikiLinkTag'>Webapp-Development in Haskell</a>.</p></div>
</div>
</div>
</li>
</ul>
</div>
</div>
<section class='flex flex-wrap items-end justify-center my-4 space-x-2 space-y-2 font-mono text-sm'>

File diff suppressed because it is too large Load Diff

File diff suppressed because it is too large Load Diff

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -806,6 +806,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -826,8 +862,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -839,6 +875,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -806,6 +806,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -826,8 +862,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -839,6 +875,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -815,6 +815,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -835,8 +871,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -848,6 +884,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -806,6 +806,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -826,8 +862,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -839,6 +875,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -815,6 +815,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -835,8 +871,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -848,6 +884,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

View File

@ -47,7 +47,7 @@
<link href='tailwind.css?instanceId=faa07eb7-0f7a-4cb2-8347-d9aa01265a0e' rel='stylesheet' type='text/css' />
<link href='tailwind.css?instanceId=e7df680a-6a6d-4eef-bcd7-f91ac333071d' rel='stylesheet' type='text/css' />
<!-- Heist error element -->
<style>
@ -795,6 +795,42 @@
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg xmlns='http://www.w3.org/2000/svg' class='w-4 h-4 flex-shrink-0 inline text-gray-700' viewBox='0 0 20 20' fill='currentColor'>
<path fill-rule='evenodd' d='M2 6a2 2 0 012-2h4l2 2h4a2 2 0 012 2v1H8a3 3 0 00-3 3v1.5a1.5 1.5 0 01-3 0V6z' clip-rule='evenodd'></path>
<path d='M6 12a2 2 0 012-2h8a2 2 0 012 2v2a2 2 0 01-2 2H2h2a2 2 0 002-2v-2z'></path>
</svg>
<a class='font-bold hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp-Example'>
Webapp-Development in Haskell
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
<!-- Variable bindings for this tree-->
@ -815,8 +851,8 @@
</svg>
<a class='hover:underline truncate' title='Webapp-Development in Haskell' href='Haskell/Webapp_Development'>
Webapp-Development in Haskell
<a class='hover:underline truncate' title='Webapp-Example: Main.hs' href='Haskell/Webapp-Example/Main.hs'>
Webapp-Example: Main.hs
</a>
@ -828,6 +864,48 @@
</div>
<!-- Variable bindings for this tree-->
<!-- Rendering of this tree -->
<div class='pl-2'>
<!-- Node's rootLabel-->
<div class='flex items-center my-2 space-x-2 justify-left'>
<svg class='w-4 h-4 flex-shrink-0 inline' fill='none' stroke='currentColor' viewBox='0 0 24 24' xmlns='http://www.w3.org/2000/svg'>
<path stroke-linecap='round' stroke-linejoin='round' stroke-width='2' d='M7 21h10a2 2 0 002-2V9.414a1 1 0 00-.293-.707l-5.414-5.414A1 1 0 0012.586 3H7a2 2 0 00-2 2v14a2 2 0 002 2z'>
</path>
</svg>
<a class='hover:underline truncate' title='Webapp-Example: MyService/Types.hs' href='Haskell/Webapp-Example/MyService_Types.hs'>
Webapp-Example: MyService/Types.hs
</a>
</div>
<!-- Node's children forest, displayed only on active trees
TODO: Use <details> to toggle visibility?
-->
</div>
</div>

File diff suppressed because one or more lines are too long