Skip to content

Commit

Permalink
Prepare Elm code generator for use of AuthProtect
Browse files Browse the repository at this point in the history
Using AuthProtect to implement custom authentication for an API won't work with
servant-elm (see haskell-servant/servant-elm#11).

This change is simlilar to the one suggested in that issue, but rather than
doing nothing, it adds an Authorization header to the request (which results
in another parameter being passed into the generated API request functions
to set the header value). Elm doesn't provide a way to modify the request data
once it has been created so without this it would be impossible to set a
header.
  • Loading branch information
tekul committed Mar 14, 2017
1 parent 7e9da5f commit e62ccbd
Show file tree
Hide file tree
Showing 2 changed files with 24 additions and 3 deletions.
26 changes: 23 additions & 3 deletions code-generator/Main.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,21 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import Control.Monad (join)
import Data.Monoid ((<>))
import Data.Proxy (Proxy (Proxy))
import Data.Proxy (Proxy (Proxy))
import Data.Text (Text)
import Elm (Spec (Spec), specsToDir, toElmTypeSource, toElmDecoderSource, toElmEncoderSource)
import GHC.TypeLits (KnownSymbol)
import Servant.Elm (ElmOptions (..), defElmImports, defElmOptions, generateElmForAPIWith, UrlPrefix (Static))
import Servant.Foreign hiding (Static)

import Api.Types

Expand Down Expand Up @@ -44,5 +51,18 @@ specs =

sourceFor t = [ (toElmTypeSource t, [toElmDecoderSource t, toElmEncoderSource t]) ]

-- Add Authorization header argument to APIs with AuthProtect in them
instance (KnownSymbol sym, HasForeignType lang ftype Text, HasForeign lang ftype sublayout)
=> HasForeign lang ftype (AuthProtect sym :> sublayout) where
type Foreign ftype (AuthProtect sym :> sublayout) = Foreign ftype sublayout

foreignFor lang ftype Proxy req = foreignFor lang ftype (Proxy :: Proxy sublayout) req'
where
req' = req { _reqHeaders = HeaderArg arg : _reqHeaders req }
arg = Arg
{ _argName = PathSegment "Authorization"
, _argType = typeFor lang (Proxy :: Proxy ftype) (Proxy :: Proxy Text)
}

main :: IO ()
main = specsToDir specs "frontend/src"
1 change: 1 addition & 0 deletions my3ml.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ executable code-generator
, my3ml
, servant-elm >= 0.4
, servant-server >= 0.5
, servant-foreign >= 0.9
, text
default-language: Haskell2010

Expand Down

0 comments on commit e62ccbd

Please sign in to comment.