{-# LINE 1 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
{-# LANGUAGE CPP #-}
{- |
   Module      :  System.Win32.Info.Version
   Copyright   :  2013 shelarcy
   License     :  BSD-style

   Maintainer  :  shelarcy@gmail.com
   Stability   :  Provisional
   Portability :  Non-portable (Win32 API)

   Version information about your computer.
-}
module System.Win32.Info.Version
  ( -- * Version Info
    OSVERSIONINFOEX(..), POSVERSIONINFOEX, LPOSVERSIONINFOEX
  , ProductType(..)
  , getVersionEx, c_GetVersionEx

    -- * Verify OS version
  , isVistaOrLater, is7OrLater
  ) where
import Foreign.Ptr           ( Ptr, plusPtr )
import Foreign.Marshal.Alloc ( alloca )
import Foreign.Storable      ( Storable(..) )
import System.Win32.String   ( withTString, peekTString )
import System.Win32.Types    ( BOOL, BYTE, failIfFalse_ )
import System.Win32.Word     ( WORD, DWORD )



#include "windows_cconv.h"

----------------------------------------------------------------
-- Version Info
----------------------------------------------------------------
getVersionEx :: IO OSVERSIONINFOEX
getVersionEx =
  alloca $ \buf -> do
    ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) buf
{-# LINE 40 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
      $ sizeOf (undefined::OSVERSIONINFOEX)
    failIfFalse_ "GetVersionEx"
      $ c_GetVersionEx buf
    peek buf

data ProductType = VerUnknow BYTE | VerNTWorkStation | VerNTDomainControler | VerNTServer
    deriving (Show,Eq)

instance Storable ProductType where
    sizeOf    _ = sizeOf    (undefined::BYTE)
    alignment _ = alignment (undefined::BYTE)
    poke buf v = pokeByteOff buf 0 $ case v of
        VerUnknow w          -> w
        VerNTWorkStation     -> 1
{-# LINE 54 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        VerNTDomainControler -> 2
{-# LINE 55 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        VerNTServer          -> 3
{-# LINE 56 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
    peek buf = do
        v <- peekByteOff buf 0
        return $ case v of
            (1)       -> VerNTWorkStation
{-# LINE 60 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
            (2) -> VerNTDomainControler
{-# LINE 61 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
            (3)            -> VerNTServer
{-# LINE 62 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
            w                                 -> VerUnknow w

type POSVERSIONINFOEX = Ptr OSVERSIONINFOEX
type LPOSVERSIONINFOEX = Ptr OSVERSIONINFOEX

data OSVERSIONINFOEX = OSVERSIONINFOEX
     { dwMajorVersion    :: DWORD
     , dwMinorVersion    :: DWORD
     , dwBuildNumber     :: DWORD
     , dwPlatformId      :: DWORD
     , szCSDVersion      :: String
     , wServicePackMajor :: WORD
     , wServicePackMinor :: WORD
     , wSuiteMask        :: WORD
     , wProductType      :: ProductType
     } deriving Show

instance Storable OSVERSIONINFOEX where
    sizeOf = const (284)
{-# LINE 81 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
    alignment _ = 4
{-# LINE 82 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
    poke buf info = do
        ((\hsc_ptr -> pokeByteOff hsc_ptr 0)) buf (sizeOf info)
{-# LINE 84 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 4)) buf (dwMajorVersion info)
{-# LINE 85 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 8)) buf (dwMinorVersion info)
{-# LINE 86 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 12))  buf (dwBuildNumber info)
{-# LINE 87 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 16)) buf (dwPlatformId info)
{-# LINE 88 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        withTString (szCSDVersion info) $ \szCSDVersion' ->
          ((\hsc_ptr -> pokeByteOff hsc_ptr 20)) buf szCSDVersion'
{-# LINE 90 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 276)) buf (wServicePackMajor info)
{-# LINE 91 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 278)) buf (wServicePackMinor info)
{-# LINE 92 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 280))   buf (wSuiteMask info)
{-# LINE 93 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 282)) buf (wProductType info)
{-# LINE 94 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        ((\hsc_ptr -> pokeByteOff hsc_ptr 283))    buf (0::BYTE)
{-# LINE 95 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}

    peek buf = do
        majorVersion     <- ((\hsc_ptr -> peekByteOff hsc_ptr 4)) buf
{-# LINE 98 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        minorVersion     <- ((\hsc_ptr -> peekByteOff hsc_ptr 8)) buf
{-# LINE 99 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        buildNumber      <- ((\hsc_ptr -> peekByteOff hsc_ptr 12)) buf
{-# LINE 100 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        platformId       <- ((\hsc_ptr -> peekByteOff hsc_ptr 16)) buf
{-# LINE 101 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        cSDVersion       <- peekTString $ ((\hsc_ptr -> hsc_ptr `plusPtr` 20)) buf
{-# LINE 102 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        servicePackMajor <- ((\hsc_ptr -> peekByteOff hsc_ptr 276)) buf
{-# LINE 103 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        servicePackMinor <- ((\hsc_ptr -> peekByteOff hsc_ptr 278)) buf
{-# LINE 104 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        suiteMask        <- ((\hsc_ptr -> peekByteOff hsc_ptr 280)) buf
{-# LINE 105 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        productType      <- ((\hsc_ptr -> peekByteOff hsc_ptr 282)) buf
{-# LINE 106 "libraries\\Win32\\System\\Win32\\Info\\Version.hsc" #-}
        return $ OSVERSIONINFOEX majorVersion minorVersion
                                 buildNumber platformId cSDVersion
                                 servicePackMajor servicePackMinor
                                 suiteMask productType

foreign import WINDOWS_CCONV unsafe "windows.h GetVersionExW"
  c_GetVersionEx :: LPOSVERSIONINFOEX -> IO BOOL

----------------------------------------------------------------
-- Verify OS version
----------------------------------------------------------------
-- See: http://msdn.microsoft.com/en-us/library/windows/desktop/ms724833(v=vs.85).aspx

isVistaOrLater, is7OrLater :: IO Bool
isVistaOrLater = do
  ver <- getVersionEx
  return $ 6 <= dwMajorVersion ver

is7OrLater = do
  ver <- getVersionEx
  return $  6 <= dwMajorVersion ver
         && 1 <= dwMinorVersion ver

{-
We don't use VerifyVersionInfo function to above functions.

Because VerifyVersionInfo is more difficult than GetVersionEx and accessing field in Haskell.

-- | See: http://support.microsoft.com/kb/225013/
-- http://msdn.microsoft.com/en-us/library/windows/desktop/ms725491(v=vs.85).aspx

bIsWindowsVersionOK :: DWORD -> DWORD -> WORD -> IO BOOL
bIsWindowsVersionOK dwMajor dwMinor dwSPMajor =
  alloca $ \buf -> do
    zeroMemory buf
      (#{size OSVERSIONINFOEXW}::DWORD)
    (#poke OSVERSIONINFOEXW, dwOSVersionInfoSize) buf
      (#{size OSVERSIONINFOEXW}::DWORD)
    (#poke OSVERSIONINFOEXW, dwMajorVersion)    buf dwMajor
    (#poke OSVERSIONINFOEXW, dwMinorVersion)    buf dwMinor
    (#poke OSVERSIONINFOEXW, wServicePackMajor) buf dwSPMajor
    --  Set up the condition mask.
    let dwlConditionMask = 0
        flag =    #const VER_MAJORVERSION
             .|.  #const VER_MINORVERSION
             .|.  #const VER_SERVICEPACKMAJOR
    dwlConditionMask'   <- vER_SET_CONDITION dwlConditionMask   #{const VER_MAJORVERSION} #{const VER_GREATER_EQUAL}
    dwlConditionMask''  <- vER_SET_CONDITION dwlConditionMask'  #{const VER_MINORVERSION} #{const VER_MINORVERSION}
    dwlConditionMask''' <- vER_SET_CONDITION dwlConditionMask'' #{const VER_SERVICEPACKMAJOR} #{const VER_SERVICEPACKMAJOR}
    verifyVersionInfo buf flag dwlConditionMask'''

type ULONGLONG = DWORDLONG

foreign import capi unsafe "windows.h VER_SET_CONDITION"
  vER_SET_CONDITION :: ULONGLONG -> DWORD -> BYTE -> IO ULONGLONG

foreign import WINDOWS_CCONV unsafe "windows.h VerifyVersionInfoW"
  verifyVersionInfo :: LPOSVERSIONINFOEX -> DWORD -> DWORDLONG -> IO BOOL
-}