Many of us don\'t have a background on functional programming, and much less on category theory algebra. So let\'s suppose that we need and therefore create a generic type like<
In my experience, the easiest way to find out and simultaneously build an intuition for monads is to just try to implement return and (>>=) for your type and verify that they satisfy the monad laws.
You should be on the lookout if you end up writing any operations that have signatures that look like any of these—or just as importantly, if you have a number of functions that can be refactored to use them:
----- Functor -----
-- Apply a one-place function "inside" `MySomething`.
fmap :: (a -> b) -> MySomething a -> MySomething b
----- Applicative -----
-- Apply an n-place function to the appropriate number and types of 
-- `MySomething`s:
lift :: (a -> ... -> z) -> MySomething a -> ... -> MySomething z
-- Combine multiple `MySomething`s into just one that contains the data of all
-- them, combined in some way.  It doesn't need to be a pair—it could be any 
-- record type.
pair :: MySomething a -> ... -> MySomething z -> MySomething (a, ..., z)
-- Some of your things act like functions, and others like their arguments.
apply :: MySomething (a -> b) -> MySomething a -> MySomething b
-- You can turn any unadorned value into a `MySomething` parametrized by
-- the type
pure :: a -> MySomething a
-- There is some "basic" constant MySomething out of which you can build 
-- any other one using `fmap`.
unit :: MySomething ()
----- Monad -----
bind :: MySomething a -> (a -> MySomething b) -> MySomething b
join :: MySomething (MySomething a) -> MySomething a
----- Traversable -----
traverse :: Applicative f => (a -> f b) -> MySomething a -> f (MySomething b)
sequence :: Applicative f => MySomething (f a) -> f (MySomething a)
Note four things:
Applicative may be less famous than Monad, yet it's a very important and valuable class—arguably the centerpiece of the API!  A lot of things that people originally used Monad for actually only require Applicative. It's a good practice not to use Monad if Applicative will do.Traversable—a lot of functions that were originally written for Monad (sequence, mapM) in fact only require Traversable + Applicative.Monad is by first discovering that it's an Applicative and then asking whether it's also a Monad.A big step forward for me in my understanding of monads was the post Monads are Trees with Grafting. If your type looks like a tree, and the t values appear at the leaves, then you may have a monad on your hands.
Some data types are obviously trees, for example the Maybe type
data Maybe a = Nothing | Just a
which either has a null leaf, or a leaf with a single value. The list is another obvious tree type
data List a = Nil | Cons a (List a)
which is either a null leaf, or a leaf with a single value and another list. An even more obvious tree is the binary tree
data Tree a = Leaf a | Bin (Tree a) (Tree a)
with values at the leaves.
However, some types don't look like trees at first glance. For example, the 'reader' monad (aka function monad or environment monad) looks like
data Reader r a = Reader { runReader :: r -> a }
Doesn't look like a tree at the moment. But let's specialize to a concrete type r, for example Bool --
data ReaderBool a = ReaderBool (Bool -> a)
A function from Bool to a is equivalent to a pair (a,a) where the left element of the pair is the value of the function on True and the right argument is the value on False --
data ReaderBool a = ReaderBool a a
which looks a lot more like a tree with only one type of leaf - and indeed, you can make it into a monad
instance Monad ReaderBool where
    return a = ReaderBool a a
    ReaderBool a b >>= f = ReaderBool a' b'
      where
        ReaderBool a' _ = f a
        ReaderBool _ b' = f b
The moral is that a function r -> a can be viewed as a big long tuple containing many values of type a, one for each possible input - and that tuple can be viewed as the leaf of a particularly simple tree.
The state monad is another example of this type
data State s a = State { runState :: s -> (a, s) }
where you can view s -> (a, s) as a big tuple of values of type (a, s) -- one for possible input of type s.
One more example - a simplified IO action monad
data Action a = Put String (Action a)
              | Get (String -> Action a)
              | Return a
This is a tree with three types of leaf -- the Put leaf which just carries another action, the Get leaf, which can be viewed as an infinite tuple of actions (one for each possible String input) and a simple Return leaf that just carries a single value of type a. So it looks like it might be a monad, and indeed it is
instance Monad Action where
  return = Return
  Put s a  >>= f = Put s (a >>= f)
  Get g    >>= f = Get (\s -> g s >>= f)
  Return a >>= f = f a
Hopefully that's given you a little bit of intuition.
Thinking of monads as trees, the return operation as a way of getting a simple tree with one value, and the >>= operation as a way replacing the elements at the leaves of the tree with new trees, can be a powerful unifying way to look at monads.
It's worth mentioning that there isn't a direct way of noticing something is a Monad—instead it's a process you go through when you suspect something may be a Monad to prove that your suspicion is correct.
That said, there are ways to improve your sensitivity to Monads.
For any type T, a law-abiding instance Monad T implies that there's a law-abiding instance Applicative T and a law-abiding instance Functor T. Oftentimes Functor is easier to detect (or disprove) than Monad. Some computations can be easily detected by their Applicative structure before seeing that they're also a Monad.
For concreteness, here's how you prove any Monad is a Functor and an Applicative
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
newtype Wrapped m a = W { unW :: m a } -- newtype lets us write new instances
  deriving ( Monad )
instance Monad m => Functor (Wrapped m) where
  fmap f (W ma) = W (ma >>= return . f)
instance Monad m => Applicative (Wrapped m) where
  pure = W . return
  W mf <*> W mx = W $ do
    f <- mf
    x <- mx
    return (f x)
Generally, the best resource available for understanding this hierarchy of types is the Typeclassopedia. I cannot recommend reading it enough.
There's a pretty standard set of simple monads that any intermediate Haskell programmer should be immediately familiar with. These are Writer, Reader, State, Identity, Maybe, and Either, Cont, and []. Frequently, you'll discover your type is just a small modification of one of these standard monads and thus can be made a monad itself in a way similar to the standard.
Further, some Monads, called transformers, "stack" to form other Monads. What this means concretely is that you can combine a (modified form of the) Reader monad and a Writer monad to form the ReaderWriter monad. These modified forms are exposed in the transformers and mtl packages and are usually demarcated by an appended T. Concretely, you can define ReaderWriter using standard transformers from transformers like this
import Control.Monad.Trans.Reader
import Control.Monad.Writer
newtype ReaderWriter r w a = RW { unRW :: ReaderT r (Writer w) a }
  deriving Monad
-- Control.Monad.Trans.Reader defines ReaderT as follows
--
--     newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
--
-- the `m` is the "next" monad on the transformer stack
Once you learn transformers you'll find that even more of your standard types are just stacks of basic monads and thus inherit their monad instance from the tranformer's monad instance. This is a very power method for both building and detecting monads.
To learn these, it's best to just study the modules in the transformers and mtl packages.
Monads are often introduced in order to provide explicit sequencing of actions. If you're writing a type which requires a concrete representation of a sequence of actions, you may have a monad on your hands—but you might also just have a Monoid.
See this previous answer of mine for a rather in-depth discussion of how a certain sequence could be written as a Monad... but derived no advantage from doing so.. Sometimes a sequence is just a list.
Sometimes you'll have a data type which is not obviously a monad, but is obviously something that depends upon a monad instance. A common example is parsing where it might be obvious that you need to have a search that follows many alternatives but it's not immediately clear that you can form a monad from this.
But if you're familiar with Applicative or Monad you know that there are the Alternative and MonadPlus classes
instance Monad m => MonadPlus m where ...
instance Applicative f => Alternative f where ...
which are useful for structure computations which take alternatives. This suggests that maybe there's way to find a monad structure in your type!
There's a notion of the free monad on a functor. This terminology is very category theory-esque but it's actually a very useful concept because any monad can be thought of as interpreting a related free monad. Furthermore, free monads are relatively simple structures and thus it's easier to get an intuition for them. Be aware that this stuff is fairly abstract and it can take a bit of effort to digest, though.
The free monad is defined as follows
data Free f a = Pure a
              | Fix (f (Fix f a))
which is just the fixed point of our functor f adjoined to a Pure value. If you study type fixpoints (see the recursion-schemes package or Bartosz Milewski's Understanding F-algebras for more) you'll find that the Fix bit just defines any recursive data type and the Pure bit allows us to inject "holes" into that regular type which are filled by as.
The (>>=) for a Free Monad is just to take one of those as and fill its hole with a new Free f a.
(>>=) :: Free f a -> (a -> Free f a) -> Free f a
Pure a >>= g = g a
Fix fx >>= g = Fix (fmap (>>= g) fx) -- push the bind down the type
This notion is very similar to Chris Taylor's answer---Monads are just tree-like types where (>>=) grafts new tree-like parts where leaves used to be. Or, as I described it above, Monads are just regular types with Pure holes that can be filled later.
Free monads have a lot more depth in their abstractness, so I'd recommend Gabriel Gonzalez's Purify your code with free monads article which shows you how to model complex computation using free monads.
The final trick I'm going to suggest combines the notion of the free monad and the notion of sequencing and is the basis for new generic monad packages like extensible-effects.
One way to think of monads is as a set of instructions executed in sequence. For instance, the State monad might be the instructions
Get :: State s s
Put :: s -> State s ()
Which we can represent concretely as a Functor in a slightly unintuitive manner
data StateF s x = Get (s -> x) | Put s x deriving Functor
The reason we introduce that x parameter is because we're going to sequence StateF operations by forming the fixed-point of StateF. Intuitively this is as if we replaced that x by StateF itself so that we could write a type like
modify f = Get (\s -> Put (f s) (...))
where the (...) is the next action in the sequence. Instead of continuing that forever, we use the Pure constructor from the free monad above. To do so we also have to mark the non-Pure bits with Fix
-- real Haskell now
modify f = Fix (Get $ \s -> Fix (Put (f s) (Pure ()))
This mode of thinking carries on a lot further and I'll again direct you to Gabriel's article.
But what you can take away right now is that sometimes you have a type which indicates a sequence of events. This can be interpreted as a certain kind of canonical way of representing a Monad and you can use free to build the Monad in question from your canonical representation. I frequently use this method to build "semantic" monads in my applications like the "database access monad" or the "logging" monad.