{-# OPTIONS_GHC -cpp #-}
{-# LANGUAGE CPP #-}

{-
Copyright (C) 2004 David Roundy

This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2, or (at your option)
any later version.

This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program; see the file COPYING.  If not, write to
the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
Boston, MA 02110-1301, USA.
-}

{-|

  Path resolving:

    * A URL contains the sequence @\":\/\/\"@.

    * A local filepath does not contain colons, except
      as second character (windows drives).

    * A path that is neither a URL nor a local file
      is an ssh-path.

  Examples:

  > /usr/repo/foo                 -- local file
  > c:/src/darcs                  -- local file
  > http://darcs.net/             -- URL
  > peter@host:/path              -- ssh
  > droundy@host:                 -- ssh
  > host:/path                    -- ssh

  This means that single-letter hosts in ssh-paths do not work,
  unless a username is provided.

  Perhaps ssh-paths should use @\"ssh:\/\/user\@host\/path\"@-syntax instead?
-}

module Darcs.URL (
    isFile, isUrl, isSsh, isRelative, isAbsolute,
    isSshNopath
  ) where

#include "impossible.h"

isRelative :: String -> Bool
isRelative (_:':':_) = False
isRelative f@(c:_) = isFile f && c /= '/' && c /= '~'
isRelative "" = bug "Empty filename in isRelative"

isAbsolute :: String -> Bool
isAbsolute "" = bug "isAbsolute called with empty filename"
isAbsolute f = isFile f && (not $ isRelative f)

isFile :: String -> Bool
isFile (_:_:fou) = ':' `notElem` fou
isFile _ = True

isUrl :: String -> Bool
isUrl (':':'/':'/':_:_) = True
isUrl (_:x) = isUrl x
isUrl "" = False

isSsh :: String -> Bool
isSsh s = not (isFile s || isUrl s)

isSshNopath :: String -> Bool
isSshNopath s = case reverse s of
                  ':':x@(_:_:_) -> ':' `notElem` x
                  _ -> False