diff --git a/htools/Ganeti/HTools/CLI.hs b/htools/Ganeti/HTools/CLI.hs
index 11344d123feac4af47db7b876c766b17a86b6c52..e79923f1957984e2f2b083407bdf54488912c1a8 100644
--- a/htools/Ganeti/HTools/CLI.hs
+++ b/htools/Ganeti/HTools/CLI.hs
@@ -199,7 +199,7 @@ oDiskMoves = Option "" ["no-disk-moves"]
 oDiskTemplate :: OptType
 oDiskTemplate = Option "" ["disk-template"]
                 (ReqArg (\ t opts -> do
-                           dt <- dtFromString t
+                           dt <- diskTemplateFromString t
                            return $ opts { optDiskTemplate = dt }) "TEMPLATE")
                 "select the desired disk template"
 
diff --git a/htools/Ganeti/HTools/Cluster.hs b/htools/Ganeti/HTools/Cluster.hs
index b11b3d4765e69935140705e0c6f5e00bb6e2b944..57873fdc58ce5ccc0603a89157a1c83e80002633 100644
--- a/htools/Ganeti/HTools/Cluster.hs
+++ b/htools/Ganeti/HTools/Cluster.hs
@@ -724,7 +724,7 @@ solutionDescription gl (groupId, result) =
     Bad message -> [printf "Group %s: error %s" gname message]
   where grp = Container.find groupId gl
         gname = Group.name grp
-        pol = apolToString (Group.allocPolicy grp)
+        pol = allocPolicyToString (Group.allocPolicy grp)
 
 -- | From a list of possibly bad and possibly empty solutions, filter
 -- only the groups with a valid result. Note that the result will be
@@ -830,7 +830,7 @@ tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
 -- this function, whatever mode we have is just a primary change.
 failOnSecondaryChange :: (Monad m) => EvacMode -> DiskTemplate -> m ()
 failOnSecondaryChange ChangeSecondary dt =
-    fail $ "Instances with disk template '" ++ dtToString dt ++
+    fail $ "Instances with disk template '" ++ diskTemplateToString dt ++
          "' can't execute change secondary"
 failOnSecondaryChange _ _ = return ()
 
diff --git a/htools/Ganeti/HTools/Program/Hspace.hs b/htools/Ganeti/HTools/Program/Hspace.hs
index 932dc270f8c9304e02f0345db33dd1e798318147..0fc7d4dc6e1bc37d69472b5cba0b9e3235ee7a66 100644
--- a/htools/Ganeti/HTools/Program/Hspace.hs
+++ b/htools/Ganeti/HTools/Program/Hspace.hs
@@ -295,7 +295,8 @@ printISpec :: Bool -> RSpec -> SpecType -> DiskTemplate -> IO ()
 printISpec True ispec spec disk_template = do
   printKeys $ map (\(a, fn) -> (prefix ++ "_" ++ a, fn ispec)) specData
   printKeys [ (prefix ++ "_RQN", printf "%d" req_nodes) ]
-  printKeys [ (prefix ++ "_DISK_TEMPLATE", dtToString disk_template) ]
+  printKeys [ (prefix ++ "_DISK_TEMPLATE",
+               diskTemplateToString disk_template) ]
       where req_nodes = Instance.requiredNodes disk_template
             prefix = specPrefix spec
 
@@ -303,7 +304,7 @@ printISpec False ispec spec disk_template =
   printf "%s instance spec is:\n  %s, using disk\
          \ template '%s'.\n"
          (specDescription spec)
-         (formatResources ispec specData) (dtToString disk_template)
+         (formatResources ispec specData) (diskTemplateToString disk_template)
 
 -- | Prints the tiered results.
 printTiered :: Bool -> [(RSpec, Int)] -> Double
diff --git a/htools/Ganeti/HTools/QC.hs b/htools/Ganeti/HTools/QC.hs
index f8cc19b6011291243a4827e66a661401b9f8f73d..393866cfd8c08df168b777601a36882071b593f4 100644
--- a/htools/Ganeti/HTools/QC.hs
+++ b/htools/Ganeti/HTools/QC.hs
@@ -587,7 +587,7 @@ prop_Text_Load_Instance name mem dsk vcpus status
         nl = Data.Map.fromList ndx
         tags = ""
         sbal = if autobal then "Y" else "N"
-        sdt = Types.dtToString dt
+        sdt = Types.diskTemplateToString dt
         inst = Text.loadInst nl
                [name, mem_s, dsk_s, vcpus_s, status,
                 sbal, pnode, snode, sdt, tags]
diff --git a/htools/Ganeti/HTools/Simu.hs b/htools/Ganeti/HTools/Simu.hs
index ef1209f8e868c7257bb94272c2647f63d029d436..22386ff6ea9958c952e2b49595a79987888c38ce 100644
--- a/htools/Ganeti/HTools/Simu.hs
+++ b/htools/Ganeti/HTools/Simu.hs
@@ -54,7 +54,7 @@ parseDesc :: String -> Result (AllocPolicy, Int, Int, Int, Int)
 parseDesc desc =
     case sepSplit ',' desc of
       [a, n, d, m, c] -> do
-        apol <- apolFromString a `mplus` apolAbbrev a
+        apol <- allocPolicyFromString a `mplus` apolAbbrev a
         ncount <- tryRead "node count" n
         disk <- annotateResult "disk size" (parseUnit d)
         mem <- annotateResult "memory size" (parseUnit m)
diff --git a/htools/Ganeti/HTools/Text.hs b/htools/Ganeti/HTools/Text.hs
index 172d67f8087a6c50864ed4fe938c0744a41f99d9..1f20f550c948bd89a592bd95f9683e4dadc51648 100644
--- a/htools/Ganeti/HTools/Text.hs
+++ b/htools/Ganeti/HTools/Text.hs
@@ -57,7 +57,7 @@ import qualified Ganeti.HTools.Instance as Instance
 serializeGroup :: Group.Group -> String
 serializeGroup grp =
     printf "%s|%s|%s" (Group.name grp) (Group.uuid grp)
-               (apolToString (Group.allocPolicy grp))
+               (allocPolicyToString (Group.allocPolicy grp))
 
 -- | Generate group file data from a group list.
 serializeGroups :: Group.List -> String
@@ -97,7 +97,7 @@ serializeInstance nl inst =
              iname (Instance.mem inst) (Instance.dsk inst)
              (Instance.vcpus inst) (Instance.runSt inst)
              (if Instance.autoBalance inst then "Y" else "N")
-             pnode snode (dtToString (Instance.diskTemplate inst))
+             pnode snode (diskTemplateToString (Instance.diskTemplate inst))
              (intercalate "," (Instance.tags inst))
 
 -- | Generate instance file data from instance objects.
@@ -121,7 +121,7 @@ loadGroup :: (Monad m) => [String]
           -> m (String, Group.Group) -- ^ The result, a tuple of group
                                      -- UUID and group object
 loadGroup [name, gid, apol] = do
-  xapol <- apolFromString apol
+  xapol <- allocPolicyFromString apol
   return (gid, Group.create name gid xapol)
 
 loadGroup s = fail $ "Invalid/incomplete group data: '" ++ show s ++ "'"
@@ -167,7 +167,8 @@ loadInst ktn [ name, mem, dsk, vcpus, status, auto_bal, pnode, snode
                     "N" -> return False
                     _ -> fail $ "Invalid auto_balance value '" ++ auto_bal ++
                          "' for instance " ++ name
-  disk_template <- annotateResult ("Instance " ++ name) (dtFromString dt)
+  disk_template <- annotateResult ("Instance " ++ name)
+                   (diskTemplateFromString dt)
   when (sidx == pidx) $ fail $ "Instance " ++ name ++
            " has same primary and secondary node - " ++ pnode
   let vtags = sepSplit ',' tags
diff --git a/htools/Ganeti/HTools/Types.hs b/htools/Ganeti/HTools/Types.hs
index ec774b012af344b0351017497e5b86fda57d97dd..75dbce59ae2c72b4b7252bedd00c3371ad8f8ce5 100644
--- a/htools/Ganeti/HTools/Types.hs
+++ b/htools/Ganeti/HTools/Types.hs
@@ -32,8 +32,8 @@ module Ganeti.HTools.Types
     , Weight
     , GroupID
     , AllocPolicy(..)
-    , apolFromString
-    , apolToString
+    , allocPolicyFromString
+    , allocPolicyToString
     , RSpec(..)
     , DynUtil(..)
     , zeroUtil
@@ -49,8 +49,8 @@ module Ganeti.HTools.Types
     , Placement
     , IMove(..)
     , DiskTemplate(..)
-    , dtToString
-    , dtFromString
+    , diskTemplateToString
+    , diskTemplateFromString
     , MoveJob
     , JobSet
     , Result(..)
@@ -110,8 +110,8 @@ data AllocPolicy
       deriving (Show, Read, Eq, Ord, Enum, Bounded)
 
 -- | Convert a string to an alloc policy.
-apolFromString :: (Monad m) => String -> m AllocPolicy
-apolFromString s =
+allocPolicyFromString :: (Monad m) => String -> m AllocPolicy
+allocPolicyFromString s =
     case () of
       _ | s == C.allocPolicyPreferred -> return AllocPreferred
         | s == C.allocPolicyLastResort -> return AllocLastResort
@@ -119,15 +119,15 @@ apolFromString s =
         | otherwise -> fail $ "Invalid alloc policy mode: " ++ s
 
 -- | Convert an alloc policy to the Ganeti string equivalent.
-apolToString :: AllocPolicy -> String
-apolToString AllocPreferred   = C.allocPolicyPreferred
-apolToString AllocLastResort  = C.allocPolicyLastResort
-apolToString AllocUnallocable = C.allocPolicyUnallocable
+allocPolicyToString :: AllocPolicy -> String
+allocPolicyToString AllocPreferred   = C.allocPolicyPreferred
+allocPolicyToString AllocLastResort  = C.allocPolicyLastResort
+allocPolicyToString AllocUnallocable = C.allocPolicyUnallocable
 
 instance JSON.JSON AllocPolicy where
-    showJSON = JSON.showJSON . apolToString
+    showJSON = JSON.showJSON . allocPolicyToString
     readJSON s = case JSON.readJSON s of
-                   JSON.Ok s' -> apolFromString s'
+                   JSON.Ok s' -> allocPolicyFromString s'
                    JSON.Error e -> JSON.Error $
                                    "Can't parse alloc_policy: " ++ e
 
@@ -191,17 +191,17 @@ data DiskTemplate = DTDiskless
                     deriving (Show, Read, Eq, Enum, Bounded)
 
 -- | Converts a DiskTemplate to String.
-dtToString :: DiskTemplate -> String
-dtToString DTDiskless   = C.dtDiskless
-dtToString DTFile       = C.dtFile
-dtToString DTSharedFile = C.dtSharedFile
-dtToString DTPlain      = C.dtPlain
-dtToString DTBlock      = C.dtBlock
-dtToString DTDrbd8      = C.dtDrbd8
+diskTemplateToString :: DiskTemplate -> String
+diskTemplateToString DTDiskless   = C.dtDiskless
+diskTemplateToString DTFile       = C.dtFile
+diskTemplateToString DTSharedFile = C.dtSharedFile
+diskTemplateToString DTPlain      = C.dtPlain
+diskTemplateToString DTBlock      = C.dtBlock
+diskTemplateToString DTDrbd8      = C.dtDrbd8
 
 -- | Converts a DiskTemplate from String.
-dtFromString :: (Monad m) => String -> m DiskTemplate
-dtFromString s =
+diskTemplateFromString :: (Monad m) => String -> m DiskTemplate
+diskTemplateFromString s =
     case () of
       _ | s == C.dtDiskless   -> return DTDiskless
         | s == C.dtFile       -> return DTFile
@@ -212,9 +212,9 @@ dtFromString s =
         | otherwise           -> fail $ "Invalid disk template: " ++ s
 
 instance JSON.JSON DiskTemplate where
-    showJSON = JSON.showJSON . dtToString
+    showJSON = JSON.showJSON . diskTemplateToString
     readJSON s = case JSON.readJSON s of
-                   JSON.Ok s' -> dtFromString s'
+                   JSON.Ok s' -> diskTemplateFromString s'
                    JSON.Error e -> JSON.Error $
                                    "Can't parse disk_template as string: " ++ e