Skip to content
Snippets Groups Projects
Commit afd548d9 authored by koz_'s avatar koz_
Browse files

Re-introduce Safe Haskell

parent c781fc45
Branches koz/safe-haskell
No related tags found
No related merge requests found
Showing
with 24 additions and 2 deletions
{-# LANGUAGE Safe #-}
{- |
Module : Control.Monad.Cont
Copyright : (c) The University of Glasgow 2001,
......
{-# LANGUAGE Safe #-}
-- Needed because the CPSed versions of Writer and State are secretly State
-- wrappers, which don't force such constraints, even though they should legally
-- be there.
......
......@@ -2,6 +2,7 @@
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE Safe #-}
-- Needed because the CPSed versions of Writer and State are secretly State
-- wrappers, which don't force such constraints, even though they should legally
-- be there.
......
{-# LANGUAGE CPP #-}
{-# LANGUAGE Safe #-}
{- |
Module : Control.Monad.Except
Copyright : (c) Michael Weber <michael.weber@post.rwth-aachen.de> 2001,
......
{-# LANGUAGE Safe #-}
{- |
Module : Control.Monad.Identity
Copyright : (c) Andy Gill 2001,
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.RWS
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.RWS.Strict
......
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
-- Search for UndecidableInstances to see why this is needed
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.RWS.Lazy
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.RWS.Strict
......
{-# LANGUAGE Safe #-}
{- |
Module : Control.Monad.Reader
Copyright : (c) Andy Gill 2001,
......
{-# LANGUAGE Safe #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.State
......
{-# LANGUAGE Safe #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.State.Lazy
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.State.Strict
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.Trans
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.Writer
......
{-# LANGUAGE Safe #-}
-----------------------------------------------------------------------------
-- |
-- Module : Control.Monad.Writer.Strict
......
{-# LANGUAGE Safe #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment