{-
Copyright (C) 2009-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE

-}

{- |
   Module     : Data.Convertible.Utils
   Copyright  : Copyright (C) 2009-2011 John Goerzen
   License    : BSD3

   Maintainer : John Goerzen <jgoerzen@complete.org>
   Stability  : provisional
   Portability: portable

-}

module Data.Convertible.Utils(boundedConversion,
                             convertVia
                             )
where
import Data.Convertible.Base
import Data.Typeable

{- | Utility function to perform bounds checking as part of a conversion.

Does this be examining the bounds of the destination type, converting to the type of
the source via 'safeConvert', comparing to the source value.  Results in an error
if the conversion is out of bounds. -}
boundedConversion :: (Bounded b, Show a, Show b, Convertible a Integer,
                      Convertible b Integer,
                      Typeable a, Typeable b) =>
                     (a -> ConvertResult b) -- ^ Function to do the conversion
                  -> a                      -- ^ Input data
                  -> ConvertResult b        -- ^ Result
boundedConversion :: (a -> ConvertResult b) -> a -> ConvertResult b
boundedConversion a -> ConvertResult b
func a
inp =
    do b
result <- a -> ConvertResult b
func a
inp
       let smallest :: b
smallest = b -> b -> b
forall a. a -> a -> a
asTypeOf b
forall a. Bounded a => a
minBound b
result
       let biggest :: b
biggest = b -> b -> b
forall a. a -> a -> a
asTypeOf b
forall a. Bounded a => a
maxBound b
result
       let smallest' :: Integer
smallest' = b -> Integer
forall a b. Convertible a b => a -> b
convert b
smallest :: Integer
       let biggest' :: Integer
biggest' = b -> Integer
forall a b. Convertible a b => a -> b
convert b
biggest :: Integer
       let inp' :: Integer
inp' = a -> Integer
forall a b. Convertible a b => a -> b
convert a
inp :: Integer
       if Integer
inp' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
smallest' Bool -> Bool -> Bool
|| Integer
inp' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
biggest'
          then String -> a -> ConvertResult b
forall a b.
(Show a, Typeable a, Typeable b) =>
String -> a -> ConvertResult b
convError (String
"Input value outside of bounds: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (b, b) -> String
forall a. Show a => a -> String
show (b
smallest, b
biggest))
               a
inp
          else b -> ConvertResult b
forall (m :: * -> *) a. Monad m => a -> m a
return b
result

{- | Useful for defining conversions that are implemented in terms of other
conversions via an intermediary type. Instead of:

>instance Convertible CalendarTime POSIXTime where
>    safeConvert a = do r <- safeConvert a
>                       safeConvert (r :: ClockTime)

we can now write:

>instance Convertible CalendarTime POSIXTime where
>    safeConvert = convertVia (undefined::ClockTime)

which does the same thing -- converts a CalendarTime to a ClockTime, then a
ClockTime to a POSIXTime, both using existing 'Convertible' instances.
 -}
convertVia :: (Convertible a b, Convertible b c) =>
              b                 -- ^ Dummy data to establish intermediate type - can be undefined
           -> a                 -- ^ Input value
           -> ConvertResult c   -- ^ Result
convertVia :: b -> a -> ConvertResult c
convertVia b
dummy a
inp =
    do b
r1 <- a -> ConvertResult b
forall a b. Convertible a b => a -> ConvertResult b
safeConvert a
inp
       b -> ConvertResult c
forall a b. Convertible a b => a -> ConvertResult b
safeConvert (b -> b -> b
forall a. a -> a -> a
asTypeOf b
r1 b
dummy)