{-# LANGUAGE TemplateHaskell #-} module MonadLab.List ( listMonad ) where import Prelude hiding (Monad) import Language.Haskell.TH import MonadLab.CommonTypes listMonad :: Monad listMonad = (listTypeCon , listReturn , listBind, [(List, [merge, halt])], listBaseLift) listTypeCon :: MonadTypeCon listTypeCon = \t -> appT listT t listReturn :: ReturnExpQ listReturn = [| \v -> [v] |] listBind :: BindExpQ listBind = [| \m -> \f -> concatMap f m |] merge :: NonProperMorphismExpQ merge = [| concat |] halt :: NonProperMorphismExpQ halt = [| [] |] listBaseLift :: LiftExpQ listBaseLift = [| id |]