{-# LANGUAGE DeriveDataTypeable #-}
module ForeignCall (
        ForeignCall(..), isSafeForeignCall,
        Safety(..), playSafe, playInterruptible,
        CExportSpec(..), CLabelString, isCLabelString, pprCLabelString,
        CCallSpec(..),
        CCallTarget(..), isDynamicTarget,
        CCallConv(..), defaultCCallConv, ccallConvToInt, ccallConvAttribute,
        Header(..), CType(..),
    ) where
import GhcPrelude
import FastString
import Binary
import Outputable
import Module
import BasicTypes ( SourceText, pprWithSourceText )
import Data.Char
import Data.Data
newtype ForeignCall = CCall CCallSpec
  deriving Eq
isSafeForeignCall :: ForeignCall -> Bool
isSafeForeignCall (CCall (CCallSpec _ _ safe)) = playSafe safe
instance Outputable ForeignCall where
  ppr (CCall cc)  = ppr cc
data Safety
  = PlaySafe            
                        
                        
                        
                        
                        
  | PlayInterruptible   
                        
                        
                        
  | PlayRisky           
                        
  deriving ( Eq, Show, Data )
        
instance Outputable Safety where
  ppr PlaySafe = text "safe"
  ppr PlayInterruptible = text "interruptible"
  ppr PlayRisky = text "unsafe"
playSafe :: Safety -> Bool
playSafe PlaySafe = True
playSafe PlayInterruptible = True
playSafe PlayRisky = False
playInterruptible :: Safety -> Bool
playInterruptible PlayInterruptible = True
playInterruptible _ = False
data CExportSpec
  = CExportStatic               
        SourceText              
                                
        CLabelString            
        CCallConv
  deriving Data
data CCallSpec
  =  CCallSpec  CCallTarget     
                CCallConv       
                Safety
  deriving( Eq )
data CCallTarget
  
  = StaticTarget
        SourceText                
                                  
        CLabelString                    
        (Maybe UnitId)              
                                        
                                        
                                        
                                        
                                        
                                        
  
  
        Bool                            
                                        
                                        
  | DynamicTarget
  deriving( Eq, Data )
isDynamicTarget :: CCallTarget -> Bool
isDynamicTarget DynamicTarget = True
isDynamicTarget _             = False
data CCallConv = CCallConv | CApiConv | StdCallConv | PrimCallConv | JavaScriptCallConv
  deriving (Eq, Data)
instance Outputable CCallConv where
  ppr StdCallConv = text "stdcall"
  ppr CCallConv   = text "ccall"
  ppr CApiConv    = text "capi"
  ppr PrimCallConv = text "prim"
  ppr JavaScriptCallConv = text "javascript"
defaultCCallConv :: CCallConv
defaultCCallConv = CCallConv
ccallConvToInt :: CCallConv -> Int
ccallConvToInt StdCallConv = 0
ccallConvToInt CCallConv   = 1
ccallConvToInt CApiConv    = panic "ccallConvToInt CApiConv"
ccallConvToInt (PrimCallConv {}) = panic "ccallConvToInt PrimCallConv"
ccallConvToInt JavaScriptCallConv = panic "ccallConvToInt JavaScriptCallConv"
ccallConvAttribute :: CCallConv -> SDoc
ccallConvAttribute StdCallConv       = text "__attribute__((__stdcall__))"
ccallConvAttribute CCallConv         = empty
ccallConvAttribute CApiConv          = empty
ccallConvAttribute (PrimCallConv {}) = panic "ccallConvAttribute PrimCallConv"
ccallConvAttribute JavaScriptCallConv = panic "ccallConvAttribute JavaScriptCallConv"
type CLabelString = FastString          
pprCLabelString :: CLabelString -> SDoc
pprCLabelString lbl = ftext lbl
isCLabelString :: CLabelString -> Bool  
isCLabelString lbl
  = all ok (unpackFS lbl)
  where
    ok c = isAlphaNum c || c == '_' || c == '.'
        
        
instance Outputable CExportSpec where
  ppr (CExportStatic _ str _) = pprCLabelString str
instance Outputable CCallSpec where
  ppr (CCallSpec fun cconv safety)
    = hcat [ whenPprDebug callconv, ppr_fun fun ]
    where
      callconv = text "{-" <> ppr cconv <> text "-}"
      gc_suf | playSafe safety = text "_GC"
             | otherwise       = empty
      ppr_fun (StaticTarget st _fn mPkgId isFun)
        = text (if isFun then "__pkg_ccall"
                         else "__pkg_ccall_value")
       <> gc_suf
       <+> (case mPkgId of
            Nothing -> empty
            Just pkgId -> ppr pkgId)
       <+> (pprWithSourceText st empty)
      ppr_fun DynamicTarget
        = text "__dyn_ccall" <> gc_suf <+> text "\"\""
data Header = Header SourceText FastString
    deriving (Eq, Data)
instance Outputable Header where
    ppr (Header st h) = pprWithSourceText st (doubleQuotes $ ppr h)
data CType = CType SourceText 
                   (Maybe Header) 
                   (SourceText,FastString) 
    deriving (Eq, Data)
instance Outputable CType where
    ppr (CType stp mh (stct,ct))
      = pprWithSourceText stp (text "{-# CTYPE") <+> hDoc
        <+> pprWithSourceText stct (doubleQuotes (ftext ct)) <+> text "#-}"
        where hDoc = case mh of
                     Nothing -> empty
                     Just h -> ppr h
instance Binary ForeignCall where
    put_ bh (CCall aa) = put_ bh aa
    get bh = do aa <- get bh; return (CCall aa)
instance Binary Safety where
    put_ bh PlaySafe = do
            putByte bh 0
    put_ bh PlayInterruptible = do
            putByte bh 1
    put_ bh PlayRisky = do
            putByte bh 2
    get bh = do
            h <- getByte bh
            case h of
              0 -> do return PlaySafe
              1 -> do return PlayInterruptible
              _ -> do return PlayRisky
instance Binary CExportSpec where
    put_ bh (CExportStatic ss aa ab) = do
            put_ bh ss
            put_ bh aa
            put_ bh ab
    get bh = do
          ss <- get bh
          aa <- get bh
          ab <- get bh
          return (CExportStatic ss aa ab)
instance Binary CCallSpec where
    put_ bh (CCallSpec aa ab ac) = do
            put_ bh aa
            put_ bh ab
            put_ bh ac
    get bh = do
          aa <- get bh
          ab <- get bh
          ac <- get bh
          return (CCallSpec aa ab ac)
instance Binary CCallTarget where
    put_ bh (StaticTarget ss aa ab ac) = do
            putByte bh 0
            put_ bh ss
            put_ bh aa
            put_ bh ab
            put_ bh ac
    put_ bh DynamicTarget = do
            putByte bh 1
    get bh = do
            h <- getByte bh
            case h of
              0 -> do ss <- get bh
                      aa <- get bh
                      ab <- get bh
                      ac <- get bh
                      return (StaticTarget ss aa ab ac)
              _ -> do return DynamicTarget
instance Binary CCallConv where
    put_ bh CCallConv = do
            putByte bh 0
    put_ bh StdCallConv = do
            putByte bh 1
    put_ bh PrimCallConv = do
            putByte bh 2
    put_ bh CApiConv = do
            putByte bh 3
    put_ bh JavaScriptCallConv = do
            putByte bh 4
    get bh = do
            h <- getByte bh
            case h of
              0 -> do return CCallConv
              1 -> do return StdCallConv
              2 -> do return PrimCallConv
              3 -> do return CApiConv
              _ -> do return JavaScriptCallConv
instance Binary CType where
    put_ bh (CType s mh fs) = do put_ bh s
                                 put_ bh mh
                                 put_ bh fs
    get bh = do s  <- get bh
                mh <- get bh
                fs <- get bh
                return (CType s mh fs)
instance Binary Header where
    put_ bh (Header s h) = put_ bh s >> put_ bh h
    get bh = do s <- get bh
                h <- get bh
                return (Header s h)