vidéo peertube - vidéo youtube - dépôt git - article linuxfr.org

Développement web frontend en Haskell, Elm et Purescript

Actuellement, le développement web côté-client (frontend) est très souvent réalisé en JavaScript ou dans des langages dérivés comme TypeScript. Il existe cependant d’autres outils intéressants, basés sur des langages de programmation fonctionnelle, qui permettent notamment d’éviter de nombreuses erreurs lors de l’exécution sur le navigateur.

L’objectif de ce tutoriel est de rappeler quelques généralités sur le développement web frontend, et de présenter les outils Elm, Purescript, Miso et Reflex, à partir d’un exemple d’application (gallerie d’images fournie via une API web).

Attention : ceci n’est pas d’une étude rigoureuse et avancée mais juste un petit retour de petite expérience.

Généralités sur le web frontend

Page web, application native, application web

exemple d’application native (libreoffice) :

exemple d’application web (google-docs) :

exemple d’application Electron (atom) :

Les langages en frontend

Haskell et le frontend

Fonctionnement des frameworks web fonctionnels

crédit : Ossi Hanhinen

crédit : André Staltz

crédit : Naukri Engineering

Projet d’exemple

Elm

Présentation de Elm

Projet d’exemple en Elm

module Main exposing (..)

import Html exposing (..)
import Html.Attributes exposing (height, href, src, width)
import Html.Events exposing (onClick, onInput)
import Http
import Json.Decode as JD

main : Program Never Model Msg
main = Html.program
        { init = init
        , view = view
        , update = update
        , subscriptions = subscriptions
        }

-- Model

type alias Animal = 
  { animalType : String 
  , animalImage : String
  }

decodeAnimal : JD.Decoder Animal
decodeAnimal = JD.map2 Animal
        (JD.field "animalType" JD.string)
        (JD.field "animalImage" JD.string)

decodeAnimalList : JD.Decoder (List Animal)
decodeAnimalList = JD.list decodeAnimal

type alias Model = { modelAnimals : List Animal }

init : ( Model, Cmd Msg )
init = ( Model [], queryAnimals "" )

-- Controler

subscriptions : Model -> Sub Msg
subscriptions _ = Sub.none

type Msg 
  = MsgInput String 
  | MsgAnimals (Result Http.Error (List Animal))

update : Msg -> Model -> ( Model, Cmd Msg )
update msg model =
    case msg of
        MsgInput animalType -> ( model, queryAnimals animalType )
        MsgAnimals (Ok Model animals) -> ( Model animals, Cmd.none )
        MsgAnimals (Err _) -> ( Model [], Cmd.none )

queryAnimals : String -> Cmd Msg
queryAnimals txt =
    let url = "http://localhost:3000/api/animals/" ++ txt
    in Http.send MsgAnimals (Http.get url decodeAnimalList)

-- View

view model =
    span [] [ h1 [] [ text "Animals (Elm)" ]
            , p [] [ input [ onInput MsgInput ] [] ]
            , span []
                (List.map
                    (\a -> div [] [ p [] [ text a.animalType ]
                                  , img
                                    [ src ("http://localhost:3000/img/" ++ a.animalImage)
                                    , height 240
                                    , width 320
                                    ]
                                    []
                                  ]
                    ) model.modelAnimals
                )
            ]

Conclusion sur Elm

Purescript

Présentation de Purescript

Projet d’exemple en Purescript

module Main where

import Control.Monad.Aff (Aff)
import Control.Monad.Eff (Eff)
import Data.Argonaut ((.?), class DecodeJson, decodeJson, Json)
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Data.Traversable (traverse)
import Halogen as H
import Halogen.Aff as HA
import Halogen.HTML as HH
import Halogen.HTML.Events as HE
import Halogen.HTML.Properties as HP
import Halogen.VDom.Driver (runUI)
import Network.HTTP.Affjax as AX
import Prelude

main :: Eff (HA.HalogenEffects (ajax :: AX.AJAX)) Unit
main = HA.runHalogenAff do
    body <- HA.awaitBody
    io <- runUI ui unit body
    io.query $ H.action $ QueryAnimals ""

ui :: forall eff. H.Component HH.HTML Query Unit Void (Aff (ajax :: AX.AJAX | eff))
ui = H.component
    { initialState: const initialState
    , render
    , eval
    , receiver: const Nothing
    }

-- Model

newtype Animal = Animal
  { animalType :: String
  , animalImage :: String
  } 

instance decodeJsonBlogPost :: DecodeJson Animal where
  decodeJson json = do
    obj <- decodeJson json
    animalType <- obj .? "animalType"
    animalImage <- obj .? "animalImage"
    pure $ Animal { animalType, animalImage }

decodeAnimalArray :: Json -> Either String (Array Animal)
decodeAnimalArray json = decodeJson json >>= traverse decodeJson

type Model = { modelAnimals :: Array Animal }

initialState :: Model
initialState = { modelAnimals: [] }

-- Controler

data Query a = QueryAnimals String a

eval :: forall eff. Query ~> H.ComponentDSL Model Query Void (Aff (ajax :: AX.AJAX | eff))
eval (QueryAnimals animal_type next) = do
    H.modify (_ { modelAnimals = [] })
    response <- H.liftAff $ AX.get ("http://localhost:3000/api/animals/" <> animal_type)
    let animals = case decodeAnimalArray response.response of
                    Left _ -> []
                    Right ra -> ra
    H.modify (_ { modelAnimals = animals })
    pure next

-- View

render :: Model -> H.ComponentHTML Query
render m =
    HH.span []
        [ HH.h1 [] [ HH.text "Animals (Purescript)" ]
        , HH.p [] [ HH.input [ HE.onValueInput (HE.input QueryAnimals) ] ]
        , HH.span [] 
            (map (\ (Animal {animalType, animalImage}) 
                  -> HH.div [] 
                        [ HH.p [] [ HH.text animalType ]
                        , HH.img [ HP.src ("http://localhost:3000/img/" <> animalImage)
                                 , HP.width 320
                                 , HP.height 240
                                 ]
                        ]
                 ) m.modelAnimals)
         ]

Conclusion sur Purescript

Haskell/Miso

Présentation de Miso

Projet d’exemple en Miso

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}

import Data.Aeson (FromJSON, decodeStrict)
import Data.Maybe (fromMaybe)
import Data.Monoid ((<>))
import Data.Text (Text)
import GHC.Generics (Generic)
import JavaScript.Web.XMLHttpRequest (Request(..), RequestData(..), Method(..), contents, xhrByteString)
import Miso
import Miso.String (MisoString, toMisoString, fromMisoString, pack)

main :: IO ()
main = startApp App 
    { model = Model []
    , update = updateModel
    , view = viewModel
    , subs = []
    , events = defaultEvents
    , initialAction = GetAnimals ""
    , mountPoint = Nothing
    }

-- Model

data Animal = Animal 
    { animalType :: Text
    , animalImage :: Text
    } deriving (Eq, Generic, Show)

instance FromJSON Animal

data Model = Model { modelAnimals :: [Animal] } deriving (Eq, Show)

-- Controler

data Action 
    = GetAnimals MisoString 
    | SetAnimals [Animal]
    | NoOp 
    deriving (Show, Eq)

updateModel :: Action -> Model -> Effect Action Model
updateModel (GetAnimals str) m = m <# (SetAnimals <$> queryAnimals str)
updateModel (SetAnimals animals) m = noEff m { modelAnimals = animals }
updateModel NoOp m = noEff m

queryAnimals :: MisoString -> IO [Animal]
queryAnimals str = do
    let uri = pack $ "http://localhost:3000/api/animals/" ++ fromMisoString str
        req = Request GET uri Nothing [] False NoData
    Just cont <- contents <$> xhrByteString req
    return $ fromMaybe [] $ decodeStrict cont

-- View

viewModel :: Model -> View Action
viewModel (Model animals) = 
    span_ []
        [ h1_ [] [ text "Animals (Miso)" ]
        , p_ [] [ input_ [ onInput GetAnimals ] ]
        , span_ [] $ map fmtAnimal animals
        ]

fmtAnimal :: Animal -> View Action
fmtAnimal animal = 
    div_ [] 
        [ p_ [] [ text $ toMisoString $ animalType animal ]
        , img_ [ src_ $ toMisoString $ "http://localhost:3000/img/" <> animalImage animal
               , width_ "320"
               , height_ "240"
               ]
        ]

Conclusion sur Miso

Haskell/Reflex

Présentation de Reflex

Projet d’exemple en Reflex

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

import Data.Aeson (FromJSON)
import Data.Default (def)
import Data.Maybe (fromJust)
import Data.Monoid ((<>))
import Data.Text (Text)
import GHC.Generics (Generic)
import Prelude
import Reflex (holdDyn)
import Reflex.Dom 
import Reflex.Dom.Xhr (decodeXhrResponse, performRequestAsync, XhrRequest(..))

main :: IO ()
main = mainWidget ui

-- Model

data Animal = Animal 
    { animalType :: Text
    , animalImage :: Text
    } deriving (Eq, Generic, Show)

instance FromJSON Animal

-- View / Controler

ui :: MonadWidget t m => m ()
ui = do
    el "h1" $ text "Animals (Reflex)"
    myInput <- el "p" $ textInput def
    evStart <- getPostBuild
    let evs = [ () <$ _textInput_input myInput , evStart ]
    let evCode = tagPromptlyDyn (value myInput) (leftmost evs)
    evResponse <- performRequestAsync $ queryAnimals <$> evCode
    let evResult = fromJust . decodeXhrResponse <$> evResponse
    dynAnimals :: (Dynamic t [Animal]) <- holdDyn [] evResult 
    _ <- el "span" $ simpleList dynAnimals displayAnimal
    return ()

queryAnimals :: Text -> XhrRequest ()
queryAnimals code = XhrRequest "GET" ("http://localhost:3000/api/animals/" <> code) def

displayAnimal :: MonadWidget t m => Dynamic t Animal -> m ()
displayAnimal dynAnimal = do
    let imgSrc = (<>) "http://localhost:3000/img/" . animalImage <$> dynAnimal
    let imgAttrs0 = ("width" =: "320") <> ("height" =: "240")
    let imgAttrs = ((<>) imgAttrs0) . (=:) "src" <$> imgSrc
    el "div" $ do
        el "p" $ dynText $ animalType <$> dynAnimal
        elDynAttr "img" imgAttrs $ dynText imgSrc

Conclusion sur Reflex

Conclusion sur le web frontend en fonctionnel