aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorIgor Pashev <pashev.igor@gmail.com>2017-08-13 14:18:31 +0300
committerIgor Pashev <pashev.igor@gmail.com>2017-08-13 14:18:31 +0300
commitd2bb4ed0ad547247f6deec755855b48111111a49 (patch)
treeda854f71d0b335fd4d18fe6a1684a570a459d8d6
parentcc2e850e39bf99d82323052fc7c7e0faadd30e7d (diff)
downloadldapply-d2bb4ed0ad547247f6deec755855b48111111a49.tar.gz
Use hindent
-rw-r--r--.hindent.yaml3
-rw-r--r--src/Main.hs116
2 files changed, 64 insertions, 55 deletions
diff --git a/.hindent.yaml b/.hindent.yaml
new file mode 100644
index 0000000..3dba089
--- /dev/null
+++ b/.hindent.yaml
@@ -0,0 +1,3 @@
+indent-size: 2
+line-length: 80
+force-trailing-newline: true
diff --git a/src/Main.hs b/src/Main.hs
index deae4c2..3d76f38 100644
--- a/src/Main.hs
+++ b/src/Main.hs
@@ -1,36 +1,45 @@
{-# LANGUAGE QuasiQuotes #-}
-module Main (
- main
-) where
+
+module Main
+ ( main
+ ) where
import Data.ByteString.Char8 (unpack)
import Data.Char (toLower)
import Data.HashMap.Strict (fromListWith, toList)
import Data.Maybe (fromJust, fromMaybe)
import Data.Version (showVersion)
-import LDAP.Init (ldapSimpleBind, ldapExternalSaslBind, ldapInitialize)
-import LDAP.Modify (LDAPMod(..), LDAPModOp(..), ldapAdd, ldapDelete, ldapModify, list2ldm)
-import LDAP.Search (LDAPScope(LdapScopeBase), SearchAttributes(LDAPAllUserAttrs), LDAPEntry(..), ldapSearch)
+import LDAP.Init
+ (ldapExternalSaslBind, ldapInitialize, ldapSimpleBind)
+import LDAP.Modify
+ (LDAPMod(..), LDAPModOp(..), ldapAdd, ldapDelete, ldapModify,
+ list2ldm)
+import LDAP.Search
+ (LDAPEntry(..), LDAPScope(LdapScopeBase),
+ SearchAttributes(LDAPAllUserAttrs), ldapSearch)
import LDAP.Types (LDAP)
import Paths_ldapply (version) -- from cabal
+import qualified System.Console.Docopt.NoTH as O
import System.Environment (getArgs)
import System.Exit (die)
import System.IO (IOMode(ReadMode), hGetLine, hIsEOF, withFile)
import Text.InterpolatedString.Perl6 (qc)
import Text.LDIF.Parser (defaulLDIFConf, parseLDIFFile)
import Text.LDIF.Printer (dn2str)
-import Text.LDIF.Types (Attribute(..), Value(..), Change(..), LDIF(..), LDIFRecord(..), Modify(..), reDN)
-import qualified System.Console.Docopt.NoTH as O
+import Text.LDIF.Types
+ (Attribute(..), Change(..), LDIF(..), LDIFRecord(..), Modify(..),
+ Value(..), reDN)
{--
TODO:
1. Streaming from stdin (good for large amount of LDIF data)
--}
-
usage :: String
usage =
- "ldapply " ++ showVersion version ++
- " - LDIF dempotent apply tool" ++ [qc|
+ "ldapply " ++
+ showVersion version ++
+ " - LDIF dempotent apply tool" ++
+ [qc|
Usage:
ldapply [options] LDIF...
@@ -48,103 +57,101 @@ Options:
If option -w is given, -y is ignored.
|]
-
main :: IO ()
main = do
doco <- O.parseUsageOrExit usage
args <- O.parseArgsOrExit doco =<< getArgs
if args `O.isPresent` O.longOption "help"
- then putStrLn $ O.usage doco
- else do
- let
- ldifs = O.getAllArgs args $ O.argument "LDIF"
- ldapUrl = fromJust $ O.getArg args $ O.shortOption 'H'
- simple = O.isPresent args $ O.shortOption 'x'
- binddn = fromMaybe "" $ O.getArg args $ O.shortOption 'D'
- passwd = O.getArg args $ O.shortOption 'w'
- passwdfile = O.getArg args $ O.shortOption 'y'
- ldap <- ldapInitialize ldapUrl
- if simple then simpleBind ldap binddn passwd passwdfile
- else ldapExternalSaslBind ldap binddn
- mapM_ (processLDIF ldap) ldifs
-
+ then putStrLn $ O.usage doco
+ else do
+ let ldifs = O.getAllArgs args $ O.argument "LDIF"
+ ldapUrl = fromJust $ O.getArg args $ O.shortOption 'H'
+ simple = O.isPresent args $ O.shortOption 'x'
+ binddn = fromMaybe "" $ O.getArg args $ O.shortOption 'D'
+ passwd = O.getArg args $ O.shortOption 'w'
+ passwdfile = O.getArg args $ O.shortOption 'y'
+ ldap <- ldapInitialize ldapUrl
+ if simple
+ then simpleBind ldap binddn passwd passwdfile
+ else ldapExternalSaslBind ldap binddn
+ mapM_ (processLDIF ldap) ldifs
simpleBind :: LDAP -> String -> Maybe String -> Maybe FilePath -> IO ()
-simpleBind ldap bdn (Just pwd) _ = ldapSimpleBind ldap bdn pwd
-simpleBind ldap bdn Nothing Nothing = ldapSimpleBind ldap bdn ""
+simpleBind ldap bdn (Just pwd) _ = ldapSimpleBind ldap bdn pwd
+simpleBind ldap bdn Nothing Nothing = ldapSimpleBind ldap bdn ""
simpleBind ldap bdn Nothing (Just f) = do
- pwd <- withFile f ReadMode $ \h -> do
- empty <- hIsEOF h
- if empty then return "" else hGetLine h
+ pwd <-
+ withFile f ReadMode $ \h -> do
+ empty <- hIsEOF h
+ if empty
+ then return ""
+ else hGetLine h
ldapSimpleBind ldap bdn pwd
-
processLDIF :: LDAP -> FilePath -> IO ()
processLDIF ldap f = do
p <- parseLDIFFile defaulLDIFConf f
case p of
- Left err -> die $ show err
+ Left err -> die $ show err
Right (LDIF _ rs) -> mapM_ (apply ldap) rs
-
apply :: LDAP -> LDIFRecord -> IO ()
apply ldap rec = do
putStrLn $ "looking for " ++ show (dn rec)
- entries <- ldapSearch ldap (Just $ dn rec) LdapScopeBase Nothing LDAPAllUserAttrs False
+ entries <-
+ ldapSearch ldap (Just $ dn rec) LdapScopeBase Nothing LDAPAllUserAttrs False
case entries of
- [] -> do
+ [] -> do
putStrLn $ "not found " ++ show (dn rec)
update ldap Nothing rec
[e] -> do
putStrLn $ "found " ++ show (dn rec)
update ldap (Just e) rec
- _ -> die $ "internal error: too many entries in response (only 1 or 0 expected): "
- ++ show (length entries)
-
+ _ ->
+ die $
+ "internal error: too many entries in response (only 1 or 0 expected): " ++
+ show (length entries)
update :: LDAP -> Maybe LDAPEntry -> LDIFRecord -> IO ()
update _ Nothing (ChangeRecord _ ChangeDelete) = return ()
-
update _ Nothing rec@(ChangeRecord _ _) =
die $ "cannot update non-existing entry " ++ show (dn rec)
-
-update ldap (Just _) rec@(ChangeRecord _ ch)= do
+update ldap (Just _) rec@(ChangeRecord _ ch) = do
putStrLn $ "modifing " ++ show (dn rec)
change ldap (dn rec) ch
-
update ldap Nothing rec@(ContentRecord _ av) = do
putStrLn $ "adding " ++ show (dn rec)
ldapAdd ldap (dn rec) . list2ldm LdapModAdd . collect $ av
-
-update ldap (Just (LDAPEntry _ attrs)) rec@(ContentRecord _ av)= do
+update ldap (Just (LDAPEntry _ attrs)) rec@(ContentRecord _ av) = do
putStrLn $ "replacing " ++ show (dn rec)
ldapModify ldap (dn rec) (replace ++ delete)
where
replace = list2ldm LdapModReplace newAttrs
delete = list2ldm LdapModDelete oldAttrs
newAttrs = collect av
- oldAttrs = [ a | a@(v, _) <- attrs, notElem (low v) $ map fst newAttrs ]
-
+ oldAttrs = [a | a@(v, _) <- attrs, notElem (low v) $ map fst newAttrs]
change :: LDAP -> String -> Change -> IO ()
-change _ _ ChangeModDN = die "modrdn is not supported"
-change ldap n (ChangeAdd av) = ldapModify ldap n . list2ldm LdapModAdd . collect $ av
+change _ _ ChangeModDN = die "modrdn is not supported"
+change ldap n (ChangeAdd av) =
+ ldapModify ldap n . list2ldm LdapModAdd . collect $ av
change ldap n (ChangeModify m) = ldapModify ldap n . map mod2mod $ m
-change ldap n ChangeDelete = ldapDelete ldap n
+change ldap n ChangeDelete = ldapDelete ldap n
mod2mod :: Modify -> LDAPMod
-mod2mod (ModAdd a vv) = LDAPMod LdapModAdd (attr2str a) (map val2str vv)
-mod2mod (ModDelete a vv) = LDAPMod LdapModDelete (attr2str a) (map val2str vv)
+mod2mod (ModAdd a vv) = LDAPMod LdapModAdd (attr2str a) (map val2str vv)
+mod2mod (ModDelete a vv) = LDAPMod LdapModDelete (attr2str a) (map val2str vv)
mod2mod (ModReplace a vv) = LDAPMod LdapModReplace (attr2str a) (map val2str vv)
collect :: [(Attribute, Value)] -> [(String, [String])]
-collect = toList . fromListWith (++) . map (\(a, v) -> (attr2str a, [val2str v]))
+collect =
+ toList . fromListWith (++) . map (\(a, v) -> (attr2str a, [val2str v]))
attr2str :: Attribute -> String
attr2str (Attribute a) = low . unpack $ a
val2str :: Value -> String
-val2str (Value v) = unpack v
+val2str (Value v) = unpack v
val2str (ValueI v) = unpack v
dn :: LDIFRecord -> String
@@ -152,4 +159,3 @@ dn = unpack . dn2str . reDN
low :: String -> String
low = map toLower
-