{-# LANGUAGE FlexibleContexts, FlexibleInstances , MultiParamTypeClasses, TemplateHaskell, UndecidableInstances #-} module AlbumEditor where import Graphics.UI.AF.WxFormAll import Maybe import AlbumDTD $(derive [''Trackref_Attrs,''Trackref,''Albumref_Attrs,''Albumref,''Notes_,''Notes_Attrs,''Notes,''Track,''Player,''Personnel,''Catalogno_Format,''Catalogno,''Location,''Coverart_Attrs,''Coverart,''Recording,''Artist,''Title,''Album]) -- Should not be neccesary, but GHC 6.6 requires it. Remove when we stop support for GHC 6.6. instance ECCreator Album someAlbum :: Album someAlbum = case createInstance of (Just a) -> a Nothing -> error "AlbumEditor: Could not create the data type" otherAlbum :: Album otherAlbum = let i :: (GInstanceCreator a) => a i = fromJust createInstance in Album (Title "The Gratefull Dead") i (Just $ Recording Nothing $ Just "Birmingham") i i i i (Notes i [Notes_Str "Foo"]) main :: IO () main = startWx "" $ do button "Dialog" albumDialog postponeAction albumDialog -- Just for the sake of creating screenshot albumDialog = settingsDialog otherAlbum -- (layoutAs dualColumn (finalDepth $ mkCom otherAlbum)) (Just (\val -> liftIO $ putStr $ "Settings: " ++ show val ++ "\n")) -- Nothing (liftIO . print) -- (\_ -> return ()) (return ())