ua-parser-0.7.5.0: A library for parsing User-Agent strings, official Haskell port of ua-parser

Safe HaskellNone
LanguageHaskell2010

Web.UAParser

Contents

Synopsis

Parsing browser (user agent)

parseUA :: ByteString -> Maybe UAResult Source #

Parse a given User-Agent string

parseUALenient :: ByteString -> UAResult Source #

Parser that, upon failure to match a pattern returns a result of family Other with all other fields blank. This is mainly for compatibility with the uap-core test suite

data UAResult Source #

Results datatype for the parsed User-Agent

Constructors

UAResult 

Instances

Eq UAResult Source # 
Data UAResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UAResult -> c UAResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UAResult #

toConstr :: UAResult -> Constr #

dataTypeOf :: UAResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UAResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UAResult) #

gmapT :: (forall b. Data b => b -> b) -> UAResult -> UAResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UAResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UAResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> UAResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UAResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UAResult -> m UAResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UAResult -> m UAResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UAResult -> m UAResult #

Read UAResult Source # 
Show UAResult Source # 
Generic UAResult Source # 

Associated Types

type Rep UAResult :: * -> * #

Methods

from :: UAResult -> Rep UAResult x #

to :: Rep UAResult x -> UAResult #

Default UAResult Source # 

Methods

def :: UAResult #

type Rep UAResult Source # 

uarVersion :: UAResult -> Text Source #

Construct a browser version-string from UAResult

Parsing OS

parseOS :: ByteString -> Maybe OSResult Source #

Parse OS from given User-Agent string

parseOSLenient :: ByteString -> OSResult Source #

Parser that, upon failure to match a pattern returns a result of family Other with all other fields blank. This is mainly for compatibility with the uap-core test suite

data OSResult Source #

Result type for parseOS

Constructors

OSResult 

Instances

Eq OSResult Source # 
Data OSResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OSResult -> c OSResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OSResult #

toConstr :: OSResult -> Constr #

dataTypeOf :: OSResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OSResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OSResult) #

gmapT :: (forall b. Data b => b -> b) -> OSResult -> OSResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OSResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OSResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> OSResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OSResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OSResult -> m OSResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OSResult -> m OSResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OSResult -> m OSResult #

Read OSResult Source # 
Show OSResult Source # 
Generic OSResult Source # 

Associated Types

type Rep OSResult :: * -> * #

Methods

from :: OSResult -> Rep OSResult x #

to :: Rep OSResult x -> OSResult #

Default OSResult Source # 

Methods

def :: OSResult #

type Rep OSResult Source # 

osrVersion :: OSResult -> Text Source #

Construct a version string from OSResult

Parsing Dev

parseDevLenient :: ByteString -> DevResult Source #

Parser that, upon failure to match a pattern returns a result of family Other with all other fields blank. This is mainly for compatibility with the uap-core test suite

data DevResult Source #

Result type for parseDev

Constructors

DevResult 

Instances

Eq DevResult Source # 
Data DevResult Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DevResult -> c DevResult #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DevResult #

toConstr :: DevResult -> Constr #

dataTypeOf :: DevResult -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DevResult) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DevResult) #

gmapT :: (forall b. Data b => b -> b) -> DevResult -> DevResult #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DevResult -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DevResult -> r #

gmapQ :: (forall d. Data d => d -> u) -> DevResult -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DevResult -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DevResult -> m DevResult #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DevResult -> m DevResult #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DevResult -> m DevResult #

Read DevResult Source # 
Show DevResult Source # 
Generic DevResult Source # 

Associated Types

type Rep DevResult :: * -> * #

Default DevResult Source # 

Methods

def :: DevResult #

type Rep DevResult Source # 
type Rep DevResult = D1 * (MetaData "DevResult" "Web.UAParser" "ua-parser-0.7.5.0-7ZG3g9ylC7CKleP4pW55aZ" False) (C1 * (MetaCons "DevResult" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "drFamily") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)) ((:*:) * (S1 * (MetaSel (Just Symbol "drBrand") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "drModel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Text))))))