{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE CPP #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} -- Plugin LDAP authentication for Yesod, based heavily on Yesod.Auth.Kerberos. -- Verify that your LDAP installation can bind and return LDAP objects before -- trying to use this module. -- sample manual LDAP code here -- module Yesod.Auth.LDAP ( genericAuthLDAP , LDAPConfig (..)) where #include "qq.h" import Yesod.Auth import Yesod.Auth.Message import Web.Authenticate.LDAP import LDAP import Data.Text (Text,pack,unpack) import Text.Hamlet import Yesod.Handler import Yesod.Widget import Control.Monad.IO.Class (liftIO) import Yesod.Form import Control.Applicative ((<$>), (<*>)) data LDAPConfig = LDAPConfig { -- | When a user gives username x, f(x) will be passed to LDAP usernameModifier :: Text -> Text -- | During the second bind, the username must be converted to a valid DN , nameToDN :: Text -> String -- | When a user gives username x, f(x) will be passed to Yesod , identifierModifier :: Text -> [LDAPEntry] -> Text , ldapHost :: String , ldapPort' :: LDAPInt , initDN :: String -- DN for initial binding, must have authority to search , initPass :: String -- Password for initDN , baseDN :: Maybe String -- Base DN for user search, if any , ldapScope :: LDAPScope } genericAuthLDAP :: YesodAuth m => LDAPConfig -> AuthPlugin m genericAuthLDAP config = AuthPlugin "LDAP" dispatch $ \tm -> addHamlet [QQ(hamlet)|