Skip to content

Commit

Permalink
Fix call to "mandatory"
Browse files Browse the repository at this point in the history
  • Loading branch information
hsyl20 committed Jul 19, 2012
1 parent bc664ec commit 85ea79e
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 6 deletions.
8 changes: 4 additions & 4 deletions System/Posix/DynamicLinker/Template.hs
Expand Up @@ -5,7 +5,7 @@ module System.Posix.DynamicLinker.Template (
) where

import Language.Haskell.TH.Syntax
import Control.Monad (liftM, when, unless)
import Control.Monad (liftM, when, unless, liftM2)
import Data.List (nub)

import System.Posix.DynamicLinker
Expand Down Expand Up @@ -69,7 +69,7 @@ makeLoader t ss = do
let unsafePick a = fromMaybe nullFunPtr $ pick a
let notFound a = error ("Mandatory symbol \"" ++ a ++ "\" not found in " ++ lib)
let mandatory a = if isNothing (pick a) then notFound a else unsafePick a
return $ $(fmap libHandle [| dl |])
return $ $(liftM2 libHandle [| dl |] [| mandatory |])

|]
let load = FunD loadName [Clause [] (NormalB body) []]
Expand All @@ -80,8 +80,8 @@ makeLoader t ss = do
makes = map nameMake ss
loadName = transformName ("load" ++) t
mand = VarE $ Name (mkOccName "mandatory") NameS
fields = map (\(field@(Name occ _),mk) -> (field, AppE (VarE mk) (AppE mand (LitE $ StringL $ occString occ)))) $ zip ss makes
libHandle x = RecConE t ((Name (mkOccName "libHandle") NameS, x) : fields)
fields mand = map (\(field@(Name occ _),mk) -> (field, AppE (VarE mk) (AppE mand (LitE $ StringL $ occString occ)))) $ zip ss makes
libHandle dl mand = RecConE t ((Name (mkOccName "libHandle") NameS, dl) : fields mand)


nodefmsg t = "Warning: No dynamic linker method generated from the name " ++ show t
Expand Down
3 changes: 1 addition & 2 deletions Tests/Test.hs
@@ -1,6 +1,7 @@
{-# LANGUAGE TemplateHaskell #-}

module Test (
loadTestWorking
) where

import System.Posix.DynamicLinker.Template
Expand Down Expand Up @@ -31,5 +32,3 @@ $(makeDynamicLinker ''TestMissingDL)-}
}
$(makeDynamicLinker ''TestOptional)-}

main = putStrLn "Hey!"

0 comments on commit 85ea79e

Please sign in to comment.